ghc-8.2.1: The GHC API

Safe HaskellNone
LanguageHaskell2010

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 DumpFlag Source #

Constructors

Opt_D_dump_cmm 
Opt_D_dump_cmm_from_stg 
Opt_D_dump_cmm_raw 
Opt_D_dump_cmm_verbose 
Opt_D_dump_cmm_cfg 
Opt_D_dump_cmm_cbe 
Opt_D_dump_cmm_switch 
Opt_D_dump_cmm_proc 
Opt_D_dump_cmm_sp 
Opt_D_dump_cmm_sink 
Opt_D_dump_cmm_caf 
Opt_D_dump_cmm_procmap 
Opt_D_dump_cmm_split 
Opt_D_dump_cmm_info 
Opt_D_dump_cmm_cps 
Opt_D_dump_asm 
Opt_D_dump_asm_native 
Opt_D_dump_asm_liveness 
Opt_D_dump_asm_regalloc 
Opt_D_dump_asm_regalloc_stages 
Opt_D_dump_asm_conflicts 
Opt_D_dump_asm_stats 
Opt_D_dump_asm_expanded 
Opt_D_dump_llvm 
Opt_D_dump_core_stats 
Opt_D_dump_deriv 
Opt_D_dump_ds 
Opt_D_dump_foreign 
Opt_D_dump_inlinings 
Opt_D_dump_rule_firings 
Opt_D_dump_rule_rewrites 
Opt_D_dump_simpl_trace 
Opt_D_dump_occur_anal 
Opt_D_dump_parsed 
Opt_D_dump_parsed_ast 
Opt_D_dump_rn 
Opt_D_dump_rn_ast 
Opt_D_dump_shape 
Opt_D_dump_simpl 
Opt_D_dump_simpl_iterations 
Opt_D_dump_spec 
Opt_D_dump_prep 
Opt_D_dump_stg 
Opt_D_dump_call_arity 
Opt_D_dump_stranal 
Opt_D_dump_str_signatures 
Opt_D_dump_tc 
Opt_D_dump_tc_ast 
Opt_D_dump_types 
Opt_D_dump_rules 
Opt_D_dump_cse 
Opt_D_dump_worker_wrapper 
Opt_D_dump_rn_trace 
Opt_D_dump_rn_stats 
Opt_D_dump_opt_cmm 
Opt_D_dump_simpl_stats 
Opt_D_dump_cs_trace 
Opt_D_dump_tc_trace 
Opt_D_dump_ec_trace 
Opt_D_dump_if_trace 
Opt_D_dump_vt_trace 
Opt_D_dump_splices 
Opt_D_th_dec_file 
Opt_D_dump_BCOs 
Opt_D_dump_vect 
Opt_D_dump_ticked 
Opt_D_dump_rtti 
Opt_D_source_stats 
Opt_D_verbose_stg2stg 
Opt_D_dump_hi 
Opt_D_dump_hi_diffs 
Opt_D_dump_mod_cycles 
Opt_D_dump_mod_map 
Opt_D_dump_view_pattern_commoning 
Opt_D_verbose_core2core 
Opt_D_dump_debug 
Opt_D_dump_json 
Opt_D_ppr_debug 
Opt_D_no_debug_output 

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_DoAnnotationLinting 
Opt_NoLlvmMangler 
Opt_WarnIsError 
Opt_ShowWarnGroups 
Opt_HideSourcePaths 
Opt_PrintExplicitForalls 
Opt_PrintExplicitKinds 
Opt_PrintExplicitCoercions 
Opt_PrintExplicitRuntimeReps 
Opt_PrintEqualityRelations 
Opt_PrintUnicodeSyntax 
Opt_PrintExpandedSynonyms 
Opt_PrintPotentialInstances 
Opt_PrintTypecheckerElaboration 
Opt_CallArity 
Opt_Strictness 
Opt_LateDmdAnal 
Opt_KillAbsence 
Opt_KillOneShot 
Opt_FullLaziness 
Opt_FloatIn 
Opt_Specialise 
Opt_SpecialiseAggressively 
Opt_CrossModuleSpecialise 
Opt_StaticArgumentTransformation 
Opt_CSE 
Opt_StgCSE 
Opt_LiberateCase 
Opt_SpecConstr 
Opt_SpecConstrKeen 
Opt_DoLambdaEtaExpansion 
Opt_IgnoreAsserts 
Opt_DoEtaReduction 
Opt_CaseMerge 
Opt_CaseFolding 
Opt_UnboxStrictFields 
Opt_UnboxSmallStrictFields 
Opt_DictsCheap 
Opt_EnableRewriteRules 
Opt_Vectorise 
Opt_VectorisationAvoidance 
Opt_RegsGraph 
Opt_RegsIterative 
Opt_PedanticBottoms 
Opt_LlvmTBAA 
Opt_LlvmPassVectorsInRegisters 
Opt_LlvmFillUndefWithGarbage 
Opt_IrrefutableTuples 
Opt_CmmSink 
Opt_CmmElimCommonBlocks 
Opt_OmitYields 
Opt_FunToThunk 
Opt_DictsStrict 
Opt_DmdTxDictSel 
Opt_Loopification 
Opt_CprAnal 
Opt_WorkerWrapper 
Opt_SolveConstantDicts 
Opt_IgnoreInterfacePragmas 
Opt_OmitInterfacePragmas 
Opt_ExposeAllUnfoldings 
Opt_WriteInterface 
Opt_AutoSccsOnIndividualCafs 
Opt_ProfCountEntries 
Opt_Pp 
Opt_ForceRecomp 
Opt_ExcessPrecision 
Opt_EagerBlackHoling 
Opt_NoHsMain 
Opt_SplitObjs 
Opt_SplitSections 
Opt_StgStats 
Opt_HideAllPackages 
Opt_HideAllPluginPackages 
Opt_PrintBindResult 
Opt_Haddock 
Opt_HaddockOptions 
Opt_BreakOnException 
Opt_BreakOnError 
Opt_PrintEvldWithShow 
Opt_PrintBindContents 
Opt_GenManifest 
Opt_EmbedManifest 
Opt_SharedImplib 
Opt_BuildingCabalPackage 
Opt_IgnoreDotGhci 
Opt_GhciSandbox 
Opt_GhciHistory 
Opt_LocalGhciHistory 
Opt_HelpfulErrors 
Opt_DeferTypeErrors 
Opt_DeferTypedHoles 
Opt_DeferOutOfScopeVariables 
Opt_PIC 
Opt_SccProfilingOn 
Opt_Ticky 
Opt_Ticky_Allocd 
Opt_Ticky_LNE 
Opt_Ticky_Dyn_Thunk 
Opt_RPath 
Opt_RelativeDynlibPaths 
Opt_Hpc 
Opt_FlatCache 
Opt_ExternalInterpreter 
Opt_OptimalApplicativeDo 
Opt_VersionMacros 
Opt_WholeArchiveHsLibs 
Opt_SimplPreInlining 
Opt_ErrorSpans 
Opt_DiagnosticsShowCaret 
Opt_PprCaseAsLet 
Opt_PprShowTicks 
Opt_ShowHoleConstraints 
Opt_SuppressCoercions 
Opt_SuppressVarKinds 
Opt_SuppressModulePrefixes 
Opt_SuppressTypeApplications 
Opt_SuppressIdInfo 
Opt_SuppressUnfoldings 
Opt_SuppressTypeSignatures 
Opt_SuppressUniques 
Opt_SuppressTicks 
Opt_AutoLinkPackages 
Opt_ImplicitImportQualified 
Opt_KeepHiDiffs 
Opt_KeepHcFiles 
Opt_KeepSFiles 
Opt_KeepTmpFiles 
Opt_KeepRawTokenStream 
Opt_KeepLlvmFiles 
Opt_KeepHiFiles 
Opt_KeepOFiles 
Opt_BuildDynamicToo 
Opt_DistrustAllPackages 
Opt_PackageTrust 
Opt_G_NoStateHack 
Opt_G_NoOptCoercion 

