help diagnosing space leak with IORef/STRef, just incrementing a million times.

I have a space leak in a function that increments a number inside IORef or STRef (either lazy or strict). Is this the kind of problem that can be diagnosed and fixed using the approach described in RWH, with space profiling? Otherwise what's the right approach to diagnose and fix? I wrote a non-list-using, and tail call-using, iterateMonadic funcation that does the same thing as replicateM, in case the problem was due to iterateM using a list structure, but iterateMonadic and replicateM had same memory leak. I can run this problem with +RTS -K100M -RTS but this aditional memory shouldn't be needed. {-# LANGUAGE RankNTypes, BangPatterns #-} import Data.List import Control.Monad.State.Strict import Data.Array.MArray import Data.Array.IO import Data.Array.ST import Control.Monad.ST import Control.Applicative import Data.IORef import Data.STRef.Strict import Data.STRef import GHC.ST import Control.Applicative ((<$>)) main = do -- putStrLn "ioIters, iterateMonadic: " -- print =<< ioIters iters iterateMonadic -- putStrLn "ioIters, replicateM_: " -- print =<< ioIters iters replicateM_ -- putStrLn "lazySTIters, iterateMonadic: " -- print $ lazySTIters iters iterateMonadic -- putStrLn "lazySTIters, replicateM_: " -- print $ lazySTIters iters replicateM_ putStrLn "strictSTIters, iterateMonadic: " print $ strictSTIters iters iterateMonadic -- putStrLn "strictSTIters, replicateM_: " -- print $ strictSTIters iters replicateM_ type Iter = (Monad m) => Int -> m () -> m () iterateMonadic :: (Monad m) => Int -> m a -> m a iterateMonadic n mx = do let loop 0 acc = acc loop n acc = loop (n-1) (acc >> mx ) loop n mx iters = 10^7 ioIters :: Int -> Iter -> IO Int ioIters numIters iteratorM = do tmp <- newIORef 0 iteratorM numIters ( modifyIORef tmp (+1) ) readIORef tmp lazySTIters :: Int -> Iter -> Int lazySTIters numIters iteratorM = runST $ do tmp <- Data.STRef.newSTRef 0 iteratorM numIters ( Data.STRef.modifySTRef tmp (+1) ) Data.STRef.readSTRef tmp strictSTIters :: Int -> Iter -> Int strictSTIters numIters iteratorM = runST $ do tmp <- Data.STRef.Strict.newSTRef 0 iteratorM numIters ( Data.STRef.Strict.modifySTRef tmp incr' ) Data.STRef.Strict.readSTRef tmp incr' (!x) = x + 1

On 13-01-07 12:12 AM, Thomas Hartman wrote:
I have a space leak in a function that increments a number inside IORef or STRef (either lazy or strict).
IORef and STRef operations do not automatically evaluate contents. "writeIORef r (x + 1)" simply stores a pointer to the expression (thunk) "x + 1" into the mutable cell. readIORef just reports back a pointer. modifyIORef just calls readIORef and writeIORef. No evaluation throughout. "modifyIORef incr" where incr !x = x + 1 does not make a difference because it is just "writeIORef r (incr x))", i.e., simply stores a pointer to the expression (thunk) "incr x" into the mutable cell. The whole process doesn't even care about how many bangs are in incr. (It is illuminating to consider how "const True (incr x)" does not evaluate x. A pointer to True and a pointer to "incr x" are passed to const, then const throws away the latter without even looking. See also "const True undefined". One day, you will thank "writeIORef r undefined"; I certainly did.) Same for both Data.STRef.Strict and Data.STRef.Lazy. They do not mean what you think. Here is what they mean: Data.STRef.Strict means what Control.Monad.ST.Strict means Data.STRef.Lazy means what Control.Monad.ST.Lazy means Control.Monad.ST.Strict means that the following hangs: x = head (runST list) where list :: ST s [Bool] list = do {xs <- list; return (True : xs)} Control.Monad.ST.Lazy means that the above terminates and gives the answer True. (Up to this point, same story for Control.Monad.State.Strict and Control.Monad.State.Lazy.) I still have not understood Control.Monad.ST.Lazy enough to articulate its full semantics, but I have some more examples to show what it does: http://hpaste.org/63925 By understanding what "Lazy" in Control.Monad.ST.Lazy means, you also see what "Strict" does *not* mean. In IO or Control.Monad.ST.Strict, use let y = x+1 in y `seq` write[IO/ST]Ref r y to expedite the evaluation of x+1. Using the same idea, you may write your own modify[IO/ST]RefNOW to evaluate while updating.

A similar use-case and same solution with IORefs:
http://hpaste.org/diff/80055/80058 Guess which one threw a
stackoverflow and which one ran indefinitely when given a few hundred
million lines of input.
On 7 January 2013 07:35, Albert Y. C. Lai
On 13-01-07 12:12 AM, Thomas Hartman wrote:
I have a space leak in a function that increments a number inside IORef or STRef (either lazy or strict).
IORef and STRef operations do not automatically evaluate contents. "writeIORef r (x + 1)" simply stores a pointer to the expression (thunk) "x + 1" into the mutable cell. readIORef just reports back a pointer. modifyIORef just calls readIORef and writeIORef. No evaluation throughout.
"modifyIORef incr" where
incr !x = x + 1
does not make a difference because it is just "writeIORef r (incr x))", i.e., simply stores a pointer to the expression (thunk) "incr x" into the mutable cell. The whole process doesn't even care about how many bangs are in incr.
(It is illuminating to consider how "const True (incr x)" does not evaluate x. A pointer to True and a pointer to "incr x" are passed to const, then const throws away the latter without even looking. See also "const True undefined". One day, you will thank "writeIORef r undefined"; I certainly did.)
Same for both Data.STRef.Strict and Data.STRef.Lazy. They do not mean what you think. Here is what they mean:
Data.STRef.Strict means what Control.Monad.ST.Strict means Data.STRef.Lazy means what Control.Monad.ST.Lazy means
Control.Monad.ST.Strict means that the following hangs:
x = head (runST list) where list :: ST s [Bool] list = do {xs <- list; return (True : xs)}
Control.Monad.ST.Lazy means that the above terminates and gives the answer True.
(Up to this point, same story for Control.Monad.State.Strict and Control.Monad.State.Lazy.)
I still have not understood Control.Monad.ST.Lazy enough to articulate its full semantics, but I have some more examples to show what it does:
By understanding what "Lazy" in Control.Monad.ST.Lazy means, you also see what "Strict" does *not* mean.
In IO or Control.Monad.ST.Strict, use
let y = x+1 in y `seq` write[IO/ST]Ref r y
to expedite the evaluation of x+1. Using the same idea, you may write your own modify[IO/ST]RefNOW to evaluate while updating.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Albert Y. C. Lai
-
Christopher Done
-
Thomas Hartman