[commit: ghc] wip/tdammers/D4395-new: Fix huge performance regression (5d1a707)
git at git.haskell.org
git at git.haskell.org
Mon Mar 26 11:47:00 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/tdammers/D4395-new
Link : http://ghc.haskell.org/trac/ghc/changeset/5d1a707c6c78dedc915604aec702d07c4bc741c5/ghc
>---------------------------------------------------------------
commit 5d1a707c6c78dedc915604aec702d07c4bc741c5
Author: Tobias Dammers <tdammers at gmail.com>
Date: Mon Mar 26 13:44:56 2018 +0200
Fix huge performance regression
Previous version caused a 10x increase in execution time for the
infamous Grammar.hs test case from #14683; this patch gets us back on
par.
>---------------------------------------------------------------
5d1a707c6c78dedc915604aec702d07c4bc741c5
compiler/simplCore/Simplify.hs | 102 +++++++++++++++++++----------------------
1 file changed, 46 insertions(+), 56 deletions(-)
diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs
index b2444e5..5e5d836 100644
--- a/compiler/simplCore/Simplify.hs
+++ b/compiler/simplCore/Simplify.hs
@@ -1215,62 +1215,52 @@ simplCast env body co0 cont0
where
-- If the first parameter is Nothing, then simplifying revealed a
-- reflexive coercion. Omit.
- addCoerce0 :: Maybe OutCoercion -> SimplCont -> SimplM SimplCont
- addCoerce0 Nothing cont = return cont
- addCoerce0 (Just co) cont = addCoerce co cont
-
- addCoerce :: OutCoercion -> SimplCont -> SimplM SimplCont
- addCoerce co cont -- just skip reflexive casts
- | isReflexiveCo co = {-#SCC "addCoerce-reflexive" #-}
- return cont
- -- It's worth checking isReflexiveCo.
- -- For example, in the initial form of a worker
- -- we may find (coerce T (coerce S (\x.e))) y
- -- and we'd like it to simplify to e[y/x] in one round
- -- of simplification
-
- addCoerce co1 (CastIt co2 cont)
- = addCoerce (mkTransCo co1 co2) cont
-
- addCoerce co cont@(ApplyToTy { sc_arg_ty = arg_ty, sc_cont = tail })
- | Just (arg_ty', m_co') <- pushCoTyArg co arg_ty
- = case m_co' of
- Just co' -> do { tail' <- addCoerce co' tail
- ; return (cont { sc_arg_ty = arg_ty', sc_cont = tail' }) }
- Nothing -> return cont
-
- addCoerce co cont@(ApplyToVal { sc_arg = arg, sc_env = arg_se
- , sc_dup = dup, sc_cont = tail })
- | Just (co1, m_co2) <- pushCoValArg co
- , Pair _ new_ty <- coercionKind co1
- , not (isTypeLevPoly new_ty) -- without this check, we get a lev-poly arg
- -- See Note [Levity polymorphism invariants] in CoreSyn
- -- test: typecheck/should_run/EtaExpandLevPoly
- = do { tail' <- addCoerce0 m_co2 tail
- ; if isReflCo co1
- then return (cont { sc_cont = tail' })
- -- Avoid simplifying if possible;
- -- See Note [Avoiding exponential behaviour]
- else do
- { (dup', arg_se', arg') <- simplArg env dup arg_se arg
- -- When we build the ApplyTo we can't mix the OutCoercion
- -- 'co' with the InExpr 'arg', so we simplify
- -- to make it all consistent. It's a bit messy.
- -- But it isn't a common case.
- -- Example of use: Trac #995
- ; return (ApplyToVal { sc_arg = mkCast arg' co1
- , sc_env = arg_se'
- , sc_dup = dup'
- , sc_cont = tail' }) } }
-
- addCoerce co cont
- | isReflexiveCo co = return cont
- | otherwise = return (CastIt co cont)
- -- It's worth checking isReflexiveCo.
- -- For example, in the initial form of a worker
- -- we may find (coerce T (coerce S (\x.e))) y
- -- and we'd like it to simplify to e[y/x] in one round
- -- of simplification
+ addCoerce0 :: Maybe OutCoercion -> SimplCont -> SimplM SimplCont
+ addCoerce0 Nothing cont = return cont
+ addCoerce0 (Just co) cont = addCoerce co cont
+
+ addCoerce :: OutCoercion -> SimplCont -> SimplM SimplCont
+
+ addCoerce co1 (CastIt co2 cont)
+ = addCoerce (mkTransCo co1 co2) cont
+
+ addCoerce co cont@(ApplyToTy { sc_arg_ty = arg_ty, sc_cont = tail })
+ | Just (arg_ty', m_co') <- pushCoTyArg co arg_ty
+ = do { tail' <- addCoerce0 m_co' tail
+ ; return (cont { sc_arg_ty = arg_ty', sc_cont = tail' }) }
+
+ addCoerce co cont@(ApplyToVal { sc_arg = arg, sc_env = arg_se
+ , sc_dup = dup, sc_cont = tail })
+ | Just (co1, m_co2) <- pushCoValArg co
+ , Pair _ new_ty <- coercionKind co1
+ , not (isTypeLevPoly new_ty) -- without this check, we get a lev-poly arg
+ -- See Note [Levity polymorphism invariants] in CoreSyn
+ -- test: typecheck/should_run/EtaExpandLevPoly
+ = do { tail' <- addCoerce0 m_co2 tail
+ ; if isReflCo co1
+ then return (cont { sc_cont = tail' })
+ -- Avoid simplifying if possible;
+ -- See Note [Avoiding exponential behaviour]
+ else do
+ { (dup', arg_se', arg') <- simplArg env dup arg_se arg
+ -- When we build the ApplyTo we can't mix the OutCoercion
+ -- 'co' with the InExpr 'arg', so we simplify
+ -- to make it all consistent. It's a bit messy.
+ -- But it isn't a common case.
+ -- Example of use: Trac #995
+ ; return (ApplyToVal { sc_arg = mkCast arg' co1
+ , sc_env = arg_se'
+ , sc_dup = dup'
+ , sc_cont = tail' }) } }
+
+ addCoerce co cont
+ | isReflexiveCo co = return cont
+ | otherwise = return (CastIt co cont)
+ -- It's worth checking isReflexiveCo.
+ -- For example, in the initial form of a worker
+ -- we may find (coerce T (coerce S (\x.e))) y
+ -- and we'd like it to simplify to e[y/x] in one round
+ -- of simplification
simplArg :: SimplEnv -> DupFlag -> StaticEnv -> CoreExpr
-> SimplM (DupFlag, StaticEnv, OutExpr)
More information about the ghc-commits
mailing list