ghc-9.6.0.20230302: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Driver.Session

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 #

Debugging flags

Constructors

Opt_D_dump_cmm 
Opt_D_dump_cmm_from_stg 
Opt_D_dump_cmm_raw 
Opt_D_dump_cmm_verbose_by_proc 
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_cmm_thread_sanitizer 
Opt_D_dump_cfg_weights

Dump the cfg used for block layout.

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_c_backend 
Opt_D_dump_llvm 
Opt_D_dump_js 
Opt_D_dump_core_stats 
Opt_D_dump_deriv 
Opt_D_dump_ds 
Opt_D_dump_ds_preopt 
Opt_D_dump_foreign 
Opt_D_dump_inlinings 
Opt_D_dump_verbose_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_simpl 
Opt_D_dump_simpl_iterations 
Opt_D_dump_spec 
Opt_D_dump_prep 
Opt_D_dump_late_cc 
Opt_D_dump_stg_from_core

Initial STG (CoreToStg output)

Opt_D_dump_stg_unarised

STG after unarise

Opt_D_dump_stg_cg

STG (after stg2stg)

Opt_D_dump_stg_tags

Result of tag inference analysis.

Opt_D_dump_stg_final

Final STG (before cmm gen)

Opt_D_dump_call_arity 
Opt_D_dump_exitify 
Opt_D_dump_stranal 
Opt_D_dump_str_signatures 
Opt_D_dump_cpranal 
Opt_D_dump_cpr_signatures 
Opt_D_dump_tc 
Opt_D_dump_tc_ast 
Opt_D_dump_hie 
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_splices 
Opt_D_th_dec_file 
Opt_D_dump_BCOs 
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_timings 
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 
Opt_D_dump_faststrings 
Opt_D_faststring_stats 

data GeneralFlag Source #

Enumerates the simple on-or-off dynamic flags

Constructors

Opt_DumpToFile

Append dump output to files instead of stdout.

Opt_DumpWithWays

Use foo.ways.dumpFlag instead of foo.dumpFlag

Opt_D_dump_minimal_imports 
Opt_DoCoreLinting 
Opt_DoLinearCoreLinting 
Opt_DoStgLinting 
Opt_DoCmmLinting 
Opt_DoAsmLinting 
Opt_DoAnnotationLinting 
Opt_DoBoundsChecking 
Opt_NoLlvmMangler 
Opt_FastLlvm 
Opt_NoTypeableBinds 
Opt_DistinctConstructorTables 
Opt_InfoTableMap 
Opt_WarnIsError 
Opt_ShowWarnGroups 
Opt_HideSourcePaths 
Opt_PrintExplicitForalls 
Opt_PrintExplicitKinds 
Opt_PrintExplicitCoercions 
Opt_PrintExplicitRuntimeReps 
Opt_PrintEqualityRelations 
Opt_PrintAxiomIncomps 
Opt_PrintUnicodeSyntax 
Opt_PrintExpandedSynonyms 
Opt_PrintPotentialInstances 
Opt_PrintRedundantPromotionTicks 
Opt_PrintTypecheckerElaboration 
Opt_CallArity 
Opt_Exitification 
Opt_Strictness 
Opt_LateDmdAnal 
Opt_KillAbsence 
Opt_KillOneShot 
Opt_FullLaziness 
Opt_FloatIn 
Opt_LocalFloatOut

Enable floating out of let-bindings in the simplifier

Opt_LocalFloatOutTopLevel

Enable floating out of let-bindings at the top level in the simplifier N.B. See Note [RHS Floating]

Opt_LateSpecialise 
Opt_Specialise 
Opt_SpecialiseAggressively 
Opt_CrossModuleSpecialise 
Opt_InlineGenerics 
Opt_InlineGenericsAggressively 
Opt_StaticArgumentTransformation 
Opt_CSE 
Opt_StgCSE 
Opt_StgLiftLams 
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_EnableThSpliceWarnings 
Opt_RegsGraph 
Opt_RegsIterative 
Opt_PedanticBottoms 
Opt_LlvmTBAA 
Opt_LlvmFillUndefWithGarbage 
Opt_IrrefutableTuples 
Opt_CmmSink 
Opt_CmmStaticPred 
Opt_CmmElimCommonBlocks 
Opt_CmmControlFlow 
Opt_AsmShortcutting 
Opt_OmitYields 
Opt_FunToThunk 
Opt_DictsStrict 
Opt_DmdTxDictSel