data WarningFlag Source #

Constructors

Opt_WarnDuplicateExports 
Opt_WarnDuplicateConstraints 
Opt_WarnRedundantConstraints 
Opt_WarnHiShadows 
Opt_WarnImplicitPrelude 
Opt_WarnIncompletePatterns 
Opt_WarnIncompleteUniPatterns 
Opt_WarnIncompletePatternsRecUpd 
Opt_WarnOverflowedLiterals 
Opt_WarnEmptyEnumerations 
Opt_WarnMissingFields 
Opt_WarnMissingImportList 
Opt_WarnMissingMethods 
Opt_WarnMissingSignatures 
Opt_WarnMissingLocalSignatures 
Opt_WarnNameShadowing 
Opt_WarnOverlappingPatterns 
Opt_WarnTypeDefaults 
Opt_WarnMonomorphism 
Opt_WarnUnusedTopBinds 
Opt_WarnUnusedLocalBinds 
Opt_WarnUnusedPatternBinds 
Opt_WarnUnusedImports 
Opt_WarnUnusedMatches 
Opt_WarnUnusedTypePatterns 
Opt_WarnUnusedForalls 
Opt_WarnWarningsDeprecations 
Opt_WarnDeprecatedFlags 
Opt_WarnAMP 
Opt_WarnMissingMonadFailInstances 
Opt_WarnSemigroup 
Opt_WarnDodgyExports 
Opt_WarnDodgyImports 
Opt_WarnOrphans 
Opt_WarnAutoOrphans 
Opt_WarnIdentities 
Opt_WarnTabs 
Opt_WarnUnrecognisedPragmas 
Opt_WarnDodgyForeignImports 
Opt_WarnUnusedDoBind 
Opt_WarnWrongDoBind 
Opt_WarnAlternativeLayoutRuleTransitional 
Opt_WarnUnsafe 
Opt_WarnSafe 
Opt_WarnTrustworthySafe 
Opt_WarnMissedSpecs 
Opt_WarnAllMissedSpecs 
Opt_WarnUnsupportedCallingConventions 
Opt_WarnUnsupportedLlvmVersion 
Opt_WarnInlineRuleShadowing 
Opt_WarnTypedHoles 
Opt_WarnPartialTypeSignatures 
Opt_WarnMissingExportedSignatures 
Opt_WarnUntickedPromotedConstructors 
Opt_WarnDerivingTypeable 
Opt_WarnDeferredTypeErrors 
Opt_WarnDeferredOutOfScopeVariables 
Opt_WarnNonCanonicalMonadInstances 
Opt_WarnNonCanonicalMonadFailInstances 
Opt_WarnNonCanonicalMonoidInstances 
Opt_WarnMissingPatternSynonymSignatures 
Opt_WarnUnrecognisedWarningFlags 
Opt_WarnSimplifiableClassConstraints 
Opt_WarnCPPUndef 
Opt_WarnUnbangedStrictPatterns 
Opt_WarnMissingHomeModules 

