
On Thu, Apr 15, 2010 at 1:33 AM, Daniel Fischer
Can some core expert please look at these and explain the difference?
I'm interested in an explanation too.
+1 The behaviour is consistent. GHC 6.8.3, 6.10.4, 6.12.1 and 6.13-20100416 all agree on the space leak. Here is the minimal program I have with the leak: \begin{code} {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Main where import Control.Monad.State import Control.Concurrent newtype Process b c = Process (StateT b IO c) deriving (Monad, MonadIO, MonadState b) run :: b -> Process b c -> IO (c, b) run st (Process p) = runStateT p st spawn :: b -> Process b () -> IO ThreadId spawn st p = forkIO $ run st p >> return () p1 :: Process () () p1 = forever $ return () startp1 :: IO ThreadId startp1 = spawn () p1 startp2 :: IO ThreadId startp2 = spawn () (forever $ do liftIO startp1 liftIO $ putStrLn "Delaying" liftIO $ threadDelay (10 * 1000000)) main = do putStrLn "Main thread starting" startp2 threadDelay (1 * 1000000) \end{code} .. so it looks like it is the state monad. I used ghc-core to print out this program in Core-format, killed all the type casts from System-F_c and inspected the code. I can't see what would make any problem there, but that was my first use of Core, so I might have overlooked something. The only thing I can see is that we "split" the State# RealWorld whenever we fork, but I think that is expected behaviour. The only other culprit I could guess at is the exception catch# primops in there. Should I file this as a bug? It has some bug-like qualities to it. In any case, what is going on is quite complicated so a resolution would be nice. If for nothing else to understand what is going on. -- J.