ghc-7.8.3: The GHC API

Safe HaskellNone
LanguageHaskell98

DynFlags

Contents

Description

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

Synopsis

Dynamic flags and associated configuration types

data GeneralFlag Source

Enumerates the simple on-or-off dynamic flags

Constructors

Opt_DumpToFile

Append dump output to files instead of stdout.

Opt_D_faststring_stats 
Opt_D_dump_minimal_imports 
Opt_DoCoreLinting 
Opt_DoStgLinting 
Opt_DoCmmLinting 
Opt_DoAsmLinting 
Opt_NoLlvmMangler 
Opt_WarnIsError 
Opt_PrintExplicitForalls 
Opt_PrintExplicitKinds 
Opt_Strictness 
Opt_LateDmdAnal 
Opt_KillAbsence 
Opt_KillOneShot 
Opt_FullLaziness 
Opt_FloatIn 
Opt_Specialise 
Opt_StaticArgumentTransformation 
Opt_CSE 
Opt_LiberateCase 
Opt_SpecConstr 
Opt_DoLambdaEtaExpansion 
Opt_IgnoreAsserts 
Opt_DoEtaReduction 
Opt_CaseMerge 
Opt_UnboxStrictFields 
Opt_UnboxSmallStrictFields 
Opt_DictsCheap 
Opt_EnableRewriteRules 
Opt_Vectorise 
Opt_VectorisationAvoidance 
Opt_RegsGraph 
Opt_RegsIterative 
Opt_PedanticBottoms 
Opt_LlvmTBAA 
Opt_LlvmPassVectorsInRegisters 
Opt_IrrefutableTuples 
Opt_CmmSink 
Opt_CmmElimCommonBlocks 
Opt_OmitYields 
Opt_SimpleListLiterals 
Opt_FunToThunk 
Opt_DictsStrict 
Opt_DmdTxDictSel 
Opt_Loopification 
Opt_IgnoreInterfacePragmas 
Opt_OmitInterfacePragmas 
Opt_ExposeAllUnfoldings 
Opt_AutoSccsOnIndividualCafs 
Opt_ProfCountEntries 
Opt_Pp 
Opt_ForceRecomp 
Opt_ExcessPrecision 
Opt_EagerBlackHoling 
Opt_NoHsMain 
Opt_SplitObjs 
Opt_StgStats 
Opt_HideAllPackages 
Opt_PrintBindResult 
Opt_Haddock 
Opt_HaddockOptions 
Opt_Hpc_No_Auto 
Opt_BreakOnException 
Opt_BreakOnError 
Opt_PrintEvldWithShow 
Opt_PrintBindContents 
Opt_GenManifest 
Opt_EmbedManifest 
Opt_EmitExternalCore 
Opt_SharedImplib 
Opt_BuildingCabalPackage 
Opt_IgnoreDotGhci 
Opt_GhciSandbox 
Opt_GhciHistory 
Opt_HelpfulErrors 
Opt_DeferTypeErrors 
Opt_Parallel 
Opt_GranMacros 
Opt_PIC 
Opt_SccProfilingOn 
Opt_Ticky 
Opt_Ticky_Allocd 
Opt_Ticky_LNE 
Opt_Ticky_Dyn_Thunk 
Opt_Static 
Opt_RPath 
Opt_RelativeDynlibPaths 
Opt_Hpc 
Opt_FlatCache 
Opt_SimplPreInlining 
Opt_ErrorSpans 
Opt_PprCaseAsLet 
Opt_SuppressCoercions 
Opt_SuppressVarKinds 
Opt_SuppressModulePrefixes 
Opt_SuppressTypeApplications 
Opt_SuppressIdInfo 
Opt_SuppressTypeSignatures 
Opt_SuppressUniques 
Opt_RunCPS 
Opt_RunCPSZ 
Opt_AutoLinkPackages 
Opt_ImplicitImportQualified 
Opt_KeepHiDiffs 
Opt_KeepHcFiles 
Opt_KeepSFiles 
Opt_KeepTmpFiles 
Opt_KeepRawTokenStream 
Opt_KeepLlvmFiles 
Opt_BuildDynamicToo 
Opt_DistrustAllPackages 
Opt_PackageTrust 

