FW: A Garbage Collection Question

Simon Peyton-Jones simonpj at microsoft.com
Tue Jan 24 13:56:04 CET 2012


Can anyone help Burak?

Simon

-----Original Message-----
From: burak ekici [mailto:ekcburak at hotmail.com] 
Sent: 24 January 2012 08:12
To: Simon Peyton-Jones
Subject: A Garbage Collection Question

Dear Dr. Jones,

this time I am disturbing you to ask a question about how
garbage collection is being managed in parallel GHC?

When I use, (compositional) original strategies to parallel any
part of a code, what I expect is that none of the created sparks
has to be pruned, instead they should be all converted. Since,
it is not possible to adopt WEAK policy in this type of strategies,
due to losing the potential parallelism.
(ref: Seq no more: Better Strategies for Parallel Haskell)

However, in my experiments most of created sparks are getting
pruned, although I use compositional strategies. Here you can see
mentioned part of code, below.

What could be the reason? I would be appreciated, if you shed light
on the issue?

Sorry for the disturbance!

Kind regards,
Burak.

CODE:

instance NFData a => NFData [a] where
   rnf [] = ()
   rnf (x:xs) = rnf x `pseq` rnf xs

karatsuba _ [] _ = []
karatsuba _ _ [] = []
karatsuba currentDepth xs ys
  | (l < 32 || currentDepth >= limit) = mul xs ys
  | otherwise = (x `add` (replicate l False ++ (z `add` (replicate l 
False ++ y)))) `Main.using` strategy
   where
    l = (min (length xs) (length ys)) `div` 2
    (xs0, xs1) = splitAt l xs
    (ys0, ys1) = splitAt l ys
    x  = (normalize (karatsuba (currentDepth+1) xs0 ys0))
    y  = (normalize (karatsuba (currentDepth+1) xs1 ys1))
    z  = (normalize (karatsuba (currentDepth+1) (add xs0 xs1) (add ys0 
ys1)))
    t =  (normalize (karatsuba (currentDepth+1) xs0 ys0))
    u =  (normalize (karatsuba (currentDepth+1) xs1 ys1))
    v  = z `sub`  t `sub` u
    strategy res =  (rnf x)   `par`
                             (rnf y)   `par`
                             ((rnf z)  `par`
                             (rnf t)    `par`
                             (rnf u))  `pseq`
                             (rnf v)   `pseq`
                             (rnf res)





More information about the Glasgow-haskell-users mailing list