deprecated, no effect and behaviour is now default. Allowed switching of a special demand transformer for dictionary selectors

Opt_Loopification 
Opt_CfgBlocklayout

Use the cfg based block layout algorithm.

Opt_WeightlessBlocklayout

Layout based on last instruction per block.

Opt_CprAnal 
Opt_WorkerWrapper 
Opt_WorkerWrapperUnlift

Do W/W split for unlifting even if we won't unbox anything.

Opt_SolveConstantDicts 
Opt_AlignmentSanitisation 
Opt_CatchNonexhaustiveCases 
Opt_NumConstantFolding 
Opt_CoreConstantFolding 
Opt_FastPAPCalls 
Opt_DoTagInferenceChecks 
Opt_SimplPreInlining 
Opt_IgnoreInterfacePragmas 
Opt_OmitInterfacePragmas 
Opt_ExposeAllUnfoldings 
Opt_WriteInterface 
Opt_WriteHie 
Opt_AutoSccsOnIndividualCafs 
Opt_ProfCountEntries 
Opt_ProfLateInlineCcs 
Opt_ProfLateCcs 
Opt_ProfManualCcs

Ignore manual SCC annotations

Opt_Pp 
Opt_ForceRecomp 
Opt_IgnoreOptimChanges 
Opt_IgnoreHpcChanges 
Opt_ExcessPrecision 
Opt_EagerBlackHoling 
Opt_NoHsMain 
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_GhciLeakCheck 
Opt_ValidateHie 
Opt_LocalGhciHistory 
Opt_NoIt 
Opt_HelpfulErrors 
Opt_DeferTypeErrors 
Opt_DeferTypedHoles 
Opt_DeferOutOfScopeVariables 
Opt_PIC
-fPIC
Opt_PIE
-fPIE
Opt_PICExecutable
-pie
Opt_ExternalDynamicRefs 
Opt_Ticky 
Opt_Ticky_Allocd 
Opt_Ticky_LNE 
Opt_Ticky_Dyn_Thunk 
Opt_Ticky_Tag 
Opt_Ticky_AP

Use regular thunks even when we could use std ap thunks in order to get entry counts

Opt_CmmThreadSanitizer 
Opt_RPath 
Opt_RelativeDynlibPaths 
Opt_CompactUnwind
-fcompact-unwind
Opt_Hpc 
Opt_FamAppCache 
Opt_ExternalInterpreter 
Opt_OptimalApplicativeDo 
Opt_VersionMacros 
Opt_WholeArchiveHsLibs 
Opt_SingleLibFolder 
Opt_ExposeInternalSymbols 
Opt_KeepCAFs 
Opt_KeepGoing 
Opt_ByteCode 
Opt_ByteCodeAndObjectCode 
Opt_LinkRts 
Opt_ErrorSpans 
Opt_DeferDiagnostics 
Opt_DiagnosticsShowCaret 
Opt_PprCaseAsLet 
Opt_PprShowTicks 
Opt_ShowHoleConstraints 
Opt_ShowValidHoleFits 
Opt_SortValidHoleFits 
Opt_SortBySizeHoleFits 
Opt_SortBySubsumHoleFits 
Opt_AbstractRefHoleFits 
Opt_UnclutterValidHoleFits 
Opt_ShowTypeAppOfHoleFits 
Opt_ShowTypeAppVarsOfHoleFits 
Opt_ShowDocsOfHoleFits 
Opt_ShowTypeOfHoleFits 
Opt_ShowProvOfHoleFits 
Opt_ShowMatchesOfHoleFits 
Opt_ShowLoadedModules 
Opt_HexWordLiterals 
Opt_SuppressCoercions 
Opt_SuppressCoercionTypes 
Opt_SuppressVarKinds 
Opt_SuppressModulePrefixes 
Opt_SuppressTypeApplications 
Opt_SuppressIdInfo 
Opt_SuppressUnfoldings 
Opt_SuppressTypeSignatures 
Opt_SuppressUniques 
Opt_SuppressStgExts 
Opt_SuppressStgReps 
Opt_SuppressTicks 
Opt_SuppressTimestamps

Suppress timestamps in dumps

Opt_SuppressCoreSizes

Suppress per binding Core size stats in dumps

