{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE LambdaCase #-}

-------------------------------------------------------------------------------
--
-- | Dynamic flags
--
-- Most flags are dynamic flags, which means they can change from compilation
-- to compilation using @OPTIONS_GHC@ pragmas, and in a multi-session GHC each
-- session can be using different dynamic flags. Dynamic flags can also be set
-- at the prompt in GHCi.
--
-- (c) The University of Glasgow 2005
--
-------------------------------------------------------------------------------

{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}

module GHC.Driver.Session (
        -- * Dynamic flags and associated configuration types
        DumpFlag(..),
        GeneralFlag(..),
        WarningFlag(..), WarnReason(..),
        Language(..),
        PlatformConstants(..),
        FatalMessager, FlushOut(..), FlushErr(..),
        ProfAuto(..),
        glasgowExtsFlags,
        warningGroups, warningHierarchies,
        hasPprDebug, hasNoDebugOutput, hasNoStateHack, hasNoOptCoercion,
        dopt, dopt_set, dopt_unset,
        gopt, gopt_set, gopt_unset, setGeneralFlag', unSetGeneralFlag',
        wopt, wopt_set, wopt_unset,
        wopt_fatal, wopt_set_fatal, wopt_unset_fatal,
        xopt, xopt_set, xopt_unset,
        xopt_set_unlessExplSpec,
        xopt_DuplicateRecordFields,
        xopt_FieldSelectors,
        lang_set,
        DynamicTooState(..), dynamicTooState, setDynamicNow, setDynamicTooFailed,
        dynamicOutputFile, dynamicOutputHi,
        sccProfilingEnabled,
        needSourceNotes,
        DynFlags(..),
        outputFile, hiSuf, objectSuf, ways,
        FlagSpec(..),
        HasDynFlags(..), ContainsDynFlags(..),
        RtsOptsEnabled(..),
        GhcMode(..), isOneShot,
        GhcLink(..), isNoLink,
        PackageFlag(..), PackageArg(..), ModRenaming(..),
        packageFlagsChanged,
        IgnorePackageFlag(..), TrustFlag(..),
        PackageDBFlag(..), PkgDbRef(..),
        Option(..), showOpt,
        DynLibLoader(..),
        fFlags, fLangFlags, xFlags,
        wWarningFlags,
        wWarningFlagMap,
        dynFlagDependencies,
        makeDynFlagsConsistent,
        positionIndependent,
        optimisationFlags,
        setFlagsFromEnvFile,
        pprDynFlagsDiff,
        flagSpecOf,
        smallestGroups,

        targetProfile,

        -- ** Safe Haskell
        safeHaskellOn, safeHaskellModeEnabled,
        safeImportsOn, safeLanguageOn, safeInferOn,
        packageTrustOn,
        safeDirectImpsReq, safeImplicitImpsReq,
        unsafeFlags, unsafeFlagsForInfer,

        -- ** LLVM Targets
        LlvmTarget(..), LlvmConfig(..),

        -- ** System tool settings and locations
        Settings(..),
        sProgramName,
        sProjectVersion,
        sGhcUsagePath,
        sGhciUsagePath,
        sToolDir,
        sTopDir,
        sTmpDir,
        sGlobalPackageDatabasePath,
        sLdSupportsCompactUnwind,
        sLdSupportsBuildId,
        sLdSupportsFilelist,
        sLdIsGnuLd,
        sGccSupportsNoPie,
        sPgm_L,
        sPgm_P,
        sPgm_F,
        sPgm_c,
        sPgm_a,
        sPgm_l,
        sPgm_lm,
        sPgm_dll,
        sPgm_T,
        sPgm_windres,
        sPgm_libtool,
        sPgm_ar,
        sPgm_ranlib,
        sPgm_lo,
        sPgm_lc,
        sPgm_lcc,
        sPgm_i,
        sOpt_L,
        sOpt_P,
        sOpt_P_fingerprint,
        sOpt_F,
        sOpt_c,
        sOpt_cxx,
        sOpt_a,
        sOpt_l,
        sOpt_lm,
        sOpt_windres,
        sOpt_lo,
        sOpt_lc,
        sOpt_lcc,
        sOpt_i,
        sExtraGccViaCFlags,
        sTargetPlatformString,
        sGhcWithInterpreter,
        sGhcWithSMP,
        sGhcRTSWays,
        sLibFFI,
        sGhcRtsWithLibdw,
        GhcNameVersion(..),
        FileSettings(..),
        PlatformMisc(..),
        settings,
        programName, projectVersion,
        ghcUsagePath, ghciUsagePath, topDir, tmpDir,
        versionedAppDir, versionedFilePath,
        extraGccViaCFlags, globalPackageDatabasePath,
        pgm_L, pgm_P, pgm_F, pgm_c, pgm_a, pgm_l, pgm_lm, pgm_dll, pgm_T,
        pgm_windres, pgm_libtool, pgm_ar, pgm_otool, pgm_install_name_tool,
        pgm_ranlib, pgm_lo, pgm_lc, pgm_lcc, pgm_i,
        opt_L, opt_P, opt_F, opt_c, opt_cxx, opt_a, opt_l, opt_lm, opt_i,
        opt_P_signature,
        opt_windres, opt_lo, opt_lc, opt_lcc,
        updatePlatformConstants,

        -- ** Manipulating DynFlags
        addPluginModuleName,
        defaultDynFlags,                -- Settings -> DynFlags
        initDynFlags,                   -- DynFlags -> IO DynFlags
        defaultFatalMessager,
        defaultFlushOut,
        defaultFlushErr,

        getOpts,                        -- DynFlags -> (DynFlags -> [a]) -> [a]
        getVerbFlags,
        updOptLevel,
        setTmpDir,
        setUnitId,

        TurnOnFlag,
        turnOn,
        turnOff,
        impliedGFlags,
        impliedOffGFlags,
        impliedXFlags,

        -- ** Parsing DynFlags
        parseDynamicFlagsCmdLine,
        parseDynamicFilePragma,
        parseDynamicFlagsFull,

        -- ** Available DynFlags
        allNonDeprecatedFlags,
        flagsAll,
        flagsDynamic,
        flagsPackage,
        flagsForCompletion,

        supportedLanguagesAndExtensions,
        languageExtensions,

        -- ** DynFlags C compiler options
        picCCOpts, picPOpts,

        -- * Compiler configuration suitable for display to the user
        compilerInfo,

        wordAlignment,

        setUnsafeGlobalDynFlags,

        -- * SSE and AVX
        isSseEnabled,
        isSse2Enabled,
        isSse4_2Enabled,
        isBmiEnabled,
        isBmi2Enabled,
        isAvxEnabled,
        isAvx2Enabled,
        isAvx512cdEnabled,
        isAvx512erEnabled,
        isAvx512fEnabled,
        isAvx512pfEnabled,

        -- * Linker/compiler information
        LinkerInfo(..),
        CompilerInfo(..),
        useXLinkerRPath,

        -- * Include specifications
        IncludeSpecs(..), addGlobalInclude, addQuoteInclude, flattenIncludes,
        addImplicitQuoteInclude,

        -- * SDoc
        initSDocContext, initDefaultSDocContext,
  ) where

#include "HsVersions.h"

import GHC.Prelude

import GHC.Platform
import GHC.Platform.Ways
import GHC.Platform.Profile

import GHC.UniqueSubdir (uniqueSubdir)
import GHC.Unit.Types
import GHC.Unit.Parser
import GHC.Unit.Module
import GHC.Builtin.Names ( mAIN_NAME )
import GHC.Driver.Phases ( Phase(..), phaseInputExt )
import GHC.Driver.Flags
import GHC.Driver.Backend
import GHC.Settings.Config
import GHC.Utils.CliOption
import {-# SOURCE #-} GHC.Core.Unfold
import GHC.Driver.CmdLine hiding (WarnReason(..))
import qualified GHC.Driver.CmdLine as Cmd
import GHC.Settings.Constants
import GHC.Utils.Panic
import qualified GHC.Utils.Ppr.Colour as Col
import GHC.Utils.Misc
import GHC.Utils.GlobalVars
import GHC.Data.Maybe
import GHC.Utils.Monad
import GHC.Types.SrcLoc
import GHC.Types.SafeHaskell
import GHC.Types.Basic ( Alignment, alignmentOf, IntWithInf, treatZeroAsInf )
import qualified GHC.Types.FieldLabel as FieldLabel
import GHC.Data.FastString
import GHC.Utils.Fingerprint
import GHC.Utils.Outputable
import GHC.Settings
import GHC.CmmToAsm.CFG.Weight
import {-# SOURCE #-} GHC.Core.Opt.CallerCC

import GHC.SysTools.Terminal ( stderrSupportsAnsiColors )
import GHC.SysTools.BaseDir ( expandToolDir, expandTopDir )

import Data.IORef
import Control.Arrow ((&&&))
import Control.Monad
import Control.Monad.Trans.Class
import Control.Monad.Trans.Writer
import Control.Monad.Trans.Reader
import Control.Monad.Trans.Except

import Data.Ord
import Data.Char
import Data.List (intercalate, sortBy)
import Data.Map (Map)
import qualified Data.Map as Map
import qualified Data.Set as Set
import System.FilePath
import System.Directory
import System.Environment (lookupEnv)
import System.IO
import System.IO.Error
import Text.ParserCombinators.ReadP hiding (char)
import Text.ParserCombinators.ReadP as R

import GHC.Data.EnumSet (EnumSet)
import qualified GHC.Data.EnumSet as EnumSet

import GHC.Foreign (withCString, peekCString)
import qualified GHC.LanguageExtensions as LangExt

-- Note [Updating flag description in the User's Guide]
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
--
-- If you modify anything in this file please make sure that your changes are
-- described in the User's Guide. Please update the flag description in the
-- users guide (docs/users_guide) whenever you add or change a flag.

-- Note [Supporting CLI completion]
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
--
-- The command line interface completion (in for example bash) is an easy way
-- for the developer to learn what flags are available from GHC.
-- GHC helps by separating which flags are available when compiling with GHC,
-- and which flags are available when using GHCi.
-- A flag is assumed to either work in both these modes, or only in one of them.
-- When adding or changing a flag, please consider for which mode the flag will
-- have effect, and annotate it accordingly. For Flags use defFlag, defGhcFlag,
-- defGhciFlag, and for FlagSpec use flagSpec or flagGhciSpec.

-- Note [Adding a language extension]
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
--
-- There are a few steps to adding (or removing) a language extension,
--
--  * Adding the extension to GHC.LanguageExtensions
--
--    The Extension type in libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs
--    is the canonical list of language extensions known by GHC.
--
--  * Adding a flag to DynFlags.xFlags
--
--    This is fairly self-explanatory. The name should be concise, memorable,
--    and consistent with any previous implementations of the similar idea in
--    other Haskell compilers.
--
--  * Adding the flag to the documentation
--
--    This is the same as any other flag. See
--    Note [Updating flag description in the User's Guide]
--
--  * Adding the flag to Cabal
--
--    The Cabal library has its own list of all language extensions supported
--    by all major compilers. This is the list that user code being uploaded
--    to Hackage is checked against to ensure language extension validity.
--    Consequently, it is very important that this list remains up-to-date.
--
--    To this end, there is a testsuite test (testsuite/tests/driver/T4437.hs)
--    whose job it is to ensure these GHC's extensions are consistent with
--    Cabal.
--
--    The recommended workflow is,
--
--     1. Temporarily add your new language extension to the
--        expectedGhcOnlyExtensions list in T4437 to ensure the test doesn't
--        break while Cabal is updated.
--
--     2. After your GHC change is accepted, submit a Cabal pull request adding
--        your new extension to Cabal's list (found in
--        Cabal/Language/Haskell/Extension.hs).
--
--     3. After your Cabal change is accepted, let the GHC developers know so
--        they can update the Cabal submodule and remove the extensions from
--        expectedGhcOnlyExtensions.
--
--  * Adding the flag to the GHC Wiki
--
--    There is a change log tracking language extension additions and removals
--    on the GHC wiki:  https://gitlab.haskell.org/ghc/ghc/wikis/language-pragma-history
--
--  See #4437 and #8176.

-- -----------------------------------------------------------------------------
-- DynFlags

-- | Used to differentiate the scope an include needs to apply to.
-- We have to split the include paths to avoid accidentally forcing recursive
-- includes since -I overrides the system search paths. See #14312.
data IncludeSpecs
  = IncludeSpecs { IncludeSpecs -> [[Char]]
includePathsQuote  :: [String]
                 , IncludeSpecs -> [[Char]]
includePathsGlobal :: [String]
                 -- | See note [Implicit include paths]
                 , IncludeSpecs -> [[Char]]
includePathsQuoteImplicit :: [String]
                 }
  deriving Int -> IncludeSpecs -> ShowS
[IncludeSpecs] -> ShowS
IncludeSpecs -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [IncludeSpecs] -> ShowS
$cshowList :: [IncludeSpecs] -> ShowS
show :: IncludeSpecs -> [Char]
$cshow :: IncludeSpecs -> [Char]
showsPrec :: Int -> IncludeSpecs -> ShowS
$cshowsPrec :: Int -> IncludeSpecs -> ShowS
Show

-- | Append to the list of includes a path that shall be included using `-I`
-- when the C compiler is called. These paths override system search paths.
addGlobalInclude :: IncludeSpecs -> [String] -> IncludeSpecs
addGlobalInclude :: IncludeSpecs -> [[Char]] -> IncludeSpecs
addGlobalInclude IncludeSpecs
spec [[Char]]
paths  = let f :: [[Char]]
f = IncludeSpecs -> [[Char]]
includePathsGlobal IncludeSpecs
spec
                               in IncludeSpecs
spec { includePathsGlobal :: [[Char]]
includePathsGlobal = [[Char]]
f forall a. [a] -> [a] -> [a]
++ [[Char]]
paths }

-- | Append to the list of includes a path that shall be included using
-- `-iquote` when the C compiler is called. These paths only apply when quoted
-- includes are used. e.g. #include "foo.h"
addQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs
addQuoteInclude :: IncludeSpecs -> [[Char]] -> IncludeSpecs
addQuoteInclude IncludeSpecs
spec [[Char]]
paths  = let f :: [[Char]]
f = IncludeSpecs -> [[Char]]
includePathsQuote IncludeSpecs
spec
                              in IncludeSpecs
spec { includePathsQuote :: [[Char]]
includePathsQuote = [[Char]]
f forall a. [a] -> [a] -> [a]
++ [[Char]]
paths }

-- | These includes are not considered while fingerprinting the flags for iface
-- | See note [Implicit include paths]
addImplicitQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs
addImplicitQuoteInclude :: IncludeSpecs -> [[Char]] -> IncludeSpecs
addImplicitQuoteInclude IncludeSpecs
spec [[Char]]
paths  = let f :: [[Char]]
f = IncludeSpecs -> [[Char]]
includePathsQuoteImplicit IncludeSpecs
spec
                              in IncludeSpecs
spec { includePathsQuoteImplicit :: [[Char]]
includePathsQuoteImplicit = [[Char]]
f forall a. [a] -> [a] -> [a]
++ [[Char]]
paths }


-- | Concatenate and flatten the list of global and quoted includes returning
-- just a flat list of paths.
flattenIncludes :: IncludeSpecs -> [String]
flattenIncludes :: IncludeSpecs -> [[Char]]
flattenIncludes IncludeSpecs
specs =
    IncludeSpecs -> [[Char]]
includePathsQuote IncludeSpecs
specs forall a. [a] -> [a] -> [a]
++
    IncludeSpecs -> [[Char]]
includePathsQuoteImplicit IncludeSpecs
specs forall a. [a] -> [a] -> [a]
++
    IncludeSpecs -> [[Char]]
includePathsGlobal IncludeSpecs
specs

{- Note [Implicit include paths]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  The compile driver adds the path to the folder containing the source file being
  compiled to the 'IncludeSpecs', and this change gets recorded in the 'DynFlags'
  that are used later to compute the interface file. Because of this,
  the flags fingerprint derived from these 'DynFlags' and recorded in the
  interface file will end up containing the absolute path to the source folder.

  Build systems with a remote cache like Bazel or Buck (or Shake, see #16956)
  store the build artifacts produced by a build BA for reuse in subsequent builds.

  Embedding source paths in interface fingerprints will thwart these attemps and
  lead to unnecessary recompilations when the source paths in BA differ from the
  source paths in subsequent builds.
 -}


-- | Contains not only a collection of 'GeneralFlag's but also a plethora of
-- information relating to the compilation of a single file or GHC session
data DynFlags = DynFlags {
  DynFlags -> GhcMode
ghcMode               :: GhcMode,
  DynFlags -> GhcLink
ghcLink               :: GhcLink,
  DynFlags -> Backend
backend               :: !Backend,
   -- ^ The backend to use (if any).
   --
   -- Whenever you change the backend, also make sure to set 'ghcLink' to
   -- something sensible.
   --
   -- 'NoBackend' can be used to avoid generating any output, however, note that:
   --
   --  * If a program uses Template Haskell the typechecker may need to run code
   --    from an imported module.  To facilitate this, code generation is enabled
   --    for modules imported by modules that use template haskell, using the
   --    default backend for the platform.
   --    See Note [-fno-code mode].


  -- formerly Settings
  DynFlags -> GhcNameVersion
ghcNameVersion    :: {-# UNPACK #-} !GhcNameVersion,
  DynFlags -> FileSettings
fileSettings      :: {-# UNPACK #-} !FileSettings,
  DynFlags -> Platform
targetPlatform    :: Platform,       -- Filled in by SysTools
  DynFlags -> ToolSettings
toolSettings      :: {-# UNPACK #-} !ToolSettings,
  DynFlags -> PlatformMisc
platformMisc      :: {-# UNPACK #-} !PlatformMisc,
  DynFlags -> [([Char], [Char])]
rawSettings       :: [(String, String)],

  DynFlags -> LlvmConfig
llvmConfig            :: LlvmConfig,
    -- ^ N.B. It's important that this field is lazy since we load the LLVM
    -- configuration lazily. See Note [LLVM Configuration] in "GHC.SysTools".
  DynFlags -> Int
verbosity             :: Int,         -- ^ Verbosity level: see Note [Verbosity levels]
  DynFlags -> Int
optLevel              :: Int,         -- ^ Optimisation level
  DynFlags -> Int
debugLevel            :: Int,         -- ^ How much debug information to produce
  DynFlags -> Int
simplPhases           :: Int,         -- ^ Number of simplifier phases
  DynFlags -> Int
maxSimplIterations    :: Int,         -- ^ Max simplifier iterations
  DynFlags -> Maybe [Char]
ruleCheck             :: Maybe String,
  DynFlags -> Maybe [Char]
inlineCheck           :: Maybe String, -- ^ A prefix to report inlining decisions about
  DynFlags -> [Int]
strictnessBefore      :: [Int],       -- ^ Additional demand analysis

  DynFlags -> Maybe Int
parMakeCount          :: Maybe Int,   -- ^ The number of modules to compile in parallel
                                        --   in --make mode, where Nothing ==> compile as
                                        --   many in parallel as there are CPUs.

  DynFlags -> Bool
enableTimeStats       :: Bool,        -- ^ Enable RTS timing statistics?
  DynFlags -> Maybe Int
ghcHeapSize           :: Maybe Int,   -- ^ The heap size to set.

  DynFlags -> Maybe Int
maxRelevantBinds      :: Maybe Int,   -- ^ Maximum number of bindings from the type envt
                                        --   to show in type error messages
  DynFlags -> Maybe Int
maxValidHoleFits      :: Maybe Int,   -- ^ Maximum number of hole fits to show
                                        --   in typed hole error messages
  DynFlags -> Maybe Int
maxRefHoleFits        :: Maybe Int,   -- ^ Maximum number of refinement hole
                                        --   fits to show in typed hole error
                                        --   messages
  DynFlags -> Maybe Int
refLevelHoleFits      :: Maybe Int,   -- ^ Maximum level of refinement for
                                        --   refinement hole fits in typed hole
                                        --   error messages
  DynFlags -> Int
maxUncoveredPatterns  :: Int,         -- ^ Maximum number of unmatched patterns to show
                                        --   in non-exhaustiveness warnings
  DynFlags -> Int
maxPmCheckModels      :: Int,         -- ^ Soft limit on the number of models
                                        --   the pattern match checker checks
                                        --   a pattern against. A safe guard
                                        --   against exponential blow-up.
  DynFlags -> Int
simplTickFactor       :: Int,         -- ^ Multiplier for simplifier ticks
  DynFlags -> Maybe Int
specConstrThreshold   :: Maybe Int,   -- ^ Threshold for SpecConstr
  DynFlags -> Maybe Int
specConstrCount       :: Maybe Int,   -- ^ Max number of specialisations for any one function
  DynFlags -> Int
specConstrRecursive   :: Int,         -- ^ Max number of specialisations for recursive types
                                        --   Not optional; otherwise ForceSpecConstr can diverge.
  DynFlags -> Word
binBlobThreshold      :: Word,        -- ^ Binary literals (e.g. strings) whose size is above
                                        --   this threshold will be dumped in a binary file
                                        --   by the assembler code generator (0 to disable)
  DynFlags -> Maybe Int
liberateCaseThreshold :: Maybe Int,   -- ^ Threshold for LiberateCase
  DynFlags -> Maybe Int
floatLamArgs          :: Maybe Int,   -- ^ Arg count for lambda floating
                                        --   See 'GHC.Core.Opt.Monad.FloatOutSwitches'

  DynFlags -> Maybe Int
liftLamsRecArgs       :: Maybe Int,   -- ^ Maximum number of arguments after lambda lifting a
                                        --   recursive function.
  DynFlags -> Maybe Int
liftLamsNonRecArgs    :: Maybe Int,   -- ^ Maximum number of arguments after lambda lifting a
                                        --   non-recursive function.
  DynFlags -> Bool
liftLamsKnown         :: Bool,        -- ^ Lambda lift even when this turns a known call
                                        --   into an unknown call.

  DynFlags -> Maybe Int
cmmProcAlignment      :: Maybe Int,   -- ^ Align Cmm functions at this boundary or use default.

  DynFlags -> Int
historySize           :: Int,         -- ^ Simplification history size

  DynFlags -> [[Char]]
importPaths           :: [FilePath],
  DynFlags -> ModuleName
mainModuleNameIs      :: ModuleName,
  DynFlags -> Maybe [Char]
mainFunIs             :: Maybe String,
  DynFlags -> IntWithInf
reductionDepth        :: IntWithInf,   -- ^ Typechecker maximum stack depth
  DynFlags -> IntWithInf
solverIterations      :: IntWithInf,   -- ^ Number of iterations in the constraints solver
                                         --   Typically only 1 is needed

  DynFlags -> UnitId
homeUnitId_             :: UnitId,                 -- ^ Target home unit-id
  DynFlags -> Maybe UnitId
homeUnitInstanceOf_     :: Maybe UnitId,           -- ^ Id of the unit to instantiate
  DynFlags -> [(ModuleName, Module)]
homeUnitInstantiations_ :: [(ModuleName, Module)], -- ^ Module instantiations

  -- ways
  DynFlags -> Ways
targetWays_           :: Ways,         -- ^ Target way flags from the command line

  -- For object splitting
  DynFlags -> Maybe ([Char], Int)
splitInfo             :: Maybe (String,Int),

  -- paths etc.
  DynFlags -> Maybe [Char]
objectDir             :: Maybe String,
  DynFlags -> Maybe [Char]
dylibInstallName      :: Maybe String,
  DynFlags -> Maybe [Char]
hiDir                 :: Maybe String,
  DynFlags -> Maybe [Char]
hieDir                :: Maybe String,
  DynFlags -> Maybe [Char]
stubDir               :: Maybe String,
  DynFlags -> Maybe [Char]
dumpDir               :: Maybe String,

  DynFlags -> [Char]
objectSuf_            :: String,
  DynFlags -> [Char]
hcSuf                 :: String,
  DynFlags -> [Char]
hiSuf_                :: String,
  DynFlags -> [Char]
hieSuf                :: String,

  DynFlags -> IORef Bool
dynamicTooFailed      :: IORef Bool,
  DynFlags -> [Char]
dynObjectSuf_         :: String,
  DynFlags -> [Char]
dynHiSuf_             :: String,

  DynFlags -> Maybe [Char]
outputFile_           :: Maybe String,
  DynFlags -> Maybe [Char]
dynOutputFile_        :: Maybe String,
  DynFlags -> Maybe [Char]
outputHi              :: Maybe String,
  DynFlags -> Maybe [Char]
dynOutputHi           :: Maybe String,
  DynFlags -> DynLibLoader
dynLibLoader          :: DynLibLoader,

  DynFlags -> Bool
dynamicNow            :: !Bool, -- ^ Indicate if we are now generating dynamic output
                                  -- because of -dynamic-too. This predicate is
                                  -- used to query the appropriate fields
                                  -- (outputFile/dynOutputFile, ways, etc.)

  -- | This is set by 'GHC.Driver.Pipeline.runPipeline'
  --    or 'ghc.GHCi.UI.runStmt' based on where its output is going.
  DynFlags -> Maybe [Char]
dumpPrefix            :: Maybe FilePath,

  -- | Override the 'dumpPrefix' set by 'GHC.Driver.Pipeline.runPipeline'
  --    or 'ghc.GHCi.UI.runStmt'.
  --    Set by @-ddump-file-prefix@
  DynFlags -> Maybe [Char]
dumpPrefixForce       :: Maybe FilePath,

  DynFlags -> [Option]
ldInputs              :: [Option],

  DynFlags -> IncludeSpecs
includePaths          :: IncludeSpecs,
  DynFlags -> [[Char]]
libraryPaths          :: [String],
  DynFlags -> [[Char]]
frameworkPaths        :: [String],    -- used on darwin only
  DynFlags -> [[Char]]
cmdlineFrameworks     :: [String],    -- ditto

  DynFlags -> Maybe [Char]
rtsOpts               :: Maybe String,
  DynFlags -> RtsOptsEnabled
rtsOptsEnabled        :: RtsOptsEnabled,
  DynFlags -> Bool
rtsOptsSuggestions    :: Bool,

  DynFlags -> [Char]
hpcDir                :: String,      -- ^ Path to store the .mix files

  -- Plugins
  DynFlags -> [ModuleName]
pluginModNames        :: [ModuleName],
  DynFlags -> [(ModuleName, [Char])]
pluginModNameOpts     :: [(ModuleName,String)],
  DynFlags -> [[Char]]
frontendPluginOpts    :: [String],
    -- ^ the @-ffrontend-opt@ flags given on the command line, in *reverse*
    -- order that they're specified on the command line.

  --  For ghc -M
  DynFlags -> [Char]
depMakefile           :: FilePath,
  DynFlags -> Bool
depIncludePkgDeps     :: Bool,
  DynFlags -> Bool
depIncludeCppDeps     :: Bool,
  DynFlags -> [ModuleName]
depExcludeMods        :: [ModuleName],
  DynFlags -> [[Char]]
depSuffixes           :: [String],

  --  Package flags
  DynFlags -> [PackageDBFlag]
packageDBFlags        :: [PackageDBFlag],
        -- ^ The @-package-db@ flags given on the command line, In
        -- *reverse* order that they're specified on the command line.
        -- This is intended to be applied with the list of "initial"
        -- package databases derived from @GHC_PACKAGE_PATH@; see
        -- 'getUnitDbRefs'.

  DynFlags -> [IgnorePackageFlag]
ignorePackageFlags    :: [IgnorePackageFlag],
        -- ^ The @-ignore-package@ flags from the command line.
        -- In *reverse* order that they're specified on the command line.
  DynFlags -> [PackageFlag]
packageFlags          :: [PackageFlag],
        -- ^ The @-package@ and @-hide-package@ flags from the command-line.
        -- In *reverse* order that they're specified on the command line.
  DynFlags -> [PackageFlag]
pluginPackageFlags    :: [PackageFlag],
        -- ^ The @-plugin-package-id@ flags from command line.
        -- In *reverse* order that they're specified on the command line.
  DynFlags -> [TrustFlag]
trustFlags            :: [TrustFlag],
        -- ^ The @-trust@ and @-distrust@ flags.
        -- In *reverse* order that they're specified on the command line.
  DynFlags -> Maybe [Char]
packageEnv            :: Maybe FilePath,
        -- ^ Filepath to the package environment file (if overriding default)


  -- hsc dynamic flags
  DynFlags -> EnumSet DumpFlag
dumpFlags             :: EnumSet DumpFlag,
  DynFlags -> EnumSet GeneralFlag
generalFlags          :: EnumSet GeneralFlag,
  DynFlags -> EnumSet WarningFlag
warningFlags          :: EnumSet WarningFlag,
  DynFlags -> EnumSet WarningFlag
fatalWarningFlags     :: EnumSet WarningFlag,
  -- Don't change this without updating extensionFlags:
  DynFlags -> Maybe Language
language              :: Maybe Language,
  -- | Safe Haskell mode
  DynFlags -> SafeHaskellMode
safeHaskell           :: SafeHaskellMode,
  DynFlags -> Bool
safeInfer             :: Bool,
  DynFlags -> Bool
safeInferred          :: Bool,
  -- We store the location of where some extension and flags were turned on so
  -- we can produce accurate error messages when Safe Haskell fails due to
  -- them.
  DynFlags -> SrcSpan
thOnLoc               :: SrcSpan,
  DynFlags -> SrcSpan
newDerivOnLoc         :: SrcSpan,
  DynFlags -> SrcSpan
deriveViaOnLoc        :: SrcSpan,
  DynFlags -> SrcSpan
overlapInstLoc        :: SrcSpan,
  DynFlags -> SrcSpan
incoherentOnLoc       :: SrcSpan,
  DynFlags -> SrcSpan
pkgTrustOnLoc         :: SrcSpan,
  DynFlags -> SrcSpan
warnSafeOnLoc         :: SrcSpan,
  DynFlags -> SrcSpan
warnUnsafeOnLoc       :: SrcSpan,
  DynFlags -> SrcSpan
trustworthyOnLoc      :: SrcSpan,
  -- Don't change this without updating extensionFlags:
  -- Here we collect the settings of the language extensions
  -- from the command line, the ghci config file and
  -- from interactive :set / :seti commands.
  DynFlags -> [OnOff Extension]
extensions            :: [OnOff LangExt.Extension],
  -- extensionFlags should always be equal to
  --     flattenExtensionFlags language extensions
  -- LangExt.Extension is defined in libraries/ghc-boot so that it can be used
  -- by template-haskell
  DynFlags -> EnumSet Extension
extensionFlags        :: EnumSet LangExt.Extension,

  -- | Unfolding control
  -- See Note [Discounts and thresholds] in GHC.Core.Unfold
  DynFlags -> UnfoldingOpts
unfoldingOpts         :: !UnfoldingOpts,

  DynFlags -> Int
maxWorkerArgs         :: Int,

  DynFlags -> Int
ghciHistSize          :: Int,

  DynFlags -> FlushOut
flushOut              :: FlushOut,
  DynFlags -> FlushErr
flushErr              :: FlushErr,

  DynFlags -> Maybe [Char]
ghcVersionFile        :: Maybe FilePath,
  DynFlags -> Maybe [Char]
haddockOptions        :: Maybe String,

  -- | GHCi scripts specified by -ghci-script, in reverse order
  DynFlags -> [[Char]]
ghciScripts           :: [String],

  -- Output style options
  DynFlags -> Int
pprUserLength         :: Int,
  DynFlags -> Int
pprCols               :: Int,

  DynFlags -> Bool
useUnicode            :: Bool,
  DynFlags -> OverridingBool
useColor              :: OverridingBool,
  DynFlags -> Bool
canUseColor           :: Bool,
  DynFlags -> Scheme
colScheme             :: Col.Scheme,

  -- | what kind of {-# SCC #-} to add automatically
  DynFlags -> ProfAuto
profAuto              :: ProfAuto,
  DynFlags -> [CallerCcFilter]
callerCcFilters       :: [CallerCcFilter],

  DynFlags -> Maybe [Char]
interactivePrint      :: Maybe String,

  DynFlags -> IORef (ModuleEnv Int)
nextWrapperNum        :: IORef (ModuleEnv Int),

  -- | Machine dependent flags (-m\<blah> stuff)
  DynFlags -> Maybe SseVersion
sseVersion            :: Maybe SseVersion,
  DynFlags -> Maybe BmiVersion
bmiVersion            :: Maybe BmiVersion,
  DynFlags -> Bool
avx                   :: Bool,
  DynFlags -> Bool
avx2                  :: Bool,
  DynFlags -> Bool
avx512cd              :: Bool, -- Enable AVX-512 Conflict Detection Instructions.
  DynFlags -> Bool
avx512er              :: Bool, -- Enable AVX-512 Exponential and Reciprocal Instructions.
  DynFlags -> Bool
avx512f               :: Bool, -- Enable AVX-512 instructions.
  DynFlags -> Bool
avx512pf              :: Bool, -- Enable AVX-512 PreFetch Instructions.

  -- | Run-time linker information (what options we need, etc.)
  DynFlags -> IORef (Maybe LinkerInfo)
rtldInfo              :: IORef (Maybe LinkerInfo),

  -- | Run-time compiler information
  DynFlags -> IORef (Maybe CompilerInfo)
rtccInfo              :: IORef (Maybe CompilerInfo),

  -- Constants used to control the amount of optimization done.

  -- | Max size, in bytes, of inline array allocations.
  DynFlags -> Int
maxInlineAllocSize    :: Int,

  -- | Only inline memcpy if it generates no more than this many
  -- pseudo (roughly: Cmm) instructions.
  DynFlags -> Int
maxInlineMemcpyInsns  :: Int,

  -- | Only inline memset if it generates no more than this many
  -- pseudo (roughly: Cmm) instructions.
  DynFlags -> Int
maxInlineMemsetInsns  :: Int,

  -- | Reverse the order of error messages in GHC/GHCi
  DynFlags -> Bool
reverseErrors         :: Bool,

  -- | Limit the maximum number of errors to show
  DynFlags -> Maybe Int
maxErrors             :: Maybe Int,

  -- | Unique supply configuration for testing build determinism
  DynFlags -> Word
initialUnique         :: Word,
  DynFlags -> Int
uniqueIncrement       :: Int,
    -- 'Int' because it can be used to test uniques in decreasing order.

  -- | Temporary: CFG Edge weights for fast iterations
  DynFlags -> Weights
cfgWeights            :: Weights
}

class HasDynFlags m where
    getDynFlags :: m DynFlags

{- It would be desirable to have the more generalised

  instance (MonadTrans t, Monad m, HasDynFlags m) => HasDynFlags (t m) where
      getDynFlags = lift getDynFlags

instance definition. However, that definition would overlap with the
`HasDynFlags (GhcT m)` instance. Instead we define instances for a
couple of common Monad transformers explicitly. -}

instance (Monoid a, Monad m, HasDynFlags m) => HasDynFlags (WriterT a m) where
    getDynFlags :: WriterT a m DynFlags
getDynFlags = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags

instance (Monad m, HasDynFlags m) => HasDynFlags (ReaderT a m) where
    getDynFlags :: ReaderT a m DynFlags
getDynFlags = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags

instance (Monad m, HasDynFlags m) => HasDynFlags (MaybeT m) where
    getDynFlags :: MaybeT m DynFlags
getDynFlags = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags

instance (Monad m, HasDynFlags m) => HasDynFlags (ExceptT e m) where
    getDynFlags :: ExceptT e m DynFlags
getDynFlags = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags

class ContainsDynFlags t where
    extractDynFlags :: t -> DynFlags

data ProfAuto
  = NoProfAuto         -- ^ no SCC annotations added
  | ProfAutoAll        -- ^ top-level and nested functions are annotated
  | ProfAutoTop        -- ^ top-level functions annotated only
  | ProfAutoExports    -- ^ exported functions annotated only
  | ProfAutoCalls      -- ^ annotate call-sites
  deriving (ProfAuto -> ProfAuto -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProfAuto -> ProfAuto -> Bool
$c/= :: ProfAuto -> ProfAuto -> Bool
== :: ProfAuto -> ProfAuto -> Bool
$c== :: ProfAuto -> ProfAuto -> Bool
Eq,Int -> ProfAuto
ProfAuto -> Int
ProfAuto -> [ProfAuto]
ProfAuto -> ProfAuto
ProfAuto -> ProfAuto -> [ProfAuto]
ProfAuto -> ProfAuto -> ProfAuto -> [ProfAuto]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ProfAuto -> ProfAuto -> ProfAuto -> [ProfAuto]
$cenumFromThenTo :: ProfAuto -> ProfAuto -> ProfAuto -> [ProfAuto]
enumFromTo :: ProfAuto -> ProfAuto -> [ProfAuto]
$cenumFromTo :: ProfAuto -> ProfAuto -> [ProfAuto]
enumFromThen :: ProfAuto -> ProfAuto -> [ProfAuto]
$cenumFromThen :: ProfAuto -> ProfAuto -> [ProfAuto]
enumFrom :: ProfAuto -> [ProfAuto]
$cenumFrom :: ProfAuto -> [ProfAuto]
fromEnum :: ProfAuto -> Int
$cfromEnum :: ProfAuto -> Int
toEnum :: Int -> ProfAuto
$ctoEnum :: Int -> ProfAuto
pred :: ProfAuto -> ProfAuto
$cpred :: ProfAuto -> ProfAuto
succ :: ProfAuto -> ProfAuto
$csucc :: ProfAuto -> ProfAuto
Enum)

data LlvmTarget = LlvmTarget
  { LlvmTarget -> [Char]
lDataLayout :: String
  , LlvmTarget -> [Char]
lCPU        :: String
  , LlvmTarget -> [[Char]]
lAttributes :: [String]
  }

-- | See Note [LLVM Configuration] in "GHC.SysTools".
data LlvmConfig = LlvmConfig { LlvmConfig -> [([Char], LlvmTarget)]
llvmTargets :: [(String, LlvmTarget)]
                             , LlvmConfig -> [(Int, [Char])]
llvmPasses  :: [(Int, String)]
                             }

-----------------------------------------------------------------------------
-- Accessessors from 'DynFlags'

-- | "unbuild" a 'Settings' from a 'DynFlags'. This shouldn't be needed in the
-- vast majority of code. But GHCi questionably uses this to produce a default
-- 'DynFlags' from which to compute a flags diff for printing.
settings :: DynFlags -> Settings
settings :: DynFlags -> Settings
settings DynFlags
dflags = Settings
  { sGhcNameVersion :: GhcNameVersion
sGhcNameVersion = DynFlags -> GhcNameVersion
ghcNameVersion DynFlags
dflags
  , sFileSettings :: FileSettings
sFileSettings = DynFlags -> FileSettings
fileSettings DynFlags
dflags
  , sTargetPlatform :: Platform
sTargetPlatform = DynFlags -> Platform
targetPlatform DynFlags
dflags
  , sToolSettings :: ToolSettings
sToolSettings = DynFlags -> ToolSettings
toolSettings DynFlags
dflags
  , sPlatformMisc :: PlatformMisc
sPlatformMisc = DynFlags -> PlatformMisc
platformMisc DynFlags
dflags
  , sRawSettings :: [([Char], [Char])]
sRawSettings = DynFlags -> [([Char], [Char])]
rawSettings DynFlags
dflags
  }

programName :: DynFlags -> String
programName :: DynFlags -> [Char]
programName DynFlags
dflags = GhcNameVersion -> [Char]
ghcNameVersion_programName forall a b. (a -> b) -> a -> b
$ DynFlags -> GhcNameVersion
ghcNameVersion DynFlags
dflags
projectVersion :: DynFlags -> String
projectVersion :: DynFlags -> [Char]
projectVersion DynFlags
dflags = GhcNameVersion -> [Char]
ghcNameVersion_projectVersion (DynFlags -> GhcNameVersion
ghcNameVersion DynFlags
dflags)
ghcUsagePath          :: DynFlags -> FilePath
ghcUsagePath :: DynFlags -> [Char]
ghcUsagePath DynFlags
dflags = FileSettings -> [Char]
fileSettings_ghcUsagePath forall a b. (a -> b) -> a -> b
$ DynFlags -> FileSettings
fileSettings DynFlags
dflags
ghciUsagePath         :: DynFlags -> FilePath
ghciUsagePath :: DynFlags -> [Char]
ghciUsagePath DynFlags
dflags = FileSettings -> [Char]
fileSettings_ghciUsagePath forall a b. (a -> b) -> a -> b
$ DynFlags -> FileSettings
fileSettings DynFlags
dflags
toolDir               :: DynFlags -> Maybe FilePath
toolDir :: DynFlags -> Maybe [Char]
toolDir DynFlags
dflags = FileSettings -> Maybe [Char]
fileSettings_toolDir forall a b. (a -> b) -> a -> b
$ DynFlags -> FileSettings
fileSettings DynFlags
dflags
topDir                :: DynFlags -> FilePath
topDir :: DynFlags -> [Char]
topDir DynFlags
dflags = FileSettings -> [Char]
fileSettings_topDir forall a b. (a -> b) -> a -> b
$ DynFlags -> FileSettings
fileSettings DynFlags
dflags
tmpDir                :: DynFlags -> String
tmpDir :: DynFlags -> [Char]
tmpDir DynFlags
dflags = FileSettings -> [Char]
fileSettings_tmpDir forall a b. (a -> b) -> a -> b
$ DynFlags -> FileSettings
fileSettings DynFlags
dflags
extraGccViaCFlags     :: DynFlags -> [String]
extraGccViaCFlags :: DynFlags -> [[Char]]
extraGccViaCFlags DynFlags
dflags = ToolSettings -> [[Char]]
toolSettings_extraGccViaCFlags forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
globalPackageDatabasePath   :: DynFlags -> FilePath
globalPackageDatabasePath :: DynFlags -> [Char]
globalPackageDatabasePath DynFlags
dflags = FileSettings -> [Char]
fileSettings_globalPackageDatabase forall a b. (a -> b) -> a -> b
$ DynFlags -> FileSettings
fileSettings DynFlags
dflags
pgm_L                 :: DynFlags -> String
pgm_L :: DynFlags -> [Char]
pgm_L DynFlags
dflags = ToolSettings -> [Char]
toolSettings_pgm_L forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
pgm_P                 :: DynFlags -> (String,[Option])
pgm_P :: DynFlags -> ([Char], [Option])
pgm_P DynFlags
dflags = ToolSettings -> ([Char], [Option])
toolSettings_pgm_P forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
pgm_F                 :: DynFlags -> String
pgm_F :: DynFlags -> [Char]
pgm_F DynFlags
dflags = ToolSettings -> [Char]
toolSettings_pgm_F forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
pgm_c                 :: DynFlags -> String
pgm_c :: DynFlags -> [Char]
pgm_c DynFlags
dflags = ToolSettings -> [Char]
toolSettings_pgm_c forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
pgm_a                 :: DynFlags -> (String,[Option])
pgm_a :: DynFlags -> ([Char], [Option])
pgm_a DynFlags
dflags = ToolSettings -> ([Char], [Option])
toolSettings_pgm_a forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
pgm_l                 :: DynFlags -> (String,[Option])
pgm_l :: DynFlags -> ([Char], [Option])
pgm_l DynFlags
dflags = ToolSettings -> ([Char], [Option])
toolSettings_pgm_l forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
pgm_lm                 :: DynFlags -> (String,[Option])
pgm_lm :: DynFlags -> ([Char], [Option])
pgm_lm DynFlags
dflags = ToolSettings -> ([Char], [Option])
toolSettings_pgm_lm forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
pgm_dll               :: DynFlags -> (String,[Option])
pgm_dll :: DynFlags -> ([Char], [Option])
pgm_dll DynFlags
dflags = ToolSettings -> ([Char], [Option])
toolSettings_pgm_dll forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
pgm_T                 :: DynFlags -> String
pgm_T :: DynFlags -> [Char]
pgm_T DynFlags
dflags = ToolSettings -> [Char]
toolSettings_pgm_T forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
pgm_windres           :: DynFlags -> String
pgm_windres :: DynFlags -> [Char]
pgm_windres DynFlags
dflags = ToolSettings -> [Char]
toolSettings_pgm_windres forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
pgm_libtool           :: DynFlags -> String
pgm_libtool :: DynFlags -> [Char]
pgm_libtool DynFlags
dflags = ToolSettings -> [Char]
toolSettings_pgm_libtool forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
pgm_lcc               :: DynFlags -> (String,[Option])
pgm_lcc :: DynFlags -> ([Char], [Option])
pgm_lcc DynFlags
dflags = ToolSettings -> ([Char], [Option])
toolSettings_pgm_lcc forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
pgm_ar                :: DynFlags -> String
pgm_ar :: DynFlags -> [Char]
pgm_ar DynFlags
dflags = ToolSettings -> [Char]
toolSettings_pgm_ar forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
pgm_otool             :: DynFlags -> String
pgm_otool :: DynFlags -> [Char]
pgm_otool DynFlags
dflags = ToolSettings -> [Char]
toolSettings_pgm_otool forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
pgm_install_name_tool :: DynFlags -> String
pgm_install_name_tool :: DynFlags -> [Char]
pgm_install_name_tool DynFlags
dflags = ToolSettings -> [Char]
toolSettings_pgm_install_name_tool forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
pgm_ranlib            :: DynFlags -> String
pgm_ranlib :: DynFlags -> [Char]
pgm_ranlib DynFlags
dflags = ToolSettings -> [Char]
toolSettings_pgm_ranlib forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
pgm_lo                :: DynFlags -> (String,[Option])
pgm_lo :: DynFlags -> ([Char], [Option])
pgm_lo DynFlags
dflags = ToolSettings -> ([Char], [Option])
toolSettings_pgm_lo forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
pgm_lc                :: DynFlags -> (String,[Option])
pgm_lc :: DynFlags -> ([Char], [Option])
pgm_lc DynFlags
dflags = ToolSettings -> ([Char], [Option])
toolSettings_pgm_lc forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
pgm_i                 :: DynFlags -> String
pgm_i :: DynFlags -> [Char]
pgm_i DynFlags
dflags = ToolSettings -> [Char]
toolSettings_pgm_i forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
opt_L                 :: DynFlags -> [String]
opt_L :: DynFlags -> [[Char]]
opt_L DynFlags
dflags = ToolSettings -> [[Char]]
toolSettings_opt_L forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
opt_P                 :: DynFlags -> [String]
opt_P :: DynFlags -> [[Char]]
opt_P DynFlags
dflags = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Platform -> Way -> [[Char]]
wayOptP (DynFlags -> Platform
targetPlatform DynFlags
dflags)) (DynFlags -> Ways
ways DynFlags
dflags)
            forall a. [a] -> [a] -> [a]
++ ToolSettings -> [[Char]]
toolSettings_opt_P (DynFlags -> ToolSettings
toolSettings DynFlags
dflags)

-- This function packages everything that's needed to fingerprint opt_P
-- flags. See Note [Repeated -optP hashing].
opt_P_signature       :: DynFlags -> ([String], Fingerprint)
opt_P_signature :: DynFlags -> ([[Char]], Fingerprint)
opt_P_signature DynFlags
dflags =
  ( forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Platform -> Way -> [[Char]]
wayOptP (DynFlags -> Platform
targetPlatform DynFlags
dflags)) (DynFlags -> Ways
ways DynFlags
dflags)
  , ToolSettings -> Fingerprint
toolSettings_opt_P_fingerprint forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
  )

opt_F                 :: DynFlags -> [String]
opt_F :: DynFlags -> [[Char]]
opt_F DynFlags
dflags= ToolSettings -> [[Char]]
toolSettings_opt_F forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
opt_c                 :: DynFlags -> [String]
opt_c :: DynFlags -> [[Char]]
opt_c DynFlags
dflags = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Platform -> Way -> [[Char]]
wayOptc (DynFlags -> Platform
targetPlatform DynFlags
dflags)) (DynFlags -> Ways
ways DynFlags
dflags)
            forall a. [a] -> [a] -> [a]
++ ToolSettings -> [[Char]]
toolSettings_opt_c (DynFlags -> ToolSettings
toolSettings DynFlags
dflags)
opt_cxx               :: DynFlags -> [String]
opt_cxx :: DynFlags -> [[Char]]
opt_cxx DynFlags
dflags= ToolSettings -> [[Char]]
toolSettings_opt_cxx forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
opt_a                 :: DynFlags -> [String]
opt_a :: DynFlags -> [[Char]]
opt_a DynFlags
dflags= ToolSettings -> [[Char]]
toolSettings_opt_a forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
opt_l                 :: DynFlags -> [String]
opt_l :: DynFlags -> [[Char]]
opt_l DynFlags
dflags = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Platform -> Way -> [[Char]]
wayOptl (DynFlags -> Platform
targetPlatform DynFlags
dflags)) (DynFlags -> Ways
ways DynFlags
dflags)
            forall a. [a] -> [a] -> [a]
++ ToolSettings -> [[Char]]
toolSettings_opt_l (DynFlags -> ToolSettings
toolSettings DynFlags
dflags)
opt_lm                :: DynFlags -> [String]
opt_lm :: DynFlags -> [[Char]]
opt_lm DynFlags
dflags= ToolSettings -> [[Char]]
toolSettings_opt_lm forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
opt_windres           :: DynFlags -> [String]
opt_windres :: DynFlags -> [[Char]]
opt_windres DynFlags
dflags= ToolSettings -> [[Char]]
toolSettings_opt_windres forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
opt_lcc                :: DynFlags -> [String]
opt_lcc :: DynFlags -> [[Char]]
opt_lcc DynFlags
dflags= ToolSettings -> [[Char]]
toolSettings_opt_lcc forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
opt_lo                :: DynFlags -> [String]
opt_lo :: DynFlags -> [[Char]]
opt_lo DynFlags
dflags= ToolSettings -> [[Char]]
toolSettings_opt_lo forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
opt_lc                :: DynFlags -> [String]
opt_lc :: DynFlags -> [[Char]]
opt_lc DynFlags
dflags= ToolSettings -> [[Char]]
toolSettings_opt_lc forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags
opt_i                 :: DynFlags -> [String]
opt_i :: DynFlags -> [[Char]]
opt_i DynFlags
dflags= ToolSettings -> [[Char]]
toolSettings_opt_i forall a b. (a -> b) -> a -> b
$ DynFlags -> ToolSettings
toolSettings DynFlags
dflags

-- | The directory for this version of ghc in the user's app directory
-- The appdir used to be in ~/.ghc but to respect the XDG specification
-- we want to move it under $XDG_DATA_HOME/
-- However, old tooling (like cabal) might still write package environments
-- to the old directory, so we prefer that if a subdirectory of ~/.ghc
-- with the correct target and GHC version suffix exists.
--
-- i.e. if ~/.ghc/$UNIQUE_SUBDIR exists we use that
-- otherwise we use $XDG_DATA_HOME/$UNIQUE_SUBDIR
--
-- UNIQUE_SUBDIR is typically a combination of the target platform and GHC version
versionedAppDir :: String -> ArchOS -> MaybeT IO FilePath
versionedAppDir :: [Char] -> ArchOS -> MaybeT IO [Char]
versionedAppDir [Char]
appname ArchOS
platform = do
  -- Make sure we handle the case the HOME isn't set (see #11678)
  -- We need to fallback to the old scheme if the subdirectory exists.
  forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map ([Char] -> MaybeT IO [Char]
checkIfExists forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Char] -> ShowS
</> ArchOS -> [Char]
versionedFilePath ArchOS
platform))
       [ forall a. IO a -> MaybeT IO a
tryMaybeT forall a b. (a -> b) -> a -> b
$ [Char] -> IO [Char]
getAppUserDataDirectory [Char]
appname  -- this is ~/.ghc/
       , forall a. IO a -> MaybeT IO a
tryMaybeT forall a b. (a -> b) -> a -> b
$ XdgDirectory -> [Char] -> IO [Char]
getXdgDirectory XdgDirectory
XdgData [Char]
appname -- this is $XDG_DATA_HOME/
       ]
  where
    checkIfExists :: [Char] -> MaybeT IO [Char]
checkIfExists [Char]
dir = forall a. IO a -> MaybeT IO a
tryMaybeT ([Char] -> IO Bool
doesDirectoryExist [Char]
dir) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
      Bool
True -> forall (f :: * -> *) a. Applicative f => a -> f a
pure [Char]
dir
      Bool
False -> forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing)

versionedFilePath :: ArchOS -> FilePath
versionedFilePath :: ArchOS -> [Char]
versionedFilePath ArchOS
platform = ArchOS -> [Char]
uniqueSubdir ArchOS
platform

-- | The 'GhcMode' tells us whether we're doing multi-module
-- compilation (controlled via the "GHC" API) or one-shot
-- (single-module) compilation.  This makes a difference primarily to
-- the "GHC.Unit.Finder": in one-shot mode we look for interface files for
-- imported modules, but in multi-module mode we look for source files
-- in order to check whether they need to be recompiled.
data GhcMode
  = CompManager         -- ^ @\-\-make@, GHCi, etc.
  | OneShot             -- ^ @ghc -c Foo.hs@
  | MkDepend            -- ^ @ghc -M@, see "GHC.Unit.Finder" for why we need this
  deriving GhcMode -> GhcMode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GhcMode -> GhcMode -> Bool
$c/= :: GhcMode -> GhcMode -> Bool
== :: GhcMode -> GhcMode -> Bool
$c== :: GhcMode -> GhcMode -> Bool
Eq

instance Outputable GhcMode where
  ppr :: GhcMode -> SDoc
ppr GhcMode
CompManager = [Char] -> SDoc
text [Char]
"CompManager"
  ppr GhcMode
OneShot     = [Char] -> SDoc
text [Char]
"OneShot"
  ppr GhcMode
MkDepend    = [Char] -> SDoc
text [Char]
"MkDepend"

isOneShot :: GhcMode -> Bool
isOneShot :: GhcMode -> Bool
isOneShot GhcMode
OneShot = Bool
True
isOneShot GhcMode
_other  = Bool
False

-- | What to do in the link step, if there is one.
data GhcLink
  = NoLink              -- ^ Don't link at all
  | LinkBinary          -- ^ Link object code into a binary
  | LinkInMemory        -- ^ Use the in-memory dynamic linker (works for both
                        --   bytecode and object code).
  | LinkDynLib          -- ^ Link objects into a dynamic lib (DLL on Windows, DSO on ELF platforms)
  | LinkStaticLib       -- ^ Link objects into a static lib
  deriving (GhcLink -> GhcLink -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GhcLink -> GhcLink -> Bool
$c/= :: GhcLink -> GhcLink -> Bool
== :: GhcLink -> GhcLink -> Bool
$c== :: GhcLink -> GhcLink -> Bool
Eq, Int -> GhcLink -> ShowS
[GhcLink] -> ShowS
GhcLink -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [GhcLink] -> ShowS
$cshowList :: [GhcLink] -> ShowS
show :: GhcLink -> [Char]
$cshow :: GhcLink -> [Char]
showsPrec :: Int -> GhcLink -> ShowS
$cshowsPrec :: Int -> GhcLink -> ShowS
Show)

isNoLink :: GhcLink -> Bool
isNoLink :: GhcLink -> Bool
isNoLink GhcLink
NoLink = Bool
True
isNoLink GhcLink
_      = Bool
False

-- | We accept flags which make packages visible, but how they select
-- the package varies; this data type reflects what selection criterion
-- is used.
data PackageArg =
      PackageArg String    -- ^ @-package@, by 'PackageName'
    | UnitIdArg Unit       -- ^ @-package-id@, by 'Unit'
  deriving (PackageArg -> PackageArg -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PackageArg -> PackageArg -> Bool
$c/= :: PackageArg -> PackageArg -> Bool
== :: PackageArg -> PackageArg -> Bool
$c== :: PackageArg -> PackageArg -> Bool
Eq, Int -> PackageArg -> ShowS
[PackageArg] -> ShowS
PackageArg -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [PackageArg] -> ShowS
$cshowList :: [PackageArg] -> ShowS
show :: PackageArg -> [Char]
$cshow :: PackageArg -> [Char]
showsPrec :: Int -> PackageArg -> ShowS
$cshowsPrec :: Int -> PackageArg -> ShowS
Show)

instance Outputable PackageArg where
    ppr :: PackageArg -> SDoc
ppr (PackageArg [Char]
pn) = [Char] -> SDoc
text [Char]
"package" SDoc -> SDoc -> SDoc
<+> [Char] -> SDoc
text [Char]
pn
    ppr (UnitIdArg Unit
uid) = [Char] -> SDoc
text [Char]
"unit" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Unit
uid

-- | Represents the renaming that may be associated with an exposed
-- package, e.g. the @rns@ part of @-package "foo (rns)"@.
--
-- Here are some example parsings of the package flags (where
-- a string literal is punned to be a 'ModuleName':
--
--      * @-package foo@ is @ModRenaming True []@
--      * @-package foo ()@ is @ModRenaming False []@
--      * @-package foo (A)@ is @ModRenaming False [("A", "A")]@
--      * @-package foo (A as B)@ is @ModRenaming False [("A", "B")]@
--      * @-package foo with (A as B)@ is @ModRenaming True [("A", "B")]@
data ModRenaming = ModRenaming {
    ModRenaming -> Bool
modRenamingWithImplicit :: Bool, -- ^ Bring all exposed modules into scope?
    ModRenaming -> [(ModuleName, ModuleName)]
modRenamings :: [(ModuleName, ModuleName)] -- ^ Bring module @m@ into scope
                                               --   under name @n@.
  } deriving (ModRenaming -> ModRenaming -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModRenaming -> ModRenaming -> Bool
$c/= :: ModRenaming -> ModRenaming -> Bool
== :: ModRenaming -> ModRenaming -> Bool
$c== :: ModRenaming -> ModRenaming -> Bool
Eq)
instance Outputable ModRenaming where
    ppr :: ModRenaming -> SDoc
ppr (ModRenaming Bool
b [(ModuleName, ModuleName)]
rns) = forall a. Outputable a => a -> SDoc
ppr Bool
b SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (forall a. Outputable a => a -> SDoc
ppr [(ModuleName, ModuleName)]
rns)

-- | Flags for manipulating the set of non-broken packages.
newtype IgnorePackageFlag = IgnorePackage String -- ^ @-ignore-package@
  deriving (IgnorePackageFlag -> IgnorePackageFlag -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IgnorePackageFlag -> IgnorePackageFlag -> Bool
$c/= :: IgnorePackageFlag -> IgnorePackageFlag -> Bool
== :: IgnorePackageFlag -> IgnorePackageFlag -> Bool
$c== :: IgnorePackageFlag -> IgnorePackageFlag -> Bool
Eq)

-- | Flags for manipulating package trust.
data TrustFlag
  = TrustPackage    String -- ^ @-trust@
  | DistrustPackage String -- ^ @-distrust@
  deriving (TrustFlag -> TrustFlag -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TrustFlag -> TrustFlag -> Bool
$c/= :: TrustFlag -> TrustFlag -> Bool
== :: TrustFlag -> TrustFlag -> Bool
$c== :: TrustFlag -> TrustFlag -> Bool
Eq)

-- | Flags for manipulating packages visibility.
data PackageFlag
  = ExposePackage   String PackageArg ModRenaming -- ^ @-package@, @-package-id@
  | HidePackage     String -- ^ @-hide-package@
  deriving (PackageFlag -> PackageFlag -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PackageFlag -> PackageFlag -> Bool
$c/= :: PackageFlag -> PackageFlag -> Bool
== :: PackageFlag -> PackageFlag -> Bool
$c== :: PackageFlag -> PackageFlag -> Bool
Eq) -- NB: equality instance is used by packageFlagsChanged

data PackageDBFlag
  = PackageDB PkgDbRef
  | NoUserPackageDB
  | NoGlobalPackageDB
  | ClearPackageDBs
  deriving (PackageDBFlag -> PackageDBFlag -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PackageDBFlag -> PackageDBFlag -> Bool
$c/= :: PackageDBFlag -> PackageDBFlag -> Bool
== :: PackageDBFlag -> PackageDBFlag -> Bool
$c== :: PackageDBFlag -> PackageDBFlag -> Bool
Eq)

packageFlagsChanged :: DynFlags -> DynFlags -> Bool
packageFlagsChanged :: DynFlags -> DynFlags -> Bool
packageFlagsChanged DynFlags
idflags1 DynFlags
idflags0 =
  DynFlags -> [PackageFlag]
packageFlags DynFlags
idflags1 forall a. Eq a => a -> a -> Bool
/= DynFlags -> [PackageFlag]
packageFlags DynFlags
idflags0 Bool -> Bool -> Bool
||
  DynFlags -> [IgnorePackageFlag]
ignorePackageFlags DynFlags
idflags1 forall a. Eq a => a -> a -> Bool
/= DynFlags -> [IgnorePackageFlag]
ignorePackageFlags DynFlags
idflags0 Bool -> Bool -> Bool
||
  DynFlags -> [PackageFlag]
pluginPackageFlags DynFlags
idflags1 forall a. Eq a => a -> a -> Bool
/= DynFlags -> [PackageFlag]
pluginPackageFlags DynFlags
idflags0 Bool -> Bool -> Bool
||
  DynFlags -> [TrustFlag]
trustFlags DynFlags
idflags1 forall a. Eq a => a -> a -> Bool
/= DynFlags -> [TrustFlag]
trustFlags DynFlags
idflags0 Bool -> Bool -> Bool
||
  DynFlags -> [PackageDBFlag]
packageDBFlags DynFlags
idflags1 forall a. Eq a => a -> a -> Bool
/= DynFlags -> [PackageDBFlag]
packageDBFlags DynFlags
idflags0 Bool -> Bool -> Bool
||
  DynFlags -> [Bool]
packageGFlags DynFlags
idflags1 forall a. Eq a => a -> a -> Bool
/= DynFlags -> [Bool]
packageGFlags DynFlags
idflags0
 where
   packageGFlags :: DynFlags -> [Bool]
packageGFlags DynFlags
dflags = forall a b. (a -> b) -> [a] -> [b]
map (GeneralFlag -> DynFlags -> Bool
`gopt` DynFlags
dflags)
     [ GeneralFlag
Opt_HideAllPackages
     , GeneralFlag
Opt_HideAllPluginPackages
     , GeneralFlag
Opt_AutoLinkPackages ]

instance Outputable PackageFlag where
    ppr :: PackageFlag -> SDoc
ppr (ExposePackage [Char]
n PackageArg
arg ModRenaming
rn) = [Char] -> SDoc
text [Char]
n SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
braces (forall a. Outputable a => a -> SDoc
ppr PackageArg
arg SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr ModRenaming
rn)
    ppr (HidePackage [Char]
str) = [Char] -> SDoc
text [Char]
"-hide-package" SDoc -> SDoc -> SDoc
<+> [Char] -> SDoc
text [Char]
str

data DynLibLoader
  = Deployable
  | SystemDependent
  deriving DynLibLoader -> DynLibLoader -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DynLibLoader -> DynLibLoader -> Bool
$c/= :: DynLibLoader -> DynLibLoader -> Bool
== :: DynLibLoader -> DynLibLoader -> Bool
$c== :: DynLibLoader -> DynLibLoader -> Bool
Eq

data RtsOptsEnabled
  = RtsOptsNone | RtsOptsIgnore | RtsOptsIgnoreAll | RtsOptsSafeOnly
  | RtsOptsAll
  deriving (Int -> RtsOptsEnabled -> ShowS
[RtsOptsEnabled] -> ShowS
RtsOptsEnabled -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [RtsOptsEnabled] -> ShowS
$cshowList :: [RtsOptsEnabled] -> ShowS
show :: RtsOptsEnabled -> [Char]
$cshow :: RtsOptsEnabled -> [Char]
showsPrec :: Int -> RtsOptsEnabled -> ShowS
$cshowsPrec :: Int -> RtsOptsEnabled -> ShowS
Show)

-- | Are we building with @-fPIE@ or @-fPIC@ enabled?
positionIndependent :: DynFlags -> Bool
positionIndependent :: DynFlags -> Bool
positionIndependent DynFlags
dflags = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_PIC DynFlags
dflags Bool -> Bool -> Bool
|| GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_PIE DynFlags
dflags

-- Note [-dynamic-too business]
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
--
-- With -dynamic-too flag, we try to build both the non-dynamic and dynamic
-- objects in a single run of the compiler: the pipeline is the same down to
-- Core optimisation, then the backend (from Core to object code) is executed
-- twice.
--
-- The implementation is currently rather hacky: recompilation avoidance is
-- broken (#17968), we don't clearly separate non-dynamic and dynamic loaded
-- interfaces (#9176), etc.
--
-- To make matters worse, we automatically enable -dynamic-too when some modules
-- need Template-Haskell and GHC is dynamically linked (cf
-- GHC.Driver.Pipeline.compileOne').
--
-- This somewhat explains why we have "dynamicTooFailed :: IORef Bool" in
-- DynFlags: when -dynamic-too is enabled, we try to build the dynamic objects,
-- but we may fail and we shouldn't abort the whole compilation because the user
-- may not even have asked for -dynamic-too in the first place. So instead we
-- use this global variable to indicate that we can't build dynamic objects and
-- compilation continues to build non-dynamic objects only. At the end of the
-- non-dynamic pipeline, if this value indicates that the dynamic compilation
-- failed, we run the whole pipeline again for the dynamic way (except on
-- Windows...). See GHC.Driver.Pipeline.runPipeline.

data DynamicTooState
   = DT_Dont    -- ^ Don't try to build dynamic objects too
   | DT_Failed  -- ^ Won't try to generate dynamic objects for some reason
   | DT_OK      -- ^ Will still try to generate dynamic objects
   | DT_Dyn     -- ^ Currently generating dynamic objects (in the backend)
   deriving (DynamicTooState -> DynamicTooState -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DynamicTooState -> DynamicTooState -> Bool
$c/= :: DynamicTooState -> DynamicTooState -> Bool
== :: DynamicTooState -> DynamicTooState -> Bool
$c== :: DynamicTooState -> DynamicTooState -> Bool
Eq,Int -> DynamicTooState -> ShowS
[DynamicTooState] -> ShowS
DynamicTooState -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [DynamicTooState] -> ShowS
$cshowList :: [DynamicTooState] -> ShowS
show :: DynamicTooState -> [Char]
$cshow :: DynamicTooState -> [Char]
showsPrec :: Int -> DynamicTooState -> ShowS
$cshowsPrec :: Int -> DynamicTooState -> ShowS
Show,Eq DynamicTooState
DynamicTooState -> DynamicTooState -> Bool
DynamicTooState -> DynamicTooState -> Ordering
DynamicTooState -> DynamicTooState -> DynamicTooState
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DynamicTooState -> DynamicTooState -> DynamicTooState
$cmin :: DynamicTooState -> DynamicTooState -> DynamicTooState
max :: DynamicTooState -> DynamicTooState -> DynamicTooState
$cmax :: DynamicTooState -> DynamicTooState -> DynamicTooState
>= :: DynamicTooState -> DynamicTooState -> Bool
$c>= :: DynamicTooState -> DynamicTooState -> Bool
> :: DynamicTooState -> DynamicTooState -> Bool
$c> :: DynamicTooState -> DynamicTooState -> Bool
<= :: DynamicTooState -> DynamicTooState -> Bool
$c<= :: DynamicTooState -> DynamicTooState -> Bool
< :: DynamicTooState -> DynamicTooState -> Bool
$c< :: DynamicTooState -> DynamicTooState -> Bool
compare :: DynamicTooState -> DynamicTooState -> Ordering
$ccompare :: DynamicTooState -> DynamicTooState -> Ordering
Ord)

dynamicTooState :: MonadIO m => DynFlags -> m DynamicTooState
dynamicTooState :: forall (m :: * -> *). MonadIO m => DynFlags -> m DynamicTooState
dynamicTooState DynFlags
dflags
   | Bool -> Bool
not (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_BuildDynamicToo DynFlags
dflags) = forall (m :: * -> *) a. Monad m => a -> m a
return DynamicTooState
DT_Dont
   | Bool
otherwise = do
      Bool
failed <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. IORef a -> IO a
readIORef (DynFlags -> IORef Bool
dynamicTooFailed DynFlags
dflags)
      if Bool
failed
         then forall (m :: * -> *) a. Monad m => a -> m a
return DynamicTooState
DT_Failed
         else if DynFlags -> Bool
dynamicNow DynFlags
dflags
               then forall (m :: * -> *) a. Monad m => a -> m a
return DynamicTooState
DT_Dyn
               else forall (m :: * -> *) a. Monad m => a -> m a
return DynamicTooState
DT_OK

setDynamicNow :: DynFlags -> DynFlags
setDynamicNow :: DynFlags -> DynFlags
setDynamicNow DynFlags
dflags0 =
   DynFlags
dflags0
      { dynamicNow :: Bool
dynamicNow = Bool
True
      }

setDynamicTooFailed :: MonadIO m => DynFlags -> m ()
setDynamicTooFailed :: forall (m :: * -> *). MonadIO m => DynFlags -> m ()
setDynamicTooFailed DynFlags
dflags =
   forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. IORef a -> a -> IO ()
writeIORef (DynFlags -> IORef Bool
dynamicTooFailed DynFlags
dflags) Bool
True

-- | Compute the path of the dynamic object corresponding to an object file.
dynamicOutputFile :: DynFlags -> FilePath -> FilePath
dynamicOutputFile :: DynFlags -> ShowS
dynamicOutputFile DynFlags
dflags [Char]
outputFile = [Char]
outputFile [Char] -> ShowS
-<.> DynFlags -> [Char]
dynObjectSuf_ DynFlags
dflags

dynamicOutputHi :: DynFlags -> FilePath -> FilePath
dynamicOutputHi :: DynFlags -> ShowS
dynamicOutputHi DynFlags
dflags [Char]
hi = [Char]
hi [Char] -> ShowS
-<.> DynFlags -> [Char]
dynHiSuf_ DynFlags
dflags

-----------------------------------------------------------------------------

-- | Used by 'GHC.runGhc' to partially initialize a new 'DynFlags' value
initDynFlags :: DynFlags -> IO DynFlags
initDynFlags :: DynFlags -> IO DynFlags
initDynFlags DynFlags
dflags = do
 let -- We can't build with dynamic-too on Windows, as labels before
     -- the fork point are different depending on whether we are
     -- building dynamically or not.
     platformCanGenerateDynamicToo :: Bool
platformCanGenerateDynamicToo
         = Platform -> OS
platformOS (DynFlags -> Platform
targetPlatform DynFlags
dflags) forall a. Eq a => a -> a -> Bool
/= OS
OSMinGW32
 IORef Bool
refDynamicTooFailed <- forall a. a -> IO (IORef a)
newIORef (Bool -> Bool
not Bool
platformCanGenerateDynamicToo)
 IORef (Maybe LinkerInfo)
refRtldInfo <- forall a. a -> IO (IORef a)
newIORef forall a. Maybe a
Nothing
 IORef (Maybe CompilerInfo)
refRtccInfo <- forall a. a -> IO (IORef a)
newIORef forall a. Maybe a
Nothing
 IORef (ModuleEnv Int)
wrapperNum <- forall a. a -> IO (IORef a)
newIORef forall a. ModuleEnv a
emptyModuleEnv
 Bool
canUseUnicode <- do let enc :: TextEncoding
enc = TextEncoding
localeEncoding
                         str :: [Char]
str = [Char]
"‘’"
                     (forall a. TextEncoding -> [Char] -> (CString -> IO a) -> IO a
withCString TextEncoding
enc [Char]
str forall a b. (a -> b) -> a -> b
$ \CString
cstr ->
                          do [Char]
str' <- TextEncoding -> CString -> IO [Char]
peekCString TextEncoding
enc CString
cstr
                             forall (m :: * -> *) a. Monad m => a -> m a
return ([Char]
str forall a. Eq a => a -> a -> Bool
== [Char]
str'))
                         forall a. IO a -> (IOError -> IO a) -> IO a
`catchIOError` \IOError
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
 Maybe [Char]
ghcNoUnicodeEnv <- [Char] -> IO (Maybe [Char])
lookupEnv [Char]
"GHC_NO_UNICODE"
 let useUnicode' :: Bool
useUnicode' = forall a. Maybe a -> Bool
isNothing Maybe [Char]
ghcNoUnicodeEnv Bool -> Bool -> Bool
&& Bool
canUseUnicode
 Maybe [Char]
maybeGhcColorsEnv  <- [Char] -> IO (Maybe [Char])
lookupEnv [Char]
"GHC_COLORS"
 Maybe [Char]
maybeGhcColoursEnv <- [Char] -> IO (Maybe [Char])
lookupEnv [Char]
"GHC_COLOURS"
 let adjustCols :: Maybe [Char]
-> (OverridingBool, Scheme) -> (OverridingBool, Scheme)
adjustCols (Just [Char]
env) = [Char] -> (OverridingBool, Scheme) -> (OverridingBool, Scheme)
Col.parseScheme [Char]
env
     adjustCols Maybe [Char]
Nothing    = forall a. a -> a
id
 let (OverridingBool
useColor', Scheme
colScheme') =
       (Maybe [Char]
-> (OverridingBool, Scheme) -> (OverridingBool, Scheme)
adjustCols Maybe [Char]
maybeGhcColoursEnv forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe [Char]
-> (OverridingBool, Scheme) -> (OverridingBool, Scheme)
adjustCols Maybe [Char]
maybeGhcColorsEnv)
       (DynFlags -> OverridingBool
useColor DynFlags
dflags, DynFlags -> Scheme
colScheme DynFlags
dflags)
 forall (m :: * -> *) a. Monad m => a -> m a
return DynFlags
dflags{
        dynamicTooFailed :: IORef Bool
dynamicTooFailed = IORef Bool
refDynamicTooFailed,
        nextWrapperNum :: IORef (ModuleEnv Int)
nextWrapperNum = IORef (ModuleEnv Int)
wrapperNum,
        useUnicode :: Bool
useUnicode    = Bool
useUnicode',
        useColor :: OverridingBool
useColor      = OverridingBool
useColor',
        canUseColor :: Bool
canUseColor   = Bool
stderrSupportsAnsiColors,
        colScheme :: Scheme
colScheme     = Scheme
colScheme',
        rtldInfo :: IORef (Maybe LinkerInfo)
rtldInfo      = IORef (Maybe LinkerInfo)
refRtldInfo,
        rtccInfo :: IORef (Maybe CompilerInfo)
rtccInfo      = IORef (Maybe CompilerInfo)
refRtccInfo
        }

-- | The normal 'DynFlags'. Note that they are not suitable for use in this form
-- and must be fully initialized by 'GHC.runGhc' first.
defaultDynFlags :: Settings -> LlvmConfig -> DynFlags
defaultDynFlags :: Settings -> LlvmConfig -> DynFlags
defaultDynFlags Settings
mySettings LlvmConfig
llvmConfig =
-- See Note [Updating flag description in the User's Guide]
     DynFlags {
        ghcMode :: GhcMode
ghcMode                 = GhcMode
CompManager,
        ghcLink :: GhcLink
ghcLink                 = GhcLink
LinkBinary,
        backend :: Backend
backend                 = Platform -> Backend
platformDefaultBackend (Settings -> Platform
sTargetPlatform Settings
mySettings),
        verbosity :: Int
verbosity               = Int
0,
        optLevel :: Int
optLevel                = Int
0,
        debugLevel :: Int
debugLevel              = Int
0,
        simplPhases :: Int
simplPhases             = Int
2,
        maxSimplIterations :: Int
maxSimplIterations      = Int
4,
        ruleCheck :: Maybe [Char]
ruleCheck               = forall a. Maybe a
Nothing,
        inlineCheck :: Maybe [Char]
inlineCheck             = forall a. Maybe a
Nothing,
        binBlobThreshold :: Word
binBlobThreshold        = Word
500000, -- 500K is a good default (see #16190)
        maxRelevantBinds :: Maybe Int
maxRelevantBinds        = forall a. a -> Maybe a
Just Int
6,
        maxValidHoleFits :: Maybe Int
maxValidHoleFits   = forall a. a -> Maybe a
Just Int
6,
        maxRefHoleFits :: Maybe Int
maxRefHoleFits     = forall a. a -> Maybe a
Just Int
6,
        refLevelHoleFits :: Maybe Int
refLevelHoleFits   = forall a. Maybe a
Nothing,
        maxUncoveredPatterns :: Int
maxUncoveredPatterns    = Int
4,
        maxPmCheckModels :: Int
maxPmCheckModels        = Int
30,
        simplTickFactor :: Int
simplTickFactor         = Int
100,
        specConstrThreshold :: Maybe Int
specConstrThreshold     = forall a. a -> Maybe a
Just Int
2000,
        specConstrCount :: Maybe Int
specConstrCount         = forall a. a -> Maybe a
Just Int
3,
        specConstrRecursive :: Int
specConstrRecursive     = Int
3,
        liberateCaseThreshold :: Maybe Int
liberateCaseThreshold   = forall a. a -> Maybe a
Just Int
2000,
        floatLamArgs :: Maybe Int
floatLamArgs            = forall a. a -> Maybe a
Just Int
0, -- Default: float only if no fvs
        liftLamsRecArgs :: Maybe Int
liftLamsRecArgs         = forall a. a -> Maybe a
Just Int
5, -- Default: the number of available argument hardware registers on x86_64
        liftLamsNonRecArgs :: Maybe Int
liftLamsNonRecArgs      = forall a. a -> Maybe a
Just Int
5, -- Default: the number of available argument hardware registers on x86_64
        liftLamsKnown :: Bool
liftLamsKnown           = Bool
False,  -- Default: don't turn known calls into unknown ones
        cmmProcAlignment :: Maybe Int
cmmProcAlignment        = forall a. Maybe a
Nothing,

        historySize :: Int
historySize             = Int
20,
        strictnessBefore :: [Int]
strictnessBefore        = [],

        parMakeCount :: Maybe Int
parMakeCount            = forall a. a -> Maybe a
Just Int
1,

        enableTimeStats :: Bool
enableTimeStats         = Bool
False,
        ghcHeapSize :: Maybe Int
ghcHeapSize             = forall a. Maybe a
Nothing,

        importPaths :: [[Char]]
importPaths             = [[Char]
"."],
        mainModuleNameIs :: ModuleName
mainModuleNameIs        = ModuleName
mAIN_NAME,
        mainFunIs :: Maybe [Char]
mainFunIs               = forall a. Maybe a
Nothing,
        reductionDepth :: IntWithInf
reductionDepth          = Int -> IntWithInf
treatZeroAsInf Int
mAX_REDUCTION_DEPTH,
        solverIterations :: IntWithInf
solverIterations        = Int -> IntWithInf
treatZeroAsInf Int
mAX_SOLVER_ITERATIONS,

        homeUnitId_ :: UnitId
homeUnitId_             = UnitId
mainUnitId,
        homeUnitInstanceOf_ :: Maybe UnitId
homeUnitInstanceOf_     = forall a. Maybe a
Nothing,
        homeUnitInstantiations_ :: [(ModuleName, Module)]
homeUnitInstantiations_ = [],

        objectDir :: Maybe [Char]
objectDir               = forall a. Maybe a
Nothing,
        dylibInstallName :: Maybe [Char]
dylibInstallName        = forall a. Maybe a
Nothing,
        hiDir :: Maybe [Char]
hiDir                   = forall a. Maybe a
Nothing,
        hieDir :: Maybe [Char]
hieDir                  = forall a. Maybe a
Nothing,
        stubDir :: Maybe [Char]
stubDir                 = forall a. Maybe a
Nothing,
        dumpDir :: Maybe [Char]
dumpDir                 = forall a. Maybe a
Nothing,

        objectSuf_ :: [Char]
objectSuf_              = Phase -> [Char]
phaseInputExt Phase
StopLn,
        hcSuf :: [Char]
hcSuf                   = Phase -> [Char]
phaseInputExt Phase
HCc,
        hiSuf_ :: [Char]
hiSuf_                  = [Char]
"hi",
        hieSuf :: [Char]
hieSuf                  = [Char]
"hie",

        dynamicTooFailed :: IORef Bool
dynamicTooFailed        = forall a. [Char] -> a
panic [Char]
"defaultDynFlags: No dynamicTooFailed",
        dynObjectSuf_ :: [Char]
dynObjectSuf_           = [Char]
"dyn_" forall a. [a] -> [a] -> [a]
++ Phase -> [Char]
phaseInputExt Phase
StopLn,
        dynHiSuf_ :: [Char]
dynHiSuf_               = [Char]
"dyn_hi",
        dynamicNow :: Bool
dynamicNow              = Bool
False,

        pluginModNames :: [ModuleName]
pluginModNames          = [],
        pluginModNameOpts :: [(ModuleName, [Char])]
pluginModNameOpts       = [],
        frontendPluginOpts :: [[Char]]
frontendPluginOpts      = [],

        outputFile_ :: Maybe [Char]
outputFile_             = forall a. Maybe a
Nothing,
        dynOutputFile_ :: Maybe [Char]
dynOutputFile_          = forall a. Maybe a
Nothing,
        outputHi :: Maybe [Char]
outputHi                = forall a. Maybe a
Nothing,
        dynOutputHi :: Maybe [Char]
dynOutputHi             = forall a. Maybe a
Nothing,
        dynLibLoader :: DynLibLoader
dynLibLoader            = DynLibLoader
SystemDependent,
        dumpPrefix :: Maybe [Char]
dumpPrefix              = forall a. Maybe a
Nothing,
        dumpPrefixForce :: Maybe [Char]
dumpPrefixForce         = forall a. Maybe a
Nothing,
        ldInputs :: [Option]
ldInputs                = [],
        includePaths :: IncludeSpecs
includePaths            = [[Char]] -> [[Char]] -> [[Char]] -> IncludeSpecs
IncludeSpecs [] [] [],
        libraryPaths :: [[Char]]
libraryPaths            = [],
        frameworkPaths :: [[Char]]
frameworkPaths          = [],
        cmdlineFrameworks :: [[Char]]
cmdlineFrameworks       = [],
        rtsOpts :: Maybe [Char]
rtsOpts                 = forall a. Maybe a
Nothing,
        rtsOptsEnabled :: RtsOptsEnabled
rtsOptsEnabled          = RtsOptsEnabled
RtsOptsSafeOnly,
        rtsOptsSuggestions :: Bool
rtsOptsSuggestions      = Bool
True,

        hpcDir :: [Char]
hpcDir                  = [Char]
".hpc",

        packageDBFlags :: [PackageDBFlag]
packageDBFlags          = [],
        packageFlags :: [PackageFlag]
packageFlags            = [],
        pluginPackageFlags :: [PackageFlag]
pluginPackageFlags      = [],
        ignorePackageFlags :: [IgnorePackageFlag]
ignorePackageFlags      = [],
        trustFlags :: [TrustFlag]
trustFlags              = [],
        packageEnv :: Maybe [Char]
packageEnv              = forall a. Maybe a
Nothing,
        targetWays_ :: Ways
targetWays_             = forall a. Set a
Set.empty,
        splitInfo :: Maybe ([Char], Int)
splitInfo               = forall a. Maybe a
Nothing,

        ghcNameVersion :: GhcNameVersion
ghcNameVersion = Settings -> GhcNameVersion
sGhcNameVersion Settings
mySettings,
        fileSettings :: FileSettings
fileSettings = Settings -> FileSettings
sFileSettings Settings
mySettings,
        toolSettings :: ToolSettings
toolSettings = Settings -> ToolSettings
sToolSettings Settings
mySettings,
        targetPlatform :: Platform
targetPlatform = Settings -> Platform
sTargetPlatform Settings
mySettings,
        platformMisc :: PlatformMisc
platformMisc = Settings -> PlatformMisc
sPlatformMisc Settings
mySettings,
        rawSettings :: [([Char], [Char])]
rawSettings = Settings -> [([Char], [Char])]
sRawSettings Settings
mySettings,

        -- See Note [LLVM configuration].
        llvmConfig :: LlvmConfig
llvmConfig              = LlvmConfig
llvmConfig,

        -- ghc -M values
        depMakefile :: [Char]
depMakefile       = [Char]
"Makefile",
        depIncludePkgDeps :: Bool
depIncludePkgDeps = Bool
False,
        depIncludeCppDeps :: Bool
depIncludeCppDeps = Bool
False,
        depExcludeMods :: [ModuleName]
depExcludeMods    = [],
        depSuffixes :: [[Char]]
depSuffixes       = [],
        -- end of ghc -M values
        ghcVersionFile :: Maybe [Char]
ghcVersionFile = forall a. Maybe a
Nothing,
        haddockOptions :: Maybe [Char]
haddockOptions = forall a. Maybe a
Nothing,
        dumpFlags :: EnumSet DumpFlag
dumpFlags = forall a. EnumSet a
EnumSet.empty,
        generalFlags :: EnumSet GeneralFlag
generalFlags = forall a. Enum a => [a] -> EnumSet a
EnumSet.fromList (Settings -> [GeneralFlag]
defaultFlags Settings
mySettings),
        warningFlags :: EnumSet WarningFlag
warningFlags = forall a. Enum a => [a] -> EnumSet a
EnumSet.fromList [WarningFlag]
standardWarnings,
        fatalWarningFlags :: EnumSet WarningFlag
fatalWarningFlags = forall a. EnumSet a
EnumSet.empty,
        ghciScripts :: [[Char]]
ghciScripts = [],
        language :: Maybe Language
language = forall a. Maybe a
Nothing,
        safeHaskell :: SafeHaskellMode
safeHaskell = SafeHaskellMode
Sf_None,
        safeInfer :: Bool
safeInfer   = Bool
True,
        safeInferred :: Bool
safeInferred = Bool
True,
        thOnLoc :: SrcSpan
thOnLoc = SrcSpan
noSrcSpan,
        newDerivOnLoc :: SrcSpan
newDerivOnLoc = SrcSpan
noSrcSpan,
        deriveViaOnLoc :: SrcSpan
deriveViaOnLoc = SrcSpan
noSrcSpan,
        overlapInstLoc :: SrcSpan
overlapInstLoc = SrcSpan
noSrcSpan,
        incoherentOnLoc :: SrcSpan
incoherentOnLoc = SrcSpan
noSrcSpan,
        pkgTrustOnLoc :: SrcSpan
pkgTrustOnLoc = SrcSpan
noSrcSpan,
        warnSafeOnLoc :: SrcSpan
warnSafeOnLoc = SrcSpan
noSrcSpan,
        warnUnsafeOnLoc :: SrcSpan
warnUnsafeOnLoc = SrcSpan
noSrcSpan,
        trustworthyOnLoc :: SrcSpan
trustworthyOnLoc = SrcSpan
noSrcSpan,
        extensions :: [OnOff Extension]
extensions = [],
        extensionFlags :: EnumSet Extension
extensionFlags = Maybe Language -> [OnOff Extension] -> EnumSet Extension
flattenExtensionFlags forall a. Maybe a
Nothing [],

        unfoldingOpts :: UnfoldingOpts
unfoldingOpts = UnfoldingOpts
defaultUnfoldingOpts,
        maxWorkerArgs :: Int
maxWorkerArgs = Int
10,

        ghciHistSize :: Int
ghciHistSize = Int
50, -- keep a log of length 50 by default

        flushOut :: FlushOut
flushOut = FlushOut
defaultFlushOut,
        flushErr :: FlushErr
flushErr = FlushErr
defaultFlushErr,
        pprUserLength :: Int
pprUserLength = Int
5,
        pprCols :: Int
pprCols = Int
100,
        useUnicode :: Bool
useUnicode = Bool
False,
        useColor :: OverridingBool
useColor = OverridingBool
Auto,
        canUseColor :: Bool
canUseColor = Bool
False,
        colScheme :: Scheme
colScheme = Scheme
Col.defaultScheme,
        profAuto :: ProfAuto
profAuto = ProfAuto
NoProfAuto,
        callerCcFilters :: [CallerCcFilter]
callerCcFilters = [],
        interactivePrint :: Maybe [Char]
interactivePrint = forall a. Maybe a
Nothing,
        nextWrapperNum :: IORef (ModuleEnv Int)
nextWrapperNum = forall a. [Char] -> a
panic [Char]
"defaultDynFlags: No nextWrapperNum",
        sseVersion :: Maybe SseVersion
sseVersion = forall a. Maybe a
Nothing,
        bmiVersion :: Maybe BmiVersion
bmiVersion = forall a. Maybe a
Nothing,
        avx :: Bool
avx = Bool
False,
        avx2 :: Bool
avx2 = Bool
False,
        avx512cd :: Bool
avx512cd = Bool
False,
        avx512er :: Bool
avx512er = Bool
False,
        avx512f :: Bool
avx512f = Bool
False,
        avx512pf :: Bool
avx512pf = Bool
False,
        rtldInfo :: IORef (Maybe LinkerInfo)
rtldInfo = forall a. [Char] -> a
panic [Char]
"defaultDynFlags: no rtldInfo",
        rtccInfo :: IORef (Maybe CompilerInfo)
rtccInfo = forall a. [Char] -> a
panic [Char]
"defaultDynFlags: no rtccInfo",

        maxInlineAllocSize :: Int
maxInlineAllocSize = Int
128,
        maxInlineMemcpyInsns :: Int
maxInlineMemcpyInsns = Int
32,
        maxInlineMemsetInsns :: Int
maxInlineMemsetInsns = Int
32,

        initialUnique :: Word
initialUnique = Word
0,
        uniqueIncrement :: Int
uniqueIncrement = Int
1,

        reverseErrors :: Bool
reverseErrors = Bool
False,
        maxErrors :: Maybe Int
maxErrors     = forall a. Maybe a
Nothing,
        cfgWeights :: Weights
cfgWeights    = Weights
defaultWeights
      }

type FatalMessager = String -> IO ()

defaultFatalMessager :: FatalMessager
defaultFatalMessager :: FatalMessager
defaultFatalMessager = Handle -> FatalMessager
hPutStrLn Handle
stderr


newtype FlushOut = FlushOut (IO ())

defaultFlushOut :: FlushOut
defaultFlushOut :: FlushOut
defaultFlushOut = IO () -> FlushOut
FlushOut forall a b. (a -> b) -> a -> b
$ Handle -> IO ()
hFlush Handle
stdout

newtype FlushErr = FlushErr (IO ())

defaultFlushErr :: FlushErr
defaultFlushErr :: FlushErr
defaultFlushErr = IO () -> FlushErr
FlushErr forall a b. (a -> b) -> a -> b
$ Handle -> IO ()
hFlush Handle
stderr

{-
Note [Verbosity levels]
~~~~~~~~~~~~~~~~~~~~~~~
    0   |   print errors & warnings only
    1   |   minimal verbosity: print "compiling M ... done." for each module.
    2   |   equivalent to -dshow-passes
    3   |   equivalent to existing "ghc -v"
    4   |   "ghc -v -ddump-most"
    5   |   "ghc -v -ddump-all"
-}

data OnOff a = On a
             | Off a
  deriving (OnOff a -> OnOff a -> Bool
forall a. Eq a => OnOff a -> OnOff a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OnOff a -> OnOff a -> Bool
$c/= :: forall a. Eq a => OnOff a -> OnOff a -> Bool
== :: OnOff a -> OnOff a -> Bool
$c== :: forall a. Eq a => OnOff a -> OnOff a -> Bool
Eq, Int -> OnOff a -> ShowS
forall a. Show a => Int -> OnOff a -> ShowS
forall a. Show a => [OnOff a] -> ShowS
forall a. Show a => OnOff a -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [OnOff a] -> ShowS
$cshowList :: forall a. Show a => [OnOff a] -> ShowS
show :: OnOff a -> [Char]
$cshow :: forall a. Show a => OnOff a -> [Char]
showsPrec :: Int -> OnOff a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> OnOff a -> ShowS
Show)

instance Outputable a => Outputable (OnOff a) where
  ppr :: OnOff a -> SDoc
ppr (On a
x)  = [Char] -> SDoc
text [Char]
"On" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr a
x
  ppr (Off a
x) = [Char] -> SDoc
text [Char]
"Off" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr a
x

-- OnOffs accumulate in reverse order, so we use foldr in order to
-- process them in the right order
flattenExtensionFlags :: Maybe Language -> [OnOff LangExt.Extension] -> EnumSet LangExt.Extension
flattenExtensionFlags :: Maybe Language -> [OnOff Extension] -> EnumSet Extension
flattenExtensionFlags Maybe Language
ml = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall {a}. Enum a => OnOff a -> EnumSet a -> EnumSet a
f EnumSet Extension
defaultExtensionFlags
    where f :: OnOff a -> EnumSet a -> EnumSet a
f (On a
f)  EnumSet a
flags = forall a. Enum a => a -> EnumSet a -> EnumSet a
EnumSet.insert a
f EnumSet a
flags
          f (Off a
f) EnumSet a
flags = forall a. Enum a => a -> EnumSet a -> EnumSet a
EnumSet.delete a
f EnumSet a
flags
          defaultExtensionFlags :: EnumSet Extension
defaultExtensionFlags = forall a. Enum a => [a] -> EnumSet a
EnumSet.fromList (Maybe Language -> [Extension]
languageExtensions Maybe Language
ml)

-- | The language extensions implied by the various language variants.
-- When updating this be sure to update the flag documentation in
-- @docs/users_guide/exts@.
languageExtensions :: Maybe Language -> [LangExt.Extension]

-- Nothing: the default case
languageExtensions :: Maybe Language -> [Extension]
languageExtensions Maybe Language
Nothing = Maybe Language -> [Extension]
languageExtensions (forall a. a -> Maybe a
Just Language
GHC2021)

languageExtensions (Just Language
Haskell98)
    = [Extension
LangExt.ImplicitPrelude,
       -- See Note [When is StarIsType enabled]
       Extension
LangExt.StarIsType,
       Extension
LangExt.CUSKs,
       Extension
LangExt.MonomorphismRestriction,
       Extension
LangExt.NPlusKPatterns,
       Extension
LangExt.DatatypeContexts,
       Extension
LangExt.TraditionalRecordSyntax,
       Extension
LangExt.FieldSelectors,
       Extension
LangExt.NondecreasingIndentation,
           -- strictly speaking non-standard, but we always had this
           -- on implicitly before the option was added in 7.1, and
           -- turning it off breaks code, so we're keeping it on for
           -- backwards compatibility.  Cabal uses -XHaskell98 by
           -- default unless you specify another language.
       Extension
LangExt.DeepSubsumption
       -- Non-standard but enabled for backwards compatability (see GHC proposal #511)
      ]

languageExtensions (Just Language
Haskell2010)
    = [Extension
LangExt.ImplicitPrelude,
       -- See Note [When is StarIsType enabled]
       Extension
LangExt.StarIsType,
       Extension
LangExt.CUSKs,
       Extension
LangExt.MonomorphismRestriction,
       Extension
LangExt.DatatypeContexts,
       Extension
LangExt.TraditionalRecordSyntax,
       Extension
LangExt.EmptyDataDecls,
       Extension
LangExt.ForeignFunctionInterface,
       Extension
LangExt.PatternGuards,
       Extension
LangExt.DoAndIfThenElse,
       Extension
LangExt.FieldSelectors,
       Extension
LangExt.RelaxedPolyRec,
       Extension
LangExt.DeepSubsumption ]

languageExtensions (Just Language
GHC2021)
    = [Extension
LangExt.ImplicitPrelude,
       -- See Note [When is StarIsType enabled]
       Extension
LangExt.StarIsType,
       Extension
LangExt.MonomorphismRestriction,
       Extension
LangExt.TraditionalRecordSyntax,
       Extension
LangExt.EmptyDataDecls,
       Extension
LangExt.ForeignFunctionInterface,
       Extension
LangExt.PatternGuards,
       Extension
LangExt.DoAndIfThenElse,
       Extension
LangExt.FieldSelectors,
       Extension
LangExt.RelaxedPolyRec,
       -- Now the new extensions (not in Haskell2010)
       Extension
LangExt.BangPatterns,
       Extension
LangExt.BinaryLiterals,
       Extension
LangExt.ConstrainedClassMethods,
       Extension
LangExt.ConstraintKinds,
       Extension
LangExt.DeriveDataTypeable,
       Extension
LangExt.DeriveFoldable,
       Extension
LangExt.DeriveFunctor,
       Extension
LangExt.DeriveGeneric,
       Extension
LangExt.DeriveLift,
       Extension
LangExt.DeriveTraversable,
       Extension
LangExt.EmptyCase,
       Extension
LangExt.EmptyDataDeriving,
       Extension
LangExt.ExistentialQuantification,
       Extension
LangExt.ExplicitForAll,
       Extension
LangExt.FlexibleContexts,
       Extension
LangExt.FlexibleInstances,
       Extension
LangExt.GADTSyntax,
       Extension
LangExt.GeneralizedNewtypeDeriving,
       Extension
LangExt.HexFloatLiterals,
       Extension
LangExt.ImportQualifiedPost,
       Extension
LangExt.InstanceSigs,
       Extension
LangExt.KindSignatures,
       Extension
LangExt.MultiParamTypeClasses,
       Extension
LangExt.RecordPuns,
       Extension
LangExt.NamedWildCards,
       Extension
LangExt.NumericUnderscores,
       Extension
LangExt.PolyKinds,
       Extension
LangExt.PostfixOperators,
       Extension
LangExt.RankNTypes,
       Extension
LangExt.ScopedTypeVariables,
       Extension
LangExt.StandaloneDeriving,
       Extension
LangExt.StandaloneKindSignatures,
       Extension
LangExt.TupleSections,
       Extension
LangExt.TypeApplications,
       Extension
LangExt.TypeOperators,
       Extension
LangExt.TypeSynonymInstances]

hasPprDebug :: DynFlags -> Bool
hasPprDebug :: DynFlags -> Bool
hasPprDebug = DumpFlag -> DynFlags -> Bool
dopt DumpFlag
Opt_D_ppr_debug

hasNoDebugOutput :: DynFlags -> Bool
hasNoDebugOutput :: DynFlags -> Bool
hasNoDebugOutput = DumpFlag -> DynFlags -> Bool
dopt DumpFlag
Opt_D_no_debug_output

hasNoStateHack :: DynFlags -> Bool
hasNoStateHack :: DynFlags -> Bool
hasNoStateHack = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_G_NoStateHack

hasNoOptCoercion :: DynFlags -> Bool
hasNoOptCoercion :: DynFlags -> Bool
hasNoOptCoercion = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_G_NoOptCoercion


-- | Test whether a 'DumpFlag' is set
dopt :: DumpFlag -> DynFlags -> Bool
dopt :: DumpFlag -> DynFlags -> Bool
dopt DumpFlag
f DynFlags
dflags = (DumpFlag
f forall a. Enum a => a -> EnumSet a -> Bool
`EnumSet.member` DynFlags -> EnumSet DumpFlag
dumpFlags DynFlags
dflags)
             Bool -> Bool -> Bool
|| (DynFlags -> Int
verbosity DynFlags
dflags forall a. Ord a => a -> a -> Bool
>= Int
4 Bool -> Bool -> Bool
&& DumpFlag -> Bool
enableIfVerbose DumpFlag
f)
    where enableIfVerbose :: DumpFlag -> Bool
enableIfVerbose DumpFlag
Opt_D_dump_tc_trace               = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_rn_trace               = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_cs_trace               = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_if_trace               = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_vt_trace               = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_tc                     = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_rn                     = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_rn_stats               = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_hi_diffs               = Bool
False
          enableIfVerbose DumpFlag
Opt_D_verbose_core2core           = Bool
False
          enableIfVerbose DumpFlag
Opt_D_verbose_stg2stg             = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_splices                = Bool
False
          enableIfVerbose DumpFlag
Opt_D_th_dec_file                 = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_rule_firings           = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_rule_rewrites          = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_simpl_trace            = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_rtti                   = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_inlinings              = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_core_stats             = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_asm_stats              = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_types                  = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_simpl_iterations       = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_ticked                 = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_view_pattern_commoning = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_mod_cycles             = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_mod_map                = Bool
False
          enableIfVerbose DumpFlag
Opt_D_dump_ec_trace               = Bool
False
          enableIfVerbose DumpFlag
_                                 = Bool
True

-- | Set a 'DumpFlag'
dopt_set :: DynFlags -> DumpFlag -> DynFlags
dopt_set :: DynFlags -> DumpFlag -> DynFlags
dopt_set DynFlags
dfs DumpFlag
f = DynFlags
dfs{ dumpFlags :: EnumSet DumpFlag
dumpFlags = forall a. Enum a => a -> EnumSet a -> EnumSet a
EnumSet.insert DumpFlag
f (DynFlags -> EnumSet DumpFlag
dumpFlags DynFlags
dfs) }

-- | Unset a 'DumpFlag'
dopt_unset :: DynFlags -> DumpFlag -> DynFlags
dopt_unset :: DynFlags -> DumpFlag -> DynFlags
dopt_unset DynFlags
dfs DumpFlag
f = DynFlags
dfs{ dumpFlags :: EnumSet DumpFlag
dumpFlags = forall a. Enum a => a -> EnumSet a -> EnumSet a
EnumSet.delete DumpFlag
f (DynFlags -> EnumSet DumpFlag
dumpFlags DynFlags
dfs) }

-- | Test whether a 'GeneralFlag' is set
--
-- Note that `dynamicNow` (i.e., dynamic objects built with `-dynamic-too`)
-- always implicitly enables Opt_PIC, Opt_ExternalDynamicRefs, and disables
-- Opt_SplitSections.
--
gopt :: GeneralFlag -> DynFlags -> Bool
gopt :: GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_PIC DynFlags
dflags
   | DynFlags -> Bool
dynamicNow DynFlags
dflags = Bool
True
gopt GeneralFlag
Opt_ExternalDynamicRefs DynFlags
dflags
   | DynFlags -> Bool
dynamicNow DynFlags
dflags = Bool
True
gopt GeneralFlag
Opt_SplitSections DynFlags
dflags
   | DynFlags -> Bool
dynamicNow DynFlags
dflags = Bool
False
gopt GeneralFlag
f DynFlags
dflags = GeneralFlag
f forall a. Enum a => a -> EnumSet a -> Bool
`EnumSet.member` DynFlags -> EnumSet GeneralFlag
generalFlags DynFlags
dflags

-- | Set a 'GeneralFlag'
gopt_set :: DynFlags -> GeneralFlag -> DynFlags
gopt_set :: DynFlags -> GeneralFlag -> DynFlags
gopt_set DynFlags
dfs GeneralFlag
f = DynFlags
dfs{ generalFlags :: EnumSet GeneralFlag
generalFlags = forall a. Enum a => a -> EnumSet a -> EnumSet a
EnumSet.insert GeneralFlag
f (DynFlags -> EnumSet GeneralFlag
generalFlags DynFlags
dfs) }

-- | Unset a 'GeneralFlag'
gopt_unset :: DynFlags -> GeneralFlag -> DynFlags
gopt_unset :: DynFlags -> GeneralFlag -> DynFlags
gopt_unset DynFlags
dfs GeneralFlag
f = DynFlags
dfs{ generalFlags :: EnumSet GeneralFlag
generalFlags = forall a. Enum a => a -> EnumSet a -> EnumSet a
EnumSet.delete GeneralFlag
f (DynFlags -> EnumSet GeneralFlag
generalFlags DynFlags
dfs) }

-- | Test whether a 'WarningFlag' is set
wopt :: WarningFlag -> DynFlags -> Bool
wopt :: WarningFlag -> DynFlags -> Bool
wopt WarningFlag
f DynFlags
dflags  = WarningFlag
f forall a. Enum a => a -> EnumSet a -> Bool
`EnumSet.member` DynFlags -> EnumSet WarningFlag
warningFlags DynFlags
dflags

-- | Set a 'WarningFlag'
wopt_set :: DynFlags -> WarningFlag -> DynFlags
wopt_set :: DynFlags -> WarningFlag -> DynFlags
wopt_set DynFlags
dfs WarningFlag
f = DynFlags
dfs{ warningFlags :: EnumSet WarningFlag
warningFlags = forall a. Enum a => a -> EnumSet a -> EnumSet a
EnumSet.insert WarningFlag
f (DynFlags -> EnumSet WarningFlag
warningFlags DynFlags
dfs) }

-- | Unset a 'WarningFlag'
wopt_unset :: DynFlags -> WarningFlag -> DynFlags
wopt_unset :: DynFlags -> WarningFlag -> DynFlags
wopt_unset DynFlags
dfs WarningFlag
f = DynFlags
dfs{ warningFlags :: EnumSet WarningFlag
warningFlags = forall a. Enum a => a -> EnumSet a -> EnumSet a
EnumSet.delete WarningFlag
f (DynFlags -> EnumSet WarningFlag
warningFlags DynFlags
dfs) }

-- | Test whether a 'WarningFlag' is set as fatal
wopt_fatal :: WarningFlag -> DynFlags -> Bool
wopt_fatal :: WarningFlag -> DynFlags -> Bool
wopt_fatal WarningFlag
f DynFlags
dflags = WarningFlag
f forall a. Enum a => a -> EnumSet a -> Bool
`EnumSet.member` DynFlags -> EnumSet WarningFlag
fatalWarningFlags DynFlags
dflags

-- | Mark a 'WarningFlag' as fatal (do not set the flag)
wopt_set_fatal :: DynFlags -> WarningFlag -> DynFlags
wopt_set_fatal :: DynFlags -> WarningFlag -> DynFlags
wopt_set_fatal DynFlags
dfs WarningFlag
f
    = DynFlags
dfs { fatalWarningFlags :: EnumSet WarningFlag
fatalWarningFlags = forall a. Enum a => a -> EnumSet a -> EnumSet a
EnumSet.insert WarningFlag
f (DynFlags -> EnumSet WarningFlag
fatalWarningFlags DynFlags
dfs) }

-- | Mark a 'WarningFlag' as not fatal
wopt_unset_fatal :: DynFlags -> WarningFlag -> DynFlags
wopt_unset_fatal :: DynFlags -> WarningFlag -> DynFlags
wopt_unset_fatal DynFlags
dfs WarningFlag
f
    = DynFlags
dfs { fatalWarningFlags :: EnumSet WarningFlag
fatalWarningFlags = forall a. Enum a => a -> EnumSet a -> EnumSet a
EnumSet.delete WarningFlag
f (DynFlags -> EnumSet WarningFlag
fatalWarningFlags DynFlags
dfs) }

-- | Test whether a 'LangExt.Extension' is set
xopt :: LangExt.Extension -> DynFlags -> Bool
xopt :: Extension -> DynFlags -> Bool
xopt Extension
f DynFlags
dflags = Extension
f forall a. Enum a => a -> EnumSet a -> Bool
`EnumSet.member` DynFlags -> EnumSet Extension
extensionFlags DynFlags
dflags

-- | Set a 'LangExt.Extension'
xopt_set :: DynFlags -> LangExt.Extension -> DynFlags
xopt_set :: DynFlags -> Extension -> DynFlags
xopt_set DynFlags
dfs Extension
f
    = let onoffs :: [OnOff Extension]
onoffs = forall a. a -> OnOff a
On Extension
f forall a. a -> [a] -> [a]
: DynFlags -> [OnOff Extension]
extensions DynFlags
dfs
      in DynFlags
dfs { extensions :: [OnOff Extension]
extensions = [OnOff Extension]
onoffs,
               extensionFlags :: EnumSet Extension
extensionFlags = Maybe Language -> [OnOff Extension] -> EnumSet Extension
flattenExtensionFlags (DynFlags -> Maybe Language
language DynFlags
dfs) [OnOff Extension]
onoffs }

-- | Unset a 'LangExt.Extension'
xopt_unset :: DynFlags -> LangExt.Extension -> DynFlags
xopt_unset :: DynFlags -> Extension -> DynFlags
xopt_unset DynFlags
dfs Extension
f
    = let onoffs :: [OnOff Extension]
onoffs = forall a. a -> OnOff a
Off Extension
f forall a. a -> [a] -> [a]
: DynFlags -> [OnOff Extension]
extensions DynFlags
dfs
      in DynFlags
dfs { extensions :: [OnOff Extension]
extensions = [OnOff Extension]
onoffs,
               extensionFlags :: EnumSet Extension
extensionFlags = Maybe Language -> [OnOff Extension] -> EnumSet Extension
flattenExtensionFlags (DynFlags -> Maybe Language
language DynFlags
dfs) [OnOff Extension]
onoffs }

-- | Set or unset a 'LangExt.Extension', unless it has been explicitly
--   set or unset before.
xopt_set_unlessExplSpec
        :: LangExt.Extension
        -> (DynFlags -> LangExt.Extension -> DynFlags)
        -> DynFlags -> DynFlags
xopt_set_unlessExplSpec :: Extension
-> (DynFlags -> Extension -> DynFlags) -> DynFlags -> DynFlags
xopt_set_unlessExplSpec Extension
ext DynFlags -> Extension -> DynFlags
setUnset DynFlags
dflags =
    let referedExts :: [Extension]
referedExts = forall {a}. OnOff a -> a
stripOnOff forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DynFlags -> [OnOff Extension]
extensions DynFlags
dflags
        stripOnOff :: OnOff a -> a
stripOnOff (On a
x)  = a
x
        stripOnOff (Off a
x) = a
x
    in
        if Extension
ext forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Extension]
referedExts then DynFlags
dflags else DynFlags -> Extension -> DynFlags
setUnset DynFlags
dflags Extension
ext

xopt_DuplicateRecordFields :: DynFlags -> FieldLabel.DuplicateRecordFields
xopt_DuplicateRecordFields :: DynFlags -> DuplicateRecordFields
xopt_DuplicateRecordFields DynFlags
dfs
  | Extension -> DynFlags -> Bool
xopt Extension
LangExt.DuplicateRecordFields DynFlags
dfs = DuplicateRecordFields
FieldLabel.DuplicateRecordFields
  | Bool
otherwise                              = DuplicateRecordFields
FieldLabel.NoDuplicateRecordFields

xopt_FieldSelectors :: DynFlags -> FieldLabel.FieldSelectors
xopt_FieldSelectors :: DynFlags -> FieldSelectors
xopt_FieldSelectors DynFlags
dfs
  | Extension -> DynFlags -> Bool
xopt Extension
LangExt.FieldSelectors DynFlags
dfs = FieldSelectors
FieldLabel.FieldSelectors
  | Bool
otherwise                       = FieldSelectors
FieldLabel.NoFieldSelectors

lang_set :: DynFlags -> Maybe Language -> DynFlags
lang_set :: DynFlags -> Maybe Language -> DynFlags
lang_set DynFlags
dflags Maybe Language
lang =
   DynFlags
dflags {
            language :: Maybe Language
language = Maybe Language
lang,
            extensionFlags :: EnumSet Extension
extensionFlags = Maybe Language -> [OnOff Extension] -> EnumSet Extension
flattenExtensionFlags Maybe Language
lang (DynFlags -> [OnOff Extension]
extensions DynFlags
dflags)
          }

-- | Set the Haskell language standard to use
setLanguage :: Language -> DynP ()
setLanguage :: Language -> DynP ()
setLanguage Language
l = (DynFlags -> DynFlags) -> DynP ()
upd (DynFlags -> Maybe Language -> DynFlags
`lang_set` forall a. a -> Maybe a
Just Language
l)

-- | Some modules have dependencies on others through the DynFlags rather than textual imports
dynFlagDependencies :: DynFlags -> [ModuleName]
dynFlagDependencies :: DynFlags -> [ModuleName]
dynFlagDependencies = DynFlags -> [ModuleName]
pluginModNames

-- | Is the -fpackage-trust mode on
packageTrustOn :: DynFlags -> Bool
packageTrustOn :: DynFlags -> Bool
packageTrustOn = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_PackageTrust

-- | Is Safe Haskell on in some way (including inference mode)
safeHaskellOn :: DynFlags -> Bool
safeHaskellOn :: DynFlags -> Bool
safeHaskellOn DynFlags
dflags = DynFlags -> Bool
safeHaskellModeEnabled DynFlags
dflags Bool -> Bool -> Bool
|| DynFlags -> Bool
safeInferOn DynFlags
dflags

safeHaskellModeEnabled :: DynFlags -> Bool
safeHaskellModeEnabled :: DynFlags -> Bool
safeHaskellModeEnabled DynFlags
dflags = DynFlags -> SafeHaskellMode
safeHaskell DynFlags
dflags forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [SafeHaskellMode
Sf_Unsafe, SafeHaskellMode
Sf_Trustworthy
                                                   , SafeHaskellMode
Sf_Safe ]


-- | Is the Safe Haskell safe language in use
safeLanguageOn :: DynFlags -> Bool
safeLanguageOn :: DynFlags -> Bool
safeLanguageOn DynFlags
dflags = DynFlags -> SafeHaskellMode
safeHaskell DynFlags
dflags forall a. Eq a => a -> a -> Bool
== SafeHaskellMode
Sf_Safe

-- | Is the Safe Haskell safe inference mode active
safeInferOn :: DynFlags -> Bool
safeInferOn :: DynFlags -> Bool
safeInferOn = DynFlags -> Bool
safeInfer

-- | Test if Safe Imports are on in some form
safeImportsOn :: DynFlags -> Bool
safeImportsOn :: DynFlags -> Bool
safeImportsOn DynFlags
dflags = DynFlags -> SafeHaskellMode
safeHaskell DynFlags
dflags forall a. Eq a => a -> a -> Bool
== SafeHaskellMode
Sf_Unsafe Bool -> Bool -> Bool
||
                       DynFlags -> SafeHaskellMode
safeHaskell DynFlags
dflags forall a. Eq a => a -> a -> Bool
== SafeHaskellMode
Sf_Trustworthy Bool -> Bool -> Bool
||
                       DynFlags -> SafeHaskellMode
safeHaskell DynFlags
dflags forall a. Eq a => a -> a -> Bool
== SafeHaskellMode
Sf_Safe

-- | Set a 'Safe Haskell' flag
setSafeHaskell :: SafeHaskellMode -> DynP ()
setSafeHaskell :: SafeHaskellMode -> DynP ()
setSafeHaskell SafeHaskellMode
s = (DynFlags -> DynP DynFlags) -> DynP ()
updM DynFlags -> DynP DynFlags
f
    where f :: DynFlags -> DynP DynFlags
f DynFlags
dfs = do
              let sf :: SafeHaskellMode
sf = DynFlags -> SafeHaskellMode
safeHaskell DynFlags
dfs
              SafeHaskellMode
safeM <- SafeHaskellMode -> SafeHaskellMode -> DynP SafeHaskellMode
combineSafeFlags SafeHaskellMode
sf SafeHaskellMode
s
              case SafeHaskellMode
s of
                SafeHaskellMode
Sf_Safe -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ DynFlags
dfs { safeHaskell :: SafeHaskellMode
safeHaskell = SafeHaskellMode
safeM, safeInfer :: Bool
safeInfer = Bool
False }
                -- leave safe inferrence on in Trustworthy mode so we can warn
                -- if it could have been inferred safe.
                SafeHaskellMode
Sf_Trustworthy -> do
                  SrcSpan
l <- forall (m :: * -> *). Monad m => EwM m SrcSpan
getCurLoc
                  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ DynFlags
dfs { safeHaskell :: SafeHaskellMode
safeHaskell = SafeHaskellMode
safeM, trustworthyOnLoc :: SrcSpan
trustworthyOnLoc = SrcSpan
l }
                -- leave safe inference on in Unsafe mode as well.
                SafeHaskellMode
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ DynFlags
dfs { safeHaskell :: SafeHaskellMode
safeHaskell = SafeHaskellMode
safeM }

-- | Are all direct imports required to be safe for this Safe Haskell mode?
-- Direct imports are when the code explicitly imports a module
safeDirectImpsReq :: DynFlags -> Bool
safeDirectImpsReq :: DynFlags -> Bool
safeDirectImpsReq DynFlags
d = DynFlags -> Bool
safeLanguageOn DynFlags
d

-- | Are all implicit imports required to be safe for this Safe Haskell mode?
-- Implicit imports are things in the prelude. e.g System.IO when print is used.
safeImplicitImpsReq :: DynFlags -> Bool
safeImplicitImpsReq :: DynFlags -> Bool
safeImplicitImpsReq DynFlags
d = DynFlags -> Bool
safeLanguageOn DynFlags
d

-- | Combine two Safe Haskell modes correctly. Used for dealing with multiple flags.
-- This makes Safe Haskell very much a monoid but for now I prefer this as I don't
-- want to export this functionality from the module but do want to export the
-- type constructors.
combineSafeFlags :: SafeHaskellMode -> SafeHaskellMode -> DynP SafeHaskellMode
combineSafeFlags :: SafeHaskellMode -> SafeHaskellMode -> DynP SafeHaskellMode
combineSafeFlags SafeHaskellMode
a SafeHaskellMode
b | SafeHaskellMode
a forall a. Eq a => a -> a -> Bool
== SafeHaskellMode
Sf_None         = forall (m :: * -> *) a. Monad m => a -> m a
return SafeHaskellMode
b
                     | SafeHaskellMode
b forall a. Eq a => a -> a -> Bool
== SafeHaskellMode
Sf_None         = forall (m :: * -> *) a. Monad m => a -> m a
return SafeHaskellMode
a
                     | SafeHaskellMode
a forall a. Eq a => a -> a -> Bool
== SafeHaskellMode
Sf_Ignore Bool -> Bool -> Bool
|| SafeHaskellMode
b forall a. Eq a => a -> a -> Bool
== SafeHaskellMode
Sf_Ignore = forall (m :: * -> *) a. Monad m => a -> m a
return SafeHaskellMode
Sf_Ignore
                     | SafeHaskellMode
a forall a. Eq a => a -> a -> Bool
== SafeHaskellMode
b               = forall (m :: * -> *) a. Monad m => a -> m a
return SafeHaskellMode
a
                     | Bool
otherwise            = forall (m :: * -> *). Monad m => [Char] -> EwM m ()
addErr [Char]
errm forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (f :: * -> *) a. Applicative f => a -> f a
pure SafeHaskellMode
a
    where errm :: [Char]
errm = [Char]
"Incompatible Safe Haskell flags! ("
                    forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show SafeHaskellMode
a forall a. [a] -> [a] -> [a]
++ [Char]
", " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show SafeHaskellMode
b forall a. [a] -> [a] -> [a]
++ [Char]
")"

-- | A list of unsafe flags under Safe Haskell. Tuple elements are:
--     * name of the flag
--     * function to get srcspan that enabled the flag
--     * function to test if the flag is on
--     * function to turn the flag off
unsafeFlags, unsafeFlagsForInfer
  :: [(String, DynFlags -> SrcSpan, DynFlags -> Bool, DynFlags -> DynFlags)]
unsafeFlags :: [([Char], DynFlags -> SrcSpan, DynFlags -> Bool,
  DynFlags -> DynFlags)]
unsafeFlags = [ ([Char]
"-XGeneralizedNewtypeDeriving", DynFlags -> SrcSpan
newDerivOnLoc,
                    Extension -> DynFlags -> Bool
xopt Extension
LangExt.GeneralizedNewtypeDeriving,
                    forall a b c. (a -> b -> c) -> b -> a -> c
flip DynFlags -> Extension -> DynFlags
xopt_unset Extension
LangExt.GeneralizedNewtypeDeriving)
              , ([Char]
"-XDerivingVia", DynFlags -> SrcSpan
deriveViaOnLoc,
                    Extension -> DynFlags -> Bool
xopt Extension
LangExt.DerivingVia,
                    forall a b c. (a -> b -> c) -> b -> a -> c
flip DynFlags -> Extension -> DynFlags
xopt_unset Extension
LangExt.DerivingVia)
              , ([Char]
"-XTemplateHaskell", DynFlags -> SrcSpan
thOnLoc,
                    Extension -> DynFlags -> Bool
xopt Extension
LangExt.TemplateHaskell,
                    forall a b c. (a -> b -> c) -> b -> a -> c
flip DynFlags -> Extension -> DynFlags
xopt_unset Extension
LangExt.TemplateHaskell)
              ]
unsafeFlagsForInfer :: [([Char], DynFlags -> SrcSpan, DynFlags -> Bool,
  DynFlags -> DynFlags)]
unsafeFlagsForInfer = [([Char], DynFlags -> SrcSpan, DynFlags -> Bool,
  DynFlags -> DynFlags)]
unsafeFlags


-- | Retrieve the options corresponding to a particular @opt_*@ field in the correct order
getOpts :: DynFlags             -- ^ 'DynFlags' to retrieve the options from
        -> (DynFlags -> [a])    -- ^ Relevant record accessor: one of the @opt_*@ accessors
        -> [a]                  -- ^ Correctly ordered extracted options
getOpts :: forall a. DynFlags -> (DynFlags -> [a]) -> [a]
getOpts DynFlags
dflags DynFlags -> [a]
opts = forall a. [a] -> [a]
reverse (DynFlags -> [a]
opts DynFlags
dflags)
        -- We add to the options from the front, so we need to reverse the list

-- | Gets the verbosity flag for the current verbosity level. This is fed to
-- other tools, so GHC-specific verbosity flags like @-ddump-most@ are not included
getVerbFlags :: DynFlags -> [String]
getVerbFlags :: DynFlags -> [[Char]]
getVerbFlags DynFlags
dflags
  | DynFlags -> Int
verbosity DynFlags
dflags forall a. Ord a => a -> a -> Bool
>= Int
4 = [[Char]
"-v"]
  | Bool
otherwise             = []

setObjectDir, setHiDir, setHieDir, setStubDir, setDumpDir, setOutputDir,
         setDynObjectSuf, setDynHiSuf,
         setDylibInstallName,
         setObjectSuf, setHiSuf, setHieSuf, setHcSuf, parseDynLibLoaderMode,
         setPgmP, addOptl, addOptc, addOptcxx, addOptP,
         addCmdlineFramework, addHaddockOpts, addGhciScript,
         setInteractivePrint
   :: String -> DynFlags -> DynFlags
setOutputFile, setDynOutputFile, setOutputHi, setDynOutputHi, setDumpPrefixForce
   :: Maybe String -> DynFlags -> DynFlags

setObjectDir :: [Char] -> DynFlags -> DynFlags
setObjectDir  [Char]
f DynFlags
d = DynFlags
d { objectDir :: Maybe [Char]
objectDir  = forall a. a -> Maybe a
Just [Char]
f}
setHiDir :: [Char] -> DynFlags -> DynFlags
setHiDir      [Char]
f DynFlags
d = DynFlags
d { hiDir :: Maybe [Char]
hiDir      = forall a. a -> Maybe a
Just [Char]
f}
setHieDir :: [Char] -> DynFlags -> DynFlags
setHieDir     [Char]
f DynFlags
d = DynFlags
d { hieDir :: Maybe [Char]
hieDir     = forall a. a -> Maybe a
Just [Char]
f}
setStubDir :: [Char] -> DynFlags -> DynFlags
setStubDir    [Char]
f DynFlags
d = DynFlags
d { stubDir :: Maybe [Char]
stubDir    = forall a. a -> Maybe a
Just [Char]
f
                      , includePaths :: IncludeSpecs
includePaths = IncludeSpecs -> [[Char]] -> IncludeSpecs
addGlobalInclude (DynFlags -> IncludeSpecs
includePaths DynFlags
d) [[Char]
f] }
  -- -stubdir D adds an implicit -I D, so that gcc can find the _stub.h file
  -- \#included from the .hc file when compiling via C (i.e. unregisterised
  -- builds).
setDumpDir :: [Char] -> DynFlags -> DynFlags
setDumpDir    [Char]
f DynFlags
d = DynFlags
d { dumpDir :: Maybe [Char]
dumpDir    = forall a. a -> Maybe a
Just [Char]
f}
setOutputDir :: [Char] -> DynFlags -> DynFlags
setOutputDir  [Char]
f = [Char] -> DynFlags -> DynFlags
setObjectDir [Char]
f
                forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> DynFlags -> DynFlags
setHieDir [Char]
f
                forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> DynFlags -> DynFlags
setHiDir [Char]
f
                forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> DynFlags -> DynFlags
setStubDir [Char]
f
                forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> DynFlags -> DynFlags
setDumpDir [Char]
f
setDylibInstallName :: [Char] -> DynFlags -> DynFlags
setDylibInstallName  [Char]
f DynFlags
d = DynFlags
d { dylibInstallName :: Maybe [Char]
dylibInstallName = forall a. a -> Maybe a
Just [Char]
f}

setObjectSuf :: [Char] -> DynFlags -> DynFlags
setObjectSuf    [Char]
f DynFlags
d = DynFlags
d { objectSuf_ :: [Char]
objectSuf_    = [Char]
f}
setDynObjectSuf :: [Char] -> DynFlags -> DynFlags
setDynObjectSuf [Char]
f DynFlags
d = DynFlags
d { dynObjectSuf_ :: [Char]
dynObjectSuf_ = [Char]
f}
setHiSuf :: [Char] -> DynFlags -> DynFlags
setHiSuf        [Char]
f DynFlags
d = DynFlags
d { hiSuf_ :: [Char]
hiSuf_        = [Char]
f}
setHieSuf :: [Char] -> DynFlags -> DynFlags
setHieSuf       [Char]
f DynFlags
d = DynFlags
d { hieSuf :: [Char]
hieSuf        = [Char]
f}
setDynHiSuf :: [Char] -> DynFlags -> DynFlags
setDynHiSuf     [Char]
f DynFlags
d = DynFlags
d { dynHiSuf_ :: [Char]
dynHiSuf_     = [Char]
f}
setHcSuf :: [Char] -> DynFlags -> DynFlags
setHcSuf        [Char]
f DynFlags
d = DynFlags
d { hcSuf :: [Char]
hcSuf         = [Char]
f}

setOutputFile :: Maybe [Char] -> DynFlags -> DynFlags
setOutputFile    Maybe [Char]
f DynFlags
d = DynFlags
d { outputFile_ :: Maybe [Char]
outputFile_    = Maybe [Char]
f}
setDynOutputFile :: Maybe [Char] -> DynFlags -> DynFlags
setDynOutputFile Maybe [Char]
f DynFlags
d = DynFlags
d { dynOutputFile_ :: Maybe [Char]
dynOutputFile_ = Maybe [Char]
f}
setOutputHi :: Maybe [Char] -> DynFlags -> DynFlags
setOutputHi      Maybe [Char]
f DynFlags
d = DynFlags
d { outputHi :: Maybe [Char]
outputHi       = Maybe [Char]
f}
setDynOutputHi :: Maybe [Char] -> DynFlags -> DynFlags
setDynOutputHi   Maybe [Char]
f DynFlags
d = DynFlags
d { dynOutputHi :: Maybe [Char]
dynOutputHi    = Maybe [Char]
f}

parseUnitInsts :: String -> Instantiations
parseUnitInsts :: [Char] -> [(ModuleName, Module)]
parseUnitInsts [Char]
str = case forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Eq a => a -> a -> Bool
==[Char]
"")forall b c a. (b -> c) -> (a -> b) -> a -> c
.forall a b. (a, b) -> b
snd) (forall a. ReadP a -> ReadS a
readP_to_S ReadP [(ModuleName, Module)]
parse [Char]
str) of
    [([(ModuleName, Module)]
r, [Char]
"")] -> [(ModuleName, Module)]
r
    [([(ModuleName, Module)], [Char])]
_ -> forall a. GhcException -> a
throwGhcException forall a b. (a -> b) -> a -> b
$ [Char] -> GhcException
CmdLineError ([Char]
"Can't parse -instantiated-with: " forall a. [a] -> [a] -> [a]
++ [Char]
str)
  where parse :: ReadP [(ModuleName, Module)]
parse = forall a sep. ReadP a -> ReadP sep -> ReadP [a]
sepBy ReadP (ModuleName, Module)
parseEntry (Char -> ReadP Char
R.char Char
',')
        parseEntry :: ReadP (ModuleName, Module)
parseEntry = do
            ModuleName
n <- ReadP ModuleName
parseModuleName
            Char
_ <- Char -> ReadP Char
R.char Char
'='
            Module
m <- ReadP Module
parseHoleyModule
            forall (m :: * -> *) a. Monad m => a -> m a
return (ModuleName
n, Module
m)

setUnitInstantiations :: String -> DynFlags -> DynFlags
setUnitInstantiations :: [Char] -> DynFlags -> DynFlags
setUnitInstantiations [Char]
s DynFlags
d =
    DynFlags
d { homeUnitInstantiations_ :: [(ModuleName, Module)]
homeUnitInstantiations_ = [Char] -> [(ModuleName, Module)]
parseUnitInsts [Char]
s }

setUnitInstanceOf :: String -> DynFlags -> DynFlags
setUnitInstanceOf :: [Char] -> DynFlags -> DynFlags
setUnitInstanceOf [Char]
s DynFlags
d =
    DynFlags
d { homeUnitInstanceOf_ :: Maybe UnitId
homeUnitInstanceOf_ = forall a. a -> Maybe a
Just (FastString -> UnitId
UnitId ([Char] -> FastString
fsLit [Char]
s)) }

addPluginModuleName :: String -> DynFlags -> DynFlags
addPluginModuleName :: [Char] -> DynFlags -> DynFlags
addPluginModuleName [Char]
name DynFlags
d = DynFlags
d { pluginModNames :: [ModuleName]
pluginModNames = ([Char] -> ModuleName
mkModuleName [Char]
name) forall a. a -> [a] -> [a]
: (DynFlags -> [ModuleName]
pluginModNames DynFlags
d) }

clearPluginModuleNames :: DynFlags -> DynFlags
clearPluginModuleNames :: DynFlags -> DynFlags
clearPluginModuleNames DynFlags
d =
    DynFlags
d { pluginModNames :: [ModuleName]
pluginModNames = []
      , pluginModNameOpts :: [(ModuleName, [Char])]
pluginModNameOpts = []
      }

addPluginModuleNameOption :: String -> DynFlags -> DynFlags
addPluginModuleNameOption :: [Char] -> DynFlags -> DynFlags
addPluginModuleNameOption [Char]
optflag DynFlags
d = DynFlags
d { pluginModNameOpts :: [(ModuleName, [Char])]
pluginModNameOpts = ([Char] -> ModuleName
mkModuleName [Char]
m, [Char]
option) forall a. a -> [a] -> [a]
: (DynFlags -> [(ModuleName, [Char])]
pluginModNameOpts DynFlags
d) }
  where ([Char]
m, [Char]
rest) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break (forall a. Eq a => a -> a -> Bool
== Char
':') [Char]
optflag
        option :: [Char]
option = case [Char]
rest of
          [] -> [Char]
"" -- should probably signal an error
          (Char
_:[Char]
plug_opt) -> [Char]
plug_opt -- ignore the ':' from break

addFrontendPluginOption :: String -> DynFlags -> DynFlags
addFrontendPluginOption :: [Char] -> DynFlags -> DynFlags
addFrontendPluginOption [Char]
s DynFlags
d = DynFlags
d { frontendPluginOpts :: [[Char]]
frontendPluginOpts = [Char]
s forall a. a -> [a] -> [a]
: DynFlags -> [[Char]]
frontendPluginOpts DynFlags
d }

parseDynLibLoaderMode :: [Char] -> DynFlags -> DynFlags
parseDynLibLoaderMode [Char]
f DynFlags
d =
 case forall a. Int -> [a] -> ([a], [a])
splitAt Int
8 [Char]
f of
   ([Char]
"deploy", [Char]
"")       -> DynFlags
d { dynLibLoader :: DynLibLoader
dynLibLoader = DynLibLoader
Deployable }
   ([Char]
"sysdep", [Char]
"")       -> DynFlags
d { dynLibLoader :: DynLibLoader
dynLibLoader = DynLibLoader
SystemDependent }
   ([Char], [Char])
_                    -> forall a. GhcException -> a
throwGhcException ([Char] -> GhcException
CmdLineError ([Char]
"Unknown dynlib loader: " forall a. [a] -> [a] -> [a]
++ [Char]
f))

setDumpPrefixForce :: Maybe [Char] -> DynFlags -> DynFlags
setDumpPrefixForce Maybe [Char]
f DynFlags
d = DynFlags
d { dumpPrefixForce :: Maybe [Char]
dumpPrefixForce = Maybe [Char]
f}

-- XXX HACK: Prelude> words "'does not' work" ===> ["'does","not'","work"]
-- Config.hs should really use Option.
setPgmP :: [Char] -> DynFlags -> DynFlags
setPgmP   [Char]
f = (ToolSettings -> ToolSettings) -> DynFlags -> DynFlags
alterToolSettings (\ToolSettings
s -> ToolSettings
s { toolSettings_pgm_P :: ([Char], [Option])
toolSettings_pgm_P   = ([Char]
pgm, forall a b. (a -> b) -> [a] -> [b]
map [Char] -> Option
Option [[Char]]
args)})
  where ([Char]
pgm:[[Char]]
args) = [Char] -> [[Char]]
words [Char]
f
addOptl :: [Char] -> DynFlags -> DynFlags
addOptl   [Char]
f = (ToolSettings -> ToolSettings) -> DynFlags -> DynFlags
alterToolSettings (\ToolSettings
s -> ToolSettings
s { toolSettings_opt_l :: [[Char]]
toolSettings_opt_l   = [Char]
f forall a. a -> [a] -> [a]
: ToolSettings -> [[Char]]
toolSettings_opt_l ToolSettings
s})
addOptc :: [Char] -> DynFlags -> DynFlags
addOptc   [Char]
f = (ToolSettings -> ToolSettings) -> DynFlags -> DynFlags
alterToolSettings (\ToolSettings
s -> ToolSettings
s { toolSettings_opt_c :: [[Char]]
toolSettings_opt_c   = [Char]
f forall a. a -> [a] -> [a]
: ToolSettings -> [[Char]]
toolSettings_opt_c ToolSettings
s})
addOptcxx :: [Char] -> DynFlags -> DynFlags
addOptcxx [Char]
f = (ToolSettings -> ToolSettings) -> DynFlags -> DynFlags
alterToolSettings (\ToolSettings
s -> ToolSettings
s { toolSettings_opt_cxx :: [[Char]]
toolSettings_opt_cxx = [Char]
f forall a. a -> [a] -> [a]
: ToolSettings -> [[Char]]
toolSettings_opt_cxx ToolSettings
s})
addOptP :: [Char] -> DynFlags -> DynFlags
addOptP   [Char]
f = (ToolSettings -> ToolSettings) -> DynFlags -> DynFlags
alterToolSettings forall a b. (a -> b) -> a -> b
$ \ToolSettings
s -> ToolSettings
s
          { toolSettings_opt_P :: [[Char]]
toolSettings_opt_P   = [Char]
f forall a. a -> [a] -> [a]
: ToolSettings -> [[Char]]
toolSettings_opt_P ToolSettings
s
          , toolSettings_opt_P_fingerprint :: Fingerprint
toolSettings_opt_P_fingerprint = [[Char]] -> Fingerprint
fingerprintStrings ([Char]
f forall a. a -> [a] -> [a]
: ToolSettings -> [[Char]]
toolSettings_opt_P ToolSettings
s)
          }
          -- See Note [Repeated -optP hashing]
  where
  fingerprintStrings :: [[Char]] -> Fingerprint
fingerprintStrings [[Char]]
ss = [Fingerprint] -> Fingerprint
fingerprintFingerprints forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map [Char] -> Fingerprint
fingerprintString [[Char]]
ss


setDepMakefile :: FilePath -> DynFlags -> DynFlags
setDepMakefile :: [Char] -> DynFlags -> DynFlags
setDepMakefile [Char]
f DynFlags
d = DynFlags
d { depMakefile :: [Char]
depMakefile = [Char]
f }

setDepIncludeCppDeps :: Bool -> DynFlags -> DynFlags
setDepIncludeCppDeps :: Bool -> DynFlags -> DynFlags
setDepIncludeCppDeps Bool
b DynFlags
d = DynFlags
d { depIncludeCppDeps :: Bool
depIncludeCppDeps = Bool
b }

setDepIncludePkgDeps :: Bool -> DynFlags -> DynFlags
setDepIncludePkgDeps :: Bool -> DynFlags -> DynFlags
setDepIncludePkgDeps Bool
b DynFlags
d = DynFlags
d { depIncludePkgDeps :: Bool
depIncludePkgDeps = Bool
b }

addDepExcludeMod :: String -> DynFlags -> DynFlags
addDepExcludeMod :: [Char] -> DynFlags -> DynFlags
addDepExcludeMod [Char]
m DynFlags
d
    = DynFlags
d { depExcludeMods :: [ModuleName]
depExcludeMods = [Char] -> ModuleName
mkModuleName [Char]
m forall a. a -> [a] -> [a]
: DynFlags -> [ModuleName]
depExcludeMods DynFlags
d }

addDepSuffix :: FilePath -> DynFlags -> DynFlags
addDepSuffix :: [Char] -> DynFlags -> DynFlags
addDepSuffix [Char]
s DynFlags
d = DynFlags
d { depSuffixes :: [[Char]]
depSuffixes = [Char]
s forall a. a -> [a] -> [a]
: DynFlags -> [[Char]]
depSuffixes DynFlags
d }

addCmdlineFramework :: [Char] -> DynFlags -> DynFlags
addCmdlineFramework [Char]
f DynFlags
d = DynFlags
d { cmdlineFrameworks :: [[Char]]
cmdlineFrameworks = [Char]
f forall a. a -> [a] -> [a]
: DynFlags -> [[Char]]
cmdlineFrameworks DynFlags
d}

addGhcVersionFile :: FilePath -> DynFlags -> DynFlags
addGhcVersionFile :: [Char] -> DynFlags -> DynFlags
addGhcVersionFile [Char]
f DynFlags
d = DynFlags
d { ghcVersionFile :: Maybe [Char]
ghcVersionFile = forall a. a -> Maybe a
Just [Char]
f }

addHaddockOpts :: [Char] -> DynFlags -> DynFlags
addHaddockOpts [Char]
f DynFlags
d = DynFlags
d { haddockOptions :: Maybe [Char]
haddockOptions = forall a. a -> Maybe a
Just [Char]
f}

addGhciScript :: [Char] -> DynFlags -> DynFlags
addGhciScript [Char]
f DynFlags
d = DynFlags
d { ghciScripts :: [[Char]]
ghciScripts = [Char]
f forall a. a -> [a] -> [a]
: DynFlags -> [[Char]]
ghciScripts DynFlags
d}

setInteractivePrint :: [Char] -> DynFlags -> DynFlags
setInteractivePrint [Char]
f DynFlags
d = DynFlags
d { interactivePrint :: Maybe [Char]
interactivePrint = forall a. a -> Maybe a
Just [Char]
f}

-----------------------------------------------------------------------------
-- Setting the optimisation level

updOptLevel :: Int -> DynFlags -> DynFlags
-- ^ Sets the 'DynFlags' to be appropriate to the optimisation level
updOptLevel :: Int -> DynFlags -> DynFlags
updOptLevel Int
n DynFlags
dfs
  = DynFlags
dfs2{ optLevel :: Int
optLevel = Int
final_n }
  where
   final_n :: Int
final_n = forall a. Ord a => a -> a -> a
max Int
0 (forall a. Ord a => a -> a -> a
min Int
2 Int
n)    -- Clamp to 0 <= n <= 2
   dfs1 :: DynFlags
dfs1 = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (forall a b c. (a -> b -> c) -> b -> a -> c
flip DynFlags -> GeneralFlag -> DynFlags
gopt_unset) DynFlags
dfs  [GeneralFlag]
remove_gopts
   dfs2 :: DynFlags
dfs2 = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (forall a b c. (a -> b -> c) -> b -> a -> c
flip DynFlags -> GeneralFlag -> DynFlags
gopt_set)   DynFlags
dfs1 [GeneralFlag]
extra_gopts

   extra_gopts :: [GeneralFlag]
extra_gopts  = [ GeneralFlag
f | ([Int]
ns,GeneralFlag
f) <- [([Int], GeneralFlag)]
optLevelFlags, Int
final_n forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Int]
ns ]
   remove_gopts :: [GeneralFlag]
remove_gopts = [ GeneralFlag
f | ([Int]
ns,GeneralFlag
f) <- [([Int], GeneralFlag)]
optLevelFlags, Int
final_n forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [Int]
ns ]

{- **********************************************************************
%*                                                                      *
                DynFlags parser
%*                                                                      *
%********************************************************************* -}

-- -----------------------------------------------------------------------------
-- Parsing the dynamic flags.


-- | Parse dynamic flags from a list of command line arguments.  Returns
-- the parsed 'DynFlags', the left-over arguments, and a list of warnings.
-- Throws a 'UsageError' if errors occurred during parsing (such as unknown
-- flags or missing arguments).
parseDynamicFlagsCmdLine :: MonadIO m => DynFlags -> [Located String]
                         -> m (DynFlags, [Located String], [Warn])
                            -- ^ Updated 'DynFlags', left-over arguments, and
                            -- list of warnings.
parseDynamicFlagsCmdLine :: forall (m :: * -> *).
MonadIO m =>
DynFlags
-> [Located [Char]] -> m (DynFlags, [Located [Char]], [Warn])
parseDynamicFlagsCmdLine = forall (m :: * -> *).
MonadIO m =>
[Flag (CmdLineP DynFlags)]
-> Bool
-> DynFlags
-> [Located [Char]]
-> m (DynFlags, [Located [Char]], [Warn])
parseDynamicFlagsFull [Flag (CmdLineP DynFlags)]
flagsAll Bool
True


-- | Like 'parseDynamicFlagsCmdLine' but does not allow the package flags
-- (-package, -hide-package, -ignore-package, -hide-all-packages, -package-db).
-- Used to parse flags set in a modules pragma.
parseDynamicFilePragma :: MonadIO m => DynFlags -> [Located String]
                       -> m (DynFlags, [Located String], [Warn])
                          -- ^ Updated 'DynFlags', left-over arguments, and
                          -- list of warnings.
parseDynamicFilePragma :: forall (m :: * -> *).
MonadIO m =>
DynFlags
-> [Located [Char]] -> m (DynFlags, [Located [Char]], [Warn])
parseDynamicFilePragma = forall (m :: * -> *).
MonadIO m =>
[Flag (CmdLineP DynFlags)]
-> Bool
-> DynFlags
-> [Located [Char]]
-> m (DynFlags, [Located [Char]], [Warn])
parseDynamicFlagsFull [Flag (CmdLineP DynFlags)]
flagsDynamic Bool
False


-- | Parses the dynamically set flags for GHC. This is the most general form of
-- the dynamic flag parser that the other methods simply wrap. It allows
-- saying which flags are valid flags and indicating if we are parsing
-- arguments from the command line or from a file pragma.
parseDynamicFlagsFull :: MonadIO m
                  => [Flag (CmdLineP DynFlags)]    -- ^ valid flags to match against
                  -> Bool                          -- ^ are the arguments from the command line?
                  -> DynFlags                      -- ^ current dynamic flags
                  -> [Located String]              -- ^ arguments to parse
                  -> m (DynFlags, [Located String], [Warn])
parseDynamicFlagsFull :: forall (m :: * -> *).
MonadIO m =>
[Flag (CmdLineP DynFlags)]
-> Bool
-> DynFlags
-> [Located [Char]]
-> m (DynFlags, [Located [Char]], [Warn])
parseDynamicFlagsFull [Flag (CmdLineP DynFlags)]
activeFlags Bool
cmdline DynFlags
dflags0 [Located [Char]]
args = do
  let (([Located [Char]]
leftover, [Err]
errs, [Warn]
warns), DynFlags
dflags1)
          = forall s a. CmdLineP s a -> s -> (a, s)
runCmdLine (forall (m :: * -> *).
Monad m =>
[Flag m] -> [Located [Char]] -> m ([Located [Char]], [Err], [Warn])
processArgs [Flag (CmdLineP DynFlags)]
activeFlags [Located [Char]]
args) DynFlags
dflags0

  -- See Note [Handling errors when parsing commandline flags]
  let rdr :: SDoc -> [Char]
rdr = SDocContext -> SDoc -> [Char]
renderWithContext (DynFlags -> PprStyle -> SDocContext
initSDocContext DynFlags
dflags0 PprStyle
defaultUserStyle)
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Err]
errs) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. GhcException -> IO a
throwGhcExceptionIO forall a b. (a -> b) -> a -> b
$ [([Char], [Char])] -> GhcException
errorsToGhcException forall a b. (a -> b) -> a -> b
$
    forall a b. (a -> b) -> [a] -> [b]
map ((SDoc -> [Char]
rdr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Outputable a => a -> SDoc
ppr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall l e. GenLocated l e -> l
getLoc forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& forall l e. GenLocated l e -> e
unLoc) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Err -> Located [Char]
errMsg) forall a b. (a -> b) -> a -> b
$ [Err]
errs

  -- check for disabled flags in safe haskell
  let (DynFlags
dflags2, [Located [Char]]
sh_warns) = Bool -> DynFlags -> (DynFlags, [Located [Char]])
safeFlagCheck Bool
cmdline DynFlags
dflags1
      theWays :: Ways
theWays = DynFlags -> Ways
ways DynFlags
dflags2

  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Ways -> Bool
allowed_combination Ways
theWays) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
      forall a. GhcException -> IO a
throwGhcExceptionIO ([Char] -> GhcException
CmdLineError ([Char]
"combination not supported: " forall a. [a] -> [a] -> [a]
++
                               forall a. [a] -> [[a]] -> [a]
intercalate [Char]
"/" (forall a b. (a -> b) -> [a] -> [b]
map Way -> [Char]
wayDesc (forall a. Set a -> [a]
Set.toAscList Ways
theWays))))

  let dflags3 :: DynFlags
dflags3
        | Just [Char]
outFile <- DynFlags -> Maybe [Char]
outputFile_ DynFlags
dflags2   -- Only iff user specified -o ...
        , Bool -> Bool
not (forall a. Maybe a -> Bool
isJust (DynFlags -> Maybe [Char]
dynOutputFile_ DynFlags
dflags2)) -- but not -dyno
        = DynFlags
dflags2 { dynOutputFile_ :: Maybe [Char]
dynOutputFile_ = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ DynFlags -> ShowS
dynamicOutputFile DynFlags
dflags2 [Char]
outFile }
        | Bool
otherwise
        = DynFlags
dflags2

  let (DynFlags
dflags4, [Located [Char]]
consistency_warnings) = DynFlags -> (DynFlags, [Located [Char]])
makeDynFlagsConsistent DynFlags
dflags3

  -- Set timer stats & heap size
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (DynFlags -> Bool
enableTimeStats DynFlags
dflags4) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ()
enableTimingStats
  case (DynFlags -> Maybe Int
ghcHeapSize DynFlags
dflags4) of
    Just Int
x -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Int -> IO ()
setHeapSize Int
x)
    Maybe Int
_      -> forall (m :: * -> *) a. Monad m => a -> m a
return ()

  forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ DynFlags -> IO ()
setUnsafeGlobalDynFlags DynFlags
dflags4

  let warns' :: [Warn]
warns' = forall a b. (a -> b) -> [a] -> [b]
map (WarnReason -> Located [Char] -> Warn
Warn WarnReason
Cmd.NoReason) ([Located [Char]]
consistency_warnings forall a. [a] -> [a] -> [a]
++ [Located [Char]]
sh_warns)

  forall (m :: * -> *) a. Monad m => a -> m a
return (DynFlags
dflags4, [Located [Char]]
leftover, [Warn]
warns' forall a. [a] -> [a] -> [a]
++ [Warn]
warns)

-- | Check (and potentially disable) any extensions that aren't allowed
-- in safe mode.
--
-- The bool is to indicate if we are parsing command line flags (false means
-- file pragma). This allows us to generate better warnings.
safeFlagCheck :: Bool -> DynFlags -> (DynFlags, [Located String])
safeFlagCheck :: Bool -> DynFlags -> (DynFlags, [Located [Char]])
safeFlagCheck Bool
_ DynFlags
dflags | DynFlags -> Bool
safeLanguageOn DynFlags
dflags = (DynFlags
dflagsUnset, [Located [Char]]
warns)
  where
    -- Handle illegal flags under safe language.
    (DynFlags
dflagsUnset, [Located [Char]]
warns) = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' forall {a} {l}.
(a, [GenLocated l [Char]])
-> ([Char], a -> l, a -> Bool, a -> a)
-> (a, [GenLocated l [Char]])
check_method (DynFlags
dflags, []) [([Char], DynFlags -> SrcSpan, DynFlags -> Bool,
  DynFlags -> DynFlags)]
unsafeFlags

    check_method :: (a, [GenLocated l [Char]])
-> ([Char], a -> l, a -> Bool, a -> a)
-> (a, [GenLocated l [Char]])
check_method (a
df, [GenLocated l [Char]]
warns) ([Char]
str,a -> l
loc,a -> Bool
test,a -> a
fix)
        | a -> Bool
test a
df   = (a -> a
fix a
df, [GenLocated l [Char]]
warns forall a. [a] -> [a] -> [a]
++ forall {l}. l -> [Char] -> [GenLocated l [Char]]
safeFailure (a -> l
loc a
df) [Char]
str)
        | Bool
otherwise = (a
df, [GenLocated l [Char]]
warns)

    safeFailure :: l -> [Char] -> [GenLocated l [Char]]
safeFailure l
loc [Char]
str
       = [forall l e. l -> e -> GenLocated l e
L l
loc forall a b. (a -> b) -> a -> b
$ [Char]
str forall a. [a] -> [a] -> [a]
++ [Char]
" is not allowed in Safe Haskell; ignoring "
           forall a. [a] -> [a] -> [a]
++ [Char]
str]

safeFlagCheck Bool
cmdl DynFlags
dflags =
  case DynFlags -> Bool
safeInferOn DynFlags
dflags of
    Bool
True   -> (DynFlags
dflags' { safeInferred :: Bool
safeInferred = Bool
safeFlags }, [Located [Char]]
warn)
    Bool
False  -> (DynFlags
dflags', [Located [Char]]
warn)

  where
    -- dynflags and warn for when -fpackage-trust by itself with no safe
    -- haskell flag
    (DynFlags
dflags', [Located [Char]]
warn)
      | Bool -> Bool
not (DynFlags -> Bool
safeHaskellModeEnabled DynFlags
dflags) Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
cmdl Bool -> Bool -> Bool
&& DynFlags -> Bool
packageTrustOn DynFlags
dflags
      = (DynFlags -> GeneralFlag -> DynFlags
gopt_unset DynFlags
dflags GeneralFlag
Opt_PackageTrust, [Located [Char]]
pkgWarnMsg)
      | Bool
otherwise = (DynFlags
dflags, [])

    pkgWarnMsg :: [Located [Char]]
pkgWarnMsg = [forall l e. l -> e -> GenLocated l e
L (DynFlags -> SrcSpan
pkgTrustOnLoc DynFlags
dflags') forall a b. (a -> b) -> a -> b
$
                    [Char]
"-fpackage-trust ignored;" forall a. [a] -> [a] -> [a]
++
                    [Char]
" must be specified with a Safe Haskell flag"]

    -- Have we inferred Unsafe? See Note [GHC.Driver.Main . Safe Haskell Inference]
    safeFlags :: Bool
safeFlags = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\([Char]
_,DynFlags -> SrcSpan
_,DynFlags -> Bool
t,DynFlags -> DynFlags
_) -> Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ DynFlags -> Bool
t DynFlags
dflags) [([Char], DynFlags -> SrcSpan, DynFlags -> Bool,
  DynFlags -> DynFlags)]
unsafeFlagsForInfer


{- **********************************************************************
%*                                                                      *
                DynFlags specifications
%*                                                                      *
%********************************************************************* -}

-- | All dynamic flags option strings without the deprecated ones.
-- These are the user facing strings for enabling and disabling options.
allNonDeprecatedFlags :: [String]
allNonDeprecatedFlags :: [[Char]]
allNonDeprecatedFlags = Bool -> [[Char]]
allFlagsDeps Bool
False

-- | All flags with possibility to filter deprecated ones
allFlagsDeps :: Bool -> [String]
allFlagsDeps :: Bool -> [[Char]]
allFlagsDeps Bool
keepDeprecated = [ Char
'-'forall a. a -> [a] -> [a]
:forall (m :: * -> *). Flag m -> [Char]
flagName Flag (CmdLineP DynFlags)
flag
                              | (Deprecation
deprecated, Flag (CmdLineP DynFlags)
flag) <- [(Deprecation, Flag (CmdLineP DynFlags))]
flagsAllDeps
                              , Bool
keepDeprecated Bool -> Bool -> Bool
|| Bool -> Bool
not (Deprecation -> Bool
isDeprecated Deprecation
deprecated)]
  where isDeprecated :: Deprecation -> Bool
isDeprecated Deprecation
Deprecated = Bool
True
        isDeprecated Deprecation
_ = Bool
False

{-
 - Below we export user facing symbols for GHC dynamic flags for use with the
 - GHC API.
 -}

-- All dynamic flags present in GHC.
flagsAll :: [Flag (CmdLineP DynFlags)]
flagsAll :: [Flag (CmdLineP DynFlags)]
flagsAll = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd [(Deprecation, Flag (CmdLineP DynFlags))]
flagsAllDeps

-- All dynamic flags present in GHC with deprecation information.
flagsAllDeps :: [(Deprecation, Flag (CmdLineP DynFlags))]
flagsAllDeps :: [(Deprecation, Flag (CmdLineP DynFlags))]
flagsAllDeps =  [(Deprecation, Flag (CmdLineP DynFlags))]
package_flags_deps forall a. [a] -> [a] -> [a]
++ [(Deprecation, Flag (CmdLineP DynFlags))]
dynamic_flags_deps


-- All dynamic flags, minus package flags, present in GHC.
flagsDynamic :: [Flag (CmdLineP DynFlags)]
flagsDynamic :: [Flag (CmdLineP DynFlags)]
flagsDynamic = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd [(Deprecation, Flag (CmdLineP DynFlags))]
dynamic_flags_deps

-- ALl package flags present in GHC.
flagsPackage :: [Flag (CmdLineP DynFlags)]
flagsPackage :: [Flag (CmdLineP DynFlags)]
flagsPackage = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd [(Deprecation, Flag (CmdLineP DynFlags))]
package_flags_deps

----------------Helpers to make flags and keep deprecation information----------

type FlagMaker m = String -> OptKind m -> Flag m
type DynFlagMaker = FlagMaker (CmdLineP DynFlags)
data Deprecation = NotDeprecated | Deprecated deriving (Deprecation -> Deprecation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Deprecation -> Deprecation -> Bool
$c/= :: Deprecation -> Deprecation -> Bool
== :: Deprecation -> Deprecation -> Bool
$c== :: Deprecation -> Deprecation -> Bool
Eq, Eq Deprecation
Deprecation -> Deprecation -> Bool
Deprecation -> Deprecation -> Ordering
Deprecation -> Deprecation -> Deprecation
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Deprecation -> Deprecation -> Deprecation
$cmin :: Deprecation -> Deprecation -> Deprecation
max :: Deprecation -> Deprecation -> Deprecation
$cmax :: Deprecation -> Deprecation -> Deprecation
>= :: Deprecation -> Deprecation -> Bool
$c>= :: Deprecation -> Deprecation -> Bool
> :: Deprecation -> Deprecation -> Bool
$c> :: Deprecation -> Deprecation -> Bool
<= :: Deprecation -> Deprecation -> Bool
$c<= :: Deprecation -> Deprecation -> Bool
< :: Deprecation -> Deprecation -> Bool
$c< :: Deprecation -> Deprecation -> Bool
compare :: Deprecation -> Deprecation -> Ordering
$ccompare :: Deprecation -> Deprecation -> Ordering
Ord)

-- Make a non-deprecated flag
make_ord_flag :: DynFlagMaker -> String -> OptKind (CmdLineP DynFlags)
              -> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag :: DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag DynFlagMaker
fm [Char]
name OptKind (CmdLineP DynFlags)
kind = (Deprecation
NotDeprecated, DynFlagMaker
fm [Char]
name OptKind (CmdLineP DynFlags)
kind)

-- Make a deprecated flag
make_dep_flag :: DynFlagMaker -> String -> OptKind (CmdLineP DynFlags) -> String
                 -> (Deprecation, Flag (CmdLineP DynFlags))
make_dep_flag :: DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> [Char]
-> (Deprecation, Flag (CmdLineP DynFlags))
make_dep_flag DynFlagMaker
fm [Char]
name OptKind (CmdLineP DynFlags)
kind [Char]
message = (Deprecation
Deprecated,
                                      DynFlagMaker
fm [Char]
name forall a b. (a -> b) -> a -> b
$ OptKind (CmdLineP DynFlags)
-> [Char] -> OptKind (CmdLineP DynFlags)
add_dep_message OptKind (CmdLineP DynFlags)
kind [Char]
message)

add_dep_message :: OptKind (CmdLineP DynFlags) -> String
                -> OptKind (CmdLineP DynFlags)
add_dep_message :: OptKind (CmdLineP DynFlags)
-> [Char] -> OptKind (CmdLineP DynFlags)
add_dep_message (NoArg DynP ()
f) [Char]
message = forall (m :: * -> *). EwM m () -> OptKind m
NoArg forall a b. (a -> b) -> a -> b
$ DynP ()
f forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *). Monad m => [Char] -> EwM m ()
deprecate [Char]
message
add_dep_message (HasArg [Char] -> DynP ()
f) [Char]
message = forall (m :: * -> *). ([Char] -> EwM m ()) -> OptKind m
HasArg forall a b. (a -> b) -> a -> b
$ \[Char]
s -> [Char] -> DynP ()
f [Char]
s forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *). Monad m => [Char] -> EwM m ()
deprecate [Char]
message
add_dep_message (SepArg [Char] -> DynP ()
f) [Char]
message = forall (m :: * -> *). ([Char] -> EwM m ()) -> OptKind m
SepArg forall a b. (a -> b) -> a -> b
$ \[Char]
s -> [Char] -> DynP ()
f [Char]
s forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *). Monad m => [Char] -> EwM m ()
deprecate [Char]
message
add_dep_message (Prefix [Char] -> DynP ()
f) [Char]
message = forall (m :: * -> *). ([Char] -> EwM m ()) -> OptKind m
Prefix forall a b. (a -> b) -> a -> b
$ \[Char]
s -> [Char] -> DynP ()
f [Char]
s forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *). Monad m => [Char] -> EwM m ()
deprecate [Char]
message
add_dep_message (OptPrefix [Char] -> DynP ()
f) [Char]
message =
                                  forall (m :: * -> *). ([Char] -> EwM m ()) -> OptKind m