data ExtensionFlag Source

Constructors

Opt_Cpp 
Opt_OverlappingInstances 
Opt_UndecidableInstances 
Opt_IncoherentInstances 
Opt_MonomorphismRestriction 
Opt_MonoPatBinds 
Opt_MonoLocalBinds 
Opt_RelaxedPolyRec 
Opt_ExtendedDefaultRules 
Opt_ForeignFunctionInterface 
Opt_UnliftedFFITypes 
Opt_InterruptibleFFI 
Opt_CApiFFI 
Opt_GHCForeignImportPrim 
Opt_JavaScriptFFI 
Opt_ParallelArrays 
Opt_Arrows 
Opt_TemplateHaskell 
Opt_QuasiQuotes 
Opt_ImplicitParams 
Opt_ImplicitPrelude 
Opt_ScopedTypeVariables 
Opt_AllowAmbiguousTypes 
Opt_UnboxedTuples 
Opt_BangPatterns 
Opt_TypeFamilies 
Opt_OverloadedStrings 
Opt_OverloadedLists 
Opt_NumDecimals 
Opt_DisambiguateRecordFields 
Opt_RecordWildCards 
Opt_RecordPuns 
Opt_ViewPatterns 
Opt_GADTs 
Opt_GADTSyntax 
Opt_NPlusKPatterns 
Opt_DoAndIfThenElse 
Opt_RebindableSyntax 
Opt_ConstraintKinds 
Opt_PolyKinds 
Opt_DataKinds 
Opt_InstanceSigs 
Opt_StandaloneDeriving 
Opt_DeriveDataTypeable 
Opt_AutoDeriveTypeable 
Opt_DeriveFunctor 
Opt_DeriveTraversable 
Opt_DeriveFoldable 
Opt_DeriveGeneric 
Opt_DefaultSignatures 
Opt_TypeSynonymInstances 
Opt_FlexibleContexts 
Opt_FlexibleInstances 
Opt_ConstrainedClassMethods 
Opt_MultiParamTypeClasses 
Opt_NullaryTypeClasses 
Opt_FunctionalDependencies 
Opt_UnicodeSyntax 
Opt_ExistentialQuantification 
Opt_MagicHash 
Opt_EmptyDataDecls 
Opt_KindSignatures 
Opt_RoleAnnotations 
Opt_ParallelListComp 
Opt_TransformListComp 
Opt_MonadComprehensions 
Opt_GeneralizedNewtypeDeriving 
Opt_RecursiveDo 
Opt_PostfixOperators 
Opt_TupleSections 
Opt_PatternGuards 
Opt_LiberalTypeSynonyms 
Opt_RankNTypes 
Opt_ImpredicativeTypes 
Opt_TypeOperators 
Opt_ExplicitNamespaces 
Opt_PackageImports 
Opt_ExplicitForAll 
Opt_AlternativeLayoutRule 
Opt_AlternativeLayoutRuleTransitional 
Opt_DatatypeContexts 
Opt_NondecreasingIndentation 
Opt_RelaxedLayout 
Opt_TraditionalRecordSyntax 
Opt_LambdaCase 
Opt_MultiWayIf 
Opt_NegativeLiterals 
Opt_EmptyCase 
Opt_PatternSynonyms 

data Language Source

Constructors

Haskell98 
Haskell2010 

Instances

data PlatformConstants Source

Constructors

PlatformConstants 

Fields

pc_platformConstants :: ()
 
pc_STD_HDR_SIZE :: Int
 
pc_PROF_HDR_SIZE :: Int
 
pc_BLOCK_SIZE :: Int
 
pc_BLOCKS_PER_MBLOCK :: Int
 
pc_OFFSET_StgRegTable_rR1 :: Int
 
