Skip to content

Commit 9d626be

Browse files
sheafMarge Bot
authored andcommitted
Simplifier/rules: fix mistakes in Notes & comments
1 parent 138a6e3 commit 9d626be

File tree

3 files changed

+16
-21
lines changed

3 files changed

+16
-21
lines changed

compiler/GHC/Core/Opt/Simplify.hs

Lines changed: 12 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -65,8 +65,9 @@ simplifyExpr :: Logger
6565
-> SimplifyExprOpts
6666
-> CoreExpr
6767
-> 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.
7071
simplifyExpr logger euc opts expr
7172
= withTiming logger (text "Simplify [expr]") (const ()) $
7273
do { eps <- eucEPS euc ;
@@ -94,23 +95,17 @@ simplifyExpr logger euc opts expr
9495
}
9596

9697
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').
104105
--
105106
-- 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.
113-
107+
-- and in fact that is so.... but the 'Gently' in 'simplExprGently' doesn't
108+
-- enforce that; it just simplifies the expression twice.
114109
simplExprGently env expr = do
115110
expr1 <- simplExpr env (occurAnalyseExpr expr)
116111
simplExpr env (occurAnalyseExpr expr1)

compiler/GHC/Core/Opt/SpecConstr.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -2324,9 +2324,9 @@ Wrinkles:
23242324
e |> Refl
23252325
or
23262326
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
23302330
end up with a rule LHS that doesn't bind the template variables
23312331
(#10602).
23322332

compiler/GHC/Core/Rules.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -850,7 +850,7 @@ bound on the LHS:
850850
RULE forall (c :: a~b). f (x |> c) = e
851851
Now, if that binding is inlined, so that a=b=Int, we'd get
852852
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),
854854
optCoercion (look at the CoVarCo case) will turn that 'c' into Refl:
855855
RULE forall (c :: Int~Int). f (x |> <Int>) = e
856856
and then perhaps drop it altogether. Now 'c' is unbound.

0 commit comments

Comments
 (0)