[Haskell-cafe] GHC, odd concurrency space leak
Jason Dagit
dagit at codersbase.com
Wed Apr 14 18:52:22 EDT 2010
On Wed, Apr 14, 2010 at 3:13 PM, Daniel Fischer <daniel.is.fischer at web.de>wrote:
> Am Mittwoch 14 April 2010 23:49:43 schrieb Jason Dagit:
> > > It will be interesting to hear what fixes this!
> > >
> > >
> > > forever' m = do _ <- m
> > > forever' m
> >
> > When I define that version of forever, the space leak goes away.
>
> Not with optimisations.
>
Thanks for pointing that out. I forgot to say so in my email.
Here are two reduced versions of the original program:
Good version, ghc --make Terminate.hs:
\begin{code}
{-# OPTIONS -O0 #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Main where
import Control.Monad (forever)
import Control.Concurrent
import Control.Concurrent.STM
spawn :: IO a -> IO ThreadId
spawn io = forkIO (io >> return ())
forever' m = do _ <- m
forever' m
startp4 :: IO ThreadId
startp4 = spawn (forever' (return ()))
startp3 :: IO ThreadId
startp3 = spawn (forever $
do startp4
putStrLn "Delaying"
threadDelay (3 * 1000000))
main = do
putStrLn "Main thread starting"
startp3
threadDelay (1 * 1000000)
\end{code}
The bad version, ghc --make NonTermination.hs:
\begin{code}
{-# OPTIONS -O2 #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
-- Note: Change the optimization to -O1 to get a terminating version
-- that uses much more memory than it should.
module Main where
import Control.Monad (forever)
import Control.Concurrent
import Control.Concurrent.STM
spawn :: IO a -> IO ThreadId
spawn io = forkIO (io >> return ())
startp4 :: IO ThreadId
startp4 = spawn (forever (return ()))
startp3 :: IO ThreadId
startp3 = spawn (forever $
do startp4
putStrLn "Delaying"
threadDelay (3 * 1000000))
main = do
putStrLn "Main thread starting"
startp3
threadDelay (1 * 1000000)
\end{code}
Can some core expert please look at these and explain the difference?
Thanks!
Jason
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100414/3bf7e398/attachment-0001.html
More information about the Haskell-Cafe
mailing list