Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC

Commits:

4 changed files:

Changes:

  • compiler/GHC/Core/Opt/Simplify.hs
    ... ... @@ -65,8 +65,9 @@ simplifyExpr :: Logger
    65 65
                  -> SimplifyExprOpts
    
    66 66
                  -> CoreExpr
    
    67 67
                  -> IO CoreExpr
    
    68
    --- simplifyExpr is called by the driver to simplify an
    
    69
    --- expression typed in at the interactive prompt
    
    68
    +-- ^ Simplify an expression using 'simplExprGently'.
    
    69
    +--
    
    70
    +-- See 'simplExprGently' for details.
    
    70 71
     simplifyExpr logger euc opts expr
    
    71 72
       = withTiming logger (text "Simplify [expr]") (const ()) $
    
    72 73
         do  { eps <- eucEPS euc ;
    
    ... ... @@ -94,23 +95,17 @@ simplifyExpr logger euc opts expr
    94 95
             }
    
    95 96
     
    
    96 97
     simplExprGently :: SimplEnv -> CoreExpr -> SimplM CoreExpr
    
    97
    --- Simplifies an expression
    
    98
    ---      does occurrence analysis, then simplification
    
    99
    ---      and repeats (twice currently) because one pass
    
    100
    ---      alone leaves tons of crud.
    
    101
    --- Used (a) for user expressions typed in at the interactive prompt
    
    102
    ---      (b) the LHS and RHS of a RULE
    
    103
    ---      (c) Template Haskell splices
    
    98
    +-- ^ Simplifies an expression by doing occurrence analysis, then simplification,
    
    99
    +-- and repeating (twice currently), because one pass alone leaves tons of crud.
    
    100
    +--
    
    101
    +-- Used only:
    
    102
    +--
    
    103
    +--   1. for user expressions typed in at the interactive prompt (see 'GHC.Driver.Main.hscStmt'),
    
    104
    +--   2. for Template Haskell splices (see 'GHC.Tc.Gen.Splice.runMeta').
    
    104 105
     --
    
    105 106
     -- The name 'Gently' suggests that the SimplMode is InitialPhase,
    
    106
    --- and in fact that is so.... but the 'Gently' in simplExprGently doesn't
    
    107
    --- enforce that; it just simplifies the expression twice
    
    108
    -
    
    109
    --- It's important that simplExprGently does eta reduction; see
    
    110
    --- Note [Simplify rule LHS] above.  The
    
    111
    --- simplifier does indeed do eta reduction (it's in GHC.Core.Opt.Simplify.completeLam)
    
    112
    --- but only if -O is on.
    
    107
    +-- and in fact that is so.... but the 'Gently' in 'simplExprGently' doesn't
    
    108
    +-- enforce that; it just simplifies the expression twice.
    
    113 109
     simplExprGently env expr = do
    
    114 110
         expr1 <- simplExpr env (occurAnalyseExpr expr)
    
    115 111
         simplExpr env (occurAnalyseExpr expr1)
    

  • compiler/GHC/Core/Opt/SpecConstr.hs
    ... ... @@ -2324,9 +2324,9 @@ Wrinkles:
    2324 2324
          e |> Refl
    
    2325 2325
       or
    
    2326 2326
         e |> g1 |> g2
    
    2327
    -  because both of these will be optimised by Simplify.simplRule. In the
    
    2328
    -  former case such optimisation benign, because the rule will match more
    
    2329
    -  terms; but in the latter we may lose a binding of 'g1' or 'g2', and
    
    2327
    +  because both of these will be optimised by GHC.Core.Opt.Simplify.Iteration.simplRules.
    
    2328
    +  In the former case such optimisation is benign, because the rule will match
    
    2329
    +  more terms; but in the latter we may lose a binding of 'g1' or 'g2', and
    
    2330 2330
       end up with a rule LHS that doesn't bind the template variables
    
    2331 2331
       (#10602).
    
    2332 2332
     
    

  • compiler/GHC/Core/Rules.hs
    ... ... @@ -850,7 +850,7 @@ bound on the LHS:
    850 850
         RULE forall (c :: a~b). f (x |> c) = e
    
    851 851
       Now, if that binding is inlined, so that a=b=Int, we'd get
    
    852 852
         RULE forall (c :: Int~Int). f (x |> c) = e
    
    853
    -  and now when we simplify the LHS (Simplify.simplRule) we
    
    853
    +  and now when we simplify the LHS (GHC.Core.Opt.Simplify.Iteration.simplRules),
    
    854 854
       optCoercion (look at the CoVarCo case) will turn that 'c' into Refl:
    
    855 855
         RULE forall (c :: Int~Int). f (x |> <Int>) = e
    
    856 856
       and then perhaps drop it altogether.  Now 'c' is unbound.
    

  • compiler/GHC/Core/Utils.hs
    ... ... @@ -275,11 +275,13 @@ mkCast expr co
    275 275
       = assertPpr (coercionRole co == Representational)
    
    276 276
                   (text "coercion" <+> ppr co <+> text "passed to mkCast"
    
    277 277
                    <+> ppr expr <+> text "has wrong role" <+> ppr (coercionRole co)) $
    
    278
    -    warnPprTrace (not (coercionLKind co `eqType` exprType expr))
    
    279
    -          "Trying to coerce" (text "(" <> ppr expr
    
    280
    -          $$ text "::" <+> ppr (exprType expr) <> text ")"
    
    281
    -          $$ ppr co $$ ppr (coercionType co)
    
    282
    -          $$ callStackDoc) $
    
    278
    +    warnPprTrace (not (coercionLKind co `eqType` exprType expr)) "Bad cast"
    
    279
    +      (vcat [ text "Coercion LHS kind does not match enclosed expression type"
    
    280
    +            , text "co:" <+> ppr co
    
    281
    +            , text "coercionLKind:" <+> ppr (coercionLKind co)
    
    282
    +            , text "exprType:" <+> ppr (exprType expr)
    
    283
    +            , text "expr:" <+> ppr expr
    
    284
    +            , callStackDoc ]) $
    
    283 285
         case expr of
    
    284 286
           Cast expr co2 -> mkCast expr (mkTransCo co2 co)
    
    285 287
           Tick t expr   -> Tick t (mkCast expr co)