
It looks offhand like you're not being strict enough when you put things back in the IORef, and so it's building up thunks of (+1)... With two slight mods: go 0 = return () go n = do modifyIORef ior (+1) go (n-1) --> go 0 = return () go n = do modifyIORef ior (\ x -> let x' = x+1 in x `seq` x') go (n-1) and go n = do x <- readIORef ior writeIORef ior (x+1) go (n-1) --> go n = do x <- readIORef ior writeIORef ior $! x+1 go (n-1) It runs much better (with loop count = 10,000,000) -- leak1 is the code you posted, leak2 is with these changes: rmm@Hugo:~$ ./leak1 +RTS -s ./leak1 +RTS -s 200,296,364 bytes allocated in the heap 365,950,896 bytes copied during GC 66,276,472 bytes maximum residency (7 sample(s)) 1,906,448 bytes maximum slop 131 MB total memory in use (1 MB lost due to fragmentation) <snip> %GC time 75.9% (79.2% elapsed) Alloc rate 977,656,335 bytes per MUT second Productivity 24.0% of total user, 20.5% of total elapsed rmm@Hugo:~$ ./leak2 +RTS -s ./leak2 +RTS -s 160,006,032 bytes allocated in the heap 11,720 bytes copied during GC 1,452 bytes maximum residency (1 sample(s)) 9,480 bytes maximum slop 1 MB total memory in use (0 MB lost due to fragmentation) <snip> %GC time 0.5% (0.8% elapsed) Alloc rate 626,590,037 bytes per MUT second Productivity 99.2% of total user, 97.8% of total elapsed -Ross On Jun 18, 2009, at 10:46 PM, Jim Snow wrote:
I'm having some trouble with excessive memory use in a program that uses a lot of IORefs. I was able to write a much simpler program which exhibits the same sort of behavior. It appears that "modifyIORef" and "writeIORef" leak memory; perhaps they keep a reference to the old value. I tried both ghc-6.8.3 and ghc-6.10.1.
Is this a known limitation, or is this a ghc bug, or am I using IORefs in the wrong way?
-jim
module Main where
import Data.IORef import Control.Monad
-- Leaks memory leakcheck1 ior = do go 1000000000 where go 0 = return () go n = do modifyIORef ior (+1) go (n-1)
-- Leaks memory leakcheck2 ior = do go 1000000000 where go 0 = return () go n = do x <- readIORef ior writeIORef ior (x+1) go (n-1)
-- Runs in constant memory leakcheck3 ior = do go 1000000000 where go 0 = return () go n = do x <- readIORef ior go (n-1)
main :: IO () main = do ior <- newIORef 0 leakcheck2 ior
compiled with: ghc -O2 --make Leak.hs -o Leak _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe