Hi,

This sort of code runs very slowly when compared to the equivalent in C:

> {-# OPTIONS -fglasgow-exts #-}
> module Main where
> 
> import Data.Array.MArray
> import Data.Array.IO
> 
> data Pos = Pos !Int !Int
>   deriving (Eq, Ord, Ix)
> 
> main = test1
> 
> test1 :: IO ()
> test1 = do
>   (arr :: IOUArray Pos Bool) <- newArray_ (Pos 0 0, Pos 99 99)
>   sequence_ [ sequence_ [ writeArray arr (Pos y x) False
>                         | y <- [0..99]
>                         , x <- [0..99] ]
>             | _ <- [0..9999] ]
> 

Timing:

$ ghc --make -O2 SpeedTest.hs -o speedtest-hs
$ time ./speedtest-hs

real    0m10.968s
user    0m10.952s
sys     0m0.005s

Comparing to an 'equivalent' C program:

> int main () {
>   char arr[100][100];
>   int n,x,y;
>   
>   for (n = 0; n != 10000; n++)
>     for (y = 0; y != 100; y++)
>       for (x = 0; x != 100; x++)
>         arr[y][x] = 0;
> }

$ gcc -O2 speedtest.c -o speedtest-c
$ time ./speedtest-c

real    0m0.129s
user    0m0.123s
sys     0m0.000s

Now parhaps this is unfair sice the Haskell program is written in terms
of lists. So lets write it using explicit looping and no lists.


> {-# 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
>
> test2 :: IO ()
> test2 = do
>   (arr :: IOUArray Pos Bool) <- newArray_ (Pos 0 0, Pos 99 99)
>   doFromTo 0 9999 $ \_ ->
>     doFromTo 0 99 $ \y ->
>       doFromTo 0 99 $ \x ->
>         writeArray arr (Pos y x) False

Timing:

$ ghc --make -O2 SpeedTest.hs -o speedtest-hs
$ time ./speedtest-hs

real    0m7.942s
user    0m7.936s
sys     0m0.001s

So not much better really. :-(

If there's way to write loops that is faster I'd dearly like to know.

I initially assumed that the second version would run fast since there
is no obvious need for any memory allocations (which is the usual
culprit).

Duncan

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to