never executed always true always false
    1 {-# LANGUAGE CPP #-}
    2 {-# LANGUAGE FlexibleInstances #-}
    3 {-# LANGUAGE RankNTypes #-}
    4 
    5 -------------------------------------------------------------------------------
    6 --
    7 -- | Dynamic flags
    8 --
    9 -- Most flags are dynamic flags, which means they can change from compilation
   10 -- to compilation using @OPTIONS_GHC@ pragmas, and in a multi-session GHC each
   11 -- session can be using different dynamic flags. Dynamic flags can also be set
   12 -- at the prompt in GHCi.
   13 --
   14 -- (c) The University of Glasgow 2005
   15 --
   16 -------------------------------------------------------------------------------
   17 
   18 {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
   19 
   20 module GHC.Driver.Session (
   21         -- * Dynamic flags and associated configuration types
   22         DumpFlag(..),
   23         GeneralFlag(..),
   24         WarningFlag(..), DiagnosticReason(..),
   25         Language(..),
   26         PlatformConstants(..),
   27         FatalMessager, FlushOut(..),
   28         ProfAuto(..),
   29         glasgowExtsFlags,
   30         hasPprDebug, hasNoDebugOutput, hasNoStateHack, hasNoOptCoercion,
   31         dopt, dopt_set, dopt_unset,
   32         gopt, gopt_set, gopt_unset, setGeneralFlag', unSetGeneralFlag',
   33         wopt, wopt_set, wopt_unset,
   34         wopt_fatal, wopt_set_fatal, wopt_unset_fatal,
   35         xopt, xopt_set, xopt_unset,
   36         xopt_set_unlessExplSpec,
   37         xopt_DuplicateRecordFields,
   38         xopt_FieldSelectors,
   39         lang_set,
   40         DynamicTooState(..), dynamicTooState, setDynamicNow,
   41         sccProfilingEnabled,
   42         DynFlags(..),
   43         outputFile, objectSuf, ways,
   44         FlagSpec(..),
   45         HasDynFlags(..), ContainsDynFlags(..),
   46         RtsOptsEnabled(..),
   47         GhcMode(..), isOneShot,
   48         GhcLink(..), isNoLink,
   49         PackageFlag(..), PackageArg(..), ModRenaming(..),
   50         packageFlagsChanged,
   51         IgnorePackageFlag(..), TrustFlag(..),
   52         PackageDBFlag(..), PkgDbRef(..),
   53         Option(..), showOpt,
   54         DynLibLoader(..),
   55         fFlags, fLangFlags, xFlags,
   56         wWarningFlags,
   57         makeDynFlagsConsistent,
   58         positionIndependent,
   59         optimisationFlags,
   60         setFlagsFromEnvFile,
   61         pprDynFlagsDiff,
   62         flagSpecOf,
   63 
   64         targetProfile,
   65 
   66         -- ** Safe Haskell
   67         safeHaskellOn, safeHaskellModeEnabled,
   68         safeImportsOn, safeLanguageOn, safeInferOn,
   69         packageTrustOn,
   70         safeDirectImpsReq, safeImplicitImpsReq,
   71         unsafeFlags, unsafeFlagsForInfer,
   72 
   73         -- ** LLVM Targets
   74         LlvmTarget(..), LlvmConfig(..),
   75 
   76         -- ** System tool settings and locations
   77         Settings(..),
   78         sProgramName,
   79         sProjectVersion,
   80         sGhcUsagePath,
   81         sGhciUsagePath,
   82         sToolDir,
   83         sTopDir,
   84         sGlobalPackageDatabasePath,
   85         sLdSupportsCompactUnwind,
   86         sLdSupportsBuildId,
   87         sLdSupportsFilelist,
   88         sLdIsGnuLd,
   89         sGccSupportsNoPie,
   90         sPgm_L,
   91         sPgm_P,
   92         sPgm_F,
   93         sPgm_c,
   94         sPgm_a,
   95         sPgm_l,
   96         sPgm_lm,
   97         sPgm_dll,
   98         sPgm_T,
   99         sPgm_windres,
  100         sPgm_libtool,
  101         sPgm_ar,
  102         sPgm_ranlib,
  103         sPgm_lo,
  104         sPgm_lc,
  105         sPgm_lcc,
  106         sPgm_i,
  107         sOpt_L,
  108         sOpt_P,
  109         sOpt_P_fingerprint,
  110         sOpt_F,
  111         sOpt_c,
  112         sOpt_cxx,
  113         sOpt_a,
  114         sOpt_l,
  115         sOpt_lm,
  116         sOpt_windres,
  117         sOpt_lo,
  118         sOpt_lc,
  119         sOpt_lcc,
  120         sOpt_i,
  121         sExtraGccViaCFlags,
  122         sTargetPlatformString,
  123         sGhcWithInterpreter,
  124         sLibFFI,
  125         GhcNameVersion(..),
  126         FileSettings(..),
  127         PlatformMisc(..),
  128         settings,
  129         programName, projectVersion,
  130         ghcUsagePath, ghciUsagePath, topDir,
  131         versionedAppDir, versionedFilePath,
  132         extraGccViaCFlags, globalPackageDatabasePath,
  133         pgm_L, pgm_P, pgm_F, pgm_c, pgm_a, pgm_l, pgm_lm, pgm_dll, pgm_T,
  134         pgm_windres, pgm_libtool, pgm_ar, pgm_otool, pgm_install_name_tool,
  135         pgm_ranlib, pgm_lo, pgm_lc, pgm_lcc, pgm_i,
  136         opt_L, opt_P, opt_F, opt_c, opt_cxx, opt_a, opt_l, opt_lm, opt_i,
  137         opt_P_signature,
  138         opt_windres, opt_lo, opt_lc, opt_lcc,
  139         updatePlatformConstants,
  140 
  141         -- ** Manipulating DynFlags
  142         addPluginModuleName,
  143         defaultDynFlags,                -- Settings -> DynFlags
  144         initDynFlags,                   -- DynFlags -> IO DynFlags
  145         defaultFatalMessager,
  146         defaultFlushOut,
  147         setOutputFile, setDynOutputFile, setOutputHi, setDynOutputHi,
  148 
  149         getOpts,                        -- DynFlags -> (DynFlags -> [a]) -> [a]
  150         getVerbFlags,
  151         updOptLevel,
  152         setTmpDir,
  153         setUnitId,
  154 
  155         TurnOnFlag,
  156         turnOn,
  157         turnOff,
  158         impliedGFlags,
  159         impliedOffGFlags,
  160         impliedXFlags,
  161 
  162         -- ** Parsing DynFlags
  163         parseDynamicFlagsCmdLine,
  164         parseDynamicFilePragma,
  165         parseDynamicFlagsFull,
  166 
  167         -- ** Available DynFlags
  168         allNonDeprecatedFlags,
  169         flagsAll,
  170         flagsDynamic,
  171         flagsPackage,
  172         flagsForCompletion,
  173 
  174         supportedLanguagesAndExtensions,
  175         languageExtensions,
  176 
  177         -- ** DynFlags C compiler options
  178         picCCOpts, picPOpts,
  179 
  180         -- * Compiler configuration suitable for display to the user
  181         compilerInfo,
  182 
  183         wordAlignment,
  184 
  185         setUnsafeGlobalDynFlags,
  186 
  187         -- * SSE and AVX
  188         isSseEnabled,
  189         isSse2Enabled,
  190         isSse4_2Enabled,
  191         isBmiEnabled,
  192         isBmi2Enabled,
  193         isAvxEnabled,
  194         isAvx2Enabled,
  195         isAvx512cdEnabled,
  196         isAvx512erEnabled,
  197         isAvx512fEnabled,
  198         isAvx512pfEnabled,
  199 
  200         -- * Linker/compiler information
  201         LinkerInfo(..),
  202         CompilerInfo(..),
  203         useXLinkerRPath,
  204 
  205         -- * Include specifications
  206         IncludeSpecs(..), addGlobalInclude, addQuoteInclude, flattenIncludes,
  207         addImplicitQuoteInclude,
  208 
  209         -- * SDoc
  210         initSDocContext, initDefaultSDocContext,
  211   ) where
  212 
  213 import GHC.Prelude
  214 
  215 import GHC.Platform
  216 import GHC.Platform.Ways
  217 import GHC.Platform.Profile
  218 
  219 import GHC.UniqueSubdir (uniqueSubdir)
  220 import GHC.Unit.Types
  221 import GHC.Unit.Parser
  222 import GHC.Unit.Module
  223 import GHC.Builtin.Names ( mAIN_NAME )
  224 import GHC.Driver.Phases ( Phase(..), phaseInputExt )
  225 import GHC.Driver.Flags
  226 import GHC.Driver.Backend
  227 import GHC.Settings.Config
  228 import GHC.Utils.CliOption
  229 import GHC.Core.Unfold
  230 import GHC.Driver.CmdLine
  231 import GHC.Settings.Constants
  232 import GHC.Utils.Panic
  233 import qualified GHC.Utils.Ppr.Colour as Col
  234 import GHC.Utils.Misc
  235 import GHC.Utils.Constants (debugIsOn)
  236 import GHC.Utils.GlobalVars
  237 import GHC.Data.Maybe
  238 import GHC.Data.Bool
  239 import GHC.Utils.Monad
  240 import GHC.Types.Error (DiagnosticReason(..))
  241 import GHC.Types.SrcLoc
  242 import GHC.Types.SafeHaskell
  243 import GHC.Types.Basic ( Alignment, alignmentOf, IntWithInf, treatZeroAsInf )
  244 import qualified GHC.Types.FieldLabel as FieldLabel
  245 import GHC.Data.FastString
  246 import GHC.Utils.TmpFs
  247 import GHC.Utils.Fingerprint
  248 import GHC.Utils.Outputable
  249 import GHC.Settings
  250 import GHC.CmmToAsm.CFG.Weight
  251 import {-# SOURCE #-} GHC.Core.Opt.CallerCC
  252 
  253 import GHC.SysTools.Terminal ( stderrSupportsAnsiColors )
  254 import GHC.SysTools.BaseDir ( expandToolDir, expandTopDir )
  255 
  256 import Data.IORef
  257 import Control.Arrow ((&&&))
  258 import Control.Monad
  259 import Control.Monad.Trans.Class
  260 import Control.Monad.Trans.Writer
  261 import Control.Monad.Trans.Reader
  262 import Control.Monad.Trans.Except
  263 
  264 import Data.Ord
  265 import Data.Char
  266 import Data.List (intercalate, sortBy)
  267 import qualified Data.List.NonEmpty as NE
  268 import qualified Data.Map as Map
  269 import qualified Data.Set as Set
  270 import System.FilePath
  271 import System.Directory
  272 import System.Environment (lookupEnv)
  273 import System.IO
  274 import System.IO.Error
  275 import Text.ParserCombinators.ReadP hiding (char)
  276 import Text.ParserCombinators.ReadP as R
  277 
  278 import GHC.Data.EnumSet (EnumSet)
  279 import qualified GHC.Data.EnumSet as EnumSet
  280 
  281 import GHC.Foreign (withCString, peekCString)
  282 import qualified GHC.LanguageExtensions as LangExt
  283 
  284 -- Note [Updating flag description in the User's Guide]
  285 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  286 --
  287 -- If you modify anything in this file please make sure that your changes are
  288 -- described in the User's Guide. Please update the flag description in the
  289 -- users guide (docs/users_guide) whenever you add or change a flag.
  290 
  291 -- Note [Supporting CLI completion]
  292 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  293 --
  294 -- The command line interface completion (in for example bash) is an easy way
  295 -- for the developer to learn what flags are available from GHC.
  296 -- GHC helps by separating which flags are available when compiling with GHC,
  297 -- and which flags are available when using GHCi.
  298 -- A flag is assumed to either work in both these modes, or only in one of them.
  299 -- When adding or changing a flag, please consider for which mode the flag will
  300 -- have effect, and annotate it accordingly. For Flags use defFlag, defGhcFlag,
  301 -- defGhciFlag, and for FlagSpec use flagSpec or flagGhciSpec.
  302 
  303 -- Note [Adding a language extension]
  304 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  305 --
  306 -- There are a few steps to adding (or removing) a language extension,
  307 --
  308 --  * Adding the extension to GHC.LanguageExtensions
  309 --
  310 --    The Extension type in libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs
  311 --    is the canonical list of language extensions known by GHC.
  312 --
  313 --  * Adding a flag to DynFlags.xFlags
  314 --
  315 --    This is fairly self-explanatory. The name should be concise, memorable,
  316 --    and consistent with any previous implementations of the similar idea in
  317 --    other Haskell compilers.
  318 --
  319 --  * Adding the flag to the documentation
  320 --
  321 --    This is the same as any other flag. See
  322 --    Note [Updating flag description in the User's Guide]
  323 --
  324 --  * Adding the flag to Cabal
  325 --
  326 --    The Cabal library has its own list of all language extensions supported
  327 --    by all major compilers. This is the list that user code being uploaded
  328 --    to Hackage is checked against to ensure language extension validity.
  329 --    Consequently, it is very important that this list remains up-to-date.
  330 --
  331 --    To this end, there is a testsuite test (testsuite/tests/driver/T4437.hs)
  332 --    whose job it is to ensure these GHC's extensions are consistent with
  333 --    Cabal.
  334 --
  335 --    The recommended workflow is,
  336 --
  337 --     1. Temporarily add your new language extension to the
  338 --        expectedGhcOnlyExtensions list in T4437 to ensure the test doesn't
  339 --        break while Cabal is updated.
  340 --
  341 --     2. After your GHC change is accepted, submit a Cabal pull request adding
  342 --        your new extension to Cabal's list (found in
  343 --        Cabal/Language/Haskell/Extension.hs).
  344 --
  345 --     3. After your Cabal change is accepted, let the GHC developers know so
  346 --        they can update the Cabal submodule and remove the extensions from
  347 --        expectedGhcOnlyExtensions.
  348 --
  349 --  * Adding the flag to the GHC Wiki
  350 --
  351 --    There is a change log tracking language extension additions and removals
  352 --    on the GHC wiki:  https://gitlab.haskell.org/ghc/ghc/wikis/language-pragma-history
  353 --
  354 --  See #4437 and #8176.
  355 
  356 -- -----------------------------------------------------------------------------
  357 -- DynFlags
  358 
  359 -- | Used to differentiate the scope an include needs to apply to.
  360 -- We have to split the include paths to avoid accidentally forcing recursive
  361 -- includes since -I overrides the system search paths. See #14312.
  362 data IncludeSpecs
  363   = IncludeSpecs { includePathsQuote  :: [String]
  364                  , includePathsGlobal :: [String]
  365                  -- | See note [Implicit include paths]
  366                  , includePathsQuoteImplicit :: [String]
  367                  }
  368   deriving Show
  369 
  370 -- | Append to the list of includes a path that shall be included using `-I`
  371 -- when the C compiler is called. These paths override system search paths.
  372 addGlobalInclude :: IncludeSpecs -> [String] -> IncludeSpecs
  373 addGlobalInclude spec paths  = let f = includePathsGlobal spec
  374                                in spec { includePathsGlobal = f ++ paths }
  375 
  376 -- | Append to the list of includes a path that shall be included using
  377 -- `-iquote` when the C compiler is called. These paths only apply when quoted
  378 -- includes are used. e.g. #include "foo.h"
  379 addQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs
  380 addQuoteInclude spec paths  = let f = includePathsQuote spec
  381                               in spec { includePathsQuote = f ++ paths }
  382 
  383 -- | These includes are not considered while fingerprinting the flags for iface
  384 -- | See note [Implicit include paths]
  385 addImplicitQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs
  386 addImplicitQuoteInclude spec paths  = let f = includePathsQuoteImplicit spec
  387                               in spec { includePathsQuoteImplicit = f ++ paths }
  388 
  389 
  390 -- | Concatenate and flatten the list of global and quoted includes returning
  391 -- just a flat list of paths.
  392 flattenIncludes :: IncludeSpecs -> [String]
  393 flattenIncludes specs =
  394     includePathsQuote specs ++
  395     includePathsQuoteImplicit specs ++
  396     includePathsGlobal specs
  397 
  398 {- Note [Implicit include paths]
  399 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  400   The compile driver adds the path to the folder containing the source file being
  401   compiled to the 'IncludeSpecs', and this change gets recorded in the 'DynFlags'
  402   that are used later to compute the interface file. Because of this,
  403   the flags fingerprint derived from these 'DynFlags' and recorded in the
  404   interface file will end up containing the absolute path to the source folder.
  405 
  406   Build systems with a remote cache like Bazel or Buck (or Shake, see #16956)
  407   store the build artifacts produced by a build BA for reuse in subsequent builds.
  408 
  409   Embedding source paths in interface fingerprints will thwart these attemps and
  410   lead to unnecessary recompilations when the source paths in BA differ from the
  411   source paths in subsequent builds.
  412  -}
  413 
  414 
  415 -- | Contains not only a collection of 'GeneralFlag's but also a plethora of
  416 -- information relating to the compilation of a single file or GHC session
  417 data DynFlags = DynFlags {
  418   ghcMode               :: GhcMode,
  419   ghcLink               :: GhcLink,
  420   backend               :: !Backend,
  421    -- ^ The backend to use (if any).
  422    --
  423    -- Whenever you change the backend, also make sure to set 'ghcLink' to
  424    -- something sensible.
  425    --
  426    -- 'NoBackend' can be used to avoid generating any output, however, note that:
  427    --
  428    --  * If a program uses Template Haskell the typechecker may need to run code
  429    --    from an imported module.  To facilitate this, code generation is enabled
  430    --    for modules imported by modules that use template haskell, using the
  431    --    default backend for the platform.
  432    --    See Note [-fno-code mode].
  433 
  434 
  435   -- formerly Settings
  436   ghcNameVersion    :: {-# UNPACK #-} !GhcNameVersion,
  437   fileSettings      :: {-# UNPACK #-} !FileSettings,
  438   targetPlatform    :: Platform,       -- Filled in by SysTools
  439   toolSettings      :: {-# UNPACK #-} !ToolSettings,
  440   platformMisc      :: {-# UNPACK #-} !PlatformMisc,
  441   rawSettings       :: [(String, String)],
  442   tmpDir            :: TempDir,
  443 
  444   llvmConfig            :: LlvmConfig,
  445     -- ^ N.B. It's important that this field is lazy since we load the LLVM
  446     -- configuration lazily. See Note [LLVM Configuration] in "GHC.SysTools".
  447   verbosity             :: Int,         -- ^ Verbosity level: see Note [Verbosity levels]
  448   optLevel              :: Int,         -- ^ Optimisation level
  449   debugLevel            :: Int,         -- ^ How much debug information to produce
  450   simplPhases           :: Int,         -- ^ Number of simplifier phases
  451   maxSimplIterations    :: Int,         -- ^ Max simplifier iterations
  452   ruleCheck             :: Maybe String,
  453   strictnessBefore      :: [Int],       -- ^ Additional demand analysis
  454 
  455   parMakeCount          :: Maybe Int,   -- ^ The number of modules to compile in parallel
  456                                         --   in --make mode, where Nothing ==> compile as
  457                                         --   many in parallel as there are CPUs.
  458 
  459   enableTimeStats       :: Bool,        -- ^ Enable RTS timing statistics?
  460   ghcHeapSize           :: Maybe Int,   -- ^ The heap size to set.
  461 
  462   maxRelevantBinds      :: Maybe Int,   -- ^ Maximum number of bindings from the type envt
  463                                         --   to show in type error messages
  464   maxValidHoleFits      :: Maybe Int,   -- ^ Maximum number of hole fits to show
  465                                         --   in typed hole error messages
  466   maxRefHoleFits        :: Maybe Int,   -- ^ Maximum number of refinement hole
  467                                         --   fits to show in typed hole error
  468                                         --   messages
  469   refLevelHoleFits      :: Maybe Int,   -- ^ Maximum level of refinement for
  470                                         --   refinement hole fits in typed hole
  471                                         --   error messages
  472   maxUncoveredPatterns  :: Int,         -- ^ Maximum number of unmatched patterns to show
  473                                         --   in non-exhaustiveness warnings
  474   maxPmCheckModels      :: Int,         -- ^ Soft limit on the number of models
  475                                         --   the pattern match checker checks
  476                                         --   a pattern against. A safe guard
  477                                         --   against exponential blow-up.
  478   simplTickFactor       :: Int,         -- ^ Multiplier for simplifier ticks
  479   dmdUnboxWidth         :: !Int,        -- ^ Whether DmdAnal should optimistically put an
  480                                         --   Unboxed demand on returned products with at most
  481                                         --   this number of fields
  482   specConstrThreshold   :: Maybe Int,   -- ^ Threshold for SpecConstr
  483   specConstrCount       :: Maybe Int,   -- ^ Max number of specialisations for any one function
  484   specConstrRecursive   :: Int,         -- ^ Max number of specialisations for recursive types
  485                                         --   Not optional; otherwise ForceSpecConstr can diverge.
  486   binBlobThreshold      :: Word,        -- ^ Binary literals (e.g. strings) whose size is above
  487                                         --   this threshold will be dumped in a binary file
  488                                         --   by the assembler code generator (0 to disable)
  489   liberateCaseThreshold :: Maybe Int,   -- ^ Threshold for LiberateCase
  490   floatLamArgs          :: Maybe Int,   -- ^ Arg count for lambda floating
  491                                         --   See 'GHC.Core.Opt.Monad.FloatOutSwitches'
  492 
  493   liftLamsRecArgs       :: Maybe Int,   -- ^ Maximum number of arguments after lambda lifting a
  494                                         --   recursive function.
  495   liftLamsNonRecArgs    :: Maybe Int,   -- ^ Maximum number of arguments after lambda lifting a
  496                                         --   non-recursive function.
  497   liftLamsKnown         :: Bool,        -- ^ Lambda lift even when this turns a known call
  498                                         --   into an unknown call.
  499 
  500   cmmProcAlignment      :: Maybe Int,   -- ^ Align Cmm functions at this boundary or use default.
  501 
  502   historySize           :: Int,         -- ^ Simplification history size
  503 
  504   importPaths           :: [FilePath],
  505   mainModuleNameIs      :: ModuleName,
  506   mainFunIs             :: Maybe String,
  507   reductionDepth        :: IntWithInf,   -- ^ Typechecker maximum stack depth
  508   solverIterations      :: IntWithInf,   -- ^ Number of iterations in the constraints solver
  509                                          --   Typically only 1 is needed
  510 
  511   homeUnitId_             :: UnitId,                 -- ^ Target home unit-id
  512   homeUnitInstanceOf_     :: Maybe UnitId,           -- ^ Id of the unit to instantiate
  513   homeUnitInstantiations_ :: [(ModuleName, Module)], -- ^ Module instantiations
  514 
  515   -- ways
  516   targetWays_           :: Ways,         -- ^ Target way flags from the command line
  517 
  518   -- For object splitting
  519   splitInfo             :: Maybe (String,Int),
  520 
  521   -- paths etc.
  522   objectDir             :: Maybe String,
  523   dylibInstallName      :: Maybe String,
  524   hiDir                 :: Maybe String,
  525   hieDir                :: Maybe String,
  526   stubDir               :: Maybe String,
  527   dumpDir               :: Maybe String,
  528 
  529   objectSuf_            :: String,
  530   hcSuf                 :: String,
  531   hiSuf_                :: String,
  532   hieSuf                :: String,
  533 
  534   dynObjectSuf_         :: String,
  535   dynHiSuf_             :: String,
  536 
  537   outputFile_           :: Maybe String,
  538   dynOutputFile_        :: Maybe String,
  539   outputHi              :: Maybe String,
  540   dynOutputHi           :: Maybe String,
  541   dynLibLoader          :: DynLibLoader,
  542 
  543   dynamicNow            :: !Bool, -- ^ Indicate if we are now generating dynamic output
  544                                   -- because of -dynamic-too. This predicate is
  545                                   -- used to query the appropriate fields
  546                                   -- (outputFile/dynOutputFile, ways, etc.)
  547 
  548   -- | This is set by 'GHC.Driver.Pipeline.setDumpPrefix'
  549   --    or 'ghc.GHCi.UI.runStmt' based on where its output is going.
  550   dumpPrefix            :: Maybe FilePath,
  551 
  552   -- | Override the 'dumpPrefix' set by 'GHC.Driver.Pipeline.setDumpPrefix'
  553   --    or 'ghc.GHCi.UI.runStmt'.
  554   --    Set by @-ddump-file-prefix@
  555   dumpPrefixForce       :: Maybe FilePath,
  556 
  557   ldInputs              :: [Option],
  558 
  559   includePaths          :: IncludeSpecs,
  560   libraryPaths          :: [String],
  561   frameworkPaths        :: [String],    -- used on darwin only
  562   cmdlineFrameworks     :: [String],    -- ditto
  563 
  564   rtsOpts               :: Maybe String,
  565   rtsOptsEnabled        :: RtsOptsEnabled,
  566   rtsOptsSuggestions    :: Bool,
  567 
  568   hpcDir                :: String,      -- ^ Path to store the .mix files
  569 
  570   -- Plugins
  571   pluginModNames        :: [ModuleName],
  572   pluginModNameOpts     :: [(ModuleName,String)],
  573   frontendPluginOpts    :: [String],
  574     -- ^ the @-ffrontend-opt@ flags given on the command line, in *reverse*
  575     -- order that they're specified on the command line.
  576 
  577   --  For ghc -M
  578   depMakefile           :: FilePath,
  579   depIncludePkgDeps     :: Bool,
  580   depIncludeCppDeps     :: Bool,
  581   depExcludeMods        :: [ModuleName],
  582   depSuffixes           :: [String],
  583 
  584   --  Package flags
  585   packageDBFlags        :: [PackageDBFlag],
  586         -- ^ The @-package-db@ flags given on the command line, In
  587         -- *reverse* order that they're specified on the command line.
  588         -- This is intended to be applied with the list of "initial"
  589         -- package databases derived from @GHC_PACKAGE_PATH@; see
  590         -- 'getUnitDbRefs'.
  591 
  592   ignorePackageFlags    :: [IgnorePackageFlag],
  593         -- ^ The @-ignore-package@ flags from the command line.
  594         -- In *reverse* order that they're specified on the command line.
  595   packageFlags          :: [PackageFlag],
  596         -- ^ The @-package@ and @-hide-package@ flags from the command-line.
  597         -- In *reverse* order that they're specified on the command line.
  598   pluginPackageFlags    :: [PackageFlag],
  599         -- ^ The @-plugin-package-id@ flags from command line.
  600         -- In *reverse* order that they're specified on the command line.
  601   trustFlags            :: [TrustFlag],
  602         -- ^ The @-trust@ and @-distrust@ flags.
  603         -- In *reverse* order that they're specified on the command line.
  604   packageEnv            :: Maybe FilePath,
  605         -- ^ Filepath to the package environment file (if overriding default)
  606 
  607 
  608   -- hsc dynamic flags
  609   dumpFlags             :: EnumSet DumpFlag,
  610   generalFlags          :: EnumSet GeneralFlag,
  611   warningFlags          :: EnumSet WarningFlag,
  612   fatalWarningFlags     :: EnumSet WarningFlag,
  613   -- Don't change this without updating extensionFlags:
  614   language              :: Maybe Language,
  615   -- | Safe Haskell mode
  616   safeHaskell           :: SafeHaskellMode,
  617   safeInfer             :: Bool,
  618   safeInferred          :: Bool,
  619   -- We store the location of where some extension and flags were turned on so
  620   -- we can produce accurate error messages when Safe Haskell fails due to
  621   -- them.
  622   thOnLoc               :: SrcSpan,
  623   newDerivOnLoc         :: SrcSpan,
  624   deriveViaOnLoc        :: SrcSpan,
  625   overlapInstLoc        :: SrcSpan,
  626   incoherentOnLoc       :: SrcSpan,
  627   pkgTrustOnLoc         :: SrcSpan,
  628   warnSafeOnLoc         :: SrcSpan,
  629   warnUnsafeOnLoc       :: SrcSpan,
  630   trustworthyOnLoc      :: SrcSpan,
  631   -- Don't change this without updating extensionFlags:
  632   -- Here we collect the settings of the language extensions
  633   -- from the command line, the ghci config file and
  634   -- from interactive :set / :seti commands.
  635   extensions            :: [OnOff LangExt.Extension],
  636   -- extensionFlags should always be equal to
  637   --     flattenExtensionFlags language extensions
  638   -- LangExt.Extension is defined in libraries/ghc-boot so that it can be used
  639   -- by template-haskell
  640   extensionFlags        :: EnumSet LangExt.Extension,
  641 
  642   -- | Unfolding control
  643   -- See Note [Discounts and thresholds] in GHC.Core.Unfold
  644   unfoldingOpts         :: !UnfoldingOpts,
  645 
  646   maxWorkerArgs         :: Int,
  647 
  648   ghciHistSize          :: Int,
  649 
  650   flushOut              :: FlushOut,
  651 
  652   ghcVersionFile        :: Maybe FilePath,
  653   haddockOptions        :: Maybe String,
  654 
  655   -- | GHCi scripts specified by -ghci-script, in reverse order
  656   ghciScripts           :: [String],
  657 
  658   -- Output style options
  659   pprUserLength         :: Int,
  660   pprCols               :: Int,
  661 
  662   useUnicode            :: Bool,
  663   useColor              :: OverridingBool,
  664   canUseColor           :: Bool,
  665   colScheme             :: Col.Scheme,
  666 
  667   -- | what kind of {-# SCC #-} to add automatically
  668   profAuto              :: ProfAuto,
  669   callerCcFilters       :: [CallerCcFilter],
  670 
  671   interactivePrint      :: Maybe String,
  672 
  673   -- | Machine dependent flags (-m\<blah> stuff)
  674   sseVersion            :: Maybe SseVersion,
  675   bmiVersion            :: Maybe BmiVersion,
  676   avx                   :: Bool,
  677   avx2                  :: Bool,
  678   avx512cd              :: Bool, -- Enable AVX-512 Conflict Detection Instructions.
  679   avx512er              :: Bool, -- Enable AVX-512 Exponential and Reciprocal Instructions.
  680   avx512f               :: Bool, -- Enable AVX-512 instructions.
  681   avx512pf              :: Bool, -- Enable AVX-512 PreFetch Instructions.
  682 
  683   -- | Run-time linker information (what options we need, etc.)
  684   rtldInfo              :: IORef (Maybe LinkerInfo),
  685 
  686   -- | Run-time C compiler information
  687   rtccInfo              :: IORef (Maybe CompilerInfo),
  688 
  689   -- | Run-time assembler information
  690   rtasmInfo              :: IORef (Maybe CompilerInfo),
  691 
  692   -- Constants used to control the amount of optimization done.
  693 
  694   -- | Max size, in bytes, of inline array allocations.
  695   maxInlineAllocSize    :: Int,
  696 
  697   -- | Only inline memcpy if it generates no more than this many
  698   -- pseudo (roughly: Cmm) instructions.
  699   maxInlineMemcpyInsns  :: Int,
  700 
  701   -- | Only inline memset if it generates no more than this many
  702   -- pseudo (roughly: Cmm) instructions.
  703   maxInlineMemsetInsns  :: Int,
  704 
  705   -- | Reverse the order of error messages in GHC/GHCi
  706   reverseErrors         :: Bool,
  707 
  708   -- | Limit the maximum number of errors to show
  709   maxErrors             :: Maybe Int,
  710 
  711   -- | Unique supply configuration for testing build determinism
  712   initialUnique         :: Word,
  713   uniqueIncrement       :: Int,
  714     -- 'Int' because it can be used to test uniques in decreasing order.
  715 
  716   -- | Temporary: CFG Edge weights for fast iterations
  717   cfgWeights            :: Weights
  718 }
  719 
  720 class HasDynFlags m where
  721     getDynFlags :: m DynFlags
  722 
  723 {- It would be desirable to have the more generalised
  724 
  725   instance (MonadTrans t, Monad m, HasDynFlags m) => HasDynFlags (t m) where
  726       getDynFlags = lift getDynFlags
  727 
  728 instance definition. However, that definition would overlap with the
  729 `HasDynFlags (GhcT m)` instance. Instead we define instances for a
  730 couple of common Monad transformers explicitly. -}
  731 
  732 instance (Monoid a, Monad m, HasDynFlags m) => HasDynFlags (WriterT a m) where
  733     getDynFlags = lift getDynFlags
  734 
  735 instance (Monad m, HasDynFlags m) => HasDynFlags (ReaderT a m) where
  736     getDynFlags = lift getDynFlags
  737 
  738 instance (Monad m, HasDynFlags m) => HasDynFlags (MaybeT m) where
  739     getDynFlags = lift getDynFlags
  740 
  741 instance (Monad m, HasDynFlags m) => HasDynFlags (ExceptT e m) where
  742     getDynFlags = lift getDynFlags
  743 
  744 class ContainsDynFlags t where
  745     extractDynFlags :: t -> DynFlags
  746 
  747 data ProfAuto
  748   = NoProfAuto         -- ^ no SCC annotations added
  749   | ProfAutoAll        -- ^ top-level and nested functions are annotated
  750   | ProfAutoTop        -- ^ top-level functions annotated only
  751   | ProfAutoExports    -- ^ exported functions annotated only
  752   | ProfAutoCalls      -- ^ annotate call-sites
  753   deriving (Eq,Enum)
  754 
  755 data LlvmTarget = LlvmTarget
  756   { lDataLayout :: String
  757   , lCPU        :: String
  758   , lAttributes :: [String]
  759   }
  760 
  761 -- | See Note [LLVM Configuration] in "GHC.SysTools".
  762 data LlvmConfig = LlvmConfig { llvmTargets :: [(String, LlvmTarget)]
  763                              , llvmPasses  :: [(Int, String)]
  764                              }
  765 
  766 -----------------------------------------------------------------------------
  767 -- Accessessors from 'DynFlags'
  768 
  769 -- | "unbuild" a 'Settings' from a 'DynFlags'. This shouldn't be needed in the
  770 -- vast majority of code. But GHCi questionably uses this to produce a default
  771 -- 'DynFlags' from which to compute a flags diff for printing.
  772 settings :: DynFlags -> Settings
  773 settings dflags = Settings
  774   { sGhcNameVersion = ghcNameVersion dflags
  775   , sFileSettings = fileSettings dflags
  776   , sTargetPlatform = targetPlatform dflags
  777   , sToolSettings = toolSettings dflags
  778   , sPlatformMisc = platformMisc dflags
  779   , sRawSettings = rawSettings dflags
  780   }
  781 
  782 programName :: DynFlags -> String
  783 programName dflags = ghcNameVersion_programName $ ghcNameVersion dflags
  784 projectVersion :: DynFlags -> String
  785 projectVersion dflags = ghcNameVersion_projectVersion (ghcNameVersion dflags)
  786 ghcUsagePath          :: DynFlags -> FilePath
  787 ghcUsagePath dflags = fileSettings_ghcUsagePath $ fileSettings dflags
  788 ghciUsagePath         :: DynFlags -> FilePath
  789 ghciUsagePath dflags = fileSettings_ghciUsagePath $ fileSettings dflags
  790 toolDir               :: DynFlags -> Maybe FilePath
  791 toolDir dflags = fileSettings_toolDir $ fileSettings dflags
  792 topDir                :: DynFlags -> FilePath
  793 topDir dflags = fileSettings_topDir $ fileSettings dflags
  794 extraGccViaCFlags     :: DynFlags -> [String]
  795 extraGccViaCFlags dflags = toolSettings_extraGccViaCFlags $ toolSettings dflags
  796 globalPackageDatabasePath   :: DynFlags -> FilePath
  797 globalPackageDatabasePath dflags = fileSettings_globalPackageDatabase $ fileSettings dflags
  798 pgm_L                 :: DynFlags -> String
  799 pgm_L dflags = toolSettings_pgm_L $ toolSettings dflags
  800 pgm_P                 :: DynFlags -> (String,[Option])
  801 pgm_P dflags = toolSettings_pgm_P $ toolSettings dflags
  802 pgm_F                 :: DynFlags -> String
  803 pgm_F dflags = toolSettings_pgm_F $ toolSettings dflags
  804 pgm_c                 :: DynFlags -> String
  805 pgm_c dflags = toolSettings_pgm_c $ toolSettings dflags
  806 pgm_a                 :: DynFlags -> (String,[Option])
  807 pgm_a dflags = toolSettings_pgm_a $ toolSettings dflags
  808 pgm_l                 :: DynFlags -> (String,[Option])
  809 pgm_l dflags = toolSettings_pgm_l $ toolSettings dflags
  810 pgm_lm                 :: DynFlags -> (String,[Option])
  811 pgm_lm dflags = toolSettings_pgm_lm $ toolSettings dflags
  812 pgm_dll               :: DynFlags -> (String,[Option])
  813 pgm_dll dflags = toolSettings_pgm_dll $ toolSettings dflags
  814 pgm_T                 :: DynFlags -> String
  815 pgm_T dflags = toolSettings_pgm_T $ toolSettings dflags
  816 pgm_windres           :: DynFlags -> String
  817 pgm_windres dflags = toolSettings_pgm_windres $ toolSettings dflags
  818 pgm_libtool           :: DynFlags -> String
  819 pgm_libtool dflags = toolSettings_pgm_libtool $ toolSettings dflags
  820 pgm_lcc               :: DynFlags -> (String,[Option])
  821 pgm_lcc dflags = toolSettings_pgm_lcc $ toolSettings dflags
  822 pgm_ar                :: DynFlags -> String
  823 pgm_ar dflags = toolSettings_pgm_ar $ toolSettings dflags
  824 pgm_otool             :: DynFlags -> String
  825 pgm_otool dflags = toolSettings_pgm_otool $ toolSettings dflags
  826 pgm_install_name_tool :: DynFlags -> String
  827 pgm_install_name_tool dflags = toolSettings_pgm_install_name_tool $ toolSettings dflags
  828 pgm_ranlib            :: DynFlags -> String
  829 pgm_ranlib dflags = toolSettings_pgm_ranlib $ toolSettings dflags
  830 pgm_lo                :: DynFlags -> (String,[Option])
  831 pgm_lo dflags = toolSettings_pgm_lo $ toolSettings dflags
  832 pgm_lc                :: DynFlags -> (String,[Option])
  833 pgm_lc dflags = toolSettings_pgm_lc $ toolSettings dflags
  834 pgm_i                 :: DynFlags -> String
  835 pgm_i dflags = toolSettings_pgm_i $ toolSettings dflags
  836 opt_L                 :: DynFlags -> [String]
  837 opt_L dflags = toolSettings_opt_L $ toolSettings dflags
  838 opt_P                 :: DynFlags -> [String]
  839 opt_P dflags = concatMap (wayOptP (targetPlatform dflags)) (ways dflags)
  840             ++ toolSettings_opt_P (toolSettings dflags)
  841 
  842 -- This function packages everything that's needed to fingerprint opt_P
  843 -- flags. See Note [Repeated -optP hashing].
  844 opt_P_signature       :: DynFlags -> ([String], Fingerprint)
  845 opt_P_signature dflags =
  846   ( concatMap (wayOptP (targetPlatform dflags)) (ways dflags)
  847   , toolSettings_opt_P_fingerprint $ toolSettings dflags
  848   )
  849 
  850 opt_F                 :: DynFlags -> [String]
  851 opt_F dflags= toolSettings_opt_F $ toolSettings dflags
  852 opt_c                 :: DynFlags -> [String]
  853 opt_c dflags = concatMap (wayOptc (targetPlatform dflags)) (ways dflags)
  854             ++ toolSettings_opt_c (toolSettings dflags)
  855 opt_cxx               :: DynFlags -> [String]
  856 opt_cxx dflags= toolSettings_opt_cxx $ toolSettings dflags
  857 opt_a                 :: DynFlags -> [String]
  858 opt_a dflags= toolSettings_opt_a $ toolSettings dflags
  859 opt_l                 :: DynFlags -> [String]
  860 opt_l dflags = concatMap (wayOptl (targetPlatform dflags)) (ways dflags)
  861             ++ toolSettings_opt_l (toolSettings dflags)
  862 opt_lm                :: DynFlags -> [String]
  863 opt_lm dflags= toolSettings_opt_lm $ toolSettings dflags
  864 opt_windres           :: DynFlags -> [String]
  865 opt_windres dflags= toolSettings_opt_windres $ toolSettings dflags
  866 opt_lcc                :: DynFlags -> [String]
  867 opt_lcc dflags= toolSettings_opt_lcc $ toolSettings dflags
  868 opt_lo                :: DynFlags -> [String]
  869 opt_lo dflags= toolSettings_opt_lo $ toolSettings dflags
  870 opt_lc                :: DynFlags -> [String]
  871 opt_lc dflags= toolSettings_opt_lc $ toolSettings dflags
  872 opt_i                 :: DynFlags -> [String]
  873 opt_i dflags= toolSettings_opt_i $ toolSettings dflags
  874 
  875 -- | The directory for this version of ghc in the user's app directory
  876 -- (typically something like @~/.ghc/x86_64-linux-7.6.3@)
  877 --
  878 versionedAppDir :: String -> ArchOS -> MaybeT IO FilePath
  879 versionedAppDir appname platform = do
  880   -- Make sure we handle the case the HOME isn't set (see #11678)
  881   appdir <- tryMaybeT $ getXdgDirectory XdgData appname
  882   return $ appdir </> versionedFilePath platform
  883 
  884 versionedFilePath :: ArchOS -> FilePath
  885 versionedFilePath platform = uniqueSubdir platform
  886 
  887 -- | The 'GhcMode' tells us whether we're doing multi-module
  888 -- compilation (controlled via the "GHC" API) or one-shot
  889 -- (single-module) compilation.  This makes a difference primarily to
  890 -- the "GHC.Unit.Finder": in one-shot mode we look for interface files for
  891 -- imported modules, but in multi-module mode we look for source files
  892 -- in order to check whether they need to be recompiled.
  893 data GhcMode
  894   = CompManager         -- ^ @\-\-make@, GHCi, etc.
  895   | OneShot             -- ^ @ghc -c Foo.hs@
  896   | MkDepend            -- ^ @ghc -M@, see "GHC.Unit.Finder" for why we need this
  897   deriving Eq
  898 
  899 instance Outputable GhcMode where
  900   ppr CompManager = text "CompManager"
  901   ppr OneShot     = text "OneShot"
  902   ppr MkDepend    = text "MkDepend"
  903 
  904 isOneShot :: GhcMode -> Bool
  905 isOneShot OneShot = True
  906 isOneShot _other  = False
  907 
  908 -- | What to do in the link step, if there is one.
  909 data GhcLink
  910   = NoLink              -- ^ Don't link at all
  911   | LinkBinary          -- ^ Link object code into a binary
  912   | LinkInMemory        -- ^ Use the in-memory dynamic linker (works for both
  913                         --   bytecode and object code).
  914   | LinkDynLib          -- ^ Link objects into a dynamic lib (DLL on Windows, DSO on ELF platforms)
  915   | LinkStaticLib       -- ^ Link objects into a static lib
  916   deriving (Eq, Show)
  917 
  918 isNoLink :: GhcLink -> Bool
  919 isNoLink NoLink = True
  920 isNoLink _      = False
  921 
  922 -- | We accept flags which make packages visible, but how they select
  923 -- the package varies; this data type reflects what selection criterion
  924 -- is used.
  925 data PackageArg =
  926       PackageArg String    -- ^ @-package@, by 'PackageName'
  927     | UnitIdArg Unit       -- ^ @-package-id@, by 'Unit'
  928   deriving (Eq, Show)
  929 
  930 instance Outputable PackageArg where
  931     ppr (PackageArg pn) = text "package" <+> text pn
  932     ppr (UnitIdArg uid) = text "unit" <+> ppr uid
  933 
  934 -- | Represents the renaming that may be associated with an exposed
  935 -- package, e.g. the @rns@ part of @-package "foo (rns)"@.
  936 --
  937 -- Here are some example parsings of the package flags (where
  938 -- a string literal is punned to be a 'ModuleName':
  939 --
  940 --      * @-package foo@ is @ModRenaming True []@
  941 --      * @-package foo ()@ is @ModRenaming False []@
  942 --      * @-package foo (A)@ is @ModRenaming False [("A", "A")]@
  943 --      * @-package foo (A as B)@ is @ModRenaming False [("A", "B")]@
  944 --      * @-package foo with (A as B)@ is @ModRenaming True [("A", "B")]@
  945 data ModRenaming = ModRenaming {
  946     modRenamingWithImplicit :: Bool, -- ^ Bring all exposed modules into scope?
  947     modRenamings :: [(ModuleName, ModuleName)] -- ^ Bring module @m@ into scope
  948                                                --   under name @n@.
  949   } deriving (Eq)
  950 instance Outputable ModRenaming where
  951     ppr (ModRenaming b rns) = ppr b <+> parens (ppr rns)
  952 
  953 -- | Flags for manipulating the set of non-broken packages.
  954 newtype IgnorePackageFlag = IgnorePackage String -- ^ @-ignore-package@
  955   deriving (Eq)
  956 
  957 -- | Flags for manipulating package trust.
  958 data TrustFlag
  959   = TrustPackage    String -- ^ @-trust@
  960   | DistrustPackage String -- ^ @-distrust@
  961   deriving (Eq)
  962 
  963 -- | Flags for manipulating packages visibility.
  964 data PackageFlag
  965   = ExposePackage   String PackageArg ModRenaming -- ^ @-package@, @-package-id@
  966   | HidePackage     String -- ^ @-hide-package@
  967   deriving (Eq) -- NB: equality instance is used by packageFlagsChanged
  968 
  969 data PackageDBFlag
  970   = PackageDB PkgDbRef
  971   | NoUserPackageDB
  972   | NoGlobalPackageDB
  973   | ClearPackageDBs
  974   deriving (Eq)
  975 
  976 packageFlagsChanged :: DynFlags -> DynFlags -> Bool
  977 packageFlagsChanged idflags1 idflags0 =
  978   packageFlags idflags1 /= packageFlags idflags0 ||
  979   ignorePackageFlags idflags1 /= ignorePackageFlags idflags0 ||
  980   pluginPackageFlags idflags1 /= pluginPackageFlags idflags0 ||
  981   trustFlags idflags1 /= trustFlags idflags0 ||
  982   packageDBFlags idflags1 /= packageDBFlags idflags0 ||
  983   packageGFlags idflags1 /= packageGFlags idflags0
  984  where
  985    packageGFlags dflags = map (`gopt` dflags)
  986      [ Opt_HideAllPackages
  987      , Opt_HideAllPluginPackages
  988      , Opt_AutoLinkPackages ]
  989 
  990 instance Outputable PackageFlag where
  991     ppr (ExposePackage n arg rn) = text n <> braces (ppr arg <+> ppr rn)
  992     ppr (HidePackage str) = text "-hide-package" <+> text str
  993 
  994 data DynLibLoader
  995   = Deployable
  996   | SystemDependent
  997   deriving Eq
  998 
  999 data RtsOptsEnabled
 1000   = RtsOptsNone | RtsOptsIgnore | RtsOptsIgnoreAll | RtsOptsSafeOnly
 1001   | RtsOptsAll
 1002   deriving (Show)
 1003 
 1004 -- | Are we building with @-fPIE@ or @-fPIC@ enabled?
 1005 positionIndependent :: DynFlags -> Bool
 1006 positionIndependent dflags = gopt Opt_PIC dflags || gopt Opt_PIE dflags
 1007 
 1008 -- Note [-dynamic-too business]
 1009 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 1010 --
 1011 -- With -dynamic-too flag, we try to build both the non-dynamic and dynamic
 1012 -- objects in a single run of the compiler: the pipeline is the same down to
 1013 -- Core optimisation, then the backend (from Core to object code) is executed
 1014 -- twice.
 1015 --
 1016 -- The implementation is currently rather hacky, for example, we don't clearly separate non-dynamic
 1017 -- and dynamic loaded interfaces (#9176).
 1018 --
 1019 -- To make matters worse, we automatically enable -dynamic-too when some modules
 1020 -- need Template-Haskell and GHC is dynamically linked (cf
 1021 -- GHC.Driver.Pipeline.compileOne').
 1022 --
 1023 -- We used to try and fall back from a dynamic-too failure but this feature
 1024 -- didn't work as expected (#20446) so it was removed to simplify the
 1025 -- implementation and not obscure latent bugs.
 1026 
 1027 data DynamicTooState
 1028    = DT_Dont    -- ^ Don't try to build dynamic objects too
 1029    | DT_OK      -- ^ Will still try to generate dynamic objects
 1030    | DT_Dyn     -- ^ Currently generating dynamic objects (in the backend)
 1031    deriving (Eq,Show,Ord)
 1032 
 1033 dynamicTooState :: DynFlags -> DynamicTooState
 1034 dynamicTooState dflags
 1035    | not (gopt Opt_BuildDynamicToo dflags) = DT_Dont
 1036    | dynamicNow dflags = DT_Dyn
 1037    | otherwise = DT_OK
 1038 
 1039 setDynamicNow :: DynFlags -> DynFlags
 1040 setDynamicNow dflags0 =
 1041    dflags0
 1042       { dynamicNow = True
 1043       }
 1044 
 1045 -----------------------------------------------------------------------------
 1046 
 1047 -- | Used by 'GHC.runGhc' to partially initialize a new 'DynFlags' value
 1048 initDynFlags :: DynFlags -> IO DynFlags
 1049 initDynFlags dflags = do
 1050  let
 1051  refRtldInfo <- newIORef Nothing
 1052  refRtccInfo <- newIORef Nothing
 1053  refRtasmInfo <- newIORef Nothing
 1054  canUseUnicode <- do let enc = localeEncoding
 1055                          str = "‘’"
 1056                      (withCString enc str $ \cstr ->
 1057                           do str' <- peekCString enc cstr
 1058                              return (str == str'))
 1059                          `catchIOError` \_ -> return False
 1060  ghcNoUnicodeEnv <- lookupEnv "GHC_NO_UNICODE"
 1061  let useUnicode' = isNothing ghcNoUnicodeEnv && canUseUnicode
 1062  maybeGhcColorsEnv  <- lookupEnv "GHC_COLORS"
 1063  maybeGhcColoursEnv <- lookupEnv "GHC_COLOURS"
 1064  let adjustCols (Just env) = Col.parseScheme env
 1065      adjustCols Nothing    = id
 1066  let (useColor', colScheme') =
 1067        (adjustCols maybeGhcColoursEnv . adjustCols maybeGhcColorsEnv)
 1068        (useColor dflags, colScheme dflags)
 1069  tmp_dir <- normalise <$> getTemporaryDirectory
 1070  return dflags{
 1071         useUnicode    = useUnicode',
 1072         useColor      = useColor',
 1073         canUseColor   = stderrSupportsAnsiColors,
 1074         colScheme     = colScheme',
 1075         rtldInfo      = refRtldInfo,
 1076         rtccInfo      = refRtccInfo,
 1077         rtasmInfo     = refRtasmInfo,
 1078         tmpDir        = TempDir tmp_dir
 1079         }
 1080 
 1081 -- | The normal 'DynFlags'. Note that they are not suitable for use in this form
 1082 -- and must be fully initialized by 'GHC.runGhc' first.
 1083 defaultDynFlags :: Settings -> LlvmConfig -> DynFlags
 1084 defaultDynFlags mySettings llvmConfig =
 1085 -- See Note [Updating flag description in the User's Guide]
 1086      DynFlags {
 1087         ghcMode                 = CompManager,
 1088         ghcLink                 = LinkBinary,
 1089         backend                 = platformDefaultBackend (sTargetPlatform mySettings),
 1090         verbosity               = 0,
 1091         optLevel                = 0,
 1092         debugLevel              = 0,
 1093         simplPhases             = 2,
 1094         maxSimplIterations      = 4,
 1095         ruleCheck               = Nothing,
 1096         binBlobThreshold        = 500000, -- 500K is a good default (see #16190)
 1097         maxRelevantBinds        = Just 6,
 1098         maxValidHoleFits   = Just 6,
 1099         maxRefHoleFits     = Just 6,
 1100         refLevelHoleFits   = Nothing,
 1101         maxUncoveredPatterns    = 4,
 1102         maxPmCheckModels        = 30,
 1103         simplTickFactor         = 100,
 1104         dmdUnboxWidth           = 3,      -- Default: Assume an unboxed demand on function bodies returning a triple
 1105         specConstrThreshold     = Just 2000,
 1106         specConstrCount         = Just 3,
 1107         specConstrRecursive     = 3,
 1108         liberateCaseThreshold   = Just 2000,
 1109         floatLamArgs            = Just 0, -- Default: float only if no fvs
 1110         liftLamsRecArgs         = Just 5, -- Default: the number of available argument hardware registers on x86_64
 1111         liftLamsNonRecArgs      = Just 5, -- Default: the number of available argument hardware registers on x86_64
 1112         liftLamsKnown           = False,  -- Default: don't turn known calls into unknown ones
 1113         cmmProcAlignment        = Nothing,
 1114 
 1115         historySize             = 20,
 1116         strictnessBefore        = [],
 1117 
 1118         parMakeCount            = Just 1,
 1119 
 1120         enableTimeStats         = False,
 1121         ghcHeapSize             = Nothing,
 1122 
 1123         importPaths             = ["."],
 1124         mainModuleNameIs        = mAIN_NAME,
 1125         mainFunIs               = Nothing,
 1126         reductionDepth          = treatZeroAsInf mAX_REDUCTION_DEPTH,
 1127         solverIterations        = treatZeroAsInf mAX_SOLVER_ITERATIONS,
 1128 
 1129         homeUnitId_             = mainUnitId,
 1130         homeUnitInstanceOf_     = Nothing,
 1131         homeUnitInstantiations_ = [],
 1132 
 1133         objectDir               = Nothing,
 1134         dylibInstallName        = Nothing,
 1135         hiDir                   = Nothing,
 1136         hieDir                  = Nothing,
 1137         stubDir                 = Nothing,
 1138         dumpDir                 = Nothing,
 1139 
 1140         objectSuf_              = phaseInputExt StopLn,
 1141         hcSuf                   = phaseInputExt HCc,
 1142         hiSuf_                  = "hi",
 1143         hieSuf                  = "hie",
 1144 
 1145         dynObjectSuf_           = "dyn_" ++ phaseInputExt StopLn,
 1146         dynHiSuf_               = "dyn_hi",
 1147         dynamicNow              = False,
 1148 
 1149         pluginModNames          = [],
 1150         pluginModNameOpts       = [],
 1151         frontendPluginOpts      = [],
 1152 
 1153         outputFile_             = Nothing,
 1154         dynOutputFile_          = Nothing,
 1155         outputHi                = Nothing,
 1156         dynOutputHi             = Nothing,
 1157         dynLibLoader            = SystemDependent,
 1158         dumpPrefix              = Nothing,
 1159         dumpPrefixForce         = Nothing,
 1160         ldInputs                = [],
 1161         includePaths            = IncludeSpecs [] [] [],
 1162         libraryPaths            = [],
 1163         frameworkPaths          = [],
 1164         cmdlineFrameworks       = [],
 1165         rtsOpts                 = Nothing,
 1166         rtsOptsEnabled          = RtsOptsSafeOnly,
 1167         rtsOptsSuggestions      = True,
 1168 
 1169         hpcDir                  = ".hpc",
 1170 
 1171         packageDBFlags          = [],
 1172         packageFlags            = [],
 1173         pluginPackageFlags      = [],
 1174         ignorePackageFlags      = [],
 1175         trustFlags              = [],
 1176         packageEnv              = Nothing,
 1177         targetWays_             = Set.empty,
 1178         splitInfo               = Nothing,
 1179 
 1180         ghcNameVersion = sGhcNameVersion mySettings,
 1181         fileSettings = sFileSettings mySettings,
 1182         toolSettings = sToolSettings mySettings,
 1183         targetPlatform = sTargetPlatform mySettings,
 1184         platformMisc = sPlatformMisc mySettings,
 1185         rawSettings = sRawSettings mySettings,
 1186 
 1187         tmpDir                  = panic "defaultDynFlags: uninitialized tmpDir",
 1188 
 1189         -- See Note [LLVM configuration].
 1190         llvmConfig              = llvmConfig,
 1191 
 1192         -- ghc -M values
 1193         depMakefile       = "Makefile",
 1194         depIncludePkgDeps = False,
 1195         depIncludeCppDeps = False,
 1196         depExcludeMods    = [],
 1197         depSuffixes       = [],
 1198         -- end of ghc -M values
 1199         ghcVersionFile = Nothing,
 1200         haddockOptions = Nothing,
 1201         dumpFlags = EnumSet.empty,
 1202         generalFlags = EnumSet.fromList (defaultFlags mySettings),
 1203         warningFlags = EnumSet.fromList standardWarnings,
 1204         fatalWarningFlags = EnumSet.empty,
 1205         ghciScripts = [],
 1206         language = Nothing,
 1207         safeHaskell = Sf_None,
 1208         safeInfer   = True,
 1209         safeInferred = True,
 1210         thOnLoc = noSrcSpan,
 1211         newDerivOnLoc = noSrcSpan,
 1212         deriveViaOnLoc = noSrcSpan,
 1213         overlapInstLoc = noSrcSpan,
 1214         incoherentOnLoc = noSrcSpan,
 1215         pkgTrustOnLoc = noSrcSpan,
 1216         warnSafeOnLoc = noSrcSpan,
 1217         warnUnsafeOnLoc = noSrcSpan,
 1218         trustworthyOnLoc = noSrcSpan,
 1219         extensions = [],
 1220         extensionFlags = flattenExtensionFlags Nothing [],
 1221 
 1222         unfoldingOpts = defaultUnfoldingOpts,
 1223         maxWorkerArgs = 10,
 1224 
 1225         ghciHistSize = 50, -- keep a log of length 50 by default
 1226 
 1227         flushOut = defaultFlushOut,
 1228         pprUserLength = 5,
 1229         pprCols = 100,
 1230         useUnicode = False,
 1231         useColor = Auto,
 1232         canUseColor = False,
 1233         colScheme = Col.defaultScheme,
 1234         profAuto = NoProfAuto,
 1235         callerCcFilters = [],
 1236         interactivePrint = Nothing,
 1237         sseVersion = Nothing,
 1238         bmiVersion = Nothing,
 1239         avx = False,
 1240         avx2 = False,
 1241         avx512cd = False,
 1242         avx512er = False,
 1243         avx512f = False,
 1244         avx512pf = False,
 1245         rtldInfo = panic "defaultDynFlags: no rtldInfo",
 1246         rtccInfo = panic "defaultDynFlags: no rtccInfo",
 1247         rtasmInfo = panic "defaultDynFlags: no rtasmInfo",
 1248 
 1249         maxInlineAllocSize = 128,
 1250         maxInlineMemcpyInsns = 32,
 1251         maxInlineMemsetInsns = 32,
 1252 
 1253         initialUnique = 0,
 1254         uniqueIncrement = 1,
 1255 
 1256         reverseErrors = False,
 1257         maxErrors     = Nothing,
 1258         cfgWeights    = defaultWeights
 1259       }
 1260 
 1261 type FatalMessager = String -> IO ()
 1262 
 1263 defaultFatalMessager :: FatalMessager
 1264 defaultFatalMessager = hPutStrLn stderr
 1265 
 1266 
 1267 newtype FlushOut = FlushOut (IO ())
 1268 
 1269 defaultFlushOut :: FlushOut
 1270 defaultFlushOut = FlushOut $ hFlush stdout
 1271 
 1272 {-
 1273 Note [Verbosity levels]
 1274 ~~~~~~~~~~~~~~~~~~~~~~~
 1275     0   |   print errors & warnings only
 1276     1   |   minimal verbosity: print "compiling M ... done." for each module.
 1277     2   |   equivalent to -dshow-passes
 1278     3   |   equivalent to existing "ghc -v"
 1279     4   |   "ghc -v -ddump-most"
 1280     5   |   "ghc -v -ddump-all"
 1281 -}
 1282 
 1283 data OnOff a = On a
 1284              | Off a
 1285   deriving (Eq, Show)
 1286 
 1287 instance Outputable a => Outputable (OnOff a) where
 1288   ppr (On x)  = text "On" <+> ppr x
 1289   ppr (Off x) = text "Off" <+> ppr x
 1290 
 1291 -- OnOffs accumulate in reverse order, so we use foldr in order to
 1292 -- process them in the right order
 1293 flattenExtensionFlags :: Maybe Language -> [OnOff LangExt.Extension] -> EnumSet LangExt.Extension
 1294 flattenExtensionFlags ml = foldr f defaultExtensionFlags
 1295     where f (On f)  flags = EnumSet.insert f flags
 1296           f (Off f) flags = EnumSet.delete f flags
 1297           defaultExtensionFlags = EnumSet.fromList (languageExtensions ml)
 1298 
 1299 -- | The language extensions implied by the various language variants.
 1300 -- When updating this be sure to update the flag documentation in
 1301 -- @docs/users_guide/exts@.
 1302 languageExtensions :: Maybe Language -> [LangExt.Extension]
 1303 
 1304 -- Nothing: the default case
 1305 languageExtensions Nothing = languageExtensions (Just GHC2021)
 1306 
 1307 languageExtensions (Just Haskell98)
 1308     = [LangExt.ImplicitPrelude,
 1309        -- See Note [When is StarIsType enabled]
 1310        LangExt.StarIsType,
 1311        LangExt.CUSKs,
 1312        LangExt.MonomorphismRestriction,
 1313        LangExt.NPlusKPatterns,
 1314        LangExt.DatatypeContexts,
 1315        LangExt.TraditionalRecordSyntax,
 1316        LangExt.FieldSelectors,
 1317        LangExt.NondecreasingIndentation
 1318            -- strictly speaking non-standard, but we always had this
 1319            -- on implicitly before the option was added in 7.1, and
 1320            -- turning it off breaks code, so we're keeping it on for
 1321            -- backwards compatibility.  Cabal uses -XHaskell98 by
 1322            -- default unless you specify another language.
 1323       ]
 1324 
 1325 languageExtensions (Just Haskell2010)
 1326     = [LangExt.ImplicitPrelude,
 1327        -- See Note [When is StarIsType enabled]
 1328        LangExt.StarIsType,
 1329        LangExt.CUSKs,
 1330        LangExt.MonomorphismRestriction,
 1331        LangExt.DatatypeContexts,
 1332        LangExt.TraditionalRecordSyntax,
 1333        LangExt.EmptyDataDecls,
 1334        LangExt.ForeignFunctionInterface,
 1335        LangExt.PatternGuards,
 1336        LangExt.DoAndIfThenElse,
 1337        LangExt.FieldSelectors,
 1338        LangExt.RelaxedPolyRec]
 1339 
 1340 languageExtensions (Just GHC2021)
 1341     = [LangExt.ImplicitPrelude,
 1342        -- See Note [When is StarIsType enabled]
 1343        LangExt.StarIsType,
 1344        LangExt.MonomorphismRestriction,
 1345        LangExt.TraditionalRecordSyntax,
 1346        LangExt.EmptyDataDecls,
 1347        LangExt.ForeignFunctionInterface,
 1348        LangExt.PatternGuards,
 1349        LangExt.DoAndIfThenElse,
 1350        LangExt.FieldSelectors,
 1351        LangExt.RelaxedPolyRec,
 1352        -- Now the new extensions (not in Haskell2010)
 1353        LangExt.BangPatterns,
 1354        LangExt.BinaryLiterals,
 1355        LangExt.ConstrainedClassMethods,
 1356        LangExt.ConstraintKinds,
 1357        LangExt.DeriveDataTypeable,
 1358        LangExt.DeriveFoldable,
 1359        LangExt.DeriveFunctor,
 1360        LangExt.DeriveGeneric,
 1361        LangExt.DeriveLift,
 1362        LangExt.DeriveTraversable,
 1363        LangExt.EmptyCase,
 1364        LangExt.EmptyDataDeriving,
 1365        LangExt.ExistentialQuantification,
 1366        LangExt.ExplicitForAll,
 1367        LangExt.FlexibleContexts,
 1368        LangExt.FlexibleInstances,
 1369        LangExt.GADTSyntax,
 1370        LangExt.GeneralizedNewtypeDeriving,
 1371        LangExt.HexFloatLiterals,
 1372        LangExt.ImportQualifiedPost,
 1373        LangExt.InstanceSigs,
 1374        LangExt.KindSignatures,
 1375        LangExt.MultiParamTypeClasses,
 1376        LangExt.NamedFieldPuns,
 1377        LangExt.NamedWildCards,
 1378        LangExt.NumericUnderscores,
 1379        LangExt.PolyKinds,
 1380        LangExt.PostfixOperators,
 1381        LangExt.RankNTypes,
 1382        LangExt.ScopedTypeVariables,
 1383        LangExt.StandaloneDeriving,
 1384        LangExt.StandaloneKindSignatures,
 1385        LangExt.TupleSections,
 1386        LangExt.TypeApplications,
 1387        LangExt.TypeOperators,
 1388        LangExt.TypeSynonymInstances]
 1389 
 1390 hasPprDebug :: DynFlags -> Bool
 1391 hasPprDebug = dopt Opt_D_ppr_debug
 1392 
 1393 hasNoDebugOutput :: DynFlags -> Bool
 1394 hasNoDebugOutput = dopt Opt_D_no_debug_output
 1395 
 1396 hasNoStateHack :: DynFlags -> Bool
 1397 hasNoStateHack = gopt Opt_G_NoStateHack
 1398 
 1399 hasNoOptCoercion :: DynFlags -> Bool
 1400 hasNoOptCoercion = gopt Opt_G_NoOptCoercion
 1401 
 1402 
 1403 -- | Test whether a 'DumpFlag' is set
 1404 dopt :: DumpFlag -> DynFlags -> Bool
 1405 dopt f dflags = (f `EnumSet.member` dumpFlags dflags)
 1406              || (verbosity dflags >= 4 && enableIfVerbose f)
 1407     where enableIfVerbose Opt_D_dump_tc_trace               = False
 1408           enableIfVerbose Opt_D_dump_rn_trace               = False
 1409           enableIfVerbose Opt_D_dump_cs_trace               = False
 1410           enableIfVerbose Opt_D_dump_if_trace               = False
 1411           enableIfVerbose Opt_D_dump_tc                     = False
 1412           enableIfVerbose Opt_D_dump_rn                     = False
 1413           enableIfVerbose Opt_D_dump_rn_stats               = False
 1414           enableIfVerbose Opt_D_dump_hi_diffs               = False
 1415           enableIfVerbose Opt_D_verbose_core2core           = False
 1416           enableIfVerbose Opt_D_verbose_stg2stg             = False
 1417           enableIfVerbose Opt_D_dump_splices                = False
 1418           enableIfVerbose Opt_D_th_dec_file                 = False
 1419           enableIfVerbose Opt_D_dump_rule_firings           = False
 1420           enableIfVerbose Opt_D_dump_rule_rewrites          = False
 1421           enableIfVerbose Opt_D_dump_simpl_trace            = False
 1422           enableIfVerbose Opt_D_dump_rtti                   = False
 1423           enableIfVerbose Opt_D_dump_inlinings              = False
 1424           enableIfVerbose Opt_D_dump_verbose_inlinings      = False
 1425           enableIfVerbose Opt_D_dump_core_stats             = False
 1426           enableIfVerbose Opt_D_dump_asm_stats              = False
 1427           enableIfVerbose Opt_D_dump_types                  = False
 1428           enableIfVerbose Opt_D_dump_simpl_iterations       = False
 1429           enableIfVerbose Opt_D_dump_ticked                 = False
 1430           enableIfVerbose Opt_D_dump_view_pattern_commoning = False
 1431           enableIfVerbose Opt_D_dump_mod_cycles             = False
 1432           enableIfVerbose Opt_D_dump_mod_map                = False
 1433           enableIfVerbose Opt_D_dump_ec_trace               = False
 1434           enableIfVerbose _                                 = True
 1435 
 1436 -- | Set a 'DumpFlag'
 1437 dopt_set :: DynFlags -> DumpFlag -> DynFlags
 1438 dopt_set dfs f = dfs{ dumpFlags = EnumSet.insert f (dumpFlags dfs) }
 1439 
 1440 -- | Unset a 'DumpFlag'
 1441 dopt_unset :: DynFlags -> DumpFlag -> DynFlags
 1442 dopt_unset dfs f = dfs{ dumpFlags = EnumSet.delete f (dumpFlags dfs) }
 1443 
 1444 -- | Test whether a 'GeneralFlag' is set
 1445 --
 1446 -- Note that `dynamicNow` (i.e., dynamic objects built with `-dynamic-too`)
 1447 -- always implicitly enables Opt_PIC, Opt_ExternalDynamicRefs, and disables
 1448 -- Opt_SplitSections.
 1449 --
 1450 gopt :: GeneralFlag -> DynFlags -> Bool
 1451 gopt Opt_PIC dflags
 1452    | dynamicNow dflags = True
 1453 gopt Opt_ExternalDynamicRefs dflags
 1454    | dynamicNow dflags = True
 1455 gopt Opt_SplitSections dflags
 1456    | dynamicNow dflags = False
 1457 gopt f dflags = f `EnumSet.member` generalFlags dflags
 1458 
 1459 -- | Set a 'GeneralFlag'
 1460 gopt_set :: DynFlags -> GeneralFlag -> DynFlags
 1461 gopt_set dfs f = dfs{ generalFlags = EnumSet.insert f (generalFlags dfs) }
 1462 
 1463 -- | Unset a 'GeneralFlag'
 1464 gopt_unset :: DynFlags -> GeneralFlag -> DynFlags
 1465 gopt_unset dfs f = dfs{ generalFlags = EnumSet.delete f (generalFlags dfs) }
 1466 
 1467 -- | Test whether a 'WarningFlag' is set
 1468 wopt :: WarningFlag -> DynFlags -> Bool
 1469 wopt f dflags  = f `EnumSet.member` warningFlags dflags
 1470 
 1471 -- | Set a 'WarningFlag'
 1472 wopt_set :: DynFlags -> WarningFlag -> DynFlags
 1473 wopt_set dfs f = dfs{ warningFlags = EnumSet.insert f (warningFlags dfs) }
 1474 
 1475 -- | Unset a 'WarningFlag'
 1476 wopt_unset :: DynFlags -> WarningFlag -> DynFlags
 1477 wopt_unset dfs f = dfs{ warningFlags = EnumSet.delete f (warningFlags dfs) }
 1478 
 1479 -- | Test whether a 'WarningFlag' is set as fatal
 1480 wopt_fatal :: WarningFlag -> DynFlags -> Bool
 1481 wopt_fatal f dflags = f `EnumSet.member` fatalWarningFlags dflags
 1482 
 1483 -- | Mark a 'WarningFlag' as fatal (do not set the flag)
 1484 wopt_set_fatal :: DynFlags -> WarningFlag -> DynFlags
 1485 wopt_set_fatal dfs f
 1486     = dfs { fatalWarningFlags = EnumSet.insert f (fatalWarningFlags dfs) }
 1487 
 1488 -- | Mark a 'WarningFlag' as not fatal
 1489 wopt_unset_fatal :: DynFlags -> WarningFlag -> DynFlags
 1490 wopt_unset_fatal dfs f
 1491     = dfs { fatalWarningFlags = EnumSet.delete f (fatalWarningFlags dfs) }
 1492 
 1493 -- | Test whether a 'LangExt.Extension' is set
 1494 xopt :: LangExt.Extension -> DynFlags -> Bool
 1495 xopt f dflags = f `EnumSet.member` extensionFlags dflags
 1496 
 1497 -- | Set a 'LangExt.Extension'
 1498 xopt_set :: DynFlags -> LangExt.Extension -> DynFlags
 1499 xopt_set dfs f
 1500     = let onoffs = On f : extensions dfs
 1501       in dfs { extensions = onoffs,
 1502                extensionFlags = flattenExtensionFlags (language dfs) onoffs }
 1503 
 1504 -- | Unset a 'LangExt.Extension'
 1505 xopt_unset :: DynFlags -> LangExt.Extension -> DynFlags
 1506 xopt_unset dfs f
 1507     = let onoffs = Off f : extensions dfs
 1508       in dfs { extensions = onoffs,
 1509                extensionFlags = flattenExtensionFlags (language dfs) onoffs }
 1510 
 1511 -- | Set or unset a 'LangExt.Extension', unless it has been explicitly
 1512 --   set or unset before.
 1513 xopt_set_unlessExplSpec
 1514         :: LangExt.Extension
 1515         -> (DynFlags -> LangExt.Extension -> DynFlags)
 1516         -> DynFlags -> DynFlags
 1517 xopt_set_unlessExplSpec ext setUnset dflags =
 1518     let referedExts = stripOnOff <$> extensions dflags
 1519         stripOnOff (On x)  = x
 1520         stripOnOff (Off x) = x
 1521     in
 1522         if ext `elem` referedExts then dflags else setUnset dflags ext
 1523 
 1524 xopt_DuplicateRecordFields :: DynFlags -> FieldLabel.DuplicateRecordFields
 1525 xopt_DuplicateRecordFields dfs
 1526   | xopt LangExt.DuplicateRecordFields dfs = FieldLabel.DuplicateRecordFields
 1527   | otherwise                              = FieldLabel.NoDuplicateRecordFields
 1528 
 1529 xopt_FieldSelectors :: DynFlags -> FieldLabel.FieldSelectors
 1530 xopt_FieldSelectors dfs
 1531   | xopt LangExt.FieldSelectors dfs = FieldLabel.FieldSelectors
 1532   | otherwise                       = FieldLabel.NoFieldSelectors
 1533 
 1534 lang_set :: DynFlags -> Maybe Language -> DynFlags
 1535 lang_set dflags lang =
 1536    dflags {
 1537             language = lang,
 1538             extensionFlags = flattenExtensionFlags lang (extensions dflags)
 1539           }
 1540 
 1541 -- | Set the Haskell language standard to use
 1542 setLanguage :: Language -> DynP ()
 1543 setLanguage l = upd (`lang_set` Just l)
 1544 
 1545 -- | Is the -fpackage-trust mode on
 1546 packageTrustOn :: DynFlags -> Bool
 1547 packageTrustOn = gopt Opt_PackageTrust
 1548 
 1549 -- | Is Safe Haskell on in some way (including inference mode)
 1550 safeHaskellOn :: DynFlags -> Bool
 1551 safeHaskellOn dflags = safeHaskellModeEnabled dflags || safeInferOn dflags
 1552 
 1553 safeHaskellModeEnabled :: DynFlags -> Bool
 1554 safeHaskellModeEnabled dflags = safeHaskell dflags `elem` [Sf_Unsafe, Sf_Trustworthy
 1555                                                    , Sf_Safe ]
 1556 
 1557 
 1558 -- | Is the Safe Haskell safe language in use
 1559 safeLanguageOn :: DynFlags -> Bool
 1560 safeLanguageOn dflags = safeHaskell dflags == Sf_Safe
 1561 
 1562 -- | Is the Safe Haskell safe inference mode active
 1563 safeInferOn :: DynFlags -> Bool
 1564 safeInferOn = safeInfer
 1565 
 1566 -- | Test if Safe Imports are on in some form
 1567 safeImportsOn :: DynFlags -> Bool
 1568 safeImportsOn dflags = safeHaskell dflags == Sf_Unsafe ||
 1569                        safeHaskell dflags == Sf_Trustworthy ||
 1570                        safeHaskell dflags == Sf_Safe
 1571 
 1572 -- | Set a 'Safe Haskell' flag
 1573 setSafeHaskell :: SafeHaskellMode -> DynP ()
 1574 setSafeHaskell s = updM f
 1575     where f dfs = do
 1576               let sf = safeHaskell dfs
 1577               safeM <- combineSafeFlags sf s
 1578               case s of
 1579                 Sf_Safe -> return $ dfs { safeHaskell = safeM, safeInfer = False }
 1580                 -- leave safe inferrence on in Trustworthy mode so we can warn
 1581                 -- if it could have been inferred safe.
 1582                 Sf_Trustworthy -> do
 1583                   l <- getCurLoc
 1584                   return $ dfs { safeHaskell = safeM, trustworthyOnLoc = l }
 1585                 -- leave safe inference on in Unsafe mode as well.
 1586                 _ -> return $ dfs { safeHaskell = safeM }
 1587 
 1588 -- | Are all direct imports required to be safe for this Safe Haskell mode?
 1589 -- Direct imports are when the code explicitly imports a module
 1590 safeDirectImpsReq :: DynFlags -> Bool
 1591 safeDirectImpsReq d = safeLanguageOn d
 1592 
 1593 -- | Are all implicit imports required to be safe for this Safe Haskell mode?
 1594 -- Implicit imports are things in the prelude. e.g System.IO when print is used.
 1595 safeImplicitImpsReq :: DynFlags -> Bool
 1596 safeImplicitImpsReq d = safeLanguageOn d
 1597 
 1598 -- | Combine two Safe Haskell modes correctly. Used for dealing with multiple flags.
 1599 -- This makes Safe Haskell very much a monoid but for now I prefer this as I don't
 1600 -- want to export this functionality from the module but do want to export the
 1601 -- type constructors.
 1602 combineSafeFlags :: SafeHaskellMode -> SafeHaskellMode -> DynP SafeHaskellMode
 1603 combineSafeFlags a b | a == Sf_None         = return b
 1604                      | b == Sf_None         = return a
 1605                      | a == Sf_Ignore || b == Sf_Ignore = return Sf_Ignore
 1606                      | a == b               = return a
 1607                      | otherwise            = addErr errm >> pure a
 1608     where errm = "Incompatible Safe Haskell flags! ("
 1609                     ++ show a ++ ", " ++ show b ++ ")"
 1610 
 1611 -- | A list of unsafe flags under Safe Haskell. Tuple elements are:
 1612 --     * name of the flag
 1613 --     * function to get srcspan that enabled the flag
 1614 --     * function to test if the flag is on
 1615 --     * function to turn the flag off
 1616 unsafeFlags, unsafeFlagsForInfer
 1617   :: [(String, DynFlags -> SrcSpan, DynFlags -> Bool, DynFlags -> DynFlags)]
 1618 unsafeFlags = [ ("-XGeneralizedNewtypeDeriving", newDerivOnLoc,
 1619                     xopt LangExt.GeneralizedNewtypeDeriving,
 1620                     flip xopt_unset LangExt.GeneralizedNewtypeDeriving)
 1621               , ("-XDerivingVia", deriveViaOnLoc,
 1622                     xopt LangExt.DerivingVia,
 1623                     flip xopt_unset LangExt.DerivingVia)
 1624               , ("-XTemplateHaskell", thOnLoc,
 1625                     xopt LangExt.TemplateHaskell,
 1626                     flip xopt_unset LangExt.TemplateHaskell)
 1627               ]
 1628 unsafeFlagsForInfer = unsafeFlags
 1629 
 1630 
 1631 -- | Retrieve the options corresponding to a particular @opt_*@ field in the correct order
 1632 getOpts :: DynFlags             -- ^ 'DynFlags' to retrieve the options from
 1633         -> (DynFlags -> [a])    -- ^ Relevant record accessor: one of the @opt_*@ accessors
 1634         -> [a]                  -- ^ Correctly ordered extracted options
 1635 getOpts dflags opts = reverse (opts dflags)
 1636         -- We add to the options from the front, so we need to reverse the list
 1637 
 1638 -- | Gets the verbosity flag for the current verbosity level. This is fed to
 1639 -- other tools, so GHC-specific verbosity flags like @-ddump-most@ are not included
 1640 getVerbFlags :: DynFlags -> [String]
 1641 getVerbFlags dflags
 1642   | verbosity dflags >= 4 = ["-v"]
 1643   | otherwise             = []
 1644 
 1645 setObjectDir, setHiDir, setHieDir, setStubDir, setDumpDir, setOutputDir,
 1646          setDynObjectSuf, setDynHiSuf,
 1647          setDylibInstallName,
 1648          setObjectSuf, setHiSuf, setHieSuf, setHcSuf, parseDynLibLoaderMode,
 1649          setPgmP, addOptl, addOptc, addOptcxx, addOptP,
 1650          addCmdlineFramework, addHaddockOpts, addGhciScript,
 1651          setInteractivePrint
 1652    :: String -> DynFlags -> DynFlags
 1653 setOutputFile, setDynOutputFile, setOutputHi, setDynOutputHi, setDumpPrefixForce
 1654    :: Maybe String -> DynFlags -> DynFlags
 1655 
 1656 setObjectDir  f d = d { objectDir  = Just f}
 1657 setHiDir      f d = d { hiDir      = Just f}
 1658 setHieDir     f d = d { hieDir     = Just f}
 1659 setStubDir    f d = d { stubDir    = Just f
 1660                       , includePaths = addGlobalInclude (includePaths d) [f] }
 1661   -- -stubdir D adds an implicit -I D, so that gcc can find the _stub.h file
 1662   -- \#included from the .hc file when compiling via C (i.e. unregisterised
 1663   -- builds).
 1664 setDumpDir    f d = d { dumpDir    = Just f}
 1665 setOutputDir  f = setObjectDir f
 1666                 . setHieDir f
 1667                 . setHiDir f
 1668                 . setStubDir f
 1669                 . setDumpDir f
 1670 setDylibInstallName  f d = d { dylibInstallName = Just f}
 1671 
 1672 setObjectSuf    f d = d { objectSuf_    = f}
 1673 setDynObjectSuf f d = d { dynObjectSuf_ = f}
 1674 setHiSuf        f d = d { hiSuf_        = f}
 1675 setHieSuf       f d = d { hieSuf        = f}
 1676 setDynHiSuf     f d = d { dynHiSuf_     = f}
 1677 setHcSuf        f d = d { hcSuf         = f}
 1678 
 1679 setOutputFile    f d = d { outputFile_    = f}
 1680 setDynOutputFile f d = d { dynOutputFile_ = f}
 1681 setOutputHi      f d = d { outputHi       = f}
 1682 setDynOutputHi   f d = d { dynOutputHi    = f}
 1683 
 1684 parseUnitInsts :: String -> Instantiations
 1685 parseUnitInsts str = case filter ((=="").snd) (readP_to_S parse str) of
 1686     [(r, "")] -> r
 1687     _ -> throwGhcException $ CmdLineError ("Can't parse -instantiated-with: " ++ str)
 1688   where parse = sepBy parseEntry (R.char ',')
 1689         parseEntry = do
 1690             n <- parseModuleName
 1691             _ <- R.char '='
 1692             m <- parseHoleyModule
 1693             return (n, m)
 1694 
 1695 setUnitInstantiations :: String -> DynFlags -> DynFlags
 1696 setUnitInstantiations s d =
 1697     d { homeUnitInstantiations_ = parseUnitInsts s }
 1698 
 1699 setUnitInstanceOf :: String -> DynFlags -> DynFlags
 1700 setUnitInstanceOf s d =
 1701     d { homeUnitInstanceOf_ = Just (UnitId (fsLit s)) }
 1702 
 1703 addPluginModuleName :: String -> DynFlags -> DynFlags
 1704 addPluginModuleName name d = d { pluginModNames = (mkModuleName name) : (pluginModNames d) }
 1705 
 1706 clearPluginModuleNames :: DynFlags -> DynFlags
 1707 clearPluginModuleNames d =
 1708     d { pluginModNames = []
 1709       , pluginModNameOpts = []
 1710       }
 1711 
 1712 addPluginModuleNameOption :: String -> DynFlags -> DynFlags
 1713 addPluginModuleNameOption optflag d = d { pluginModNameOpts = (mkModuleName m, option) : (pluginModNameOpts d) }
 1714   where (m, rest) = break (== ':') optflag
 1715         option = case rest of
 1716           [] -> "" -- should probably signal an error
 1717           (_:plug_opt) -> plug_opt -- ignore the ':' from break
 1718 
 1719 addFrontendPluginOption :: String -> DynFlags -> DynFlags
 1720 addFrontendPluginOption s d = d { frontendPluginOpts = s : frontendPluginOpts d }
 1721 
 1722 parseDynLibLoaderMode f d =
 1723  case splitAt 8 f of
 1724    ("deploy", "")       -> d { dynLibLoader = Deployable }
 1725    ("sysdep", "")       -> d { dynLibLoader = SystemDependent }
 1726    _                    -> throwGhcException (CmdLineError ("Unknown dynlib loader: " ++ f))
 1727 
 1728 setDumpPrefixForce f d = d { dumpPrefixForce = f}
 1729 
 1730 -- XXX HACK: Prelude> words "'does not' work" ===> ["'does","not'","work"]
 1731 -- Config.hs should really use Option.
 1732 setPgmP   f = alterToolSettings (\s -> s { toolSettings_pgm_P   = (pgm, map Option args)})
 1733   where (pgm:args) = words f
 1734 addOptl   f = alterToolSettings (\s -> s { toolSettings_opt_l   = f : toolSettings_opt_l s})
 1735 addOptc   f = alterToolSettings (\s -> s { toolSettings_opt_c   = f : toolSettings_opt_c s})
 1736 addOptcxx f = alterToolSettings (\s -> s { toolSettings_opt_cxx = f : toolSettings_opt_cxx s})
 1737 addOptP   f = alterToolSettings $ \s -> s
 1738           { toolSettings_opt_P   = f : toolSettings_opt_P s
 1739           , toolSettings_opt_P_fingerprint = fingerprintStrings (f : toolSettings_opt_P s)
 1740           }
 1741           -- See Note [Repeated -optP hashing]
 1742   where
 1743   fingerprintStrings ss = fingerprintFingerprints $ map fingerprintString ss
 1744 
 1745 
 1746 setDepMakefile :: FilePath -> DynFlags -> DynFlags
 1747 setDepMakefile f d = d { depMakefile = f }
 1748 
 1749 setDepIncludeCppDeps :: Bool -> DynFlags -> DynFlags
 1750 setDepIncludeCppDeps b d = d { depIncludeCppDeps = b }
 1751 
 1752 setDepIncludePkgDeps :: Bool -> DynFlags -> DynFlags
 1753 setDepIncludePkgDeps b d = d { depIncludePkgDeps = b }
 1754 
 1755 addDepExcludeMod :: String -> DynFlags -> DynFlags
 1756 addDepExcludeMod m d
 1757     = d { depExcludeMods = mkModuleName m : depExcludeMods d }
 1758 
 1759 addDepSuffix :: FilePath -> DynFlags -> DynFlags
 1760 addDepSuffix s d = d { depSuffixes = s : depSuffixes d }
 1761 
 1762 addCmdlineFramework f d = d { cmdlineFrameworks = f : cmdlineFrameworks d}
 1763 
 1764 addGhcVersionFile :: FilePath -> DynFlags -> DynFlags
 1765 addGhcVersionFile f d = d { ghcVersionFile = Just f }
 1766 
 1767 addHaddockOpts f d = d { haddockOptions = Just f}
 1768 
 1769 addGhciScript f d = d { ghciScripts = f : ghciScripts d}
 1770 
 1771 setInteractivePrint f d = d { interactivePrint = Just f}
 1772 
 1773 -----------------------------------------------------------------------------
 1774 -- Setting the optimisation level
 1775 
 1776 updOptLevel :: Int -> DynFlags -> DynFlags
 1777 -- ^ Sets the 'DynFlags' to be appropriate to the optimisation level
 1778 updOptLevel n dfs
 1779   = dfs2{ optLevel = final_n }
 1780   where
 1781    final_n = max 0 (min 2 n)    -- Clamp to 0 <= n <= 2
 1782    dfs1 = foldr (flip gopt_unset) dfs  remove_gopts
 1783    dfs2 = foldr (flip gopt_set)   dfs1 extra_gopts
 1784 
 1785    extra_gopts  = [ f | (ns,f) <- optLevelFlags, final_n `elem` ns ]
 1786    remove_gopts = [ f | (ns,f) <- optLevelFlags, final_n `notElem` ns ]
 1787 
 1788 {- **********************************************************************
 1789 %*                                                                      *
 1790                 DynFlags parser
 1791 %*                                                                      *
 1792 %********************************************************************* -}
 1793 
 1794 -- -----------------------------------------------------------------------------
 1795 -- Parsing the dynamic flags.
 1796 
 1797 
 1798 -- | Parse dynamic flags from a list of command line arguments.  Returns
 1799 -- the parsed 'DynFlags', the left-over arguments, and a list of warnings.
 1800 -- Throws a 'UsageError' if errors occurred during parsing (such as unknown
 1801 -- flags or missing arguments).
 1802 parseDynamicFlagsCmdLine :: MonadIO m => DynFlags -> [Located String]
 1803                          -> m (DynFlags, [Located String], [Warn])
 1804                             -- ^ Updated 'DynFlags', left-over arguments, and
 1805                             -- list of warnings.
 1806 parseDynamicFlagsCmdLine = parseDynamicFlagsFull flagsAll True
 1807 
 1808 
 1809 -- | Like 'parseDynamicFlagsCmdLine' but does not allow the package flags
 1810 -- (-package, -hide-package, -ignore-package, -hide-all-packages, -package-db).
 1811 -- Used to parse flags set in a modules pragma.
 1812 parseDynamicFilePragma :: MonadIO m => DynFlags -> [Located String]
 1813                        -> m (DynFlags, [Located String], [Warn])
 1814                           -- ^ Updated 'DynFlags', left-over arguments, and
 1815                           -- list of warnings.
 1816 parseDynamicFilePragma = parseDynamicFlagsFull flagsDynamic False
 1817 
 1818 
 1819 -- | Parses the dynamically set flags for GHC. This is the most general form of
 1820 -- the dynamic flag parser that the other methods simply wrap. It allows
 1821 -- saying which flags are valid flags and indicating if we are parsing
 1822 -- arguments from the command line or from a file pragma.
 1823 parseDynamicFlagsFull :: MonadIO m
 1824                   => [Flag (CmdLineP DynFlags)]    -- ^ valid flags to match against
 1825                   -> Bool                          -- ^ are the arguments from the command line?
 1826                   -> DynFlags                      -- ^ current dynamic flags
 1827                   -> [Located String]              -- ^ arguments to parse
 1828                   -> m (DynFlags, [Located String], [Warn])
 1829 parseDynamicFlagsFull activeFlags cmdline dflags0 args = do
 1830   let ((leftover, errs, warns), dflags1)
 1831           = runCmdLine (processArgs activeFlags args) dflags0
 1832 
 1833   -- See Note [Handling errors when parsing commandline flags]
 1834   let rdr = renderWithContext (initSDocContext dflags0 defaultUserStyle)
 1835   unless (null errs) $ liftIO $ throwGhcExceptionIO $ errorsToGhcException $
 1836     map ((rdr . ppr . getLoc &&& unLoc) . errMsg) $ errs
 1837 
 1838   -- check for disabled flags in safe haskell
 1839   let (dflags2, sh_warns) = safeFlagCheck cmdline dflags1
 1840       theWays = ways dflags2
 1841 
 1842   unless (allowed_combination theWays) $ liftIO $
 1843       throwGhcExceptionIO (CmdLineError ("combination not supported: " ++
 1844                                intercalate "/" (map wayDesc (Set.toAscList theWays))))
 1845 
 1846   let (dflags3, consistency_warnings) = makeDynFlagsConsistent dflags2
 1847 
 1848   -- Set timer stats & heap size
 1849   when (enableTimeStats dflags3) $ liftIO enableTimingStats
 1850   case (ghcHeapSize dflags3) of
 1851     Just x -> liftIO (setHeapSize x)
 1852     _      -> return ()
 1853 
 1854   liftIO $ setUnsafeGlobalDynFlags dflags3
 1855 
 1856   let warns' = map (Warn WarningWithoutFlag) (consistency_warnings ++ sh_warns)
 1857 
 1858   return (dflags3, leftover, warns' ++ warns)
 1859 
 1860 -- | Check (and potentially disable) any extensions that aren't allowed
 1861 -- in safe mode.
 1862 --
 1863 -- The bool is to indicate if we are parsing command line flags (false means
 1864 -- file pragma). This allows us to generate better warnings.
 1865 safeFlagCheck :: Bool -> DynFlags -> (DynFlags, [Located String])
 1866 safeFlagCheck _ dflags | safeLanguageOn dflags = (dflagsUnset, warns)
 1867   where
 1868     -- Handle illegal flags under safe language.
 1869     (dflagsUnset, warns) = foldl' check_method (dflags, []) unsafeFlags
 1870 
 1871     check_method (df, warns) (str,loc,test,fix)
 1872         | test df   = (fix df, warns ++ safeFailure (loc df) str)
 1873         | otherwise = (df, warns)
 1874 
 1875     safeFailure loc str
 1876        = [L loc $ str ++ " is not allowed in Safe Haskell; ignoring "
 1877            ++ str]
 1878 
 1879 safeFlagCheck cmdl dflags =
 1880   case safeInferOn dflags of
 1881     True   -> (dflags' { safeInferred = safeFlags }, warn)
 1882     False  -> (dflags', warn)
 1883 
 1884   where
 1885     -- dynflags and warn for when -fpackage-trust by itself with no safe
 1886     -- haskell flag
 1887     (dflags', warn)
 1888       | not (safeHaskellModeEnabled dflags) && not cmdl && packageTrustOn dflags
 1889       = (gopt_unset dflags Opt_PackageTrust, pkgWarnMsg)
 1890       | otherwise = (dflags, [])
 1891 
 1892     pkgWarnMsg = [L (pkgTrustOnLoc dflags') $
 1893                     "-fpackage-trust ignored;" ++
 1894                     " must be specified with a Safe Haskell flag"]
 1895 
 1896     -- Have we inferred Unsafe? See Note [GHC.Driver.Main . Safe Haskell Inference]
 1897     safeFlags = all (\(_,_,t,_) -> not $ t dflags) unsafeFlagsForInfer
 1898 
 1899 
 1900 {- **********************************************************************
 1901 %*                                                                      *
 1902                 DynFlags specifications
 1903 %*                                                                      *
 1904 %********************************************************************* -}
 1905 
 1906 -- | All dynamic flags option strings without the deprecated ones.
 1907 -- These are the user facing strings for enabling and disabling options.
 1908 allNonDeprecatedFlags :: [String]
 1909 allNonDeprecatedFlags = allFlagsDeps False
 1910 
 1911 -- | All flags with possibility to filter deprecated ones
 1912 allFlagsDeps :: Bool -> [String]
 1913 allFlagsDeps keepDeprecated = [ '-':flagName flag
 1914                               | (deprecated, flag) <- flagsAllDeps
 1915                               , keepDeprecated || not (isDeprecated deprecated)]
 1916   where isDeprecated Deprecated = True
 1917         isDeprecated _ = False
 1918 
 1919 {-
 1920  - Below we export user facing symbols for GHC dynamic flags for use with the
 1921  - GHC API.
 1922  -}
 1923 
 1924 -- All dynamic flags present in GHC.
 1925 flagsAll :: [Flag (CmdLineP DynFlags)]
 1926 flagsAll = map snd flagsAllDeps
 1927 
 1928 -- All dynamic flags present in GHC with deprecation information.
 1929 flagsAllDeps :: [(Deprecation, Flag (CmdLineP DynFlags))]
 1930 flagsAllDeps =  package_flags_deps ++ dynamic_flags_deps
 1931 
 1932 
 1933 -- All dynamic flags, minus package flags, present in GHC.
 1934 flagsDynamic :: [Flag (CmdLineP DynFlags)]
 1935 flagsDynamic = map snd dynamic_flags_deps
 1936 
 1937 -- ALl package flags present in GHC.
 1938 flagsPackage :: [Flag (CmdLineP DynFlags)]
 1939 flagsPackage = map snd package_flags_deps
 1940 
 1941 ----------------Helpers to make flags and keep deprecation information----------
 1942 
 1943 type FlagMaker m = String -> OptKind m -> Flag m
 1944 type DynFlagMaker = FlagMaker (CmdLineP DynFlags)
 1945 data Deprecation = NotDeprecated | Deprecated deriving (Eq, Ord)
 1946 
 1947 -- Make a non-deprecated flag
 1948 make_ord_flag :: DynFlagMaker -> String -> OptKind (CmdLineP DynFlags)
 1949               -> (Deprecation, Flag (CmdLineP DynFlags))
 1950 make_ord_flag fm name kind = (NotDeprecated, fm name kind)
 1951 
 1952 -- Make a deprecated flag
 1953 make_dep_flag :: DynFlagMaker -> String -> OptKind (CmdLineP DynFlags) -> String
 1954                  -> (Deprecation, Flag (CmdLineP DynFlags))
 1955 make_dep_flag fm name kind message = (Deprecated,
 1956                                       fm name $ add_dep_message kind message)
 1957 
 1958 add_dep_message :: OptKind (CmdLineP DynFlags) -> String
 1959                 -> OptKind (CmdLineP DynFlags)
 1960 add_dep_message (NoArg f) message = NoArg $ f >> deprecate message
 1961 add_dep_message (HasArg f) message = HasArg $ \s -> f s >> deprecate message
 1962 add_dep_message (SepArg f) message = SepArg $ \s -> f s >> deprecate message
 1963 add_dep_message (Prefix f) message = Prefix $ \s -> f s >> deprecate message
 1964 add_dep_message (OptPrefix f) message =
 1965                                   OptPrefix $ \s -> f s >> deprecate message
 1966 add_dep_message (OptIntSuffix f) message =
 1967                                OptIntSuffix $ \oi -> f oi >> deprecate message
 1968 add_dep_message (IntSuffix f) message =
 1969                                   IntSuffix $ \i -> f i >> deprecate message
 1970 add_dep_message (WordSuffix f) message =
 1971                                   WordSuffix $ \i -> f i >> deprecate message
 1972 add_dep_message (FloatSuffix f) message =
 1973                                 FloatSuffix $ \fl -> f fl >> deprecate message
 1974 add_dep_message (PassFlag f) message =
 1975                                    PassFlag $ \s -> f s >> deprecate message
 1976 add_dep_message (AnySuffix f) message =
 1977                                   AnySuffix $ \s -> f s >> deprecate message
 1978 
 1979 ----------------------- The main flags themselves ------------------------------
 1980 -- See Note [Updating flag description in the User's Guide]
 1981 -- See Note [Supporting CLI completion]
 1982 dynamic_flags_deps :: [(Deprecation, Flag (CmdLineP DynFlags))]
 1983 dynamic_flags_deps = [
 1984     make_dep_flag defFlag "n" (NoArg $ return ())
 1985         "The -n flag is deprecated and no longer has any effect"
 1986   , make_ord_flag defFlag "cpp"      (NoArg (setExtensionFlag LangExt.Cpp))
 1987   , make_ord_flag defFlag "F"        (NoArg (setGeneralFlag Opt_Pp))
 1988   , (Deprecated, defFlag "#include"
 1989       (HasArg (\_s ->
 1990          deprecate ("-#include and INCLUDE pragmas are " ++
 1991                     "deprecated: They no longer have any effect"))))
 1992   , make_ord_flag defFlag "v"        (OptIntSuffix setVerbosity)
 1993 
 1994   , make_ord_flag defGhcFlag "j"     (OptIntSuffix
 1995         (\n -> case n of
 1996                  Just n
 1997                      | n > 0     -> upd (\d -> d { parMakeCount = Just n })
 1998                      | otherwise -> addErr "Syntax: -j[n] where n > 0"
 1999                  Nothing -> upd (\d -> d { parMakeCount = Nothing })))
 2000                  -- When the number of parallel builds
 2001                  -- is omitted, it is the same
 2002                  -- as specifying that the number of
 2003                  -- parallel builds is equal to the
 2004                  -- result of getNumProcessors
 2005   , make_ord_flag defFlag "instantiated-with"   (sepArg setUnitInstantiations)
 2006   , make_ord_flag defFlag "this-component-id"   (sepArg setUnitInstanceOf)
 2007 
 2008     -- RTS options -------------------------------------------------------------
 2009   , make_ord_flag defFlag "H"           (HasArg (\s -> upd (\d ->
 2010           d { ghcHeapSize = Just $ fromIntegral (decodeSize s)})))
 2011 
 2012   , make_ord_flag defFlag "Rghc-timing" (NoArg (upd (\d ->
 2013                                                d { enableTimeStats = True })))
 2014 
 2015     ------- ways ---------------------------------------------------------------
 2016   , make_ord_flag defGhcFlag "prof"           (NoArg (addWayDynP WayProf))
 2017   , make_ord_flag defGhcFlag "eventlog"       (NoArg (addWayDynP WayTracing))
 2018   , make_ord_flag defGhcFlag "debug"          (NoArg (addWayDynP WayDebug))
 2019   , make_ord_flag defGhcFlag "threaded"       (NoArg (addWayDynP WayThreaded))
 2020 
 2021   , make_ord_flag defGhcFlag "ticky"
 2022       (NoArg (setGeneralFlag Opt_Ticky >> addWayDynP WayDebug))
 2023 
 2024     -- -ticky enables ticky-ticky code generation, and also implies -debug which
 2025     -- is required to get the RTS ticky support.
 2026 
 2027         ----- Linker --------------------------------------------------------
 2028   , make_ord_flag defGhcFlag "static"         (NoArg removeWayDyn)
 2029   , make_ord_flag defGhcFlag "dynamic"        (NoArg (addWayDynP WayDyn))
 2030   , make_ord_flag defGhcFlag "rdynamic" $ noArg $
 2031 #if defined(linux_HOST_OS)
 2032                               addOptl "-rdynamic"
 2033 #elif defined(mingw32_HOST_OS)
 2034                               addOptl "-Wl,--export-all-symbols"
 2035 #else
 2036     -- ignored for compat w/ gcc:
 2037                               id
 2038 #endif
 2039   , make_ord_flag defGhcFlag "relative-dynlib-paths"
 2040       (NoArg (setGeneralFlag Opt_RelativeDynlibPaths))
 2041   , make_ord_flag defGhcFlag "copy-libs-when-linking"
 2042       (NoArg (setGeneralFlag Opt_SingleLibFolder))
 2043   , make_ord_flag defGhcFlag "pie"            (NoArg (setGeneralFlag Opt_PICExecutable))
 2044   , make_ord_flag defGhcFlag "no-pie"         (NoArg (unSetGeneralFlag Opt_PICExecutable))
 2045 
 2046         ------- Specific phases  --------------------------------------------
 2047     -- need to appear before -pgmL to be parsed as LLVM flags.
 2048   , make_ord_flag defFlag "pgmlo"
 2049       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_lo  = (f,[]) }
 2050   , make_ord_flag defFlag "pgmlc"
 2051       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_lc  = (f,[]) }
 2052   , make_ord_flag defFlag "pgmlm"
 2053       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_lm  = (f,[]) }
 2054   , make_ord_flag defFlag "pgmi"
 2055       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_i   =  f }
 2056   , make_ord_flag defFlag "pgmL"
 2057       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_L   = f }
 2058   , make_ord_flag defFlag "pgmP"
 2059       (hasArg setPgmP)
 2060   , make_ord_flag defFlag "pgmF"
 2061       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_F   = f }
 2062   , make_ord_flag defFlag "pgmc"
 2063       $ hasArg $ \f -> alterToolSettings $ \s -> s
 2064          { toolSettings_pgm_c   = f
 2065          , -- Don't pass -no-pie with -pgmc
 2066            -- (see #15319)
 2067            toolSettings_ccSupportsNoPie = False
 2068          }
 2069   , make_ord_flag defFlag "pgmc-supports-no-pie"
 2070       $ noArg $ alterToolSettings $ \s -> s { toolSettings_ccSupportsNoPie = True }
 2071   , make_ord_flag defFlag "pgms"
 2072       (HasArg (\_ -> addWarn "Object splitting was removed in GHC 8.8"))
 2073   , make_ord_flag defFlag "pgma"
 2074       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_a   = (f,[]) }
 2075   , make_ord_flag defFlag "pgml"
 2076       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_l   = (f,[]) }
 2077   , make_ord_flag defFlag "pgmdll"
 2078       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_dll = (f,[]) }
 2079   , make_ord_flag defFlag "pgmwindres"
 2080       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_windres = f }
 2081   , make_ord_flag defFlag "pgmlibtool"
 2082       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_libtool = f }
 2083   , make_ord_flag defFlag "pgmar"
 2084       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_ar = f }
 2085   , make_ord_flag defFlag "pgmotool"
 2086       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_otool = f}
 2087   , make_ord_flag defFlag "pgminstall_name_tool"
 2088       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_install_name_tool = f}
 2089   , make_ord_flag defFlag "pgmranlib"
 2090       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_ranlib = f }
 2091 
 2092 
 2093     -- need to appear before -optl/-opta to be parsed as LLVM flags.
 2094   , make_ord_flag defFlag "optlm"
 2095       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_opt_lm  = f : toolSettings_opt_lm s }
 2096   , make_ord_flag defFlag "optlo"
 2097       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_opt_lo  = f : toolSettings_opt_lo s }
 2098   , make_ord_flag defFlag "optlc"
 2099       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_opt_lc  = f : toolSettings_opt_lc s }
 2100   , make_ord_flag defFlag "opti"
 2101       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_opt_i   = f : toolSettings_opt_i s }
 2102   , make_ord_flag defFlag "optL"
 2103       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_opt_L   = f : toolSettings_opt_L s }
 2104   , make_ord_flag defFlag "optP"
 2105       (hasArg addOptP)
 2106   , make_ord_flag defFlag "optF"
 2107       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_opt_F   = f : toolSettings_opt_F s }
 2108   , make_ord_flag defFlag "optc"
 2109       (hasArg addOptc)
 2110   , make_ord_flag defFlag "optcxx"
 2111       (hasArg addOptcxx)
 2112   , make_ord_flag defFlag "opta"
 2113       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_opt_a   = f : toolSettings_opt_a s }
 2114   , make_ord_flag defFlag "optl"
 2115       (hasArg addOptl)
 2116   , make_ord_flag defFlag "optwindres"
 2117       $ hasArg $ \f ->
 2118         alterToolSettings $ \s -> s { toolSettings_opt_windres = f : toolSettings_opt_windres s }
 2119 
 2120   , make_ord_flag defGhcFlag "split-objs"
 2121       (NoArg $ addWarn "ignoring -split-objs")
 2122 
 2123   , make_ord_flag defGhcFlag "split-sections"
 2124       (noArgM (\dflags -> do
 2125         if platformHasSubsectionsViaSymbols (targetPlatform dflags)
 2126           then do addWarn $
 2127                     "-split-sections is not useful on this platform " ++
 2128                     "since it always uses subsections via symbols. Ignoring."
 2129                   return dflags
 2130           else return (gopt_set dflags Opt_SplitSections)))
 2131 
 2132         -------- ghc -M -----------------------------------------------------
 2133   , make_ord_flag defGhcFlag "dep-suffix"              (hasArg addDepSuffix)
 2134   , make_ord_flag defGhcFlag "dep-makefile"            (hasArg setDepMakefile)
 2135   , make_ord_flag defGhcFlag "include-cpp-deps"
 2136         (noArg (setDepIncludeCppDeps True))
 2137   , make_ord_flag defGhcFlag "include-pkg-deps"
 2138         (noArg (setDepIncludePkgDeps True))
 2139   , make_ord_flag defGhcFlag "exclude-module"          (hasArg addDepExcludeMod)
 2140 
 2141         -------- Linking ----------------------------------------------------
 2142   , make_ord_flag defGhcFlag "no-link"
 2143         (noArg (\d -> d { ghcLink=NoLink }))
 2144   , make_ord_flag defGhcFlag "shared"
 2145         (noArg (\d -> d { ghcLink=LinkDynLib }))
 2146   , make_ord_flag defGhcFlag "staticlib"
 2147         (noArg (\d -> setGeneralFlag' Opt_LinkRts (d { ghcLink=LinkStaticLib })))
 2148   , make_ord_flag defGhcFlag "dynload"            (hasArg parseDynLibLoaderMode)
 2149   , make_ord_flag defGhcFlag "dylib-install-name" (hasArg setDylibInstallName)
 2150 
 2151         ------- Libraries ---------------------------------------------------
 2152   , make_ord_flag defFlag "L"   (Prefix addLibraryPath)
 2153   , make_ord_flag defFlag "l"   (hasArg (addLdInputs . Option . ("-l" ++)))
 2154 
 2155         ------- Frameworks --------------------------------------------------
 2156         -- -framework-path should really be -F ...
 2157   , make_ord_flag defFlag "framework-path" (HasArg addFrameworkPath)
 2158   , make_ord_flag defFlag "framework"      (hasArg addCmdlineFramework)
 2159 
 2160         ------- Output Redirection ------------------------------------------
 2161   , make_ord_flag defGhcFlag "odir"              (hasArg setObjectDir)
 2162   , make_ord_flag defGhcFlag "o"                 (sepArg (setOutputFile . Just))
 2163   , make_ord_flag defGhcFlag "dyno"
 2164         (sepArg (setDynOutputFile . Just))
 2165   , make_ord_flag defGhcFlag "ohi"
 2166         (hasArg (setOutputHi . Just ))
 2167   , make_ord_flag defGhcFlag "dynohi"
 2168         (hasArg (setDynOutputHi . Just ))
 2169   , make_ord_flag defGhcFlag "osuf"              (hasArg setObjectSuf)
 2170   , make_ord_flag defGhcFlag "dynosuf"           (hasArg setDynObjectSuf)
 2171   , make_ord_flag defGhcFlag "hcsuf"             (hasArg setHcSuf)
 2172   , make_ord_flag defGhcFlag "hisuf"             (hasArg setHiSuf)
 2173   , make_ord_flag defGhcFlag "hiesuf"            (hasArg setHieSuf)
 2174   , make_ord_flag defGhcFlag "dynhisuf"          (hasArg setDynHiSuf)
 2175   , make_ord_flag defGhcFlag "hidir"             (hasArg setHiDir)
 2176   , make_ord_flag defGhcFlag "hiedir"            (hasArg setHieDir)
 2177   , make_ord_flag defGhcFlag "tmpdir"            (hasArg setTmpDir)
 2178   , make_ord_flag defGhcFlag "stubdir"           (hasArg setStubDir)
 2179   , make_ord_flag defGhcFlag "dumpdir"           (hasArg setDumpDir)
 2180   , make_ord_flag defGhcFlag "outputdir"         (hasArg setOutputDir)
 2181   , make_ord_flag defGhcFlag "ddump-file-prefix"
 2182         (hasArg (setDumpPrefixForce . Just))
 2183 
 2184   , make_ord_flag defGhcFlag "dynamic-too"
 2185         (NoArg (setGeneralFlag Opt_BuildDynamicToo))
 2186 
 2187         ------- Keeping temporary files -------------------------------------
 2188      -- These can be singular (think ghc -c) or plural (think ghc --make)
 2189   , make_ord_flag defGhcFlag "keep-hc-file"
 2190         (NoArg (setGeneralFlag Opt_KeepHcFiles))
 2191   , make_ord_flag defGhcFlag "keep-hc-files"
 2192         (NoArg (setGeneralFlag Opt_KeepHcFiles))
 2193   , make_ord_flag defGhcFlag "keep-hscpp-file"
 2194         (NoArg (setGeneralFlag Opt_KeepHscppFiles))
 2195   , make_ord_flag defGhcFlag "keep-hscpp-files"
 2196         (NoArg (setGeneralFlag Opt_KeepHscppFiles))
 2197   , make_ord_flag defGhcFlag "keep-s-file"
 2198         (NoArg (setGeneralFlag Opt_KeepSFiles))
 2199   , make_ord_flag defGhcFlag "keep-s-files"
 2200         (NoArg (setGeneralFlag Opt_KeepSFiles))
 2201   , make_ord_flag defGhcFlag "keep-llvm-file"
 2202         (NoArg $ setObjBackend LLVM >> setGeneralFlag Opt_KeepLlvmFiles)
 2203   , make_ord_flag defGhcFlag "keep-llvm-files"
 2204         (NoArg $ setObjBackend LLVM >> setGeneralFlag Opt_KeepLlvmFiles)
 2205      -- This only makes sense as plural
 2206   , make_ord_flag defGhcFlag "keep-tmp-files"
 2207         (NoArg (setGeneralFlag Opt_KeepTmpFiles))
 2208   , make_ord_flag defGhcFlag "keep-hi-file"
 2209         (NoArg (setGeneralFlag Opt_KeepHiFiles))
 2210   , make_ord_flag defGhcFlag "no-keep-hi-file"
 2211         (NoArg (unSetGeneralFlag Opt_KeepHiFiles))
 2212   , make_ord_flag defGhcFlag "keep-hi-files"
 2213         (NoArg (setGeneralFlag Opt_KeepHiFiles))
 2214   , make_ord_flag defGhcFlag "no-keep-hi-files"
 2215         (NoArg (unSetGeneralFlag Opt_KeepHiFiles))
 2216   , make_ord_flag defGhcFlag "keep-o-file"
 2217         (NoArg (setGeneralFlag Opt_KeepOFiles))
 2218   , make_ord_flag defGhcFlag "no-keep-o-file"
 2219         (NoArg (unSetGeneralFlag Opt_KeepOFiles))
 2220   , make_ord_flag defGhcFlag "keep-o-files"
 2221         (NoArg (setGeneralFlag Opt_KeepOFiles))
 2222   , make_ord_flag defGhcFlag "no-keep-o-files"
 2223         (NoArg (unSetGeneralFlag Opt_KeepOFiles))
 2224 
 2225         ------- Miscellaneous ----------------------------------------------
 2226   , make_ord_flag defGhcFlag "no-auto-link-packages"
 2227         (NoArg (unSetGeneralFlag Opt_AutoLinkPackages))
 2228   , make_ord_flag defGhcFlag "no-hs-main"
 2229         (NoArg (setGeneralFlag Opt_NoHsMain))
 2230   , make_ord_flag defGhcFlag "fno-state-hack"
 2231         (NoArg (setGeneralFlag Opt_G_NoStateHack))
 2232   , make_ord_flag defGhcFlag "fno-opt-coercion"
 2233         (NoArg (setGeneralFlag Opt_G_NoOptCoercion))
 2234   , make_ord_flag defGhcFlag "with-rtsopts"
 2235         (HasArg setRtsOpts)
 2236   , make_ord_flag defGhcFlag "rtsopts"
 2237         (NoArg (setRtsOptsEnabled RtsOptsAll))
 2238   , make_ord_flag defGhcFlag "rtsopts=all"
 2239         (NoArg (setRtsOptsEnabled RtsOptsAll))
 2240   , make_ord_flag defGhcFlag "rtsopts=some"
 2241         (NoArg (setRtsOptsEnabled RtsOptsSafeOnly))
 2242   , make_ord_flag defGhcFlag "rtsopts=none"
 2243         (NoArg (setRtsOptsEnabled RtsOptsNone))
 2244   , make_ord_flag defGhcFlag "rtsopts=ignore"
 2245         (NoArg (setRtsOptsEnabled RtsOptsIgnore))
 2246   , make_ord_flag defGhcFlag "rtsopts=ignoreAll"
 2247         (NoArg (setRtsOptsEnabled RtsOptsIgnoreAll))
 2248   , make_ord_flag defGhcFlag "no-rtsopts"
 2249         (NoArg (setRtsOptsEnabled RtsOptsNone))
 2250   , make_ord_flag defGhcFlag "no-rtsopts-suggestions"
 2251       (noArg (\d -> d {rtsOptsSuggestions = False}))
 2252   , make_ord_flag defGhcFlag "dhex-word-literals"
 2253         (NoArg (setGeneralFlag Opt_HexWordLiterals))
 2254 
 2255   , make_ord_flag defGhcFlag "ghcversion-file"      (hasArg addGhcVersionFile)
 2256   , make_ord_flag defGhcFlag "main-is"              (SepArg setMainIs)
 2257   , make_ord_flag defGhcFlag "haddock"              (NoArg (setGeneralFlag Opt_Haddock))
 2258   , make_ord_flag defGhcFlag "no-haddock"           (NoArg (unSetGeneralFlag Opt_Haddock))
 2259   , make_ord_flag defGhcFlag "haddock-opts"         (hasArg addHaddockOpts)
 2260   , make_ord_flag defGhcFlag "hpcdir"               (SepArg setOptHpcDir)
 2261   , make_ord_flag defGhciFlag "ghci-script"         (hasArg addGhciScript)
 2262   , make_ord_flag defGhciFlag "interactive-print"   (hasArg setInteractivePrint)
 2263   , make_ord_flag defGhcFlag "ticky-allocd"
 2264         (NoArg (setGeneralFlag Opt_Ticky_Allocd))
 2265   , make_ord_flag defGhcFlag "ticky-LNE"
 2266         (NoArg (setGeneralFlag Opt_Ticky_LNE))
 2267   , make_ord_flag defGhcFlag "ticky-dyn-thunk"
 2268         (NoArg (setGeneralFlag Opt_Ticky_Dyn_Thunk))
 2269         ------- recompilation checker --------------------------------------
 2270   , make_dep_flag defGhcFlag "recomp"
 2271         (NoArg $ unSetGeneralFlag Opt_ForceRecomp)
 2272              "Use -fno-force-recomp instead"
 2273   , make_dep_flag defGhcFlag "no-recomp"
 2274         (NoArg $ setGeneralFlag Opt_ForceRecomp) "Use -fforce-recomp instead"
 2275   , make_ord_flag defFlag "fmax-errors"
 2276       (intSuffix (\n d -> d { maxErrors = Just (max 1 n) }))
 2277   , make_ord_flag defFlag "fno-max-errors"
 2278       (noArg (\d -> d { maxErrors = Nothing }))
 2279   , make_ord_flag defFlag "freverse-errors"
 2280         (noArg (\d -> d {reverseErrors = True} ))
 2281   , make_ord_flag defFlag "fno-reverse-errors"
 2282         (noArg (\d -> d {reverseErrors = False} ))
 2283 
 2284         ------ HsCpp opts ---------------------------------------------------
 2285   , make_ord_flag defFlag "D"              (AnySuffix (upd . addOptP))
 2286   , make_ord_flag defFlag "U"              (AnySuffix (upd . addOptP))
 2287 
 2288         ------- Include/Import Paths ----------------------------------------
 2289   , make_ord_flag defFlag "I"              (Prefix    addIncludePath)
 2290   , make_ord_flag defFlag "i"              (OptPrefix addImportPath)
 2291 
 2292         ------ Output style options -----------------------------------------
 2293   , make_ord_flag defFlag "dppr-user-length" (intSuffix (\n d ->
 2294                                                        d { pprUserLength = n }))
 2295   , make_ord_flag defFlag "dppr-cols"        (intSuffix (\n d ->
 2296                                                              d { pprCols = n }))
 2297   , make_ord_flag defFlag "fdiagnostics-color=auto"
 2298       (NoArg (upd (\d -> d { useColor = Auto })))
 2299   , make_ord_flag defFlag "fdiagnostics-color=always"
 2300       (NoArg (upd (\d -> d { useColor = Always })))
 2301   , make_ord_flag defFlag "fdiagnostics-color=never"
 2302       (NoArg (upd (\d -> d { useColor = Never })))
 2303 
 2304   -- Suppress all that is suppressable in core dumps.
 2305   -- Except for uniques, as some simplifier phases introduce new variables that
 2306   -- have otherwise identical names.
 2307   , make_ord_flag defGhcFlag "dsuppress-all"
 2308       (NoArg $ do setGeneralFlag Opt_SuppressCoercions
 2309                   setGeneralFlag Opt_SuppressVarKinds
 2310                   setGeneralFlag Opt_SuppressModulePrefixes
 2311                   setGeneralFlag Opt_SuppressTypeApplications
 2312                   setGeneralFlag Opt_SuppressIdInfo
 2313                   setGeneralFlag Opt_SuppressTicks
 2314                   setGeneralFlag Opt_SuppressStgExts
 2315                   setGeneralFlag Opt_SuppressTypeSignatures
 2316                   setGeneralFlag Opt_SuppressCoreSizes
 2317                   setGeneralFlag Opt_SuppressTimestamps)
 2318 
 2319         ------ Debugging ----------------------------------------------------
 2320   , make_ord_flag defGhcFlag "dstg-stats"
 2321         (NoArg (setGeneralFlag Opt_StgStats))
 2322 
 2323   , make_ord_flag defGhcFlag "ddump-cmm"
 2324         (setDumpFlag Opt_D_dump_cmm)
 2325   , make_ord_flag defGhcFlag "ddump-cmm-from-stg"
 2326         (setDumpFlag Opt_D_dump_cmm_from_stg)
 2327   , make_ord_flag defGhcFlag "ddump-cmm-raw"
 2328         (setDumpFlag Opt_D_dump_cmm_raw)
 2329   , make_ord_flag defGhcFlag "ddump-cmm-verbose"
 2330         (setDumpFlag Opt_D_dump_cmm_verbose)
 2331   , make_ord_flag defGhcFlag "ddump-cmm-verbose-by-proc"
 2332         (setDumpFlag Opt_D_dump_cmm_verbose_by_proc)
 2333   , make_ord_flag defGhcFlag "ddump-cmm-cfg"
 2334         (setDumpFlag Opt_D_dump_cmm_cfg)
 2335   , make_ord_flag defGhcFlag "ddump-cmm-cbe"
 2336         (setDumpFlag Opt_D_dump_cmm_cbe)
 2337   , make_ord_flag defGhcFlag "ddump-cmm-switch"
 2338         (setDumpFlag Opt_D_dump_cmm_switch)
 2339   , make_ord_flag defGhcFlag "ddump-cmm-proc"
 2340         (setDumpFlag Opt_D_dump_cmm_proc)
 2341   , make_ord_flag defGhcFlag "ddump-cmm-sp"
 2342         (setDumpFlag Opt_D_dump_cmm_sp)
 2343   , make_ord_flag defGhcFlag "ddump-cmm-sink"
 2344         (setDumpFlag Opt_D_dump_cmm_sink)
 2345   , make_ord_flag defGhcFlag "ddump-cmm-caf"
 2346         (setDumpFlag Opt_D_dump_cmm_caf)
 2347   , make_ord_flag defGhcFlag "ddump-cmm-procmap"
 2348         (setDumpFlag Opt_D_dump_cmm_procmap)
 2349   , make_ord_flag defGhcFlag "ddump-cmm-split"
 2350         (setDumpFlag Opt_D_dump_cmm_split)
 2351   , make_ord_flag defGhcFlag "ddump-cmm-info"
 2352         (setDumpFlag Opt_D_dump_cmm_info)
 2353   , make_ord_flag defGhcFlag "ddump-cmm-cps"
 2354         (setDumpFlag Opt_D_dump_cmm_cps)
 2355   , make_ord_flag defGhcFlag "ddump-cmm-opt"
 2356         (setDumpFlag Opt_D_dump_opt_cmm)
 2357   , make_ord_flag defGhcFlag "ddump-cfg-weights"
 2358         (setDumpFlag Opt_D_dump_cfg_weights)
 2359   , make_ord_flag defGhcFlag "ddump-core-stats"
 2360         (setDumpFlag Opt_D_dump_core_stats)
 2361   , make_ord_flag defGhcFlag "ddump-asm"
 2362         (setDumpFlag Opt_D_dump_asm)
 2363   , make_ord_flag defGhcFlag "ddump-asm-native"
 2364         (setDumpFlag Opt_D_dump_asm_native)
 2365   , make_ord_flag defGhcFlag "ddump-asm-liveness"
 2366         (setDumpFlag Opt_D_dump_asm_liveness)
 2367   , make_ord_flag defGhcFlag "ddump-asm-regalloc"
 2368         (setDumpFlag Opt_D_dump_asm_regalloc)
 2369   , make_ord_flag defGhcFlag "ddump-asm-conflicts"
 2370         (setDumpFlag Opt_D_dump_asm_conflicts)
 2371   , make_ord_flag defGhcFlag "ddump-asm-regalloc-stages"
 2372         (setDumpFlag Opt_D_dump_asm_regalloc_stages)
 2373   , make_ord_flag defGhcFlag "ddump-asm-stats"
 2374         (setDumpFlag Opt_D_dump_asm_stats)
 2375   , make_ord_flag defGhcFlag "ddump-asm-expanded"
 2376         (setDumpFlag Opt_D_dump_asm_expanded)
 2377   , make_ord_flag defGhcFlag "ddump-llvm"
 2378         (NoArg $ setObjBackend LLVM >> setDumpFlag' Opt_D_dump_llvm)
 2379   , make_ord_flag defGhcFlag "ddump-c-backend"
 2380         (NoArg $ setDumpFlag' Opt_D_dump_c_backend)
 2381   , make_ord_flag defGhcFlag "ddump-deriv"
 2382         (setDumpFlag Opt_D_dump_deriv)
 2383   , make_ord_flag defGhcFlag "ddump-ds"
 2384         (setDumpFlag Opt_D_dump_ds)
 2385   , make_ord_flag defGhcFlag "ddump-ds-preopt"
 2386         (setDumpFlag Opt_D_dump_ds_preopt)
 2387   , make_ord_flag defGhcFlag "ddump-foreign"
 2388         (setDumpFlag Opt_D_dump_foreign)
 2389   , make_ord_flag defGhcFlag "ddump-inlinings"
 2390         (setDumpFlag Opt_D_dump_inlinings)
 2391   , make_ord_flag defGhcFlag "ddump-verbose-inlinings"
 2392         (setDumpFlag Opt_D_dump_verbose_inlinings)
 2393   , make_ord_flag defGhcFlag "ddump-rule-firings"
 2394         (setDumpFlag Opt_D_dump_rule_firings)
 2395   , make_ord_flag defGhcFlag "ddump-rule-rewrites"
 2396         (setDumpFlag Opt_D_dump_rule_rewrites)
 2397   , make_ord_flag defGhcFlag "ddump-simpl-trace"
 2398         (setDumpFlag Opt_D_dump_simpl_trace)
 2399   , make_ord_flag defGhcFlag "ddump-occur-anal"
 2400         (setDumpFlag Opt_D_dump_occur_anal)
 2401   , make_ord_flag defGhcFlag "ddump-parsed"
 2402         (setDumpFlag Opt_D_dump_parsed)
 2403   , make_ord_flag defGhcFlag "ddump-parsed-ast"
 2404         (setDumpFlag Opt_D_dump_parsed_ast)
 2405   , make_ord_flag defGhcFlag "ddump-rn"
 2406         (setDumpFlag Opt_D_dump_rn)
 2407   , make_ord_flag defGhcFlag "ddump-rn-ast"
 2408         (setDumpFlag Opt_D_dump_rn_ast)
 2409   , make_ord_flag defGhcFlag "ddump-simpl"
 2410         (setDumpFlag Opt_D_dump_simpl)
 2411   , make_ord_flag defGhcFlag "ddump-simpl-iterations"
 2412       (setDumpFlag Opt_D_dump_simpl_iterations)
 2413   , make_ord_flag defGhcFlag "ddump-spec"
 2414         (setDumpFlag Opt_D_dump_spec)
 2415   , make_ord_flag defGhcFlag "ddump-prep"
 2416         (setDumpFlag Opt_D_dump_prep)
 2417   , make_ord_flag defGhcFlag "ddump-stg-from-core"
 2418         (setDumpFlag Opt_D_dump_stg_from_core)
 2419   , make_ord_flag defGhcFlag "ddump-stg-unarised"
 2420         (setDumpFlag Opt_D_dump_stg_unarised)
 2421   , make_ord_flag defGhcFlag "ddump-stg-final"
 2422         (setDumpFlag Opt_D_dump_stg_final)
 2423   , make_dep_flag defGhcFlag "ddump-stg"
 2424         (setDumpFlag Opt_D_dump_stg_from_core)
 2425         "Use `-ddump-stg-from-core` or `-ddump-stg-final` instead"
 2426   , make_ord_flag defGhcFlag "ddump-call-arity"
 2427         (setDumpFlag Opt_D_dump_call_arity)
 2428   , make_ord_flag defGhcFlag "ddump-exitify"
 2429         (setDumpFlag Opt_D_dump_exitify)
 2430   , make_ord_flag defGhcFlag "ddump-stranal"
 2431         (setDumpFlag Opt_D_dump_stranal)
 2432   , make_ord_flag defGhcFlag "ddump-str-signatures"
 2433         (setDumpFlag Opt_D_dump_str_signatures)
 2434   , make_ord_flag defGhcFlag "ddump-cpranal"
 2435         (setDumpFlag Opt_D_dump_cpranal)
 2436   , make_ord_flag defGhcFlag "ddump-cpr-signatures"
 2437         (setDumpFlag Opt_D_dump_cpr_signatures)
 2438   , make_ord_flag defGhcFlag "ddump-tc"
 2439         (setDumpFlag Opt_D_dump_tc)
 2440   , make_ord_flag defGhcFlag "ddump-tc-ast"
 2441         (setDumpFlag Opt_D_dump_tc_ast)
 2442   , make_ord_flag defGhcFlag "ddump-hie"
 2443         (setDumpFlag Opt_D_dump_hie)
 2444   , make_ord_flag defGhcFlag "ddump-types"
 2445         (setDumpFlag Opt_D_dump_types)
 2446   , make_ord_flag defGhcFlag "ddump-rules"
 2447         (setDumpFlag Opt_D_dump_rules)
 2448   , make_ord_flag defGhcFlag "ddump-cse"
 2449         (setDumpFlag Opt_D_dump_cse)
 2450   , make_ord_flag defGhcFlag "ddump-worker-wrapper"
 2451         (setDumpFlag Opt_D_dump_worker_wrapper)
 2452   , make_ord_flag defGhcFlag "ddump-rn-trace"
 2453         (setDumpFlag Opt_D_dump_rn_trace)
 2454   , make_ord_flag defGhcFlag "ddump-if-trace"
 2455         (setDumpFlag Opt_D_dump_if_trace)
 2456   , make_ord_flag defGhcFlag "ddump-cs-trace"
 2457         (setDumpFlag Opt_D_dump_cs_trace)
 2458   , make_ord_flag defGhcFlag "ddump-tc-trace"
 2459         (NoArg (do setDumpFlag' Opt_D_dump_tc_trace
 2460                    setDumpFlag' Opt_D_dump_cs_trace))
 2461   , make_ord_flag defGhcFlag "ddump-ec-trace"
 2462         (setDumpFlag Opt_D_dump_ec_trace)
 2463   , make_ord_flag defGhcFlag "ddump-splices"
 2464         (setDumpFlag Opt_D_dump_splices)
 2465   , make_ord_flag defGhcFlag "dth-dec-file"
 2466         (setDumpFlag Opt_D_th_dec_file)
 2467 
 2468   , make_ord_flag defGhcFlag "ddump-rn-stats"
 2469         (setDumpFlag Opt_D_dump_rn_stats)
 2470   , make_ord_flag defGhcFlag "ddump-opt-cmm" --old alias for cmm-opt
 2471         (setDumpFlag Opt_D_dump_opt_cmm)
 2472   , make_ord_flag defGhcFlag "ddump-simpl-stats"
 2473         (setDumpFlag Opt_D_dump_simpl_stats)
 2474   , make_ord_flag defGhcFlag "ddump-bcos"
 2475         (setDumpFlag Opt_D_dump_BCOs)
 2476   , make_ord_flag defGhcFlag "dsource-stats"
 2477         (setDumpFlag Opt_D_source_stats)
 2478   , make_ord_flag defGhcFlag "dverbose-core2core"
 2479         (NoArg $ setVerbosity (Just 2) >> setDumpFlag' Opt_D_verbose_core2core)
 2480   , make_ord_flag defGhcFlag "dverbose-stg2stg"
 2481         (setDumpFlag Opt_D_verbose_stg2stg)
 2482   , make_ord_flag defGhcFlag "ddump-hi"
 2483         (setDumpFlag Opt_D_dump_hi)
 2484   , make_ord_flag defGhcFlag "ddump-minimal-imports"
 2485         (NoArg (setGeneralFlag Opt_D_dump_minimal_imports))
 2486   , make_ord_flag defGhcFlag "ddump-hpc"
 2487         (setDumpFlag Opt_D_dump_ticked) -- back compat
 2488   , make_ord_flag defGhcFlag "ddump-ticked"
 2489         (setDumpFlag Opt_D_dump_ticked)
 2490   , make_ord_flag defGhcFlag "ddump-mod-cycles"
 2491         (setDumpFlag Opt_D_dump_mod_cycles)
 2492   , make_ord_flag defGhcFlag "ddump-mod-map"
 2493         (setDumpFlag Opt_D_dump_mod_map)
 2494   , make_ord_flag defGhcFlag "ddump-timings"
 2495         (setDumpFlag Opt_D_dump_timings)
 2496   , make_ord_flag defGhcFlag "ddump-view-pattern-commoning"
 2497         (setDumpFlag Opt_D_dump_view_pattern_commoning)
 2498   , make_ord_flag defGhcFlag "ddump-to-file"
 2499         (NoArg (setGeneralFlag Opt_DumpToFile))
 2500   , make_ord_flag defGhcFlag "ddump-hi-diffs"
 2501         (setDumpFlag Opt_D_dump_hi_diffs)
 2502   , make_ord_flag defGhcFlag "ddump-rtti"
 2503         (setDumpFlag Opt_D_dump_rtti)
 2504   , make_ord_flag defGhcFlag "dcore-lint"
 2505         (NoArg (setGeneralFlag Opt_DoCoreLinting))
 2506   , make_ord_flag defGhcFlag "dlinear-core-lint"
 2507         (NoArg (setGeneralFlag Opt_DoLinearCoreLinting))
 2508   , make_ord_flag defGhcFlag "dstg-lint"
 2509         (NoArg (setGeneralFlag Opt_DoStgLinting))
 2510   , make_ord_flag defGhcFlag "dcmm-lint"
 2511         (NoArg (setGeneralFlag Opt_DoCmmLinting))
 2512   , make_ord_flag defGhcFlag "dasm-lint"
 2513         (NoArg (setGeneralFlag Opt_DoAsmLinting))
 2514   , make_ord_flag defGhcFlag "dannot-lint"
 2515         (NoArg (setGeneralFlag Opt_DoAnnotationLinting))
 2516   , make_ord_flag defGhcFlag "dshow-passes"
 2517         (NoArg $ forceRecompile >> (setVerbosity $ Just 2))
 2518   , make_ord_flag defGhcFlag "dfaststring-stats"
 2519         (setDumpFlag Opt_D_faststring_stats)
 2520   , make_ord_flag defGhcFlag "dno-llvm-mangler"
 2521         (NoArg (setGeneralFlag Opt_NoLlvmMangler)) -- hidden flag
 2522   , make_ord_flag defGhcFlag "dno-typeable-binds"
 2523         (NoArg (setGeneralFlag Opt_NoTypeableBinds))
 2524   , make_ord_flag defGhcFlag "ddump-debug"
 2525         (setDumpFlag Opt_D_dump_debug)
 2526   , make_ord_flag defGhcFlag "ddump-json"
 2527         (setDumpFlag Opt_D_dump_json )
 2528   , make_ord_flag defGhcFlag "dppr-debug"
 2529         (setDumpFlag Opt_D_ppr_debug)
 2530   , make_ord_flag defGhcFlag "ddebug-output"
 2531         (noArg (flip dopt_unset Opt_D_no_debug_output))
 2532   , make_ord_flag defGhcFlag "dno-debug-output"
 2533         (setDumpFlag Opt_D_no_debug_output)
 2534 
 2535   , make_ord_flag defGhcFlag "ddump-faststrings"
 2536         (setDumpFlag Opt_D_dump_faststrings)
 2537 
 2538         ------ Machine dependent (-m<blah>) stuff ---------------------------
 2539 
 2540   , make_ord_flag defGhcFlag "msse"         (noArg (\d ->
 2541                                                   d { sseVersion = Just SSE1 }))
 2542   , make_ord_flag defGhcFlag "msse2"        (noArg (\d ->
 2543                                                   d { sseVersion = Just SSE2 }))
 2544   , make_ord_flag defGhcFlag "msse3"        (noArg (\d ->
 2545                                                   d { sseVersion = Just SSE3 }))
 2546   , make_ord_flag defGhcFlag "msse4"        (noArg (\d ->
 2547                                                   d { sseVersion = Just SSE4 }))
 2548   , make_ord_flag defGhcFlag "msse4.2"      (noArg (\d ->
 2549                                                  d { sseVersion = Just SSE42 }))
 2550   , make_ord_flag defGhcFlag "mbmi"         (noArg (\d ->
 2551                                                  d { bmiVersion = Just BMI1 }))
 2552   , make_ord_flag defGhcFlag "mbmi2"        (noArg (\d ->
 2553                                                  d { bmiVersion = Just BMI2 }))
 2554   , make_ord_flag defGhcFlag "mavx"         (noArg (\d -> d { avx = True }))
 2555   , make_ord_flag defGhcFlag "mavx2"        (noArg (\d -> d { avx2 = True }))
 2556   , make_ord_flag defGhcFlag "mavx512cd"    (noArg (\d ->
 2557                                                          d { avx512cd = True }))
 2558   , make_ord_flag defGhcFlag "mavx512er"    (noArg (\d ->
 2559                                                          d { avx512er = True }))
 2560   , make_ord_flag defGhcFlag "mavx512f"     (noArg (\d -> d { avx512f = True }))
 2561   , make_ord_flag defGhcFlag "mavx512pf"    (noArg (\d ->
 2562                                                          d { avx512pf = True }))
 2563 
 2564      ------ Warning opts -------------------------------------------------
 2565   , make_ord_flag defFlag "W"       (NoArg (mapM_ setWarningFlag minusWOpts))
 2566   , make_ord_flag defFlag "Werror"
 2567                (NoArg (do { setGeneralFlag Opt_WarnIsError
 2568                           ; mapM_ setFatalWarningFlag minusWeverythingOpts   }))
 2569   , make_ord_flag defFlag "Wwarn"
 2570                (NoArg (do { unSetGeneralFlag Opt_WarnIsError
 2571                           ; mapM_ unSetFatalWarningFlag minusWeverythingOpts }))
 2572                           -- Opt_WarnIsError is still needed to pass -Werror
 2573                           -- to CPP; see runCpp in SysTools
 2574   , make_dep_flag defFlag "Wnot"    (NoArg (upd (\d ->
 2575                                               d {warningFlags = EnumSet.empty})))
 2576                                              "Use -w or -Wno-everything instead"
 2577   , make_ord_flag defFlag "w"       (NoArg (upd (\d ->
 2578                                               d {warningFlags = EnumSet.empty})))
 2579 
 2580      -- New-style uniform warning sets
 2581      --
 2582      -- Note that -Weverything > -Wall > -Wextra > -Wdefault > -Wno-everything
 2583   , make_ord_flag defFlag "Weverything"    (NoArg (mapM_
 2584                                            setWarningFlag minusWeverythingOpts))
 2585   , make_ord_flag defFlag "Wno-everything"
 2586                            (NoArg (upd (\d -> d {warningFlags = EnumSet.empty})))
 2587 
 2588   , make_ord_flag defFlag "Wall"           (NoArg (mapM_
 2589                                                   setWarningFlag minusWallOpts))
 2590   , make_ord_flag defFlag "Wno-all"        (NoArg (mapM_
 2591                                                 unSetWarningFlag minusWallOpts))
 2592 
 2593   , make_ord_flag defFlag "Wextra"         (NoArg (mapM_
 2594                                                      setWarningFlag minusWOpts))
 2595   , make_ord_flag defFlag "Wno-extra"      (NoArg (mapM_
 2596                                                    unSetWarningFlag minusWOpts))
 2597 
 2598   , make_ord_flag defFlag "Wdefault"       (NoArg (mapM_
 2599                                                setWarningFlag standardWarnings))
 2600   , make_ord_flag defFlag "Wno-default"    (NoArg (mapM_
 2601                                              unSetWarningFlag standardWarnings))
 2602 
 2603   , make_ord_flag defFlag "Wcompat"        (NoArg (mapM_
 2604                                                setWarningFlag minusWcompatOpts))
 2605   , make_ord_flag defFlag "Wno-compat"     (NoArg (mapM_
 2606                                              unSetWarningFlag minusWcompatOpts))
 2607 
 2608         ------ Plugin flags ------------------------------------------------
 2609   , make_ord_flag defGhcFlag "fplugin-opt" (hasArg addPluginModuleNameOption)
 2610   , make_ord_flag defGhcFlag "fplugin-trustworthy"
 2611       (NoArg (setGeneralFlag Opt_PluginTrustworthy))
 2612   , make_ord_flag defGhcFlag "fplugin"     (hasArg addPluginModuleName)
 2613   , make_ord_flag defGhcFlag "fclear-plugins" (noArg clearPluginModuleNames)
 2614   , make_ord_flag defGhcFlag "ffrontend-opt" (hasArg addFrontendPluginOption)
 2615 
 2616         ------ Optimisation flags ------------------------------------------
 2617   , make_dep_flag defGhcFlag "Onot"   (noArgM $ setOptLevel 0 )
 2618                                                             "Use -O0 instead"
 2619   , make_ord_flag defGhcFlag "O"      (optIntSuffixM (\mb_n ->
 2620                                                 setOptLevel (mb_n `orElse` 1)))
 2621                 -- If the number is missing, use 1
 2622 
 2623   , make_ord_flag defFlag "fbinary-blob-threshold"
 2624       (intSuffix (\n d -> d { binBlobThreshold = fromIntegral n }))
 2625 
 2626   , make_ord_flag defFlag "fmax-relevant-binds"
 2627       (intSuffix (\n d -> d { maxRelevantBinds = Just n }))
 2628   , make_ord_flag defFlag "fno-max-relevant-binds"
 2629       (noArg (\d -> d { maxRelevantBinds = Nothing }))
 2630 
 2631   , make_ord_flag defFlag "fmax-valid-hole-fits"
 2632       (intSuffix (\n d -> d { maxValidHoleFits = Just n }))
 2633   , make_ord_flag defFlag "fno-max-valid-hole-fits"
 2634       (noArg (\d -> d { maxValidHoleFits = Nothing }))
 2635   , make_ord_flag defFlag "fmax-refinement-hole-fits"
 2636       (intSuffix (\n d -> d { maxRefHoleFits = Just n }))
 2637   , make_ord_flag defFlag "fno-max-refinement-hole-fits"
 2638       (noArg (\d -> d { maxRefHoleFits = Nothing }))
 2639   , make_ord_flag defFlag "frefinement-level-hole-fits"
 2640       (intSuffix (\n d -> d { refLevelHoleFits = Just n }))
 2641   , make_ord_flag defFlag "fno-refinement-level-hole-fits"
 2642       (noArg (\d -> d { refLevelHoleFits = Nothing }))
 2643 
 2644   , make_dep_flag defGhcFlag "fllvm-pass-vectors-in-regs"
 2645             (noArg id)
 2646             "vectors registers are now passed in registers by default."
 2647   , make_ord_flag defFlag "fmax-uncovered-patterns"
 2648       (intSuffix (\n d -> d { maxUncoveredPatterns = n }))
 2649   , make_ord_flag defFlag "fmax-pmcheck-models"
 2650       (intSuffix (\n d -> d { maxPmCheckModels = n }))
 2651   , make_ord_flag defFlag "fsimplifier-phases"
 2652       (intSuffix (\n d -> d { simplPhases = n }))
 2653   , make_ord_flag defFlag "fmax-simplifier-iterations"
 2654       (intSuffix (\n d -> d { maxSimplIterations = n }))
 2655   , (Deprecated, defFlag "fmax-pmcheck-iterations"
 2656       (intSuffixM (\_ d ->
 2657        do { deprecate $ "use -fmax-pmcheck-models instead"
 2658           ; return d })))
 2659   , make_ord_flag defFlag "fsimpl-tick-factor"
 2660       (intSuffix (\n d -> d { simplTickFactor = n }))
 2661   , make_ord_flag defFlag "fdmd-unbox-width"
 2662       (intSuffix (\n d -> d { dmdUnboxWidth = n }))
 2663   , make_ord_flag defFlag "fspec-constr-threshold"
 2664       (intSuffix (\n d -> d { specConstrThreshold = Just n }))
 2665   , make_ord_flag defFlag "fno-spec-constr-threshold"
 2666       (noArg (\d -> d { specConstrThreshold = Nothing }))
 2667   , make_ord_flag defFlag "fspec-constr-count"
 2668       (intSuffix (\n d -> d { specConstrCount = Just n }))
 2669   , make_ord_flag defFlag "fno-spec-constr-count"
 2670       (noArg (\d -> d { specConstrCount = Nothing }))
 2671   , make_ord_flag defFlag "fspec-constr-recursive"
 2672       (intSuffix (\n d -> d { specConstrRecursive = n }))
 2673   , make_ord_flag defFlag "fliberate-case-threshold"
 2674       (intSuffix (\n d -> d { liberateCaseThreshold = Just n }))
 2675   , make_ord_flag defFlag "fno-liberate-case-threshold"
 2676       (noArg (\d -> d { liberateCaseThreshold = Nothing }))
 2677   , make_ord_flag defFlag "drule-check"
 2678       (sepArg (\s d -> d { ruleCheck = Just s }))
 2679   , make_ord_flag defFlag "dinline-check"
 2680       (sepArg (\s d -> d { unfoldingOpts = updateReportPrefix (Just s) (unfoldingOpts d)}))
 2681   , make_ord_flag defFlag "freduction-depth"
 2682       (intSuffix (\n d -> d { reductionDepth = treatZeroAsInf n }))
 2683   , make_ord_flag defFlag "fconstraint-solver-iterations"
 2684       (intSuffix (\n d -> d { solverIterations = treatZeroAsInf n }))
 2685   , (Deprecated, defFlag "fcontext-stack"
 2686       (intSuffixM (\n d ->
 2687        do { deprecate $ "use -freduction-depth=" ++ show n ++ " instead"
 2688           ; return $ d { reductionDepth = treatZeroAsInf n } })))
 2689   , (Deprecated, defFlag "ftype-function-depth"
 2690       (intSuffixM (\n d ->
 2691        do { deprecate $ "use -freduction-depth=" ++ show n ++ " instead"
 2692           ; return $ d { reductionDepth = treatZeroAsInf n } })))
 2693   , make_ord_flag defFlag "fstrictness-before"
 2694       (intSuffix (\n d -> d { strictnessBefore = n : strictnessBefore d }))
 2695   , make_ord_flag defFlag "ffloat-lam-args"
 2696       (intSuffix (\n d -> d { floatLamArgs = Just n }))
 2697   , make_ord_flag defFlag "ffloat-all-lams"
 2698       (noArg (\d -> d { floatLamArgs = Nothing }))
 2699   , make_ord_flag defFlag "fstg-lift-lams-rec-args"
 2700       (intSuffix (\n d -> d { liftLamsRecArgs = Just n }))
 2701   , make_ord_flag defFlag "fstg-lift-lams-rec-args-any"
 2702       (noArg (\d -> d { liftLamsRecArgs = Nothing }))
 2703   , make_ord_flag defFlag "fstg-lift-lams-non-rec-args"
 2704       (intSuffix (\n d -> d { liftLamsNonRecArgs = Just n }))
 2705   , make_ord_flag defFlag "fstg-lift-lams-non-rec-args-any"
 2706       (noArg (\d -> d { liftLamsNonRecArgs = Nothing }))
 2707   , make_ord_flag defFlag "fstg-lift-lams-known"
 2708       (noArg (\d -> d { liftLamsKnown = True }))
 2709   , make_ord_flag defFlag "fno-stg-lift-lams-known"
 2710       (noArg (\d -> d { liftLamsKnown = False }))
 2711   , make_ord_flag defFlag "fproc-alignment"
 2712       (intSuffix (\n d -> d { cmmProcAlignment = Just n }))
 2713   , make_ord_flag defFlag "fblock-layout-weights"
 2714         (HasArg (\s ->
 2715             upd (\d -> d { cfgWeights =
 2716                 parseWeights s (cfgWeights d)})))
 2717   , make_ord_flag defFlag "fhistory-size"
 2718       (intSuffix (\n d -> d { historySize = n }))
 2719 
 2720   , make_ord_flag defFlag "funfolding-creation-threshold"
 2721       (intSuffix   (\n d -> d { unfoldingOpts = updateCreationThreshold n (unfoldingOpts d)}))
 2722   , make_ord_flag defFlag "funfolding-use-threshold"
 2723       (intSuffix   (\n d -> d { unfoldingOpts = updateUseThreshold n (unfoldingOpts d)}))
 2724   , make_ord_flag defFlag "funfolding-fun-discount"
 2725       (intSuffix   (\n d -> d { unfoldingOpts = updateFunAppDiscount n (unfoldingOpts d)}))
 2726   , make_ord_flag defFlag "funfolding-dict-discount"
 2727       (intSuffix   (\n d -> d { unfoldingOpts = updateDictDiscount n (unfoldingOpts d)}))
 2728 
 2729   , make_ord_flag defFlag "funfolding-case-threshold"
 2730       (intSuffix   (\n d -> d { unfoldingOpts = updateCaseThreshold n (unfoldingOpts d)}))
 2731   , make_ord_flag defFlag "funfolding-case-scaling"
 2732       (intSuffix   (\n d -> d { unfoldingOpts = updateCaseScaling n (unfoldingOpts d)}))
 2733 
 2734   , make_dep_flag defFlag "funfolding-keeness-factor"
 2735       (floatSuffix (\_ d -> d))
 2736       "-funfolding-keeness-factor is no longer respected as of GHC 9.0"
 2737 
 2738   , make_ord_flag defFlag "fmax-worker-args"
 2739       (intSuffix (\n d -> d {maxWorkerArgs = n}))
 2740   , make_ord_flag defGhciFlag "fghci-hist-size"
 2741       (intSuffix (\n d -> d {ghciHistSize = n}))
 2742   , make_ord_flag defGhcFlag "fmax-inline-alloc-size"
 2743       (intSuffix (\n d -> d { maxInlineAllocSize = n }))
 2744   , make_ord_flag defGhcFlag "fmax-inline-memcpy-insns"
 2745       (intSuffix (\n d -> d { maxInlineMemcpyInsns = n }))
 2746   , make_ord_flag defGhcFlag "fmax-inline-memset-insns"
 2747       (intSuffix (\n d -> d { maxInlineMemsetInsns = n }))
 2748   , make_ord_flag defGhcFlag "dinitial-unique"
 2749       (wordSuffix (\n d -> d { initialUnique = n }))
 2750   , make_ord_flag defGhcFlag "dunique-increment"
 2751       (intSuffix (\n d -> d { uniqueIncrement = n }))
 2752 
 2753         ------ Profiling ----------------------------------------------------
 2754 
 2755         -- OLD profiling flags
 2756   , make_dep_flag defGhcFlag "auto-all"
 2757                     (noArg (\d -> d { profAuto = ProfAutoAll } ))
 2758                     "Use -fprof-auto instead"
 2759   , make_dep_flag defGhcFlag "no-auto-all"
 2760                     (noArg (\d -> d { profAuto = NoProfAuto } ))
 2761                     "Use -fno-prof-auto instead"
 2762   , make_dep_flag defGhcFlag "auto"
 2763                     (noArg (\d -> d { profAuto = ProfAutoExports } ))
 2764                     "Use -fprof-auto-exported instead"
 2765   , make_dep_flag defGhcFlag "no-auto"
 2766             (noArg (\d -> d { profAuto = NoProfAuto } ))
 2767                     "Use -fno-prof-auto instead"
 2768   , make_dep_flag defGhcFlag "caf-all"
 2769             (NoArg (setGeneralFlag Opt_AutoSccsOnIndividualCafs))
 2770                     "Use -fprof-cafs instead"
 2771   , make_dep_flag defGhcFlag "no-caf-all"
 2772             (NoArg (unSetGeneralFlag Opt_AutoSccsOnIndividualCafs))
 2773                     "Use -fno-prof-cafs instead"
 2774 
 2775         -- NEW profiling flags
 2776   , make_ord_flag defGhcFlag "fprof-auto"
 2777       (noArg (\d -> d { profAuto = ProfAutoAll } ))
 2778   , make_ord_flag defGhcFlag "fprof-auto-top"
 2779       (noArg (\d -> d { profAuto = ProfAutoTop } ))
 2780   , make_ord_flag defGhcFlag "fprof-auto-exported"
 2781       (noArg (\d -> d { profAuto = ProfAutoExports } ))
 2782   , make_ord_flag defGhcFlag "fprof-auto-calls"
 2783       (noArg (\d -> d { profAuto = ProfAutoCalls } ))
 2784   , make_ord_flag defGhcFlag "fno-prof-auto"
 2785       (noArg (\d -> d { profAuto = NoProfAuto } ))
 2786 
 2787         -- Caller-CC
 2788   , make_ord_flag defGhcFlag "fprof-callers"
 2789          (HasArg setCallerCcFilters)
 2790   , make_ord_flag defGhcFlag "fdistinct-constructor-tables"
 2791       (NoArg (setGeneralFlag Opt_DistinctConstructorTables))
 2792   , make_ord_flag defGhcFlag "finfo-table-map"
 2793       (NoArg (setGeneralFlag Opt_InfoTableMap))
 2794         ------ Compiler flags -----------------------------------------------
 2795 
 2796   , make_ord_flag defGhcFlag "fasm"             (NoArg (setObjBackend NCG))
 2797   , make_ord_flag defGhcFlag "fvia-c"           (NoArg
 2798          (deprecate $ "The -fvia-c flag does nothing; " ++
 2799                       "it will be removed in a future GHC release"))
 2800   , make_ord_flag defGhcFlag "fvia-C"           (NoArg
 2801          (deprecate $ "The -fvia-C flag does nothing; " ++
 2802                       "it will be removed in a future GHC release"))
 2803   , make_ord_flag defGhcFlag "fllvm"            (NoArg (setObjBackend LLVM))
 2804 
 2805   , make_ord_flag defFlag "fno-code"         (NoArg ((upd $ \d ->
 2806                   d { ghcLink=NoLink }) >> setBackend NoBackend))
 2807   , make_ord_flag defFlag "fbyte-code"
 2808       (noArgM $ \dflags -> do
 2809         setBackend Interpreter
 2810         pure $ gopt_set dflags Opt_ByteCode)
 2811   , make_ord_flag defFlag "fobject-code"     $ NoArg $ do
 2812       dflags <- liftEwM getCmdLineState
 2813       setBackend $ platformDefaultBackend (targetPlatform dflags)
 2814 
 2815   , make_dep_flag defFlag "fglasgow-exts"
 2816       (NoArg enableGlasgowExts) "Use individual extensions instead"
 2817   , make_dep_flag defFlag "fno-glasgow-exts"
 2818       (NoArg disableGlasgowExts) "Use individual extensions instead"
 2819   , make_ord_flag defFlag "Wunused-binds" (NoArg enableUnusedBinds)
 2820   , make_ord_flag defFlag "Wno-unused-binds" (NoArg disableUnusedBinds)
 2821   , make_ord_flag defHiddenFlag "fwarn-unused-binds" (NoArg enableUnusedBinds)
 2822   , make_ord_flag defHiddenFlag "fno-warn-unused-binds" (NoArg
 2823                                                             disableUnusedBinds)
 2824 
 2825         ------ Safe Haskell flags -------------------------------------------
 2826   , make_ord_flag defFlag "fpackage-trust"   (NoArg setPackageTrust)
 2827   , make_ord_flag defFlag "fno-safe-infer"   (noArg (\d ->
 2828                                                     d { safeInfer = False }))
 2829   , make_ord_flag defFlag "fno-safe-haskell" (NoArg (setSafeHaskell Sf_Ignore))
 2830 
 2831         ------ position independent flags  ----------------------------------
 2832   , make_ord_flag defGhcFlag "fPIC"          (NoArg (setGeneralFlag Opt_PIC))
 2833   , make_ord_flag defGhcFlag "fno-PIC"       (NoArg (unSetGeneralFlag Opt_PIC))
 2834   , make_ord_flag defGhcFlag "fPIE"          (NoArg (setGeneralFlag Opt_PIE))
 2835   , make_ord_flag defGhcFlag "fno-PIE"       (NoArg (unSetGeneralFlag Opt_PIE))
 2836 
 2837          ------ Debugging flags ----------------------------------------------
 2838   , make_ord_flag defGhcFlag "g"             (OptIntSuffix setDebugLevel)
 2839  ]
 2840  ++ map (mkFlag turnOn  ""          setGeneralFlag    ) negatableFlagsDeps
 2841  ++ map (mkFlag turnOff "no-"       unSetGeneralFlag  ) negatableFlagsDeps
 2842  ++ map (mkFlag turnOn  "d"         setGeneralFlag    ) dFlagsDeps
 2843  ++ map (mkFlag turnOff "dno-"      unSetGeneralFlag  ) dFlagsDeps
 2844  ++ map (mkFlag turnOn  "f"         setGeneralFlag    ) fFlagsDeps
 2845  ++ map (mkFlag turnOff "fno-"      unSetGeneralFlag  ) fFlagsDeps
 2846  ++ map (mkFlag turnOn  "W"         setWarningFlag    ) wWarningFlagsDeps
 2847  ++ map (mkFlag turnOff "Wno-"      unSetWarningFlag  ) wWarningFlagsDeps
 2848  ++ map (mkFlag turnOn  "Werror="   setWErrorFlag )     wWarningFlagsDeps
 2849  ++ map (mkFlag turnOn  "Wwarn="     unSetFatalWarningFlag )
 2850                                                         wWarningFlagsDeps
 2851  ++ map (mkFlag turnOn  "Wno-error=" unSetFatalWarningFlag )
 2852                                                         wWarningFlagsDeps
 2853  ++ map (mkFlag turnOn  "fwarn-"    setWarningFlag   . hideFlag)
 2854     wWarningFlagsDeps
 2855  ++ map (mkFlag turnOff "fno-warn-" unSetWarningFlag . hideFlag)
 2856     wWarningFlagsDeps
 2857  ++ [ (NotDeprecated, unrecognisedWarning "W"),
 2858       (Deprecated,    unrecognisedWarning "fwarn-"),
 2859       (Deprecated,    unrecognisedWarning "fno-warn-") ]
 2860  ++ [ make_ord_flag defFlag "Werror=compat"
 2861         (NoArg (mapM_ setWErrorFlag minusWcompatOpts))
 2862     , make_ord_flag defFlag "Wno-error=compat"
 2863         (NoArg (mapM_ unSetFatalWarningFlag minusWcompatOpts))
 2864     , make_ord_flag defFlag "Wwarn=compat"
 2865         (NoArg (mapM_ unSetFatalWarningFlag minusWcompatOpts)) ]
 2866  ++ map (mkFlag turnOn  "f"         setExtensionFlag  ) fLangFlagsDeps
 2867  ++ map (mkFlag turnOff "fno-"      unSetExtensionFlag) fLangFlagsDeps
 2868  ++ map (mkFlag turnOn  "X"         setExtensionFlag  ) xFlagsDeps
 2869  ++ map (mkFlag turnOff "XNo"       unSetExtensionFlag) xFlagsDeps
 2870  ++ map (mkFlag turnOn  "X"         setLanguage       ) languageFlagsDeps
 2871  ++ map (mkFlag turnOn  "X"         setSafeHaskell    ) safeHaskellFlagsDeps
 2872 
 2873 -- | This is where we handle unrecognised warning flags. We only issue a warning
 2874 -- if -Wunrecognised-warning-flags is set. See #11429 for context.
 2875 unrecognisedWarning :: String -> Flag (CmdLineP DynFlags)
 2876 unrecognisedWarning prefix = defHiddenFlag prefix (Prefix action)
 2877   where
 2878     action :: String -> EwM (CmdLineP DynFlags) ()
 2879     action flag = do
 2880       f <- wopt Opt_WarnUnrecognisedWarningFlags <$> liftEwM getCmdLineState
 2881       when f $ addFlagWarn (WarningWithFlag Opt_WarnUnrecognisedWarningFlags) $
 2882         "unrecognised warning flag: -" ++ prefix ++ flag
 2883 
 2884 -- See Note [Supporting CLI completion]
 2885 package_flags_deps :: [(Deprecation, Flag (CmdLineP DynFlags))]
 2886 package_flags_deps = [
 2887         ------- Packages ----------------------------------------------------
 2888     make_ord_flag defFlag "package-db"
 2889       (HasArg (addPkgDbRef . PkgDbPath))
 2890   , make_ord_flag defFlag "clear-package-db"      (NoArg clearPkgDb)
 2891   , make_ord_flag defFlag "no-global-package-db"  (NoArg removeGlobalPkgDb)
 2892   , make_ord_flag defFlag "no-user-package-db"    (NoArg removeUserPkgDb)
 2893   , make_ord_flag defFlag "global-package-db"
 2894       (NoArg (addPkgDbRef GlobalPkgDb))
 2895   , make_ord_flag defFlag "user-package-db"
 2896       (NoArg (addPkgDbRef UserPkgDb))
 2897     -- backwards compat with GHC<=7.4 :
 2898   , make_dep_flag defFlag "package-conf"
 2899       (HasArg $ addPkgDbRef . PkgDbPath) "Use -package-db instead"
 2900   , make_dep_flag defFlag "no-user-package-conf"
 2901       (NoArg removeUserPkgDb)              "Use -no-user-package-db instead"
 2902   , make_ord_flag defGhcFlag "package-name"       (HasArg $ \name ->
 2903                                       upd (setUnitId name))
 2904   , make_ord_flag defGhcFlag "this-unit-id"       (hasArg setUnitId)
 2905   , make_ord_flag defFlag "package"               (HasArg exposePackage)
 2906   , make_ord_flag defFlag "plugin-package-id"     (HasArg exposePluginPackageId)
 2907   , make_ord_flag defFlag "plugin-package"        (HasArg exposePluginPackage)
 2908   , make_ord_flag defFlag "package-id"            (HasArg exposePackageId)
 2909   , make_ord_flag defFlag "hide-package"          (HasArg hidePackage)
 2910   , make_ord_flag defFlag "hide-all-packages"
 2911       (NoArg (setGeneralFlag Opt_HideAllPackages))
 2912   , make_ord_flag defFlag "hide-all-plugin-packages"
 2913       (NoArg (setGeneralFlag Opt_HideAllPluginPackages))
 2914   , make_ord_flag defFlag "package-env"           (HasArg setPackageEnv)
 2915   , make_ord_flag defFlag "ignore-package"        (HasArg ignorePackage)
 2916   , make_dep_flag defFlag "syslib" (HasArg exposePackage) "Use -package instead"
 2917   , make_ord_flag defFlag "distrust-all-packages"
 2918       (NoArg (setGeneralFlag Opt_DistrustAllPackages))
 2919   , make_ord_flag defFlag "trust"                 (HasArg trustPackage)
 2920   , make_ord_flag defFlag "distrust"              (HasArg distrustPackage)
 2921   ]
 2922   where
 2923     setPackageEnv env = upd $ \s -> s { packageEnv = Just env }
 2924 
 2925 -- | Make a list of flags for shell completion.
 2926 -- Filter all available flags into two groups, for interactive GHC vs all other.
 2927 flagsForCompletion :: Bool -> [String]
 2928 flagsForCompletion isInteractive
 2929     = [ '-':flagName flag
 2930       | flag <- flagsAll
 2931       , modeFilter (flagGhcMode flag)
 2932       ]
 2933     where
 2934       modeFilter AllModes = True
 2935       modeFilter OnlyGhci = isInteractive
 2936       modeFilter OnlyGhc = not isInteractive
 2937       modeFilter HiddenFlag = False
 2938 
 2939 type TurnOnFlag = Bool   -- True  <=> we are turning the flag on
 2940                          -- False <=> we are turning the flag off
 2941 turnOn  :: TurnOnFlag; turnOn  = True
 2942 turnOff :: TurnOnFlag; turnOff = False
 2943 
 2944 data FlagSpec flag
 2945    = FlagSpec
 2946        { flagSpecName :: String   -- ^ Flag in string form
 2947        , flagSpecFlag :: flag     -- ^ Flag in internal form
 2948        , flagSpecAction :: (TurnOnFlag -> DynP ())
 2949            -- ^ Extra action to run when the flag is found
 2950            -- Typically, emit a warning or error
 2951        , flagSpecGhcMode :: GhcFlagMode
 2952            -- ^ In which ghc mode the flag has effect
 2953        }
 2954 
 2955 -- | Define a new flag.
 2956 flagSpec :: String -> flag -> (Deprecation, FlagSpec flag)
 2957 flagSpec name flag = flagSpec' name flag nop
 2958 
 2959 -- | Define a new flag with an effect.
 2960 flagSpec' :: String -> flag -> (TurnOnFlag -> DynP ())
 2961           -> (Deprecation, FlagSpec flag)
 2962 flagSpec' name flag act = (NotDeprecated, FlagSpec name flag act AllModes)
 2963 
 2964 -- | Define a warning flag.
 2965 warnSpec :: WarningFlag -> [(Deprecation, FlagSpec WarningFlag)]
 2966 warnSpec flag = warnSpec' flag nop
 2967 
 2968 -- | Define a warning flag with an effect.
 2969 warnSpec' :: WarningFlag -> (TurnOnFlag -> DynP ())
 2970           -> [(Deprecation, FlagSpec WarningFlag)]
 2971 warnSpec' flag act = [ (NotDeprecated, FlagSpec name flag act AllModes)
 2972                      | name <- NE.toList (warnFlagNames flag)
 2973                      ]
 2974 
 2975 -- | Define a new deprecated flag with an effect.
 2976 depFlagSpecOp :: String -> flag -> (TurnOnFlag -> DynP ()) -> String
 2977             -> (Deprecation, FlagSpec flag)
 2978 depFlagSpecOp name flag act dep =
 2979     (Deprecated, snd (flagSpec' name flag (\f -> act f >> deprecate dep)))
 2980 
 2981 -- | Define a new deprecated flag.
 2982 depFlagSpec :: String -> flag -> String
 2983             -> (Deprecation, FlagSpec flag)
 2984 depFlagSpec name flag dep = depFlagSpecOp name flag nop dep
 2985 
 2986 -- | Define a deprecated warning flag.
 2987 depWarnSpec :: WarningFlag -> String
 2988             -> [(Deprecation, FlagSpec WarningFlag)]
 2989 depWarnSpec flag dep = [ depFlagSpecOp name flag nop dep
 2990                        | name <- NE.toList (warnFlagNames flag)
 2991                        ]
 2992 
 2993 -- | Define a deprecated warning name substituted by another.
 2994 subWarnSpec :: String -> WarningFlag -> String
 2995             -> [(Deprecation, FlagSpec WarningFlag)]
 2996 subWarnSpec oldname flag dep = [ depFlagSpecOp oldname flag nop dep ]
 2997 
 2998 
 2999 -- | Define a new deprecated flag with an effect where the deprecation message
 3000 -- depends on the flag value
 3001 depFlagSpecOp' :: String
 3002              -> flag
 3003              -> (TurnOnFlag -> DynP ())
 3004              -> (TurnOnFlag -> String)
 3005              -> (Deprecation, FlagSpec flag)
 3006 depFlagSpecOp' name flag act dep =
 3007     (Deprecated, FlagSpec name flag (\f -> act f >> (deprecate $ dep f))
 3008                                                                        AllModes)
 3009 
 3010 -- | Define a new deprecated flag where the deprecation message
 3011 -- depends on the flag value
 3012 depFlagSpec' :: String
 3013              -> flag
 3014              -> (TurnOnFlag -> String)
 3015              -> (Deprecation, FlagSpec flag)
 3016 depFlagSpec' name flag dep = depFlagSpecOp' name flag nop dep
 3017 
 3018 
 3019 -- | Define a new deprecated flag where the deprecation message
 3020 -- is shown depending on the flag value
 3021 depFlagSpecCond :: String
 3022                 -> flag
 3023                 -> (TurnOnFlag -> Bool)
 3024                 -> String
 3025                 -> (Deprecation, FlagSpec flag)
 3026 depFlagSpecCond name flag cond dep =
 3027     (Deprecated, FlagSpec name flag (\f -> when (cond f) $ deprecate dep)
 3028                                                                        AllModes)
 3029 
 3030 -- | Define a new flag for GHCi.
 3031 flagGhciSpec :: String -> flag -> (Deprecation, FlagSpec flag)
 3032 flagGhciSpec name flag = flagGhciSpec' name flag nop
 3033 
 3034 -- | Define a new flag for GHCi with an effect.
 3035 flagGhciSpec' :: String -> flag -> (TurnOnFlag -> DynP ())
 3036               -> (Deprecation, FlagSpec flag)
 3037 flagGhciSpec' name flag act = (NotDeprecated, FlagSpec name flag act OnlyGhci)
 3038 
 3039 -- | Define a new flag invisible to CLI completion.
 3040 flagHiddenSpec :: String -> flag -> (Deprecation, FlagSpec flag)
 3041 flagHiddenSpec name flag = flagHiddenSpec' name flag nop
 3042 
 3043 -- | Define a new flag invisible to CLI completion with an effect.
 3044 flagHiddenSpec' :: String -> flag -> (TurnOnFlag -> DynP ())
 3045                 -> (Deprecation, FlagSpec flag)
 3046 flagHiddenSpec' name flag act = (NotDeprecated, FlagSpec name flag act
 3047                                                                      HiddenFlag)
 3048 
 3049 -- | Hide a 'FlagSpec' from being displayed in @--show-options@.
 3050 --
 3051 -- This is for example useful for flags that are obsolete, but should not
 3052 -- (yet) be deprecated for compatibility reasons.
 3053 hideFlag :: (Deprecation, FlagSpec a) -> (Deprecation, FlagSpec a)
 3054 hideFlag (dep, fs) = (dep, fs { flagSpecGhcMode = HiddenFlag })
 3055 
 3056 mkFlag :: TurnOnFlag            -- ^ True <=> it should be turned on
 3057        -> String                -- ^ The flag prefix
 3058        -> (flag -> DynP ())     -- ^ What to do when the flag is found
 3059        -> (Deprecation, FlagSpec flag)  -- ^ Specification of
 3060                                         -- this particular flag
 3061        -> (Deprecation, Flag (CmdLineP DynFlags))
 3062 mkFlag turn_on flagPrefix f (dep, (FlagSpec name flag extra_action mode))
 3063     = (dep,
 3064        Flag (flagPrefix ++ name) (NoArg (f flag >> extra_action turn_on)) mode)
 3065 
 3066 -- here to avoid module cycle with GHC.Driver.CmdLine
 3067 deprecate :: Monad m => String -> EwM m ()
 3068 deprecate s = do
 3069     arg <- getArg
 3070     addFlagWarn (WarningWithFlag Opt_WarnDeprecatedFlags) (arg ++ " is deprecated: " ++ s)
 3071 
 3072 deprecatedForExtension :: String -> TurnOnFlag -> String
 3073 deprecatedForExtension lang turn_on
 3074     = "use -X" ++ flag ++
 3075       " or pragma {-# LANGUAGE " ++ flag ++ " #-} instead"
 3076     where
 3077       flag | turn_on   = lang
 3078            | otherwise = "No" ++ lang
 3079 
 3080 useInstead :: String -> String -> TurnOnFlag -> String
 3081 useInstead prefix flag turn_on
 3082   = "Use " ++ prefix ++ no ++ flag ++ " instead"
 3083   where
 3084     no = if turn_on then "" else "no-"
 3085 
 3086 nop :: TurnOnFlag -> DynP ()
 3087 nop _ = return ()
 3088 
 3089 -- | Find the 'FlagSpec' for a 'WarningFlag'.
 3090 flagSpecOf :: WarningFlag -> Maybe (FlagSpec WarningFlag)
 3091 flagSpecOf = flip Map.lookup wWarningFlagMap
 3092 
 3093 wWarningFlagMap :: Map.Map WarningFlag (FlagSpec WarningFlag)
 3094 wWarningFlagMap = Map.fromListWith (\_ x -> x) $ map (flagSpecFlag &&& id) wWarningFlags
 3095 
 3096 -- | These @-W\<blah\>@ flags can all be reversed with @-Wno-\<blah\>@
 3097 wWarningFlags :: [FlagSpec WarningFlag]
 3098 wWarningFlags = map snd (sortBy (comparing fst) wWarningFlagsDeps)
 3099 
 3100 wWarningFlagsDeps :: [(Deprecation, FlagSpec WarningFlag)]
 3101 wWarningFlagsDeps = mconcat [
 3102 -- See Note [Updating flag description in the User's Guide]
 3103 -- See Note [Supporting CLI completion]
 3104 -- Please keep the list of flags below sorted alphabetically
 3105   warnSpec    Opt_WarnAlternativeLayoutRuleTransitional,
 3106   warnSpec    Opt_WarnAmbiguousFields,
 3107   depWarnSpec Opt_WarnAutoOrphans
 3108               "it has no effect",
 3109   warnSpec    Opt_WarnCPPUndef,
 3110   warnSpec    Opt_WarnUnbangedStrictPatterns,
 3111   warnSpec    Opt_WarnDeferredTypeErrors,
 3112   warnSpec    Opt_WarnDeferredOutOfScopeVariables,
 3113   warnSpec    Opt_WarnWarningsDeprecations,
 3114   warnSpec    Opt_WarnDeprecatedFlags,
 3115   warnSpec    Opt_WarnDerivingDefaults,
 3116   warnSpec    Opt_WarnDerivingTypeable,
 3117   warnSpec    Opt_WarnDodgyExports,
 3118   warnSpec    Opt_WarnDodgyForeignImports,
 3119   warnSpec    Opt_WarnDodgyImports,
 3120   warnSpec    Opt_WarnEmptyEnumerations,
 3121   subWarnSpec "duplicate-constraints"
 3122               Opt_WarnDuplicateConstraints
 3123               "it is subsumed by -Wredundant-constraints",
 3124   warnSpec    Opt_WarnRedundantConstraints,
 3125   warnSpec    Opt_WarnDuplicateExports,
 3126   depWarnSpec Opt_WarnHiShadows
 3127               "it is not used, and was never implemented",
 3128   warnSpec    Opt_WarnInaccessibleCode,
 3129   warnSpec    Opt_WarnImplicitPrelude,
 3130   depWarnSpec Opt_WarnImplicitKindVars
 3131               "it is now an error",
 3132   warnSpec    Opt_WarnIncompletePatterns,
 3133   warnSpec    Opt_WarnIncompletePatternsRecUpd,
 3134   warnSpec    Opt_WarnIncompleteUniPatterns,
 3135   warnSpec    Opt_WarnInlineRuleShadowing,
 3136   warnSpec    Opt_WarnIdentities,
 3137   warnSpec    Opt_WarnMissingFields,
 3138   warnSpec    Opt_WarnMissingImportList,
 3139   warnSpec    Opt_WarnMissingExportList,
 3140   subWarnSpec "missing-local-sigs"
 3141               Opt_WarnMissingLocalSignatures
 3142               "it is replaced by -Wmissing-local-signatures",
 3143   warnSpec    Opt_WarnMissingLocalSignatures,
 3144   warnSpec    Opt_WarnMissingMethods,
 3145   depWarnSpec Opt_WarnMissingMonadFailInstances
 3146               "fail is no longer a method of Monad",
 3147   warnSpec    Opt_WarnSemigroup,
 3148   warnSpec    Opt_WarnMissingSignatures,
 3149   warnSpec    Opt_WarnMissingKindSignatures,
 3150   subWarnSpec "missing-exported-sigs"
 3151               Opt_WarnMissingExportedSignatures
 3152               "it is replaced by -Wmissing-exported-signatures",
 3153   warnSpec    Opt_WarnMissingExportedSignatures,
 3154   warnSpec    Opt_WarnMonomorphism,
 3155   warnSpec    Opt_WarnNameShadowing,
 3156   warnSpec    Opt_WarnNonCanonicalMonadInstances,
 3157   depWarnSpec Opt_WarnNonCanonicalMonadFailInstances
 3158               "fail is no longer a method of Monad",
 3159   warnSpec    Opt_WarnNonCanonicalMonoidInstances,
 3160   warnSpec    Opt_WarnOrphans,
 3161   warnSpec    Opt_WarnOverflowedLiterals,
 3162   warnSpec    Opt_WarnOverlappingPatterns,
 3163   warnSpec    Opt_WarnMissedSpecs,
 3164   warnSpec    Opt_WarnAllMissedSpecs,
 3165   warnSpec'   Opt_WarnSafe setWarnSafe,
 3166   warnSpec    Opt_WarnTrustworthySafe,
 3167   warnSpec    Opt_WarnInferredSafeImports,
 3168   warnSpec    Opt_WarnMissingSafeHaskellMode,
 3169   warnSpec    Opt_WarnTabs,
 3170   warnSpec    Opt_WarnTypeDefaults,
 3171   warnSpec    Opt_WarnTypedHoles,
 3172   warnSpec    Opt_WarnPartialTypeSignatures,
 3173   warnSpec    Opt_WarnUnrecognisedPragmas,
 3174   warnSpec'   Opt_WarnUnsafe setWarnUnsafe,
 3175   warnSpec    Opt_WarnUnsupportedCallingConventions,
 3176   warnSpec    Opt_WarnUnsupportedLlvmVersion,
 3177   warnSpec    Opt_WarnMissedExtraSharedLib,
 3178   warnSpec    Opt_WarnUntickedPromotedConstructors,
 3179   warnSpec    Opt_WarnUnusedDoBind,
 3180   warnSpec    Opt_WarnUnusedForalls,
 3181   warnSpec    Opt_WarnUnusedImports,
 3182   warnSpec    Opt_WarnUnusedLocalBinds,
 3183   warnSpec    Opt_WarnUnusedMatches,
 3184   warnSpec    Opt_WarnUnusedPatternBinds,
 3185   warnSpec    Opt_WarnUnusedTopBinds,
 3186   warnSpec    Opt_WarnUnusedTypePatterns,
 3187   warnSpec    Opt_WarnUnusedRecordWildcards,
 3188   warnSpec    Opt_WarnRedundantBangPatterns,
 3189   warnSpec    Opt_WarnRedundantRecordWildcards,
 3190   warnSpec    Opt_WarnRedundantStrictnessFlags,
 3191   warnSpec    Opt_WarnWrongDoBind,
 3192   warnSpec    Opt_WarnMissingPatternSynonymSignatures,
 3193   warnSpec    Opt_WarnMissingDerivingStrategies,
 3194   warnSpec    Opt_WarnSimplifiableClassConstraints,
 3195   warnSpec    Opt_WarnMissingHomeModules,
 3196   warnSpec    Opt_WarnUnrecognisedWarningFlags,
 3197   warnSpec    Opt_WarnStarBinder,
 3198   warnSpec    Opt_WarnStarIsType,
 3199   depWarnSpec Opt_WarnSpaceAfterBang
 3200               "bang patterns can no longer be written with a space",
 3201   warnSpec    Opt_WarnPartialFields,
 3202   warnSpec    Opt_WarnPrepositiveQualifiedModule,
 3203   warnSpec    Opt_WarnUnusedPackages,
 3204   warnSpec    Opt_WarnCompatUnqualifiedImports,
 3205   warnSpec    Opt_WarnInvalidHaddock,
 3206   warnSpec    Opt_WarnOperatorWhitespaceExtConflict,
 3207   warnSpec    Opt_WarnOperatorWhitespace,
 3208   warnSpec    Opt_WarnImplicitLift,
 3209   warnSpec    Opt_WarnMissingExportedPatternSynonymSignatures,
 3210   warnSpec    Opt_WarnUnicodeBidirectionalFormatCharacters
 3211  ]
 3212 
 3213 -- | These @-\<blah\>@ flags can all be reversed with @-no-\<blah\>@
 3214 negatableFlagsDeps :: [(Deprecation, FlagSpec GeneralFlag)]
 3215 negatableFlagsDeps = [
 3216   flagGhciSpec "ignore-dot-ghci"         Opt_IgnoreDotGhci ]
 3217 
 3218 -- | These @-d\<blah\>@ flags can all be reversed with @-dno-\<blah\>@
 3219 dFlagsDeps :: [(Deprecation, FlagSpec GeneralFlag)]
 3220 dFlagsDeps = [
 3221 -- See Note [Updating flag description in the User's Guide]
 3222 -- See Note [Supporting CLI completion]
 3223 -- Please keep the list of flags below sorted alphabetically
 3224   flagSpec "ppr-case-as-let"            Opt_PprCaseAsLet,
 3225   depFlagSpec' "ppr-ticks"              Opt_PprShowTicks
 3226      (\turn_on -> useInstead "-d" "suppress-ticks" (not turn_on)),
 3227   flagSpec "suppress-ticks"             Opt_SuppressTicks,
 3228   depFlagSpec' "suppress-stg-free-vars" Opt_SuppressStgExts
 3229      (useInstead "-d" "suppress-stg-exts"),
 3230   flagSpec "suppress-stg-exts"          Opt_SuppressStgExts,
 3231   flagSpec "suppress-coercions"         Opt_SuppressCoercions,
 3232   flagSpec "suppress-idinfo"            Opt_SuppressIdInfo,
 3233   flagSpec "suppress-unfoldings"        Opt_SuppressUnfoldings,
 3234   flagSpec "suppress-module-prefixes"   Opt_SuppressModulePrefixes,
 3235   flagSpec "suppress-timestamps"        Opt_SuppressTimestamps,
 3236   flagSpec "suppress-type-applications" Opt_SuppressTypeApplications,
 3237   flagSpec "suppress-type-signatures"   Opt_SuppressTypeSignatures,
 3238   flagSpec "suppress-uniques"           Opt_SuppressUniques,
 3239   flagSpec "suppress-var-kinds"         Opt_SuppressVarKinds,
 3240   flagSpec "suppress-core-sizes"        Opt_SuppressCoreSizes
 3241   ]
 3242 
 3243 -- | These @-f\<blah\>@ flags can all be reversed with @-fno-\<blah\>@
 3244 fFlags :: [FlagSpec GeneralFlag]
 3245 fFlags = map snd fFlagsDeps
 3246 
 3247 fFlagsDeps :: [(Deprecation, FlagSpec GeneralFlag)]
 3248 fFlagsDeps = [
 3249 -- See Note [Updating flag description in the User's Guide]
 3250 -- See Note [Supporting CLI completion]
 3251 -- Please keep the list of flags below sorted alphabetically
 3252   flagSpec "asm-shortcutting"                 Opt_AsmShortcutting,
 3253   flagGhciSpec "break-on-error"               Opt_BreakOnError,
 3254   flagGhciSpec "break-on-exception"           Opt_BreakOnException,
 3255   flagSpec "building-cabal-package"           Opt_BuildingCabalPackage,
 3256   flagSpec "call-arity"                       Opt_CallArity,
 3257   flagSpec "exitification"                    Opt_Exitification,
 3258   flagSpec "case-merge"                       Opt_CaseMerge,
 3259   flagSpec "case-folding"                     Opt_CaseFolding,
 3260   flagSpec "cmm-elim-common-blocks"           Opt_CmmElimCommonBlocks,
 3261   flagSpec "cmm-sink"                         Opt_CmmSink,
 3262   flagSpec "cmm-static-pred"                  Opt_CmmStaticPred,
 3263   flagSpec "cse"                              Opt_CSE,
 3264   flagSpec "stg-cse"                          Opt_StgCSE,
 3265   flagSpec "stg-lift-lams"                    Opt_StgLiftLams,
 3266   flagSpec "cpr-anal"                         Opt_CprAnal,
 3267   flagSpec "defer-diagnostics"                Opt_DeferDiagnostics,
 3268   flagSpec "defer-type-errors"                Opt_DeferTypeErrors,
 3269   flagSpec "defer-typed-holes"                Opt_DeferTypedHoles,
 3270   flagSpec "defer-out-of-scope-variables"     Opt_DeferOutOfScopeVariables,
 3271   flagSpec "diagnostics-show-caret"           Opt_DiagnosticsShowCaret,
 3272   flagSpec "dicts-cheap"                      Opt_DictsCheap,
 3273   flagSpec "dicts-strict"                     Opt_DictsStrict,
 3274   depFlagSpec "dmd-tx-dict-sel"
 3275       Opt_DmdTxDictSel "effect is now unconditionally enabled",
 3276   flagSpec "do-eta-reduction"                 Opt_DoEtaReduction,
 3277   flagSpec "do-lambda-eta-expansion"          Opt_DoLambdaEtaExpansion,
 3278   flagSpec "eager-blackholing"                Opt_EagerBlackHoling,
 3279   flagSpec "embed-manifest"                   Opt_EmbedManifest,
 3280   flagSpec "enable-rewrite-rules"             Opt_EnableRewriteRules,
 3281   flagSpec "enable-th-splice-warnings"        Opt_EnableThSpliceWarnings,
 3282   flagSpec "error-spans"                      Opt_ErrorSpans,
 3283   flagSpec "excess-precision"                 Opt_ExcessPrecision,
 3284   flagSpec "expose-all-unfoldings"            Opt_ExposeAllUnfoldings,
 3285   flagSpec "expose-internal-symbols"          Opt_ExposeInternalSymbols,
 3286   flagSpec "external-dynamic-refs"            Opt_ExternalDynamicRefs,
 3287   flagSpec "external-interpreter"             Opt_ExternalInterpreter,
 3288   flagSpec "family-application-cache"         Opt_FamAppCache,
 3289   flagSpec "float-in"                         Opt_FloatIn,
 3290   flagSpec "force-recomp"                     Opt_ForceRecomp,
 3291   flagSpec "ignore-optim-changes"             Opt_IgnoreOptimChanges,
 3292   flagSpec "ignore-hpc-changes"               Opt_IgnoreHpcChanges,
 3293   flagSpec "full-laziness"                    Opt_FullLaziness,
 3294   flagSpec "fun-to-thunk"                     Opt_FunToThunk,
 3295   flagSpec "gen-manifest"                     Opt_GenManifest,
 3296   flagSpec "ghci-history"                     Opt_GhciHistory,
 3297   flagSpec "ghci-leak-check"                  Opt_GhciLeakCheck,
 3298   flagSpec "validate-ide-info"                Opt_ValidateHie,
 3299   flagGhciSpec "local-ghci-history"           Opt_LocalGhciHistory,
 3300   flagGhciSpec "no-it"                        Opt_NoIt,
 3301   flagSpec "ghci-sandbox"                     Opt_GhciSandbox,
 3302   flagSpec "helpful-errors"                   Opt_HelpfulErrors,
 3303   flagSpec "hpc"                              Opt_Hpc,
 3304   flagSpec "ignore-asserts"                   Opt_IgnoreAsserts,
 3305   flagSpec "ignore-interface-pragmas"         Opt_IgnoreInterfacePragmas,
 3306   flagGhciSpec "implicit-import-qualified"    Opt_ImplicitImportQualified,
 3307   flagSpec "irrefutable-tuples"               Opt_IrrefutableTuples,
 3308   flagSpec "keep-going"                       Opt_KeepGoing,
 3309   flagSpec "late-dmd-anal"                    Opt_LateDmdAnal,
 3310   flagSpec "late-specialise"                  Opt_LateSpecialise,
 3311   flagSpec "liberate-case"                    Opt_LiberateCase,
 3312   flagHiddenSpec "llvm-tbaa"                  Opt_LlvmTBAA,
 3313   flagHiddenSpec "llvm-fill-undef-with-garbage" Opt_LlvmFillUndefWithGarbage,
 3314   flagSpec "loopification"                    Opt_Loopification,
 3315   flagSpec "block-layout-cfg"                 Opt_CfgBlocklayout,
 3316   flagSpec "block-layout-weightless"          Opt_WeightlessBlocklayout,
 3317   flagSpec "omit-interface-pragmas"           Opt_OmitInterfacePragmas,
 3318   flagSpec "omit-yields"                      Opt_OmitYields,
 3319   flagSpec "optimal-applicative-do"           Opt_OptimalApplicativeDo,
 3320   flagSpec "pedantic-bottoms"                 Opt_PedanticBottoms,
 3321   flagSpec "pre-inlining"                     Opt_SimplPreInlining,
 3322   flagGhciSpec "print-bind-contents"          Opt_PrintBindContents,
 3323   flagGhciSpec "print-bind-result"            Opt_PrintBindResult,
 3324   flagGhciSpec "print-evld-with-show"         Opt_PrintEvldWithShow,
 3325   flagSpec "print-explicit-foralls"           Opt_PrintExplicitForalls,
 3326   flagSpec "print-explicit-kinds"             Opt_PrintExplicitKinds,
 3327   flagSpec "print-explicit-coercions"         Opt_PrintExplicitCoercions,
 3328   flagSpec "print-explicit-runtime-reps"      Opt_PrintExplicitRuntimeReps,
 3329   flagSpec "print-equality-relations"         Opt_PrintEqualityRelations,
 3330   flagSpec "print-axiom-incomps"              Opt_PrintAxiomIncomps,
 3331   flagSpec "print-unicode-syntax"             Opt_PrintUnicodeSyntax,
 3332   flagSpec "print-expanded-synonyms"          Opt_PrintExpandedSynonyms,
 3333   flagSpec "print-potential-instances"        Opt_PrintPotentialInstances,
 3334   flagSpec "print-typechecker-elaboration"    Opt_PrintTypecheckerElaboration,
 3335   flagSpec "prof-cafs"                        Opt_AutoSccsOnIndividualCafs,
 3336   flagSpec "prof-count-entries"               Opt_ProfCountEntries,
 3337   flagSpec "regs-graph"                       Opt_RegsGraph,
 3338   flagSpec "regs-iterative"                   Opt_RegsIterative,
 3339   depFlagSpec' "rewrite-rules"                Opt_EnableRewriteRules
 3340    (useInstead "-f" "enable-rewrite-rules"),
 3341   flagSpec "shared-implib"                    Opt_SharedImplib,
 3342   flagSpec "spec-constr"                      Opt_SpecConstr,
 3343   flagSpec "spec-constr-keen"                 Opt_SpecConstrKeen,
 3344   flagSpec "specialise"                       Opt_Specialise,
 3345   flagSpec "specialize"                       Opt_Specialise,
 3346   flagSpec "specialise-aggressively"          Opt_SpecialiseAggressively,
 3347   flagSpec "specialize-aggressively"          Opt_SpecialiseAggressively,
 3348   flagSpec "cross-module-specialise"          Opt_CrossModuleSpecialise,
 3349   flagSpec "cross-module-specialize"          Opt_CrossModuleSpecialise,
 3350   flagSpec "inline-generics"                  Opt_InlineGenerics,
 3351   flagSpec "inline-generics-aggressively"     Opt_InlineGenericsAggressively,
 3352   flagSpec "static-argument-transformation"   Opt_StaticArgumentTransformation,
 3353   flagSpec "strictness"                       Opt_Strictness,
 3354   flagSpec "use-rpaths"                       Opt_RPath,
 3355   flagSpec "write-interface"                  Opt_WriteInterface,
 3356   flagSpec "write-ide-info"                   Opt_WriteHie,
 3357   flagSpec "unbox-small-strict-fields"        Opt_UnboxSmallStrictFields,
 3358   flagSpec "unbox-strict-fields"              Opt_UnboxStrictFields,
 3359   flagSpec "version-macros"                   Opt_VersionMacros,
 3360   flagSpec "worker-wrapper"                   Opt_WorkerWrapper,
 3361   flagSpec "solve-constant-dicts"             Opt_SolveConstantDicts,
 3362   flagSpec "catch-bottoms"                    Opt_CatchBottoms,
 3363   flagSpec "alignment-sanitisation"           Opt_AlignmentSanitisation,
 3364   flagSpec "num-constant-folding"             Opt_NumConstantFolding,
 3365   flagSpec "show-warning-groups"              Opt_ShowWarnGroups,
 3366   flagSpec "hide-source-paths"                Opt_HideSourcePaths,
 3367   flagSpec "show-loaded-modules"              Opt_ShowLoadedModules,
 3368   flagSpec "whole-archive-hs-libs"            Opt_WholeArchiveHsLibs,
 3369   flagSpec "keep-cafs"                        Opt_KeepCAFs,
 3370   flagSpec "link-rts"                         Opt_LinkRts
 3371   ]
 3372   ++ fHoleFlags
 3373 
 3374 -- | These @-f\<blah\>@ flags have to do with the typed-hole error message or
 3375 -- the valid hole fits in that message. See Note [Valid hole fits include ...]
 3376 -- in the "GHC.Tc.Errors.Hole" module. These flags can all be reversed with
 3377 -- @-fno-\<blah\>@
 3378 fHoleFlags :: [(Deprecation, FlagSpec GeneralFlag)]
 3379 fHoleFlags = [
 3380   flagSpec "show-hole-constraints"            Opt_ShowHoleConstraints,
 3381   depFlagSpec' "show-valid-substitutions"     Opt_ShowValidHoleFits
 3382    (useInstead "-f" "show-valid-hole-fits"),
 3383   flagSpec "show-valid-hole-fits"             Opt_ShowValidHoleFits,
 3384   -- Sorting settings
 3385   flagSpec "sort-valid-hole-fits"             Opt_SortValidHoleFits,
 3386   flagSpec "sort-by-size-hole-fits"           Opt_SortBySizeHoleFits,
 3387   flagSpec "sort-by-subsumption-hole-fits"    Opt_SortBySubsumHoleFits,
 3388   flagSpec "abstract-refinement-hole-fits"    Opt_AbstractRefHoleFits,
 3389   -- Output format settings
 3390   flagSpec "show-hole-matches-of-hole-fits"   Opt_ShowMatchesOfHoleFits,
 3391   flagSpec "show-provenance-of-hole-fits"     Opt_ShowProvOfHoleFits,
 3392   flagSpec "show-type-of-hole-fits"           Opt_ShowTypeOfHoleFits,
 3393   flagSpec "show-type-app-of-hole-fits"       Opt_ShowTypeAppOfHoleFits,
 3394   flagSpec "show-type-app-vars-of-hole-fits"  Opt_ShowTypeAppVarsOfHoleFits,
 3395   flagSpec "show-docs-of-hole-fits"           Opt_ShowDocsOfHoleFits,
 3396   flagSpec "unclutter-valid-hole-fits"        Opt_UnclutterValidHoleFits
 3397   ]
 3398 
 3399 -- | These @-f\<blah\>@ flags can all be reversed with @-fno-\<blah\>@
 3400 fLangFlags :: [FlagSpec LangExt.Extension]
 3401 fLangFlags = map snd fLangFlagsDeps
 3402 
 3403 fLangFlagsDeps :: [(Deprecation, FlagSpec LangExt.Extension)]
 3404 fLangFlagsDeps = [
 3405 -- See Note [Updating flag description in the User's Guide]
 3406 -- See Note [Supporting CLI completion]
 3407   depFlagSpecOp' "th"                           LangExt.TemplateHaskell
 3408     checkTemplateHaskellOk
 3409     (deprecatedForExtension "TemplateHaskell"),
 3410   depFlagSpec' "fi"                             LangExt.ForeignFunctionInterface
 3411     (deprecatedForExtension "ForeignFunctionInterface"),
 3412   depFlagSpec' "ffi"                            LangExt.ForeignFunctionInterface
 3413     (deprecatedForExtension "ForeignFunctionInterface"),
 3414   depFlagSpec' "arrows"                         LangExt.Arrows
 3415     (deprecatedForExtension "Arrows"),
 3416   depFlagSpec' "implicit-prelude"               LangExt.ImplicitPrelude
 3417     (deprecatedForExtension "ImplicitPrelude"),
 3418   depFlagSpec' "bang-patterns"                  LangExt.BangPatterns
 3419     (deprecatedForExtension "BangPatterns"),
 3420   depFlagSpec' "monomorphism-restriction"       LangExt.MonomorphismRestriction
 3421     (deprecatedForExtension "MonomorphismRestriction"),
 3422   depFlagSpec' "extended-default-rules"         LangExt.ExtendedDefaultRules
 3423     (deprecatedForExtension "ExtendedDefaultRules"),
 3424   depFlagSpec' "implicit-params"                LangExt.ImplicitParams
 3425     (deprecatedForExtension "ImplicitParams"),
 3426   depFlagSpec' "scoped-type-variables"          LangExt.ScopedTypeVariables
 3427     (deprecatedForExtension "ScopedTypeVariables"),
 3428   depFlagSpec' "allow-overlapping-instances"    LangExt.OverlappingInstances
 3429     (deprecatedForExtension "OverlappingInstances"),
 3430   depFlagSpec' "allow-undecidable-instances"    LangExt.UndecidableInstances
 3431     (deprecatedForExtension "UndecidableInstances"),
 3432   depFlagSpec' "allow-incoherent-instances"     LangExt.IncoherentInstances
 3433     (deprecatedForExtension "IncoherentInstances")
 3434   ]
 3435 
 3436 supportedLanguages :: [String]
 3437 supportedLanguages = map (flagSpecName . snd) languageFlagsDeps
 3438 
 3439 supportedLanguageOverlays :: [String]
 3440 supportedLanguageOverlays = map (flagSpecName . snd) safeHaskellFlagsDeps
 3441 
 3442 supportedExtensions :: ArchOS -> [String]
 3443 supportedExtensions (ArchOS _ os) = concatMap toFlagSpecNamePair xFlags
 3444   where
 3445     toFlagSpecNamePair flg
 3446       -- IMPORTANT! Make sure that `ghc --supported-extensions` omits
 3447       -- "TemplateHaskell"/"QuasiQuotes" when it's known not to work out of the
 3448       -- box. See also GHC #11102 and #16331 for more details about
 3449       -- the rationale
 3450       | isAIX, flagSpecFlag flg == LangExt.TemplateHaskell  = [noName]
 3451       | isAIX, flagSpecFlag flg == LangExt.QuasiQuotes      = [noName]
 3452       | otherwise = [name, noName]
 3453       where
 3454         isAIX = os == OSAIX
 3455         noName = "No" ++ name
 3456         name = flagSpecName flg
 3457 
 3458 supportedLanguagesAndExtensions :: ArchOS -> [String]
 3459 supportedLanguagesAndExtensions arch_os =
 3460     supportedLanguages ++ supportedLanguageOverlays ++ supportedExtensions arch_os
 3461 
 3462 -- | These -X<blah> flags cannot be reversed with -XNo<blah>
 3463 languageFlagsDeps :: [(Deprecation, FlagSpec Language)]
 3464 languageFlagsDeps = [
 3465   flagSpec "Haskell98"   Haskell98,
 3466   flagSpec "Haskell2010" Haskell2010,
 3467   flagSpec "GHC2021"     GHC2021
 3468   ]
 3469 
 3470 -- | These -X<blah> flags cannot be reversed with -XNo<blah>
 3471 -- They are used to place hard requirements on what GHC Haskell language
 3472 -- features can be used.
 3473 safeHaskellFlagsDeps :: [(Deprecation, FlagSpec SafeHaskellMode)]
 3474 safeHaskellFlagsDeps = [mkF Sf_Unsafe, mkF Sf_Trustworthy, mkF Sf_Safe]
 3475     where mkF flag = flagSpec (show flag) flag
 3476 
 3477 -- | These -X<blah> flags can all be reversed with -XNo<blah>
 3478 xFlags :: [FlagSpec LangExt.Extension]
 3479 xFlags = map snd xFlagsDeps
 3480 
 3481 xFlagsDeps :: [(Deprecation, FlagSpec LangExt.Extension)]
 3482 xFlagsDeps = [
 3483 -- See Note [Updating flag description in the User's Guide]
 3484 -- See Note [Supporting CLI completion]
 3485 -- See Note [Adding a language extension]
 3486 -- Please keep the list of flags below sorted alphabetically
 3487   flagSpec "AllowAmbiguousTypes"              LangExt.AllowAmbiguousTypes,
 3488   flagSpec "AlternativeLayoutRule"            LangExt.AlternativeLayoutRule,
 3489   flagSpec "AlternativeLayoutRuleTransitional"
 3490                                               LangExt.AlternativeLayoutRuleTransitional,
 3491   flagSpec "Arrows"                           LangExt.Arrows,
 3492   depFlagSpecCond "AutoDeriveTypeable"        LangExt.AutoDeriveTypeable
 3493     id
 3494          ("Typeable instances are created automatically " ++
 3495                      "for all types since GHC 8.2."),
 3496   flagSpec "BangPatterns"                     LangExt.BangPatterns,
 3497   flagSpec "BinaryLiterals"                   LangExt.BinaryLiterals,
 3498   flagSpec "CApiFFI"                          LangExt.CApiFFI,
 3499   flagSpec "CPP"                              LangExt.Cpp,
 3500   flagSpec "CUSKs"                            LangExt.CUSKs,
 3501   flagSpec "ConstrainedClassMethods"          LangExt.ConstrainedClassMethods,
 3502   flagSpec "ConstraintKinds"                  LangExt.ConstraintKinds,
 3503   flagSpec "DataKinds"                        LangExt.DataKinds,
 3504   depFlagSpecCond "DatatypeContexts"          LangExt.DatatypeContexts
 3505     id
 3506          ("It was widely considered a misfeature, " ++
 3507                      "and has been removed from the Haskell language."),
 3508   flagSpec "DefaultSignatures"                LangExt.DefaultSignatures,
 3509   flagSpec "DeriveAnyClass"                   LangExt.DeriveAnyClass,
 3510   flagSpec "DeriveDataTypeable"               LangExt.DeriveDataTypeable,
 3511   flagSpec "DeriveFoldable"                   LangExt.DeriveFoldable,
 3512   flagSpec "DeriveFunctor"                    LangExt.DeriveFunctor,
 3513   flagSpec "DeriveGeneric"                    LangExt.DeriveGeneric,
 3514   flagSpec "DeriveLift"                       LangExt.DeriveLift,
 3515   flagSpec "DeriveTraversable"                LangExt.DeriveTraversable,
 3516   flagSpec "DerivingStrategies"               LangExt.DerivingStrategies,
 3517   flagSpec' "DerivingVia"                     LangExt.DerivingVia
 3518                                               setDeriveVia,
 3519   flagSpec "DisambiguateRecordFields"         LangExt.DisambiguateRecordFields,
 3520   flagSpec "DoAndIfThenElse"                  LangExt.DoAndIfThenElse,
 3521   flagSpec "BlockArguments"                   LangExt.BlockArguments,
 3522   depFlagSpec' "DoRec"                        LangExt.RecursiveDo
 3523     (deprecatedForExtension "RecursiveDo"),
 3524   flagSpec "DuplicateRecordFields"            LangExt.DuplicateRecordFields,
 3525   flagSpec "FieldSelectors"                   LangExt.FieldSelectors,
 3526   flagSpec "EmptyCase"                        LangExt.EmptyCase,
 3527   flagSpec "EmptyDataDecls"                   LangExt.EmptyDataDecls,
 3528   flagSpec "EmptyDataDeriving"                LangExt.EmptyDataDeriving,
 3529   flagSpec "ExistentialQuantification"        LangExt.ExistentialQuantification,
 3530   flagSpec "ExplicitForAll"                   LangExt.ExplicitForAll,
 3531   flagSpec "ExplicitNamespaces"               LangExt.ExplicitNamespaces,
 3532   flagSpec "ExtendedDefaultRules"             LangExt.ExtendedDefaultRules,
 3533   flagSpec "FlexibleContexts"                 LangExt.FlexibleContexts,
 3534   flagSpec "FlexibleInstances"                LangExt.FlexibleInstances,
 3535   flagSpec "ForeignFunctionInterface"         LangExt.ForeignFunctionInterface,
 3536   flagSpec "FunctionalDependencies"           LangExt.FunctionalDependencies,
 3537   flagSpec "GADTSyntax"                       LangExt.GADTSyntax,
 3538   flagSpec "GADTs"                            LangExt.GADTs,
 3539   flagSpec "GHCForeignImportPrim"             LangExt.GHCForeignImportPrim,
 3540   flagSpec' "GeneralizedNewtypeDeriving"      LangExt.GeneralizedNewtypeDeriving
 3541                                               setGenDeriving,
 3542   flagSpec' "GeneralisedNewtypeDeriving"      LangExt.GeneralizedNewtypeDeriving
 3543                                               setGenDeriving,
 3544   flagSpec "ImplicitParams"                   LangExt.ImplicitParams,
 3545   flagSpec "ImplicitPrelude"                  LangExt.ImplicitPrelude,
 3546   flagSpec "ImportQualifiedPost"              LangExt.ImportQualifiedPost,
 3547   flagSpec "ImpredicativeTypes"               LangExt.ImpredicativeTypes,
 3548   flagSpec' "IncoherentInstances"             LangExt.IncoherentInstances
 3549                                               setIncoherentInsts,
 3550   flagSpec "TypeFamilyDependencies"           LangExt.TypeFamilyDependencies,
 3551   flagSpec "InstanceSigs"                     LangExt.InstanceSigs,
 3552   flagSpec "ApplicativeDo"                    LangExt.ApplicativeDo,
 3553   flagSpec "InterruptibleFFI"                 LangExt.InterruptibleFFI,
 3554   flagSpec "JavaScriptFFI"                    LangExt.JavaScriptFFI,
 3555   flagSpec "KindSignatures"                   LangExt.KindSignatures,
 3556   flagSpec "LambdaCase"                       LangExt.LambdaCase,
 3557   flagSpec "LexicalNegation"                  LangExt.LexicalNegation,
 3558   flagSpec "LiberalTypeSynonyms"              LangExt.LiberalTypeSynonyms,
 3559   flagSpec "LinearTypes"                      LangExt.LinearTypes,
 3560   flagSpec "MagicHash"                        LangExt.MagicHash,
 3561   flagSpec "MonadComprehensions"              LangExt.MonadComprehensions,
 3562   flagSpec "MonoLocalBinds"                   LangExt.MonoLocalBinds,
 3563   flagSpec "MonomorphismRestriction"          LangExt.MonomorphismRestriction,
 3564   flagSpec "MultiParamTypeClasses"            LangExt.MultiParamTypeClasses,
 3565   flagSpec "MultiWayIf"                       LangExt.MultiWayIf,
 3566   flagSpec "NumericUnderscores"               LangExt.NumericUnderscores,
 3567   flagSpec "NPlusKPatterns"                   LangExt.NPlusKPatterns,
 3568   flagSpec "NamedFieldPuns"                   LangExt.NamedFieldPuns,
 3569   flagSpec "NamedWildCards"                   LangExt.NamedWildCards,
 3570   flagSpec "NegativeLiterals"                 LangExt.NegativeLiterals,
 3571   flagSpec "HexFloatLiterals"                 LangExt.HexFloatLiterals,
 3572   flagSpec "NondecreasingIndentation"         LangExt.NondecreasingIndentation,
 3573   depFlagSpec' "NullaryTypeClasses"           LangExt.NullaryTypeClasses
 3574     (deprecatedForExtension "MultiParamTypeClasses"),
 3575   flagSpec "NumDecimals"                      LangExt.NumDecimals,
 3576   depFlagSpecOp "OverlappingInstances"        LangExt.OverlappingInstances
 3577     setOverlappingInsts
 3578     "instead use per-instance pragmas OVERLAPPING/OVERLAPPABLE/OVERLAPS",
 3579   flagSpec "OverloadedLabels"                 LangExt.OverloadedLabels,
 3580   flagSpec "OverloadedLists"                  LangExt.OverloadedLists,
 3581   flagSpec "OverloadedStrings"                LangExt.OverloadedStrings,
 3582   flagSpec "PackageImports"                   LangExt.PackageImports,
 3583   flagSpec "ParallelArrays"                   LangExt.ParallelArrays,
 3584   flagSpec "ParallelListComp"                 LangExt.ParallelListComp,
 3585   flagSpec "PartialTypeSignatures"            LangExt.PartialTypeSignatures,
 3586   flagSpec "PatternGuards"                    LangExt.PatternGuards,
 3587   depFlagSpec' "PatternSignatures"            LangExt.ScopedTypeVariables
 3588     (deprecatedForExtension "ScopedTypeVariables"),
 3589   flagSpec "PatternSynonyms"                  LangExt.PatternSynonyms,
 3590   flagSpec "PolyKinds"                        LangExt.PolyKinds,
 3591   flagSpec "PolymorphicComponents"            LangExt.RankNTypes,
 3592   flagSpec "QuantifiedConstraints"            LangExt.QuantifiedConstraints,
 3593   flagSpec "PostfixOperators"                 LangExt.PostfixOperators,
 3594   flagSpec "QuasiQuotes"                      LangExt.QuasiQuotes,
 3595   flagSpec "QualifiedDo"                      LangExt.QualifiedDo,
 3596   flagSpec "Rank2Types"                       LangExt.RankNTypes,
 3597   flagSpec "RankNTypes"                       LangExt.RankNTypes,
 3598   flagSpec "RebindableSyntax"                 LangExt.RebindableSyntax,
 3599   flagSpec "OverloadedRecordDot"              LangExt.OverloadedRecordDot,
 3600   flagSpec "OverloadedRecordUpdate"           LangExt.OverloadedRecordUpdate,
 3601   depFlagSpec' "RecordPuns"                   LangExt.NamedFieldPuns
 3602     (deprecatedForExtension "NamedFieldPuns"),
 3603   flagSpec "RecordWildCards"                  LangExt.RecordWildCards,
 3604   flagSpec "RecursiveDo"                      LangExt.RecursiveDo,
 3605   flagSpec "RelaxedLayout"                    LangExt.RelaxedLayout,
 3606   depFlagSpecCond "RelaxedPolyRec"            LangExt.RelaxedPolyRec
 3607     not
 3608          "You can't turn off RelaxedPolyRec any more",
 3609   flagSpec "RoleAnnotations"                  LangExt.RoleAnnotations,
 3610   flagSpec "ScopedTypeVariables"              LangExt.ScopedTypeVariables,
 3611   flagSpec "StandaloneDeriving"               LangExt.StandaloneDeriving,
 3612   flagSpec "StarIsType"                       LangExt.StarIsType,
 3613   flagSpec "StaticPointers"                   LangExt.StaticPointers,
 3614   flagSpec "Strict"                           LangExt.Strict,
 3615   flagSpec "StrictData"                       LangExt.StrictData,
 3616   flagSpec' "TemplateHaskell"                 LangExt.TemplateHaskell
 3617                                               checkTemplateHaskellOk,
 3618   flagSpec "TemplateHaskellQuotes"            LangExt.TemplateHaskellQuotes,
 3619   flagSpec "StandaloneKindSignatures"         LangExt.StandaloneKindSignatures,
 3620   flagSpec "TraditionalRecordSyntax"          LangExt.TraditionalRecordSyntax,
 3621   flagSpec "TransformListComp"                LangExt.TransformListComp,
 3622   flagSpec "TupleSections"                    LangExt.TupleSections,
 3623   flagSpec "TypeApplications"                 LangExt.TypeApplications,
 3624   flagSpec "TypeInType"                       LangExt.TypeInType,
 3625   flagSpec "TypeFamilies"                     LangExt.TypeFamilies,
 3626   flagSpec "TypeOperators"                    LangExt.TypeOperators,
 3627   flagSpec "TypeSynonymInstances"             LangExt.TypeSynonymInstances,
 3628   flagSpec "UnboxedTuples"                    LangExt.UnboxedTuples,
 3629   flagSpec "UnboxedSums"                      LangExt.UnboxedSums,
 3630   flagSpec "UndecidableInstances"             LangExt.UndecidableInstances,
 3631   flagSpec "UndecidableSuperClasses"          LangExt.UndecidableSuperClasses,
 3632   flagSpec "UnicodeSyntax"                    LangExt.UnicodeSyntax,
 3633   flagSpec "UnliftedDatatypes"                LangExt.UnliftedDatatypes,
 3634   flagSpec "UnliftedFFITypes"                 LangExt.UnliftedFFITypes,
 3635   flagSpec "UnliftedNewtypes"                 LangExt.UnliftedNewtypes,
 3636   flagSpec "ViewPatterns"                     LangExt.ViewPatterns
 3637   ]
 3638 
 3639 defaultFlags :: Settings -> [GeneralFlag]
 3640 defaultFlags settings
 3641 -- See Note [Updating flag description in the User's Guide]
 3642   = [ Opt_AutoLinkPackages,
 3643       Opt_DiagnosticsShowCaret,
 3644       Opt_EmbedManifest,
 3645       Opt_FamAppCache,
 3646       Opt_GenManifest,
 3647       Opt_GhciHistory,
 3648       Opt_GhciSandbox,
 3649       Opt_HelpfulErrors,
 3650       Opt_KeepHiFiles,
 3651       Opt_KeepOFiles,
 3652       Opt_OmitYields,
 3653       Opt_PrintBindContents,
 3654       Opt_ProfCountEntries,
 3655       Opt_SharedImplib,
 3656       Opt_SimplPreInlining,
 3657       Opt_VersionMacros,
 3658       Opt_RPath
 3659     ]
 3660 
 3661     ++ [f | (ns,f) <- optLevelFlags, 0 `elem` ns]
 3662              -- The default -O0 options
 3663 
 3664     ++ default_PIC platform
 3665 
 3666     ++ validHoleFitDefaults
 3667 
 3668     where platform = sTargetPlatform settings
 3669 
 3670 -- | These are the default settings for the display and sorting of valid hole
 3671 --  fits in typed-hole error messages. See Note [Valid hole fits include ...]
 3672  -- in the "GHC.Tc.Errors.Hole" module.
 3673 validHoleFitDefaults :: [GeneralFlag]
 3674 validHoleFitDefaults
 3675   =  [ Opt_ShowTypeAppOfHoleFits
 3676      , Opt_ShowTypeOfHoleFits
 3677      , Opt_ShowProvOfHoleFits
 3678      , Opt_ShowMatchesOfHoleFits
 3679      , Opt_ShowValidHoleFits
 3680      , Opt_SortValidHoleFits
 3681      , Opt_SortBySizeHoleFits
 3682      , Opt_ShowHoleConstraints ]
 3683 
 3684 
 3685 validHoleFitsImpliedGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)]
 3686 validHoleFitsImpliedGFlags
 3687   = [ (Opt_UnclutterValidHoleFits, turnOff, Opt_ShowTypeAppOfHoleFits)
 3688     , (Opt_UnclutterValidHoleFits, turnOff, Opt_ShowTypeAppVarsOfHoleFits)
 3689     , (Opt_UnclutterValidHoleFits, turnOff, Opt_ShowDocsOfHoleFits)
 3690     , (Opt_ShowTypeAppVarsOfHoleFits, turnOff, Opt_ShowTypeAppOfHoleFits)
 3691     , (Opt_UnclutterValidHoleFits, turnOff, Opt_ShowProvOfHoleFits) ]
 3692 
 3693 default_PIC :: Platform -> [GeneralFlag]
 3694 default_PIC platform =
 3695   case (platformOS platform, platformArch platform) of
 3696     -- Darwin always requires PIC.  Especially on more recent macOS releases
 3697     -- there will be a 4GB __ZEROPAGE that prevents us from using 32bit addresses
 3698     -- while we could work around this on x86_64 (like WINE does), we won't be
 3699     -- able on aarch64, where this is enforced.
 3700     (OSDarwin,  ArchX86_64)  -> [Opt_PIC]
 3701     -- For AArch64, we need to always have PIC enabled.  The relocation model
 3702     -- on AArch64 does not permit arbitrary relocations.  Under ASLR, we can't
 3703     -- control much how far apart symbols are in memory for our in-memory static
 3704     -- linker;  and thus need to ensure we get sufficiently capable relocations.
 3705     -- This requires PIC on AArch64, and ExternalDynamicRefs on Linux as on top
 3706     -- of that.  Subsequently we expect all code on aarch64/linux (and macOS) to
 3707     -- be built with -fPIC.
 3708     (OSDarwin,  ArchAArch64) -> [Opt_PIC]
 3709     (OSLinux,   ArchAArch64) -> [Opt_PIC, Opt_ExternalDynamicRefs]
 3710     (OSLinux,   ArchARM {})  -> [Opt_PIC, Opt_ExternalDynamicRefs]
 3711     (OSOpenBSD, ArchX86_64)  -> [Opt_PIC] -- Due to PIE support in
 3712                                          -- OpenBSD since 5.3 release
 3713                                          -- (1 May 2013) we need to
 3714                                          -- always generate PIC. See
 3715                                          -- #10597 for more
 3716                                          -- information.
 3717     _                      -> []
 3718 
 3719 -- General flags that are switched on/off when other general flags are switched
 3720 -- on
 3721 impliedGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)]
 3722 impliedGFlags = [(Opt_DeferTypeErrors, turnOn, Opt_DeferTypedHoles)
 3723                 ,(Opt_DeferTypeErrors, turnOn, Opt_DeferOutOfScopeVariables)
 3724                 ,(Opt_DoLinearCoreLinting, turnOn, Opt_DoCoreLinting)
 3725                 ,(Opt_Strictness, turnOn, Opt_WorkerWrapper)
 3726                 ] ++ validHoleFitsImpliedGFlags
 3727 
 3728 -- General flags that are switched on/off when other general flags are switched
 3729 -- off
 3730 impliedOffGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)]
 3731 impliedOffGFlags = [(Opt_Strictness, turnOff, Opt_WorkerWrapper)]
 3732 
 3733 impliedXFlags :: [(LangExt.Extension, TurnOnFlag, LangExt.Extension)]
 3734 impliedXFlags
 3735 -- See Note [Updating flag description in the User's Guide]
 3736   = [ (LangExt.RankNTypes,                turnOn, LangExt.ExplicitForAll)
 3737     , (LangExt.QuantifiedConstraints,     turnOn, LangExt.ExplicitForAll)
 3738     , (LangExt.ScopedTypeVariables,       turnOn, LangExt.ExplicitForAll)
 3739     , (LangExt.LiberalTypeSynonyms,       turnOn, LangExt.ExplicitForAll)
 3740     , (LangExt.ExistentialQuantification, turnOn, LangExt.ExplicitForAll)
 3741     , (LangExt.FlexibleInstances,         turnOn, LangExt.TypeSynonymInstances)
 3742     , (LangExt.FunctionalDependencies,    turnOn, LangExt.MultiParamTypeClasses)
 3743     , (LangExt.MultiParamTypeClasses,     turnOn, LangExt.ConstrainedClassMethods)  -- c.f. #7854
 3744     , (LangExt.TypeFamilyDependencies,    turnOn, LangExt.TypeFamilies)
 3745 
 3746     , (LangExt.RebindableSyntax, turnOff, LangExt.ImplicitPrelude)      -- NB: turn off!
 3747 
 3748     , (LangExt.DerivingVia, turnOn, LangExt.DerivingStrategies)
 3749 
 3750     , (LangExt.GADTs,            turnOn, LangExt.GADTSyntax)
 3751     , (LangExt.GADTs,            turnOn, LangExt.MonoLocalBinds)
 3752     , (LangExt.TypeFamilies,     turnOn, LangExt.MonoLocalBinds)
 3753 
 3754     , (LangExt.TypeFamilies,     turnOn, LangExt.KindSignatures)  -- Type families use kind signatures
 3755     , (LangExt.PolyKinds,        turnOn, LangExt.KindSignatures)  -- Ditto polymorphic kinds
 3756 
 3757     -- TypeInType is now just a synonym for a couple of other extensions.
 3758     , (LangExt.TypeInType,       turnOn, LangExt.DataKinds)
 3759     , (LangExt.TypeInType,       turnOn, LangExt.PolyKinds)
 3760     , (LangExt.TypeInType,       turnOn, LangExt.KindSignatures)
 3761 
 3762     -- Standalone kind signatures are a replacement for CUSKs.
 3763     , (LangExt.StandaloneKindSignatures, turnOff, LangExt.CUSKs)
 3764 
 3765     -- AutoDeriveTypeable is not very useful without DeriveDataTypeable
 3766     , (LangExt.AutoDeriveTypeable, turnOn, LangExt.DeriveDataTypeable)
 3767 
 3768     -- We turn this on so that we can export associated type
 3769     -- type synonyms in subordinates (e.g. MyClass(type AssocType))
 3770     , (LangExt.TypeFamilies,     turnOn, LangExt.ExplicitNamespaces)
 3771     , (LangExt.TypeOperators, turnOn, LangExt.ExplicitNamespaces)
 3772 
 3773     , (LangExt.ImpredicativeTypes,  turnOn, LangExt.RankNTypes)
 3774 
 3775         -- Record wild-cards implies field disambiguation
 3776         -- Otherwise if you write (C {..}) you may well get
 3777         -- stuff like " 'a' not in scope ", which is a bit silly
 3778         -- if the compiler has just filled in field 'a' of constructor 'C'
 3779     , (LangExt.RecordWildCards,     turnOn, LangExt.DisambiguateRecordFields)
 3780 
 3781     , (LangExt.ParallelArrays, turnOn, LangExt.ParallelListComp)
 3782 
 3783     , (LangExt.JavaScriptFFI, turnOn, LangExt.InterruptibleFFI)
 3784 
 3785     , (LangExt.DeriveTraversable, turnOn, LangExt.DeriveFunctor)
 3786     , (LangExt.DeriveTraversable, turnOn, LangExt.DeriveFoldable)
 3787 
 3788     -- Duplicate record fields require field disambiguation
 3789     , (LangExt.DuplicateRecordFields, turnOn, LangExt.DisambiguateRecordFields)
 3790 
 3791     , (LangExt.TemplateHaskell, turnOn, LangExt.TemplateHaskellQuotes)
 3792     , (LangExt.Strict, turnOn, LangExt.StrictData)
 3793 
 3794     -- The extensions needed to declare an H98 unlifted data type
 3795     , (LangExt.UnliftedDatatypes, turnOn, LangExt.DataKinds)
 3796     , (LangExt.UnliftedDatatypes, turnOn, LangExt.StandaloneKindSignatures)
 3797   ]
 3798 
 3799 -- Note [When is StarIsType enabled]
 3800 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 3801 -- The StarIsType extension determines whether to treat '*' as a regular type
 3802 -- operator or as a synonym for 'Data.Kind.Type'. Many existing pre-TypeInType
 3803 -- programs expect '*' to be synonymous with 'Type', so by default StarIsType is
 3804 -- enabled.
 3805 --
 3806 -- Programs that use TypeOperators might expect to repurpose '*' for
 3807 -- multiplication or another binary operation, but making TypeOperators imply
 3808 -- NoStarIsType caused too much breakage on Hackage.
 3809 --
 3810 
 3811 -- Note [Documenting optimisation flags]
 3812 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 3813 --
 3814 -- If you change the list of flags enabled for particular optimisation levels
 3815 -- please remember to update the User's Guide. The relevant file is:
 3816 --
 3817 --   docs/users_guide/using-optimisation.rst
 3818 --
 3819 -- Make sure to note whether a flag is implied by -O0, -O or -O2.
 3820 
 3821 optLevelFlags :: [([Int], GeneralFlag)]
 3822 -- Default settings of flags, before any command-line overrides
 3823 optLevelFlags -- see Note [Documenting optimisation flags]
 3824   = [ ([0,1,2], Opt_DoLambdaEtaExpansion)
 3825     , ([0,1,2], Opt_DoEtaReduction)       -- See Note [Eta-reduction in -O0]
 3826     , ([0,1,2], Opt_LlvmTBAA)
 3827     , ([2], Opt_DictsStrict)
 3828 
 3829     , ([0],     Opt_IgnoreInterfacePragmas)
 3830     , ([0],     Opt_OmitInterfacePragmas)
 3831 
 3832     , ([1,2],   Opt_CallArity)
 3833     , ([1,2],   Opt_Exitification)
 3834     , ([1,2],   Opt_CaseMerge)
 3835     , ([1,2],   Opt_CaseFolding)
 3836     , ([1,2],   Opt_CmmElimCommonBlocks)
 3837     , ([2],     Opt_AsmShortcutting)
 3838     , ([1,2],   Opt_CmmSink)
 3839     , ([1,2],   Opt_CmmStaticPred)
 3840     , ([1,2],   Opt_CSE)
 3841     , ([1,2],   Opt_StgCSE)
 3842     , ([2],     Opt_StgLiftLams)
 3843 
 3844     , ([1,2],   Opt_EnableRewriteRules)
 3845           -- Off for -O0.   Otherwise we desugar list literals
 3846           -- to 'build' but don't run the simplifier passes that
 3847           -- would rewrite them back to cons cells!  This seems
 3848           -- silly, and matters for the GHCi debugger.
 3849 
 3850     , ([1,2],   Opt_FloatIn)
 3851     , ([1,2],   Opt_FullLaziness)
 3852     , ([1,2],   Opt_IgnoreAsserts)
 3853     , ([1,2],   Opt_Loopification)
 3854     , ([1,2],   Opt_CfgBlocklayout)      -- Experimental
 3855 
 3856     , ([1,2],   Opt_Specialise)
 3857     , ([1,2],   Opt_CrossModuleSpecialise)
 3858     , ([1,2],   Opt_InlineGenerics)
 3859     , ([1,2],   Opt_Strictness)
 3860     , ([1,2],   Opt_UnboxSmallStrictFields)
 3861     , ([1,2],   Opt_CprAnal)
 3862     , ([1,2],   Opt_WorkerWrapper)
 3863     , ([1,2],   Opt_SolveConstantDicts)
 3864     , ([1,2],   Opt_NumConstantFolding)
 3865 
 3866     , ([2],     Opt_LiberateCase)
 3867     , ([2],     Opt_SpecConstr)
 3868 --  , ([2],     Opt_RegsGraph)
 3869 --   RegsGraph suffers performance regression. See #7679
 3870 --  , ([2],     Opt_StaticArgumentTransformation)
 3871 --   Static Argument Transformation needs investigation. See #9374
 3872     ]
 3873 
 3874 
 3875 enableUnusedBinds :: DynP ()
 3876 enableUnusedBinds = mapM_ setWarningFlag unusedBindsFlags
 3877 
 3878 disableUnusedBinds :: DynP ()
 3879 disableUnusedBinds = mapM_ unSetWarningFlag unusedBindsFlags
 3880 
 3881 enableGlasgowExts :: DynP ()
 3882 enableGlasgowExts = do setGeneralFlag Opt_PrintExplicitForalls
 3883                        mapM_ setExtensionFlag glasgowExtsFlags
 3884 
 3885 disableGlasgowExts :: DynP ()
 3886 disableGlasgowExts = do unSetGeneralFlag Opt_PrintExplicitForalls
 3887                         mapM_ unSetExtensionFlag glasgowExtsFlags
 3888 
 3889 -- Please keep what_glasgow_exts_does.rst up to date with this list
 3890 glasgowExtsFlags :: [LangExt.Extension]
 3891 glasgowExtsFlags = [
 3892              LangExt.ConstrainedClassMethods
 3893            , LangExt.DeriveDataTypeable
 3894            , LangExt.DeriveFoldable
 3895            , LangExt.DeriveFunctor
 3896            , LangExt.DeriveGeneric
 3897            , LangExt.DeriveTraversable
 3898            , LangExt.EmptyDataDecls
 3899            , LangExt.ExistentialQuantification
 3900            , LangExt.ExplicitNamespaces
 3901            , LangExt.FlexibleContexts
 3902            , LangExt.FlexibleInstances
 3903            , LangExt.ForeignFunctionInterface
 3904            , LangExt.FunctionalDependencies
 3905            , LangExt.GeneralizedNewtypeDeriving
 3906            , LangExt.ImplicitParams
 3907            , LangExt.KindSignatures
 3908            , LangExt.LiberalTypeSynonyms
 3909            , LangExt.MagicHash
 3910            , LangExt.MultiParamTypeClasses
 3911            , LangExt.ParallelListComp
 3912            , LangExt.PatternGuards
 3913            , LangExt.PostfixOperators
 3914            , LangExt.RankNTypes
 3915            , LangExt.RecursiveDo
 3916            , LangExt.ScopedTypeVariables
 3917            , LangExt.StandaloneDeriving
 3918            , LangExt.TypeOperators
 3919            , LangExt.TypeSynonymInstances
 3920            , LangExt.UnboxedTuples
 3921            , LangExt.UnicodeSyntax
 3922            , LangExt.UnliftedFFITypes ]
 3923 
 3924 setWarnSafe :: Bool -> DynP ()
 3925 setWarnSafe True  = getCurLoc >>= \l -> upd (\d -> d { warnSafeOnLoc = l })
 3926 setWarnSafe False = return ()
 3927 
 3928 setWarnUnsafe :: Bool -> DynP ()
 3929 setWarnUnsafe True  = getCurLoc >>= \l -> upd (\d -> d { warnUnsafeOnLoc = l })
 3930 setWarnUnsafe False = return ()
 3931 
 3932 setPackageTrust :: DynP ()
 3933 setPackageTrust = do
 3934     setGeneralFlag Opt_PackageTrust
 3935     l <- getCurLoc
 3936     upd $ \d -> d { pkgTrustOnLoc = l }
 3937 
 3938 setGenDeriving :: TurnOnFlag -> DynP ()
 3939 setGenDeriving True  = getCurLoc >>= \l -> upd (\d -> d { newDerivOnLoc = l })
 3940 setGenDeriving False = return ()
 3941 
 3942 setDeriveVia :: TurnOnFlag -> DynP ()
 3943 setDeriveVia True  = getCurLoc >>= \l -> upd (\d -> d { deriveViaOnLoc = l })
 3944 setDeriveVia False = return ()
 3945 
 3946 setOverlappingInsts :: TurnOnFlag -> DynP ()
 3947 setOverlappingInsts False = return ()
 3948 setOverlappingInsts True = do
 3949   l <- getCurLoc
 3950   upd (\d -> d { overlapInstLoc = l })
 3951 
 3952 setIncoherentInsts :: TurnOnFlag -> DynP ()
 3953 setIncoherentInsts False = return ()
 3954 setIncoherentInsts True = do
 3955   l <- getCurLoc
 3956   upd (\d -> d { incoherentOnLoc = l })
 3957 
 3958 checkTemplateHaskellOk :: TurnOnFlag -> DynP ()
 3959 checkTemplateHaskellOk _turn_on
 3960   = getCurLoc >>= \l -> upd (\d -> d { thOnLoc = l })
 3961 
 3962 {- **********************************************************************
 3963 %*                                                                      *
 3964                 DynFlags constructors
 3965 %*                                                                      *
 3966 %********************************************************************* -}
 3967 
 3968 type DynP = EwM (CmdLineP DynFlags)
 3969 
 3970 upd :: (DynFlags -> DynFlags) -> DynP ()
 3971 upd f = liftEwM (do dflags <- getCmdLineState
 3972                     putCmdLineState $! f dflags)
 3973 
 3974 updM :: (DynFlags -> DynP DynFlags) -> DynP ()
 3975 updM f = do dflags <- liftEwM getCmdLineState
 3976             dflags' <- f dflags
 3977             liftEwM $ putCmdLineState $! dflags'
 3978 
 3979 --------------- Constructor functions for OptKind -----------------
 3980 noArg :: (DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
 3981 noArg fn = NoArg (upd fn)
 3982 
 3983 noArgM :: (DynFlags -> DynP DynFlags) -> OptKind (CmdLineP DynFlags)
 3984 noArgM fn = NoArg (updM fn)
 3985 
 3986 hasArg :: (String -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
 3987 hasArg fn = HasArg (upd . fn)
 3988 
 3989 sepArg :: (String -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
 3990 sepArg fn = SepArg (upd . fn)
 3991 
 3992 intSuffix :: (Int -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
 3993 intSuffix fn = IntSuffix (\n -> upd (fn n))
 3994 
 3995 intSuffixM :: (Int -> DynFlags -> DynP DynFlags) -> OptKind (CmdLineP DynFlags)
 3996 intSuffixM fn = IntSuffix (\n -> updM (fn n))
 3997 
 3998 wordSuffix :: (Word -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
 3999 wordSuffix fn = WordSuffix (\n -> upd (fn n))
 4000 
 4001 floatSuffix :: (Float -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
 4002 floatSuffix fn = FloatSuffix (\n -> upd (fn n))
 4003 
 4004 optIntSuffixM :: (Maybe Int -> DynFlags -> DynP DynFlags)
 4005               -> OptKind (CmdLineP DynFlags)
 4006 optIntSuffixM fn = OptIntSuffix (\mi -> updM (fn mi))
 4007 
 4008 setDumpFlag :: DumpFlag -> OptKind (CmdLineP DynFlags)
 4009 setDumpFlag dump_flag = NoArg (setDumpFlag' dump_flag)
 4010 
 4011 --------------------------
 4012 addWayDynP :: Way -> DynP ()
 4013 addWayDynP = upd . addWay'
 4014 
 4015 addWay' :: Way -> DynFlags -> DynFlags
 4016 addWay' w dflags0 =
 4017    let platform = targetPlatform dflags0
 4018        dflags1 = dflags0 { targetWays_ = addWay w (targetWays_ dflags0) }
 4019        dflags2 = foldr setGeneralFlag' dflags1
 4020                        (wayGeneralFlags platform w)
 4021        dflags3 = foldr unSetGeneralFlag' dflags2
 4022                        (wayUnsetGeneralFlags platform w)
 4023    in dflags3
 4024 
 4025 removeWayDyn :: DynP ()
 4026 removeWayDyn = upd (\dfs -> dfs { targetWays_ = removeWay WayDyn (targetWays_ dfs) })
 4027 
 4028 --------------------------
 4029 setGeneralFlag, unSetGeneralFlag :: GeneralFlag -> DynP ()
 4030 setGeneralFlag   f = upd (setGeneralFlag' f)
 4031 unSetGeneralFlag f = upd (unSetGeneralFlag' f)
 4032 
 4033 setGeneralFlag' :: GeneralFlag -> DynFlags -> DynFlags
 4034 setGeneralFlag' f dflags = foldr ($) (gopt_set dflags f) deps
 4035   where
 4036     deps = [ if turn_on then setGeneralFlag'   d
 4037                         else unSetGeneralFlag' d
 4038            | (f', turn_on, d) <- impliedGFlags, f' == f ]
 4039         -- When you set f, set the ones it implies
 4040         -- NB: use setGeneralFlag recursively, in case the implied flags
 4041         --     implies further flags
 4042 
 4043 unSetGeneralFlag' :: GeneralFlag -> DynFlags -> DynFlags
 4044 unSetGeneralFlag' f dflags = foldr ($) (gopt_unset dflags f) deps
 4045   where
 4046     deps = [ if turn_on then setGeneralFlag' d
 4047                         else unSetGeneralFlag' d
 4048            | (f', turn_on, d) <- impliedOffGFlags, f' == f ]
 4049    -- In general, when you un-set f, we don't un-set the things it implies.
 4050    -- There are however some exceptions, e.g., -fno-strictness implies
 4051    -- -fno-worker-wrapper.
 4052    --
 4053    -- NB: use unSetGeneralFlag' recursively, in case the implied off flags
 4054    --     imply further flags.
 4055 
 4056 --------------------------
 4057 setWarningFlag, unSetWarningFlag :: WarningFlag -> DynP ()
 4058 setWarningFlag   f = upd (\dfs -> wopt_set dfs f)
 4059 unSetWarningFlag f = upd (\dfs -> wopt_unset dfs f)
 4060 
 4061 setFatalWarningFlag, unSetFatalWarningFlag :: WarningFlag -> DynP ()
 4062 setFatalWarningFlag   f = upd (\dfs -> wopt_set_fatal dfs f)
 4063 unSetFatalWarningFlag f = upd (\dfs -> wopt_unset_fatal dfs f)
 4064 
 4065 setWErrorFlag :: WarningFlag -> DynP ()
 4066 setWErrorFlag flag =
 4067   do { setWarningFlag flag
 4068      ; setFatalWarningFlag flag }
 4069 
 4070 --------------------------
 4071 setExtensionFlag, unSetExtensionFlag :: LangExt.Extension -> DynP ()
 4072 setExtensionFlag f = upd (setExtensionFlag' f)
 4073 unSetExtensionFlag f = upd (unSetExtensionFlag' f)
 4074 
 4075 setExtensionFlag', unSetExtensionFlag' :: LangExt.Extension -> DynFlags -> DynFlags
 4076 setExtensionFlag' f dflags = foldr ($) (xopt_set dflags f) deps
 4077   where
 4078     deps = [ if turn_on then setExtensionFlag'   d
 4079                         else unSetExtensionFlag' d
 4080            | (f', turn_on, d) <- impliedXFlags, f' == f ]
 4081         -- When you set f, set the ones it implies
 4082         -- NB: use setExtensionFlag recursively, in case the implied flags
 4083         --     implies further flags
 4084 
 4085 unSetExtensionFlag' f dflags = xopt_unset dflags f
 4086    -- When you un-set f, however, we don't un-set the things it implies
 4087    --      (except for -fno-glasgow-exts, which is treated specially)
 4088 
 4089 --------------------------
 4090 
 4091 alterToolSettings :: (ToolSettings -> ToolSettings) -> DynFlags -> DynFlags
 4092 alterToolSettings f dynFlags = dynFlags { toolSettings = f (toolSettings dynFlags) }
 4093 
 4094 --------------------------
 4095 setDumpFlag' :: DumpFlag -> DynP ()
 4096 setDumpFlag' dump_flag
 4097   = do upd (\dfs -> dopt_set dfs dump_flag)
 4098        when want_recomp forceRecompile
 4099     where -- Certain dumpy-things are really interested in what's going
 4100           -- on during recompilation checking, so in those cases we
 4101           -- don't want to turn it off.
 4102           want_recomp = dump_flag `notElem` [Opt_D_dump_if_trace,
 4103                                              Opt_D_dump_hi_diffs,
 4104                                              Opt_D_no_debug_output]
 4105 
 4106 forceRecompile :: DynP ()
 4107 -- Whenever we -ddump, force recompilation (by switching off the
 4108 -- recompilation checker), else you don't see the dump! However,
 4109 -- don't switch it off in --make mode, else *everything* gets
 4110 -- recompiled which probably isn't what you want
 4111 forceRecompile = do dfs <- liftEwM getCmdLineState
 4112                     when (force_recomp dfs) (setGeneralFlag Opt_ForceRecomp)
 4113         where
 4114           force_recomp dfs = isOneShot (ghcMode dfs)
 4115 
 4116 
 4117 setVerbosity :: Maybe Int -> DynP ()
 4118 setVerbosity mb_n = upd (\dfs -> dfs{ verbosity = mb_n `orElse` 3 })
 4119 
 4120 setDebugLevel :: Maybe Int -> DynP ()
 4121 setDebugLevel mb_n =
 4122   upd (\dfs -> exposeSyms $ dfs{ debugLevel = n })
 4123   where
 4124     n = mb_n `orElse` 2
 4125     exposeSyms
 4126       | n > 2     = setGeneralFlag' Opt_ExposeInternalSymbols
 4127       | otherwise = id
 4128 
 4129 data PkgDbRef
 4130   = GlobalPkgDb
 4131   | UserPkgDb
 4132   | PkgDbPath FilePath
 4133   deriving Eq
 4134 
 4135 addPkgDbRef :: PkgDbRef -> DynP ()
 4136 addPkgDbRef p = upd $ \s ->
 4137   s { packageDBFlags = PackageDB p : packageDBFlags s }
 4138 
 4139 removeUserPkgDb :: DynP ()
 4140 removeUserPkgDb = upd $ \s ->
 4141   s { packageDBFlags = NoUserPackageDB : packageDBFlags s }
 4142 
 4143 removeGlobalPkgDb :: DynP ()
 4144 removeGlobalPkgDb = upd $ \s ->
 4145  s { packageDBFlags = NoGlobalPackageDB : packageDBFlags s }
 4146 
 4147 clearPkgDb :: DynP ()
 4148 clearPkgDb = upd $ \s ->
 4149   s { packageDBFlags = ClearPackageDBs : packageDBFlags s }
 4150 
 4151 parsePackageFlag :: String                 -- the flag
 4152                  -> ReadP PackageArg       -- type of argument
 4153                  -> String                 -- string to parse
 4154                  -> PackageFlag
 4155 parsePackageFlag flag arg_parse str
 4156  = case filter ((=="").snd) (readP_to_S parse str) of
 4157     [(r, "")] -> r
 4158     _ -> throwGhcException $ CmdLineError ("Can't parse package flag: " ++ str)
 4159   where doc = flag ++ " " ++ str
 4160         parse = do
 4161             pkg_arg <- tok arg_parse
 4162             let mk_expose = ExposePackage doc pkg_arg
 4163             ( do _ <- tok $ string "with"
 4164                  fmap (mk_expose . ModRenaming True) parseRns
 4165              <++ fmap (mk_expose . ModRenaming False) parseRns
 4166              <++ return (mk_expose (ModRenaming True [])))
 4167         parseRns = do _ <- tok $ R.char '('
 4168                       rns <- tok $ sepBy parseItem (tok $ R.char ',')
 4169                       _ <- tok $ R.char ')'
 4170                       return rns
 4171         parseItem = do
 4172             orig <- tok $ parseModuleName
 4173             (do _ <- tok $ string "as"
 4174                 new <- tok $ parseModuleName
 4175                 return (orig, new)
 4176               +++
 4177              return (orig, orig))
 4178         tok m = m >>= \x -> skipSpaces >> return x
 4179 
 4180 exposePackage, exposePackageId, hidePackage,
 4181         exposePluginPackage, exposePluginPackageId,
 4182         ignorePackage,
 4183         trustPackage, distrustPackage :: String -> DynP ()
 4184 exposePackage p = upd (exposePackage' p)
 4185 exposePackageId p =
 4186   upd (\s -> s{ packageFlags =
 4187     parsePackageFlag "-package-id" parseUnitArg p : packageFlags s })
 4188 exposePluginPackage p =
 4189   upd (\s -> s{ pluginPackageFlags =
 4190     parsePackageFlag "-plugin-package" parsePackageArg p : pluginPackageFlags s })
 4191 exposePluginPackageId p =
 4192   upd (\s -> s{ pluginPackageFlags =
 4193     parsePackageFlag "-plugin-package-id" parseUnitArg p : pluginPackageFlags s })
 4194 hidePackage p =
 4195   upd (\s -> s{ packageFlags = HidePackage p : packageFlags s })
 4196 ignorePackage p =
 4197   upd (\s -> s{ ignorePackageFlags = IgnorePackage p : ignorePackageFlags s })
 4198 
 4199 trustPackage p = exposePackage p >> -- both trust and distrust also expose a package
 4200   upd (\s -> s{ trustFlags = TrustPackage p : trustFlags s })
 4201 distrustPackage p = exposePackage p >>
 4202   upd (\s -> s{ trustFlags = DistrustPackage p : trustFlags s })
 4203 
 4204 exposePackage' :: String -> DynFlags -> DynFlags
 4205 exposePackage' p dflags
 4206     = dflags { packageFlags =
 4207             parsePackageFlag "-package" parsePackageArg p : packageFlags dflags }
 4208 
 4209 parsePackageArg :: ReadP PackageArg
 4210 parsePackageArg =
 4211     fmap PackageArg (munch1 (\c -> isAlphaNum c || c `elem` ":-_."))
 4212 
 4213 parseUnitArg :: ReadP PackageArg
 4214 parseUnitArg =
 4215     fmap UnitIdArg parseUnit
 4216 
 4217 setUnitId :: String -> DynFlags -> DynFlags
 4218 setUnitId p d = d { homeUnitId_ = stringToUnitId p }
 4219 
 4220 -- If we're linking a binary, then only backends that produce object
 4221 -- code are allowed (requests for other target types are ignored).
 4222 setBackend :: Backend -> DynP ()
 4223 setBackend l = upd $ \ dfs ->
 4224   if ghcLink dfs /= LinkBinary || backendProducesObject l
 4225   then dfs{ backend = l }
 4226   else dfs
 4227 
 4228 -- Changes the target only if we're compiling object code.  This is
 4229 -- used by -fasm and -fllvm, which switch from one to the other, but
 4230 -- not from bytecode to object-code.  The idea is that -fasm/-fllvm
 4231 -- can be safely used in an OPTIONS_GHC pragma.
 4232 setObjBackend :: Backend -> DynP ()
 4233 setObjBackend l = updM set
 4234   where
 4235    set dflags
 4236      | backendProducesObject (backend dflags)
 4237        = return $ dflags { backend = l }
 4238      | otherwise = return dflags
 4239 
 4240 setOptLevel :: Int -> DynFlags -> DynP DynFlags
 4241 setOptLevel n dflags = return (updOptLevel n dflags)
 4242 
 4243 checkOptLevel :: Int -> DynFlags -> Either String DynFlags
 4244 checkOptLevel n dflags
 4245    | backend dflags == Interpreter && n > 0
 4246      = Left "-O conflicts with --interactive; -O ignored."
 4247    | otherwise
 4248      = Right dflags
 4249 
 4250 setCallerCcFilters :: String -> DynP ()
 4251 setCallerCcFilters arg =
 4252   case parseCallerCcFilter arg of
 4253     Right filt -> upd $ \d -> d { callerCcFilters = filt : callerCcFilters d }
 4254     Left err -> addErr err
 4255 
 4256 setMainIs :: String -> DynP ()
 4257 setMainIs arg
 4258   | not (null main_fn) && isLower (head main_fn)
 4259      -- The arg looked like "Foo.Bar.baz"
 4260   = upd $ \d -> d { mainFunIs = Just main_fn,
 4261                     mainModuleNameIs = mkModuleName main_mod }
 4262 
 4263   | isUpper (head arg)  -- The arg looked like "Foo" or "Foo.Bar"
 4264   = upd $ \d -> d { mainModuleNameIs = mkModuleName arg }
 4265 
 4266   | otherwise                   -- The arg looked like "baz"
 4267   = upd $ \d -> d { mainFunIs = Just arg }
 4268   where
 4269     (main_mod, main_fn) = splitLongestPrefix arg (== '.')
 4270 
 4271 addLdInputs :: Option -> DynFlags -> DynFlags
 4272 addLdInputs p dflags = dflags{ldInputs = ldInputs dflags ++ [p]}
 4273 
 4274 -- -----------------------------------------------------------------------------
 4275 -- Load dynflags from environment files.
 4276 
 4277 setFlagsFromEnvFile :: FilePath -> String -> DynP ()
 4278 setFlagsFromEnvFile envfile content = do
 4279   setGeneralFlag Opt_HideAllPackages
 4280   parseEnvFile envfile content
 4281 
 4282 parseEnvFile :: FilePath -> String -> DynP ()
 4283 parseEnvFile envfile = mapM_ parseEntry . lines
 4284   where
 4285     parseEntry str = case words str of
 4286       ("package-db": _)     -> addPkgDbRef (PkgDbPath (envdir </> db))
 4287         -- relative package dbs are interpreted relative to the env file
 4288         where envdir = takeDirectory envfile
 4289               db     = drop 11 str
 4290       ["clear-package-db"]  -> clearPkgDb
 4291       ["global-package-db"] -> addPkgDbRef GlobalPkgDb
 4292       ["user-package-db"]   -> addPkgDbRef UserPkgDb
 4293       ["package-id", pkgid] -> exposePackageId pkgid
 4294       (('-':'-':_):_)       -> return () -- comments
 4295       -- and the original syntax introduced in 7.10:
 4296       [pkgid]               -> exposePackageId pkgid
 4297       []                    -> return ()
 4298       _                     -> throwGhcException $ CmdLineError $
 4299                                     "Can't parse environment file entry: "
 4300                                  ++ envfile ++ ": " ++ str
 4301 
 4302 
 4303 -----------------------------------------------------------------------------
 4304 -- Paths & Libraries
 4305 
 4306 addImportPath, addLibraryPath, addIncludePath, addFrameworkPath :: FilePath -> DynP ()
 4307 
 4308 -- -i on its own deletes the import paths
 4309 addImportPath "" = upd (\s -> s{importPaths = []})
 4310 addImportPath p  = upd (\s -> s{importPaths = importPaths s ++ splitPathList p})
 4311 
 4312 addLibraryPath p =
 4313   upd (\s -> s{libraryPaths = libraryPaths s ++ splitPathList p})
 4314 
 4315 addIncludePath p =
 4316   upd (\s -> s{includePaths =
 4317                   addGlobalInclude (includePaths s) (splitPathList p)})
 4318 
 4319 addFrameworkPath p =
 4320   upd (\s -> s{frameworkPaths = frameworkPaths s ++ splitPathList p})
 4321 
 4322 #if !defined(mingw32_HOST_OS)
 4323 split_marker :: Char
 4324 split_marker = ':'   -- not configurable (ToDo)
 4325 #endif
 4326 
 4327 splitPathList :: String -> [String]
 4328 splitPathList s = filter notNull (splitUp s)
 4329                 -- empty paths are ignored: there might be a trailing
 4330                 -- ':' in the initial list, for example.  Empty paths can
 4331                 -- cause confusion when they are translated into -I options
 4332                 -- for passing to gcc.
 4333   where
 4334 #if !defined(mingw32_HOST_OS)
 4335     splitUp xs = split split_marker xs
 4336 #else
 4337      -- Windows: 'hybrid' support for DOS-style paths in directory lists.
 4338      --
 4339      -- That is, if "foo:bar:baz" is used, this interpreted as
 4340      -- consisting of three entries, 'foo', 'bar', 'baz'.
 4341      -- However, with "c:/foo:c:\\foo;x:/bar", this is interpreted
 4342      -- as 3 elts, "c:/foo", "c:\\foo", "x:/bar"
 4343      --
 4344      -- Notice that no attempt is made to fully replace the 'standard'
 4345      -- split marker ':' with the Windows / DOS one, ';'. The reason being
 4346      -- that this will cause too much breakage for users & ':' will
 4347      -- work fine even with DOS paths, if you're not insisting on being silly.
 4348      -- So, use either.
 4349     splitUp []             = []
 4350     splitUp (x:':':div:xs) | div `elem` dir_markers
 4351                            = ((x:':':div:p): splitUp rs)
 4352                            where
 4353                               (p,rs) = findNextPath xs
 4354           -- we used to check for existence of the path here, but that
 4355           -- required the IO monad to be threaded through the command-line
 4356           -- parser which is quite inconvenient.  The
 4357     splitUp xs = cons p (splitUp rs)
 4358                where
 4359                  (p,rs) = findNextPath xs
 4360 
 4361                  cons "" xs = xs
 4362                  cons x  xs = x:xs
 4363 
 4364     -- will be called either when we've consumed nought or the
 4365     -- "<Drive>:/" part of a DOS path, so splitting is just a Q of
 4366     -- finding the next split marker.
 4367     findNextPath xs =
 4368         case break (`elem` split_markers) xs of
 4369            (p, _:ds) -> (p, ds)
 4370            (p, xs)   -> (p, xs)
 4371 
 4372     split_markers :: [Char]
 4373     split_markers = [':', ';']
 4374 
 4375     dir_markers :: [Char]
 4376     dir_markers = ['/', '\\']
 4377 #endif
 4378 
 4379 -- -----------------------------------------------------------------------------
 4380 -- tmpDir, where we store temporary files.
 4381 
 4382 setTmpDir :: FilePath -> DynFlags -> DynFlags
 4383 setTmpDir dir d = d { tmpDir = TempDir (normalise dir) }
 4384   -- we used to fix /cygdrive/c/.. on Windows, but this doesn't
 4385   -- seem necessary now --SDM 7/2/2008
 4386 
 4387 -----------------------------------------------------------------------------
 4388 -- RTS opts
 4389 
 4390 setRtsOpts :: String -> DynP ()
 4391 setRtsOpts arg  = upd $ \ d -> d {rtsOpts = Just arg}
 4392 
 4393 setRtsOptsEnabled :: RtsOptsEnabled -> DynP ()
 4394 setRtsOptsEnabled arg  = upd $ \ d -> d {rtsOptsEnabled = arg}
 4395 
 4396 -----------------------------------------------------------------------------
 4397 -- Hpc stuff
 4398 
 4399 setOptHpcDir :: String -> DynP ()
 4400 setOptHpcDir arg  = upd $ \ d -> d {hpcDir = arg}
 4401 
 4402 -----------------------------------------------------------------------------
 4403 -- Via-C compilation stuff
 4404 
 4405 -- There are some options that we need to pass to gcc when compiling
 4406 -- Haskell code via C, but are only supported by recent versions of
 4407 -- gcc.  The configure script decides which of these options we need,
 4408 -- and puts them in the "settings" file in $topdir. The advantage of
 4409 -- having these in a separate file is that the file can be created at
 4410 -- install-time depending on the available gcc version, and even
 4411 -- re-generated later if gcc is upgraded.
 4412 --
 4413 -- The options below are not dependent on the version of gcc, only the
 4414 -- platform.
 4415 
 4416 picCCOpts :: DynFlags -> [String]
 4417 picCCOpts dflags = pieOpts ++ picOpts
 4418   where
 4419     picOpts =
 4420       case platformOS (targetPlatform dflags) of
 4421       OSDarwin
 4422           -- Apple prefers to do things the other way round.
 4423           -- PIC is on by default.
 4424           -- -mdynamic-no-pic:
 4425           --     Turn off PIC code generation.
 4426           -- -fno-common:
 4427           --     Don't generate "common" symbols - these are unwanted
 4428           --     in dynamic libraries.
 4429 
 4430        | gopt Opt_PIC dflags -> ["-fno-common", "-U__PIC__", "-D__PIC__"]
 4431        | otherwise           -> ["-mdynamic-no-pic"]
 4432       OSMinGW32 -- no -fPIC for Windows
 4433        | gopt Opt_PIC dflags -> ["-U__PIC__", "-D__PIC__"]
 4434        | otherwise           -> []
 4435       _
 4436       -- we need -fPIC for C files when we are compiling with -dynamic,
 4437       -- otherwise things like stub.c files don't get compiled
 4438       -- correctly.  They need to reference data in the Haskell
 4439       -- objects, but can't without -fPIC.  See
 4440       -- https://gitlab.haskell.org/ghc/ghc/wikis/commentary/position-independent-code
 4441        | gopt Opt_PIC dflags || ways dflags `hasWay` WayDyn ->
 4442           ["-fPIC", "-U__PIC__", "-D__PIC__"]
 4443       -- gcc may be configured to have PIC on by default, let's be
 4444       -- explicit here, see #15847
 4445        | otherwise -> ["-fno-PIC"]
 4446 
 4447     pieOpts
 4448       | gopt Opt_PICExecutable dflags       = ["-pie"]
 4449         -- See Note [No PIE when linking]
 4450       | toolSettings_ccSupportsNoPie (toolSettings dflags) = ["-no-pie"]
 4451       | otherwise                           = []
 4452 
 4453 
 4454 {-
 4455 Note [No PIE while linking]
 4456 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 4457 As of 2016 some Linux distributions (e.g. Debian) have started enabling -pie by
 4458 default in their gcc builds. This is incompatible with -r as it implies that we
 4459 are producing an executable. Consequently, we must manually pass -no-pie to gcc
 4460 when joining object files or linking dynamic libraries. Unless, of course, the
 4461 user has explicitly requested a PIE executable with -pie. See #12759.
 4462 -}
 4463 
 4464 picPOpts :: DynFlags -> [String]
 4465 picPOpts dflags
 4466  | gopt Opt_PIC dflags = ["-U__PIC__", "-D__PIC__"]
 4467  | otherwise           = []
 4468 
 4469 -- -----------------------------------------------------------------------------
 4470 -- Compiler Info
 4471 
 4472 compilerInfo :: DynFlags -> [(String, String)]
 4473 compilerInfo dflags
 4474     = -- We always make "Project name" be first to keep parsing in
 4475       -- other languages simple, i.e. when looking for other fields,
 4476       -- you don't have to worry whether there is a leading '[' or not
 4477       ("Project name",                 cProjectName)
 4478       -- Next come the settings, so anything else can be overridden
 4479       -- in the settings file (as "lookup" uses the first match for the
 4480       -- key)
 4481     : map (fmap $ expandDirectories (topDir dflags) (toolDir dflags))
 4482           (rawSettings dflags)
 4483    ++ [("Project version",             projectVersion dflags),
 4484        ("Project Git commit id",       cProjectGitCommitId),
 4485        ("Booter version",              cBooterVersion),
 4486        ("Stage",                       cStage),
 4487        ("Build platform",              cBuildPlatformString),
 4488        ("Host platform",               cHostPlatformString),
 4489        ("Target platform",             platformMisc_targetPlatformString $ platformMisc dflags),
 4490        ("Have interpreter",            showBool $ platformMisc_ghcWithInterpreter $ platformMisc dflags),
 4491        ("Object splitting supported",  showBool False),
 4492        ("Have native code generator",  showBool $ platformNcgSupported (targetPlatform dflags)),
 4493        ("Target default backend",      show $ platformDefaultBackend (targetPlatform dflags)),
 4494        -- Whether or not we support @-dynamic-too@
 4495        ("Support dynamic-too",         showBool $ not isWindows),
 4496        -- Whether or not we support the @-j@ flag with @--make@.
 4497        ("Support parallel --make",     "YES"),
 4498        -- Whether or not we support "Foo from foo-0.1-XXX:Foo" syntax in
 4499        -- installed package info.
 4500        ("Support reexported-modules",  "YES"),
 4501        -- Whether or not we support extended @-package foo (Foo)@ syntax.
 4502        ("Support thinning and renaming package flags", "YES"),
 4503        -- Whether or not we support Backpack.
 4504        ("Support Backpack", "YES"),
 4505        -- If true, we require that the 'id' field in installed package info
 4506        -- match what is passed to the @-this-unit-id@ flag for modules
 4507        -- built in it
 4508        ("Requires unified installed package IDs", "YES"),
 4509        -- Whether or not we support the @-this-package-key@ flag.  Prefer
 4510        -- "Uses unit IDs" over it. We still say yes even if @-this-package-key@
 4511        -- flag has been removed, otherwise it breaks Cabal...
 4512        ("Uses package keys",           "YES"),
 4513        -- Whether or not we support the @-this-unit-id@ flag
 4514        ("Uses unit IDs",               "YES"),
 4515        -- Whether or not GHC was compiled using -dynamic
 4516        ("GHC Dynamic",                 showBool hostIsDynamic),
 4517        -- Whether or not GHC was compiled using -prof
 4518        ("GHC Profiled",                showBool hostIsProfiled),
 4519        ("Debug on",                    showBool debugIsOn),
 4520        ("LibDir",                      topDir dflags),
 4521        -- The path of the global package database used by GHC
 4522        ("Global Package DB",           globalPackageDatabasePath dflags)
 4523       ]
 4524   where
 4525     showBool True  = "YES"
 4526     showBool False = "NO"
 4527     platform  = targetPlatform dflags
 4528     isWindows = platformOS platform == OSMinGW32
 4529     expandDirectories :: FilePath -> Maybe FilePath -> String -> String
 4530     expandDirectories topd mtoold = expandToolDir mtoold . expandTopDir topd
 4531 
 4532 
 4533 wordAlignment :: Platform -> Alignment
 4534 wordAlignment platform = alignmentOf (platformWordSizeInBytes platform)
 4535 
 4536 -- | Get target profile
 4537 targetProfile :: DynFlags -> Profile
 4538 targetProfile dflags = Profile (targetPlatform dflags) (ways dflags)
 4539 
 4540 {- -----------------------------------------------------------------------------
 4541 Note [DynFlags consistency]
 4542 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 4543 
 4544 There are a number of number of DynFlags configurations which either
 4545 do not make sense or lead to unimplemented or buggy codepaths in the
 4546 compiler. makeDynFlagsConsistent is responsible for verifying the validity
 4547 of a set of DynFlags, fixing any issues, and reporting them back to the
 4548 caller.
 4549 
 4550 GHCi and -O
 4551 ---------------
 4552 
 4553 When using optimization, the compiler can introduce several things
 4554 (such as unboxed tuples) into the intermediate code, which GHCi later
 4555 chokes on since the bytecode interpreter can't handle this (and while
 4556 this is arguably a bug these aren't handled, there are no plans to fix
 4557 it.)
 4558 
 4559 While the driver pipeline always checks for this particular erroneous
 4560 combination when parsing flags, we also need to check when we update
 4561 the flags; this is because API clients may parse flags but update the
 4562 DynFlags afterwords, before finally running code inside a session (see
 4563 T10052 and #10052).
 4564 -}
 4565 
 4566 -- | Resolve any internal inconsistencies in a set of 'DynFlags'.
 4567 -- Returns the consistent 'DynFlags' as well as a list of warnings
 4568 -- to report to the user.
 4569 makeDynFlagsConsistent :: DynFlags -> (DynFlags, [Located String])
 4570 -- Whenever makeDynFlagsConsistent does anything, it starts over, to
 4571 -- ensure that a later change doesn't invalidate an earlier check.
 4572 -- Be careful not to introduce potential loops!
 4573 makeDynFlagsConsistent dflags
 4574  -- Disable -dynamic-too on Windows (#8228, #7134, #5987)
 4575  | os == OSMinGW32 && gopt Opt_BuildDynamicToo dflags
 4576     = let dflags' = gopt_unset dflags Opt_BuildDynamicToo
 4577           warn    = "-dynamic-too is not supported on Windows"
 4578       in loop dflags' warn
 4579  -- Disable -dynamic-too if we are are compiling with -dynamic already, otherwise
 4580  -- you get two dynamic object files (.o and .dyn_o). (#20436)
 4581  | ways dflags `hasWay` WayDyn && gopt Opt_BuildDynamicToo dflags
 4582     = let dflags' = gopt_unset dflags Opt_BuildDynamicToo
 4583           warn = "-dynamic-too is ignored when using -dynamic"
 4584       in loop dflags' warn
 4585 
 4586    -- Via-C backend only supports unregisterised ABI. Switch to a backend
 4587    -- supporting it if possible.
 4588  | backend dflags == ViaC &&
 4589    not (platformUnregisterised (targetPlatform dflags))
 4590     = case platformDefaultBackend (targetPlatform dflags) of
 4591          NCG ->  let dflags' = dflags { backend = NCG }
 4592                      warn = "Target platform doesn't use unregisterised ABI, so using native code generator rather than compiling via C"
 4593                  in loop dflags' warn
 4594          LLVM -> let dflags' = dflags { backend = LLVM }
 4595                      warn = "Target platform doesn't use unregisterised ABI, so using LLVM rather than compiling via C"
 4596                  in loop dflags' warn
 4597          _    -> pgmError "Compiling via C only supports unregisterised ABI but target platform doesn't use it."
 4598 
 4599  | gopt Opt_Hpc dflags && backend dflags == Interpreter
 4600     = let dflags' = gopt_unset dflags Opt_Hpc
 4601           warn = "Hpc can't be used with byte-code interpreter. Ignoring -fhpc."
 4602       in loop dflags' warn
 4603 
 4604  | backend dflags `elem` [NCG, LLVM] &&
 4605    platformUnregisterised (targetPlatform dflags)
 4606     = loop (dflags { backend = ViaC })
 4607            "Target platform uses unregisterised ABI, so compiling via C"
 4608 
 4609  | backend dflags == NCG &&
 4610    not (platformNcgSupported $ targetPlatform dflags)
 4611       = let dflags' = dflags { backend = LLVM }
 4612             warn = "Native code generator doesn't support target platform, so using LLVM"
 4613         in loop dflags' warn
 4614 
 4615  | not (osElfTarget os) && gopt Opt_PIE dflags
 4616     = loop (gopt_unset dflags Opt_PIE)
 4617            "Position-independent only supported on ELF platforms"
 4618  | os == OSDarwin &&
 4619    arch == ArchX86_64 &&
 4620    not (gopt Opt_PIC dflags)
 4621     = loop (gopt_set dflags Opt_PIC)
 4622            "Enabling -fPIC as it is always on for this platform"
 4623  | Left err <- checkOptLevel (optLevel dflags) dflags
 4624     = loop (updOptLevel 0 dflags) err
 4625 
 4626  | LinkInMemory <- ghcLink dflags
 4627  , not (gopt Opt_ExternalInterpreter dflags)
 4628  , hostIsProfiled
 4629  , backendProducesObject (backend dflags)
 4630  , ways dflags `hasNotWay` WayProf
 4631     = loop dflags{targetWays_ = addWay WayProf (targetWays_ dflags)}
 4632          "Enabling -prof, because -fobject-code is enabled and GHCi is profiled"
 4633 
 4634  | otherwise = (dflags, [])
 4635     where loc = mkGeneralSrcSpan (fsLit "when making flags consistent")
 4636           loop updated_dflags warning
 4637               = case makeDynFlagsConsistent updated_dflags of
 4638                 (dflags', ws) -> (dflags', L loc warning : ws)
 4639           platform = targetPlatform dflags
 4640           arch = platformArch platform
 4641           os   = platformOS   platform
 4642 
 4643 
 4644 setUnsafeGlobalDynFlags :: DynFlags -> IO ()
 4645 setUnsafeGlobalDynFlags dflags = do
 4646    writeIORef v_unsafeHasPprDebug (hasPprDebug dflags)
 4647    writeIORef v_unsafeHasNoDebugOutput (hasNoDebugOutput dflags)
 4648    writeIORef v_unsafeHasNoStateHack (hasNoStateHack dflags)
 4649 
 4650 
 4651 -- -----------------------------------------------------------------------------
 4652 -- SSE and AVX
 4653 
 4654 -- TODO: Instead of using a separate predicate (i.e. isSse2Enabled) to
 4655 -- check if SSE is enabled, we might have x86-64 imply the -msse2
 4656 -- flag.
 4657 
 4658 isSseEnabled :: Platform -> Bool
 4659 isSseEnabled platform = case platformArch platform of
 4660     ArchX86_64 -> True
 4661     ArchX86    -> True
 4662     _          -> False
 4663 
 4664 isSse2Enabled :: Platform -> Bool
 4665 isSse2Enabled platform = case platformArch platform of
 4666   -- We assume  SSE1 and SSE2 operations are available on both
 4667   -- x86 and x86_64. Historically we didn't default to SSE2 and
 4668   -- SSE1 on x86, which results in defacto nondeterminism for how
 4669   -- rounding behaves in the associated x87 floating point instructions
 4670   -- because variations in the spill/fpu stack placement of arguments for
 4671   -- operations would change the precision and final result of what
 4672   -- would otherwise be the same expressions with respect to single or
 4673   -- double precision IEEE floating point computations.
 4674     ArchX86_64 -> True
 4675     ArchX86    -> True
 4676     _          -> False
 4677 
 4678 
 4679 isSse4_2Enabled :: DynFlags -> Bool
 4680 isSse4_2Enabled dflags = sseVersion dflags >= Just SSE42
 4681 
 4682 isAvxEnabled :: DynFlags -> Bool
 4683 isAvxEnabled dflags = avx dflags || avx2 dflags || avx512f dflags
 4684 
 4685 isAvx2Enabled :: DynFlags -> Bool
 4686 isAvx2Enabled dflags = avx2 dflags || avx512f dflags
 4687 
 4688 isAvx512cdEnabled :: DynFlags -> Bool
 4689 isAvx512cdEnabled dflags = avx512cd dflags
 4690 
 4691 isAvx512erEnabled :: DynFlags -> Bool
 4692 isAvx512erEnabled dflags = avx512er dflags
 4693 
 4694 isAvx512fEnabled :: DynFlags -> Bool
 4695 isAvx512fEnabled dflags = avx512f dflags
 4696 
 4697 isAvx512pfEnabled :: DynFlags -> Bool
 4698 isAvx512pfEnabled dflags = avx512pf dflags
 4699 
 4700 -- -----------------------------------------------------------------------------
 4701 -- BMI2
 4702 
 4703 isBmiEnabled :: DynFlags -> Bool
 4704 isBmiEnabled dflags = case platformArch (targetPlatform dflags) of
 4705     ArchX86_64 -> bmiVersion dflags >= Just BMI1
 4706     ArchX86    -> bmiVersion dflags >= Just BMI1
 4707     _          -> False
 4708 
 4709 isBmi2Enabled :: DynFlags -> Bool
 4710 isBmi2Enabled dflags = case platformArch (targetPlatform dflags) of
 4711     ArchX86_64 -> bmiVersion dflags >= Just BMI2
 4712     ArchX86    -> bmiVersion dflags >= Just BMI2
 4713     _          -> False
 4714 
 4715 -- | Indicate if cost-centre profiling is enabled
 4716 sccProfilingEnabled :: DynFlags -> Bool
 4717 sccProfilingEnabled dflags = profileIsProfiling (targetProfile dflags)
 4718 
 4719 -- -----------------------------------------------------------------------------
 4720 -- Linker/compiler information
 4721 
 4722 -- LinkerInfo contains any extra options needed by the system linker.
 4723 data LinkerInfo
 4724   = GnuLD    [Option]
 4725   | GnuGold  [Option]
 4726   | LlvmLLD  [Option]
 4727   | DarwinLD [Option]
 4728   | SolarisLD [Option]
 4729   | AixLD    [Option]
 4730   | UnknownLD
 4731   deriving Eq
 4732 
 4733 -- CompilerInfo tells us which C compiler we're using
 4734 data CompilerInfo
 4735    = GCC
 4736    | Clang
 4737    | AppleClang
 4738    | AppleClang51
 4739    | UnknownCC
 4740    deriving Eq
 4741 
 4742 
 4743 -- | Should we use `-XLinker -rpath` when linking or not?
 4744 -- See Note [-fno-use-rpaths]
 4745 useXLinkerRPath :: DynFlags -> OS -> Bool
 4746 useXLinkerRPath _ OSDarwin = False -- See Note [Dynamic linking on macOS]
 4747 useXLinkerRPath dflags _ = gopt Opt_RPath dflags
 4748 
 4749 {-
 4750 Note [-fno-use-rpaths]
 4751 ~~~~~~~~~~~~~~~~~~~~~~
 4752 
 4753 First read, Note [Dynamic linking on macOS] to understand why on darwin we never
 4754 use `-XLinker -rpath`.
 4755 
 4756 The specification of `Opt_RPath` is as follows:
 4757 
 4758 The default case `-fuse-rpaths`:
 4759 * On darwin, never use `-Xlinker -rpath -Xlinker`, always inject the rpath
 4760   afterwards, see `runInjectRPaths`. There is no way to use `-Xlinker` on darwin
 4761   as things stand but it wasn't documented in the user guide before this patch how
 4762   `-fuse-rpaths` should behave and the fact it was always disabled on darwin.
 4763 * Otherwise, use `-Xlinker -rpath -Xlinker` to set the rpath of the executable,
 4764   this is the normal way you should set the rpath.
 4765 
 4766 The case of `-fno-use-rpaths`
 4767 * Never inject anything into the rpath.
 4768 
 4769 When this was first implemented, `Opt_RPath` was disabled on darwin, but
 4770 the rpath was still always augmented by `runInjectRPaths`, and there was no way to
 4771 stop this. This was problematic because you couldn't build an executable in CI
 4772 with a clean rpath.
 4773 
 4774 -}
 4775 
 4776 -- -----------------------------------------------------------------------------
 4777 -- RTS hooks
 4778 
 4779 -- Convert sizes like "3.5M" into integers
 4780 decodeSize :: String -> Integer
 4781 decodeSize str
 4782   | c == ""      = truncate n
 4783   | c == "K" || c == "k" = truncate (n * 1000)
 4784   | c == "M" || c == "m" = truncate (n * 1000 * 1000)
 4785   | c == "G" || c == "g" = truncate (n * 1000 * 1000 * 1000)
 4786   | otherwise            = throwGhcException (CmdLineError ("can't decode size: " ++ str))
 4787   where (m, c) = span pred str
 4788         n      = readRational m
 4789         pred c = isDigit c || c == '.'
 4790 
 4791 foreign import ccall unsafe "setHeapSize"       setHeapSize       :: Int -> IO ()
 4792 foreign import ccall unsafe "enableTimingStats" enableTimingStats :: IO ()
 4793 
 4794 
 4795 -- | Initialize the pretty-printing options
 4796 initSDocContext :: DynFlags -> PprStyle -> SDocContext
 4797 initSDocContext dflags style = SDC
 4798   { sdocStyle                       = style
 4799   , sdocColScheme                   = colScheme dflags
 4800   , sdocLastColour                  = Col.colReset
 4801   , sdocShouldUseColor              = overrideWith (canUseColor dflags) (useColor dflags)
 4802   , sdocDefaultDepth                = pprUserLength dflags
 4803   , sdocLineLength                  = pprCols dflags
 4804   , sdocCanUseUnicode               = useUnicode dflags
 4805   , sdocHexWordLiterals             = gopt Opt_HexWordLiterals dflags
 4806   , sdocPprDebug                    = dopt Opt_D_ppr_debug dflags
 4807   , sdocPrintUnicodeSyntax          = gopt Opt_PrintUnicodeSyntax dflags
 4808   , sdocPrintCaseAsLet              = gopt Opt_PprCaseAsLet dflags
 4809   , sdocPrintTypecheckerElaboration = gopt Opt_PrintTypecheckerElaboration dflags
 4810   , sdocPrintAxiomIncomps           = gopt Opt_PrintAxiomIncomps dflags
 4811   , sdocPrintExplicitKinds          = gopt Opt_PrintExplicitKinds dflags
 4812   , sdocPrintExplicitCoercions      = gopt Opt_PrintExplicitCoercions dflags
 4813   , sdocPrintExplicitRuntimeReps    = gopt Opt_PrintExplicitRuntimeReps dflags
 4814   , sdocPrintExplicitForalls        = gopt Opt_PrintExplicitForalls dflags
 4815   , sdocPrintPotentialInstances     = gopt Opt_PrintPotentialInstances dflags
 4816   , sdocPrintEqualityRelations      = gopt Opt_PrintEqualityRelations dflags
 4817   , sdocSuppressTicks               = gopt Opt_SuppressTicks dflags
 4818   , sdocSuppressTypeSignatures      = gopt Opt_SuppressTypeSignatures dflags
 4819   , sdocSuppressTypeApplications    = gopt Opt_SuppressTypeApplications dflags
 4820   , sdocSuppressIdInfo              = gopt Opt_SuppressIdInfo dflags
 4821   , sdocSuppressCoercions           = gopt Opt_SuppressCoercions dflags
 4822   , sdocSuppressUnfoldings          = gopt Opt_SuppressUnfoldings dflags
 4823   , sdocSuppressVarKinds            = gopt Opt_SuppressVarKinds dflags
 4824   , sdocSuppressUniques             = gopt Opt_SuppressUniques dflags
 4825   , sdocSuppressModulePrefixes      = gopt Opt_SuppressModulePrefixes dflags
 4826   , sdocSuppressStgExts             = gopt Opt_SuppressStgExts dflags
 4827   , sdocErrorSpans                  = gopt Opt_ErrorSpans dflags
 4828   , sdocStarIsType                  = xopt LangExt.StarIsType dflags
 4829   , sdocImpredicativeTypes          = xopt LangExt.ImpredicativeTypes dflags
 4830   , sdocLinearTypes                 = xopt LangExt.LinearTypes dflags
 4831   , sdocPrintTypeAbbreviations      = True
 4832   , sdocUnitIdForUser               = ftext
 4833   }
 4834 
 4835 -- | Initialize the pretty-printing options using the default user style
 4836 initDefaultSDocContext :: DynFlags -> SDocContext
 4837 initDefaultSDocContext dflags = initSDocContext dflags defaultUserStyle
 4838 
 4839 outputFile :: DynFlags -> Maybe String
 4840 outputFile dflags
 4841    | dynamicNow dflags = dynOutputFile_ dflags
 4842    | otherwise         = outputFile_    dflags
 4843 
 4844 objectSuf :: DynFlags -> String
 4845 objectSuf dflags
 4846    | dynamicNow dflags = dynObjectSuf_ dflags
 4847    | otherwise         = objectSuf_    dflags
 4848 
 4849 ways :: DynFlags -> Ways
 4850 ways dflags
 4851    | dynamicNow dflags = addWay WayDyn (targetWays_ dflags)
 4852    | otherwise         = targetWays_ dflags
 4853 
 4854 -- | Pretty-print the difference between 2 DynFlags.
 4855 --
 4856 -- For now only their general flags but it could be extended.
 4857 -- Useful mostly for debugging.
 4858 pprDynFlagsDiff :: DynFlags -> DynFlags -> SDoc
 4859 pprDynFlagsDiff d1 d2 =
 4860    let gf_removed  = EnumSet.difference (generalFlags d1) (generalFlags d2)
 4861        gf_added    = EnumSet.difference (generalFlags d2) (generalFlags d1)
 4862        ext_removed = EnumSet.difference (extensionFlags d1) (extensionFlags d2)
 4863        ext_added   = EnumSet.difference (extensionFlags d2) (extensionFlags d1)
 4864    in vcat
 4865       [ text "Added general flags:"
 4866       , text $ show $ EnumSet.toList $ gf_added
 4867       , text "Removed general flags:"
 4868       , text $ show $ EnumSet.toList $ gf_removed
 4869       , text "Added extension flags:"
 4870       , text $ show $ EnumSet.toList $ ext_added
 4871       , text "Removed extension flags:"
 4872       , text $ show $ EnumSet.toList $ ext_removed
 4873       ]
 4874 
 4875 updatePlatformConstants :: DynFlags -> Maybe PlatformConstants -> IO DynFlags
 4876 updatePlatformConstants dflags mconstants = do
 4877   let platform1 = (targetPlatform dflags) { platform_constants = mconstants }
 4878   let dflags1   = dflags { targetPlatform = platform1 }
 4879   return dflags1