summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorBen Gamari <ben@smart-cactus.org>2016-01-03 02:04:16 (GMT)
committerBen Gamari <ben@smart-cactus.org>2016-01-03 02:04:16 (GMT)
commitc45d7441d7b8ff2e41e83adfde176a300cb5b091 (patch)
treeb2d71498c9f235fbcc4c5d600bb0fb69c438661b
parented23b494a51c6544da2061377e8e0b07671bd890 (diff)
downloadghc-c45d7441d7b8ff2e41e83adfde176a300cb5b091.zip
ghc-c45d7441d7b8ff2e41e83adfde176a300cb5b091.tar.gz
ghc-c45d7441d7b8ff2e41e83adfde176a300cb5b091.tar.bz2
HACK: "Fix" labels
-rw-r--r--compiler/cmm/Debug.hs11
-rw-r--r--compiler/nativeGen/X86/Ppr.hs2
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"