[Git][ghc/ghc][master] simplCore: Ignore ticks in rule templates

Marge Bot gitlab at gitlab.haskell.org
Sat May 23 17:38:00 UTC 2020



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
dcd6bdcc by Ben Gamari at 2020-05-23T13:37:48-04:00
simplCore: Ignore ticks in rule templates

This fixes #17619, where a tick snuck in to the template of a rule,
resulting in a panic during rule matching. The tick in question was
introduced via post-inlining, as discussed in `Note [Simplifying
rules]`. The solution we decided upon was to simply ignore ticks in the
rule template, as discussed in `Note [Tick annotations in RULE
matching]`.

Fixes #18162.
Fixes #17619.

- - - - -


2 changed files:

- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Rules.hs


Changes:

=====================================
compiler/GHC/Core/Opt/Simplify/Utils.hs
=====================================
@@ -830,6 +830,21 @@ Ticks into the LHS, which makes matching trickier. #10665, #10745.
 Doing this to either side confounds tools like HERMIT, which seek to reason
 about and apply the RULES as originally written. See #10829.
 
+There is, however, one case where we are pretty much /forced/ to transform the
+LHS of a rule: postInlineUnconditionally. For instance, in the case of
+
+    let f = g @Int in f
+
+We very much want to inline f into the body of the let. However, to do so (and
+be able to safely drop f's binding) we must inline into all occurrences of f,
+including those in the LHS of rules.
+
+This can cause somewhat surprising results; for instance, in #18162 we found
+that a rule template contained ticks in its arguments, because
+postInlineUnconditionally substituted in a trivial expression that contains
+ticks. See Note [Tick annotations in RULE matching] in GHC.Core.Rules for
+details.
+
 Note [No eta expansion in stable unfoldings]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 If we have a stable unfolding
@@ -1251,6 +1266,10 @@ it's best to inline it anyway.  We often get a=E; b=a from desugaring,
 with both a and b marked NOINLINE.  But that seems incompatible with
 our new view that inlining is like a RULE, so I'm sticking to the 'active'
 story for now.
+
+NB: unconditional inlining of this sort can introduce ticks in places that
+may seem surprising; for instance, the LHS of rules. See Note [Simplfying
+rules] for details.
 -}
 
 postInlineUnconditionally


=====================================
compiler/GHC/Core/Rules.hs
=====================================
@@ -714,11 +714,15 @@ match :: RuleMatchEnv
       -> CoreExpr               -- Target
       -> Maybe RuleSubst
 
--- We look through certain ticks. See note [Tick annotations in RULE matching]
+-- We look through certain ticks. See Note [Tick annotations in RULE matching]
 match renv subst e1 (Tick t e2)
   | tickishFloatable t
   = match renv subst' e1 e2
   where subst' = subst { rs_binds = rs_binds subst . mkTick t }
+match renv subst (Tick t e1) e2
+  -- Ignore ticks in rule template.
+  | tickishFloatable t
+  =  match renv subst e1 e2
 match _ _ e at Tick{} _
   = pprPanic "Tick in rule" (ppr e)
 
@@ -1016,7 +1020,7 @@ Hence, (a) the guard (not (isLocallyBoundR v2))
 Note [Tick annotations in RULE matching]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 
-We used to unconditionally look through Notes in both template and
+We used to unconditionally look through ticks in both template and
 expression being matched. This is actually illegal for counting or
 cost-centre-scoped ticks, because we have no place to put them without
 changing entry counts and/or costs. So now we just fail the match in
@@ -1025,6 +1029,11 @@ these cases.
 On the other hand, where we are allowed to insert new cost into the
 tick scope, we can float them upwards to the rule application site.
 
+Moreover, we may encounter ticks in the template of a rule. There are a few
+ways in which these may be introduced (e.g. #18162, #17619). Such ticks are
+ignored by the matcher. See Note [Simplifying rules] in
+GHC.Core.Opt.Simplify.Utils for details.
+
 cf Note [Notes in call patterns] in GHC.Core.Opt.SpecConstr
 
 Note [Matching lets]



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dcd6bdcce57430d08b335014625722c487ea08e4

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dcd6bdcce57430d08b335014625722c487ea08e4
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200523/933e7d3a/attachment-0001.html>


More information about the ghc-commits mailing list