pc_OFFSET_StgRegTable_rR2 :: Int
 
pc_OFFSET_StgRegTable_rR3 :: Int
 
pc_OFFSET_StgRegTable_rR4 :: Int
 
pc_OFFSET_StgRegTable_rR5 :: Int
 
pc_OFFSET_StgRegTable_rR6 :: Int
 
pc_OFFSET_StgRegTable_rR7 :: Int
 
pc_OFFSET_StgRegTable_rR8 :: Int
 
pc_OFFSET_StgRegTable_rR9 :: Int
 
pc_OFFSET_StgRegTable_rR10 :: Int
 
pc_OFFSET_StgRegTable_rF1 :: Int
 
pc_OFFSET_StgRegTable_rF2 :: Int
 
pc_OFFSET_StgRegTable_rF3 :: Int
 
pc_OFFSET_StgRegTable_rF4 :: Int
 
pc_OFFSET_StgRegTable_rF5 :: Int
 
pc_OFFSET_StgRegTable_rF6 :: Int
 
pc_OFFSET_StgRegTable_rD1 :: Int
 
pc_OFFSET_StgRegTable_rD2 :: Int
 
pc_OFFSET_StgRegTable_rD3 :: Int
 
pc_OFFSET_StgRegTable_rD4 :: Int
 
pc_OFFSET_StgRegTable_rD5 :: Int
 
pc_OFFSET_StgRegTable_rD6 :: Int
 
pc_OFFSET_StgRegTable_rXMM1 :: Int
 
pc_OFFSET_StgRegTable_rXMM2 :: Int
 
pc_OFFSET_StgRegTable_rXMM3 :: Int
 
pc_OFFSET_StgRegTable_rXMM4 :: Int
 
pc_OFFSET_StgRegTable_rXMM5 :: Int
 
pc_OFFSET_StgRegTable_rXMM6 :: Int
 
pc_OFFSET_StgRegTable_rYMM1 :: Int
 
pc_OFFSET_StgRegTable_rYMM2 :: Int
 
pc_OFFSET_StgRegTable_rYMM3 :: Int
 
pc_OFFSET_StgRegTable_rYMM4 :: Int
 
pc_OFFSET_StgRegTable_rYMM5 :: Int
 
pc_OFFSET_StgRegTable_rYMM6 :: Int
 
pc_OFFSET_StgRegTable_rZMM1 :: Int
 
pc_OFFSET_StgRegTable_rZMM2 :: Int
 
pc_OFFSET_StgRegTable_rZMM3 :: Int
 
pc_OFFSET_StgRegTable_rZMM4 :: Int
 
pc_OFFSET_StgRegTable_rZMM5 :: Int
 
pc_OFFSET_StgRegTable_rZMM6 :: Int
 
pc_OFFSET_StgRegTable_rL1 :: Int
 
pc_OFFSET_StgRegTable_rSp :: Int
 
pc_OFFSET_StgRegTable_rSpLim :: Int
 
pc_OFFSET_StgRegTable_rHp :: Int
 
pc_OFFSET_StgRegTable_rHpLim :: Int
 
pc_OFFSET_StgRegTable_rCCCS :: Int
 
pc_OFFSET_StgRegTable_rCurrentTSO :: Int
 
pc_OFFSET_StgRegTable_rCurrentNursery :: Int
 
pc_OFFSET_StgRegTable_rHpAlloc :: Int
 
pc_OFFSET_stgEagerBlackholeInfo :: Int
 
pc_OFFSET_stgGCEnter1 :: Int
 
pc_OFFSET_stgGCFun :: Int
 
pc_OFFSET_Capability_r :: Int
 
pc_OFFSET_bdescr_start :: Int
 
pc_OFFSET_bdescr_free :: Int
 
pc_OFFSET_bdescr_blocks :: Int
 
pc_SIZEOF_CostCentreStack :: Int
 
pc_OFFSET_CostCentreStack_mem_alloc :: Int
 
