[commit: ghc] master: Debug: Use local symbols for unwind points (#13278) (2d6e91e)

git at git.haskell.org git at git.haskell.org
Tue Feb 14 15:54:35 UTC 2017


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

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

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

commit 2d6e91eab9391210b8b816d9664407f246ef30e4
Author: Ben Gamari <bgamari.foss at gmail.com>
Date:   Tue Feb 14 08:43:40 2017 -0500

    Debug: Use local symbols for unwind points (#13278)
    
    While this apparently didn't matter on Linux, the OS X toolchain seems
    to treat local and external symbols differently during linking. Namely,
    the linker assumes that an external symbol marks the beginning of a new,
    unused procedure, and consequently drops it.
    
    Fixes regression introduced in D2741.
    
    Test Plan: `debug` testcase on OS X
    
    Reviewers: austin, simonmar, rwbarton
    
    Reviewed By: rwbarton
    
    Subscribers: rwbarton, thomie
    
    Differential Revision: https://phabricator.haskell.org/D3135


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

2d6e91eab9391210b8b816d9664407f246ef30e4
 compiler/cmm/Debug.hs             | 2 +-
 compiler/nativeGen/X86/CodeGen.hs | 5 +++--
 compiler/nativeGen/X86/Instr.hs   | 2 +-
 3 files changed, 5 insertions(+), 4 deletions(-)

diff --git a/compiler/cmm/Debug.hs b/compiler/cmm/Debug.hs
index 7902694..428721a 100644
--- a/compiler/cmm/Debug.hs
+++ b/compiler/cmm/Debug.hs
@@ -393,7 +393,7 @@ See also: Note [Unwinding information in the NCG] in AsmCodeGen.
 -}
 
 -- | A label associated with an 'UnwindTable'
-data UnwindPoint = UnwindPoint !Label !UnwindTable
+data UnwindPoint = UnwindPoint !CLabel !UnwindTable
 
 instance Outputable UnwindPoint where
   ppr (UnwindPoint lbl uws) =
diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs
index a0a8f9d..72f8290 100644
--- a/compiler/nativeGen/X86/CodeGen.hs
+++ b/compiler/nativeGen/X86/CodeGen.hs
@@ -68,6 +68,7 @@ import Unique
 import FastString
 import DynFlags
 import Util
+import UniqSupply       ( getUniqueM )
 
 import Control.Monad
 import Data.Bits
@@ -162,7 +163,7 @@ addSpUnwindings :: Instr -> NatM (OrdList Instr)
 addSpUnwindings instr@(DELTA d) = do
     dflags <- getDynFlags
     if debugLevel dflags >= 1
-        then do lbl <- newBlockId
+        then do lbl <- mkAsmTempLabel <$> getUniqueM
                 let unwind = M.singleton MachSp (Just $ UwReg MachSp $ negate d)
                 return $ toOL [ instr, UNWIND lbl unwind ]
         else return (unitOL instr)
@@ -188,7 +189,7 @@ stmtToInstrs stmt = do
       case foldMap to_unwind_entry regs of
         tbl | M.null tbl -> return nilOL
             | otherwise  -> do
-                lbl <- newBlockId
+                lbl <- mkAsmTempLabel <$> getUniqueM
                 return $ unitOL $ UNWIND lbl tbl
 
     CmmAssign reg src
diff --git a/compiler/nativeGen/X86/Instr.hs b/compiler/nativeGen/X86/Instr.hs
index 4b43a1c..f4ac55c 100644
--- a/compiler/nativeGen/X86/Instr.hs
+++ b/compiler/nativeGen/X86/Instr.hs
@@ -182,7 +182,7 @@ data Instr
 
         -- unwinding information
         -- See Note [Unwinding information in the NCG].
-        | UNWIND BlockId UnwindTable
+        | UNWIND CLabel UnwindTable
 
         -- specify current stack offset for benefit of subsequent passes.
         -- This carries a BlockId so it can be used in unwinding information.



More information about the ghc-commits mailing list