On Fri, Nov 14, 2003 at 12:22:00AM +0100, Tomasz Zielonka wrote:
>
> 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 con
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 pro
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
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? I