pc_REP_CostCentreStack_mem_alloc :: Int
 
pc_OFFSET_CostCentreStack_scc_count :: Int
 
pc_REP_CostCentreStack_scc_count :: Int
 
pc_OFFSET_StgHeader_ccs :: Int
 
pc_OFFSET_StgHeader_ldvw :: Int
 
pc_SIZEOF_StgSMPThunkHeader :: Int
 
pc_OFFSET_StgEntCounter_allocs :: Int
 
pc_REP_StgEntCounter_allocs :: Int
 
pc_OFFSET_StgEntCounter_allocd :: Int
 
pc_REP_StgEntCounter_allocd :: Int
 
pc_OFFSET_StgEntCounter_registeredp :: Int
 
pc_OFFSET_StgEntCounter_link :: Int
 
pc_OFFSET_StgEntCounter_entry_count :: Int
 
pc_SIZEOF_StgUpdateFrame_NoHdr :: Int
 
pc_SIZEOF_StgMutArrPtrs_NoHdr :: Int
 
pc_OFFSET_StgMutArrPtrs_ptrs :: Int
 
pc_OFFSET_StgMutArrPtrs_size :: Int
 
pc_SIZEOF_StgArrWords_NoHdr :: Int
 
pc_OFFSET_StgTSO_cccs :: Int
 
pc_OFFSET_StgTSO_stackobj :: Int
 
pc_OFFSET_StgStack_sp :: Int
 
pc_OFFSET_StgStack_stack :: Int
 
pc_OFFSET_StgUpdateFrame_updatee :: Int
 
pc_OFFSET_StgFunInfoExtraFwd_arity :: Int
 
pc_REP_StgFunInfoExtraFwd_arity :: Int
 
pc_SIZEOF_StgFunInfoExtraRev :: Int
 
pc_OFFSET_StgFunInfoExtraRev_arity :: Int
 
pc_REP_StgFunInfoExtraRev_arity :: Int
 
pc_MAX_SPEC_SELECTEE_SIZE :: Int
 
pc_MAX_SPEC_AP_SIZE :: Int
 
pc_MIN_PAYLOAD_SIZE :: Int
 
pc_MIN_INTLIKE :: Int
 
pc_MAX_INTLIKE :: Int
 
pc_MIN_CHARLIKE :: Int
 
pc_MAX_CHARLIKE :: Int
 
pc_MUT_ARR_PTRS_CARD_BITS :: Int
 
pc_MAX_Vanilla_REG :: Int
 
pc_MAX_Float_REG :: Int
 
pc_MAX_Double_REG :: Int
 
pc_MAX_Long_REG :: Int
 
pc_MAX_XMM_REG :: Int
 
pc_MAX_Real_Vanilla_REG :: Int
 
pc_MAX_Real_Float_REG :: Int
 
pc_MAX_Real_Double_REG :: Int
 
pc_MAX_Real_XMM_REG :: Int
 
pc_MAX_Real_Long_REG :: Int
 
pc_RESERVED_C_STACK_BYTES :: Int
 
pc_RESERVED_STACK_WORDS :: Int
 
pc_AP_STACK_SPLIM :: Int
 
pc_WORD_SIZE :: Int
 
pc_DOUBLE_SIZE :: Int
 
pc_CINT_SIZE :: Int
 
pc_CLONG_SIZE :: Int
 
pc_CLONG_LONG_SIZE :: Int
 
pc_BITMAP_BITS_SHIFT :: Int
 
pc_TAG_BITS :: Int
 
pc_WORDS_BIGENDIAN :: Bool
 
pc_DYNAMIC_BY_DEFAULT :: Bool
 
pc_LDV_SHIFT :: Int
 
pc_ILDV_CREATE_MASK :: Integer
 
pc_ILDV_STATE_CREATE :: Integer
 
pc_ILDV_STATE_USE :: Integer
 

newtype FlushOut Source

Constructors

FlushOut (IO ()) 

newtype FlushErr Source