Opt_ShowErrorContext 
Opt_AutoLinkPackages 
Opt_ImplicitImportQualified 
Opt_KeepHscppFiles 
Opt_KeepHiDiffs 
Opt_KeepHcFiles 
Opt_KeepSFiles 
Opt_KeepTmpFiles 
Opt_KeepRawTokenStream 
Opt_KeepLlvmFiles 
Opt_KeepHiFiles 
Opt_KeepOFiles 
Opt_BuildDynamicToo 
Opt_WriteIfSimplifiedCore 
Opt_UseBytecodeRatherThanObjects 
Opt_DistrustAllPackages 
Opt_PackageTrust 
Opt_PluginTrustworthy 
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_WarnUnusedRecordWildcards 
Opt_WarnRedundantBangPatterns 
Opt_WarnRedundantRecordWildcards 
Opt_WarnWarningsDeprecations 
Opt_WarnDeprecatedFlags 
Opt_WarnMissingMonadFailInstances 
Opt_WarnSemigroup 
Opt_WarnDodgyExports 
Opt_WarnDodgyImports 
Opt_WarnOrphans 
Opt_WarnAutoOrphans 
Opt_WarnIdentities 
Opt_WarnTabs 
Opt_WarnUnrecognisedPragmas 
Opt_WarnMisplacedPragmas 
Opt_WarnDodgyForeignImports 
Opt_WarnUnusedDoBind 
Opt_WarnWrongDoBind 
Opt_WarnAlternativeLayoutRuleTransitional 
Opt_WarnUnsafe 
Opt_WarnSafe 
Opt_WarnTrustworthySafe 
Opt_WarnMissedSpecs 
Opt_WarnAllMissedSpecs 
Opt_WarnUnsupportedCallingConventions 
Opt_WarnUnsupportedLlvmVersion 
Opt_WarnMissedExtraSharedLib 
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 
Opt_WarnPartialFields 
Opt_WarnMissingExportList 
Opt_WarnInaccessibleCode 
Opt_WarnStarIsType 
Opt_WarnStarBinder 
Opt_WarnImplicitKindVars 
Opt_WarnSpaceAfterBang 
Opt_WarnMissingDerivingStrategies 
Opt_WarnPrepositiveQualifiedModule 
Opt_WarnUnusedPackages 
Opt_WarnInferredSafeImports 
Opt_WarnMissingSafeHaskellMode 
Opt_WarnCompatUnqualifiedImports 
Opt_WarnDerivingDefaults 
Opt_WarnInvalidHaddock 
Opt_WarnOperatorWhitespaceExtConflict 
Opt_WarnOperatorWhitespace 
Opt_WarnAmbiguousFields 
Opt_WarnImplicitLift 
Opt_WarnMissingKindSignatures 
Opt_WarnMissingExportedPatternSynonymSignatures 
Opt_WarnRedundantStrictnessFlags 
Opt_WarnForallIdentifier 
Opt_WarnUnicodeBidirectionalFormatCharacters 
Opt_WarnGADTMonoLocalBinds 
Opt_WarnTypeEqualityOutOfScope 
Opt_WarnTypeEqualityRequiresOperators 
Opt_WarnLoopySuperclassSolve 

data DiagnosticReason Source #

The reason why a Diagnostic was emitted in the first place. Diagnostic messages are born within GHC with a very precise reason, which can be completely statically-computed (i.e. this is an error or a warning no matter what), or influenced by the specific state of the DynFlags at the moment of the creation of a new Diagnostic. For example, a parsing error is always going to be an error, whereas a 'WarningWithoutFlag Opt_WarnUnusedImports' might turn into an error due to '-Werror' or '-Werror=warn-unused-imports'. Interpreting a DiagnosticReason together with its associated Severity gives us the full picture.

Constructors

WarningWithoutFlag

Born as a warning.

WarningWithFlag !WarningFlag

Warning was enabled with the flag.

ErrorWithoutFlag

Born as an error.

newtype FlushOut Source #

Constructors

FlushOut (IO ()) 

data ProfAuto Source #

