[Haskell-cafe] Space Leak with semi-implicit parallelization and the nasty Garbage collector

Michael Lesniak mlesniak at uni-kassel.de
Wed Dec 23 20:14:51 EST 2009


Hello haskell-cafe (and merry christmas!),

I have a strange problem with the garbage collector / memory which I'm unable
to find a solution for. I think the source of my problems has to do with lazy
evaluation, but currently I'm unable to find it.

Using the attached program and threadscope I see that the GC is using a lot of
time and the program comes (more or less) to a halt (see exa-1.png). When I
increase the heap the program takes much longer and the GC is running more or
less all the time (see exa-2.png).

Some more detailled information:

* I can see the described behaviour under both GHC 10.4 and GHC 12.1
* Linux kernel 2.6.31-16 on a dualcore
* Program compiled with ghc --make -O2 -threaded -eventlog Example.hs -o exa
* Started with exa +RTS -ls and one of { -N, -N1, -N2 }

Any help (pointing into the right direction, mention possibly helpful
blog articles
or paper, constructive critic in general) is appreciated!

Best wishes,
Michael

PS:
1. I hope the graphs are good enough to see the problem
2. Is it a known bug that threadscope eats 100%+ CPU when I just view
    an eventlog?

-------------------------------------------------------------------------------
-- 
-- Minimal test example for problems with garbage collection (both under
-- GHC6.10.4 and GHC6.12.1). We calculate Pi to an arbitrary length (here
-- 50.000 + n) for n times using Machin's formula[1].
--
-- [1] http://en.literateprograms.org/Pi_with_Machin's_formula_(Haskell)
-------------------------------------------------------------------------------

module Main where
import Control.Parallel
import Control.Parallel.Strategies


main = do
    -- 20 tasks, length 50000 + [1..20]
    let values = implicit (initTasks 20 50000)
    -- Dirty trick to force evaluation:
    mapM_ (print . (`mod` 10)) values


-------------------------------------------------------------------------------
-- Using semi-implicit parallelization here.
implicit :: [PiTask] -> [Integer]
implicit tasks = parMap rdeepseq (\(PiTask k) -> calcPiPure k) tasks


-------------------------------------------------------------------------------
-- Definition of a task to calculate \pi to an arbitrary length and its
-- implementation.
data PiTask = PiTask Integer
instance Show PiTask where show (PiTask i) = "PiTask <" ++ show i ++ ">"


-- Returns @number@ tasks of length @len@ up to @len+number at . We add one for
-- each successive task to prevent additional compiler or runtime optimizations
-- through referential transparency. In dimensions of 10^5 this should
not make a
-- measureable difference.
initTasks :: Int -> Int -> [PiTask]
initTasks number len =
    let len' = toEnum len
        num' = toEnum number
    in map PiTask [len'..len'+num']


-- Not used here
calcPi :: Integer -> IO ()
calcPi digits = calcPiPure digits `pseq` return ()


calcPiPure :: Integer -> Integer
calcPiPure digits =
    pi' `div` (10 ^ (10 :: Integer))
  where unity = 10 ^ (toInteger digits + 10)
        pi'   = 4 * (4 * arccot 5 unity - arccot 239 unity :: Integer)


arccot :: Integral t => t -> t -> t
arccot x unity = arccot' x unity 0 start 1 1
  where start = unity `div` x
        arccot' x' u sm xpower n sign | xpower `div` n == 0 = sm
                                      | otherwise           =
            arccot' x' u (sm + sign*term) (xpower `div` (x'*x')) (n+2) (-sign)
              where term = xpower `div` n
-------------- next part --------------
A non-text attachment was scrubbed...
Name: exa-1.png
Type: image/png
Size: 29850 bytes
Desc: not available
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20091223/a7bc879c/exa-1.png
-------------- next part --------------
A non-text attachment was scrubbed...
Name: exa-2.png
Type: image/png
Size: 20819 bytes
Desc: not available
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20091223/a7bc879c/exa-2.png


More information about the Haskell-Cafe mailing list