[Haskell-beginners] space leak

Uchida Yasuo kg6y_ucd at yahoo.co.jp
Mon Feb 15 10:44:51 EST 2010


Hello,

I came across the following space leak problem today.
How can I fix this?
(Tested on Mac OS X 10.5.8, GHC 6.10.3)

-- test.hs
module Main where

import System
import qualified Data.ByteString.Lazy.Char8 as L

main = do args <- getArgs
          let n = read $ args !! 0
          cs <- L.getContents
          let !a = L.take n cs
          mapM_ (print . L.length) $ L.lines cs
          print a


-- gen.hs
module Main where

main = do putStrLn $ take 1000000 $ cycle "foo"
          main


These are compiled with the following options:

$ ghc --make -O2 test
$ ghc --make -O2 gen

The memory usage seems to depend on the argument(=17000) passed. 
On my MacBook(Core2 Duo 2.0GHz), 16000 works fine.

$ ./gen | head -1000 | ./test 17000 +RTS -sstderr

...

   3,793,673,564 bytes allocated in the heap
       9,901,516 bytes copied during GC
     635,576,092 bytes maximum residency (11 sample(s))
     248,725,136 bytes maximum slop
            1759 MB total memory in use (562 MB lost due to fragmentation)

  Generation 0:  6941 collections,     0 parallel, 16.91s, 18.15s elapsed
  Generation 1:    11 collections,     0 parallel,  0.03s,  0.03s elapsed

  INIT  time    0.00s  (  0.00s elapsed)
  MUT   time    3.04s  ( 27.64s elapsed)
  GC    time   16.94s  ( 18.18s elapsed)
  EXIT  time    0.00s  (  0.01s elapsed)
  Total time   19.99s  ( 45.82s elapsed)

  %GC time      84.8%  (39.7% elapsed)

  Alloc rate    1,245,766,300 bytes per MUT second

  Productivity  15.2% of total user, 6.6% of total elapsed



$ ./gen | head -1000 | ./test 16000 +RTS -sstderr

...

   4,000,652,128 bytes allocated in the heap
       7,428,180 bytes copied during GC
       1,057,588 bytes maximum residency (1001 sample(s))
         525,092 bytes maximum slop
               5 MB total memory in use (1 MB lost due to fragmentation)

  Generation 0:  6362 collections,     0 parallel,  0.10s,  0.12s elapsed
  Generation 1:  1001 collections,     0 parallel,  0.09s,  0.09s elapsed

  INIT  time    0.00s  (  0.00s elapsed)
  MUT   time    2.59s  ( 23.26s elapsed)
  GC    time    0.18s  (  0.22s elapsed)
  EXIT  time    0.00s  (  0.00s elapsed)
  Total time    2.77s  ( 23.47s elapsed)

  %GC time       6.6%  (0.9% elapsed)

  Alloc rate    1,545,246,968 bytes per MUT second

  Productivity  93.4% of total user, 11.0% of total elapsed

--
Regards,
Yasuo Uchida


More information about the Beginners mailing list