| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Driver.DynFlags
Synopsis
- data DumpFlag
- = 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
 - | 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_spec_constr
 - | Opt_D_dump_prep
 - | Opt_D_dump_late_cc
 - | Opt_D_dump_stg_from_core
 - | Opt_D_dump_stg_unarised
 - | Opt_D_dump_stg_cg
 - | Opt_D_dump_stg_tags
 - | Opt_D_dump_stg_final
 - | 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_float_out
 - | Opt_D_dump_float_in
 - | Opt_D_dump_liberate_case
 - | Opt_D_dump_static_argument_transformation
 - | 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
- = Opt_DumpToFile
 - | Opt_DumpWithWays
 - | 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
 - | Opt_LocalFloatOutTopLevel
 - | Opt_LateSpecialise
 - | Opt_Specialise
 - | Opt_SpecialiseAggressively
 - | Opt_CrossModuleSpecialise
 - | Opt_PolymorphicSpecialisation
 - | Opt_InlineGenerics
 - | Opt_InlineGenericsAggressively
 - | Opt_StaticArgumentTransformation
 - | Opt_CSE
 - | Opt_StgCSE
 - | Opt_StgLiftLams
 - | Opt_LiberateCase
 - | Opt_SpecConstr
 - | Opt_SpecConstrKeen
 - | Opt_SpecialiseIncoherents
 - | 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
 - | Opt_Loopification
 - | Opt_CfgBlocklayout
 - | Opt_WeightlessBlocklayout
 - | Opt_CprAnal
 - | Opt_WorkerWrapper
 - | Opt_WorkerWrapperUnlift
 - | 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_DisableJsMinifier
 - | Opt_AutoSccsOnIndividualCafs
 - | Opt_ProfCountEntries
 - | Opt_ProfLateInlineCcs
 - | Opt_ProfLateCcs
 - | Opt_ProfManualCcs
 - | 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
 - | Opt_PIE
 - | Opt_PICExecutable
 - | Opt_ExternalDynamicRefs
 - | Opt_Ticky
 - | Opt_Ticky_Allocd
 - | Opt_Ticky_LNE
 - | Opt_Ticky_Dyn_Thunk
 - | Opt_Ticky_Tag
 - | Opt_Ticky_AP
 - | Opt_CmmThreadSanitizer
 - | Opt_RPath
 - | Opt_RelativeDynlibPaths
 - | Opt_CompactUnwind
 - | 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_UnoptimizedCoreForInterpreter
 - | 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
 - | Opt_SuppressCoreSizes
 - | 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
