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

2012-11-29 Thread Fixie Fixie
The program seems to take around 6 seconds on my linux-box, while the c version 
goes for 0.06 sekcond.

That is really some regression bug :-)

Anyone with a more recent version thatn 7.4.1?

Felix



 Fra: Johan Tibell johan.tib...@gmail.com
Til: Fixie Fixie fixie.fi...@rocketmail.com 
Kopi: Haskell cafe haskell-cafe@haskell.org 
Sendt: Torsdag, 29. november 2012 21.50
Emne: Re: [Haskell-cafe] To my boss: The code is cool, but it is about 100 
times slower than the old one...
 
Ack, it seems like you're running into one of these bugs (all now
fixed, but I don't know in which GHC version):

http://hackage.haskell.org/trac/ghc/search?q=doubleFromInteger___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2012-11-29 Thread Fixie Fixie
That's really an argument for upgrading to 7.4.2 :-)

Another reason for doing things with haskell is this mailing list.

Thanks!

Felix



 Fra: Johan Tibell johan.tib...@gmail.com
Til: Fixie Fixie fixie.fi...@rocketmail.com 
Kopi: Haskell cafe haskell-cafe@haskell.org 
Sendt: Torsdag, 29. november 2012 22.06
Emne: Re: [Haskell-cafe] To my boss: The code is cool, but it is about 100 
times slower than the old one...
 
On Thu, Nov 29, 2012 at 1:00 PM, Fixie Fixie fixie.fi...@rocketmail.com wrote:
 The program seems to take around 6 seconds on my linux-box, while the c
 version goes for 0.06 sekcond.

 That is really some regression bug :-)

 Anyone with a more recent version thatn 7.4.1?

On 7.4.2:

$ time ./c_test
...

real    0m0.145s
user    0m0.040s
sys    0m0.003s

$ time ./Test
...

real    0m0.234s
user    0m0.220s
sys    0m0.006s

Both compiled with -O2.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2012-11-29 Thread Daniel Fischer
On Donnerstag, 29. November 2012, 21:00:36, Fixie Fixie wrote:
 The program seems to take around 6 seconds on my linux-box, while the c
 version goes for 0.06 sekcond.
 
 That is really some regression bug :-)
 
 Anyone with a more recent version thatn 7.4.1?

I don't even have a problem with 7.4.1:

$ for ghc in $GHCS; do echo $ghc; time ./hskahan-$ghc  /dev/null; done;
7.0.4

real0m0.217s
user0m0.214s
sys 0m0.002s
7.2.1

real0m0.197s
user0m0.194s
sys 0m0.002s
7.2.2

real0m0.187s
user0m0.187s
sys 0m0.000s
7.4.1

real0m0.253s
user0m0.249s
sys 0m0.003s
7.4.2

real0m0.250s
user0m0.247s
sys 0m0.002s
7.6.1

real0m0.224s
user0m0.221s
sys 0m0.002s

$ time ./ckahan  /dev/null

real0m0.102s
user0m0.079s
sys 0m0.022s


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?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2012-11-29 Thread Johan Tibell
On Thu, Nov 29, 2012 at 1:32 PM, Daniel Fischer
daniel.is.fisc...@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 10

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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2012-11-29 Thread Johan Tibell
On Thu, Nov 29, 2012 at 1:40 PM, Johan Tibell johan.tib...@gmail.com wrote:
 This version works around the Word-Double conversion bug and shows
 good performance:

I'd also like to point out that I've removed lots of bang patterns
that weren't needed. This program runs fine without any bang patterns
(but I've kept the one that can possibly have any performance
implication at all).

-- Johan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2012-11-29 Thread Daniel Fischer
On Donnerstag, 29. November 2012, 13:40:42, Johan Tibell wrote:
 word2Double :: Word - Double
 word2Double (W# w) = D# (int2Double# (word2Int# w))
 
 On my (64-bit) machine the Haskell and C versions are on par.

Yes, but the result is very different.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2012-11-29 Thread Daniel Fischer
On Donnerstag, 29. November 2012, 13:40:42, Johan Tibell wrote:
 
 word2Double :: Word - Double
 word2Double (W# w) = D# (int2Double# (word2Int# w))
 
 On my (64-bit) machine the Haskell and C versions are on par.

On my box, the Haskell is even faster then, but, as said, the result is 
incorrect

With

correction :: Double
correction = 2 * int2Double minBound

word2Double :: Word - Double
word2Double w = case fromIntegral w of
   i | i  0 - int2Double i - correction
 | otherwise - int2Double i

I get

real0m0.078s
user0m0.077s
sys 0m0.001s

with correct results.

Okay, we **need** a better Word - Double etc. conversion. We could start with 
the above, that seems not too shabby.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2012-11-29 Thread Johan Tibell
On Thu, Nov 29, 2012 at 2:02 PM, Johan Tibell johan.tib...@gmail.com wrote:
 On Thu, Nov 29, 2012 at 2:01 PM, Daniel Fischer
 daniel.is.fisc...@googlemail.com wrote:
 On Donnerstag, 29. November 2012, 13:40:42, Johan Tibell wrote:
 word2Double :: Word - Double
 word2Double (W# w) = D# (int2Double# (word2Int# w))

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

 Yes, but the result is very different.

 Doh, I guess I didn't look at the output carefully enough.

One obvious error is that the C code has one loop go from 1..n where I
just naively assumed all loops go from 0..n-1. This fixes that:

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

Perhaps the other issue is that

word2Double (W# w) = D# (int2Double# (word2Int# w))

is possibly the wrong way and we need a word2Double#.

-- Johan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe