[commit: ghc] master: Clarify comments and liberalise stack-check optimisation slightly (41212fd)
git at git.haskell.org
git at git.haskell.org
Fri Oct 18 13:35:37 UTC 2013
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/41212fd652b59d949a993225e90cb202f2a33087/ghc
>---------------------------------------------------------------
commit 41212fd652b59d949a993225e90cb202f2a33087
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Fri Oct 18 14:35:07 2013 +0100
Clarify comments and liberalise stack-check optimisation slightly
The only substantive change here is to change "==" into ">=" in
the Note [Always false stack check] code. This is semantically
correct, but won't have any practical impact.
>---------------------------------------------------------------
41212fd652b59d949a993225e90cb202f2a33087
compiler/cmm/CmmLayoutStack.hs | 19 ++++++++++---------
compiler/cmm/CmmNode.hs | 6 +++++-
2 files changed, 15 insertions(+), 10 deletions(-)
diff --git a/compiler/cmm/CmmLayoutStack.hs b/compiler/cmm/CmmLayoutStack.hs
index 2efb806..23da5d0 100644
--- a/compiler/cmm/CmmLayoutStack.hs
+++ b/compiler/cmm/CmmLayoutStack.hs
@@ -775,23 +775,24 @@ areaToSp dflags sp_old _sp_hwm area_off (CmmStackSlot area n) =
areaToSp dflags _ sp_hwm _ (CmmLit CmmHighStackMark) = mkIntExpr dflags sp_hwm
areaToSp dflags _ _ _ (CmmMachOp (MO_U_Lt _) -- Note [Always false stack check]
[CmmMachOp (MO_Sub _)
- [ CmmRegOff (CmmGlobal Sp) off
- , CmmLit (CmmInt lit _)],
+ [ CmmRegOff (CmmGlobal Sp) x_off
+ , CmmLit (CmmInt y_lit _)],
CmmReg (CmmGlobal SpLim)])
- | fromIntegral off == lit = zeroExpr dflags
+ | fromIntegral x_off >= y_lit = zeroExpr dflags
areaToSp _ _ _ _ other = other
-- Note [Always false stack check]
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
---
-- We can optimise stack checks of the form
--
--- if ((Sp + x) - x < SpLim) then .. else ..
+-- if ((Sp + x) - y < SpLim) then .. else ..
--
--- where x is an integer offset. Optimising this away depends on knowing that
--- SpLim <= Sp, so it is really the job of the stack layout algorithm, hence we
--- do it now. This is also convenient because sinking pass will later drop the
--- dead code.
+-- where are non-negative integer byte offsets. Since we know that
+-- SpLim <= Sp (remember the stack grows downwards), this test must
+-- yield False if (x >= y), so we can rewrite the comparison to False.
+-- A subsequent sinking pass will later drop the dead code.
+-- Optimising this away depends on knowing that SpLim <= Sp, so it is
+-- really the job of the stack layout algorithm, hence we do it now.
optStackCheck :: CmmNode O C -> CmmNode O C
optStackCheck n = -- Note [null stack check]
diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs
index 7a4fb98..5c520d3 100644
--- a/compiler/cmm/CmmNode.hs
+++ b/compiler/cmm/CmmNode.hs
@@ -421,8 +421,10 @@ mapForeignTarget :: (CmmExpr -> CmmExpr) -> ForeignTarget -> ForeignTarget
mapForeignTarget exp (ForeignTarget e c) = ForeignTarget (exp e) c
mapForeignTarget _ m@(PrimTarget _) = m
--- Take a transformer on expressions and apply it recursively.
wrapRecExp :: (CmmExpr -> CmmExpr) -> CmmExpr -> CmmExpr
+-- Take a transformer on expressions and apply it recursively.
+-- (wrapRecExp f e) first recursively applies itself to sub-expressions of e
+-- then uses f to rewrite the resulting expression
wrapRecExp f (CmmMachOp op es) = f (CmmMachOp op $ map (wrapRecExp f) es)
wrapRecExp f (CmmLoad addr ty) = f (CmmLoad (wrapRecExp f addr) ty)
wrapRecExp f e = f e
@@ -450,6 +452,8 @@ mapForeignTargetM f (ForeignTarget e c) = (\x -> ForeignTarget x c) `fmap` f e
mapForeignTargetM _ (PrimTarget _) = Nothing
wrapRecExpM :: (CmmExpr -> Maybe CmmExpr) -> (CmmExpr -> Maybe CmmExpr)
+-- (wrapRecExpM f e) first recursively applies itself to sub-expressions of e
+-- then gives f a chance to rewrite the resulting expression
wrapRecExpM f n@(CmmMachOp op es) = maybe (f n) (f . CmmMachOp op) (mapListM (wrapRecExpM f) es)
wrapRecExpM f n@(CmmLoad addr ty) = maybe (f n) (f . flip CmmLoad ty) (wrapRecExpM f addr)
wrapRecExpM f e = f e
More information about the ghc-commits
mailing list