Simon Peyton Jones pushed to branch wip/andreask/spec_tyfams at Glasgow Haskell Compiler / GHC
Commits:
a76cbf2d by Simon Peyton Jones at 2025-04-27T12:55:52+01:00
Typos
- - - - -
752ecf79 by Simon Peyton Jones at 2025-04-27T12:56:00+01:00
Remove a special case that appears to do nothing
See the commented-out block of `specCase`
- - - - -
2 changed files:
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Tc/Solver/Monad.hs
Changes:
=====================================
compiler/GHC/Core/Opt/Specialise.hs
=====================================
@@ -65,7 +65,6 @@ import GHC.Unit.Module.ModGuts
import GHC.Core.Unfold
import Data.List( partition )
-import Data.List.NonEmpty ( NonEmpty (..) )
import GHC.Core.Subst (substTickish)
import GHC.Core.TyCon (tyConClass_maybe)
import GHC.Core.DataCon (dataConTyCon)
@@ -1280,6 +1279,36 @@ specCase :: SpecEnv
, OutId
, [OutAlt]
, UsageDetails)
+{-
+------------------
+SLPJ: I am commenting out this entire special case.
+Reading Note [Floating dictionaries out of cases] carefully, I just don't get it.
+* We never explicitly pattern-match on a dictionary; rather the class-op rules
+ select superclasses from it.
+* Calling `interestingDict` on every scrutinee is hardly sensible;
+ generally `interestingDict` is called only on Constraint-kinded things.
+* It was giving a Lint scope error in !14272
+
+So I think this code does no good; it's a waste of time and complexity.
+
+The commit that introduced it is back in 2010:
+
+ commit c107a00ccf1e641a2d008939cf477c71caa028d5
+ Author: Simon Peyton Jones
+ Date: Thu Aug 12 13:11:33 2010 +0000
+
+ Improve the Specialiser, fixing Trac #4203
+
+ Simply fixing #4203 is a tiny fix: in case alterantives we should
+ do dumpUDs *including* the case binder.
+
+ But I realised that we can do better and wasted far too much time
+ implementing the idea. It's described in
+ Note [Floating dictionaries out of cases]
+
+There is no compelling motivation and no test case
+----------------------
+
specCase env scrut' case_bndr [Alt con args rhs]
| -- See Note [Floating dictionaries out of cases]
-- interestingDict scrut' (idType case_bndr)
@@ -1340,7 +1369,7 @@ specCase env scrut' case_bndr [Alt con args rhs]
&& tyCoVarsOfType var_ty `disjointVarSet` arg_set
where
var_ty = idType var
-
+-}
specCase env scrut case_bndr alts
= do { (alts', uds_alts) <- mapAndCombineSM spec_alt alts
=====================================
compiler/GHC/Tc/Solver/Monad.hs
=====================================
@@ -397,7 +397,7 @@ updInertDicts dict_ct@(DictCt { di_cls = cls, di_ev = ev, di_tys = tys })
does_not_mention_ip_for :: Type -> DictCt -> Bool
does_not_mention_ip_for str_ty (DictCt { di_cls = cls, di_tys = tys })
= not $ mightMentionIP (not . typesAreApart str_ty) (const True) cls tys
- -- See Note [Using typesAreApart when calling mightMmentionIP]
+ -- See Note [Using typesAreApart when calling mightMentionIP]
-- in GHC.Core.Predicate
updInertIrreds :: IrredCt -> TcS ()
@@ -586,7 +586,7 @@ Note [Using isCallStackTy in mightMentionIP]
To implement Note [Don't add HasCallStack constraints to the solved set],
we need to check whether a constraint contains a HasCallStack or HasExceptionContext
constraint. We do this using the 'mentionsIP' function, but as per
-Note [Using typesAreApart when calling mightMentions] we don't want to simply do:
+Note [Using typesAreApart when calling mightMentionIP] we don't want to simply do:
mightMentionIP
(const True) -- (ignore the implicit parameter string)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/279442edcad54e8b5b23240c0354c87...
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/279442edcad54e8b5b23240c0354c87...
You're receiving this email because of your account on gitlab.haskell.org.