Reconstructing a record leaks space if any field has a HasCallStack constraint
The following program:
module Main where
import Control.Monad
import Data.IORef
import GHC.Stack
newtype F = F (HasCallStack => ())
main :: IO ()
main = do
ref <- newIORef $ F ()
forever $ do
F f <- readIORef ref
writeIORef ref $! F f
will eat all of your memory because it looks like a call stack entry is attached to f
every time a new F
is written to the IORef
. There doesn't seem to be a way to stop this from happening with withFrozenCallStack
(at least I didn't find any).
The workaround seems to be putting a newtype
around any field that has HasCallStack
, since
module Main where
import Control.Monad
import Data.IORef
import GHC.Stack
newtype X = X (HasCallStack => ())
newtype F = F X
main :: IO ()
main = do
ref <- newIORef . F $ X ()
forever $ do
F f <- readIORef ref
writeIORef ref $! F f
doesn't leak, but it's not at all obvious.
Tested with GHC 9.6.6 and 9.10.1.