[Haskell-cafe] In-place modification

Hugh Perkins hughperkins at gmail.com
Sat Jul 14 16:45:00 EDT 2007


On 7/14/07, Henk-Jan van Tuyl <hjgtuyl at chello.nl> wrote:
>
>
> There was some discussion about prime number generators earlier this year:
>    http://www.haskell.org/pipermail/haskell-cafe/2007-February/022347.html
>    http://www.haskell.org/pipermail/haskell-cafe/2007-February/022699.html
>
> Ok, so using the following code:

module Main
   where


import IO
import Char
import GHC.Float
import List
import Control.Monad
import System.Time
import System.Locale

sieve :: [Int] -> [Int]
sieve [] = []
sieve (p : xs) = p : sieve [x | x <- xs, x `mod` p > 0]

calculateNumberOfPrimes :: Int -> Int
calculateNumberOfPrimes max = 1 + length( sieve [ 3,5.. (max -1) ] )

gettime :: IO ClockTime
gettime = getClockTime

main = do starttime <- gettime
          let numberOfPrimes = (calculateNumberOfPrimes 200000)
          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 ()

With "200000" as the upper limit on the sieve, this gives:

O:\dev\haskell>ghc -fglasgow-exts -O2 -o prime.exe Prime.hs

O:\dev\haskell>prime
number of primes: 17984
8.734

For comparison, on the same machine, in C# this gives:

O:\dev\test\testperf>csc /nologo primecs.cs

O:\dev\test\testperf>primecs
number of primes: 17984
elapsed time: 0,015625

That's over 500 times faster ;-)

Here's the code in C#

using System;

class Primes
{

    public int  CalculateNumberOfPrimes( int maxprime )
    {
    bool[]IsNotPrime = new bool[ maxprime ];
        int NumberOfPrimes = 1;

        for( int i = 3; i < maxprime; i+= 2 )
        {
            if( !IsNotPrime [i] )
            {
                NumberOfPrimes++;
                for( int j = ( i << 1 ); j < maxprime; j+= i )
                {
            if( !IsNotPrime [j] )
                        IsNotPrime [ j] = true;
                }

            }
        }

        return NumberOfPrimes;
    }
}

class EntryPoint
{
    public static void Main()
    {
        System.DateTime start = System.DateTime.Now;

       int NumberOfPrimes = new Primes().CalculateNumberOfPrimes( 200000 );

       System.DateTime finish = System.DateTime.Now;
       double time = finish.Subtract( start ).TotalMilliseconds;;

       Console.WriteLine( "number of primes: " + NumberOfPrimes );
       Console.WriteLine( "elapsed time: " + ( time / 1000 ) );
    }
}
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20070714/a6c22d1c/attachment.htm


More information about the Haskell-Cafe mailing list