[Haskell-cafe] IORef memory leak

Jim Snow jsnow at cs.pdx.edu
Thu Jun 18 22:46:17 EDT 2009


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


More information about the Haskell-Cafe mailing list