[Haskell-cafe] Monad Transformer Space Leak
Clark Gaebel
cgaebel at uwaterloo.ca
Mon Apr 22 21:54:54 CEST 2013
Hi everyone!
For some reason, this leaks thunks:
module Main where
import Control.Monad
import Control.Monad.MC -- from monte-carlo
import Control.Monad.ST.Strict
go :: Int -> MCT (ST s) ()
go k = replicateM_ k (return ())
main = print $ runST $ evalMCT (go 100000000) rng
where
rng = mt19937 0
while this does not:
module Main where
import Control.Monad
import Control.Monad.MC
go :: Int -> MC ()
go k = replicateM_ k (return ())
main = print $ evalMC (go 100000000) rng
where
rng = mt19937 0
Can anyone help me figure out what's going on here?
Thanks,
- Clark
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130422/cd20c36e/attachment.htm>
More information about the Haskell-Cafe
mailing list