[Haskell-cafe] Efficiency question

Evil Bro rwiggerink at hotmail.com
Sun May 27 06:01:02 EDT 2007


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.



More information about the Haskell-Cafe mailing list