[commit: ghc] master: More comments about stack layout (d4f7e01)

git at git.haskell.org git at git.haskell.org
Fri Oct 18 21:32:59 UTC 2013


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/d4f7e011481084e8e99ac3490e9e8bace5da1a84/ghc

>---------------------------------------------------------------

commit d4f7e011481084e8e99ac3490e9e8bace5da1a84
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Fri Oct 18 22:29:57 2013 +0100

    More comments about stack layout


>---------------------------------------------------------------

d4f7e011481084e8e99ac3490e9e8bace5da1a84
 compiler/cmm/CmmLayoutStack.hs |   21 ++++++++++++++++-----
 compiler/codeGen/StgCmmHeap.hs |   36 +++++++++++++++++++++++++++---------
 2 files changed, 43 insertions(+), 14 deletions(-)

diff --git a/compiler/cmm/CmmLayoutStack.hs b/compiler/cmm/CmmLayoutStack.hs
index 23da5d0..5b881d8 100644
--- a/compiler/cmm/CmmLayoutStack.hs
+++ b/compiler/cmm/CmmLayoutStack.hs
@@ -770,15 +770,26 @@ arguments.
 -}
 
 areaToSp :: DynFlags -> ByteOff -> ByteOff -> (Area -> StackLoc) -> CmmExpr -> CmmExpr
-areaToSp dflags sp_old _sp_hwm area_off (CmmStackSlot area n) =
-  cmmOffset dflags (CmmReg spReg) (sp_old - area_off area - n)
-areaToSp dflags _ sp_hwm _ (CmmLit CmmHighStackMark) = mkIntExpr dflags sp_hwm
-areaToSp dflags _ _ _ (CmmMachOp (MO_U_Lt _)  -- Note [Always false stack check]
+
+areaToSp dflags sp_old _sp_hwm area_off (CmmStackSlot area n)
+  = cmmOffset dflags (CmmReg spReg) (sp_old - area_off area - n)
+    -- Replace (CmmStackSlot area n) with an offset from Sp
+
+areaToSp dflags _ sp_hwm _ (CmmLit CmmHighStackMark) 
+  = mkIntExpr dflags sp_hwm
+    -- Replace CmmHighStackMark with the number of bytes of stack used, 
+    -- the sp_hwm.   See Note [Stack usage] in StgCmmHeap
+
+areaToSp dflags _ _ _ (CmmMachOp (MO_U_Lt _)  
                           [CmmMachOp (MO_Sub _)
                                   [ CmmRegOff (CmmGlobal Sp) x_off
                                   , CmmLit (CmmInt y_lit _)],
                            CmmReg (CmmGlobal SpLim)])
-                              | fromIntegral x_off >= y_lit = zeroExpr dflags
+  | fromIntegral x_off >= y_lit 
+  = zeroExpr dflags
+    -- Replace a stack-overflow test that cannot fail with a no-op
+    -- See Note [Always false stack check]
+
 areaToSp _ _ _ _ other = other
 
 -- Note [Always false stack check]
diff --git a/compiler/codeGen/StgCmmHeap.hs b/compiler/codeGen/StgCmmHeap.hs
index 7710b6f..55ddfd4 100644
--- a/compiler/codeGen/StgCmmHeap.hs
+++ b/compiler/codeGen/StgCmmHeap.hs
@@ -535,14 +535,15 @@ heapStackCheckGen stk_hwm mb_bytes
 
 -- Note [Single stack check]
 -- ~~~~~~~~~~~~~~~~~~~~~~~~~
--- When compiling a function we can determine how much stack space it will
--- use. We therefore need to perform only a single stack check at the beginning
--- of a function to see if we have enough stack space.
+-- When compiling a function we can determine how much stack space it
+-- will use. We therefore need to perform only a single stack check at
+-- the beginning of a function to see if we have enough stack space.
 --
--- The check boils down to comparing Sp+N with SpLim, where N is the
--- amount of stack space needed.  *BUT* at this stage of the pipeline
--- we are not supposed to refer to Sp itself, because the stack is not
--- yet manifest, so we don't quite know where Sp pointing.
+-- The check boils down to comparing Sp-N with SpLim, where N is the
+-- amount of stack space needed (see Note [Stack usage] below).  *BUT*
+-- at this stage of the pipeline we are not supposed to refer to Sp
+-- itself, because the stack is not yet manifest, so we don't quite
+-- know where Sp pointing.
 
 -- So instead of referring directly to Sp - as we used to do in the
 -- past - the code generator uses (old + 0) in the stack check. That
@@ -562,10 +563,27 @@ heapStackCheckGen stk_hwm mb_bytes
 -- into account changes already made to stack pointer. The idea for
 -- this change came from observations made while debugging #8275.
 
+-- Note [Stack usage]
+-- ~~~~~~~~~~~~~~~~~~
+-- At the moment we convert from STG to Cmm we don't know N, the
+-- number of bytes of stack that the function will use, so we use a
+-- special late-bound CmmLit, namely
+--       CmmHighStackMark
+-- to stand for the number of bytes needed. When the stack is made 
+-- manifest, the number of bytes needed is calculated, and used to
+-- replace occurrences of CmmHighStackMark
+--
+-- The (Maybe CmmExpr) passed to do_checks is usually 
+--     Just (CmmLit CmmHighStackMark)
+-- but can also (in certain hand-written RTS functions)
+--     Just (CmmLit 8)  or some other fixed valuet
+-- If it is Nothing, we don't generate a stack check at all.
+
 do_checks :: Maybe CmmExpr    -- Should we check the stack?
-          -> Bool       -- Should we check for preemption?
+                              -- See Note [Stack usage]
+          -> Bool             -- Should we check for preemption?
           -> Maybe CmmExpr    -- Heap headroom (bytes)
-          -> CmmAGraph  -- What to do on failure
+          -> CmmAGraph        -- What to do on failure
           -> FCode ()
 do_checks mb_stk_hwm checkYield mb_alloc_lit do_gc = do
   dflags <- getDynFlags



More information about the ghc-commits mailing list