[commit: ghc] master: Record some notes about "innocuous" transformations (1c2c2d3)
git at git.haskell.org
git at git.haskell.org
Mon Jun 25 16:46:02 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/1c2c2d3dfd4c36884b22163872feb87122b4528d/ghc
>---------------------------------------------------------------
commit 1c2c2d3dfd4c36884b22163872feb87122b4528d
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Thu Jun 7 09:25:33 2018 +0100
Record some notes about "innocuous" transformations
I wondered if some transformations (ticks) might be "innocuous",
in the sense that they do not unlock a later transformation that
does not occur in the same pass. If so, we could refrain from
bumping the overall tick-count for such innocuous transformations,
and perhaps terminate the simplifier one pass earlier.
BUt alas I found that virtually nothing was innocuous! This
commit just adds a Note to record what I learned, in case
anyone wants to try again.
>---------------------------------------------------------------
1c2c2d3dfd4c36884b22163872feb87122b4528d
compiler/simplCore/CoreMonad.hs | 75 ++++++++++++++++++++++++++++++++++++++++-
compiler/simplCore/SimplCore.hs | 1 +
2 files changed, 75 insertions(+), 1 deletion(-)
diff --git a/compiler/simplCore/CoreMonad.hs b/compiler/simplCore/CoreMonad.hs
index 4deee37..6b7393c 100644
--- a/compiler/simplCore/CoreMonad.hs
+++ b/compiler/simplCore/CoreMonad.hs
@@ -343,6 +343,79 @@ pprSimplCount (SimplCount { ticks = tks, details = dts, log1 = l1, log2 = l2 })
else Outputable.empty
]
+{- Note [Which transformations are innocuous]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+At one point (Jun 18) I wondered if some transformations (ticks)
+might be "innocuous", in the sense that they do not unlock a later
+transformation that does not occur in the same pass. If so, we could
+refrain from bumping the overall tick-count for such innocuous
+transformations, and perhaps terminate the simplifier one pass
+earlier.
+
+BUt alas I found that virtually nothing was innocuous! This Note
+just records what I learned, in case anyone wants to try again.
+
+These transformations are not innocuous:
+
+*** NB: I think these ones could be made innocuous
+ EtaExpansion
+ LetFloatFromLet
+
+LetFloatFromLet
+ x = K (let z = e2 in Just z)
+ prepareRhs transforms to
+ x2 = let z=e2 in Just z
+ x = K xs
+ And now more let-floating can happen in the
+ next pass, on x2
+
+PreInlineUnconditionally
+ Example in spectral/cichelli/Auxil
+ hinsert = ...let lo = e in
+ let j = ...lo... in
+ case x of
+ False -> ()
+ True -> case lo of I# lo' ->
+ ...j...
+ When we PreInlineUnconditionally j, lo's occ-info changes to once,
+ so it can be PreInlineUnconditionally in the next pass, and a
+ cascade of further things can happen.
+
+PostInlineUnconditionally
+ let x = e in
+ let y = ...x.. in
+ case .. of { A -> ...x...y...
+ B -> ...x...y... }
+ Current postinlineUnconditinaly will inline y, and then x; sigh.
+
+ But PostInlineUnconditionally might also unlock subsequent
+ transformations for the same reason as PreInlineUnconditionally,
+ so it's probably not innocuous anyway.
+
+KnownBranch, BetaReduction:
+ May drop chunks of code, and thereby enable PreInlineUnconditionally
+ for some let-binding which now occurs once
+
+EtaExpansion:
+ Example in imaginary/digits-of-e1
+ fail = \void. e where e :: IO ()
+ --> etaExpandRhs
+ fail = \void. (\s. (e |> g) s) |> sym g where g :: IO () ~ S -> (S,())
+ --> Next iteration of simplify
+ fail1 = \void. \s. (e |> g) s
+ fail = fail1 |> Void#->sym g
+ And now inline 'fail'
+
+CaseMerge:
+ case x of y {
+ DEFAULT -> case y of z { pi -> ei }
+ alts2 }
+ ---> CaseMerge
+ case x of { pi -> let z = y in ei
+ ; alts2 }
+ The "let z=y" case-binder-swap gets dealt with in the next pass
+-}
+
pprTickCounts :: Map Tick Int -> SDoc
pprTickCounts counts
= vcat (map pprTickGroup groups)
@@ -360,7 +433,7 @@ pprTickGroup group@((tick1,_):_)
| (tick,n) <- sortBy (flip (comparing snd)) group])
pprTickGroup [] = panic "pprTickGroup"
-data Tick
+data Tick -- See Note [Which transformations are innocuous]
= PreInlineUnconditionally Id
| PostInlineUnconditionally Id
diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs
index d461b99..168ece9 100644
--- a/compiler/simplCore/SimplCore.hs
+++ b/compiler/simplCore/SimplCore.hs
@@ -723,6 +723,7 @@ simplifyPgmIO pass@(CoreDoSimplify max_iterations mode)
; return (getTopFloatBinds floats, rules1) } ;
-- Stop if nothing happened; don't dump output
+ -- See Note [Which transformations are innocuous] in CoreMonad
if isZeroSimplCount counts1 then
return ( "Simplifier reached fixed point", iteration_no
, totalise (counts1 : counts_so_far) -- Include "free" ticks
More information about the ghc-commits
mailing list