- = 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_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_WarnMissingPolyKindSignatures
 - | Opt_WarnMissingExportedPatternSynonymSignatures
 - | Opt_WarnRedundantStrictnessFlags
 - | Opt_WarnForallIdentifier
 - | Opt_WarnUnicodeBidirectionalFormatCharacters
 - | Opt_WarnGADTMonoLocalBinds
 - | Opt_WarnTypeEqualityOutOfScope
 - | Opt_WarnTypeEqualityRequiresOperators
 - | Opt_WarnLoopySuperclassSolve
 - | Opt_WarnTermVariableCapture
 - | Opt_WarnMissingRoleAnnotations
 - | Opt_WarnImplicitRhsQuantification
 - | Opt_WarnIncompleteExportWarnings
 - | Opt_WarnInconsistentFlags
 
 - data DiagnosticReason where
 - data Language
 - type FatalMessager = String -> IO ()
 - newtype FlushOut = FlushOut (IO ())
 - data ProfAuto
 - hasPprDebug :: DynFlags -> Bool
 - hasNoDebugOutput :: DynFlags -> Bool
 - hasNoStateHack :: DynFlags -> Bool
 - hasNoOptCoercion :: DynFlags -> Bool
 - dopt :: DumpFlag -> DynFlags -> Bool
 - dopt_set :: DynFlags -> DumpFlag -> DynFlags
 - dopt_unset :: DynFlags -> DumpFlag -> DynFlags
 - gopt :: GeneralFlag -> DynFlags -> Bool
 - gopt_set :: DynFlags -> GeneralFlag -> DynFlags
 - gopt_unset :: DynFlags -> GeneralFlag -> DynFlags
 - wopt :: WarningFlag -> DynFlags -> Bool
 - wopt_set :: DynFlags -> WarningFlag -> DynFlags
 - wopt_unset :: DynFlags -> WarningFlag -> DynFlags
 - wopt_fatal :: WarningFlag -> DynFlags -> Bool
 - wopt_set_fatal :: DynFlags -> WarningFlag -> DynFlags
 - wopt_unset_fatal :: DynFlags -> WarningFlag -> DynFlags
 - wopt_set_all_custom :: DynFlags -> DynFlags
 - wopt_unset_all_custom :: DynFlags -> DynFlags
 - wopt_set_all_fatal_custom :: DynFlags -> DynFlags
 - wopt_unset_all_fatal_custom :: DynFlags -> DynFlags
 - wopt_set_custom :: DynFlags -> WarningCategory -> DynFlags
 - wopt_unset_custom :: DynFlags -> WarningCategory -> DynFlags
 - wopt_set_fatal_custom :: DynFlags -> WarningCategory -> DynFlags
 - wopt_unset_fatal_custom :: DynFlags -> WarningCategory -> DynFlags
 - wopt_any_custom :: DynFlags -> Bool
 - xopt :: Extension -> DynFlags -> Bool
 - xopt_set :: DynFlags -> Extension -> DynFlags
 - xopt_unset :: DynFlags -> Extension -> DynFlags
 - xopt_set_unlessExplSpec :: Extension -> (DynFlags -> Extension -> DynFlags) -> DynFlags -> DynFlags
 - xopt_DuplicateRecordFields :: DynFlags -> DuplicateRecordFields
 - xopt_FieldSelectors :: DynFlags -> FieldSelectors
 - lang_set :: DynFlags -> Maybe Language -> DynFlags
 - data DynamicTooState
 - dynamicTooState :: DynFlags -> DynamicTooState
 - setDynamicNow :: DynFlags -> DynFlags
 - data OnOff a
 - data DynFlags = DynFlags {
- ghcMode :: GhcMode
 - ghcLink :: GhcLink
 - backend :: !Backend
 - ghcNameVersion :: !GhcNameVersion
 - fileSettings :: !FileSettings
 - targetPlatform :: Platform
 - toolSettings :: !ToolSettings
 - platformMisc :: !PlatformMisc
 - rawSettings :: [(String, String)]
 - tmpDir :: TempDir
 - llvmOptLevel :: Int
 - verbosity :: Int
 - debugLevel :: Int
 - simplPhases :: Int
 - maxSimplIterations :: Int
 - ruleCheck :: Maybe String
 - strictnessBefore :: [Int]
 - parMakeCount :: Maybe ParMakeCount
 - enableTimeStats :: Bool
 - ghcHeapSize :: Maybe Int
 - maxRelevantBinds :: Maybe Int
 - maxValidHoleFits :: Maybe Int
 - maxRefHoleFits :: Maybe Int
 - refLevelHoleFits :: Maybe Int
 - maxUncoveredPatterns :: Int
 - maxPmCheckModels :: Int
 - simplTickFactor :: Int
 - dmdUnboxWidth :: !Int
 - specConstrThreshold :: Maybe Int
 - specConstrCount :: Maybe Int
 - specConstrRecursive :: Int
 - binBlobThreshold :: Maybe Word
 - liberateCaseThreshold :: Maybe Int
 - floatLamArgs :: Maybe Int
 - liftLamsRecArgs :: Maybe Int
 - liftLamsNonRecArgs :: Maybe Int
 - liftLamsKnown :: Bool
 - cmmProcAlignment :: Maybe Int
 - historySize :: Int
 - importPaths :: [FilePath]
 - mainModuleNameIs :: ModuleName
 - mainFunIs :: Maybe String
 - reductionDepth :: IntWithInf
 - solverIterations :: IntWithInf
 - givensFuel :: Int
 - wantedsFuel :: Int
 - qcsFuel :: Int
 - homeUnitId_ :: UnitId
 - homeUnitInstanceOf_ :: Maybe UnitId
 - homeUnitInstantiations_ :: [(ModuleName, Module)]
 - workingDirectory :: Maybe FilePath
 - thisPackageName :: Maybe String
 - hiddenModules :: Set ModuleName
 - reexportedModules :: Set ModuleName
 - targetWays_ :: Ways
 - splitInfo :: Maybe (String, Int)
 - objectDir :: Maybe String
 - dylibInstallName :: Maybe String
 - hiDir :: Maybe String
 - hieDir :: Maybe String
 - stubDir :: Maybe String
 - dumpDir :: Maybe String
 - objectSuf_ :: String
 - hcSuf :: String
 - hiSuf_ :: String
 - hieSuf :: String
 - dynObjectSuf_ :: String
 - dynHiSuf_ :: String
 - outputFile_ :: Maybe String
 - dynOutputFile_ :: Maybe String
 - outputHi :: Maybe String
 - dynOutputHi :: Maybe String
 - dynLibLoader :: DynLibLoader
 - dynamicNow :: !Bool
 - dumpPrefix :: FilePath
 - dumpPrefixForce :: Maybe FilePath
 - ldInputs :: [Option]
 - includePaths :: IncludeSpecs
 - libraryPaths :: [String]
 - frameworkPaths :: [String]
 - cmdlineFrameworks :: [String]
 - rtsOpts :: Maybe String
 - rtsOptsEnabled :: RtsOptsEnabled
 - rtsOptsSuggestions :: Bool
 - hpcDir :: String
 - pluginModNames :: [ModuleName]
 - pluginModNameOpts :: [(ModuleName, String)]
 - frontendPluginOpts :: [String]
 - externalPluginSpecs :: [ExternalPluginSpec]
 - depMakefile :: FilePath
 - depIncludePkgDeps :: Bool
 - depIncludeCppDeps :: Bool
 - depExcludeMods :: [ModuleName]
 - depSuffixes :: [String]
 - packageDBFlags :: [PackageDBFlag]
 - ignorePackageFlags :: [IgnorePackageFlag]
 - packageFlags :: [PackageFlag]
 - pluginPackageFlags :: [PackageFlag]
 - trustFlags :: [TrustFlag]
 - packageEnv :: Maybe FilePath
 - dumpFlags :: EnumSet DumpFlag
 - generalFlags :: EnumSet GeneralFlag
 - warningFlags :: EnumSet WarningFlag
 - fatalWarningFlags :: EnumSet WarningFlag
 - customWarningCategories :: WarningCategorySet
 - fatalCustomWarningCategories :: WarningCategorySet
 - language :: Maybe Language
 - safeHaskell :: SafeHaskellMode
 - safeInfer :: Bool
 - safeInferred :: Bool
 - thOnLoc :: SrcSpan
 - newDerivOnLoc :: SrcSpan
 - deriveViaOnLoc :: SrcSpan
 - overlapInstLoc :: SrcSpan
 - incoherentOnLoc :: SrcSpan
 - pkgTrustOnLoc :: SrcSpan
 - warnSafeOnLoc :: SrcSpan
 - warnUnsafeOnLoc :: SrcSpan
 - trustworthyOnLoc :: SrcSpan
 - extensions :: [OnOff Extension]
 - extensionFlags :: EnumSet Extension
 - unfoldingOpts :: !UnfoldingOpts
 - maxWorkerArgs :: Int
 - ghciHistSize :: Int
 - flushOut :: FlushOut
 - ghcVersionFile :: Maybe FilePath
 - haddockOptions :: Maybe String
 - ghciScripts :: [String]
 - pprUserLength :: Int
 - pprCols :: Int
 - useUnicode :: Bool
 - useColor :: OverridingBool
 - canUseColor :: Bool
 - colScheme :: Scheme
 - profAuto :: ProfAuto
 - callerCcFilters :: [CallerCcFilter]
 - interactivePrint :: Maybe String
 - sseVersion :: Maybe SseVersion
 - bmiVersion :: Maybe BmiVersion
 - avx :: Bool
 - avx2 :: Bool
 - avx512cd :: Bool
 - avx512er :: Bool
 - avx512f :: Bool
 - avx512pf :: Bool
 - fma :: Bool
 - rtldInfo :: IORef (Maybe LinkerInfo)
 - rtccInfo :: IORef (Maybe CompilerInfo)
 - rtasmInfo :: IORef (Maybe CompilerInfo)
 - maxInlineAllocSize :: Int
 - maxInlineMemcpyInsns :: Int
 - maxInlineMemsetInsns :: Int
 - reverseErrors :: Bool
 - maxErrors :: Maybe Int
 - initialUnique :: Word
 - uniqueIncrement :: Int
 - cfgWeights :: Weights
 
 - data ParMakeCount
 - ways :: DynFlags -> Ways
 - class HasDynFlags (m :: Type -> Type) where
- getDynFlags :: m DynFlags
 
 - class ContainsDynFlags t where
- extractDynFlags :: t -> DynFlags
 
 - data RtsOptsEnabled
 - data GhcMode
 - isOneShot :: GhcMode -> Bool
 - data GhcLink
 - isNoLink :: GhcLink -> Bool
 - data PackageFlag
 - data PackageArg
 - data ModRenaming = ModRenaming {}
 - packageFlagsChanged :: DynFlags -> DynFlags -> Bool
 - newtype IgnorePackageFlag = IgnorePackage String
 - data TrustFlag
 - data PackageDBFlag
 - data PkgDbRef
 - data Option
 - showOpt :: Option -> String
 - data DynLibLoader
 - positionIndependent :: DynFlags -> Bool
 - optimisationFlags :: EnumSet GeneralFlag
 - targetProfile :: DynFlags -> Profile
 - defaultDynFlags :: Settings -> DynFlags
 - initDynFlags :: DynFlags -> IO DynFlags
 - defaultFatalMessager :: FatalMessager
 - defaultFlushOut :: FlushOut
 - optLevelFlags :: [([Int], GeneralFlag)]
 - languageExtensions :: Maybe Language -> [Extension]
 - type TurnOnFlag = Bool
 - turnOn :: TurnOnFlag
 - turnOff :: TurnOnFlag
 - programName :: DynFlags -> String
 - projectVersion :: DynFlags -> String
 - ghcUsagePath :: DynFlags -> FilePath
 - ghciUsagePath :: DynFlags -> FilePath
 - topDir :: DynFlags -> FilePath
 - toolDir :: DynFlags -> Maybe FilePath
 - versionedAppDir :: String -> ArchOS -> MaybeT IO FilePath
 - versionedFilePath :: ArchOS -> FilePath
 - extraGccViaCFlags :: DynFlags -> [String]
 - globalPackageDatabasePath :: DynFlags -> FilePath
 - data LinkerInfo
 - data CompilerInfo
 - data IncludeSpecs = IncludeSpecs {}
 - addGlobalInclude :: IncludeSpecs -> [String] -> IncludeSpecs
 - addQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs
 - flattenIncludes :: IncludeSpecs -> [String]
 - addImplicitQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs
 - initSDocContext :: DynFlags -> PprStyle -> SDocContext
 - initDefaultSDocContext :: DynFlags -> SDocContext
 - initPromotionTickContext :: DynFlags -> PromotionTickContext
 
Dynamic flags and associated configuration types
Debugging flags
Constructors
Instances
| Enum DumpFlag Source # | |
Defined in GHC.Driver.Flags Methods succ :: DumpFlag -> DumpFlag Source # pred :: DumpFlag -> DumpFlag Source # toEnum :: Int -> DumpFlag Source # fromEnum :: DumpFlag -> Int Source # enumFrom :: DumpFlag -> [DumpFlag] Source # enumFromThen :: DumpFlag -> DumpFlag -> [DumpFlag] Source # enumFromTo :: DumpFlag -> DumpFlag -> [DumpFlag] Source # enumFromThenTo :: DumpFlag -> DumpFlag -> DumpFlag -> [DumpFlag] Source #  | |
| Show DumpFlag Source # | |
| Eq DumpFlag Source # | |
data GeneralFlag Source #
Enumerates the simple on-or-off dynamic flags
Constructors
Instances
| Enum GeneralFlag Source # | |
Defined in GHC.Driver.Flags Methods succ :: GeneralFlag -> GeneralFlag Source # pred :: GeneralFlag -> GeneralFlag Source # toEnum :: Int -> GeneralFlag Source # fromEnum :: GeneralFlag -> Int Source # enumFrom :: GeneralFlag -> [GeneralFlag] Source # enumFromThen :: GeneralFlag -> GeneralFlag -> [GeneralFlag] Source # enumFromTo :: GeneralFlag -> GeneralFlag -> [GeneralFlag] Source # enumFromThenTo :: GeneralFlag -> GeneralFlag -> GeneralFlag -> [GeneralFlag] Source #  | |
| Show GeneralFlag Source # | |
Defined in GHC.Driver.Flags  | |
| Eq GeneralFlag Source # | |
Defined in GHC.Driver.Flags  | |
data WarningFlag Source #
Constructors
Instances
| Enum WarningFlag Source # | |
Defined in GHC.Driver.Flags Methods succ :: WarningFlag -> WarningFlag Source # pred :: WarningFlag -> WarningFlag Source # toEnum :: Int -> WarningFlag Source # fromEnum :: WarningFlag -> Int Source # enumFrom :: WarningFlag -> [WarningFlag] Source # enumFromThen :: WarningFlag -> WarningFlag -> [WarningFlag] Source # enumFromTo :: WarningFlag -> WarningFlag -> [WarningFlag] Source # enumFromThenTo :: WarningFlag -> WarningFlag -> WarningFlag -> [WarningFlag] Source #  | |
| Show WarningFlag Source # | |
Defined in GHC.Driver.Flags  | |
| Eq WarningFlag Source # | |
Defined in GHC.Driver.Flags  | |
| Ord WarningFlag Source # | |
Defined in GHC.Driver.Flags Methods compare :: WarningFlag -> WarningFlag -> Ordering # (<) :: WarningFlag -> WarningFlag -> Bool # (<=) :: WarningFlag -> WarningFlag -> Bool # (>) :: WarningFlag -> WarningFlag -> Bool # (>=) :: WarningFlag -> WarningFlag -> Bool # max :: WarningFlag -> WarningFlag -> WarningFlag # min :: WarningFlag -> WarningFlag -> WarningFlag #  | |
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.  | 
| WarningWithFlags !(NonEmpty WarningFlag) | Warning was enabled with the flag.  | 
| WarningWithCategory !WarningCategory | Warning was enabled with a custom category.  | 
| ErrorWithoutFlag | Born as an error.  | 
Bundled Patterns
| pattern WarningWithFlag :: WarningFlag -> DiagnosticReason | The single warning case   | 
Instances
| Show DiagnosticReason Source # | |
Defined in GHC.Types.Error  | |
| Outputable DiagnosticReason Source # | |
Defined in GHC.Types.Error Methods ppr :: DiagnosticReason -> SDoc Source #  | |
| Eq DiagnosticReason Source # | |
Defined in GHC.Types.Error Methods (==) :: DiagnosticReason -> DiagnosticReason -> Bool # (/=) :: DiagnosticReason -> DiagnosticReason -> Bool #  | |
Constructors
| Haskell98 | |
| Haskell2010 | |
| GHC2021 | 
Instances
| Bounded Language Source # | |
| Enum Language Source # | |
Defined in GHC.Driver.Flags Methods succ :: Language -> Language Source # pred :: Language -> Language Source # toEnum :: Int -> Language Source # fromEnum :: Language -> Int Source # enumFrom :: Language -> [Language] Source # enumFromThen :: Language -> Language -> [Language] Source # enumFromTo :: Language -> Language -> [Language] Source # enumFromThenTo :: Language -> Language -> Language -> [Language] Source #  | |
| Show Language Source # | |
| NFData Language Source # | |
Defined in GHC.Driver.Flags  | |
| Binary Language Source # | |
| Outputable Language Source # | |
| Eq Language Source # | |
type FatalMessager = String -> IO () 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  | 
Instances
| Enum ProfAuto Source # | |
Defined in GHC.Types.ProfAuto Methods succ :: ProfAuto -> ProfAuto Source # pred :: ProfAuto -> ProfAuto Source # toEnum :: Int -> ProfAuto Source # fromEnum :: ProfAuto -> Int Source # enumFrom :: ProfAuto -> [ProfAuto] Source # enumFromThen :: ProfAuto -> ProfAuto -> [ProfAuto] Source # enumFromTo :: ProfAuto -> ProfAuto -> [ProfAuto] Source # enumFromThenTo :: ProfAuto -> ProfAuto -> ProfAuto -> [ProfAuto] Source #  | |
| Eq ProfAuto Source # | |
hasPprDebug :: DynFlags -> Bool Source #
hasNoDebugOutput :: DynFlags -> Bool Source #
hasNoStateHack :: DynFlags -> Bool Source #
hasNoOptCoercion :: DynFlags -> Bool Source #
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.
gopt_set :: DynFlags -> GeneralFlag -> DynFlags Source #
Set a GeneralFlag
gopt_unset :: DynFlags -> GeneralFlag -> DynFlags Source #
Unset a GeneralFlag
wopt :: WarningFlag -> DynFlags -> Bool Source #
Test whether a WarningFlag is set
wopt_set :: DynFlags -> WarningFlag -> DynFlags Source #
Set a WarningFlag
wopt_unset :: DynFlags -> WarningFlag -> DynFlags Source #
Unset a WarningFlag
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)
wopt_unset_fatal :: DynFlags -> WarningFlag -> DynFlags Source #
Mark a WarningFlag as not fatal
wopt_set_all_custom :: DynFlags -> DynFlags Source #
Enable all custom warning categories.
wopt_unset_all_custom :: DynFlags -> DynFlags Source #
Disable all custom warning categories.
wopt_set_all_fatal_custom :: DynFlags -> DynFlags Source #
Mark all custom warning categories as fatal (do not set the flags).
wopt_unset_all_fatal_custom :: DynFlags -> DynFlags Source #
Mark all custom warning categories as non-fatal.
wopt_set_custom :: DynFlags -> WarningCategory -> DynFlags Source #
Set a custom WarningCategory
wopt_unset_custom :: DynFlags -> WarningCategory -> DynFlags Source #
Unset a custom WarningCategory
wopt_set_fatal_custom :: DynFlags -> WarningCategory -> DynFlags Source #
Mark a custom WarningCategory as fatal (do not set the flag)
wopt_unset_fatal_custom :: DynFlags -> WarningCategory -> DynFlags Source #
Mark a custom WarningCategory as not fatal
wopt_any_custom :: DynFlags -> Bool Source #
Are there any custom warning categories enabled?
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)  | 
Instances
| Show DynamicTooState Source # | |
Defined in GHC.Driver.DynFlags  | |
| Eq DynamicTooState Source # | |
Defined in GHC.Driver.DynFlags Methods (==) :: DynamicTooState -> DynamicTooState -> Bool # (/=) :: DynamicTooState -> DynamicTooState -> Bool #  | |
| Ord DynamicTooState Source # | |
Defined in GHC.Driver.DynFlags Methods compare :: DynamicTooState -> DynamicTooState -> Ordering # (<) :: DynamicTooState -> DynamicTooState -> Bool # (<=) :: DynamicTooState -> DynamicTooState -> Bool # (>) :: DynamicTooState -> DynamicTooState -> Bool # (>=) :: DynamicTooState -> DynamicTooState -> Bool # max :: DynamicTooState -> DynamicTooState -> DynamicTooState # min :: DynamicTooState -> DynamicTooState -> DynamicTooState #  | |
setDynamicNow :: DynFlags -> 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 ParMakeCount Source #
The type for the -jN argument, specifying that -j on its own represents using the number of machine processors.
Constructors
| ParMakeThisMany Int | Use this many processors (  | 
| ParMakeNumProcessors | Use parallelism with as many processors as possible (  | 
| ParMakeSemaphore FilePath | Use the specific semaphore   | 
class HasDynFlags (m :: Type -> Type) where Source #
Methods
getDynFlags :: m DynFlags Source #
Instances
class ContainsDynFlags t where Source #
Methods
extractDynFlags :: t -> DynFlags Source #
Instances
| ContainsDynFlags HscEnv Source # | |
Defined in GHC.Driver.Env.Types Methods extractDynFlags :: HscEnv -> DynFlags Source #  | |
| ContainsDynFlags (Env gbl lcl) Source # | |
Defined in GHC.Tc.Types Methods extractDynFlags :: Env gbl lcl -> DynFlags Source #  | |
data RtsOptsEnabled Source #
Instances
| Show RtsOptsEnabled Source # | |
Defined in GHC.Driver.DynFlags  | |
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 | 
  | 
| OneShot | ghc -c Foo.hs  | 
| MkDepend | 
  | 
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"  | 
data PackageFlag Source #
Flags for manipulating packages visibility.
Constructors
| ExposePackage String PackageArg ModRenaming | 
  | 
| HidePackage String | -hide-package  | 
Instances
| Outputable PackageFlag Source # | |
Defined in GHC.Driver.DynFlags Methods ppr :: PackageFlag -> SDoc Source #  | |
| Eq PackageFlag Source # | |
Defined in GHC.Driver.DynFlags  | |
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 | 
  | 
| UnitIdArg Unit | 
  | 
Instances
| Show PackageArg Source # | |
Defined in GHC.Driver.DynFlags  | |
| Outputable PackageArg Source # | |
Defined in GHC.Driver.DynFlags Methods ppr :: PackageArg -> SDoc Source #  | |
| Eq PackageArg Source # | |
Defined in GHC.Driver.DynFlags  | |
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:
Constructors
| ModRenaming | |
Fields 
  | |
Instances
| Outputable ModRenaming Source # | |
Defined in GHC.Driver.DynFlags Methods ppr :: ModRenaming -> SDoc Source #  | |
| Eq ModRenaming Source # | |
Defined in GHC.Driver.DynFlags  | |
newtype IgnorePackageFlag Source #
Flags for manipulating the set of non-broken packages.
Constructors
| IgnorePackage String | -ignore-package  | 
Instances
| Eq IgnorePackageFlag Source # | |
Defined in GHC.Driver.DynFlags Methods (==) :: IgnorePackageFlag -> IgnorePackageFlag -> Bool # (/=) :: IgnorePackageFlag -> IgnorePackageFlag -> Bool #  | |
Flags for manipulating package trust.
Constructors
| TrustPackage String | -trust  | 
| DistrustPackage String | -distrust  | 
data PackageDBFlag Source #
Constructors
| PackageDB PkgDbRef | |
| NoUserPackageDB | |
| NoGlobalPackageDB | |
| ClearPackageDBs | 
Instances
| Eq PackageDBFlag Source # | |
Defined in GHC.Driver.DynFlags Methods (==) :: PackageDBFlag -> PackageDBFlag -> Bool # (/=) :: PackageDBFlag -> PackageDBFlag -> Bool #  | |
Constructors
| GlobalPkgDb | |
| UserPkgDb | |
| PkgDbPath FilePath | 
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.
Constructors
| FileOption String String | |
| Option String | 
data DynLibLoader Source #
Constructors
| Deployable | |
| SystemDependent | 
Instances
| Eq DynLibLoader Source # | |
Defined in GHC.Driver.DynFlags  | |
positionIndependent :: DynFlags -> Bool Source #
Are we building with -fPIE or -fPIC enabled?
optimisationFlags :: EnumSet GeneralFlag Source #
The set of flags which affect optimisation for the purposes of recompilation avoidance. Specifically, these include flags which affect code generation but not the semantics of the program.
See Note [Ignoring some flag changes] in GHC.Iface.Recomp.Flags)
targetProfile :: DynFlags -> Profile Source #
Get target profile
Manipulating DynFlags
defaultDynFlags :: Settings -> DynFlags Source #
optLevelFlags :: [([Int], GeneralFlag)] Source #
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.
type TurnOnFlag = Bool Source #
turnOn :: TurnOnFlag Source #
turnOff :: TurnOnFlag Source #
System tool settings and locations
programName :: DynFlags -> String Source #
projectVersion :: DynFlags -> String Source #
ghcUsagePath :: DynFlags -> FilePath Source #
ghciUsagePath :: DynFlags -> FilePath Source #
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
versionedFilePath :: ArchOS -> FilePath Source #
extraGccViaCFlags :: DynFlags -> [String] Source #
Linker/compiler information
data LinkerInfo Source #
Constructors
| GnuLD [Option] | |
| Mold [Option] | |
| GnuGold [Option] | |
| LlvmLLD [Option] | |
| DarwinLD [Option] | |
| SolarisLD [Option] | |
| AixLD [Option] | |
| UnknownLD | 
Instances
| Eq LinkerInfo Source # | |
Defined in GHC.Driver.DynFlags  | |
data CompilerInfo Source #
Constructors
| GCC | |
| Clang | |
| AppleClang | |
| AppleClang51 | |
| Emscripten | |
| UnknownCC | 
Instances
| Eq CompilerInfo Source # | |
Defined in GHC.Driver.DynFlags  | |
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
| Show IncludeSpecs Source # | |
Defined in GHC.Driver.DynFlags  | |
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