[Haskell-cafe] GHC, odd concurrency space leak

Daniel Fischer daniel.is.fischer at web.de
Sat Apr 17 19:05:15 EDT 2010


Am Samstag 17 April 2010 22:11:05 schrieb Bertram Felgenhauer:
> Daniel Fischer wrote:
> > Am Samstag 17 April 2010 14:41:28 schrieb Simon Peyton-Jones:
> > > I have not been following the details of this, I'm afraid, but I
> > > notice
> >
> > this:
> > > > forever' m = do _ <- m
> > > >                 forever' m
> > >
> > > When I define that version of forever, the space leak goes away.
> > >
> > > What was the old version of forever that led to the leak?
> >
> > Control.Monad.forever
> >
> > forever :: Monad m => m a -> m b
> > forever m = m >> forever m
> >
> > However, that isn't the problem. In my tests, both variants of forever
> > exhibit the same behaviour, what makes it leak or not is the
> > optimisation level.
>
> This definition, plus sharing, is the source of the space leak.
> Consider this modification of your code:
>
>     import Control.Concurrent
>
>     always :: Monad m => m a -> m b
>     always a = -- let act = a >> act in act
>         do
>         _ <- a
>         always a
>
>     noop :: IO ()
>     noop = return ()
>
>     body :: IO ()
>     body = always noop
>
>     spawner :: IO ()
>     spawner = do
>         forkIO $ body
>         putStrLn "Delaying"
>         threadDelay 1000000
>         body `seq` return ()
>
>     main :: IO ()
>     main = do
>         putStrLn "Spawning"
>         forkIO spawner
>         putStrLn "Delaying main"
>         threadDelay 4000000
>
> Note that the 'always' in 'spawner' is gone, but it still exhibits the
> space leak. The leak goes away if the final line of 'spawner' is
> removed, hinting at the real problem: 'always' actually creates a long
> chain of actions instead of tying the knot.

Except that with optimisations turned on, GHC ties the knot for you (at 
least if always isn't exported).
Without -fno-state-hack, the knot is tied so tightly that 
always (return ()) is never descheduled (and there's no leak).
With -fno-state-hack, I get

Rec {
Main.main_always :: GHC.Types.IO () -> GHC.Types.IO ()
GblId
[Arity 1
 NoCafRefs
 Str: DmdType L]
Main.main_always =
  \ (a_aeO :: GHC.Types.IO ()) ->
    let {
      k_sYz :: GHC.Types.IO ()
      LclId
      [Str: DmdType]
      k_sYz = Main.main_always a_aeO } in
    (\ (eta_ann :: GHC.Prim.State# GHC.Prim.RealWorld) ->
       case (a_aeO
             `cast` (GHC.Types.NTCo:IO ()
                     :: GHC.Types.IO ()
                          ~
                        (GHC.Prim.State# GHC.Prim.RealWorld
                         -> (# GHC.Prim.State# GHC.Prim.RealWorld, () #))))
              eta_ann
       of _ { (# new_s_anz, _ #) ->
       (k_sYz
        `cast` (GHC.Types.NTCo:IO ()
                :: GHC.Types.IO ()
                     ~
                   (GHC.Prim.State# GHC.Prim.RealWorld
                    -> (# GHC.Prim.State# GHC.Prim.RealWorld, () #))))
         new_s_anz
       })
    `cast` (sym (GHC.Types.NTCo:IO ())
            :: (GHC.Prim.State# GHC.Prim.RealWorld
                -> (# GHC.Prim.State# GHC.Prim.RealWorld, () #))
                 ~
               GHC.Types.IO ())
end Rec }

which, despite tying the knot, leaks (so the program at least terminates).

>
> Indeed the following definition of 'always' (or 'forever') fares better
> in that regard, but is more susceptible to producing unproductive loops:

Indeed, that doesn't terminate with -O2 -fno-state-hack

>
>     always a = let act = a >> act in act
>
> (I used  noop = yield  for avoiding that problem in my tests)
>
> regards,
>
> Bertram


More information about the Haskell-Cafe mailing list