[commit: ghc] master: Generate (old + 0) instead of Sp in stack checks (94125c9)

git at git.haskell.org git at git.haskell.org
Wed Oct 16 11:05:27 UTC 2013


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

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

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

commit 94125c97e49987e91fa54da6c86bc6d17417f5cf
Author: Jan Stolarek <jan.stolarek at p.lodz.pl>
Date:   Wed Oct 16 09:45:56 2013 +0200

    Generate (old + 0) instead of Sp in stack checks
    
    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. Instead of referring
    directly to Sp - as we used to do in the past - the code generator uses
    (old + 0) in the stack check. Stack layout phase turns (old + 0) into Sp.
    
    The idea here is that, while we need to perform only one stack check for
    each function, we could in theory place more stack checks later in the
    function. They would be redundant, but not incorrect (in a sense that they
    should not change program behaviour). We need to make sure however that a
    stack check inserted after incrementing the stack pointer checks for a
    respectively smaller stack space. This would not be the case if the code
    generator produced direct references to Sp. By referencing (old + 0) we make
    sure that we always check for a correct amount of stack: when converting
    (old + 0) to Sp the stack layout phase takes into account changes already
    made to stack pointer. The idea for this change came from observations made
    while debugging #8275.


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

94125c97e49987e91fa54da6c86bc6d17417f5cf
 compiler/cmm/CmmLayoutStack.hs |   12 ++----------
 compiler/codeGen/StgCmmHeap.hs |   27 +++++++++++++++++++++++++--
 2 files changed, 27 insertions(+), 12 deletions(-)

diff --git a/compiler/cmm/CmmLayoutStack.hs b/compiler/cmm/CmmLayoutStack.hs
index 17d111d..4ac5725 100644
--- a/compiler/cmm/CmmLayoutStack.hs
+++ b/compiler/cmm/CmmLayoutStack.hs
@@ -147,7 +147,7 @@ layout :: DynFlags
           , [CmmBlock]                  -- [out] new blocks
           )
 
-layout dflags procpoints liveness entry entry_args final_stackmaps final_hwm blocks
+layout dflags procpoints liveness entry entry_args final_stackmaps final_sp_high blocks
   = go blocks init_stackmap entry_args []
   where
     (updfr, cont_info)  = collectContInfo blocks
@@ -204,14 +204,7 @@ layout dflags procpoints liveness entry entry_args final_stackmaps final_hwm blo
        --
        let middle_pre = blockToList $ foldl blockSnoc middle1 middle2
 
-           sp_high = final_hwm - entry_args
-              -- The stack check value is adjusted by the Sp offset on
-              -- entry to the proc, which is entry_args.  We are
-              -- assuming that we only do a stack check at the
-              -- beginning of a proc, and we don't modify Sp before the
-              -- check.
-
-           final_blocks = manifestSp dflags final_stackmaps stack0 sp0 sp_high entry0
+           final_blocks = manifestSp dflags final_stackmaps stack0 sp0 final_sp_high entry0
                               middle_pre sp_off last1 fixup_blocks
 
            acc_stackmaps' = mapUnion acc_stackmaps out
@@ -1021,4 +1014,3 @@ insertReloads stackmap =
 
 stackSlotRegs :: StackMap -> [(LocalReg, StackLoc)]
 stackSlotRegs sm = eltsUFM (sm_regs sm)
-
diff --git a/compiler/codeGen/StgCmmHeap.hs b/compiler/codeGen/StgCmmHeap.hs
index f4c58e9..1d1100c 100644
--- a/compiler/codeGen/StgCmmHeap.hs
+++ b/compiler/codeGen/StgCmmHeap.hs
@@ -533,6 +533,27 @@ heapStackCheckGen stk_hwm mb_bytes
        call <- mkCall generic_gc (GC, GC) [] [] updfr_sz []
        do_checks stk_hwm False  mb_bytes (call <*> mkBranch lretry)
 
+-- 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. Instead of referring
+-- directly to Sp - as we used to do in the past - the code generator uses
+-- (old + 0) in the stack check. Stack layout phase turns (old + 0) into Sp.
+--
+-- The idea here is that, while we need to perform only one stack check for
+-- each function, we could in theory place more stack checks later in the
+-- function. They would be redundant, but not incorrect (in a sense that they
+-- should not change program behaviour). We need to make sure however that a
+-- stack check inserted after incrementing the stack pointer checks for a
+-- respectively smaller stack space. This would not be the case if the code
+-- generator produced direct references to Sp. By referencing (old + 0) we make
+-- sure that we always check for a correct amount of stack: when converting
+-- (old + 0) to Sp the stack layout phase takes into account changes already
+-- made to stack pointer. The idea for this change came from observations made
+-- while debugging #8275.
+
 do_checks :: Maybe CmmExpr    -- Should we check the stack?
           -> Bool       -- Should we check for preemption?
           -> Maybe CmmExpr    -- Heap headroom (bytes)
@@ -547,11 +568,13 @@ do_checks mb_stk_hwm checkYield mb_alloc_lit do_gc = do
 
     bump_hp   = cmmOffsetExprB dflags (CmmReg hpReg) alloc_lit
 
-    -- Sp overflow if (Sp - CmmHighStack < SpLim)
+    -- Sp overflow if ((old + 0) - CmmHighStack < SpLim)
+    -- At the beginning of a function old + 0 = Sp
+    -- See Note [Single stack check]
     sp_oflo sp_hwm =
          CmmMachOp (mo_wordULt dflags)
                   [CmmMachOp (MO_Sub (typeWidth (cmmRegType dflags spReg)))
-                             [CmmReg spReg, sp_hwm],
+                             [CmmStackSlot Old 0, sp_hwm],
                    CmmReg spLimReg]
 
     -- Hp overflow if (Hp > HpLim)



More information about the ghc-commits mailing list