[Haskell-cafe] In-place modification
Sebastian Sylvan
sebastian.sylvan at gmail.com
Sun Jul 15 08:21:37 EDT 2007
On 15/07/07, Donald Bruce Stewart <dons at cse.unsw.edu.au> wrote:
> hughperkins:
> >
> > Hey, I just realized I can shave off another 30% in C# ;-)
> > So now the timings become:
>
> Ok. So do the same thing to the Haskell program. The compilers should
> produce pretty much identical assembly.
>
>
> {-# OPTIONS -O2 -optc-O -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 10000000)
>
> pureSieve :: Int -> Int
> pureSieve n = runST( sieve n )
>
> sieve n = do
> a <- newArray (0,n-1) True :: ST s (STUArray s Int Bool)
> let cutoff = truncate (sqrt (fromIntegral n)) + 1
> go a n cutoff 2 0
>
> go !a !m cutoff !n !c
> | n == m = return c
> | otherwise = do
> e <- unsafeRead a n
> if e then
> if n < cutoff
> then let loop !j
> | j < m = do
> x <- unsafeRead a j
> when x $ unsafeWrite a j False
Surely you can remove the read here, and just always do the write?
--
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
More information about the Haskell-Cafe
mailing list