[Git][ghc/ghc][master] mkTick: Push ticks through unsafeCoerce#.
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Tue Oct 22 20:31:17 UTC 2024
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
edf3bdf5 by Andreas Klebinger at 2024-10-22T16:30:42-04:00
mkTick: Push ticks through unsafeCoerce#.
unsafeCoerce# doesn't exist at runtime so we should treat it like a Cast
for the purpose of mkTick.
This means if we have `{-# SCC foo #-} (unsafeCoerce# trivial_expr))` we
now push the scope part of the cost centre up to `trivial_expr` at which
point we can discard it completely if the expression is trivial enough.
This fixes #25212.
- - - - -
2 changed files:
- compiler/GHC/Core/Utils.hs
- compiler/GHC/Types/Tickish.hs
Changes:
=====================================
compiler/GHC/Core/Utils.hs
=====================================
@@ -305,7 +305,6 @@ mkTick t orig_expr = mkTick' id id orig_expr
-- Some ticks (cost-centres) can be split in two, with the
-- non-counting part having laxer placement properties.
canSplit = tickishCanSplit t && tickishPlace (mkNoCount t) /= tickishPlace t
-
-- mkTick' handles floating of ticks *into* the expression.
-- In this function, `top` is applied after adding the tick, and `rest` before.
-- This will result in applications that look like (top $ Tick t $ rest expr).
@@ -316,6 +315,10 @@ mkTick t orig_expr = mkTick' id id orig_expr
-> CoreExpr -- current expression
-> CoreExpr
mkTick' top rest expr = case expr of
+ -- Float ticks into unsafe coerce the same way we would do with a cast.
+ Case scrut bndr ty alts@[Alt ac abs _rhs]
+ | Just rhs <- isUnsafeEqualityCase scrut bndr alts
+ -> top $ mkTick' (\e -> Case scrut bndr ty [Alt ac abs e]) rest rhs
-- Cost centre ticks should never be reordered relative to each
-- other. Therefore we can stop whenever two collide.
@@ -1251,7 +1254,7 @@ Note [Tick trivial]
Ticks are only trivial if they are pure annotations. If we treat
"tick<n> x" as trivial, it will be inlined inside lambdas and the
entry count will be skewed, for example. Furthermore "scc<n> x" will
-turn into just "x" in mkTick.
+turn into just "x" in mkTick. At least if `x` is not a function.
Note [Empty case is trivial]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~
=====================================
compiler/GHC/Types/Tickish.hs
=====================================
@@ -295,13 +295,15 @@ tickishCanSplit _ = False
mkNoCount :: GenTickish pass -> GenTickish pass
mkNoCount n | not (tickishCounts n) = n
| not (tickishCanSplit n) = panic "mkNoCount: Cannot split!"
-mkNoCount n at ProfNote{} = n {profNoteCount = False}
+mkNoCount n at ProfNote{} = let n' = n {profNoteCount = False}
+ in assert (profNoteCount n) n'
mkNoCount _ = panic "mkNoCount: Undefined split!"
mkNoScope :: GenTickish pass -> GenTickish pass
mkNoScope n | tickishScoped n == NoScope = n
| not (tickishCanSplit n) = panic "mkNoScope: Cannot split!"
-mkNoScope n at ProfNote{} = n {profNoteScope = False}
+mkNoScope n at ProfNote{} = let n' = n {profNoteScope = False}
+ in assert (profNoteCount n) n'
mkNoScope _ = panic "mkNoScope: Undefined split!"
-- | Return @True@ if this source annotation compiles to some backend
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/edf3bdf57501beb3372eaa0a9602f1094cdf30d1
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/edf3bdf57501beb3372eaa0a9602f1094cdf30d1
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/20241022/b7f13bd3/attachment-0001.html>
More information about the ghc-commits
mailing list