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

Commits:

2 changed files:

Changes:

  • compiler/GHC/Core/Opt/DmdAnal.hs
    ... ... @@ -23,7 +23,7 @@ import GHC.Core.DataCon
    23 23
     import GHC.Core.Utils
    
    24 24
     import GHC.Core.TyCon
    
    25 25
     import GHC.Core.Type
    
    26
    -import GHC.Core.Predicate( isEqualityClass, isCTupleClass )
    
    26
    +import GHC.Core.Predicate( isEqualityClass {- , isCTupleClass -} )
    
    27 27
     import GHC.Core.FVs      ( rulesRhsFreeIds, bndrRuleAndUnfoldingIds )
    
    28 28
     import GHC.Core.Coercion ( Coercion )
    
    29 29
     import GHC.Core.TyCo.FVs     ( coVarsOfCos )
    
    ... ... @@ -2194,8 +2194,10 @@ doNotUnbox :: Type -> Bool
    2194 2194
     doNotUnbox arg_ty
    
    2195 2195
       = case tyConAppTyCon_maybe arg_ty of
    
    2196 2196
           Just tc | Just cls <- tyConClass_maybe tc
    
    2197
    -              -> not (isEqualityClass cls || isCTupleClass cls)
    
    2197
    +              -> not (isEqualityClass cls {- || isCTupleClass cls -})
    
    2198 2198
            -- See (DNB2) and (DNB1) in Note [Do not unbox class dictionaries]
    
    2199
    +       --
    
    2200
    +       --   *** TODO *** document the removal of isCTupleClass!
    
    2199 2201
     
    
    2200 2202
           _ -> False
    
    2201 2203
     
    
    ... ... @@ -2243,7 +2245,7 @@ Wrinkle (DNB1): we /do/ want to unbox tuple dictionaries (#23398)
    2243 2245
          f = /\a. \d:(% Eq a, Show a %). ... f @a (% sel1 d, sel2 d %)...
    
    2244 2246
       where there is a recurive call to `f`, or to another function that takes the
    
    2245 2247
       same tuple dictionary, but where the tuple is built from the components of
    
    2246
    -  `d`.  The Simplier does not fix this.  But if we unpacked the dictionary
    
    2248
    +  `d`.  The Simplifier does not fix this.  But if we unpacked the dictionary
    
    2247 2249
       we'd get
    
    2248 2250
          $wf = /\a. \(d1:Eq a) (d2:Show a). let d = (% d1, d2 %)
    
    2249 2251
                  in ...f @a (% sel1 d, sel2 d %)
    

  • compiler/GHC/Core/Opt/Specialise.hs
    ... ... @@ -1283,6 +1283,7 @@ specCase :: SpecEnv
    1283 1283
                       , OutId
    
    1284 1284
                       , [OutAlt]
    
    1285 1285
                       , UsageDetails)
    
    1286
    +{-
    
    1286 1287
     specCase env scrut' case_bndr [Alt con args rhs]
    
    1287 1288
       | -- See Note [Floating dictionaries out of cases]
    
    1288 1289
         isDictTy (idType case_bndr)
    
    ... ... @@ -1343,6 +1344,7 @@ specCase env scrut' case_bndr [Alt con args rhs]
    1343 1344
                           && tyCoVarsOfType var_ty `disjointVarSet` arg_set
    
    1344 1345
            where
    
    1345 1346
              var_ty = idType var
    
    1347
    +-}
    
    1346 1348
     
    
    1347 1349
     specCase env scrut case_bndr alts
    
    1348 1350
       = do { (alts', uds_alts) <- mapAndCombineSM spec_alt alts