[commit: ghc] wip/libdw-unwind: HACK: "Fix" labels (c45d744)

git at git.haskell.org git at git.haskell.org
Mon Jan 4 22:20:29 UTC 2016


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

On branch  : wip/libdw-unwind
Link       : http://ghc.haskell.org/trac/ghc/changeset/c45d7441d7b8ff2e41e83adfde176a300cb5b091/ghc

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

commit c45d7441d7b8ff2e41e83adfde176a300cb5b091
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Sun Jan 3 03:04:16 2016 +0100

    HACK: "Fix" labels


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

c45d7441d7b8ff2e41e83adfde176a300cb5b091
 compiler/cmm/Debug.hs         | 11 ++++++++---
 compiler/nativeGen/X86/Ppr.hs |  2 +-
 2 files changed, 9 insertions(+), 4 deletions(-)

diff --git a/compiler/cmm/Debug.hs b/compiler/cmm/Debug.hs
index d8513d4..83eff7c 100644
--- a/compiler/cmm/Debug.hs
+++ b/compiler/cmm/Debug.hs
@@ -20,7 +20,7 @@ module Debug (
 
   ) where
 
-import BlockId         ( blockLbl )
+import BlockId
 import CLabel
 import Cmm
 import CmmUtils
@@ -32,6 +32,7 @@ import PprCore         ()
 import PprCmmExpr      ( pprExpr )
 import SrcLoc
 import Util
+import Unique
 
 import Compiler.Hoopl
 
@@ -269,7 +270,10 @@ type UnwindTable = Map.Map GlobalReg UnwindExpr
 
 -- | An unwinding table associated with a particular point in the generated
 -- code.
-data UnwindDecl = UnwindDecl !Label !UnwindTable
+data UnwindDecl = UnwindDecl !CLabel !UnwindTable
+
+instance Outputable UnwindDecl where
+  ppr (UnwindDecl lbl tbl) = parens $ ppr lbl <+> ppr tbl
 
 -- | Expressions, used for unwind information
 data UnwindExpr = UwConst Int                   -- ^ literal value
@@ -302,7 +306,8 @@ extractUnwindTables b = mapMaybe nodeToUnwind $ blockToList mid
 
     nodeToUnwind :: CmmNode O O -> Maybe UnwindDecl
     nodeToUnwind (CmmUnwind lbl g so) =
-        Just $ UnwindDecl lbl' (Map.singleton g (toUnwindExpr so))
+        -- FIXME: why a block label if this isn't a block?
+        Just $ UnwindDecl (mkAsmTempLabel $ getUnique lbl') (Map.singleton g (toUnwindExpr so))
       where
         lbl' = case lbl of
                  NewLabel l      -> l
diff --git a/compiler/nativeGen/X86/Ppr.hs b/compiler/nativeGen/X86/Ppr.hs
index 8c1a336..44bb282 100644
--- a/compiler/nativeGen/X86/Ppr.hs
+++ b/compiler/nativeGen/X86/Ppr.hs
@@ -489,7 +489,7 @@ pprInstr (NEWBLOCK _)
    = panic "PprMach.pprInstr: NEWBLOCK"
 
 pprInstr (LABEL lbl)
-   = ppr lbl <> colon
+   = pprLabel $ mkAsmTempLabel $ getUnique lbl
 
 pprInstr (LDATA _ _)
    = panic "PprMach.pprInstr: LDATA"



More information about the ghc-commits mailing list