data WarnReason Source #

Used when outputting warnings: if a reason is given, it is displayed. If a warning isn't controlled by a flag, this is made explicit at the point of use.

Constructors

NoReason 
Reason !WarningFlag 

data PlatformConstants Source #

Constructors

PlatformConstants 

Fields

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

warningGroups :: [(String, [WarningFlag])] Source #

Warning groups.

As all warnings are in the Weverything set, it is ignored when displaying to the user which group a warning is in.

warningHierarchies :: [[String]] Source #

Warning group hierarchies, where there is an explicit inclusion relation.

Each inner list is a hierarchy of warning groups, ordered from smallest to largest, where each group is a superset of the one before it.

Separating this from warningGroups allows for multiple hierarchies with no inherent relation to be defined.

The special-case Weverything group is not included.

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

wopt_fatal :: WarningFlag -> DynFlags -> Bool Source #

Test whether a WarningFlag is set as fatal

xopt :: Extension -> DynFlags -> Bool Source #

Test whether a Extension is set

useUnicodeSyntax :: DynFlags -> Bool Source #

An internal helper to check whether to use unicode syntax for output.

Note: You should very likely be using unicodeSyntax instead of this function.

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

data FlagSpec flag Source #

Constructors

FlagSpec 

Fields

class HasDynFlags m where Source #

Minimal complete definition

getDynFlags

Instances

HasDynFlags PD Source # 
HasDynFlags LlvmM Source # 
HasDynFlags FCode Source # 
HasDynFlags CmmParse Source # 
HasDynFlags Hsc Source # 
HasDynFlags CompPipeline Source # 
HasDynFlags Ghc Source # 
HasDynFlags CoreM Source # 
HasDynFlags SimplM Source # 
HasDynFlags TcS Source # 
HasDynFlags VM Source # 
HasDynFlags NatM Source # 
(Monad m, HasDynFlags m) => HasDynFlags (MaybeT m) Source # 
ContainsDynFlags env => HasDynFlags (IOEnv env) Source # 
HasDynFlags (RegM a) Source # 
MonadIO m => HasDynFlags (GhcT m) Source # 
(Monoid a, Monad m, HasDynFlags m) => HasDynFlags (WriterT a m) Source # 
(Monad m, HasDynFlags m) => HasDynFlags (ExceptT e m) Source # 
(Monad m, HasDynFlags m) => HasDynFlags (ReaderT * a m) Source # 

class ContainsDynFlags t where Source #

Minimal complete definition

extractDynFlags

Instances

ContainsDynFlags (Env gbl lcl) Source # 

Methods

extractDynFlags :: Env gbl lcl -> DynFlags Source #

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 PackageFlag Source #

Flags for manipulating packages visibility.

Constructors

ExposePackage String PackageArg ModRenaming

-package, -package-id

HidePackage String
-hide-package

data PackageArg Source #

We accept flags which make packages visible, but how they select the package varies; this data type reflects what selection criterion is used.

Constructors

PackageArg String

-package, by PackageName

UnitIdArg UnitId

-package-id, by UnitId

data ModRenaming Source #

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)]

Constructors

ModRenaming 

Fields

newtype IgnorePackageFlag Source #

Flags for manipulating the set of non-broken packages.

Constructors

IgnorePackage String
-ignore-package

data TrustFlag Source #

Flags for manipulating package trust.

Constructors

TrustPackage String
-trust
DistrustPackage String
-distrust

Instances

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

Eq Option Source # 

Methods

(==) :: Option -> Option -> Bool #

(/=) :: Option -> Option -> Bool #

fFlags :: [FlagSpec GeneralFlag] Source #

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

fLangFlags :: [FlagSpec Extension] Source #

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

xFlags :: [FlagSpec Extension] Source #

These -Xblah flags can all be reversed with -XNoblah

wWarningFlags :: [FlagSpec WarningFlag] Source #

These -W<blah> flags can all be reversed with -Wno-<blah>

dynFlagDependencies :: DynFlags -> [ModuleName] Source #

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

makeDynFlagsConsistent :: DynFlags -> (DynFlags, [Located String]) Source #

Resolve any internal inconsistencies in a set of DynFlags. Returns the consistent DynFlags as well as a list of warnings to report to the user.

data Way Source #

Instances

Eq Way Source # 

Methods

(==) :: Way -> Way -> Bool #

(/=) :: Way -> Way -> Bool #

Ord Way Source # 

Methods

compare :: Way -> Way -> Ordering #

(<) :: Way -> Way -> Bool #

(<=) :: Way -> Way -> Bool #

(>) :: Way -> Way -> Bool #

(>=) :: Way -> Way -> Bool #

max :: Way -> Way -> Way #

min :: Way -> Way -> Way #

Show Way Source # 

Methods

showsPrec :: Int -> Way -> ShowS #

show :: Way -> String #

showList :: [Way] -> ShowS #

Log output

putLogMsg :: DynFlags -> WarnReason -> Severity -> SrcSpan -> PprStyle -> MsgDoc -> IO () Source #

Write an error or warning to the LogOutput.

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

unsafeFlagsForInfer :: [(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

versionedAppDir :: DynFlags -> MaybeT IO FilePath Source #

The directory for this version of ghc in the user's app directory (typically something like ~.ghcx86_64-linux-7.6.3)

Manipulating DynFlags

defaultDynFlags :: Settings -> DynFlags Source #

The normal DynFlags. Note that they are 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

defaultLogActionHPrintDoc :: DynFlags -> Handle -> SDoc -> PprStyle -> IO () Source #

Like defaultLogActionHPutStrDoc but appends an extra newline.

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

interpretPackageEnv :: DynFlags -> IO DynFlags Source #

Find the package environment (if one exists)

We interpret the package environment as a set of package flags; to be specific, if we find a package environment file like

clear-package-db
global-package-db
package-db blah/package.conf.d
package-id id1
package-id id2

we interpret this as

[ -hide-all-packages
, -clear-package-db
, -global-package-db
, -package-db blah/package.conf.d
, -package-id id1
, -package-id id2
]

There's also an older syntax alias for package-id, which is just an unadorned package id

id1
id2

canonicalizeHomeModule :: DynFlags -> ModuleName -> Module Source #

Given a ModuleName of a signature in the home library, find out how it is instantiated. E.g., the canonical form of A in p[A=q[]:A] is q[]:A.

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

allNonDeprecatedFlags :: [String] Source #

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

flagsForCompletion :: Bool -> [String] Source #

Make a list of flags for shell completion. Filter all available flags into two groups, for interactive GHC vs all other.

DynFlags C compiler options

Compiler configuration suitable for display to the user

rtsIsProfiled :: Bool Source #

Was the runtime system built with profiling enabled?

SSE and AVX

Linker/compiler information