[Haskell-cafe] GHC, odd concurrency space leak

Bertram Felgenhauer bertram.felgenhauer at googlemail.com
Sat Apr 17 20:05:30 EDT 2010


Daniel Fischer wrote:
> 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).

Yes, I was concentrating on -O2, without -fno-state-hack.

> 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 is

    always = \a_aeO -> let k_sYz = always a_aeO
                       in  a_aeO >> k_sYz

specialised to IO, and with (>>) inlined.

Where is the knot?

regards,

Bertram


More information about the Haskell-Cafe mailing list