Send Beginners mailing list submissions to
        [email protected]

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        [email protected]

You can reach the person managing the list at
        [email protected]

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Is foldr slow? (Zhi-Qiang Lei)
   2. Re:  Is foldr slow? (Chadda? Fouch?)


----------------------------------------------------------------------

Message: 1
Date: Fri, 3 Feb 2012 00:16:35 +0800
From: Zhi-Qiang Lei <[email protected]>
Subject: [Haskell-beginners] Is foldr slow?
To: Haskell Beginer <[email protected]>
Message-ID: <[email protected]>
Content-Type: text/plain; charset="us-ascii"

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
[email protected]

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

------------------------------

Message: 2
Date: Thu, 2 Feb 2012 22:36:48 +0100
From: Chadda? Fouch? <[email protected]>
Subject: Re: [Haskell-beginners] Is foldr slow?
To: Zhi-Qiang Lei <[email protected]>
Cc: Haskell Beginer <[email protected]>
Message-ID:
        <CANfjZRYrfviUeTxdD+Rzc=s6-ze1ams3uvkfgnx1qtegbb3...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Thu, Feb 2, 2012 at 5:16 PM, Zhi-Qiang Lei <[email protected]> wrote:
> 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".
>

let go a b = b `minus` (multiplies a c)
foldr go cs' (p:p':ps) ==> foldr go cs' (p':ps) `minus` multiplies p c
==> (minus needs his first argument to start removing stuff) (foldr go
cs' ps `minus` multiplies p' c) `minus` multiplies p c
And so on and so forth...
In other words, contrary to your first version, this function must
develop the entire list before making its first suppression...

Your version rather correspond to a foldl (be careful of strictness,
using foldl it's pretty easy to get big thunks).

Foldr is very useful for functions that are lazy in their second
argument like (||) , (&&),  (:) or others but if the function is
strict in its second argument like yours (strict in b)...

-- 
Jeda?



------------------------------

_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 44, Issue 3
****************************************

Reply via email to