OptPrefix forall a b. (a -> b) -> a -> b
$ \[Char]
s -> [Char] -> DynP ()
f [Char]
s forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *). Monad m => [Char] -> EwM m ()
deprecate [Char]
message
add_dep_message (OptIntSuffix Maybe Int -> DynP ()
f) [Char]
message =
                               forall (m :: * -> *). (Maybe Int -> EwM m ()) -> OptKind m
OptIntSuffix forall a b. (a -> b) -> a -> b
$ \Maybe Int
oi -> Maybe Int -> DynP ()
f Maybe Int
oi forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *). Monad m => [Char] -> EwM m ()
deprecate [Char]
message
add_dep_message (IntSuffix Int -> DynP ()
f) [Char]
message =
                                  forall (m :: * -> *). (Int -> EwM m ()) -> OptKind m
IntSuffix forall a b. (a -> b) -> a -> b
$ \Int
i -> Int -> DynP ()
f Int
i forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *). Monad m => [Char] -> EwM m ()
deprecate [Char]
message
add_dep_message (WordSuffix Word -> DynP ()
f) [Char]
message =
                                  forall (m :: * -> *). (Word -> EwM m ()) -> OptKind m
WordSuffix forall a b. (a -> b) -> a -> b
$ \Word
i -> Word -> DynP ()
f Word
i forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *). Monad m => [Char] -> EwM m ()
deprecate [Char]
message
add_dep_message (FloatSuffix Float -> DynP ()
f) [Char]
message =
                                forall (m :: * -> *). (Float -> EwM m ()) -> OptKind m
