[Haskell-cafe] Efficiency question

Donald Bruce Stewart dons at cse.unsw.edu.au
Wed May 30 02:48:44 EDT 2007


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


More information about the Haskell-Cafe mailing list