@@ -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.
7071simplifyExpr 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
9697simplExprGently :: 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.
114109simplExprGently env expr = do
115110 expr1 <- simplExpr env (occurAnalyseExpr expr)
116111 simplExpr env (occurAnalyseExpr expr1)
0 commit comments