Constructors

FlushErr (IO ()) 

data ProfAuto Source

Constructors

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

Instances

dopt :: DumpFlag -> DynFlags -> Bool Source

Test whether a DumpFlag is set

gopt :: GeneralFlag -> DynFlags -> Bool Source

Test whether a GeneralFlag is set

wopt :: WarningFlag -> DynFlags -> Bool Source

Test whether a WarningFlag is set

xopt :: ExtensionFlag -> DynFlags -> Bool Source

Test whether a ExtensionFlag is set

ifGeneratingDynamicToo :: MonadIO m => DynFlags -> m a -> m a -> m a Source

data DynFlags Source

Contains not only a collection of GeneralFlags but also a plethora of information relating to the compilation of a single file or GHC session

Constructors

DynFlags 

Fields

ghcMode :: GhcMode
 
ghcLink :: GhcLink
 
hscTarget :: HscTarget
 
settings :: Settings
 
verbosity :: Int

Verbosity level: see Note [Verbosity levels]

optLevel :: Int

Optimisation level

simplPhases :: Int

Number of simplifier phases

maxSimplIterations :: Int

Max simplifier iterations

shouldDumpSimplPhase :: Maybe String
 
ruleCheck :: Maybe String
 
strictnessBefore :: [Int]

Additional demand analysis

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.

enableTimeStats :: Bool

Enable RTS timing statistics?

ghcHeapSize :: Maybe Int

The heap size to set.

maxRelevantBinds :: Maybe Int

Maximum number of bindings from the type envt to show in type error messages

simplTickFactor :: Int

Multiplier for simplifier ticks

specConstrThreshold :: Maybe Int

Threshold for SpecConstr

specConstrCount :: Maybe Int

Max number of specialisations for any one function

specConstrRecursive :: Int

Max number of specialisations for recursive types Not optional; otherwise ForceSpecConstr can diverge.

liberateCaseThreshold :: Maybe Int

Threshold for LiberateCase

floatLamArgs :: Maybe Int

Arg count for lambda floating See CoreMonad.FloatOutSwitches

historySize :: Int
 
cmdlineHcIncludes :: [String]
-#includes
importPaths :: [FilePath]
 
mainModIs :: Module
 
mainFunIs :: Maybe String
 
ctxtStkDepth :: Int

Typechecker context stack depth

tyFunStkDepth :: Int

Typechecker type function stack depth

thisPackage :: PackageId

name of package currently being compiled

ways :: [Way]

Way flags from the command line

buildTag :: String

The global "way" (e.g. "p" for prof)

rtsBuildTag :: String

The RTS "way"

splitInfo :: Maybe (String, Int)
 
objectDir :: Maybe String
 
dylibInstallName :: Maybe String
 
hiDir :: Maybe String
 
stubDir :: Maybe String
 
dumpDir :: Maybe String
 
objectSuf :: String
 
hcSuf :: String
 
hiSuf :: String
 
canGenerateDynamicToo :: IORef Bool
 
dynObjectSuf :: String
 
dynHiSuf :: String
 
dllSplitFile :: Maybe FilePath
 
dllSplit :: Maybe [Set String]
 
outputFile :: Maybe String
 
dynOutputFile :: Maybe String
 
outputHi :: Maybe String
 
dynLibLoader :: DynLibLoader
 
dumpPrefix :: Maybe FilePath

This is set by runPipeline based on where its output is going.

dumpPrefixForce :: Maybe FilePath

Override the dumpPrefix set by runPipeline. Set by -ddump-file-prefix

ldInputs :: [Option]
 
includePaths :: [String]
 
libraryPaths :: [String]
 
frameworkPaths :: [String]
 
cmdlineFrameworks :: [String]
 
rtsOpts :: Maybe String
 
rtsOptsEnabled :: RtsOptsEnabled
 
hpcDir :: String

Path to store the .mix files

pluginModNames :: [ModuleName]
 
pluginModNameOpts :: [(ModuleName, String)]
 
