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

#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=,
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

#14895: STG CSE makes dead binders undead -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by osa1): Good catch. I had observed this when debugging some other tickets, but couldn't figure why it was happening. I ended up enabling some debug flags that make printer print all variables. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14895#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14895: STG CSE makes dead binders undead -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by simonpj): I am not sure if the dead-ness info is use for anything except pretty- printing. Perhaps not.... but worth a check. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14895#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14895: STG CSE makes dead binders undead -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by osa1): Actually `isDeadBinder` check (the check that causes not printing case binders) is also used in code generation: {{{#!haskell cgCase (StgOpApp (StgPrimOp op) args _) bndr (AlgAlt tycon) alts | isEnumerationTyCon tycon -- Note [case on bool] = do { tag_expr <- do_enum_primop op args -- If the binder is not dead, convert the tag to a constructor -- and assign it. ; unless (isDeadBinder bndr) $ do { dflags <- getDynFlags ; tmp_reg <- bindArgToReg (NonVoid bndr) ; emitAssign (CmmLocal tmp_reg) (tagToClosure dflags tycon tag_expr) } ; (mb_deflt, branches) <- cgAlgAltRhss (NoGcInAlts,AssignedDirectly) (NonVoid bndr) alts -- See Note [GC for conditionals] ; emitSwitch tag_expr branches mb_deflt 0 (tyConFamilySize tycon - 1) ; return AssignedDirectly } }}} But this probably doesn't break anything because the scrutinee binder becomes undead only when (1) scrutinee is a data con application (2) the application repeats in an alternative. The code I showed above is for generating code when scrutinee is a primop application so it's safe. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14895#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14895: STG CSE makes dead binders undead -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by simonpj): Delicate! Can you add a Note in `StgCSE` to explain? Actually it'd be more correct to do this in `StgCSE` * Zap the dead-binder flag on most case-binders (explaining why) * But not the ones for primop applications (because they aren't CSE'd, I think you are saying). That way they never lie. We'd still need a note to say that dead-ness is now a bit pessimistic; but the code gen doesn't use it (except in a narrow case) so the pessimism doesn't matter. Not hard to do. Thanks -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14895#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC