diff options
Diffstat (limited to 'compiler/nativeGen')
-rw-r--r-- | compiler/nativeGen/AsmCodeGen.hs | 10 | ||||
-rw-r--r-- | compiler/nativeGen/Instruction.hs | 6 | ||||
-rw-r--r-- | compiler/nativeGen/NCGMonad.hs | 6 | ||||
-rw-r--r-- | compiler/nativeGen/PIC.hs | 8 | ||||
-rw-r--r-- | compiler/nativeGen/PPC/CodeGen.hs | 14 | ||||
-rw-r--r-- | compiler/nativeGen/PPC/Instr.hs | 4 | ||||
-rw-r--r-- | compiler/nativeGen/PPC/Ppr.hs | 14 | ||||
-rw-r--r-- | compiler/nativeGen/PPC/RegInfo.hs | 6 | ||||
-rw-r--r-- | compiler/nativeGen/RegAlloc/Liveness.hs | 2 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/CodeGen.hs | 8 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/CodeGen/Expand.hs | 2 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/CodeGen/Gen32.hs | 4 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/Instr.hs | 2 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/Ppr.hs | 14 | ||||
-rw-r--r-- | compiler/nativeGen/SPARC/ShortcutJump.hs | 6 | ||||
-rw-r--r-- | compiler/nativeGen/X86/CodeGen.hs | 12 | ||||
-rw-r--r-- | compiler/nativeGen/X86/Instr.hs | 8 | ||||
-rw-r--r-- | compiler/nativeGen/X86/Ppr.hs | 14 |
18 files changed, 70 insertions, 70 deletions
diff --git a/compiler/nativeGen/AsmCodeGen.hs b/compiler/nativeGen/AsmCodeGen.hs index 4a38909e65..88f666c375 100644 --- a/compiler/nativeGen/AsmCodeGen.hs +++ b/compiler/nativeGen/AsmCodeGen.hs @@ -182,12 +182,12 @@ nativeCodeGen dflags this_mod modLoc h us cmms ArchUnknown -> panic "nativeCodeGen: No NCG for unknown arch" ArchJavaScript-> panic "nativeCodeGen: No NCG for JavaScript" -x86NcgImpl :: DynFlags -> NcgImpl (Alignment, CmmStatics) +x86NcgImpl :: DynFlags -> NcgImpl (Alignment, RawCmmStatics) X86.Instr.Instr X86.Instr.JumpDest x86NcgImpl dflags = (x86_64NcgImpl dflags) -x86_64NcgImpl :: DynFlags -> NcgImpl (Alignment, CmmStatics) +x86_64NcgImpl :: DynFlags -> NcgImpl (Alignment, RawCmmStatics) X86.Instr.Instr X86.Instr.JumpDest x86_64NcgImpl dflags = NcgImpl { @@ -208,7 +208,7 @@ x86_64NcgImpl dflags } where platform = targetPlatform dflags -ppcNcgImpl :: DynFlags -> NcgImpl CmmStatics PPC.Instr.Instr PPC.RegInfo.JumpDest +ppcNcgImpl :: DynFlags -> NcgImpl RawCmmStatics PPC.Instr.Instr PPC.RegInfo.JumpDest ppcNcgImpl dflags = NcgImpl { cmmTopCodeGen = PPC.CodeGen.cmmTopCodeGen @@ -228,7 +228,7 @@ ppcNcgImpl dflags } where platform = targetPlatform dflags -sparcNcgImpl :: DynFlags -> NcgImpl CmmStatics SPARC.Instr.Instr SPARC.ShortcutJump.JumpDest +sparcNcgImpl :: DynFlags -> NcgImpl RawCmmStatics SPARC.Instr.Instr SPARC.ShortcutJump.JumpDest sparcNcgImpl dflags = NcgImpl { cmmTopCodeGen = SPARC.CodeGen.cmmTopCodeGen @@ -748,7 +748,7 @@ cmmNativeGen dflags this_mod modLoc ncgImpl us fileIds dbgMap cmm count {-# SCC "invertCondBranches" #-} map invert sequenced where - invertConds :: LabelMap CmmStatics -> [NatBasicBlock instr] + invertConds :: LabelMap RawCmmStatics -> [NatBasicBlock instr] -> [NatBasicBlock instr] invertConds = invertCondBranches ncgImpl optimizedCFG invert top@CmmData {} = top diff --git a/compiler/nativeGen/Instruction.hs b/compiler/nativeGen/Instruction.hs index 150bd8adba..ad4937bf08 100644 --- a/compiler/nativeGen/Instruction.hs +++ b/compiler/nativeGen/Instruction.hs @@ -46,14 +46,14 @@ noUsage = RU [] [] -- Type synonyms for Cmm populated with native code type NatCmm instr = GenCmmGroup - CmmStatics - (LabelMap CmmStatics) + RawCmmStatics + (LabelMap RawCmmStatics) (ListGraph instr) type NatCmmDecl statics instr = GenCmmDecl statics - (LabelMap CmmStatics) + (LabelMap RawCmmStatics) (ListGraph instr) diff --git a/compiler/nativeGen/NCGMonad.hs b/compiler/nativeGen/NCGMonad.hs index b963623535..849b3fe761 100644 --- a/compiler/nativeGen/NCGMonad.hs +++ b/compiler/nativeGen/NCGMonad.hs @@ -65,7 +65,7 @@ import Control.Monad ( ap ) import Instruction import Outputable (SDoc, pprPanic, ppr) -import GHC.Cmm (RawCmmDecl, CmmStatics) +import GHC.Cmm (RawCmmDecl, RawCmmStatics) import CFG data NcgImpl statics instr jumpDest = NcgImpl { @@ -83,13 +83,13 @@ data NcgImpl statics instr jumpDest = NcgImpl { -> UniqSM (NatCmmDecl statics instr, [(BlockId,BlockId)]), -- ^ The list of block ids records the redirected jumps to allow us to update -- the CFG. - ncgMakeFarBranches :: LabelMap CmmStatics -> [NatBasicBlock instr] -> [NatBasicBlock instr], + ncgMakeFarBranches :: LabelMap RawCmmStatics -> [NatBasicBlock instr] -> [NatBasicBlock instr], extractUnwindPoints :: [instr] -> [UnwindPoint], -- ^ given the instruction sequence of a block, produce a list of -- the block's 'UnwindPoint's -- See Note [What is this unwinding business?] in Debug -- and Note [Unwinding information in the NCG] in this module. - invertCondBranches :: Maybe CFG -> LabelMap CmmStatics -> [NatBasicBlock instr] + invertCondBranches :: Maybe CFG -> LabelMap RawCmmStatics -> [NatBasicBlock instr] -> [NatBasicBlock instr] -- ^ Turn the sequence of `jcc l1; jmp l2` into `jncc l2; <block_l1>` -- when possible. diff --git a/compiler/nativeGen/PIC.hs b/compiler/nativeGen/PIC.hs index e4aba00596..6e0708ab04 100644 --- a/compiler/nativeGen/PIC.hs +++ b/compiler/nativeGen/PIC.hs @@ -730,8 +730,8 @@ pprImportedSymbol _ _ _ initializePicBase_ppc :: Arch -> OS -> Reg - -> [NatCmmDecl CmmStatics PPC.Instr] - -> NatM [NatCmmDecl CmmStatics PPC.Instr] + -> [NatCmmDecl RawCmmStatics PPC.Instr] + -> NatM [NatCmmDecl RawCmmStatics PPC.Instr] initializePicBase_ppc ArchPPC os picReg (CmmProc info lab live (ListGraph blocks) : statics) @@ -805,8 +805,8 @@ initializePicBase_ppc _ _ _ _ initializePicBase_x86 :: Arch -> OS -> Reg - -> [NatCmmDecl (Alignment, CmmStatics) X86.Instr] - -> NatM [NatCmmDecl (Alignment, CmmStatics) X86.Instr] + -> [NatCmmDecl (Alignment, RawCmmStatics) X86.Instr] + -> NatM [NatCmmDecl (Alignment, RawCmmStatics) X86.Instr] initializePicBase_x86 ArchX86 os picReg (CmmProc info lab live (ListGraph blocks) : statics) diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs index 4d9a38b9de..4374cbeb8d 100644 --- a/compiler/nativeGen/PPC/CodeGen.hs +++ b/compiler/nativeGen/PPC/CodeGen.hs @@ -74,7 +74,7 @@ import Util cmmTopCodeGen :: RawCmmDecl - -> NatM [NatCmmDecl CmmStatics Instr] + -> NatM [NatCmmDecl RawCmmStatics Instr] cmmTopCodeGen (CmmProc info lab live graph) = do let blocks = toBlockListEntryFirst graph @@ -115,7 +115,7 @@ cmmTopCodeGen (CmmData sec dat) = do basicBlockCodeGen :: Block CmmNode C C -> NatM ( [NatBasicBlock Instr] - , [NatCmmDecl CmmStatics Instr]) + , [NatCmmDecl RawCmmStatics Instr]) basicBlockCodeGen block = do let (_, nodes, tail) = blockSplit block @@ -669,7 +669,7 @@ getRegister' _ (CmmLit (CmmFloat f frep)) = do let format = floatFormat frep code dst = LDATA (Section ReadOnlyData lbl) - (Statics lbl [CmmStaticLit (CmmFloat f frep)]) + (RawCmmStatics lbl [CmmStaticLit (CmmFloat f frep)]) `consOL` (addr_code `snocOL` LD format dst addr) return (Any format code) @@ -690,7 +690,7 @@ getRegister' dflags (CmmLit lit) let rep = cmmLitType dflags lit format = cmmTypeFormat rep code dst = - LDATA (Section ReadOnlyData lbl) (Statics lbl [CmmStaticLit lit]) + LDATA (Section ReadOnlyData lbl) (RawCmmStatics lbl [CmmStaticLit lit]) `consOL` (addr_code `snocOL` LD format dst addr) return (Any format code) @@ -2095,7 +2095,7 @@ genSwitch dflags expr targets where (offset, ids) = switchTargetsToTable targets generateJumpTableForInstr :: DynFlags -> Instr - -> Maybe (NatCmmDecl CmmStatics Instr) + -> Maybe (NatCmmDecl RawCmmStatics Instr) generateJumpTableForInstr dflags (BCTR ids (Just lbl) _) = let jumpTable | (positionIndependent dflags) @@ -2108,7 +2108,7 @@ generateJumpTableForInstr dflags (BCTR ids (Just lbl) _) = = CmmStaticLit (CmmLabelDiffOff blockLabel lbl 0 (wordWidth dflags)) where blockLabel = blockLbl blockid - in Just (CmmData (Section ReadOnlyData lbl) (Statics lbl jumpTable)) + in Just (CmmData (Section ReadOnlyData lbl) (RawCmmStatics lbl jumpTable)) generateJumpTableForInstr _ _ = Nothing -- ----------------------------------------------------------------------------- @@ -2337,7 +2337,7 @@ coerceInt2FP' ArchPPC fromRep toRep x = do Amode addr addr_code <- getAmode D dynRef let code' dst = code `appOL` maybe_exts `appOL` toOL [ - LDATA (Section ReadOnlyData lbl) $ Statics lbl + LDATA (Section ReadOnlyData lbl) $ RawCmmStatics lbl [CmmStaticLit (CmmInt 0x43300000 W32), CmmStaticLit (CmmInt 0x80000000 W32)], XORIS itmp src (ImmInt 0x8000), diff --git a/compiler/nativeGen/PPC/Instr.hs b/compiler/nativeGen/PPC/Instr.hs index f149c92c9d..2dff3349fb 100644 --- a/compiler/nativeGen/PPC/Instr.hs +++ b/compiler/nativeGen/PPC/Instr.hs @@ -190,7 +190,7 @@ data Instr -- some static data spat out during code -- generation. Will be extracted before -- pretty-printing. - | LDATA Section CmmStatics + | LDATA Section RawCmmStatics -- start a new basic block. Useful during -- codegen, removed later. Preceding @@ -682,7 +682,7 @@ ppc_takeRegRegMoveInstr _ = Nothing -- big, we have to work around this limitation. makeFarBranches - :: LabelMap CmmStatics + :: LabelMap RawCmmStatics -> [NatBasicBlock Instr] -> [NatBasicBlock Instr] makeFarBranches info_env blocks diff --git a/compiler/nativeGen/PPC/Ppr.hs b/compiler/nativeGen/PPC/Ppr.hs index 9669076bef..5ede19bd5e 100644 --- a/compiler/nativeGen/PPC/Ppr.hs +++ b/compiler/nativeGen/PPC/Ppr.hs @@ -42,7 +42,7 @@ import Data.Bits -- ----------------------------------------------------------------------------- -- Printing this stuff out -pprNatCmmDecl :: NatCmmDecl CmmStatics Instr -> SDoc +pprNatCmmDecl :: NatCmmDecl RawCmmStatics Instr -> SDoc pprNatCmmDecl (CmmData section dats) = pprSectionAlign section $$ pprDatas dats @@ -59,7 +59,7 @@ pprNatCmmDecl proc@(CmmProc top_info lbl _ (ListGraph blocks)) = -- so label needed vcat (map (pprBasicBlock top_info) blocks) - Just (Statics info_lbl _) -> + Just (RawCmmStatics info_lbl _) -> sdocWithPlatform $ \platform -> pprSectionAlign (Section Text info_lbl) $$ (if platformHasSubsectionsViaSymbols platform @@ -104,7 +104,7 @@ pprFunctionPrologue lab = pprGloblDecl lab $$ text "\t.localentry\t" <> ppr lab <> text ",.-" <> ppr lab -pprBasicBlock :: LabelMap CmmStatics -> NatBasicBlock Instr -> SDoc +pprBasicBlock :: LabelMap RawCmmStatics -> NatBasicBlock Instr -> SDoc pprBasicBlock info_env (BasicBlock blockid instrs) = maybe_infotable $$ pprLabel (blockLbl blockid) $$ @@ -112,16 +112,16 @@ pprBasicBlock info_env (BasicBlock blockid instrs) where maybe_infotable = case mapLookup blockid info_env of Nothing -> empty - Just (Statics info_lbl info) -> + Just (RawCmmStatics info_lbl info) -> pprAlignForSection Text $$ vcat (map pprData info) $$ pprLabel info_lbl -pprDatas :: CmmStatics -> SDoc +pprDatas :: RawCmmStatics -> SDoc -- See note [emit-time elimination of static indirections] in CLabel. -pprDatas (Statics alias [CmmStaticLit (CmmLabel lbl), CmmStaticLit ind, _, _]) +pprDatas (RawCmmStatics alias [CmmStaticLit (CmmLabel lbl), CmmStaticLit ind, _, _]) | lbl == mkIndStaticInfoLabel , let labelInd (CmmLabelOff l _) = Just l labelInd (CmmLabel l) = Just l @@ -130,7 +130,7 @@ pprDatas (Statics alias [CmmStaticLit (CmmLabel lbl), CmmStaticLit ind, _, _]) , alias `mayRedirectTo` ind' = pprGloblDecl alias $$ text ".equiv" <+> ppr alias <> comma <> ppr (CmmLabel ind') -pprDatas (Statics lbl dats) = vcat (pprLabel lbl : map pprData dats) +pprDatas (RawCmmStatics lbl dats) = vcat (pprLabel lbl : map pprData dats) pprData :: CmmStatic -> SDoc pprData (CmmString str) = pprBytes str diff --git a/compiler/nativeGen/PPC/RegInfo.hs b/compiler/nativeGen/PPC/RegInfo.hs index e99a69313e..c1a4e73e3d 100644 --- a/compiler/nativeGen/PPC/RegInfo.hs +++ b/compiler/nativeGen/PPC/RegInfo.hs @@ -47,9 +47,9 @@ shortcutJump _ other = other -- Here because it knows about JumpDest -shortcutStatics :: (BlockId -> Maybe JumpDest) -> CmmStatics -> CmmStatics -shortcutStatics fn (Statics lbl statics) - = Statics lbl $ map (shortcutStatic fn) statics +shortcutStatics :: (BlockId -> Maybe JumpDest) -> RawCmmStatics -> RawCmmStatics +shortcutStatics fn (RawCmmStatics lbl statics) + = RawCmmStatics lbl $ map (shortcutStatic fn) statics -- we need to get the jump tables, so apply the mapping to the entries -- of a CmmData too. diff --git a/compiler/nativeGen/RegAlloc/Liveness.hs b/compiler/nativeGen/RegAlloc/Liveness.hs index 44a7b359a8..cf17d149e9 100644 --- a/compiler/nativeGen/RegAlloc/Liveness.hs +++ b/compiler/nativeGen/RegAlloc/Liveness.hs @@ -176,7 +176,7 @@ data Liveness -- | Stash regs live on entry to each basic block in the info part of the cmm code. data LiveInfo = LiveInfo - (LabelMap CmmStatics) -- cmm info table static stuff + (LabelMap RawCmmStatics) -- cmm info table static stuff [BlockId] -- entry points (first one is the -- entry point for the proc). (BlockMap RegSet) -- argument locals live on entry to this block diff --git a/compiler/nativeGen/SPARC/CodeGen.hs b/compiler/nativeGen/SPARC/CodeGen.hs index d8cda40d1a..60cfd91de9 100644 --- a/compiler/nativeGen/SPARC/CodeGen.hs +++ b/compiler/nativeGen/SPARC/CodeGen.hs @@ -62,7 +62,7 @@ import Control.Monad ( mapAndUnzipM ) -- | Top level code generation cmmTopCodeGen :: RawCmmDecl - -> NatM [NatCmmDecl CmmStatics Instr] + -> NatM [NatCmmDecl RawCmmStatics Instr] cmmTopCodeGen (CmmProc info lab live graph) = do let blocks = toBlockListEntryFirst graph @@ -84,7 +84,7 @@ cmmTopCodeGen (CmmData sec dat) = do -- LDATAs here too. basicBlockCodeGen :: CmmBlock -> NatM ( [NatBasicBlock Instr] - , [NatCmmDecl CmmStatics Instr]) + , [NatCmmDecl RawCmmStatics Instr]) basicBlockCodeGen block = do let (_, nodes, tail) = blockSplit block @@ -339,10 +339,10 @@ genSwitch dflags expr targets where (offset, ids) = switchTargetsToTable targets generateJumpTableForInstr :: DynFlags -> Instr - -> Maybe (NatCmmDecl CmmStatics Instr) + -> Maybe (NatCmmDecl RawCmmStatics Instr) generateJumpTableForInstr dflags (JMP_TBL _ ids label) = let jumpTable = map (jumpTableEntry dflags) ids - in Just (CmmData (Section ReadOnlyData label) (Statics label jumpTable)) + in Just (CmmData (Section ReadOnlyData label) (RawCmmStatics label jumpTable)) generateJumpTableForInstr _ _ = Nothing diff --git a/compiler/nativeGen/SPARC/CodeGen/Expand.hs b/compiler/nativeGen/SPARC/CodeGen/Expand.hs index a384e498d2..b6d78a9f79 100644 --- a/compiler/nativeGen/SPARC/CodeGen/Expand.hs +++ b/compiler/nativeGen/SPARC/CodeGen/Expand.hs @@ -23,7 +23,7 @@ import Outputable import OrdList -- | Expand out synthetic instructions in this top level thing -expandTop :: NatCmmDecl CmmStatics Instr -> NatCmmDecl CmmStatics Instr +expandTop :: NatCmmDecl RawCmmStatics Instr -> NatCmmDecl RawCmmStatics Instr expandTop top@(CmmData{}) = top diff --git a/compiler/nativeGen/SPARC/CodeGen/Gen32.hs b/compiler/nativeGen/SPARC/CodeGen/Gen32.hs index a4f6214edc..01f133ed8f 100644 --- a/compiler/nativeGen/SPARC/CodeGen/Gen32.hs +++ b/compiler/nativeGen/SPARC/CodeGen/Gen32.hs @@ -88,7 +88,7 @@ getRegister (CmmLit (CmmFloat f W32)) = do let code dst = toOL [ -- the data area - LDATA (Section ReadOnlyData lbl) $ Statics lbl + LDATA (Section ReadOnlyData lbl) $ RawCmmStatics lbl [CmmStaticLit (CmmFloat f W32)], -- load the literal @@ -101,7 +101,7 @@ getRegister (CmmLit (CmmFloat d W64)) = do lbl <- getNewLabelNat tmp <- getNewRegNat II32 let code dst = toOL [ - LDATA (Section ReadOnlyData lbl) $ Statics lbl + LDATA (Section ReadOnlyData lbl) $ RawCmmStatics lbl [CmmStaticLit (CmmFloat d W64)], SETHI (HI (ImmCLbl lbl)) tmp, LD II64 (AddrRegImm tmp (LO (ImmCLbl lbl))) dst] diff --git a/compiler/nativeGen/SPARC/Instr.hs b/compiler/nativeGen/SPARC/Instr.hs index 43edfc61f4..7b4935802b 100644 --- a/compiler/nativeGen/SPARC/Instr.hs +++ b/compiler/nativeGen/SPARC/Instr.hs @@ -117,7 +117,7 @@ data Instr -- some static data spat out during code generation. -- Will be extracted before pretty-printing. - | LDATA Section CmmStatics + | LDATA Section RawCmmStatics -- Start a new basic block. Useful during codegen, removed later. -- Preceding instruction should be a jump, as per the invariants diff --git a/compiler/nativeGen/SPARC/Ppr.hs b/compiler/nativeGen/SPARC/Ppr.hs index 7e40f0d60b..566f438403 100644 --- a/compiler/nativeGen/SPARC/Ppr.hs +++ b/compiler/nativeGen/SPARC/Ppr.hs @@ -52,7 +52,7 @@ import FastString -- ----------------------------------------------------------------------------- -- Printing this stuff out -pprNatCmmDecl :: NatCmmDecl CmmStatics Instr -> SDoc +pprNatCmmDecl :: NatCmmDecl RawCmmStatics Instr -> SDoc pprNatCmmDecl (CmmData section dats) = pprSectionAlign section $$ pprDatas dats @@ -64,7 +64,7 @@ pprNatCmmDecl proc@(CmmProc top_info lbl _ (ListGraph blocks)) = pprLabel lbl $$ -- blocks guaranteed not null, so label needed vcat (map (pprBasicBlock top_info) blocks) - Just (Statics info_lbl _) -> + Just (RawCmmStatics info_lbl _) -> sdocWithPlatform $ \platform -> (if platformHasSubsectionsViaSymbols platform then pprSectionAlign dspSection $$ @@ -86,7 +86,7 @@ dspSection :: Section dspSection = Section Text $ panic "subsections-via-symbols doesn't combine with split-sections" -pprBasicBlock :: LabelMap CmmStatics -> NatBasicBlock Instr -> SDoc +pprBasicBlock :: LabelMap RawCmmStatics -> NatBasicBlock Instr -> SDoc pprBasicBlock info_env (BasicBlock blockid instrs) = maybe_infotable $$ pprLabel (blockLbl blockid) $$ @@ -94,15 +94,15 @@ pprBasicBlock info_env (BasicBlock blockid instrs) where maybe_infotable = case mapLookup blockid info_env of Nothing -> empty - Just (Statics info_lbl info) -> + Just (RawCmmStatics info_lbl info) -> pprAlignForSection Text $$ vcat (map pprData info) $$ pprLabel info_lbl -pprDatas :: CmmStatics -> SDoc +pprDatas :: RawCmmStatics -> SDoc -- See note [emit-time elimination of static indirections] in CLabel. -pprDatas (Statics alias [CmmStaticLit (CmmLabel lbl), CmmStaticLit ind, _, _]) +pprDatas (RawCmmStatics alias [CmmStaticLit (CmmLabel lbl), CmmStaticLit ind, _, _]) | lbl == mkIndStaticInfoLabel , let labelInd (CmmLabelOff l _) = Just l labelInd (CmmLabel l) = Just l @@ -111,7 +111,7 @@ pprDatas (Statics alias [CmmStaticLit (CmmLabel lbl), CmmStaticLit ind, _, _]) , alias `mayRedirectTo` ind' = pprGloblDecl alias $$ text ".equiv" <+> ppr alias <> comma <> ppr (CmmLabel ind') -pprDatas (Statics lbl dats) = vcat (pprLabel lbl : map pprData dats) +pprDatas (RawCmmStatics lbl dats) = vcat (pprLabel lbl : map pprData dats) pprData :: CmmStatic -> SDoc pprData (CmmString str) = pprBytes str diff --git a/compiler/nativeGen/SPARC/ShortcutJump.hs b/compiler/nativeGen/SPARC/ShortcutJump.hs index 02d51de30f..35604b0b7e 100644 --- a/compiler/nativeGen/SPARC/ShortcutJump.hs +++ b/compiler/nativeGen/SPARC/ShortcutJump.hs @@ -43,9 +43,9 @@ shortcutJump _ other = other -shortcutStatics :: (BlockId -> Maybe JumpDest) -> CmmStatics -> CmmStatics -shortcutStatics fn (Statics lbl statics) - = Statics lbl $ map (shortcutStatic fn) statics +shortcutStatics :: (BlockId -> Maybe JumpDest) -> RawCmmStatics -> RawCmmStatics +shortcutStatics fn (RawCmmStatics lbl statics) + = RawCmmStatics lbl $ map (shortcutStatic fn) statics -- we need to get the jump tables, so apply the mapping to the entries -- of a CmmData too. diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs index 8811385965..d60231f7b2 100644 --- a/compiler/nativeGen/X86/CodeGen.hs +++ b/compiler/nativeGen/X86/CodeGen.hs @@ -122,7 +122,7 @@ sse4_2Enabled = do cmmTopCodeGen :: RawCmmDecl - -> NatM [NatCmmDecl (Alignment, CmmStatics) Instr] + -> NatM [NatCmmDecl (Alignment, RawCmmStatics) Instr] cmmTopCodeGen (CmmProc info lab live graph) = do let blocks = toBlockListEntryFirst graph @@ -194,7 +194,7 @@ verifyBasicBlock instrs basicBlockCodeGen :: CmmBlock -> NatM ( [NatBasicBlock Instr] - , [NatCmmDecl (Alignment, CmmStatics) Instr]) + , [NatCmmDecl (Alignment, RawCmmStatics) Instr]) basicBlockCodeGen block = do let (_, nodes, tail) = blockSplit block @@ -1482,7 +1482,7 @@ memConstant align lit = do return (addr, addr_code) else return (ripRel (ImmCLbl lbl), nilOL) let code = - LDATA rosection (align, Statics lbl [CmmStaticLit lit]) + LDATA rosection (align, RawCmmStatics lbl [CmmStaticLit lit]) `consOL` addr_code return (Amode addr code) @@ -3305,7 +3305,7 @@ genSwitch dflags expr targets (offset, blockIds) = switchTargetsToTable targets ids = map (fmap DestBlockId) blockIds -generateJumpTableForInstr :: DynFlags -> Instr -> Maybe (NatCmmDecl (Alignment, CmmStatics) Instr) +generateJumpTableForInstr :: DynFlags -> Instr -> Maybe (NatCmmDecl (Alignment, RawCmmStatics) Instr) generateJumpTableForInstr dflags (JMP_TBL _ ids section lbl) = let getBlockId (DestBlockId id) = id getBlockId _ = panic "Non-Label target in Jump Table" @@ -3314,7 +3314,7 @@ generateJumpTableForInstr dflags (JMP_TBL _ ids section lbl) generateJumpTableForInstr _ _ = Nothing createJumpTable :: DynFlags -> [Maybe BlockId] -> Section -> CLabel - -> GenCmmDecl (Alignment, CmmStatics) h g + -> GenCmmDecl (Alignment, RawCmmStatics) h g createJumpTable dflags ids section lbl = let jumpTable | positionIndependent dflags = @@ -3326,7 +3326,7 @@ createJumpTable dflags ids section lbl where blockLabel = blockLbl blockid in map jumpTableEntryRel ids | otherwise = map (jumpTableEntry dflags) ids - in CmmData section (mkAlignment 1, Statics lbl jumpTable) + in CmmData section (mkAlignment 1, RawCmmStatics lbl jumpTable) extractUnwindPoints :: [Instr] -> [UnwindPoint] extractUnwindPoints instrs = diff --git a/compiler/nativeGen/X86/Instr.hs b/compiler/nativeGen/X86/Instr.hs index 4591464671..422bb96de4 100644 --- a/compiler/nativeGen/X86/Instr.hs +++ b/compiler/nativeGen/X86/Instr.hs @@ -174,7 +174,7 @@ data Instr -- some static data spat out during code -- generation. Will be extracted before -- pretty-printing. - | LDATA Section (Alignment, CmmStatics) + | LDATA Section (Alignment, RawCmmStatics) -- start a new basic block. Useful during -- codegen, removed later. Preceding @@ -1017,9 +1017,9 @@ shortcutJump fn insn = shortcutJump' fn (setEmpty :: LabelSet) insn shortcutJump' _ _ other = other -- Here because it knows about JumpDest -shortcutStatics :: (BlockId -> Maybe JumpDest) -> (Alignment, CmmStatics) -> (Alignment, CmmStatics) -shortcutStatics fn (align, Statics lbl statics) - = (align, Statics lbl $ map (shortcutStatic fn) statics) +shortcutStatics :: (BlockId -> Maybe JumpDest) -> (Alignment, RawCmmStatics) -> (Alignment, RawCmmStatics) +shortcutStatics fn (align, RawCmmStatics lbl statics) + = (align, RawCmmStatics lbl $ map (shortcutStatic fn) statics) -- we need to get the jump tables, so apply the mapping to the entries -- of a CmmData too. diff --git a/compiler/nativeGen/X86/Ppr.hs b/compiler/nativeGen/X86/Ppr.hs index d857a952ce..8b73cdffc1 100644 --- a/compiler/nativeGen/X86/Ppr.hs +++ b/compiler/nativeGen/X86/Ppr.hs @@ -73,7 +73,7 @@ pprProcAlignment :: SDoc pprProcAlignment = sdocWithDynFlags $ \dflags -> (maybe empty (pprAlign . mkAlignment) (cmmProcAlignment dflags)) -pprNatCmmDecl :: NatCmmDecl (Alignment, CmmStatics) Instr -> SDoc +pprNatCmmDecl :: NatCmmDecl (Alignment, RawCmmStatics) Instr -> SDoc pprNatCmmDecl (CmmData section dats) = pprSectionAlign section $$ pprDatas dats @@ -91,7 +91,7 @@ pprNatCmmDecl proc@(CmmProc top_info lbl _ (ListGraph blocks)) = then ppr (mkAsmTempEndLabel lbl) <> char ':' else empty) $$ pprSizeDecl lbl - Just (Statics info_lbl _) -> + Just (RawCmmStatics info_lbl _) -> sdocWithPlatform $ \platform -> pprSectionAlign (Section Text info_lbl) $$ pprProcAlignment $$ @@ -118,7 +118,7 @@ pprSizeDecl lbl then text "\t.size" <+> ppr lbl <> ptext (sLit ", .-") <> ppr lbl else empty -pprBasicBlock :: LabelMap CmmStatics -> NatBasicBlock Instr -> SDoc +pprBasicBlock :: LabelMap RawCmmStatics -> NatBasicBlock Instr -> SDoc pprBasicBlock info_env (BasicBlock blockid instrs) = sdocWithDynFlags $ \dflags -> maybe_infotable dflags $ @@ -130,7 +130,7 @@ pprBasicBlock info_env (BasicBlock blockid instrs) asmLbl = blockLbl blockid maybe_infotable dflags c = case mapLookup blockid info_env of Nothing -> c - Just (Statics infoLbl info) -> + Just (RawCmmStatics infoLbl info) -> pprAlignForSection Text $$ infoTableLoc $$ vcat (map pprData info) $$ @@ -145,9 +145,9 @@ pprBasicBlock info_env (BasicBlock blockid instrs) _other -> empty -pprDatas :: (Alignment, CmmStatics) -> SDoc +pprDatas :: (Alignment, RawCmmStatics) -> SDoc -- See note [emit-time elimination of static indirections] in CLabel. -pprDatas (_, Statics alias [CmmStaticLit (CmmLabel lbl), CmmStaticLit ind, _, _]) +pprDatas (_, RawCmmStatics alias [CmmStaticLit (CmmLabel lbl), CmmStaticLit ind, _, _]) | lbl == mkIndStaticInfoLabel , let labelInd (CmmLabelOff l _) = Just l labelInd (CmmLabel l) = Just l @@ -157,7 +157,7 @@ pprDatas (_, Statics alias [CmmStaticLit (CmmLabel lbl), CmmStaticLit ind, _, _] = pprGloblDecl alias $$ text ".equiv" <+> ppr alias <> comma <> ppr (CmmLabel ind') -pprDatas (align, (Statics lbl dats)) +pprDatas (align, (RawCmmStatics lbl dats)) = vcat (pprAlign align : pprLabel lbl : map pprData dats) pprData :: CmmStatic -> SDoc |