hooks :: Hooks
 
depMakefile :: FilePath
 
depIncludePkgDeps :: Bool
 
depExcludeMods :: [ModuleName]
 
depSuffixes :: [String]
 
extraPkgConfs :: [PkgConfRef] -> [PkgConfRef]

The -package-db flags given on the command line, in the order they appeared.

packageFlags :: [PackageFlag]

The -package and -hide-package flags from the command-line

pkgDatabase :: Maybe [PackageConfig]
 
pkgState :: PackageState
 
filesToClean :: IORef [FilePath]
 
dirsToClean :: IORef (Map FilePath FilePath)
 
filesToNotIntermediateClean :: IORef [FilePath]
 
nextTempSuffix :: IORef Int
 
generatedDumps :: IORef (Set FilePath)
 
dumpFlags :: IntSet
 
generalFlags :: IntSet
 
warningFlags :: IntSet
 
language :: Maybe Language
 
safeHaskell :: SafeHaskellMode

Safe Haskell mode

thOnLoc :: SrcSpan
 
newDerivOnLoc :: SrcSpan
 
pkgTrustOnLoc :: SrcSpan
 
warnSafeOnLoc :: SrcSpan
 
warnUnsafeOnLoc :: SrcSpan
 
extensions :: [OnOff ExtensionFlag]
 
extensionFlags :: IntSet
 
ufCreationThreshold :: Int
 
ufUseThreshold :: Int
 
ufFunAppDiscount :: Int
 
ufDictDiscount :: Int
 
ufKeenessFactor :: Float
 
ufDearOp :: Int
 
maxWorkerArgs :: Int
 
ghciHistSize :: Int
 
log_action :: LogAction

MsgDoc output action: use ErrUtils instead of this if you can

flushOut :: FlushOut
 
flushErr :: FlushErr
 
haddockOptions :: Maybe String
 
ghciScripts :: [String]
 
pprUserLength :: Int
 
pprCols :: Int
 
traceLevel :: Int
 
useUnicodeQuotes :: Bool
 
profAuto :: ProfAuto

what kind of {--} to add automatically

interactivePrint :: Maybe String
 
llvmVersion :: IORef Int
 
nextWrapperNum :: IORef (ModuleEnv Int)
 
sseVersion :: Maybe (Int, Int)

Machine dependant flags (-mblah stuff)

avx :: Bool
 
avx2 :: Bool
 
avx512cd :: Bool
 
avx512er :: Bool
 
avx512f :: Bool
 
avx512pf :: Bool
 
rtldInfo :: IORef (Maybe LinkerInfo)

Run-time linker information (what options we need, etc.)

rtccInfo :: IORef (Maybe CompilerInfo)

Run-time compiler information

data HscTarget Source

The target code type of the compilation (if any).

Whenever you change the target, also make sure to set ghcLink to something sensible.

HscNothing can be used to avoid generating any output, however, note that:

  • If a program uses Template Haskell the typechecker may try to run code from an imported module. This will fail if no code has been generated for this module. You can use needsTemplateHaskell to detect whether this might be the case and choose to either switch to a different target or avoid typechecking such modules. (The latter may be preferable for security reasons.)

Constructors

HscC

Generate C code.

HscAsm

Generate assembly using the native code generator.

HscLlvm

Generate assembly using the llvm code generator.

HscInterpreted

Generate bytecode. (Requires LinkInMemory)

HscNothing

Don't generate any code. See notes above.

isObjectTarget :: HscTarget -> Bool Source

Will this target result in an object file on the disk?

defaultObjectTarget :: Platform -> HscTarget Source

The HscTarget value corresponding to the default way to create object files on the current platform.

targetRetainsAllBindings :: HscTarget -> Bool Source

Does this target retain *all* top-level bindings for a module, rather than just the exported bindings, in the TypeEnv and compiled code (if any)? In interpreted mode we do this, so that GHCi can call functions inside a module. In HscNothing mode we also do it, so that Haddock can get access to the GlobalRdrEnv for a module after typechecking it.

