[Haskell-cafe] To my boss: The code is cool, but it is about 100 times slower than the old one...
Fixie Fixie
fixie.fixie at rocketmail.com
Thu Nov 29 21:00:49 CET 2012
Oh, my - what an indentation :-)
New try:
----- Videresendt melding ----
Fra: Fixie Fixie <fixie.fixie at rocketmail.com>
Til: "haskell-cafe at haskell.org" <haskell-cafe at haskell.org>
Kopi: Clark Gaebel <cgaebel at uwaterloo.ca>
Sendt: Torsdag, 29. november 2012 20.57
Emne: Vedr: [Haskell-cafe] To my boss: The code is cool, but it is about 100 times slower than the old one...
Sure, the code is from the url I mentioned, both in C and in Haskell.
It allready seems like the haskell-version should run fast to me - it uses unboxed arrays and even unsafe functions to make it run faster. Well, have a look:
C-version:
#include <stdint.h>
#include <stdio.h>
#define VDIM 100
#define VNUM 100000
uint64_t prng (uint64_t w) {
w ^= w << 13;
w ^= w >> 7;
w ^= w << 17;
return w;
};
void kahanStep (double *s, double *c, double x) {
double y, t;
y = x - *c;
t = *s + y;
*c = (t - *s) - y;
*s = t;
}
void kahan(double s[], double c[]) {
for (int i = 1; i <= VNUM; i++) {
uint64_t w = i;
for (int j = 0; j
< VDIM; j++) {
kahanStep(&s[j], &c[j], w);
w = prng(w);
}
}
};
int main (int argc, char* argv[]) {
double acc[VDIM], err[VDIM];
for (int i = 0; i < VDIM; i++) {
acc[i] = err[i] = 0.0;
};
kahan(acc, err);
printf("[ ");
for (int i = 0; i < VDIM; i++) {
printf("%g ", acc[i]);
};
printf("]\n");
};
And the haskell version:
{-# LANGUAGE CPP, BangPatterns #-}
module Main (main) where
#define VDIM 100
#define VNUM 100000
import Data.Array.Base
import Data.Array.ST
import Data.Array.Unboxed
import Control.Monad.ST
import GHC.Word
import Control.Monad
import Data.Bits
prng :: Word -> Word
prng w = w'
where
!w1 = w `xor` (w `shiftL` 13)
!w2 = w1 `xor` (w1 `shiftR` 7)
!w' = w2 `xor` (w2 `shiftL` 17)
type Vec s = STUArray s Int Double
kahan :: Vec s -> Vec s -> ST s ()
kahan s c = do
let inner w j
| j < VDIM = do
!cj <- unsafeRead c j
!sj <- unsafeRead s j
let !y = fromIntegral w - cj
!t = sj + y
!w' = prng w
unsafeWrite c j ((t-sj)-y)
unsafeWrite s j t
inner w' (j+1)
| otherwise = return ()
forM_ [1 .. VNUM] $ \i -> inner (fromIntegral i) 0
calc :: ST s (Vec s)
calc = do
s <- newArray (0,VDIM-1) 0
c <- newArray (0,VDIM-1) 0
kahan s c
return s
main :: IO ()
main = print . elems $ runSTUArray calc
Cheers,
Felix
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20121129/d2081cfb/attachment-0001.htm>
More information about the Haskell-Cafe
mailing list