[Haskell-cafe] IORef memory leak
Don Stewart
dons at galois.com
Fri Jun 19 12:00:06 EDT 2009
jsnow:
>
> 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)
It is not possible to write a modifyIORef that *doesn't* leak memory!
-- Don
More information about the Haskell-Cafe
mailing list