summaryrefslogtreecommitdiff
path: root/compiler/main
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/main')
-rw-r--r--compiler/main/CodeOutput.lhs2
-rw-r--r--compiler/main/DriverMkDepend.hs2
-rw-r--r--compiler/main/DriverPipeline.hs58
-rw-r--r--compiler/main/DynFlags.hs50
-rw-r--r--compiler/main/ErrUtils.lhs8
-rw-r--r--compiler/main/Finder.lhs2
-rw-r--r--compiler/main/GHC.hs2
-rw-r--r--compiler/main/GhcMake.hs8
-rw-r--r--compiler/main/HeaderInfo.hs2
-rw-r--r--compiler/main/HscMain.hs8
-rw-r--r--compiler/main/HscTypes.lhs2
-rw-r--r--compiler/main/InteractiveEval.hs10
-rw-r--r--compiler/main/Packages.lhs12
-rw-r--r--compiler/main/SysTools.lhs12
-rw-r--r--compiler/main/TidyPgm.lhs8
15 files changed, 93 insertions, 93 deletions
diff --git a/compiler/main/CodeOutput.lhs b/compiler/main/CodeOutput.lhs
index fc20ef4988..beaf7c8eec 100644
--- a/compiler/main/CodeOutput.lhs
+++ b/compiler/main/CodeOutput.lhs
@@ -56,7 +56,7 @@ codeOutput dflags this_mod location foreign_stubs pkg_deps cmm_stream
do {
-- Lint each CmmGroup as it goes past
; let linted_cmm_stream =
- if dopt Opt_DoCmmLinting dflags
+ if gopt Opt_DoCmmLinting dflags
then Stream.mapM do_lint cmm_stream
else cmm_stream
diff --git a/compiler/main/DriverMkDepend.hs b/compiler/main/DriverMkDepend.hs
index 953b2c4568..fecf28362a 100644
--- a/compiler/main/DriverMkDepend.hs
+++ b/compiler/main/DriverMkDepend.hs
@@ -335,7 +335,7 @@ endMkDependHS dflags
dumpModCycles :: DynFlags -> [ModSummary] -> IO ()
dumpModCycles dflags mod_summaries
- | not (dopt Opt_D_dump_mod_cycles dflags)
+ | not (gopt Opt_D_dump_mod_cycles dflags)
= return ()
| null cycles
diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs
index d7b80e62fb..2326e57403 100644
--- a/compiler/main/DriverPipeline.hs
+++ b/compiler/main/DriverPipeline.hs
@@ -155,7 +155,7 @@ compile' (nothingCompiler, interactiveCompiler, batchCompiler)
let hsc_env' = hsc_env { hsc_dflags = dflags' }
-- -fforce-recomp should also work with --make
- let force_recomp = dopt Opt_ForceRecomp dflags
+ let force_recomp = gopt Opt_ForceRecomp dflags
source_modified
| force_recomp || isNothing maybe_old_linkable = SourceModified
| otherwise = source_modified0
@@ -320,7 +320,7 @@ link' dflags batch_attempt_linking hpt
linking_needed <- linkingNeeded dflags linkables pkg_deps
- if not (dopt Opt_ForceRecomp dflags) && not linking_needed
+ if not (gopt Opt_ForceRecomp dflags) && not linking_needed
then do debugTraceMsg dflags 2 (text exe_file <+> ptext (sLit "is up to date, linking not required."))
return Succeeded
else do
@@ -410,7 +410,7 @@ ghcLinkInfoSectionName = ".debug-ghc-link-info"
findHSLib :: DynFlags -> [String] -> String -> IO (Maybe FilePath)
findHSLib dflags dirs lib = do
- let batch_lib_file = if dopt Opt_Static dflags
+ let batch_lib_file = if gopt Opt_Static dflags
then "lib" ++ lib <.> "a"
else mkSOName (targetPlatform dflags) lib
found <- filterM doesFileExist (map (</> batch_lib_file) dirs)
@@ -434,7 +434,7 @@ compileFile hsc_env stop_phase (src, mb_phase) = do
let
dflags = hsc_dflags hsc_env
- split = dopt Opt_SplitObjs dflags
+ split = gopt Opt_SplitObjs dflags
mb_o_file = outputFile dflags
ghc_link = ghcLink dflags -- Set by -c or -no-link
@@ -675,9 +675,9 @@ getOutputFilename stop_phase output basename
hcsuf = hcSuf dflags
odir = objectDir dflags
osuf = objectSuf dflags
- keep_hc = dopt Opt_KeepHcFiles dflags
- keep_s = dopt Opt_KeepSFiles dflags
- keep_bc = dopt Opt_KeepLlvmFiles dflags
+ keep_hc = gopt Opt_KeepHcFiles dflags
+ keep_s = gopt Opt_KeepSFiles dflags
+ keep_bc = gopt Opt_KeepLlvmFiles dflags
myPhaseInputExt HCc = hcsuf
myPhaseInputExt MergeStub = osuf
@@ -778,7 +778,7 @@ runPhase (Cpp sf) input_fn dflags0
if not (xopt Opt_Cpp dflags1) then do
-- we have to be careful to emit warnings only once.
- unless (dopt Opt_Pp dflags1) $ io $ handleFlagWarnings dflags1 warns
+ unless (gopt Opt_Pp dflags1) $ io $ handleFlagWarnings dflags1 warns
-- no need to preprocess CPP, just pass input file along
-- to the next phase of the pipeline.
@@ -792,7 +792,7 @@ runPhase (Cpp sf) input_fn dflags0
(dflags2, unhandled_flags, warns)
<- io $ parseDynamicFilePragma dflags0 src_opts
io $ checkProcessArgsResult dflags2 unhandled_flags
- unless (dopt Opt_Pp dflags2) $ io $ handleFlagWarnings dflags2 warns
+ unless (gopt Opt_Pp dflags2) $ io $ handleFlagWarnings dflags2 warns
-- the HsPp pass below will emit warnings
setDynFlags dflags2
@@ -804,7 +804,7 @@ runPhase (Cpp sf) input_fn dflags0
runPhase (HsPp sf) input_fn dflags
= do
- if not (dopt Opt_Pp dflags) then
+ if not (gopt Opt_Pp dflags) then
-- no need to preprocess, just pass input file along
-- to the next phase of the pipeline.
return (Hsc sf, input_fn)
@@ -1054,7 +1054,7 @@ runPhase cc_phase input_fn dflags
_ ->
return []
- let split_objs = dopt Opt_SplitObjs dflags
+ let split_objs = gopt Opt_SplitObjs dflags
split_opt | hcc && split_objs = [ "-DUSE_SPLIT_MARKERS" ]
| otherwise = [ ]
@@ -1072,7 +1072,7 @@ runPhase cc_phase input_fn dflags
-- By default, we turn this off with -ffloat-store unless
-- the user specified -fexcess-precision.
(if platformArch platform == ArchX86 &&
- not (dopt Opt_ExcessPrecision dflags)
+ not (gopt Opt_ExcessPrecision dflags)
then [ "-ffloat-store" ]
else []) ++
@@ -1324,7 +1324,7 @@ runPhase LlvmOpt input_fn dflags
then [SysTools.Option (llvmOpts !! opt_lvl)]
else []
tbaa | ver < 29 = "" -- no tbaa in 2.8 and earlier
- | dopt Opt_LlvmTBAA dflags = "--enable-tbaa=true"
+ | gopt Opt_LlvmTBAA dflags = "--enable-tbaa=true"
| otherwise = "--enable-tbaa=false"
@@ -1353,17 +1353,17 @@ runPhase LlvmLlc input_fn dflags
let lc_opts = getOpts dflags opt_lc
opt_lvl = max 0 (min 2 $ optLevel dflags)
- rmodel | dopt Opt_PIC dflags = "pic"
- | not (dopt Opt_Static dflags) = "dynamic-no-pic"
+ rmodel | gopt Opt_PIC dflags = "pic"
+ | not (gopt Opt_Static dflags) = "dynamic-no-pic"
| otherwise = "static"
tbaa | ver < 29 = "" -- no tbaa in 2.8 and earlier
- | dopt Opt_LlvmTBAA dflags = "--enable-tbaa=true"
+ | gopt Opt_LlvmTBAA dflags = "--enable-tbaa=true"
| otherwise = "--enable-tbaa=false"
-- hidden debugging flag '-dno-llvm-mangler' to skip mangling
- let next_phase = case dopt Opt_NoLlvmMangler dflags of
+ let next_phase = case gopt Opt_NoLlvmMangler dflags of
False -> LlvmMangle
- True | dopt Opt_SplitObjs dflags -> Splitter
+ True | gopt Opt_SplitObjs dflags -> Splitter
True -> As
output_fn <- phaseOutputFilename next_phase
@@ -1407,7 +1407,7 @@ runPhase LlvmLlc input_fn dflags
runPhase LlvmMangle input_fn dflags
= do
- let next_phase = if dopt Opt_SplitObjs dflags then Splitter else As
+ let next_phase = if gopt Opt_SplitObjs dflags then Splitter else As
output_fn <- phaseOutputFilename next_phase
io $ llvmFixupAsm dflags input_fn output_fn
return (next_phase, output_fn)
@@ -1449,7 +1449,7 @@ maybeMergeStub
runPhase_MoveBinary :: DynFlags -> FilePath -> IO Bool
runPhase_MoveBinary dflags input_fn
- | WayPar `elem` ways dflags && not (dopt Opt_Static dflags) =
+ | WayPar `elem` ways dflags && not (gopt Opt_Static dflags) =
panic ("Don't know how to combine PVM wrapper and dynamic wrapper")
| WayPar `elem` ways dflags = do
let sysMan = pgm_sysman dflags
@@ -1490,7 +1490,7 @@ mkExtraObj dflags extn xs
--
mkExtraObjToLinkIntoBinary :: DynFlags -> IO FilePath
mkExtraObjToLinkIntoBinary dflags = do
- when (dopt Opt_NoHsMain dflags && haveRtsOptsFlags dflags) $ do
+ when (gopt Opt_NoHsMain dflags && haveRtsOptsFlags dflags) $ do
log_action dflags dflags SevInfo noSrcSpan defaultUserStyle
(text "Warning: -rtsopts and -with-rtsopts have no effect with -no-hs-main." $$
text " Call hs_init_ghc() from your main() function to set these options.")
@@ -1499,7 +1499,7 @@ mkExtraObjToLinkIntoBinary dflags = do
where
main
- | dopt Opt_NoHsMain dflags = empty
+ | gopt Opt_NoHsMain dflags = empty
| otherwise = vcat [
ptext (sLit "#include \"Rts.h\""),
ptext (sLit "extern StgClosure ZCMain_main_closure;"),
@@ -1564,7 +1564,7 @@ getLinkInfo dflags dep_packages = do
pkg_frameworks,
rtsOpts dflags,
rtsOptsEnabled dflags,
- dopt Opt_NoHsMain dflags,
+ gopt Opt_NoHsMain dflags,
extra_ld_inputs,
getOpts dflags opt_l)
--
@@ -1673,12 +1673,12 @@ linkBinary dflags o_files dep_packages = do
get_pkg_lib_path_opts l
| osElfTarget (platformOS platform) &&
dynLibLoader dflags == SystemDependent &&
- not (dopt Opt_Static dflags)
- = let libpath = if dopt Opt_RelativeDynlibPaths dflags
+ not (gopt Opt_Static dflags)
+ = let libpath = if gopt Opt_RelativeDynlibPaths dflags
then "$ORIGIN" </>
(l `makeRelativeTo` full_output_fn)
else l
- rpath = if dopt Opt_RPath dflags
+ rpath = if gopt Opt_RPath dflags
then ["-Wl,-rpath", "-Wl," ++ libpath]
else []
in ["-L" ++ l, "-Wl,-rpath-link", "-Wl," ++ l] ++ rpath
@@ -1835,7 +1835,7 @@ maybeCreateManifest
-> IO [FilePath] -- extra objects to embed, maybe
maybeCreateManifest dflags exe_filename
| platformOS (targetPlatform dflags) == OSMinGW32 &&
- dopt Opt_GenManifest dflags
+ gopt Opt_GenManifest dflags
= do let manifest_filename = exe_filename <.> "manifest"
writeFile manifest_filename $
@@ -1858,7 +1858,7 @@ maybeCreateManifest dflags exe_filename
-- foo.exe.manifest. However, for extra robustness, and so that
-- we can move the binary around, we can embed the manifest in
-- the binary itself using windres:
- if not (dopt Opt_EmbedManifest dflags) then return [] else do
+ if not (gopt Opt_EmbedManifest dflags) then return [] else do
rc_filename <- newTempName dflags "rc"
rc_obj_filename <- newTempName dflags (objectSuf dflags)
@@ -1994,7 +1994,7 @@ hscPostBackendPhase _ HsBootFile _ = StopLn
hscPostBackendPhase dflags _ hsc_lang =
case hsc_lang of
HscC -> HCc
- HscAsm | dopt Opt_SplitObjs dflags -> Splitter
+ HscAsm | gopt Opt_SplitObjs dflags -> Splitter
| otherwise -> As
HscLlvm -> LlvmOpt
HscNothing -> StopLn
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 0a8c8c6719..bcc6358a76 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -21,9 +21,9 @@ module DynFlags (
FatalMessager, LogAction, FlushOut(..), FlushErr(..),
ProfAuto(..),
glasgowExtsFlags,
- dopt,
- dopt_set,
- dopt_unset,
+ gopt,
+ gopt_set,
+ gopt_unset,
wopt,
wopt_set,
wopt_unset,
@@ -1355,16 +1355,16 @@ languageExtensions (Just Haskell2010)
Opt_RelaxedPolyRec]
-- | Test whether a 'GeneralFlag' is set
-dopt :: GeneralFlag -> DynFlags -> Bool
-dopt f dflags = fromEnum f `IntSet.member` flags dflags
+gopt :: GeneralFlag -> DynFlags -> Bool
+gopt f dflags = fromEnum f `IntSet.member` flags dflags
-- | Set a 'GeneralFlag'
-dopt_set :: DynFlags -> GeneralFlag -> DynFlags
-dopt_set dfs f = dfs{ flags = IntSet.insert (fromEnum f) (flags dfs) }
+gopt_set :: DynFlags -> GeneralFlag -> DynFlags
+gopt_set dfs f = dfs{ flags = IntSet.insert (fromEnum f) (flags dfs) }
-- | Unset a 'GeneralFlag'
-dopt_unset :: DynFlags -> GeneralFlag -> DynFlags
-dopt_unset dfs f = dfs{ flags = IntSet.delete (fromEnum f) (flags dfs) }
+gopt_unset :: DynFlags -> GeneralFlag -> DynFlags
+gopt_unset dfs f = dfs{ flags = IntSet.delete (fromEnum f) (flags dfs) }
-- | Test whether a 'WarningFlag' is set
wopt :: WarningFlag -> DynFlags -> Bool
@@ -1413,7 +1413,7 @@ dynFlagDependencies = pluginModNames
-- | Is the -fpackage-trust mode on
packageTrustOn :: DynFlags -> Bool
-packageTrustOn = dopt Opt_PackageTrust
+packageTrustOn = gopt Opt_PackageTrust
-- | Is Safe Haskell on in some way (including inference mode)
safeHaskellOn :: DynFlags -> Bool
@@ -1604,11 +1604,11 @@ updOptLevel n dfs
= dfs2{ optLevel = final_n }
where
final_n = max 0 (min 2 n) -- Clamp to 0 <= n <= 2
- dfs1 = foldr (flip dopt_unset) dfs remove_dopts
- dfs2 = foldr (flip dopt_set) dfs1 extra_dopts
+ dfs1 = foldr (flip gopt_unset) dfs remove_gopts
+ dfs2 = foldr (flip gopt_set) dfs1 extra_gopts
- extra_dopts = [ f | (ns,f) <- optLevelFlags, final_n `elem` ns ]
- remove_dopts = [ f | (ns,f) <- optLevelFlags, final_n `notElem` ns ]
+ extra_gopts = [ f | (ns,f) <- optLevelFlags, final_n `elem` ns ]
+ remove_gopts = [ f | (ns,f) <- optLevelFlags, final_n `notElem` ns ]
-- -----------------------------------------------------------------------------
-- StgToDo: abstraction of stg-to-stg passes to run.
@@ -1623,7 +1623,7 @@ getStgToDo :: DynFlags -> [StgToDo]
getStgToDo dflags
= todo2
where
- stg_stats = dopt Opt_StgStats dflags
+ stg_stats = gopt Opt_StgStats dflags
todo1 = if stg_stats then [D_stg_stats] else []
@@ -1728,7 +1728,7 @@ safeFlagCheck cmdl dflags =
-- throw error if -fpackage-trust by itself with no safe haskell flag
False | not cmdl && packageTrustOn dflags
- -> (dopt_unset dflags' Opt_PackageTrust,
+ -> (gopt_unset dflags' Opt_PackageTrust,
[L (pkgTrustOnLoc dflags') $
"-fpackage-trust ignored;" ++
" must be specified with a Safe Haskell flag"]
@@ -2823,8 +2823,8 @@ removeWay w = upd (\dfs -> dfs { ways = filter (w /=) (ways dfs) })
--------------------------
setGeneralFlag, unSetGeneralFlag :: GeneralFlag -> DynP ()
-setGeneralFlag f = upd (\dfs -> dopt_set dfs f)
-unSetGeneralFlag f = upd (\dfs -> dopt_unset dfs f)
+setGeneralFlag f = upd (\dfs -> gopt_set dfs f)
+unSetGeneralFlag f = upd (\dfs -> gopt_unset dfs f)
--------------------------
setWarningFlag, unSetWarningFlag :: WarningFlag -> DynP ()
@@ -3115,10 +3115,10 @@ picCCOpts dflags
-- Don't generate "common" symbols - these are unwanted
-- in dynamic libraries.
- | dopt Opt_PIC dflags -> ["-fno-common", "-U __PIC__", "-D__PIC__"]
+ | gopt Opt_PIC dflags -> ["-fno-common", "-U __PIC__", "-D__PIC__"]
| otherwise -> ["-mdynamic-no-pic"]
OSMinGW32 -- no -fPIC for Windows
- | dopt Opt_PIC dflags -> ["-U __PIC__", "-D__PIC__"]
+ | gopt Opt_PIC dflags -> ["-U __PIC__", "-D__PIC__"]
| otherwise -> []
_
-- we need -fPIC for C files when we are compiling with -dynamic,
@@ -3126,13 +3126,13 @@ picCCOpts dflags
-- correctly. They need to reference data in the Haskell
-- objects, but can't without -fPIC. See
-- http://hackage.haskell.org/trac/ghc/wiki/Commentary/PositionIndependentCode
- | dopt Opt_PIC dflags || not (dopt Opt_Static dflags) ->
+ | gopt Opt_PIC dflags || not (gopt Opt_Static dflags) ->
["-fPIC", "-U __PIC__", "-D__PIC__"]
| otherwise -> []
picPOpts :: DynFlags -> [String]
picPOpts dflags
- | dopt Opt_PIC dflags = ["-U __PIC__", "-D__PIC__"]
+ | gopt Opt_PIC dflags = ["-U __PIC__", "-D__PIC__"]
| otherwise = []
-- -----------------------------------------------------------------------------
@@ -3232,7 +3232,7 @@ makeDynFlagsConsistent dflags
in loop dflags' warn
| hscTarget dflags == HscLlvm &&
not ((arch == ArchX86_64) && (os == OSLinux || os == OSDarwin)) &&
- (not (dopt Opt_Static dflags) || dopt Opt_PIC dflags)
+ (not (gopt Opt_Static dflags) || gopt Opt_PIC dflags)
= if cGhcWithNativeCodeGen == "YES"
then let dflags' = dflags { hscTarget = HscAsm }
warn = "Using native code generator rather than LLVM, as LLVM is incompatible with -fPIC and -dynamic on this platform"
@@ -3240,8 +3240,8 @@ makeDynFlagsConsistent dflags
else ghcError $ CmdLineError "Can't use -fPIC or -dynamic on this platform"
| os == OSDarwin &&
arch == ArchX86_64 &&
- not (dopt Opt_PIC dflags)
- = loop (dopt_set dflags Opt_PIC)
+ not (gopt Opt_PIC dflags)
+ = loop (gopt_set dflags Opt_PIC)
"Enabling -fPIC as it is always on for this platform"
| otherwise = (dflags, [])
where loc = mkGeneralSrcSpan (fsLit "when making flags consistent")
diff --git a/compiler/main/ErrUtils.lhs b/compiler/main/ErrUtils.lhs
index 1404782939..b13cded064 100644
--- a/compiler/main/ErrUtils.lhs
+++ b/compiler/main/ErrUtils.lhs
@@ -93,7 +93,7 @@ mkLocMessage :: Severity -> SrcSpan -> MsgDoc -> MsgDoc
-- would look strange. Better to say explicitly "<no location info>".
mkLocMessage severity locn msg
= sdocWithDynFlags $ \dflags ->
- let locn' = if dopt Opt_ErrorSpans dflags
+ let locn' = if gopt Opt_ErrorSpans dflags
then ppr locn
else ppr (srcSpanStart locn)
in hang (locn' <> colon <+> sev_info) 4 msg
@@ -194,7 +194,7 @@ doIfSet flag action | flag = action
| otherwise = return ()
doIfSet_dyn :: DynFlags -> GeneralFlag -> IO () -> IO()
-doIfSet_dyn dflags flag action | dopt flag dflags = action
+doIfSet_dyn dflags flag action | gopt flag dflags = action
| otherwise = return ()
-- -----------------------------------------------------------------------------
@@ -207,7 +207,7 @@ dumpIfSet dflags flag hdr doc
dumpIfSet_dyn :: DynFlags -> GeneralFlag -> String -> SDoc -> IO ()
dumpIfSet_dyn dflags flag hdr doc
- | dopt flag dflags || verbosity dflags >= 4
+ | gopt flag dflags || verbosity dflags >= 4
= dumpSDoc dflags flag hdr doc
| otherwise
= return ()
@@ -264,7 +264,7 @@ dumpSDoc dflags flag hdr doc
chooseDumpFile :: DynFlags -> GeneralFlag -> Maybe String
chooseDumpFile dflags flag
- | dopt Opt_DumpToFile dflags
+ | gopt Opt_DumpToFile dflags
, Just prefix <- getPrefix
= Just $ setDir (prefix ++ (beautifyDumpName flag))
diff --git a/compiler/main/Finder.lhs b/compiler/main/Finder.lhs
index 1417dad061..f674b19183 100644
--- a/compiler/main/Finder.lhs
+++ b/compiler/main/Finder.lhs
@@ -612,7 +612,7 @@ cantFindErr cannot_find _ dflags mod_name find_result
ptext (sLit "It is a member of the hidden package") <+> quotes (ppr pkg)
<> dot $$ cabal_pkg_hidden_hint pkg
cabal_pkg_hidden_hint pkg
- | dopt Opt_BuildingCabalPackage dflags
+ | gopt Opt_BuildingCabalPackage dflags
= case simpleParse (packageIdString pkg) of
Just pid ->
ptext (sLit "Perhaps you need to add") <+>
diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs
index d41d9c9b78..2af8c6f608 100644
--- a/compiler/main/GHC.hs
+++ b/compiler/main/GHC.hs
@@ -22,7 +22,7 @@ module GHC (
needsTemplateHaskell,
-- * Flags and settings
- DynFlags(..), GeneralFlag(..), Severity(..), HscTarget(..), dopt,
+ DynFlags(..), GeneralFlag(..), Severity(..), HscTarget(..), gopt,
GhcMode(..), GhcLink(..), defaultObjectTarget,
parseDynamicFlags,
getSessionDynFlags, setSessionDynFlags,
diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs
index 6dd27029f1..62ac63fc1d 100644
--- a/compiler/main/GhcMake.hs
+++ b/compiler/main/GhcMake.hs
@@ -283,7 +283,7 @@ load how_much = do
-- that main() is going to come from somewhere else.
--
let ofile = outputFile dflags
- let no_hs_main = dopt Opt_NoHsMain dflags
+ let no_hs_main = gopt Opt_NoHsMain dflags
let
main_mod = mainModIs dflags
a_root_is_Main = any ((==main_mod).ms_mod) mod_graph
@@ -562,7 +562,7 @@ checkStability hpt sccs all_home_mods = foldl checkSCC ([],[]) sccs
&& all bco_ok scc
object_ok ms
- | dopt Opt_ForceRecomp (ms_hspp_opts ms) = False
+ | gopt Opt_ForceRecomp (ms_hspp_opts ms) = False
| Just t <- ms_obj_date ms = t >= ms_hs_date ms
&& same_as_prev t
| otherwise = False
@@ -582,7 +582,7 @@ checkStability hpt sccs all_home_mods = foldl checkSCC ([],[]) sccs
-- a problem.
bco_ok ms
- | dopt Opt_ForceRecomp (ms_hspp_opts ms) = False
+ | gopt Opt_ForceRecomp (ms_hspp_opts ms) = False
| otherwise = case lookupUFM hpt (ms_mod_name ms) of
Just hmi | Just l <- hm_linkable hmi ->
not (isObjectLinkable l) &&
@@ -1414,7 +1414,7 @@ preprocessFile hsc_env src_fn mb_phase (Just (buf, _time))
| Nothing <- mb_phase, Unlit _ <- startPhase src_fn = True
-- note: local_opts is only required if there's no Unlit phase
| xopt Opt_Cpp dflags' = True
- | dopt Opt_Pp dflags' = True
+ | gopt Opt_Pp dflags' = True
| otherwise = False
when needs_preprocessing $
diff --git a/compiler/main/HeaderInfo.hs b/compiler/main/HeaderInfo.hs
index 91902d6b77..f7ae35ff55 100644
--- a/compiler/main/HeaderInfo.hs
+++ b/compiler/main/HeaderInfo.hs
@@ -152,7 +152,7 @@ getOptionsFromFile dflags filename
-- we already have an apparently-complete token.
-- We therefore just turn Opt_Haddock off when doing the lazy
-- lex.
- dflags' = dopt_unset dflags Opt_Haddock
+ dflags' = gopt_unset dflags Opt_Haddock
blockSize :: Int
-- blockSize = 17 -- for testing :-)
diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs
index 62a472037b..d9949db1e4 100644
--- a/compiler/main/HscMain.hs
+++ b/compiler/main/HscMain.hs
@@ -1400,7 +1400,7 @@ tryNewCodeGen hsc_env this_mod data_tycons
-- we generate one SRT for the whole module.
let
pipeline_stream
- | dopt Opt_SplitObjs dflags
+ | gopt Opt_SplitObjs dflags
= {-# SCC "cmmPipeline" #-}
let run_pipeline us cmmgroup = do
let (topSRT', us') = initUs us emptySRT
@@ -1733,7 +1733,7 @@ hscCompileCoreExpr hsc_env srcspan ds_expr
| otherwise = do
let dflags = hsc_dflags hsc_env
- let lint_on = dopt Opt_DoCoreLinting dflags
+ let lint_on = gopt Opt_DoCoreLinting dflags
{- Simplify it -}
simpl_expr <- simplifyExpr dflags ds_expr
@@ -1779,8 +1779,8 @@ dumpIfaceStats hsc_env = do
(ifaceStats eps)
where
dflags = hsc_dflags hsc_env
- dump_rn_stats = dopt Opt_D_dump_rn_stats dflags
- dump_if_trace = dopt Opt_D_dump_if_trace dflags
+ dump_rn_stats = gopt Opt_D_dump_rn_stats dflags
+ dump_if_trace = gopt Opt_D_dump_if_trace dflags
{- **********************************************************************
diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs
index a56bcabea8..937d09a313 100644
--- a/compiler/main/HscTypes.lhs
+++ b/compiler/main/HscTypes.lhs
@@ -235,7 +235,7 @@ instance Exception GhcApiError
-- -Werror is enabled, or print them out otherwise.
printOrThrowWarnings :: DynFlags -> Bag WarnMsg -> IO ()
printOrThrowWarnings dflags warns
- | dopt Opt_WarnIsError dflags
+ | gopt Opt_WarnIsError dflags
= when (not (isEmptyBag warns)) $ do
throwIO $ mkSrcErr $ warns `snocBag` warnIsErrorMsg dflags
| otherwise
diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs
index 806f8356e6..3f184d6278 100644
--- a/compiler/main/InteractiveEval.hs
+++ b/compiler/main/InteractiveEval.hs
@@ -380,7 +380,7 @@ sandboxIO :: DynFlags -> MVar Status -> IO [HValue] -> IO Status
sandboxIO dflags statusMVar thing =
mask $ \restore -> -- fork starts blocked
let runIt = liftM Complete $ try (restore $ rethrow dflags thing)
- in if dopt Opt_GhciSandbox dflags
+ in if gopt Opt_GhciSandbox dflags
then do tid <- forkIO $ do res <- runIt
putMVar statusMVar res -- empty: can't block
withInterruptsSentTo tid $ takeMVar statusMVar
@@ -403,8 +403,8 @@ rethrow :: DynFlags -> IO a -> IO a
rethrow dflags io = Exception.catch io $ \se -> do
-- If -fbreak-on-error, we break unconditionally,
-- but with care of not breaking twice
- if dopt Opt_BreakOnError dflags &&
- not (dopt Opt_BreakOnException dflags)
+ if gopt Opt_BreakOnError dflags &&
+ not (gopt Opt_BreakOnException dflags)
then poke exceptionFlag 1
else case fromException se of
-- If it is a "UserInterrupt" exception, we allow
@@ -433,7 +433,7 @@ withBreakAction step dflags breakMVar statusMVar act
setBreakAction = do
stablePtr <- newStablePtr onBreak
poke breakPointIOAction stablePtr
- when (dopt Opt_BreakOnException dflags) $ poke exceptionFlag 1
+ when (gopt Opt_BreakOnException dflags) $ poke exceptionFlag 1
when step $ setStepFlag
return stablePtr
-- Breaking on exceptions is not enabled by default, since it
@@ -706,7 +706,7 @@ rttiEnvironment hsc_env@HscEnv{hsc_IC=ic} = do
++ "improvement for a type")) hsc_env
Just subst -> do
let dflags = hsc_dflags hsc_env
- when (dopt Opt_D_dump_rtti dflags) $
+ when (gopt Opt_D_dump_rtti dflags) $
printInfoForUser dflags alwaysQualify $
fsep [text "RTTI Improvement for", ppr id, equals, ppr subst]
diff --git a/compiler/main/Packages.lhs b/compiler/main/Packages.lhs
index 8a3f6f40fe..9204763ebf 100644
--- a/compiler/main/Packages.lhs
+++ b/compiler/main/Packages.lhs
@@ -252,11 +252,11 @@ setBatchPackageFlags :: DynFlags -> [PackageConfig] -> [PackageConfig]
setBatchPackageFlags dflags pkgs = (maybeDistrustAll . maybeHideAll) pkgs
where
maybeHideAll pkgs'
- | dopt Opt_HideAllPackages dflags = map hide pkgs'
+ | gopt Opt_HideAllPackages dflags = map hide pkgs'
| otherwise = pkgs'
maybeDistrustAll pkgs'
- | dopt Opt_DistrustAllPackages dflags = map distrust pkgs'
+ | gopt Opt_DistrustAllPackages dflags = map distrust pkgs'
| otherwise = pkgs'
hide pkg = pkg{ exposed = False }
@@ -792,7 +792,7 @@ mkPackageState dflags pkgs0 preload0 this_package = do
let
-- add base & rts to the preload packages
basicLinkedPackages
- | dopt Opt_AutoLinkPackages dflags
+ | gopt Opt_AutoLinkPackages dflags
= filter (flip elemUFM pkg_db) [basePackageId, rtsPackageId]
| otherwise = []
-- but in any case remove the current package from the set of
@@ -895,7 +895,7 @@ packageHsLibs dflags p = map (mkDynName . addSuffix) (hsLibraries p)
tag = mkBuildTag (filter (not . wayRTSOnly) ways2)
rts_tag = mkBuildTag ways2
- mkDynName | dopt Opt_Static dflags = id
+ mkDynName | gopt Opt_Static dflags = id
| otherwise = (++ ("-ghc" ++ cProjectVersion))
addSuffix rts@"HSrts" = rts ++ (expandTag rts_tag)
@@ -947,7 +947,7 @@ lookupModuleWithSuggestions dflags m
where
pkg_state = pkgState dflags
suggestions
- | dopt Opt_HelpfulErrors dflags = fuzzyLookup (moduleNameString m) all_mods
+ | gopt Opt_HelpfulErrors dflags = fuzzyLookup (moduleNameString m) all_mods
| otherwise = []
all_mods :: [(String, Module)] -- All modules
@@ -1035,7 +1035,7 @@ isDllName :: DynFlags -> PackageId -> Name -> Bool
-- the synbol comes from another dynamically-linked package,
-- and applies on all platforms, not just Windows
isDllName dflags this_pkg name
- | dopt Opt_Static dflags = False
+ | gopt Opt_Static dflags = False
| Just mod <- nameModule_maybe name = modulePackageId mod /= this_pkg
| otherwise = False -- no, it is not even an external name
diff --git a/compiler/main/SysTools.lhs b/compiler/main/SysTools.lhs
index eeebe694ac..877bd6b4b4 100644
--- a/compiler/main/SysTools.lhs
+++ b/compiler/main/SysTools.lhs
@@ -375,7 +375,7 @@ runCpp :: DynFlags -> [Option] -> IO ()
runCpp dflags args = do
let (p,args0) = pgm_P dflags
args1 = args0 ++ args
- args2 = if dopt Opt_WarnIsError dflags
+ args2 = if gopt Opt_WarnIsError dflags
then Option "-Werror" : args1
else args1
mb_env <- getGccEnv args2
@@ -676,7 +676,7 @@ readElfSection _dflags section exe = do
\begin{code}
cleanTempDirs :: DynFlags -> IO ()
cleanTempDirs dflags
- = unless (dopt Opt_KeepTmpFiles dflags)
+ = unless (gopt Opt_KeepTmpFiles dflags)
$ do let ref = dirsToClean dflags
ds <- readIORef ref
removeTmpDirs dflags (Map.elems ds)
@@ -684,7 +684,7 @@ cleanTempDirs dflags
cleanTempFiles :: DynFlags -> IO ()
cleanTempFiles dflags
- = unless (dopt Opt_KeepTmpFiles dflags)
+ = unless (gopt Opt_KeepTmpFiles dflags)
$ do let ref = filesToClean dflags
fs <- readIORef ref
removeTmpFiles dflags fs
@@ -692,7 +692,7 @@ cleanTempFiles dflags
cleanTempFilesExcept :: DynFlags -> [FilePath] -> IO ()
cleanTempFilesExcept dflags dont_delete
- = unless (dopt Opt_KeepTmpFiles dflags)
+ = unless (gopt Opt_KeepTmpFiles dflags)
$ do let ref = filesToClean dflags
files <- readIORef ref
let (to_keep, to_delete) = partition (`elem` dont_delete) files
@@ -1053,7 +1053,7 @@ linkDynLib dflags o_files dep_packages
get_pkg_lib_path_opts l
| osElfTarget (platformOS (targetPlatform dflags)) &&
dynLibLoader dflags == SystemDependent &&
- not (dopt Opt_Static dflags)
+ not (gopt Opt_Static dflags)
= ["-L" ++ l, "-Wl,-rpath", "-Wl," ++ l]
| otherwise = ["-L" ++ l]
@@ -1097,7 +1097,7 @@ linkDynLib dflags o_files dep_packages
, Option "-shared"
] ++
[ FileOption "-Wl,--out-implib=" (output_fn ++ ".a")
- | dopt Opt_SharedImplib dflags
+ | gopt Opt_SharedImplib dflags
]
++ map (FileOption "") o_files
++ map Option (
diff --git a/compiler/main/TidyPgm.lhs b/compiler/main/TidyPgm.lhs
index ebb8f4889a..e2010645b2 100644
--- a/compiler/main/TidyPgm.lhs
+++ b/compiler/main/TidyPgm.lhs
@@ -307,8 +307,8 @@ tidyProgram hsc_env (ModGuts { mg_module = mod
})
= do { let { dflags = hsc_dflags hsc_env
- ; omit_prags = dopt Opt_OmitInterfacePragmas dflags
- ; expose_all = dopt Opt_ExposeAllUnfoldings dflags
+ ; omit_prags = gopt Opt_OmitInterfacePragmas dflags
+ ; expose_all = gopt Opt_ExposeAllUnfoldings dflags
; th = xopt Opt_TemplateHaskell dflags
; data_kinds = xopt Opt_DataKinds dflags
; no_trim_types = th || data_kinds
@@ -373,14 +373,14 @@ tidyProgram hsc_env (ModGuts { mg_module = mod
-- If the endPass didn't print the rules, but ddump-rules is
-- on, print now
- ; unless (dopt Opt_D_dump_simpl dflags) $
+ ; unless (gopt Opt_D_dump_simpl dflags) $
Err.dumpIfSet_dyn dflags Opt_D_dump_rules
(showSDoc dflags (ppr CoreTidy <+> ptext (sLit "rules")))
(pprRulesForUser tidy_rules)
-- Print one-line size info
; let cs = coreBindsStats tidy_binds
- ; when (dopt Opt_D_dump_core_stats dflags)
+ ; when (gopt Opt_D_dump_core_stats dflags)
(log_action dflags dflags SevDump noSrcSpan defaultDumpStyle
(ptext (sLit "Tidy size (terms,types,coercions)")
<+> ppr (moduleName mod) <> colon