On 15/07/07, Hugh Perkins <[EMAIL PROTECTED]> wrote:
On 7/15/07, Sebastian Sylvan <[EMAIL PROTECTED]> wrote:
> I don't see what the point of this is? Why do timings of different
> algorithms? Of course you could do the same optimization in any
> language, so why do you think it's relevant to change the algorithm in
> *one* of the languages and then make comparisons?
>

Sebastien,

Well, as you yourself said, different languages work differently, so there's
no point in trying to directly implement the C# algorithm in Haskell: it
just wont work, or it will be slow.  The same works from Haskell to C#.

So, you guys are Haskell experts, show the world what Haskell is capable of.
 Come up with algorithms to calculate prime numbers in Haskell that are:
- safe
- easy to understand/read/maintain
- fast

 I'll ditch the "sieve of arastophenes" rule if you like.  Use any algorithm
you like.  Now that is fair I think?

I in turn will do my part to keep the C# version a step ahead of the Haskell
version.  It seems this is pretty easy :-D

Try this one then. I removed the unsafe reads...
Still, I think youre methodology sucks. If you want to compare
languages you should implement the same algorithm. Dons implemented a
Haskell version of your C++ algorithm, even though it wasn't optimal.
He didn't go off an implement some state-of-the-art primes algorithm
that was completey different now did he?
If this is about comparing languages, you should compare them fairly.

{-# OPTIONS -O2 -fbang-patterns #-}

import Control.Monad.ST
import Data.Array.ST
import Data.Array.Base
import System
import Control.Monad

import System.Time
import System.Locale


main = do starttime <- getClockTime
         let numberOfPrimes = (pureSieve 17984)
         putStrLn( "number of primes: " ++ show( numberOfPrimes ) )
         endtime <- getClockTime
         let timediff = diffClockTimes endtime starttime
         let secondsfloat = realToFrac( tdSec timediff ) +
realToFrac(tdPicosec timediff) / 1000000000000
         putStrLn( "Elapsed time: " ++ show(secondsfloat) )
         return ()

pureSieve :: Int -> Int
pureSieve n = runST( sieve n )

sieve n = do
        a <- newArray (2,n) True :: ST s (STUArray s Int Bool) -- an array of 
Bool   
        go a n 2 0

go !a !m !n !c
      | n == m    = return c
      | otherwise = do
              e <- readArray a n
              if e then let loop !j
                              | j < m     = do
                                  writeArray a j False
                                  loop (j+n)

                              | otherwise = go a m (n+1) (c+1)
                        in loop (n * n)
                   else go a m (n+1) c


--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to