[Haskell-cafe] I killed performance of my code with Eval and Strategies
Janek S.
fremenzone at poczta.onet.pl
Wed Nov 14 22:43:08 CET 2012
Dear Haskellers,
I am reading Simon Marlow's tutorial on parallelism and I have problems with correctly using Eval
monad and Strategies. I *thought* I understand them but after writing some code it turns out that
obviously I don't because parallelized code is about 20 times slower. Here's a short example
(code + criterion benchmarks):
{-# LANGUAGE BangPatterns #-}
module Main where
import Control.Parallel.Strategies
import Criterion.Main
main :: IO ()
main = defaultMain [
bench "Seq" $ nf calculateSeq xs
, bench "Par" $ nf calculatePar xs ]
where xs = [1..16384]
calculateSeq :: [Double] -> [Double]
calculateSeq [] = []
calculateSeq (x:xs) = (sin . sqrt $ x) : xs
calculatePar :: [Double] -> [Double]
calculatePar xss = runEval $ go xss
where
go :: Strategy [Double]
go [] = return []
go xs = do
lsh <- (rpar `dot` rdeepseq) $ calculateSeq as
lst <- go bs
return (lsh ++ lst)
where
!(as, bs) = splitAt 8192 xs
Compiling and running with:
ghc -O2 -Wall -threaded -rtsopts -fforce-recomp -eventlog evalleak.hs
./evalleak -oreport.html -g +RTS -N2 -ls -s
I get:
benchmarking Seq
mean: 100.5990 us, lb 100.1937 us, ub 101.1521 us, ci 0.950
std dev: 2.395003 us, lb 1.860923 us, ub 3.169562 us, ci 0.950
benchmarking Par
mean: 2.233127 ms, lb 2.169669 ms, ub 2.296155 ms, ci 0.950
std dev: 323.5201 us, lb 310.2844 us, ub 344.8252 us, ci 0.950
That's a hopeless result. Looking at the spark allocation everything looks fine:
SPARKS: 202 (202 converted, 0 overflowed, 0 dud, 0 GC'd, 0 fizzled)
But analyzing eventlog with ThreadScope I see that parallel function spends most of the time doing
garbage collection, which suggests that I have a memory leak somewhere. I suspected that problem
might be caused by appending two lists together in the parallel implementation, but replacing
this with difference lists doesn't help. Changing granularity (e.g. splitAt 512) also brings no
improvement. Can anyone point me to what am I doing wrong?
Janek
PS. This is of course not a real world code - I know that I'd be better of using unboxed data
structures for doing computations on Doubles.
More information about the Haskell-Cafe
mailing list