[Git][ghc/ghc][wip/simplifier-tweaks] Slightly more aggressive postInlineUnconditionally

Simon Peyton Jones (@simonpj) gitlab at gitlab.haskell.org
Thu Jul 27 12:48:56 UTC 2023



Simon Peyton Jones pushed to branch wip/simplifier-tweaks at Glasgow Haskell Compiler / GHC


Commits:
b8ed2990 by Simon Peyton Jones at 2023-07-27T13:47:04+01:00
Slightly more aggressive postInlineUnconditionally

- - - - -


3 changed files:

- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/Stats.hs


Changes:

=====================================
compiler/GHC/Core/Opt/Simplify/Iteration.hs
=====================================
@@ -4106,9 +4106,9 @@ what `f` is, instead of lambda-abstracting over it.
 
 To achieve this:
 
-1. Do not postInlineUnconditionally a join point, until the Final
-   phase.  (The Final phase is still quite early, so we might consider
-   delaying still more.)
+1. Do not postInlineUnconditionally a join point, ever. Doing
+   postInlineUnconditionally is primarily to push allocation into cold
+   branches; but a join point doesn't allocate, so that's a non-motivation.
 
 2. In mkDupableAlt and mkDupableStrictBind, generate an alterative for
    all alternatives, except for exprIsTrival RHSs. Previously we used


=====================================
compiler/GHC/Core/Opt/Simplify/Utils.hs
=====================================
@@ -1538,7 +1538,7 @@ postInlineUnconditionally env bind_cxt old_bndr bndr rhs
                                 = False -- Note [Top level and postInlineUnconditionally]
   | exprIsTrivial rhs           = True
   | BC_Join {} <- bind_cxt      = False -- See point (1) of Note [Duplicating join points]
---   , not (phase == FinalPhase)   = False -- in Simplify.hs
+                                        --     in GHC.Core.Opt.Simplify.Iteration
   | otherwise
   = case occ_info of
       OneOcc { occ_in_lam = in_lam, occ_int_cxt = int_cxt, occ_n_br = n_br }
@@ -1547,10 +1547,10 @@ postInlineUnconditionally env bind_cxt old_bndr bndr rhs
         | let not_inside_lam = in_lam == NotInsideLam
         -> n_br < 100  -- See #23627
 
-           && (  (n_br == 1 && not_inside_lam)
-                      -- See Note [Post-inline for single-use things]
+           && (  (n_br == 1)  -- One syntactic occurrence
+                              -- See Note [Post-inline for single-use things]
               || (is_lazy && smallEnoughToInline uf_opts unfolding))
-                      -- Lazy, and small enough to dup
+                      -- Multiple syntactic occurences; but lazy, and small enough to dup
                       -- ToDo: consider discount on smallEnoughToInline if int_cxt is true
 
            && (not_inside_lam ||
@@ -2353,6 +2353,14 @@ the outer case scrutinises the same variable as the outer case. This
 transformation is called Case Merging.  It avoids that the same
 variable is scrutinised multiple times.
 
+The auxiliary bindings b'=b are annoying, because they force another
+simplifier pass, but there seems no easy way to avoid them.  See
+Note [Which transformations are innocuous] in GHC.Core.Opt.Stats.
+
+See also
+* Note [Example of case-merging and caseRules]
+* Note [Cascading case merge]
+
 Note [Eliminate Identity Case]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
         case e of               ===> e
@@ -2444,7 +2452,6 @@ Wrinkle 4:
   see Note [caseRules for dataToTag] in GHC.Core.Opt.ConstantFold
 
 
-
 Note [Example of case-merging and caseRules]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 The case-transformation rules are quite powerful. Here's a
@@ -2530,6 +2537,9 @@ mkCase, mkCase1, mkCase2, mkCase3
 
 --------------------------------------------------
 --      1. Merge Nested Cases
+--         See Note [Merge Nested Cases]
+--             Note [Example of case-merging and caseRules]
+--             Note [Cascading case merge]
 --------------------------------------------------
 
 mkCase mode scrut outer_bndr alts_ty (Alt DEFAULT _ deflt_rhs : outer_alts)
@@ -2572,6 +2582,7 @@ mkCase mode scrut bndr alts_ty alts = mkCase1 mode scrut bndr alts_ty alts
 
 --------------------------------------------------
 --      2. Eliminate Identity Case
+--         See Note [Eliminate Identity Case]
 --------------------------------------------------
 
 mkCase1 _mode scrut case_bndr _ alts@(Alt _ _ rhs1 : alts')      -- Identity case
@@ -2617,6 +2628,7 @@ mkCase1 mode scrut bndr alts_ty alts = mkCase2 mode scrut bndr alts_ty alts
 
 --------------------------------------------------
 --      2. Scrutinee Constant Folding
+--         See Note [Scrutinee Constant Folding]
 --------------------------------------------------
 
 mkCase2 mode scrut bndr alts_ty alts


=====================================
compiler/GHC/Core/Opt/Stats.hs
=====================================
@@ -179,6 +179,13 @@ PostInlineUnconditionally
   transformations for the same reason as PreInlineUnconditionally,
   so it's probably not innocuous anyway.
 
+  One annoying variant is this.  CaseMerge introduces auxiliary bindings
+     let b = b' in ...
+  This takes another full run of the simplifier to elimiante.  But if
+  the PostInlineUnconditionally, replacing b with b', is the only thing
+  that happens in a Simplifier run, that probably really is innocuous.
+  Perhaps an opportunity here.
+
 KnownBranch, BetaReduction:
   May drop chunks of code, and thereby enable PreInlineUnconditionally
   for some let-binding which now occurs once



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b8ed299073bc7149f868d1c6c0c95e45ac26d038
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/20230727/6d0f96c3/attachment-0001.html>


More information about the ghc-commits mailing list