I am trying to solve the problem 2's complement here (sorry, it requires login, but anyone can login with FB/google account). The problem in short is to count the number of ones appearing in the 2's complement representation of all numbers in a given range [A, B] where A and B are within the 32-bit limits (231 in absolute value). I know my algorithm is correct (it's logarithmic in the bigger absolute value, since I already solved the problem in another language).
I am testing the code below on my machine and it's giving perfectly correct results. When it runs on the Amazon server, it gives a few wrong answers (obviously overflows) and also some stack overflows. This is not a bug in the logic here, because I test the same code on my machine on the same test inputs and get different results. For example, for the range [-1548535525, 662630637] I get 35782216444 on my machine, while according to the tests, my result is some negative overflow value.
The only problem I can think of, is that perhaps I am not using Int64 correctly, or I have a wrong assumption about it's operation.
Any help is appreciated. Code is here.
The stack overflows are a bug in the logic.
countOnes !a !b | a == b = countOnes' a
countOnes' :: Int64 -> Integer
countOnes' !0 = 0
countOnes' !a = (fromIntegral (a .&. 1)) + (countOnes' (a `shiftR` 1))
Whenever you call countOnes' with a negative argument, you get a nonterminating computation, since the shiftR is an arithmetic shift and not a logical one, so you always shift in a 1-bit and never reach 0.
But even with a logical shift, for negative arguments, you'd get a result 32 too large, since the top 32 bits are all 1.
Solution: mask out the uninteresting bits before calling countOnes',
countOnes !a !b | a == b = countOnes' (a .&. 0xFFFFFFFF)
There are some superfluous guards in countOnes,
countOnes :: Int64 -> Int64 -> Integer
countOnes !a !b | a > b = 0
-- From here on we know a <= b
countOnes !a !b | a == b = countOnes' (a .&. 0xFFFFFFFF)
-- From here on, we know a < b
countOnes !0 !n = range + leading + (countOnes 0 (n - (1 `shiftL` m)))
where
range = fromIntegral $ m * (1 `shiftL` (m - 1))
leading = fromIntegral $ (n - (1 `shiftL` m) + 1)
m = (getLog n) - 1
-- From here on, we know a /= 0
countOnes !a !b | a > 0 = (countOnes 0 b) - (countOnes 0 (a - 1))
-- From here on, we know a < 0,
-- the guard in the next and the last equation are superfluous
countOnes !a !0 | a < 0 = countOnes (maxInt + a + 1) maxInt
countOnes !a !b | b < 0 = (countOnes a 0) - (countOnes (b + 1) 0)
countOnes !a !b | a < 0 = (countOnes a 0) + (countOnes 0 b)
The integer overflows on the server are caused by
getLog :: Int64 -> Int
--
countOnes !0 !n = range + leading + (countOnes 0 (n - (1 `shiftL` m)))
where
range = fromIntegral $ m * (1 `shiftL` (m - 1))
leading = fromIntegral $ (n - (1 `shiftL` m) + 1)
m = (getLog n) - 1
because the server has a 32-bit GHC, while you have a 64-bit one. The shift distance/bit width m is an Int (and because it's used as the shift distance, it has to be).
Therefore
m * (1 `shiftL` (m-1))
is an Int too. For m >= 28, that overflows a 32-bit Int.
Solution: remove a $
range = fromIntegral m * (1 `shiftL` (m - 1))
Then the 1 that is shifted is an Integer, hence no overflow.
Related
I want to create a function as mentioned in the title. The specific is that it adds the digits in reversed order, you can see that in the test cases: 12 -> 1; 852369 -> 628; 1714 -> 11; 12345 -> 42; 891 -> 9; 448575 -> 784; 4214 -> 14
The main idea is that when the number is bigger than 99 it enters the helper function which has i - indicator if the the digit is on an even position, and res which stores the result. Helper begins to cycle n as it checks whether or not the current digit is on even position and adds it to the result.
So far I've tried the following code:
everyOther :: Int -> Int
everyOther n
| n < 10 = error "n must be bigger than 10 or equal"
| n < 100 = div n 10
| otherwise = helper n 0 0
where
helper :: Int -> Int -> Int -> Int
helper n i res
| n < 100 = res
| i == 1 = helper (div n 10) (i - 1) (res + (mod n 10)*10)
| otherwise = helper (div n 10) i res
Any help would be appreciated!
You can obtain the one but last digit of x with mod (div x 10) 10. You can use this with an accumulator that accumulates the value by each time multiplying with 10, so:
everyOther :: Int -> Int
everyOther = go 0
where go a v
| v < 10 = a
| otherwise = go (10*a + mod (div v 10) 10) (div v 100)
If v is thus less than 10, we can return the accumulator, since there is no "other digit" anymore. If that is not the case, we multiply a with 10, and add mod (div v 10) 10 to add the other digit to it, and recurse with the value divided by 100 to move it two places to the right.
We can improve this, as #Daniel Wagner says, by making use of quotRem :: Integral a => a -> a -> (a, a):
everyOther :: Int -> Int
everyOther = go 0
where go a v
| v < 10 = a
| otherwise = let (q, r) = v `quotRem` 100 in go (10*a + r `quot` 10) q
here we thus work with the remainder of a division by 100, and this thus avoids an extra modulo.
The number π can be calculated with the following infinite series sum:
I want to define a Haskell function roughlyPI that, given a natural number k, calculates the series sum from 0 to the k value.
Example: roughlyPi 1000 (or whatever) => 3.1415926535897922
What I did was this (in VS Code):
roughlyPI :: Double -> Double
roughlyPI 0 = 2
roughlyPI n = e1/e2 + (roughlyPI (n-1))
where
e1 = 2**(n+1)*(factorial n)**2
e2 = factorial (2*n +1)
factorial 0 = 1
factorial n = n * factorial (n-1)
but it doesn't really work....
*Main> roughlyPI 100
NaN
I don't know what's wrong. I'm new to Haskell, by the way.
All I really want is to be able to type in a number that will give me PI at the end. It can't be that hard...
As mentioned in the comments, we need to avoid large divisions and instead intersperse smaller divisions within the factorials. We use Double for representing PI but even Double has its limits. For instance 1 / 0 == Infinity and (1 / 0) / (1 / 0) == Infinity / Infinity == NaN.
Luckily, we can use algebra to simplify the formula and hopefully delay the blowup of our Doubles. By dividing within our factorial the numbers don't grow too unwieldy too quickly.
This solution will calculate roughlyPI 1000, but it fails on 1023 with NaN because 2 ^ 1024 :: Double == Infinity. Note how each iteration of fac has a division as well as a multiplication to help keep the numbers from blowing up. If you are trying to approximate PI with a computer, I believe there are better algorithms, but I tried to keep it as conceptually close to your attempt as possible.
roughlyPI :: Integer -> Double
roughlyPI 0 = 2
roughlyPI k = e + roughlyPI (k - 1)
where
k' = fromIntegral k
e = 2 ** (k' + 1) * fac k / (2 * k' + 1)
where
fac 1 = 1 / (k' + 1)
fac p = (fromIntegral p / (k' + fromIntegral p)) * fac (p - 1)
We can do better than having a blowup of Double after 1000 by doing computations with Rationals then converting to Double with realToFrac (credit to #leftaroundabout):
roughlyPI' :: Integer -> Double
roughlyPI' = realToFrac . go
where
go 0 = 2
go k = e + go (k - 1)
where
e = 2 ^ (k + 1) * fac k / (2 * fromIntegral k + 1)
where
fac 1 = 1 % (k + 1)
fac p = (p % (k + p)) * fac (p - 1)
For further reference see Wikipedia page on approximations of PI
P.S. Sorry for the bulky equations, stackoverflow does not support LaTex
First note that your code actually works:
*Main> roughlyPI 91
3.1415926535897922
The problem, as was already said, is that when you try to make the approximation better, the factorial terms become too big to be representable in double-precision floats. The simplest – albeit somewhat brute-force – way to fix that is to do all the computation in rational arithmetic instead. Because numerical operations in Haskell are polymorphic, this works with almost the same code as you have, only the ** operator can't be used since that allows fractional exponents (which are in general irrational). Instead, you should use integer exponents, which is anyway the conceptually right thing. That requires a few fromIntegral:
roughlyPI :: Integer -> Rational
roughlyPI 0 = 2
roughlyPI n = e1/e2 + (roughlyPI (n-1))
where
e1 = 2^(n+1)*fromIntegral (factorial n^2)
e2 = fromIntegral . factorial $ 2*n + 1
factorial 0 = 1
factorial n = n * factorial (n-1)
This now works also for much higher degrees of approximation, although it takes a long time to carry around the giant fractions involved:
*Main> realToFrac $ roughlyPI 1000
3.141592653589793
The way to go in such cases is to calculate the ratio of consecutive terms and calculate the terms by rolling multiplications of the ratios:
-- 1. -------------
pi1 n = Sum { k = 0 .. n } T(k)
where
T(k) = 2^(k+1)(k!)^2 / (2k+1)!
-- 2. -------------
ts2 = [ 2^(k+1)*(k!)^2 / (2k+1)! | k <- [0..] ]
pis2 = scanl1 (+) ts2
pi2 n = pis2 !! n
-- 3. -------------
T(k) = 2^(k+1)(k!)^2 / (2k+1)!
T(k+1) = 2^(k+2)((k+1)!)^2 / (2(k+1)+1)!
= T(k) 2 (k+1)^2 / (2k+2) (2k+3)
= T(k) (k+1)^2 / ( k+1) (2k+3)
= T(k) (k+1) / (k+1 + k+2)
= T(k) / (1 + (k+2)/(k+1))
= T(k) / (2 + 1 /(k+1))
-- 4. -------------
ts4 = scanl (/) 2 [ 2 + 1/(k+1) | k <- [0..]] :: [Double]
pis4 = scanl1 (+) ts4
pi4 n = pis4 !! n
This way we share and reuse the calculations as much as possible. This leads to the most efficient code, hopefully leading to the smallest cumulative numerical error. The formula also turned out to be exceptionally simple, and could even be simplified further as ts5 = scanl (/) 2 [ 2 + recip k | k <- [1..]].
Trying it out:
> pis2 = scanl1 (+) $ [ fromIntegral (2^(k+1))*fromIntegral (product[1..k])^2 /
fromIntegral (product[1..(2*k+1)]) | k <- [0..] ] :: [Double]
> take 8 $ drop 30 pis2
[3.1415926533011587,3.141592653447635,3.141592653519746,3.1415926535552634,
3.141592653572765,3.1415926535813923,3.141592653585647,3.141592653587746]
> take 8 $ drop 90 pis2
[3.1415926535897922,3.1415926535897922,NaN,NaN,NaN,NaN,NaN,NaN]
> take 8 $ drop 30 pis4
[3.1415926533011587,3.141592653447635,3.141592653519746,3.1415926535552634,
3.141592653572765,3.1415926535813923,3.141592653585647,3.141592653587746]
> take 8 $ drop 90 pis4
[3.1415926535897922,3.1415926535897922,3.1415926535897922,3.1415926535897922,
3.1415926535897922,3.1415926535897922,3.1415926535897922,3.1415926535897922]
> pis4 !! 1000
3.1415926535897922
I am writing some code to work with arbitrary radix numbers in haskell. They will be stored as lists of integers representing the digits.
I almost managed to get it working, but I have run into the problem of converting a list of tuples [(a_1,b_1),...,(a_n,b_n)] into a single list which is defined as follows:
for all i, L(a_i) = b_i.
if there is no i such that a_i = k, a(k)=0
In other words, this is a list of (position,value) pairs for values in an array. If a position does not have a corresponding value, it should be set to zero.
I have read this (https://wiki.haskell.org/How_to_work_on_lists) but I don't think any of these methods are suitable for this task.
baseN :: Integer -> Integer -> [Integer]
baseN n b = convert_digits (baseN_digits n b)
chunk :: (Integer, Integer) -> [Integer]
chunk (e,m) = m : (take (fromIntegral e) (repeat 0))
-- This is broken because the exponents don't count for each other's zeroes
convert_digits :: [(Integer,Integer)] -> [Integer]
convert_digits ((e,m):rest) = m : (take (fromIntegral (e)) (repeat 0))
convert_digits [] = []
-- Converts n to base b array form, where a tuple represents (exponent,digit).
-- This works, except it ignores digits which are zero. thus, I converted it to return (exponent, digit) pairs.
baseN_digits :: Integer -> Integer -> [(Integer,Integer)]
baseN_digits n b | n <= 0 = [] -- we're done.
| b <= 0 = [] -- garbage input.
| True = (e,m) : (baseN_digits (n-((b^e)*m)) b)
where e = (greedy n b 0) -- Exponent of highest digit
m = (get_coef n b e 1) -- the highest digit
-- Returns the exponent of the highest digit.
greedy :: Integer -> Integer -> Integer -> Integer
greedy n b e | n-(b^e) < 0 = (e-1) -- We have overshot so decrement.
| n-(b^e) == 0 = e -- We nailed it. No need to decrement.
| n-(b^e) > 0 = (greedy n b (e+1)) -- Not there yet.
-- Finds the multiplicity of the highest digit
get_coef :: Integer -> Integer -> Integer -> Integer -> Integer
get_coef n b e m | n - ((b^e)*m) < 0 = (m-1) -- We overshot so decrement.
| n - ((b^e)*m) == 0 = m -- Nailed it, no need to decrement.
| n - ((b^e)*m) > 0 = get_coef n b e (m+1) -- Not there yet.
You can call "baseN_digits n base" and it will give you the corresponding array of tuples which needs to be converted to the correct output
Here's something I threw together.
f = snd . foldr (\(e,n) (i,l') -> ( e , (n : replicate (e-i-1) 0) ++ l')) (-1,[])
f . map (fromIntegral *** fromIntegral) $ baseN_digits 50301020 10 = [5,0,3,0,1,0,2,0]
I think I understood your requirements (?)
EDIT:
Perhaps more naturally,
f xs = foldr (\(e,n) fl' i -> (replicate (i-e) 0) ++ (n : fl' (e-1))) (\i -> replicate (i+1) 0) xs 0
I need to determine a recursive function crosssum :: Int -> Int in Haskell to calculate the cross sum of positive numbers. I am not allowed to use any functions from the hierarchical library besides (:), (>), (++), (<), (>=), (<=), div, mod, not (&&), max, min, etc.
crosssum :: Int -> Int
cross sum x = if x > 0
then x `mod` 10
+ x `div` 10 + crosssum x
else 0
so whenever I fill in e.g. crosssum 12 it says 'thread killed'. I do not understand how to get this right. I would appreciate any ideas. Thx
One of the problems with your code is that x is not reduced (or changed somehow) when it's passed as an argument to the recursive call of crosssum. That's why your program never stops.
The modified code:
crosssum :: Int -> Int
crosssum x = if x > 0
then x `mod` 10 + crosssum (x `div` 10)
else 0
is going to have the following logic
crosssum 12 = 2 + (crosssum 1) = 2 + (1 + (crosssum 0)) = 2 + 1 + 0
By the way, Haskell will help you to avoid if condition by using pattern-matching to receive more readable code:
crosssum :: Int -> Int
crosssum 0 = 0
crosssum x =
(mod x 10) + (crosssum (div x 10))
divMod in Prelude is very handy, too. It's one operation for both div and mod, In fact for all 2 digit numbers dm n = sum.sequence [fst,snd] $ divMod n 10
cs 0 = 0; cs n = m+ cs d where (d,m) = divMod n 10
cs will do any size number.
I found myself having a case where the equivalent of floor $ 1/0 was being executed.
λ> 1/0
Infinity
This is normal behavior as far as I understand but, when Infinity is floor'd or ceiling'd
λ> floor $ 1/0
179769313486231590772930519078902473361797697894230657273430081157732675805500963132708477322407536021120113879871393357658789768814416622492847430639474124377767893424865485276302219601246094119453082952085005768838150682342462881473913110540827237163350510684586298239947245938479716304835356329624224137216
Instead of failing, this very big number is produced. Why?
Maybe more importantly, how can I distinguish this from a non faulty result without using a filter before applying another function?
The first question is perhaps not so important, so I'll try to answer the second question first.
Once you have a number, if you know that it came from floor x, you can't know whether x was the valid representation of 2^1024 or if it was infinity. You can probably assume anything outside of the range of double is invalid and was produced from infinity, negative infinity, NaN or the like. It would be quite simple to check if your value is valid using one/many of the functions in RealFloat, like isNaN, isInfinite, etc.
You could also use something like data Number a = N a | PosInf | NegInf. Then you write:
instance RealFrac a => RealFrac (Number a) where
...
floor (N n) = floor n
floor PosInf = error "Floor of positive infinity"
floor NegInf = error "Floor of negative infinity"
..
Which approach is best is based mostly on your use case.
Maybe it would be correct for floor (1/0) to be an error. But the value is garbage anyways. Is it better to deal with garbage or an error?
But why 2^1024? I took a look at the source for GHC.Float:
properFraction (F# x#)
= case decodeFloat_Int# x# of
(# m#, n# #) ->
let m = I# m#
n = I# n#
in
if n >= 0
then (fromIntegral m * (2 ^ n), 0.0)
else let i = if m >= 0 then m `shiftR` negate n
else negate (negate m `shiftR` negate n)
f = m - (i `shiftL` negate n)
in (fromIntegral i, encodeFloat (fromIntegral f) n)
floor x = case properFraction x of
(n,r) -> if r < 0.0 then n - 1 else n
Note that decodeFloat_Int# returns the mantissa and exponent. According to wikipedia:
Positive and negative infinity are represented thus: sign = 0 for
positive infinity, 1 for negative infinity. biased exponent = all 1
bits. fraction = all 0 bits.
For Float, this means a base of 2^23, since there are 23 bits in the base, and an exponent of 105 (why 105? I actually have no idea. I would think it should be 255 - 127 = 128, but it seems to actually be 128 - 23). The value of floor is fromIntegral m * (2 ^ n) or base*(2^exponent) == 2^23 * 2^105 == 2^128. For double this value is 1024.