[Haskell] Haskell fast (?) arrays
Federico Squartini
federico.squartini at googlemail.com
Tue May 1 11:01:23 EDT 2007
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
-----------------------------------------------------------------------------
-- compile with
-- ghc --make -o IOMutUnbUnsafe IOMutUnbUnsafe.hs
module Main
where
import Monad
import Data.Array.IO
import Data.Array.MArray
import Data.Array.Unboxed
import Data.Array.Base ( unsafeWrite, unsafeRead )
total, semiTotal ::Int
total= 500000
semiTotal=250000
testArray :: IO (IOUArray Int Int)
testArray = newListArray (0,total) [(19*i+23) `mod` 911 |i <- [0..total]]
reverseArray :: IOUArray Int Int -> IO ()
reverseArray arr = doFromTo 0 semiTotal (\i -> do oldi <- unsafeRead arr i
oldj <- unsafeRead arr (total-i)
unsafeWrite arr i oldj
unsafeWrite arr (total-i) oldi)
sumArrayMod :: IOUArray Int Int -> IO Int
sumArrayMod arr = foldM (\s i -> do x <- unsafeRead arr i
return
$!(s+x) `mod` 911) 0 [0..total]
main::IO()
main = testArray >>= \a ->
doFromTo 1 120 (\_ -> reverseArray a) >> sumArrayMod a >>= print
{-# INLINE doFromTo #-}
-- do the action for [from..to], ie it's inclusive.
doFromTo :: Int -> Int -> (Int -> IO ()) -> IO ()
doFromTo from to action =
let loop n | n > to = return ()
| otherwise = do action n
loop (n+1)
in loop from
-----------------------------------------------------------------------------------
Federico
More information about the Haskell
mailing list