summaryrefslogtreecommitdiff
path: root/compiler/nativeGen
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/nativeGen')
-rw-r--r--compiler/nativeGen/AsmCodeGen.lhs20
-rw-r--r--compiler/nativeGen/PIC.hs32
-rw-r--r--compiler/nativeGen/PPC/CodeGen.hs4
-rw-r--r--compiler/nativeGen/RegAlloc/Graph/Main.hs12
-rw-r--r--compiler/nativeGen/SPARC/CodeGen.hs2
-rw-r--r--compiler/nativeGen/X86/CodeGen.hs8
6 files changed, 39 insertions, 39 deletions
diff --git a/compiler/nativeGen/AsmCodeGen.lhs b/compiler/nativeGen/AsmCodeGen.lhs
index d0e4a17746..a233a8ffba 100644
--- a/compiler/nativeGen/AsmCodeGen.lhs
+++ b/compiler/nativeGen/AsmCodeGen.lhs
@@ -287,7 +287,7 @@ nativeCodeGen' dflags ncgImpl h us cmms
return ()
where add_split tops
- | dopt Opt_SplitObjs dflags = split_marker : tops
+ | gopt Opt_SplitObjs dflags = split_marker : tops
| otherwise = tops
split_marker = CmmProc mapEmpty mkSplitMarkerLabel (ListGraph [])
@@ -356,8 +356,8 @@ cmmNativeGens dflags ncgImpl h us (cmm : cmms) impAcc profAcc count
-- and then using 'seq' doesn't work, because the let
-- apparently gets inlined first.
lsPprNative <- return $!
- if dopt Opt_D_dump_asm dflags
- || dopt Opt_D_dump_asm_stats dflags
+ if gopt Opt_D_dump_asm dflags
+ || gopt Opt_D_dump_asm_stats dflags
then native
else []
@@ -432,8 +432,8 @@ cmmNativeGen dflags ncgImpl us cmm count
-- allocate registers
(alloced, usAlloc, ppr_raStatsColor, ppr_raStatsLinear) <-
- if ( dopt Opt_RegsGraph dflags
- || dopt Opt_RegsIterative dflags)
+ if ( gopt Opt_RegsGraph dflags
+ || gopt Opt_RegsIterative dflags)
then do
-- the regs usable for allocation
let (alloc_regs :: UniqFM (UniqSet RealReg))
@@ -466,7 +466,7 @@ cmmNativeGen dflags ncgImpl us cmm count
$ zip [0..] regAllocStats)
let mPprStats =
- if dopt Opt_D_dump_asm_stats dflags
+ if gopt Opt_D_dump_asm_stats dflags
then Just regAllocStats else Nothing
-- force evaluation of the Maybe to avoid space leak
@@ -498,7 +498,7 @@ cmmNativeGen dflags ncgImpl us cmm count
(vcat $ map (pprNatCmmDecl ncgImpl) alloced)
let mPprStats =
- if dopt Opt_D_dump_asm_stats dflags
+ if gopt Opt_D_dump_asm_stats dflags
then Just (catMaybes regAllocStats) else Nothing
-- force evaluation of the Maybe to avoid space leak
@@ -1024,15 +1024,15 @@ cmmExprNative referenceKind expr = do
-- to use the register table, so we replace these registers
-- with the corresponding labels:
CmmReg (CmmGlobal EagerBlackholeInfo)
- | arch == ArchPPC && not (dopt Opt_PIC dflags)
+ | arch == ArchPPC && not (gopt Opt_PIC dflags)
-> cmmExprNative referenceKind $
CmmLit (CmmLabel (mkCmmCodeLabel rtsPackageId (fsLit "__stg_EAGER_BLACKHOLE_info")))
CmmReg (CmmGlobal GCEnter1)
- | arch == ArchPPC && not (dopt Opt_PIC dflags)
+ | arch == ArchPPC && not (gopt Opt_PIC dflags)
-> cmmExprNative referenceKind $
CmmLit (CmmLabel (mkCmmCodeLabel rtsPackageId (fsLit "__stg_gc_enter_1")))
CmmReg (CmmGlobal GCFun)
- | arch == ArchPPC && not (dopt Opt_PIC dflags)
+ | arch == ArchPPC && not (gopt Opt_PIC dflags)
-> cmmExprNative referenceKind $
CmmLit (CmmLabel (mkCmmCodeLabel rtsPackageId (fsLit "__stg_gc_fun")))
diff --git a/compiler/nativeGen/PIC.hs b/compiler/nativeGen/PIC.hs
index af4bb9e9ed..4153ea9bcb 100644
--- a/compiler/nativeGen/PIC.hs
+++ b/compiler/nativeGen/PIC.hs
@@ -160,7 +160,7 @@ cmmMakePicReference dflags lbl
= CmmLit $ CmmLabel lbl
- | (dopt Opt_PIC dflags || not (dopt Opt_Static dflags)) && absoluteLabel lbl
+ | (gopt Opt_PIC dflags || not (gopt Opt_Static dflags)) && absoluteLabel lbl
= CmmMachOp (MO_Add (wordWidth dflags))
[ CmmReg (CmmGlobal PicBaseReg)
, CmmLit $ picRelative
@@ -220,7 +220,7 @@ howToAccessLabel
howToAccessLabel dflags _ OSMinGW32 _ lbl
-- Assume all symbols will be in the same PE, so just access them directly.
- | dopt Opt_Static dflags
+ | gopt Opt_Static dflags
= AccessDirectly
-- If the target symbol is in another PE we need to access it via the
@@ -256,7 +256,7 @@ howToAccessLabel dflags arch OSDarwin DataReference lbl
-- we'd need to pass the current Module all the way in to
-- this function.
| arch /= ArchX86_64
- , dopt Opt_PIC dflags && externallyVisibleCLabel lbl
+ , gopt Opt_PIC dflags && externallyVisibleCLabel lbl
= AccessViaSymbolPtr
| otherwise
@@ -306,7 +306,7 @@ howToAccessLabel dflags _ os _ _
-- if we don't dynamically link to Haskell code,
-- it actually manages to do so without messing thins up.
| osElfTarget os
- , not (dopt Opt_PIC dflags) && dopt Opt_Static dflags
+ , not (gopt Opt_PIC dflags) && gopt Opt_Static dflags
= AccessDirectly
howToAccessLabel dflags arch os DataReference lbl
@@ -320,7 +320,7 @@ howToAccessLabel dflags arch os DataReference lbl
-- via a symbol pointer (see below for an explanation why
-- PowerPC32 Linux is especially broken).
| arch == ArchPPC
- , dopt Opt_PIC dflags
+ , gopt Opt_PIC dflags
-> AccessViaSymbolPtr
| otherwise
@@ -341,12 +341,12 @@ howToAccessLabel dflags arch os DataReference lbl
howToAccessLabel dflags arch os CallReference lbl
| osElfTarget os
- , labelDynamic dflags (thisPackage dflags) lbl && not (dopt Opt_PIC dflags)
+ , labelDynamic dflags (thisPackage dflags) lbl && not (gopt Opt_PIC dflags)
= AccessDirectly
| osElfTarget os
, arch /= ArchX86
- , labelDynamic dflags (thisPackage dflags) lbl && dopt Opt_PIC dflags
+ , labelDynamic dflags (thisPackage dflags) lbl && gopt Opt_PIC dflags
= AccessViaStub
howToAccessLabel dflags _ os _ lbl
@@ -357,7 +357,7 @@ howToAccessLabel dflags _ os _ lbl
-- all other platforms
howToAccessLabel dflags _ _ _ _
- | not (dopt Opt_PIC dflags)
+ | not (gopt Opt_PIC dflags)
= AccessDirectly
| otherwise
@@ -428,12 +428,12 @@ needImportedSymbols dflags arch os
-- PowerPC Linux: -fPIC or -dynamic
| osElfTarget os
, arch == ArchPPC
- = dopt Opt_PIC dflags || not (dopt Opt_Static dflags)
+ = gopt Opt_PIC dflags || not (gopt Opt_Static dflags)
-- i386 (and others?): -dynamic but not -fPIC
| osElfTarget os
, arch /= ArchPPC_64
- = not (dopt Opt_Static dflags) && not (dopt Opt_PIC dflags)
+ = not (gopt Opt_Static dflags) && not (gopt Opt_PIC dflags)
| otherwise
= False
@@ -455,7 +455,7 @@ gotLabel
-- However, for PIC on x86, we need a small helper function.
pprGotDeclaration :: DynFlags -> Arch -> OS -> SDoc
pprGotDeclaration dflags ArchX86 OSDarwin
- | dopt Opt_PIC dflags
+ | gopt Opt_PIC dflags
= vcat [
ptext (sLit ".section __TEXT,__textcoal_nt,coalesced,no_toc"),
ptext (sLit ".weak_definition ___i686.get_pc_thunk.ax"),
@@ -475,7 +475,7 @@ pprGotDeclaration _ _ OSDarwin
pprGotDeclaration dflags arch os
| osElfTarget os
, arch /= ArchPPC_64
- , not (dopt Opt_PIC dflags)
+ , not (gopt Opt_PIC dflags)
= empty
| osElfTarget os
@@ -499,7 +499,7 @@ pprGotDeclaration _ _ _
pprImportedSymbol :: DynFlags -> Platform -> CLabel -> SDoc
pprImportedSymbol dflags platform@(Platform { platformArch = ArchPPC, platformOS = OSDarwin }) importedLbl
| Just (CodeStub, lbl) <- dynamicLinkerLabelInfo importedLbl
- = case dopt Opt_PIC dflags of
+ = case gopt Opt_PIC dflags of
False ->
vcat [
ptext (sLit ".symbol_stub"),
@@ -553,7 +553,7 @@ pprImportedSymbol dflags platform@(Platform { platformArch = ArchPPC, platformOS
pprImportedSymbol dflags platform@(Platform { platformArch = ArchX86, platformOS = OSDarwin }) importedLbl
| Just (CodeStub, lbl) <- dynamicLinkerLabelInfo importedLbl
- = case dopt Opt_PIC dflags of
+ = case gopt Opt_PIC dflags of
False ->
vcat [
ptext (sLit ".symbol_stub"),
@@ -586,7 +586,7 @@ pprImportedSymbol dflags platform@(Platform { platformArch = ArchX86, platformOS
ptext (sLit "\tjmp dyld_stub_binding_helper")
]
$+$ vcat [ ptext (sLit ".section __DATA, __la_sym_ptr")
- <> (if dopt Opt_PIC dflags then int 2 else int 3)
+ <> (if gopt Opt_PIC dflags then int 2 else int 3)
<> ptext (sLit ",lazy_symbol_pointers"),
ptext (sLit "L") <> pprCLabel platform lbl <> ptext (sLit "$lazy_ptr:"),
ptext (sLit "\t.indirect_symbol") <+> pprCLabel platform lbl,
@@ -622,7 +622,7 @@ pprImportedSymbol _ (Platform { platformOS = OSDarwin }) _
-- section.
-- The "official" GOT mechanism (label@got) isn't intended to be used
-- in position dependent code, so we have to create our own "fake GOT"
--- when not Opt_PIC && not (dopt Opt_Static dflags).
+-- when not Opt_PIC && not (gopt Opt_Static dflags).
--
-- 2) PowerPC Linux is just plain broken.
-- While it's theoretically possible to use GOT offsets larger
diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs
index 1f036aa43e..026e8933d7 100644
--- a/compiler/nativeGen/PPC/CodeGen.hs
+++ b/compiler/nativeGen/PPC/CodeGen.hs
@@ -1162,7 +1162,7 @@ genCCall' dflags gcp target dest_regs argsAndHints
genSwitch :: DynFlags -> CmmExpr -> [Maybe BlockId] -> NatM InstrBlock
genSwitch dflags expr ids
- | dopt Opt_PIC dflags
+ | gopt Opt_PIC dflags
= do
(reg,e_code) <- getSomeReg expr
tmp <- getNewRegNat II32
@@ -1196,7 +1196,7 @@ generateJumpTableForInstr :: DynFlags -> Instr
-> Maybe (NatCmmDecl CmmStatics Instr)
generateJumpTableForInstr dflags (BCTR ids (Just lbl)) =
let jumpTable
- | dopt Opt_PIC dflags = map jumpTableEntryRel ids
+ | gopt Opt_PIC dflags = map jumpTableEntryRel ids
| otherwise = map (jumpTableEntry dflags) ids
where jumpTableEntryRel Nothing
= CmmStaticLit (CmmInt 0 (wordWidth dflags))
diff --git a/compiler/nativeGen/RegAlloc/Graph/Main.hs b/compiler/nativeGen/RegAlloc/Graph/Main.hs
index 1611a710fb..57c150b6b0 100644
--- a/compiler/nativeGen/RegAlloc/Graph/Main.hs
+++ b/compiler/nativeGen/RegAlloc/Graph/Main.hs
@@ -91,9 +91,9 @@ regAlloc_spin dflags spinCount triv regsFree slotsFree debug_codeGraphs code
-- intermediate structures in the allocator - otherwise tell the
-- allocator to ditch them early so we don't end up creating space leaks.
let dump = or
- [ dopt Opt_D_dump_asm_regalloc_stages dflags
- , dopt Opt_D_dump_asm_stats dflags
- , dopt Opt_D_dump_asm_conflicts dflags ]
+ [ gopt Opt_D_dump_asm_regalloc_stages dflags
+ , gopt Opt_D_dump_asm_stats dflags
+ , gopt Opt_D_dump_asm_conflicts dflags ]
-- check that we're not running off down the garden path.
when (spinCount > maxSpinCount)
@@ -137,7 +137,7 @@ regAlloc_spin dflags spinCount triv regsFree slotsFree debug_codeGraphs code
let (graph_colored, rsSpill, rmCoalesce)
= {-# SCC "ColorGraph" #-}
Color.colorGraph
- (dopt Opt_RegsIterative dflags)
+ (gopt Opt_RegsIterative dflags)
spinCount
regsFree triv spill graph
@@ -160,7 +160,7 @@ regAlloc_spin dflags spinCount triv regsFree slotsFree debug_codeGraphs code
then do
-- if -fasm-lint is turned on then validate the graph
let graph_colored_lint =
- if dopt Opt_DoAsmLinting dflags
+ if gopt Opt_DoAsmLinting dflags
then Color.validateGraph (text "")
True -- require all nodes to be colored
graph_colored
@@ -205,7 +205,7 @@ regAlloc_spin dflags spinCount triv regsFree slotsFree debug_codeGraphs code
else do
-- if -fasm-lint is turned on then validate the graph
let graph_colored_lint =
- if dopt Opt_DoAsmLinting dflags
+ if gopt Opt_DoAsmLinting dflags
then Color.validateGraph (text "")
False -- don't require nodes to be colored
graph_colored
diff --git a/compiler/nativeGen/SPARC/CodeGen.hs b/compiler/nativeGen/SPARC/CodeGen.hs
index 9d6aeaafc9..aeb6d10acc 100644
--- a/compiler/nativeGen/SPARC/CodeGen.hs
+++ b/compiler/nativeGen/SPARC/CodeGen.hs
@@ -296,7 +296,7 @@ genCondJump bid bool = do
genSwitch :: DynFlags -> CmmExpr -> [Maybe BlockId] -> NatM InstrBlock
genSwitch dflags expr ids
- | dopt Opt_PIC dflags
+ | gopt Opt_PIC dflags
= error "MachCodeGen: sparc genSwitch PIC not finished\n"
| otherwise
diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs
index fbbc37e6c9..7ab30bf922 100644
--- a/compiler/nativeGen/X86/CodeGen.hs
+++ b/compiler/nativeGen/X86/CodeGen.hs
@@ -76,13 +76,13 @@ sse2Enabled = do
-- calling convention specifies the use of xmm regs,
-- and possibly other places.
return True
- ArchX86 -> return (dopt Opt_SSE2 dflags || dopt Opt_SSE4_2 dflags)
+ ArchX86 -> return (gopt Opt_SSE2 dflags || gopt Opt_SSE4_2 dflags)
_ -> panic "sse2Enabled: Not an X86* arch"
sse4_2Enabled :: NatM Bool
sse4_2Enabled = do
dflags <- getDynFlags
- return (dopt Opt_SSE4_2 dflags)
+ return (gopt Opt_SSE4_2 dflags)
if_sse2 :: NatM a -> NatM a -> NatM a
if_sse2 sse2 x87 = do
@@ -2291,7 +2291,7 @@ outOfLineCmmOp mop res args
genSwitch :: DynFlags -> CmmExpr -> [Maybe BlockId] -> NatM InstrBlock
genSwitch dflags expr ids
- | dopt Opt_PIC dflags
+ | gopt Opt_PIC dflags
= do
(reg,e_code) <- getSomeReg expr
lbl <- getNewLabelNat
@@ -2352,7 +2352,7 @@ createJumpTable :: DynFlags -> [Maybe BlockId] -> Section -> CLabel
-> GenCmmDecl (Alignment, CmmStatics) h g
createJumpTable dflags ids section lbl
= let jumpTable
- | dopt Opt_PIC dflags =
+ | gopt Opt_PIC dflags =
let jumpTableEntryRel Nothing
= CmmStaticLit (CmmInt 0 (wordWidth dflags))
jumpTableEntryRel (Just blockid)