
I'm pretty new to Haskell, so forgive me if my question is due to my non-functional way of thinking... I have the following code: module Main where main = print solution solution = solve 1000000 solve d = countUniqueFractions d 2 1 0 canBeSimplified (a,b) = gcd a b > 1 countUniqueFractions stopD currentD currentN count | currentD > stopD = count | currentN == currentD = countUniqueFractions stopD (currentD + 1) 1 count | canBeSimplified (currentN, currentD) = countUniqueFractions stopD currentD (currentN+1) count | otherwise = countUniqueFractions stopD currentD (currentN+1) (count + 1) When I run this code, I get a stack overflow. I don't understand why. Could anyone explain please? -- View this message in context: http://www.nabble.com/Efficiency-question-tf3823154.html#a10823572 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

rwiggerink:
I'm pretty new to Haskell, so forgive me if my question is due to my non-functional way of thinking...
I have the following code:
module Main where
main = print solution
solution = solve 1000000
solve d = countUniqueFractions d 2 1 0
canBeSimplified (a,b) = gcd a b > 1
countUniqueFractions stopD currentD currentN count | currentD > stopD = count | currentN == currentD = countUniqueFractions stopD (currentD + 1) 1 count | canBeSimplified (currentN, currentD) = countUniqueFractions stopD currentD (currentN+1) count | otherwise = countUniqueFractions stopD currentD (currentN+1) (count + 1)
When I run this code, I get a stack overflow. I don't understand why. Could anyone explain please?
Lazy accumulators. Did you try compiling with ghc -O2 ? -- Don

On Sun, 27 May 2007, Evil Bro wrote:
I'm pretty new to Haskell, so forgive me if my question is due to my non-functional way of thinking...
I have the following code:
Counting can be done elegantly by 'filter' and 'length': length $ filter (>1) $ Monad.liftM2 gcd [2..1000] [2..1000]

Counting can be done elegantly by 'filter' and 'length': I figured out the following code after posting:
solve d = length [(y,x) | x <- [2..d], y <- [1..(x-1)], gcd x y == 1] main = print (solve 1000000) However when running it, it gave an answer of -1255316543. How on earth can a length be negative?
length $ filter (>1) $ Monad.liftM2 gcd [2..1000] [2..1000] Thanks... now I'll just have to figure out what it does and why it does what it does.
-- View this message in context: http://www.nabble.com/Efficiency-question-tf3823154.html#a10873232 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Evil Bro wrote:
Counting can be done elegantly by 'filter' and 'length': I figured out the following code after posting:
solve d = length [(y,x) | x <- [2..d], y <- [1..(x-1)], gcd x y == 1] main = print (solve 1000000)
However when running it, it gave an answer of -1255316543. How on earth can a length be negative?
Yu got an integer overflow - length returns an Int. You can use Data.List.genericLength instead, however, which can return its result in any Num instance. (In particular, Integer works)
import Data.List
solve :: Integer -> Integer solve d = genericLength [(y,x) | x <- [2..d], y <- [1..(x-1)], gcd x y == 1]
main = print (solve 1000000)
(Note: untested.) HTH, Bertram
participants (4)
-
Bertram Felgenhauer
-
dons@cse.unsw.edu.au
-
Evil Bro
-
Henning Thielemann