Simon Peyton Jones pushed to branch wip/andreask/spec_tyfams at Glasgow Haskell Compiler / GHC

Commits:

2 changed files:

Changes:

  • compiler/GHC/Core/Opt/Specialise.hs
    ... ... @@ -65,7 +65,6 @@ import GHC.Unit.Module.ModGuts
    65 65
     import GHC.Core.Unfold
    
    66 66
     
    
    67 67
     import Data.List( partition )
    
    68
    -import Data.List.NonEmpty ( NonEmpty (..) )
    
    69 68
     import GHC.Core.Subst (substTickish)
    
    70 69
     import GHC.Core.TyCon (tyConClass_maybe)
    
    71 70
     import GHC.Core.DataCon (dataConTyCon)
    
    ... ... @@ -1280,6 +1279,36 @@ specCase :: SpecEnv
    1280 1279
                       , OutId
    
    1281 1280
                       , [OutAlt]
    
    1282 1281
                       , UsageDetails)
    
    1282
    +{-
    
    1283
    +------------------
    
    1284
    +SLPJ: I am commenting out this entire special case.
    
    1285
    +Reading Note [Floating dictionaries out of cases] carefully, I just don't get it.
    
    1286
    +* We never explicitly pattern-match on a dictionary; rather the class-op rules
    
    1287
    +  select superclasses from it.
    
    1288
    +* Calling `interestingDict` on every scrutinee is hardly sensible;
    
    1289
    +  generally `interestingDict` is called only on Constraint-kinded things.
    
    1290
    +* It was giving a Lint scope error in !14272
    
    1291
    +
    
    1292
    +So I think this code does no good; it's a waste of time and complexity.
    
    1293
    +
    
    1294
    +The commit that introduced it is back in 2010:
    
    1295
    +
    
    1296
    +   commit c107a00ccf1e641a2d008939cf477c71caa028d5
    
    1297
    +   Author: Simon Peyton Jones <simonpj@microsoft.com>
    
    1298
    +   Date:   Thu Aug 12 13:11:33 2010 +0000
    
    1299
    +
    
    1300
    +       Improve the Specialiser, fixing Trac #4203
    
    1301
    +
    
    1302
    +       Simply fixing #4203 is a tiny fix: in case alterantives we should
    
    1303
    +       do dumpUDs *including* the case binder.
    
    1304
    +
    
    1305
    +       But I realised that we can do better and wasted far too much time
    
    1306
    +       implementing the idea.  It's described in
    
    1307
    +           Note [Floating dictionaries out of cases]
    
    1308
    +
    
    1309
    +There is no compelling motivation and no test case
    
    1310
    +----------------------
    
    1311
    +
    
    1283 1312
     specCase env scrut' case_bndr [Alt con args rhs]
    
    1284 1313
       | -- See Note [Floating dictionaries out of cases]
    
    1285 1314
         -- interestingDict scrut' (idType case_bndr)
    
    ... ... @@ -1340,7 +1369,7 @@ specCase env scrut' case_bndr [Alt con args rhs]
    1340 1369
                           && tyCoVarsOfType var_ty `disjointVarSet` arg_set
    
    1341 1370
            where
    
    1342 1371
              var_ty = idType var
    
    1343
    -
    
    1372
    +-}
    
    1344 1373
     
    
    1345 1374
     specCase env scrut case_bndr alts
    
    1346 1375
       = 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 })
    397 397
         does_not_mention_ip_for :: Type -> DictCt -> Bool
    
    398 398
         does_not_mention_ip_for str_ty (DictCt { di_cls = cls, di_tys = tys })
    
    399 399
           = not $ mightMentionIP (not . typesAreApart str_ty) (const True) cls tys
    
    400
    -        -- See Note [Using typesAreApart when calling mightMmentionIP]
    
    400
    +        -- See Note [Using typesAreApart when calling mightMentionIP]
    
    401 401
             -- in GHC.Core.Predicate
    
    402 402
     
    
    403 403
     updInertIrreds :: IrredCt -> TcS ()
    
    ... ... @@ -586,7 +586,7 @@ Note [Using isCallStackTy in mightMentionIP]
    586 586
     To implement Note [Don't add HasCallStack constraints to the solved set],
    
    587 587
     we need to check whether a constraint contains a HasCallStack or HasExceptionContext
    
    588 588
     constraint. We do this using the 'mentionsIP' function, but as per
    
    589
    -Note [Using typesAreApart when calling mightMentions] we don't want to simply do:
    
    589
    +Note [Using typesAreApart when calling mightMentionIP] we don't want to simply do:
    
    590 590
     
    
    591 591
       mightMentionIP
    
    592 592
         (const True) -- (ignore the implicit parameter string)