Control.Monad.Writer.Strict not as strict as expected

Matt Brown matt at softmechanics.net
Thu Sep 15 22:43:36 CEST 2011


Hello all,

I've been debugging a space leak, and believe I've traced it to a
chain of unevaluated calls to mappend in the bind operator for
Control.Monad.Writer.Strict.  I had expected these calls to be
evaluated strictly by the strict Writer, but it doesn't seem to be the
case.  Am I understanding this correctly?  If so, is this the intended
behavior?

Below are two example programs with runtime stats demonstrating the
issue.  The first uses Control.Monad.Writer.Strict, the second uses an
alternative implementation that is strict in the Writer's monoid.  The
first runs in 78.5s with total memory 630MB.  The second runs in
38.15s with total memory 237MB.

FWIW, the lazy writer monad turned out to be more efficient for my
program (and this example -- it runs in 9.96s with total memory 389MB,
and doesn't need an increased stack size).

thanks,
-matt

-- BEGIN writerTest.hs
import Control.Monad.Writer.Strict

type M = Writer [()]

go :: Integer -> M ()
go 0 = return ()
go n = return () >> go (n-1)

main = print $ runWriter $ go 3000000
-- END writerTest.hs


-- BEGIN ./writerTest +RTS -K1G -sstderr
((),[])
   1,521,548,048 bytes allocated in the heap
     654,690,520 bytes copied during GC
     380,421,720 bytes maximum residency (10 sample(s))
     268,515,200 bytes maximum slop
             630 MB total memory in use (0 MB lost due to fragmentation)

  Generation 0:  1869 collections,     0 parallel, 77.34s, 77.40s elapsed
  Generation 1:    10 collections,     0 parallel,  0.40s,  0.40s elapsed

  INIT  time    0.00s  (  0.00s elapsed)
  MUT   time    0.76s  (  0.76s elapsed)
  GC    time   77.75s  ( 77.81s elapsed)
  EXIT  time    0.00s  (  0.11s elapsed)
  Total time   78.50s  ( 78.56s elapsed)

  %GC time      99.0%  (99.0% elapsed)

  Alloc rate    2,008,440,129 bytes per MUT second

  Productivity   1.0% of total user, 1.0% of total elapsed
-- END


-- BEGIN writerTest2.hs
import Data.Monoid

data Writer w a = Writer a !w

runWriter (Writer a w) = (a, w)

instance (Monoid w) => Monad (Writer w) where
  return a = Writer a mempty
  m >>= k  = case m of
                  Writer a w  ->
                    case k a of
                         Writer b w' ->
                           Writer b (w `mappend` w')
type M = Writer [()]

go :: Integer -> M ()
go 0 = return ()
go n = return () >> go (n-1)

main = print $ runWriter $ go 3000000
-- END writerTest2.hs


-- BEGIN ./writerTest2 +RTS -K1G -sstderr
((),[])
     894,148,696 bytes allocated in the heap
     221,145,720 bytes copied during GC
     161,143,256 bytes maximum residency (9 sample(s))
     133,479,928 bytes maximum slop
             257 MB total memory in use (11 MB lost due to fragmentation)

  Generation 0:  1185 collections,     0 parallel, 37.57s, 37.60s elapsed
  Generation 1:     9 collections,     0 parallel,  0.14s,  0.14s elapsed

  INIT  time    0.00s  (  0.00s elapsed)
  MUT   time    0.44s  (  0.44s elapsed)
  GC    time   37.72s  ( 37.75s elapsed)
  EXIT  time    0.00s  (  0.00s elapsed)
  Total time   38.15s  ( 38.18s elapsed)

  %GC time      98.8%  (98.9% elapsed)

  Alloc rate    2,036,159,030 bytes per MUT second

  Productivity   1.1% of total user, 1.1% of total elapsed
-- END



More information about the Libraries mailing list