[Haskell] Haskell fast (?) arrays

Donald Bruce Stewart dons at cse.unsw.edu.au
Tue May 1 23:38:25 EDT 2007


federico.squartini:
> Sorry, I was very silly!
> 
> This is the correct version of the program using the doFromto loop.
> And it runs fast! I hope there are no further mistakes.
> Thanks Axel.
> 
> time ./IOMutUnbUnsafe
> 499
> real	0m0.708s
> user	0m0.573s
> sys	0m0.008s

Here's an improved version, using Foreign.Marshal.Array. I spent about 2
minutes inspecting the core, as well.

Before, with your IOUArray version:

    $ time ./T
    499
    ./T  1.46s user 0.02s system 97% cpu 1.515 total

with the new version:

    $ time ./S
    499
    ./S  1.15s user 0.01s system 99% cpu 1.168 total

Here's the source, its more idiomatic high-perf Haskell, I'd argue.

Cheers,
  Don

------------------------------------------------------------------------


{-# OPTIONS -O2 -optc-O -optc-march=pentium4 -fbang-patterns #-}

import Control.Monad
import Foreign.Marshal.Array
import Foreign

total :: Int
total = 500001

type Arr = Ptr Int

testArray :: IO Arr
testArray = do
    u <- mallocArray total :: IO Arr
    forM_ [0 .. total] $ \i -> pokeElemOff u i ((19*i+23) `mod` 911)
    return u

reverseArray :: Arr -> Int -> Int -> IO ()
reverseArray !p !i !j
    | i < j = do
        x <- peekElemOff p i
        y <- peekElemOff p j
        pokeElemOff p i y
        pokeElemOff p j x
        reverseArray p (i+1) (j-1)
    | otherwise = return ()

sumArrayMod :: Arr -> Int -> Int -> IO Int
sumArrayMod !p !s !i
    | i < total = do
        x <- peekElemOff p i
        sumArrayMod p ((s + x) `rem` 911) (i+1)
    | otherwise = return s

main :: IO ()
main = do
    a <- testArray
    replicateM_ 120 (reverseArray a 0 (total-1))
    print =<< sumArrayMod a 0 0



More information about the Haskell mailing list