[Haskell-beginners] Is foldr slow?

Zhi-Qiang Lei zhiqiang.lei at gmail.com
Thu Feb 2 17:16:35 CET 2012


Hi,

When I refactor my Segmented Seive of Eratosthenes, I'm puzzled by the performance of "foldr".
Here is my original code. I realized that "sieveWith"(Integral a => ([a], [a]) -> ([a], [a]), it takes a tuple with sieving primes and prime candidates, and remove all multiplies of sieving primes in candidates, at last return a tuple with blank sieving primes and a pure primes list) in "primesFromTo" is not much readable and can be replaced by "foldr".

But when I did, I find it would take about 5 seconds to sieve primes between 999900000 and 1000000000, whereas the original one just takes 1.6 
seconds. The "sieveWith" function is the only place I change. I also have tried foldr', which does not much help. Is foldr slow? Or did I make any 
mistake? Thanks.

=== Origin (./main < data1.txt  1.45s user 0.11s system 99% cpu 1.562 total) ===
{-# OPTIONS_GHC -O2 #-}

import Data.List
import System.IO

minus (x:xs) (y:ys) = case (compare x y) of 
           LT -> x : minus  xs  (y:ys)
           EQ ->     minus  xs     ys 
           GT ->     minus (x:xs)  ys
minus  xs     _     = xs

intSqrt :: Integral a => a -> a
intSqrt = floor . sqrt . fromIntegral

primesTo :: Integral a => a -> [a]
primesTo x = 2 : sieve [3, 5 .. x] where
    sieve ns@(n : rs)
        | n <= intSqrt x    = n : sieve (rs `minus` [n * n, n * (n + 2) .. x])
        | otherwise         = ns
    sieve [] = []

candidatesBetween :: Integral a => a -> a -> [a]
candidatesBetween x y = let x' = if odd x then x else x + 1 in [x', x' + 2 .. y]

primesFromTo :: Integral a => a -> a -> [a]
primesFromTo x y
    | x < 2 = primesTo y
    | otherwise = snd . sieveWith $ (primes, candidates) where
        primes = tail . primesTo . intSqrt $ y
        candidates = candidatesBetween x y
        sieveWith (a : as, bs'@(b : bs)) = sieveWith (as, bs' `minus` multiplies a b) where
        sieveWith ([], bs) = ([], bs)
        multiplies a b = let b' = b + ((-b) `mod` a) in [b', b' + 2 * a .. y]

primesFromTo' [x, y] = primesFromTo x y

main :: IO ()
main = do
    count <- fmap read getLine
    inputLines <- fmap (take count . lines) getContents
    let answers = map (primesFromTo' . map read . words) inputLines
    putStr . unlines . map (unlines . map show) $ answers

=== Origin ===

=== New (./main < data1.txt  4.76s user 0.15s system 99% cpu 4.917 total) ===
{-# OPTIONS_GHC -O2 #-}

import Data.List
import System.IO

minus (x:xs) (y:ys) = case (compare x y) of 
           LT -> x : minus  xs  (y:ys)
           EQ ->     minus  xs     ys 
           GT ->     minus (x:xs)  ys
minus  xs     _     = xs

intSqrt :: Integral a => a -> a
intSqrt = floor . sqrt . fromIntegral

primesTo :: Integral a => a -> [a]
primesTo x = 2 : sieve [3, 5 .. x] where
    sieve ns@(n : rs)
        | n <= intSqrt x    = n : sieve (rs `minus` [n * n, n * (n + 2) .. x])
        | otherwise         = ns
    sieve [] = []

candidatesBetween :: Integral a => a -> a -> [a]
candidatesBetween x y = let x' = if odd x then x else x + 1 in [x', x' + 2 .. y]

primesFromTo :: Integral a => a -> a -> [a]
primesFromTo x y
    | x < 2 = primesTo y
    | otherwise = sieveWith primes candidates where
        primes = tail . primesTo . intSqrt $ y
        candidates = candidatesBetween x y
        -- sieve a list of candidates with sieving primes
        -- foldr version: ./main < data1.txt  4.76s user 0.15s system 99% cpu 4.917 total
        sieveWith ps'@(p : ps) cs'@(c : cs) = foldr (\a b -> b `minus` (multiplies a c)) cs' ps'
        sieveWith [] cs = cs
        multiplies a b = let b' = b + ((-b) `mod` a) in [b', b' + 2 * a .. y]

primesFromTo' [x, y] = primesFromTo x y

main :: IO ()
main = do
    count <- fmap read getLine
    inputLines <- fmap (take count . lines) getContents
    let answers = map (primesFromTo' . map read . words) inputLines
    putStr . unlines . map (unlines . map show) $ answers

=== New ===

Best regards,
Zhi-Qiang Lei
zhiqiang.lei at gmail.com

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20120203/ff850794/attachment.htm>


More information about the Beginners mailing list