[Haskell-cafe] Vedr: To my boss: The code is cool, but it is about 100 times slower than the old one...

Johan Tibell johan.tibell at gmail.com
Thu Nov 29 22:40:42 CET 2012


On Thu, Nov 29, 2012 at 1:32 PM, Daniel Fischer
<daniel.is.fischer at googlemail.com> wrote:
> We have an unpleasant regression in comparison to 7.2.* and the 7.4.* were
> slower than 7.6.1 is, but it's all okay here (not that it wouldn't be nice to
> have it faster still).
>
> Are you on a 32-bit system?

This version works around the Word->Double conversion bug and shows
good performance:

(Always compile with -Wall, it tells you if some arguments are
defaulted to slow Integers, instead of fast Ints.)

{-# LANGUAGE CPP, BangPatterns, MagicHash #-}
module Main (main) where

#define VDIM 100
#define VNUM 100000

import Control.Monad.ST
import Data.Array.Base
import Data.Array.ST
import Data.Bits
import GHC.Word

import GHC.Exts

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 = word2Double w - cj
                    t = sj + y
                    w' = prng w
                unsafeWrite c j ((t-sj)-y)
                unsafeWrite s j t
                inner w' (j+1)
            | otherwise = return ()

        outer i | i < VNUM = inner (fromIntegral i) 0 >> outer (i + 1)
                | otherwise = return ()
    outer (0 :: Int)

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

word2Double :: Word -> Double
word2Double (W# w) = D# (int2Double# (word2Int# w))

On my (64-bit) machine the Haskell and C versions are on par.

-- Johan



More information about the Haskell-Cafe mailing list