What kind of {-# SCC #-} to add automatically

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

dopt :: DumpFlag -> DynFlags -> Bool Source #

Test whether a DumpFlag is set

gopt :: GeneralFlag -> DynFlags -> Bool Source #

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.

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

wopt_set_fatal :: DynFlags -> WarningFlag -> DynFlags Source #

Mark a WarningFlag as fatal (do not set the flag)

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

Test whether a Extension is set

xopt_set_unlessExplSpec :: Extension -> (DynFlags -> Extension -> DynFlags) -> DynFlags -> DynFlags Source #

Set or unset a Extension, unless it has been explicitly set or unset before.

data DynamicTooState Source #

Constructors

DT_Dont

Don't try to build dynamic objects too

DT_OK

Will still try to generate dynamic objects

DT_Dyn

Currently generating dynamic objects (in the backend)

sccProfilingEnabled :: DynFlags -> Bool Source #

Indicate if cost-centre profiling is enabled

needSourceNotes :: DynFlags -> Bool Source #

Indicate whether we need to generate source notes

data OnOff a Source #

Constructors

On a 
Off a 

Instances

Instances details
Show a => Show (OnOff a) Source # 
Instance details

Defined in GHC.Driver.Session

Outputable a => Outputable (OnOff a) Source # 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: OnOff a -> SDoc Source #

Eq a => Eq (OnOff a) Source # 
Instance details

Defined in GHC.Driver.Session

Methods

(==) :: OnOff a -> OnOff a -> Bool #

(/=) :: OnOff a -> OnOff a -> Bool #

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 #

Instances

Instances details
HasDynFlags CoreM Source # 
Instance details

Defined in GHC.Core.Opt.Monad

HasDynFlags Hsc Source # 
Instance details

Defined in GHC.Driver.Env.Types

HasDynFlags Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

HasDynFlags TcS Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

ContainsDynFlags env => HasDynFlags (IOEnv env) Source # 
Instance details

Defined in GHC.Data.IOEnv

MonadIO m => HasDynFlags (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

(Monad m, HasDynFlags m) => HasDynFlags (MaybeT m) Source # 
Instance details

Defined in GHC.Driver.Session

(Monad m, HasDynFlags m) => HasDynFlags (ExceptT e m) Source # 
Instance details

Defined in GHC.Driver.Session

(Monad m, HasDynFlags m) => HasDynFlags (ReaderT a m) Source # 
Instance details

Defined in GHC.Driver.Session

(Monoid a, Monad m, HasDynFlags m) => HasDynFlags (WriterT a m) Source # 
Instance details

Defined in GHC.Driver.Session

class ContainsDynFlags t where Source #

Instances

Instances details
ContainsDynFlags HscEnv Source # 
Instance details

Defined in GHC.Driver.Env.Types

ContainsDynFlags (Env gbl lcl) Source # 
Instance details

Defined in GHC.Tc.Types

Methods

extractDynFlags :: Env gbl lcl -> DynFlags Source #

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

Constructors

CompManager

--make, GHCi, etc.

OneShot
ghc -c Foo.hs
MkDepend

ghc -M, see GHC.Unit.Finder for why we need this

Instances

Instances details
Outputable GhcMode Source # 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: GhcMode -> SDoc Source #

Eq GhcMode Source # 
Instance details

Defined in GHC.Driver.Session

Methods

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

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

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

LinkMergedObj

Link objects into a merged "GHCi object"

Instances

data PackageFlag Source #

Flags for manipulating packages visibility.

Constructors

ExposePackage String PackageArg ModRenaming

-package, -package-id

HidePackage String
-hide-package

Instances

Instances details
Outputable PackageFlag Source # 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: PackageFlag -> SDoc Source #

Eq PackageFlag Source # 
Instance details

Defined in GHC.Driver.Session

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 Unit

-package-id, by Unit

Instances

Instances details
Show PackageArg Source # 
Instance details

Defined in GHC.Driver.Session

Outputable PackageArg Source # 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: PackageArg -> SDoc Source #

Eq PackageArg Source # 
Instance details

Defined in GHC.Driver.Session

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

Instances

Instances details
Outputable ModRenaming Source # 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: ModRenaming -> SDoc Source #

Eq ModRenaming Source # 
Instance details

Defined in GHC.Driver.Session

newtype IgnorePackageFlag Source #

Flags for manipulating the set of non-broken packages.

Constructors

IgnorePackage String
-ignore-package

Instances

Instances details
Eq IgnorePackageFlag Source # 
Instance details

Defined in GHC.Driver.Session

data TrustFlag Source #

Flags for manipulating package trust.

Constructors

TrustPackage String
-trust
DistrustPackage String
-distrust

Instances

Instances details
Eq TrustFlag Source # 
Instance details

Defined in GHC.Driver.Session

data PkgDbRef Source #

Instances

Instances details
Eq PkgDbRef Source # 
Instance details

Defined in GHC.Driver.Session

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

Instances details
Eq Option Source # 
Instance details

Defined in GHC.Utils.CliOption

Methods

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

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

data DynLibLoader Source #

Instances

Instances details
Eq DynLibLoader Source # 
Instance details

Defined in GHC.Driver.Session

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>

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.

positionIndependent :: DynFlags -> Bool Source #

Are we building with -fPIE or -fPIC enabled?

pprDynFlagsDiff :: DynFlags -> DynFlags -> SDoc Source #

Pretty-print the difference between 2 DynFlags.

For now only their general flags but it could be extended. Useful mostly for debugging.

targetProfile :: DynFlags -> Profile Source #

Get target profile

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

data GhcNameVersion Source #

Settings for what GHC this is.

data FileSettings Source #

Paths to various files and directories used by GHC, including those that provide more settings.

data PlatformMisc Source #

Platform-specific settings formerly hard-coded in Config.hs.

These should probably be all be triaged whether they can be computed from other settings or belong in another another place (like Platform above).

settings :: DynFlags -> Settings Source #

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

versionedAppDir :: String -> ArchOS -> MaybeT IO FilePath Source #

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

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

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

State

newtype CmdLineP s a Source #

Constructors

CmdLineP (forall m. Monad m => StateT s m a) 

Instances

Instances details
Applicative (CmdLineP s) Source # 
Instance details

Defined in GHC.Driver.Session

Methods

pure :: a -> CmdLineP s a Source #

(<*>) :: CmdLineP s (a -> b) -> CmdLineP s a -> CmdLineP s b Source #

liftA2 :: (a -> b -> c) -> CmdLineP s a -> CmdLineP s b -> CmdLineP s c Source #

(*>) :: CmdLineP s a -> CmdLineP s b -> CmdLineP s b Source #

(<*) :: CmdLineP s a -> CmdLineP s b -> CmdLineP s a Source #

Functor (CmdLineP s) Source # 
Instance details

Defined in GHC.Driver.Session

Methods

fmap :: (a -> b) -> CmdLineP s a -> CmdLineP s b Source #

(<$) :: a -> CmdLineP s b -> CmdLineP s a Source #

Monad (CmdLineP s) Source # 
Instance details

Defined in GHC.Driver.Session

Methods

(>>=) :: CmdLineP s a -> (a -> CmdLineP s b) -> CmdLineP s b Source #

(>>) :: CmdLineP s a -> CmdLineP s b -> CmdLineP s b Source #

return :: a -> CmdLineP s a Source #

runCmdLineP :: CmdLineP s a -> s -> (a, s) Source #

processCmdLineP Source #

Arguments

:: forall s m. MonadIO m 
=> [Flag (CmdLineP s)]

valid flags to match against

-> s

current state

-> [Located String]

arguments to parse

-> m (([Located String], [Err], [Warn]), s)

(leftovers, errors, warnings)

A helper to parse a set of flags from a list of command-line arguments, handling response files.

Parsing DynFlags

parseDynamicFlagsCmdLine Source #

Arguments

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

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

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

parseDynamicFilePragma Source #

Arguments

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

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

:: forall m. 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]) 

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.