data GhcMode Source

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 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.

Constructors

CompManager

--make, GHCi, etc.

OneShot
ghc -c Foo.hs
MkDepend

ghc -M, see Finder for why we need this

data GhcLink Source

What to do in the link step, if there is one.

Constructors

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

data Option Source

When invoking external tools as part of the compilation pipeline, we pass these a sequence of options on the command-line. Rather than just using a list of Strings, we use a type that allows us to distinguish between filepaths and 'other stuff'. The reason for this is that this type gives us a handle on transforming filenames, and filenames only, to whatever format they're expected to be on a particular platform.

Instances

fFlags :: [FlagSpec GeneralFlag] Source

These -f<blah> flags can all be reversed with -fno-<blah>

fWarningFlags :: [FlagSpec WarningFlag] Source

These -f<blah> flags can all be reversed with -fno-<blah>

fLangFlags :: [FlagSpec ExtensionFlag] Source

These -f<blah> flags can all be reversed with -fno-<blah>

xFlags :: [FlagSpec ExtensionFlag] Source

These -Xblah flags can all be reversed with -XNoblah

dynFlagDependencies :: DynFlags -> [ModuleName] Source

Some modules have dependencies on others through the DynFlags rather than textual imports

Safe Haskell

safeHaskellOn :: DynFlags -> Bool Source

Is Safe Haskell on in some way (including inference mode)

safeImportsOn :: DynFlags -> Bool Source

Test if Safe Imports are on in some form

safeLanguageOn :: DynFlags -> Bool Source

Is the Safe Haskell safe language in use

safeInferOn :: DynFlags -> Bool Source

Is the Safe Haskell safe inference mode active

packageTrustOn :: DynFlags -> Bool Source

Is the -fpackage-trust mode on

safeDirectImpsReq :: DynFlags -> Bool Source

Are all direct imports required to be safe for this Safe Haskell mode? Direct imports are when the code explicitly imports a module

safeImplicitImpsReq :: DynFlags -> Bool Source

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.

unsafeFlags :: [(String, DynFlags -> SrcSpan, DynFlags -> Bool, DynFlags -> DynFlags)] Source

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

System tool settings and locations

Manipulating DynFlags

defaultDynFlags :: Settings -> DynFlags Source

The normal DynFlags. Note that they is not suitable for use in this form and must be fully initialized by runGhc first.

initDynFlags :: DynFlags -> IO DynFlags Source

Used by runGhc to partially initialize a new DynFlags value

getOpts Source

Arguments

:: DynFlags

DynFlags to retrieve the options from

-> (DynFlags -> [a])

Relevant record accessor: one of the opt_* accessors

-> [a]

Correctly ordered extracted options

Retrieve the options corresponding to a particular opt_* field in the correct order

getVerbFlags :: DynFlags -> [String] Source

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

updOptLevel :: Int -> DynFlags -> DynFlags Source

Sets the DynFlags to be appropriate to the optimisation level

Parsing DynFlags

parseDynamicFlagsCmdLine Source

Arguments

:: MonadIO m 
=> DynFlags 
-> [Located String] 
-> m (DynFlags, [Located String], [Located String])

Updated DynFlags, left-over arguments, and list of warnings.

Parse dynamic flags from a list of command line arguments. Returns the 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).

parseDynamicFilePragma Source

Arguments

:: MonadIO m 
=> DynFlags 
-> [Located String] 
-> m (DynFlags, [Located String], [Located String])

Updated DynFlags, left-over arguments, and list of warnings.

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.

parseDynamicFlagsFull Source

Arguments

:: 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], [Located String]) 

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.

Available DynFlags

allFlags :: [String] Source

All dynamic flags option strings. These are the user facing strings for enabling and disabling options.

DynFlags C compiler options

Configuration of the stg-to-stg passes

Compiler configuration suitable for display to the user

SSE and AVX

Linker/compiler information