Bulat Ziganshin wrote:

Wednesday, January 18, 2006, 3:33:40 PM, you wrote:

SMH> and gets a runtime for the GHC-compiled binary that's about 10x as long
SMH> as for GCC. Simon M. tells me this should be much better. Here are the

attached version is only 5 times slower :)  please note that

1) unsafeRead/Write indexes from 0 and don't checks bounds (just C-like :)
2) generating random values takes about 1.5-2 seconds by itself.
Haskell's RNG is very different from C's one

I squeezed a bit more out (see attached). I think the main bottleneck is now the random number generator, in particular it is supplying boxed Doubles which have to be unboxed again before storing in the array.

Cheers,
        Simon
import Data.Array.IO
import Data.Array.Base
import System.Environment (getArgs)
import System.Random

type Vector = IOUArray Int Double

main = do  (n:f:m:_) <- getArgs
           let  (nelems,niterations) = case f of
                    "elements"    -> (read n, read m)
                    "iterations"  -> (read m, read n)

           x <- newArray (0,nelems-1) 0 :: IO Vector
           v <- newArray_ (0,nelems-1) :: IO Vector

           x `seq` v `seq` return ()

           for 0 nelems $ \i ->
             do  r <- randomRIO (-1,1)
                 unsafeWrite v i r

           for 0 niterations $ \_ ->
             for 0 nelems $ \i ->
               do  xi <- unsafeRead x i
                   vi <- unsafeRead v i
                   unsafeWrite x i (xi+vi)

           --for 0 nelems $ \i ->
           --  do  xi <- unsafeRead x i
           --      putStr (show xi)
           --      putChar ' '
           --putChar '\n'

for :: Int -> Int -> (Int -> IO a) -> IO ()
-- Faster equivalent of "mapM_ action [from..to-1]"
for from to action | from `seq` to `seq` False = undefined
for from to action  = go from
  where
    go i | i>=to      = return ()
         | otherwise = do action i
                          go $! (i+1)
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to