
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 138a6e34 by sheaf at 2025-09-04T19:22:46-04:00 Make mkCast assertion a bit clearer This commit changes the assertion message that gets printed when one calls mkCast with a coercion whose kind does not match the type of the inner expression. I always found the assertion message a bit confusing, as it didn't clearly state what exactly was the error. - - - - - 9d626be1 by sheaf at 2025-09-04T19:22:46-04:00 Simplifier/rules: fix mistakes in Notes & comments - - - - - 4 changed files: - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/Utils.hs Changes: ===================================== compiler/GHC/Core/Opt/Simplify.hs ===================================== @@ -65,8 +65,9 @@ simplifyExpr :: Logger -> SimplifyExprOpts -> CoreExpr -> IO CoreExpr --- simplifyExpr is called by the driver to simplify an --- expression typed in at the interactive prompt +-- ^ Simplify an expression using 'simplExprGently'. +-- +-- See 'simplExprGently' for details. simplifyExpr logger euc opts expr = withTiming logger (text "Simplify [expr]") (const ()) $ do { eps <- eucEPS euc ; @@ -94,23 +95,17 @@ simplifyExpr logger euc opts expr } simplExprGently :: SimplEnv -> CoreExpr -> SimplM CoreExpr --- Simplifies an expression --- does occurrence analysis, then simplification --- and repeats (twice currently) because one pass --- alone leaves tons of crud. --- Used (a) for user expressions typed in at the interactive prompt --- (b) the LHS and RHS of a RULE --- (c) Template Haskell splices +-- ^ Simplifies an expression by doing occurrence analysis, then simplification, +-- and repeating (twice currently), because one pass alone leaves tons of crud. +-- +-- Used only: +-- +-- 1. for user expressions typed in at the interactive prompt (see 'GHC.Driver.Main.hscStmt'), +-- 2. for Template Haskell splices (see 'GHC.Tc.Gen.Splice.runMeta'). -- -- The name 'Gently' suggests that the SimplMode is InitialPhase, --- and in fact that is so.... but the 'Gently' in simplExprGently doesn't --- enforce that; it just simplifies the expression twice - --- It's important that simplExprGently does eta reduction; see --- Note [Simplify rule LHS] above. The --- simplifier does indeed do eta reduction (it's in GHC.Core.Opt.Simplify.completeLam) --- but only if -O is on. - +-- and in fact that is so.... but the 'Gently' in 'simplExprGently' doesn't +-- enforce that; it just simplifies the expression twice. simplExprGently env expr = do expr1 <- simplExpr env (occurAnalyseExpr expr) simplExpr env (occurAnalyseExpr expr1) ===================================== compiler/GHC/Core/Opt/SpecConstr.hs ===================================== @@ -2324,9 +2324,9 @@ Wrinkles: e |> Refl or e |> g1 |> g2 - because both of these will be optimised by Simplify.simplRule. In the - former case such optimisation benign, because the rule will match more - terms; but in the latter we may lose a binding of 'g1' or 'g2', and + because both of these will be optimised by GHC.Core.Opt.Simplify.Iteration.simplRules. + In the former case such optimisation is benign, because the rule will match + more terms; but in the latter we may lose a binding of 'g1' or 'g2', and end up with a rule LHS that doesn't bind the template variables (#10602). ===================================== compiler/GHC/Core/Rules.hs ===================================== @@ -850,7 +850,7 @@ bound on the LHS: RULE forall (c :: a~b). f (x |> c) = e Now, if that binding is inlined, so that a=b=Int, we'd get RULE forall (c :: Int~Int). f (x |> c) = e - and now when we simplify the LHS (Simplify.simplRule) we + and now when we simplify the LHS (GHC.Core.Opt.Simplify.Iteration.simplRules), optCoercion (look at the CoVarCo case) will turn that 'c' into Refl: RULE forall (c :: Int~Int). f (x |> <Int>) = e and then perhaps drop it altogether. Now 'c' is unbound. ===================================== compiler/GHC/Core/Utils.hs ===================================== @@ -275,11 +275,13 @@ mkCast expr co = assertPpr (coercionRole co == Representational) (text "coercion" <+> ppr co <+> text "passed to mkCast" <+> ppr expr <+> text "has wrong role" <+> ppr (coercionRole co)) $ - warnPprTrace (not (coercionLKind co `eqType` exprType expr)) - "Trying to coerce" (text "(" <> ppr expr - $$ text "::" <+> ppr (exprType expr) <> text ")" - $$ ppr co $$ ppr (coercionType co) - $$ callStackDoc) $ + warnPprTrace (not (coercionLKind co `eqType` exprType expr)) "Bad cast" + (vcat [ text "Coercion LHS kind does not match enclosed expression type" + , text "co:" <+> ppr co + , text "coercionLKind:" <+> ppr (coercionLKind co) + , text "exprType:" <+> ppr (exprType expr) + , text "expr:" <+> ppr expr + , callStackDoc ]) $ case expr of Cast expr co2 -> mkCast expr (mkTransCo co2 co) Tick t expr -> Tick t (mkCast expr co) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/46bb9a7985557818ee2a031f6a0fdef... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/46bb9a7985557818ee2a031f6a0fdef... You're receiving this email because of your account on gitlab.haskell.org.