[Haskell-cafe] In-place modification
Hugh Perkins
hughperkins at gmail.com
Sat Jul 14 20:05:18 EDT 2007
On 7/15/07, Derek Elkins <derek.a.elkins at gmail.com> wrote:
>
> Read http://www.cs.hmc.edu/~oneill/papers/Sieve-JFP.pdf
>
Ok, so switched to using the Data.Map version from this paper, which looks
like a lazy, but real, version of the sieve of Arostothenes.
This does run quite a lot faster, so we're going to run on a sieve of
1000000 to increase the timings a bit (timings on 200000 in C# are a bit
inaccurate...).
Here are the results:
J:\dev\haskell>ghc -O2 -fglasgow-exts -o Prime2.exe Prime2.hs
J:\dev\haskell>prime2
number of primes: 78493
19.547
J:\dev\test\testperf>csc /nologo primecs.cs
J:\dev\test\testperf>primecs
number of primes: 78498
elapsed time: 0,0625
So, only 300 times faster this time ;-)
Here's the Haskell code:
module Main
where
import IO
import Char
import GHC.Float
import List
import qualified Data.Map as Map
import Control.Monad
import System.Time
import System.Locale
sieve xs = sieve' xs Map.empty
where
sieve' [] table = []
sieve' (x:xs) table =
case Map.lookup x table of
Nothing -> ( x : sieve' xs (Map.insert (x*x) [x] table) )
Just facts -> (sieve' xs (foldl reinsert (Map.delete x table)
facts))
where
reinsert table prime = Map.insertWith (++) (x+prime) [prime]
table
calculateNumberOfPrimes :: Int -> Int
calculateNumberOfPrimes max = length (sieve [ 2.. max ])
gettime :: IO ClockTime
gettime = getClockTime
main = do starttime <- gettime
let numberOfPrimes = (calculateNumberOfPrimes 1000000)
putStrLn( "number of primes: " ++ show( numberOfPrimes ) )
endtime <- gettime
let timediff = diffClockTimes endtime starttime
let secondsfloat = realToFrac( tdSec timediff ) +
realToFrac(tdPicosec timediff) / 1000000000000
putStrLn( show(secondsfloat) )
return ()
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20070715/9c0c0295/attachment.htm
More information about the Haskell-Cafe
mailing list