[GHC] #15417: Memory leaks because of too conservative isAlive check in the GC
GHC
ghc-devs at haskell.org
Thu Jul 19 14:39:44 UTC 2018
#15417: Memory leaks because of too conservative isAlive check in the GC
-------------------------------------+-------------------------------------
Reporter: osa1 | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: Research needed
Component: Runtime | Version: 8.5
System |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
(See also the mailing list [https://mail.haskell.org/pipermail/ghc-
devs/2018-July/016027.html thread])
Static objects with no SRTs and pointer fields are currently ignored by
`evacuate()`. This is efficient but causes trouble when checking alive-
ness of static objects in `isAlive()`, which is used for (among other
things) checking whether a weak's key has died. This causes leaks as value
of a weak with static key will always be kept alive.
Here's a demonstration:
{{{#!haskell
module Main where
import System.Mem.Weak (mkWeak, deRefWeak)
import System.Mem (performMajorGC)
mkKey :: IO String
mkKey = readFile "/dev/random"
-- mkKey :: IO Int
-- mkKey = return 1
main :: IO ()
main = do
w <- mkKey >>= \k -> mkWeak k () Nothing
performMajorGC
performMajorGC
performMajorGC
deRefWeak w >>= print
}}}
The idea is that the first `mkKey` function returns a non-static string
and this program prints `Nothing`. If I enable the second `mkKey` function
the key is now a static object and the program prints `Just ()`.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15417>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list