[Git][ghc/ghc][wip/simplifier-tweaks] 2 commits: Wibbles
Simon Peyton Jones (@simonpj)
gitlab at gitlab.haskell.org
Tue Oct 10 15:26:59 UTC 2023
Simon Peyton Jones pushed to branch wip/simplifier-tweaks at Glasgow Haskell Compiler / GHC
Commits:
12609f12 by Simon Peyton Jones at 2023-10-10T16:26:33+01:00
Wibbles
- - - - -
d5d52467 by Simon Peyton Jones at 2023-10-10T16:26:42+01:00
Tickish comment
- - - - -
3 changed files:
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Types/Tickish.hs
Changes:
=====================================
compiler/GHC/Core/Opt/OccurAnal.hs
=====================================
@@ -2490,6 +2490,20 @@ But it is not necessary to gather CoVars from the types of other binders.
* For case-alt binders, if the type mentions a CoVar, so will the scrutinee
(since it has the same type)
+
+Note [Simplifying ticks]
+~~~~~~~~~~~~~~~~~~~~~~~~
+Here's a worry I tripped over, but have not actioned (#24078). Consider
+ f (Tick t e)
+where f is strict. According to GHC.Core.Opt.Simplify.Iteraion.simplTick,
+if (t `tickishScopesLike` SoftScope) we will float the tick to the outside:
+ Tick t (f e)
+Fine for counting ticks, not for scoped ticks.
+
+Now suppose `f` is a join point `$j`. That should not lose the tail-call-ness.
+We care just counting t. But here we zap tail calls precisely for
+ (t `tickishScopesLike` SoftScope)
+To me it looks as if we should zap with precisely the negation!
-}
occAnal env (Tick tickish body)
@@ -2499,7 +2513,7 @@ occAnal env (Tick tickish body)
-- If we drop a tick due to the issues described below it's
-- not the end of the world.
- | tickish `tickishScopesLike` SoftScope
+ | tickish `tickishScopesLike` SoftScope -- Worry: see Note [Simplifying ticks]
= WUD (markAllNonTail usage) (Tick tickish body')
| Breakpoint _ _ ids _ <- tickish
@@ -3827,7 +3841,8 @@ tagRecBinders lvl body_uds details_s
, AlwaysTailCalled arity <- lookupTailCallInfo unadj_uds bndr
= JoinPoint arity
| otherwise
- = assert (not will_be_joins) -- Should be AlwaysTailCalled if
+ = warnPprTrace (will_be_joins) "tagRecBinders" (ppr bndr $$ ppr bndrs) $
+ -- Should be AlwaysTailCalled if
NotJoinPoint -- we are making join points!
-- 2. Adjust usage details of each RHS, taking into account the
=====================================
compiler/GHC/Tc/Solver/Equality.hs
=====================================
@@ -49,7 +49,6 @@ import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Utils.Misc
import GHC.Utils.Monad
-import GHC.Utils.Constants( debugIsOn )
import GHC.Data.Pair
import GHC.Data.Bag
@@ -843,13 +842,6 @@ canTyConApp ev eq_rel both_generative (ty1,tc1,tys1) (ty2,tc2,tys2)
then canEqHardFailure ev ty1 ty2
else canEqSoftFailure ev eq_rel ty1 ty2
where
- -- Reconstruct the types for error messages. This would do
- -- the wrong thing (from a pretty printing point of view)
- -- for functions, because we've lost the FunTyFlag; but
- -- in fact we never call canTyConApp on a saturated FunTyCon
- ty1 = mkTyConApp tc1 tys1
- ty2 = mkTyConApp tc2 tys2
-
-- See Note [Decomposing TyConApp equalities]
-- and Note [Decomposing newtype equalities]
can_decompose inerts
=====================================
compiler/GHC/Types/Tickish.hs
=====================================
@@ -106,9 +106,11 @@ data GenTickish pass =
-- the user.
ProfNote {
profNoteCC :: CostCentre, -- ^ the cost centre
+
profNoteCount :: !Bool, -- ^ bump the entry count?
profNoteScope :: !Bool -- ^ scopes over the enclosed expression
-- (i.e. not just a tick)
+ -- Invariant: the False/False case never happens
}
-- | A "tick" used by HPC to track the execution of each
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/735951ddd7b86a8c5979ffea394797d49314c0fc...d5d5246735d309504863bfc1066b40e2beda2a62
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/735951ddd7b86a8c5979ffea394797d49314c0fc...d5d5246735d309504863bfc1066b40e2beda2a62
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/20231010/cfab0a5c/attachment-0001.html>
More information about the ghc-commits
mailing list