FloatSuffix forall a b. (a -> b) -> a -> b
$ \Float
fl -> Float -> DynP ()
f Float
fl forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *). Monad m => [Char] -> EwM m ()
deprecate [Char]
message
add_dep_message (PassFlag [Char] -> DynP ()
f) [Char]
message =
                                   forall (m :: * -> *). ([Char] -> EwM m ()) -> OptKind m
PassFlag forall a b. (a -> b) -> a -> b
$ \[Char]
s -> [Char] -> DynP ()
f [Char]
s forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *). Monad m => [Char] -> EwM m ()
deprecate [Char]
message
add_dep_message (AnySuffix [Char] -> DynP ()
f) [Char]
message =
                                  forall (m :: * -> *). ([Char] -> EwM m ()) -> OptKind m
AnySuffix forall a b. (a -> b) -> a -> b
$ \[Char]
s -> [Char] -> DynP ()
f [Char]
s forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *). Monad m => [Char] -> EwM m ()
deprecate [Char]
message

----------------------- The main flags themselves ------------------------------
-- See Note [Updating flag description in the User's Guide]
-- See Note [Supporting CLI completion]
dynamic_flags_deps :: [(Deprecation, Flag (CmdLineP DynFlags))]
dynamic_flags_deps :: [(Deprecation, Flag (CmdLineP DynFlags))]
dynamic_flags_deps = [
    DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> [Char]
-> (Deprecation, Flag (CmdLineP DynFlags))
make_dep_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defFlag [Char]
"n" (forall (m :: * -> *). EwM m () -> OptKind m
NoArg forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return ())
        [Char]
"The -n flag is deprecated and no longer has any effect"
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defFlag [Char]
"cpp"      (forall (m :: * -> *). EwM m () -> OptKind m
NoArg (Extension -> DynP ()
setExtensionFlag Extension
LangExt.Cpp))
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defFlag [Char]
"F"        (forall (m :: * -> *). EwM m () -> OptKind m
NoArg (GeneralFlag -> DynP ()
setGeneralFlag GeneralFlag
Opt_Pp))
  , (Deprecation
Deprecated, forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defFlag [Char]
"#include"
      (forall (m :: * -> *). ([Char] -> EwM m ()) -> OptKind m
HasArg (\[Char]
_s ->
         forall (m :: * -> *). Monad m => [Char] -> EwM m ()
deprecate ([Char]
"-#include and INCLUDE pragmas are " forall a. [a] -> [a] -> [a]
++
                    [Char]
"deprecated: They no longer have any effect"))))
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defFlag [Char]
"v"        (forall (m :: * -> *). (Maybe Int -> EwM m ()) -> OptKind m
OptIntSuffix Maybe Int -> DynP ()
setVerbosity)

  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defGhcFlag [Char]
"j"     (forall (m :: * -> *). (Maybe Int -> EwM m ()) -> OptKind m
OptIntSuffix
        (\Maybe Int
n -> case Maybe Int
n of
                 Just Int
n
                     | Int
n forall a. Ord a => a -> a -> Bool
> Int
0     -> (DynFlags -> DynFlags) -> DynP ()
upd (\DynFlags
d -> DynFlags
d { parMakeCount :: Maybe Int
parMakeCount = forall a. a -> Maybe a
Just Int
n })
                     | Bool
otherwise -> forall (m :: * -> *). Monad m => [Char] -> EwM m ()
addErr [Char]
"Syntax: -j[n] where n > 0"
                 Maybe Int
Nothing -> (DynFlags -> DynFlags) -> DynP ()
upd (\DynFlags
d -> DynFlags
d { parMakeCount :: Maybe Int
parMakeCount = forall a. Maybe a
Nothing })))
                 -- When the number of parallel builds
                 -- is omitted, it is the same
                 -- as specifying that the number of
                 -- parallel builds is equal to the
                 -- result of getNumProcessors
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defFlag [Char]
"instantiated-with"   (([Char] -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
sepArg [Char] -> DynFlags -> DynFlags
setUnitInstantiations)
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defFlag [Char]
"this-component-id"   (([Char] -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
sepArg [Char] -> DynFlags -> DynFlags
setUnitInstanceOf)

    -- RTS options -------------------------------------------------------------
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defFlag [Char]
"H"           (forall (m :: * -> *). ([Char] -> EwM m ()) -> OptKind m
HasArg (\[Char]
s -> (DynFlags -> DynFlags) -> DynP ()
upd (\DynFlags
d ->
          DynFlags
d { ghcHeapSize :: Maybe Int
ghcHeapSize = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral ([Char] -> Integer
decodeSize [Char]
s)})))

  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defFlag [Char]
"Rghc-timing" (forall (m :: * -> *). EwM m () -> OptKind m
NoArg ((DynFlags -> DynFlags) -> DynP ()
upd (\DynFlags
d ->
                                               DynFlags
d { enableTimeStats :: Bool
enableTimeStats = Bool
True })))

    ------- ways ---------------------------------------------------------------
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defGhcFlag [Char]
"prof"           (forall (m :: * -> *). EwM m () -> OptKind m
NoArg (Way -> DynP ()
addWayDynP Way
WayProf))
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defGhcFlag [Char]
"eventlog"       (forall (m :: * -> *). EwM m () -> OptKind m
NoArg (Way -> DynP ()
addWayDynP Way
WayTracing))
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defGhcFlag [Char]
"debug"          (forall (m :: * -> *). EwM m () -> OptKind m
NoArg (Way -> DynP ()
addWayDynP Way
WayDebug))
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defGhcFlag [Char]
"threaded"       (forall (m :: * -> *). EwM m () -> OptKind m
NoArg (Way -> DynP ()
addWayDynP Way
WayThreaded))

  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defGhcFlag [Char]
"ticky"
      (forall (m :: * -> *). EwM m () -> OptKind m
NoArg (GeneralFlag -> DynP ()
setGeneralFlag GeneralFlag
Opt_Ticky forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Way -> DynP ()
addWayDynP Way
WayDebug))

    -- -ticky enables ticky-ticky code generation, and also implies -debug which
    -- is required to get the RTS ticky support.

        ----- Linker --------------------------------------------------------
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defGhcFlag [Char]
"static"         (forall (m :: * -> *). EwM m () -> OptKind m
NoArg DynP ()
removeWayDyn)
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defGhcFlag [Char]
"dynamic"        (forall (m :: * -> *). EwM m () -> OptKind m
NoArg (Way -> DynP ()
addWayDynP Way
WayDyn))
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defGhcFlag [Char]
"rdynamic" forall a b. (a -> b) -> a -> b
$ (DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
noArg forall a b. (a -> b) -> a -> b
$
#if defined(linux_HOST_OS)
                              [Char] -> DynFlags -> DynFlags
addOptl [Char]
"-rdynamic"
#elif defined(mingw32_HOST_OS)
                              addOptl "-Wl,--export-all-symbols"
#else
    -- ignored for compat w/ gcc:
                              id
#endif
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defGhcFlag [Char]
"relative-dynlib-paths"
      (forall (m :: * -> *). EwM m () -> OptKind m
NoArg (GeneralFlag -> DynP ()
setGeneralFlag GeneralFlag
Opt_RelativeDynlibPaths))
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defGhcFlag [Char]
"copy-libs-when-linking"
      (forall (m :: * -> *). EwM m () -> OptKind m
NoArg (GeneralFlag -> DynP ()
setGeneralFlag GeneralFlag
Opt_SingleLibFolder))
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defGhcFlag [Char]
"pie"            (forall (m :: * -> *). EwM m () -> OptKind m
NoArg (GeneralFlag -> DynP ()
setGeneralFlag GeneralFlag
Opt_PICExecutable))
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defGhcFlag [Char]
"no-pie"         (forall (m :: * -> *). EwM m () -> OptKind m
NoArg (GeneralFlag -> DynP ()
unSetGeneralFlag GeneralFlag
Opt_PICExecutable))
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defGhcFlag [Char]
"fcompact-unwind"
      ((DynFlags -> DynP DynFlags) -> OptKind (CmdLineP DynFlags)
noArgM (\DynFlags
dflags -> do
       if Platform -> OS
platformOS (DynFlags -> Platform
targetPlatform DynFlags
dflags) forall a. Eq a => a -> a -> Bool
== OS
OSDarwin
          then forall (m :: * -> *) a. Monad m => a -> m a
return (DynFlags -> GeneralFlag -> DynFlags
gopt_set DynFlags
dflags GeneralFlag
Opt_CompactUnwind)
          else do forall (m :: * -> *). Monad m => [Char] -> EwM m ()
addWarn [Char]
"-compact-unwind is only implemented by the darwin platform. Ignoring."
                  forall (m :: * -> *) a. Monad m => a -> m a
return DynFlags
dflags))

        ------- Specific phases  --------------------------------------------
    -- need to appear before -pgmL to be parsed as LLVM flags.
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defFlag [Char]
"pgmlo"
      forall a b. (a -> b) -> a -> b
$ ([Char] -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
hasArg forall a b. (a -> b) -> a -> b
$ \[Char]
f -> (ToolSettings -> ToolSettings) -> DynFlags -> DynFlags
alterToolSettings forall a b. (a -> b) -> a -> b
$ \ToolSettings
s -> ToolSettings
s { toolSettings_pgm_lo :: ([Char], [Option])
toolSettings_pgm_lo  = ([Char]
f,[]) }
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defFlag [Char]
"pgmlc"
      forall a b. (a -> b) -> a -> b
$ ([Char] -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
hasArg forall a b. (a -> b) -> a -> b
$ \[Char]
f -> (ToolSettings -> ToolSettings) -> DynFlags -> DynFlags
alterToolSettings forall a b. (a -> b) -> a -> b
$ \ToolSettings
s -> ToolSettings
s { toolSettings_pgm_lc :: ([Char], [Option])
toolSettings_pgm_lc  = ([Char]
f,[]) }
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defFlag [Char]
"pgmlm"
      forall a b. (a -> b) -> a -> b
$ ([Char] -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
hasArg forall a b. (a -> b) -> a -> b
$ \[Char]
f -> (ToolSettings -> ToolSettings) -> DynFlags -> DynFlags
alterToolSettings forall a b. (a -> b) -> a -> b
$ \ToolSettings
s -> ToolSettings
s { toolSettings_pgm_lm :: ([Char], [Option])
toolSettings_pgm_lm  = ([Char]
f,[]) }
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defFlag [Char]
"pgmi"
      forall a b. (a -> b) -> a -> b
$ ([Char] -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
hasArg forall a b. (a -> b) -> a -> b
$ \[Char]
f -> (ToolSettings -> ToolSettings) -> DynFlags -> DynFlags
alterToolSettings forall a b. (a -> b) -> a -> b
$ \ToolSettings
s -> ToolSettings
s { toolSettings_pgm_i :: [Char]
toolSettings_pgm_i   =  [Char]
f }
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defFlag [Char]
"pgmL"
      forall a b. (a -> b) -> a -> b
$ ([Char] -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
hasArg forall a b. (a -> b) -> a -> b
$ \[Char]
f -> (ToolSettings -> ToolSettings) -> DynFlags -> DynFlags
alterToolSettings forall a b. (a -> b) -> a -> b
$ \ToolSettings
s -> ToolSettings
s { toolSettings_pgm_L :: [Char]
toolSettings_pgm_L   = [Char]
f }
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defFlag [Char]
"pgmP"
      (([Char] -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
hasArg [Char] -> DynFlags -> DynFlags
setPgmP)
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defFlag [Char]
"pgmF"
      forall a b. (a -> b) -> a -> b
$ ([Char] -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
hasArg forall a b. (a -> b) -> a -> b
$ \[Char]
f -> (ToolSettings -> ToolSettings) -> DynFlags -> DynFlags
alterToolSettings forall a b. (a -> b) -> a -> b
$ \ToolSettings
s -> ToolSettings
s { toolSettings_pgm_F :: [Char]
toolSettings_pgm_F   = [Char]
f }
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defFlag [Char]
"pgmc"
      forall a b. (a -> b) -> a -> b
$ ([Char] -> DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
hasArg forall a b. (a -> b) -> a -> b
$ \[Char]
f -> (ToolSettings -> ToolSettings) -> DynFlags -> DynFlags
alterToolSettings forall a b. (a -> b) -> a -> b
$ \ToolSettings
s -> ToolSettings
s
         { toolSettings_pgm_c :: [Char]
toolSettings_pgm_c   = [Char]
f
         , -- Don't pass -no-pie with -pgmc
           -- (see #15319)
           toolSettings_ccSupportsNoPie :: Bool
toolSettings_ccSupportsNoPie = Bool
False
         }
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defFlag [Char]
"pgmc-supports-no-pie"
      forall a b. (a -> b) -> a -> b
$ (DynFlags -> DynFlags) -> OptKind (CmdLineP DynFlags)
noArg forall a b. (a -> b) -> a -> b
$ (ToolSettings -> ToolSettings) -> DynFlags -> DynFlags
alterToolSettings forall a b. (a -> b) -> a -> b
$ \ToolSettings
s -> ToolSettings
s { toolSettings_ccSupportsNoPie :: Bool
toolSettings_ccSupportsNoPie = Bool
True }
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defFlag [Char]
"pgms"
      (forall (m :: * -> *). ([Char] -> EwM m ()) -> OptKind m
HasArg (\[Char]
_ -> forall (m :: * -> *). Monad m => [Char] -> EwM m ()
addWarn [Char]
"Object splitting was removed in GHC 8.8"))
  , DynFlagMaker
-> [Char]
-> OptKind (CmdLineP DynFlags)
-> (Deprecation, Flag (CmdLineP DynFlags))
make_ord_flag forall (m :: * -> *). [Char] -> OptKind m -> Flag m
defFlag [Char]
"pgma&