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

Commits:

3 changed files:

Changes:

  • compiler/GHC/Core/Opt/Simplify/Inline.hs
    ... ... @@ -390,7 +390,7 @@ tryUnfolding env logger id lone_variable arg_infos
    390 390
                -- be *something* interesting about some argument, or the
    
    391 391
                -- result context, to make it worth inlining
    
    392 392
         calc_some_benefit :: Arity -> Bool -> Bool   -- The Arity is the number of args
    
    393
    -                                         -- expected by the unfolding
    
    393
    +                                                 -- expected by the unfolding
    
    394 394
         calc_some_benefit uf_arity is_inline
    
    395 395
            | not saturated = interesting_args       -- Under-saturated
    
    396 396
                                             -- Note [Unsaturated applications]
    

  • compiler/GHC/Core/Opt/Simplify/Utils.hs
    ... ... @@ -910,7 +910,7 @@ interestingCallContext env cont
    910 910
             -- in GHC.Core.Unfold
    
    911 911
     
    
    912 912
         interesting (StrictArg { sc_fun = fun }) = strictArgContext fun
    
    913
    -    interesting (StrictBind {})              = BoringCtxt
    
    913
    +    interesting (StrictBind {})              = RhsCtxt NonRecursive
    
    914 914
         interesting (Stop _ cci _)               = cci
    
    915 915
         interesting (TickIt _ k)                 = interesting k
    
    916 916
         interesting (ApplyToTy { sc_cont = k })  = interesting k
    
    ... ... @@ -1032,7 +1032,7 @@ interestingArg env e = go env 0 e
    1032 1032
            | n > 0         = NonTrivArg -- Saturated or unknown call
    
    1033 1033
            | otherwise  -- n==0, no value arguments; look for an interesting unfolding
    
    1034 1034
            = case idUnfolding v of
    
    1035
    -           OtherCon [] -> TrivArg      -- It's evaluated, but that's all we know
    
    1035
    +--           OtherCon [] -> NonTrivArg   -- It's evaluated, but that's all we know
    
    1036 1036
                OtherCon _  -> NonTrivArg   -- Evaluated and we know it isn't these constructors
    
    1037 1037
                   -- See Note [OtherCon and interestingArg]
    
    1038 1038
                DFunUnfolding {} -> ValueArg   -- We konw that idArity=0
    

  • compiler/GHC/Core/Reduction.hs
    ... ... @@ -94,7 +94,7 @@ but in fact `reductionOriginalType` is very seldom used, so it's not worth it.
    94 94
     -- See Note [The Reduction type].
    
    95 95
     data Reduction =
    
    96 96
       Reduction
    
    97
    -    { reductionCoercion    :: !Coercion
    
    97
    +    { reductionCoercion    :: Coercion
    
    98 98
         , reductionReducedType :: !Type
    
    99 99
         }
    
    100 100
     -- N.B. the 'Coercion' field must be lazy: see for instance GHC.Tc.Solver.Rewrite.rewrite_tyvar2