[Haskell-beginners] Question about time consume when calculate prime numbers

Yi Cheng chengyidna at gmail.com
Wed Sep 12 10:06:16 CEST 2012


Recently, I'm trying to solve some problems in project euler using haskell.
When it came to problem 10, calculating the sum of all primes below
20000000, I try to write a program which can generate primes.
In my memory Eratosthenes is faster than just whether a number can be
divided by the number less then the square root of it.
Firstly, I wrote the following programs:

module Main where
isPrime x = isPrime' 3 x (round . sqrt. fromIntegral $ x)
isPrime' d target maxd
  | d > maxd = True
  | mod target d == 0 = False
  | otherwise = isPrime' (d + 2) target maxd

main = print $ (sum (filter isPrime [3,5..2000000]) + 2)

And it consume about 11s in my computer.
Then, I tried to figure out how to solve the problem by Eratosthenes, but
failed. Later, I find a program implemented by others, meeting my purpose
and I've used it to solve the problem:

primes :: [Int]
primes = primes' [2..]

primes' :: [Int] -> [Int]
primes' [] = []
primes' (n:ns) = n : primes' (filter (\v -> v `mod` n /= 0) ns)

solve x = sum $ primes' [2..x]

main = print $ solve 2000000

Well, although the code is beautiful, it is slow. Even waiting for a
minute, no answer was printed.

In C version, Eratosthenes is faster than the method implemented in my
earlier code, which only consume 0.3s(the earlier method consume 1.6s).

So I want to know, why Eratosthenes implemented in Haskell is slow than the
ugly code implemented by me.
Could anyone tell me?


Thank you
Yi Cheng
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20120912/9e22aeec/attachment.htm>


More information about the Beginners mailing list