<br><br><div class="gmail_quote">On Fri, Apr 16, 2010 at 2:51 PM, Jesper Louis Andersen <span dir="ltr">&lt;<a href="mailto:jesper.louis.andersen@gmail.com">jesper.louis.andersen@gmail.com</a>&gt;</span> wrote:<br><blockquote class="gmail_quote" style="border-left: 1px solid rgb(204, 204, 204); margin: 0pt 0pt 0pt 0.8ex; padding-left: 1ex;">
On Thu, Apr 15, 2010 at 1:33 AM, Daniel Fischer<br>
<div class="im">&lt;<a href="mailto:daniel.is.fischer@web.de">daniel.is.fischer@web.de</a>&gt; wrote:<br>
&gt;&gt;<br>
</div><div class="im">&gt;&gt; Can some core expert please look at these and explain the difference?<br>
&gt;&gt;<br>
&gt;<br>
&gt; I&#39;m interested in an explanation too.<br>
&gt;<br>
<br>
</div>+1<br>
<br>
The behaviour is consistent. GHC 6.8.3, 6.10.4, 6.12.1 and<br>
6.13-20100416 all agree on the space leak. Here is the minimal program<br>
I have with the leak:<br></blockquote><div><br>Myself and others posted &quot;simpler&quot; programs that had similar bad behavior, including the space leak (depending on optimizations flags).  I realize it&#39;s tedious to retest all those versions, but do you think you could check with one of the other versions that doesn&#39;t need mtl?<br>
 <br></div><blockquote class="gmail_quote" style="border-left: 1px solid rgb(204, 204, 204); margin: 0pt 0pt 0pt 0.8ex; padding-left: 1ex;">
<br>
\begin{code}<br>
<div class="im">{-# LANGUAGE GeneralizedNewtypeDeriving #-}<br>
<br>
module Main where<br>
</div>import Control.Monad.State<br>
import Control.Concurrent<br>
<br>
newtype Process b c = Process (StateT b IO c)<br>
  deriving (Monad, MonadIO, MonadState b)<br>
<br>
run :: b -&gt; Process b c -&gt; IO (c, b)<br>
run st (Process p) = runStateT p st<br>
<br>
spawn :: b -&gt; Process b () -&gt; IO ThreadId<br>
spawn st p = forkIO $ run st p &gt;&gt; return ()<br>
<div class="im"><br>
p1 :: Process () ()<br>
p1 = forever $ return ()<br>
<br>
startp1 :: IO ThreadId<br>
startp1 = spawn () p1<br>
<br>
startp2 :: IO ThreadId<br>
startp2 = spawn () (forever $<br>
                       do liftIO startp1<br>
                          liftIO $ putStrLn &quot;Delaying&quot;<br>
</div>                          liftIO $ threadDelay (10 * 1000000))<br>
<div class="im"><br>
main = do<br>
  putStrLn &quot;Main thread starting&quot;<br>
</div>  startp2<br>
<div class="im">  threadDelay (1 * 1000000)<br>
\end{code}<br>
<br>
</div>.. so it looks like it is the state monad.</blockquote><div><br>I don&#39;t think so because we were able to produce the space leak without using StateT.<br><br> </div><blockquote class="gmail_quote" style="border-left: 1px solid rgb(204, 204, 204); margin: 0pt 0pt 0pt 0.8ex; padding-left: 1ex;">
 I used ghc-core to print<br>
out this program in Core-format, killed all the type casts from<br>
System-F_c and inspected the code. I can&#39;t see what would make any<br>
problem there, but that was my first use of Core, so I might have<br>
overlooked something. The only thing I can see is that we &quot;split&quot; the<br>
State# RealWorld whenever we fork, but I think that is expected<br>
behaviour. The only other culprit I could guess at is the exception<br>
catch# primops in there.<br>
<br>
Should I file this as a bug? It has some bug-like qualities to it. In<br>
any case, what is going on is quite complicated so a resolution would<br>
be nice. If for nothing else to understand what is going on.<br></blockquote><div><br>Well, I think Bulat correctly characterized the non-termination aspect.  I didn&#39;t think the cooperative aspect of threading applied with the threaded RTS, so I&#39;m not 100% sure I believe his characterization, but otherwise it seems like a reasonable explanation.  The space leakiness is a different issue and likely worth a bug report in its own right.  Do you think you could try checking for the speak leaking using the compacting garbage collector?  I think that one is enabled with +RTS -c -RTS.<br>
<br>Thanks for checking on all those different versions of GHC.<br><br>Jason<br><br><br><br><br></div></div>