On 15/07/07, Donald Bruce Stewart <[EMAIL PROTECTED]> wrote:
hughperkins:
>
>    On 7/15/07, Donald Bruce Stewart <[EMAIL PROTECTED]>
>    wrote:
>    > [snip] unsafeWrite[snip]
>    > [snip]unsafeRead[snip]
>    Hi Donald, the idea is to use this for operational code, so
>    avoiding unsafe operations is preferable ;-)  You'll note
>    that the C# version is not using unsafe operations, although
>    to be fair that's because they worked out slower than the
>    safe version ;-)

"unsafe"' here just means direct array indexing. Same as the other
languages. Haskell's 'unsafe' is a little more paranoid that other
languages.

>    Also, the whole algorithm is bound to the IO Monad, which is
>    something I'd like to avoid if possible, since my entire
>    interest in Haskell stems from the possibilites of running
>    programs easily on 1 megacore processors in the future.

You're deciding that on a cache-thrashing primes benchmark?

Since the goal is to flip bits very quickly in the cache, you could
localise this to the ST monad then, as its perfectly pure on the
outside.

Yep:

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

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


main = print ( pureSieve 17984 )

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 <- unsafeRead a n
              if e then let loop !j
                              | j < m     = do
                                  x <- unsafeRead a j
                                  when x (unsafeWrite a j False)
                                  loop (j+n)

                              | otherwise = go a m (n+1) (c+1)
                        in loop (n `shiftL` 1)
                   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