StateT space leak

Tomasz Zielonka t.zielonka at students.mimuw.edu.pl
Fri Nov 14 00:22:00 EST 2003


On Thu, Nov 13, 2003 at 05:19:28PM -0500, Wojtek Moczydlowski wrote:
> 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.

There is more to it. Let's define

    t2 :: IO ()
    t2 = sequence_ $ repeat $ return ()

t2 behaves in the same way. However, if you compile the module with GHC
with optimisations turned on, both t and t2 run in constant space. OK, I
understand that GHC doesn't do optimisations in interpreted code.

The strange thing is that if you execute

    *A> runStateT (sequence_ $ repeat $ return ()) 1 :: IO ((), Int)

or

    *A> (sequence_ $ repeat $ return ()) :: IO ()

directly in GHCi, then is seems to run in constant space.

> Wojtek

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links


More information about the Haskell mailing list