StateT space leak

Donald Bruce Stewart dons at cse.unsw.edu.au
Fri Nov 14 10:02:10 EST 2003


wojtek:
> Consider the following program:
> 
> module A where
> 
> import Control.Monad.State
> 
> f :: StateT Int IO ()
> f = (sequence_ $ repeat $ return ())
> 
> t = runStateT f 0
> 
> When t is evaluated under ghci or hugs, the program quickly runs out
> of heap memory. What's going on here? Is this inherent in StateT
> monad? If so, then this is very surprising, I would expect f to run in
> constant space for any sensible monad.

For any sensible compiler...

I replaced 't' with 'main', and commented out the 'module' line. I then
compiled this program under GHC 6.0.1 or 6.3 on 4 different
architectures (x86, ia64, mips64, sparc) and it doesn't run out of heap,
at least not in the time I was giving it, with and without
optimisations, and via the NCG where applicable.

GHCi (on the machines that support it : x86, ia64, sparc), didn't result
in heap trouble either.

What version of GHC are you using? And how long was "quickly"?

Cheers,
    Don


More information about the Haskell mailing list