[Haskell] Haskell fast (?) arrays

Stephan Herhut s.a.herhut at herts.ac.uk
Tue May 1 14:46:30 EDT 2007


While scanning my Inbox I read 'fast' and 'array' in the context of
functional programming. Well, of course SaC instantly came to my mind (what
a surprise ;) ). So I did some measurements myself. I used your programs,
except that I increased the array size by a factor of 10. For the C++
version I had to move the array to the heap and fix the order of function
applications within the fold. Here are the timings:

C++
520
real    0m0.204s
user    0m0.182s
sys     0m0.023s

Haskell IOArray (the extended version with unsafe accesses that was posted
shortly after yours)
520

real    0m5.542s
user    0m5.453s
sys     0m0.068s

Haskell Lists (just to be complete)
520

real    0m27.596s
user    0m26.650s
sys     0m0.870s

and finally SaC
Dimension:  0
Shape    : < >
 520

real    0m0.057s
user    0m0.048s
sys     0m0.000s

The corresponding SaC program follows. I have compiled it with sac2c -O3. I
used the current compiler from the website http://www.sac-home.org.

use Structures : all;
use StdIO : all;

inline
int sumMod( int a, int b)
{
  return( (a + b) % 911);
}

inline
int sumArrayMod( int[*] A)
{
  res = with {
          ( shape(A) * 0 <= iv < shape(A)) : A[iv];
        } : fold( sumMod, 0);

  return( res);
}

int main() {
  testArray = (19*iota(5000001)+23) % 911;

  print( sumArrayMod(
    reverse( reverse( reverse( reverse(
    reverse( reverse( reverse( reverse(
    reverse( reverse( reverse( reverse(
    reverse( reverse( reverse( reverse(
      testArray))))))))))))))))));

  return( 0);
}

On 5/1/07, Federico Squartini <federico.squartini at googlemail.com> wrote:
>
> I was reading an old post where Hal Daume III was analyzing Haskell
> performance for arrays.
> He proposed a test program which initializes an array, reverse it a number
> of times, and sums the contents.
>
> So I wrote a c++ reference program, a naive haskell version using lists
> and I also tweaked a little bit with the IOArray version, which should be
> the fastest. Unfortunately there is a  huge performance gap. Haskell is
> slower by a factor of ten, even when using imperative style.
>
> C++
> time ./arrayC
> 499
> real    0m0.059s
> user    0m0.044s
> sys    0m0.008s
>
> HASKELL - IOUArray
> time ./IOMutArrayUnboxed
> 499
> real    0m0.720s
> user    0m0.571s
> sys    0m0.019s
>
> HASKELL - list
> time ./list
> 499
> real    0m1.845s
> user    0m1.770s
> sys    0m0.064s
>
>
> Can anyone suggest a faster version (using whatever data structure)? I
> like Haskell very much but I still have to figure out if the slowness of
> some code is due to my lack of knowledge or to some intrinsic limitation of
> the language (or libraries).
>
> By the way, sorry for the poor quality of the code, I am not a computer
> scientist.
>
>
> -------------------------------------------------------------------------------------------------------------------------------
>
>
> -------------------------------------------------------------------------------------------------------------------------------
> //compile with
> //g++ -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<12;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 --make -o list list.hs
> module Main
>     where
>
> testArray = [ (19*i+23) `mod` 911 |i <- [0..500000]]
>
> sumArrayMod =  foldl (\x y -> (y+x) `mod` 911) 0
>
> main = print $ sumArrayMod$
>        reverse$ reverse$ reverse$ reverse$
>        reverse$ reverse$ reverse$ reverse$
>        reverse$ reverse$ reverse$ reverse$
>        reverse$ reverse$ reverse$ reverse$
>        testArray
>
>
> ---------------------------------------------------------------------------------------------
>
>
> ---------------------------------------------------------------------------------------------
> -- compile with
> -- ghc --make -o IOMutArrayUnboxed IOMutArrayUnboxed.hs
> module Main
>     where
>
> import Monad
> import Data.Array.IO
> import Data.Array.MArray
> import Data.Array.Unboxed
>
> 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 = 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 ->
>        reverseArray a >> reverseArray a >> reverseArray a >> reverseArray
> a >>
>        reverseArray a >> reverseArray a >> reverseArray a >> reverseArray
> a >>
>        reverseArray a >> reverseArray a >> reverseArray a >> reverseArray
> a >>
>        reverseArray a >> reverseArray a >> reverseArray a >> reverseArray
> a >>
>        sumArrayMod a >>=  print
>
>
> ---------------------------------------------------------------------------------------------------------
>
> Federico
>
>
>
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>
>


-- 
Stephan Herhut
Centre for Computer Science and Informatics Research
University of Hertfordshire
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell/attachments/20070501/6ff54f39/attachment.htm


More information about the Haskell mailing list