[Haskell-cafe] Performance Help

Dominic Steinitz dominic.steinitz at blueyonder.co.uk
Sun Mar 11 16:18:44 EDT 2007


I have re-written the sha1 code so that it is (hopefully) easy to see that it 
faithfully implements the algorithm (see 
http://www.itl.nist.gov/fipspubs/fip180-1.htm). Having got rid of the space 
leak, I have been trying to improve performance.

Currently, the haskell code is 2 orders of magnitude slower than the sha1sum 
that ships with my linux.

> dom at heisenberg:~/sha1/testdist/sha1> time ./perfTest perfTest
> c7eae62ddabb653bb9ce4eb18fa8b94264f92a76
> Success
>
> real    0m2.152s
> user    0m2.112s
> sys     0m0.028s
> dom at heisenberg:~/sha1/testdist/sha1> time sha1sum perfTest
> c7eae62ddabb653bb9ce4eb18fa8b94264f92a76  perfTest
>
> real    0m0.057s
> user    0m0.008s
> sys     0m0.004s

I've played around with profiling and doubled the performance of the haskell 
code but I'm nowhere near the C performance.

>         Sun Mar 11 19:32 2007 Time and Allocation Profiling Report  (Final)
>
>            perfTest +RTS -p -RTS eg
>
>         total time  =        6.75 secs   (135 ticks @ 50 ms)
>         total alloc = 1,483,413,752 bytes  (excludes profiling overheads)
>
> COST CENTRE                    MODULE               %time %alloc
>
> oneBlock                       Data.Digest.SHA1      39.3   40.1
> $&                             Data.Digest.SHA1      20.7   21.6
> f                              Data.Digest.SHA1      13.3    6.2
> getWord32s                     Data.Digest.SHA1       7.4    6.6
> test2                          Main                   5.9    8.7
> blockWord8sIn32                Data.Digest.SHA1       5.2    5.3
> blockWord8sIn512               Data.Digest.SHA1       3.0    4.4
> pad                            Data.Digest.SHA1       1.5    3.5
> k                              Data.Digest.SHA1       1.5    0.0
> fromBytes                      Data.Digest.SHA1       0.0    3.5

Here's the code that is taking the majority of the time.

> ($&) :: [Word32] -> [Word32] -> [Word32]
> a $& b = zipWith (+) a b
> 
> -- Word128 -> Word512 -> Word128
> oneBlock ss xs = Word128 (as!!80) (bs!!80) (cs!!80) (ds!!80) (es!!80)
>    where
>       ws = xs ++ map (rotL 1) (zipWith4 xxxor wm3s wm8s wm14s ws)
>          where
>             xxxor a b c d = a `xor` b `xor` c `xor` d
>             wm3s  = drop (16-3)  ws
>             wm8s  = drop (16-8)  ws
>             wm14s = drop (16-14) ws
>       as = ai:ts
>       bs = bi:as
>       cs = ci:(map (rotL 30) bs)
>       ds = di:cs
>       es = ei:ds
>       ts = (map (rotL 5) as) $& (zipWith4 f [0..] bs cs ds) $& es $& (map k
> [0..]) $& ws 
>       Word128 ai bi ci di ei = ss 

Any help would be appreciated.

I've put a copy of a working system here if anyone wants to experiment 
(http://www.haskell.org/crypto/downloads/sha1.tar.gz).

Thanks, Dominic.



More information about the Haskell-Cafe mailing list