Of course I know that the list version is very unfair, but I wanted to see
what was the trade off between elegance and speed.
Regarding whether low level programming makes sense or not, I was just
curious to see what are the limits of Haskell. Moreover there is not much
literature on high performance Haskell programming (tricks like
unsafeWrite), at least organized in a systematic and concise way.

My original problem was writing a  fast library for simple matrix
computations (i.e. multiplication and inversion for small dense matrices).
I have not been able to make GSLHaskell work with Lapack so far. :(

Anyway here are the new versions and timings, I increased the number of
times the vector is reversed, I also compiled everything with -O2.

time ./arrayC
499
real    0m0.244s
user    0m0.236s
sys    0m0.005s

time ./list
499
real    0m11.036s
user    0m10.770s
sys    0m0.118s

time ./IOMutArrayUnboxed
499
real    0m2.573s
user    0m2.408s
sys    0m0.042s

time ./IOMutUnbUnsafe
499
real    0m2.264s
user    0m2.183s
sys    0m0.025s

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

//compile with g++ -O2 -o arrayC arrayC.cc
#include < stdio.h>
#include <math.h>



int main()
{
 int array[500001];

 for (int i=0;i<=500000;i++)
   {
   array[i]=(19*i+23)%911;
   }
 int tmp=0;
 for (int cnt=0;cnt<120;cnt++)
   {
     for (int x=0;x<=250000;x++)
       {
         tmp=array[500000-x];
         array[500000-x]=array[x];
         array[x]=tmp;
       }
   }
 int result=0;
 for (int i=0;i<=500000;i++)
   {
     result=result+(array[i]%911);
   }
 result=result % 911;
 printf("%d",result);
 return 0;
}

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


-- compile with
-- ghc -O2 --make -o list list.hs

module Main
   where

import Data.List

testArray = [ (19*i+23) `mod` 911 |i <- [0..500000]]

sumArrayMod =  foldl (\x y -> (y+x) `mod` 911) 0

main = print $ sumArrayMod$
      foldl (.) id  (replicate 120 reverse) $testArray

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

-- compile with
-- ghc -O2 --make -o IOMutArrayUnboxed IOMutArrayUnboxed.hs
module Main
   where

import Monad
import Data.Array.IO <http://data.array.io/>
import Data.Array.MArray
import Data.Array.Unboxed

total, semiTotal ::Int
total= 500000 <javascript:void(0)>
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 = mapM_  (\i -> do oldi <- readArray arr i
                                   oldj <- readArray arr (total-i)
                                   writeArray arr i oldj
                                   writeArray arr (total-i) oldi)
                  [0..semiTotal]

sumArrayMod :: IOUArray Int Int -> IO Int
sumArrayMod arr = foldM (\s i -> do x <- readArray arr i
                                   return   $!(s+x) `mod` 911) 0 [0..total]


main::IO()
main = testArray >>= \a ->
      sequence  (replicate 120 $reverseArray a)>>
      sumArrayMod a >>=  print

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


-- compile with
-- ghc -O2 --make -o IOMutUnbUnsafe IOMutUnbUnsafe.hs
module Main
   where

import Monad
import Data.Array.IO <http://data.array.io/>
import Data.Array.MArray
import Data.Array.Unboxed
import Data.Array.Base ( unsafeWrite, unsafeRead )

total, semiTotal ::Int
total= 500000 <javascript:void(0)>
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 = mapM_  (\i -> do oldi <- unsafeRead arr i
                                   oldj <- unsafeRead arr (total-i)
                                   unsafeWrite arr i oldj
                                   unsafeWrite arr (total-i) oldi)
                  [0..semiTotal]

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

-----------------------------------------------------------------------
_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to