comparison of execution speed of array types

Hi all, I was curious about how fast the different array implementations were so I decided to test it. I wrote five programs all of which take an array containing 50001 elements, reverse it a couple of times then sum (modulo) them finally printing the sum. The programs are as follows: NormalArray -- uses the standard Array package for everything NormalArrayReplace -- same as NormalArray but builds a new array every time it is reversed UnboxedArray -- uses UArray UnboxedArrayReplace -- obvious IOMutArray -- uses the IOArray from IOExts and everything is in the IO monad I've stuck the code for these at the bottom of this message, but here are the timing results: NormalArray 1.65u 0.20s 0:01.89 97.8% NormalArrayReplace 2.40u 0.08s 0:02.56 96.8% UnboxedArray 0.80u 0.04s 0:00.87 96.5% UnboxedArrayReplace 1.83u 0.07s 0:01.99 95.4% IOMutArray 0.60u 0.03s 0:01.09 57.7% clearly IOMutArray is the best, even outperforming the UnboxedArray. Unfortunately, writing code in the IOMutArray format is much uglier than writing it in the UnboxedArray or NormalArray formats, even though I know that I'm never going to refer to an old version of the array, so inplace updates are a-okay. So my question is: how can I get better performance without wrapping everything in the IO (or some other) monad? - Hal Source code: -- NormalArray: module Main where import Data.Array testArray :: Array Int Int testArray = array (0,50000) [(i, (19*i+23) `mod` 911) | i <- [0..50000]] reverseArray :: Array Int Int -> Array Int Int reverseArray arr = arr // [(50000-i, arr!i) | i <- [0..50000]] sumArrayMod :: Array Int Int -> Int sumArrayMod arr = sumArrayMod' low 0 where sumArrayMod' pos sum | pos > high = sum | otherwise = sumArrayMod' (pos+1) ((sum + arr!pos) `mod` 911) (low,high) = bounds arr main = print $ sumArrayMod $ reverseArray $ reverseArray $ reverseArray $ reverseArray $ reverseArray $ reverseArray testArray -- NormalArrayReplace: module Main where import Data.Array testArray :: Array Int Int testArray = array (0,50000) [(i, (19*i+23) `mod` 911) | i <- [0..50000]] reverseArray :: Array Int Int -> Array Int Int reverseArray arr = array (0,50000) [(50000-i, arr!i) | i <- [0..50000]] sumArrayMod :: Array Int Int -> Int sumArrayMod arr = sumArrayMod' low 0 where sumArrayMod' pos sum | pos > high = sum | otherwise = sumArrayMod' (pos+1) ((sum + arr!pos) `mod` 911) (low,high) = bounds arr main = print $ sumArrayMod $ reverseArray $ reverseArray $ reverseArray $ reverseArray $ reverseArray $ reverseArray testArray -- UnboxedArray: module Main where import Data.Array.IArray import Data.Array.Unboxed testArray :: UArray Int Int testArray = array (0,50000) [(i, (19*i+23) `mod` 911) | i <- [0..50000]] reverseArray :: UArray Int Int -> UArray Int Int reverseArray arr = arr // [(50000-i, arr!i) | i <- [0..50000]] sumArrayMod :: UArray Int Int -> Int sumArrayMod arr = sumArrayMod' low 0 where sumArrayMod' pos sum | pos > high = sum | otherwise = sumArrayMod' (pos+1) ((sum + arr!pos) `mod` 911) (low,high) = bounds arr main = print $ sumArrayMod $ reverseArray $ reverseArray $ reverseArray $ reverseArray $ reverseArray $ reverseArray testArray -- UnboxedArrayReplace module Main where import Data.Array.IArray import Data.Array.Unboxed testArray :: UArray Int Int testArray = array (0,50000) [(i, (19*i+23) `mod` 911) | i <- [0..50000]] reverseArray :: UArray Int Int -> UArray Int Int reverseArray arr = array (0,50000) [(50000-i, arr!i) | i <- [0..50000]] sumArrayMod :: UArray Int Int -> Int sumArrayMod arr = sumArrayMod' low 0 where sumArrayMod' pos sum | pos > high = sum | otherwise = sumArrayMod' (pos+1) ((sum + arr!pos) `mod` 911) (low,high) = bounds arr main = print $ sumArrayMod $ reverseArray $ reverseArray $ reverseArray $ reverseArray $ reverseArray $ reverseArray testArray -- IOMutArray: module Main where import IOExts import Monad testArray :: IO (IOArray Int Int) testArray = newIOArray (0,50000) 0 >>= \arr -> mapM_ (uncurry (writeIOArray arr)) [(i, (19*i+23) `mod` 911) | i <- [0..50000]] >> return arr reverseArray :: IOArray Int Int -> IO () reverseArray arr = mapM_ (\i -> readIOArray arr i >>= \oldi -> readIOArray arr (50000-i) >>= \oldj -> writeIOArray arr i oldj >> writeIOArray arr (50000-i) oldi) [0..25000] sumArrayMod :: IOArray Int Int -> IO Int sumArrayMod arr = foldM (\s p -> readIOArray arr p >>= return . (`mod` 911) . (s+)) 0 [0..50000] main = testArray >>= \a -> reverseArray a >> reverseArray a >> reverseArray a >> reverseArray a >> reverseArray a >> reverseArray a >> sumArrayMod a >>= print -- Hal Daume III "Computer science is no more about computers | hdaume@isi.edu than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume

Hal Daume III
clearly IOMutArray is the best, even outperforming the UnboxedArray. Unfortunately, writing code in the IOMutArray format is much uglier than writing it in the UnboxedArray or NormalArray formats, even though I know that I'm never going to refer to an old version of the array, so inplace updates are a-okay.
So my question is: how can I get better performance without wrapping everything in the IO (or some other) monad?
<Shameless Plug> This question is the motivation for our work on optimising array codes: http://www.cse.unsw.edu.au/~chak/papers/CK01.html Unfortunately, I can't point you to a web site where you can download everything ready to run, but the plan is to have some library code for more general consumption ready in the next couple of weeks. Cheers, Manuel
participants (2)
-
Hal Daume III
-
Manuel M T Chakravarty