languageExtensions :: Maybe Language -> [Extension] Source #

The language extensions implied by the various language variants. When updating this be sure to update the flag documentation in docsusers_guideexts.

DynFlags C compiler options

DynFlags C linker options

Compiler configuration suitable for display to the user

SSE and AVX

Linker/compiler information

data LinkerInfo Source #

Instances

Instances details
Eq LinkerInfo Source # 
Instance details

Defined in GHC.Driver.Session

data CompilerInfo Source #

Instances

Instances details
Eq CompilerInfo Source # 
Instance details

Defined in GHC.Driver.Session

useXLinkerRPath :: DynFlags -> OS -> Bool Source #

Should we use `-XLinker -rpath` when linking or not? See Note [-fno-use-rpaths]

Include specifications

data IncludeSpecs Source #

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.

Constructors

IncludeSpecs 

Fields

Instances

Instances details
Show IncludeSpecs Source # 
Instance details

Defined in GHC.Driver.Session

addGlobalInclude :: IncludeSpecs -> [String] -> IncludeSpecs Source #

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.

addQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs Source #

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"

flattenIncludes :: IncludeSpecs -> [String] Source #

Concatenate and flatten the list of global and quoted includes returning just a flat list of paths.

addImplicitQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs Source #

These includes are not considered while fingerprinting the flags for iface | See Note [Implicit include paths]

SDoc

initSDocContext :: DynFlags -> PprStyle -> SDocContext Source #

Initialize the pretty-printing options

initDefaultSDocContext :: DynFlags -> SDocContext Source #

Initialize the pretty-printing options using the default user style