[GHC] #14895: STG CSE makes dead binders undead

GHC ghc-devs at haskell.org
Mon Mar 5 21:42:25 UTC 2018


#14895: STG CSE makes dead binders undead
-------------------------------------+-------------------------------------
           Reporter:  hsyl20         |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.2.2
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Debugging
  Unknown/Multiple                   |  information is incorrect
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Consider the following example:

 {{{#!hs
 go :: (a -> b) -> Either String a -> Either String b
 go f (Right a) = Right (f a)
 go _ (Left e)  = Left e
 }}}

 GHC with `-O2` converts it into the following STG:

 {{{#!hs
 TestUndead.go
   :: forall a b.
      (a -> b)
      -> Data.Either.Either GHC.Base.String a
      -> Data.Either.Either GHC.Base.String b
 [GblId,
  Arity=2,
  Caf=NoCafRefs,
  Str=<L,1*C1(U)><S,1*U>,
  Unf=OtherCon []] =
     \r [f_s17n ds_s17o]
         case ds_s17o of {
           Data.Either.Left e_s17q [Occ=Once] -> wild_s17p;
           Data.Either.Right a1_s17r [Occ=Once] ->
               let {
                 sat_s17s [Occ=Once] :: b_aVN
                 [LclId] =
                     \u [] f_s17n a1_s17r;
               } in  Data.Either.Right [sat_s17s];
         };
 }}}

 Notice that the dead binder `wild_s17p` is now alive (in the first
 alternative) but it isn't shown in `case ds_s17o of {` because the pretty-
 printer still assumes it is dead.

 I think that in `stgCseExpr .. (StgCase ...)` (simplStg/StgCse.hs) we
 should check if the new binder is alive in the new alternatives, just like
 we do in `coreToStgExpr (Case ...)` (stgSyn/CoreToStg.hs), and use
 `setIdOccInfo (ManyOccs NoTailCallInfo)` on the new binder if necessary.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14895>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list