Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
- 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_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_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
- | Opt_D_ipe_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_InfoTableMapWithFallback
- | Opt_InfoTableMapWithStack
- | 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_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_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_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_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
- data Language
- type FatalMessager = String -> IO ()
- newtype FlushOut = FlushOut (IO ())
- data ProfAuto
- glasgowExtsFlags :: [Extension]
- 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
- setGeneralFlag' :: GeneralFlag -> DynFlags -> DynFlags
- unSetGeneralFlag' :: GeneralFlag -> DynFlags -> 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
- 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
- sccProfilingEnabled :: DynFlags -> Bool
- needSourceNotes :: DynFlags -> Bool
- 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 Int
- 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
- 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
- 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
- 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
- outputFile :: DynFlags -> Maybe String
- objectSuf :: DynFlags -> String
- ways :: DynFlags -> Ways
- data FlagSpec flag = FlagSpec {
- flagSpecName :: String
- flagSpecFlag :: flag
- flagSpecAction :: TurnOnFlag -> DynP ()
- flagSpecGhcMode :: GhcFlagMode
- class HasDynFlags m 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
- fFlags :: [FlagSpec GeneralFlag]
- fLangFlags :: [FlagSpec Extension]
- xFlags :: [FlagSpec Extension]
- wWarningFlags :: [FlagSpec WarningFlag]
- makeDynFlagsConsistent :: DynFlags -> (DynFlags, [Located String])
- positionIndependent :: DynFlags -> Bool
- optimisationFlags :: EnumSet GeneralFlag
- codeGenFlags :: EnumSet GeneralFlag
- setFlagsFromEnvFile :: FilePath -> String -> DynP ()
- pprDynFlagsDiff :: DynFlags -> DynFlags -> SDoc
- flagSpecOf :: WarningFlag -> Maybe (FlagSpec WarningFlag)
- targetProfile :: DynFlags -> Profile
- safeHaskellOn :: DynFlags -> Bool
- safeHaskellModeEnabled :: DynFlags -> Bool
- safeImportsOn :: DynFlags -> Bool
- safeLanguageOn :: DynFlags -> Bool
- safeInferOn :: DynFlags -> Bool
- packageTrustOn :: DynFlags -> Bool
- safeDirectImpsReq :: DynFlags -> Bool
- safeImplicitImpsReq :: DynFlags -> Bool
- unsafeFlags :: [(String, DynFlags -> SrcSpan, DynFlags -> Bool, DynFlags -> DynFlags)]
- unsafeFlagsForInfer :: [(String, DynFlags -> SrcSpan, DynFlags -> Bool, DynFlags -> DynFlags)]
- data Settings = Settings {}
- sProgramName :: Settings -> String
- sProjectVersion :: Settings -> String
- sGhcUsagePath :: Settings -> FilePath
- sGhciUsagePath :: Settings -> FilePath
- sToolDir :: Settings -> Maybe FilePath
- sTopDir :: Settings -> FilePath
- sGlobalPackageDatabasePath :: Settings -> FilePath
- sLdSupportsCompactUnwind :: Settings -> Bool
- sLdSupportsFilelist :: Settings -> Bool
- sLdIsGnuLd :: Settings -> Bool
- sGccSupportsNoPie :: Settings -> Bool
- sPgm_L :: Settings -> String
- sPgm_P :: Settings -> (String, [Option])
- sPgm_F :: Settings -> String
- sPgm_c :: Settings -> String
- sPgm_cxx :: Settings -> String
- sPgm_a :: Settings -> (String, [Option])
- sPgm_l :: Settings -> (String, [Option])
- sPgm_lm :: Settings -> Maybe (String, [Option])
- sPgm_dll :: Settings -> (String, [Option])
- sPgm_T :: Settings -> String
- sPgm_windres :: Settings -> String
- sPgm_ar :: Settings -> String
- sPgm_ranlib :: Settings -> String
- sPgm_lo :: Settings -> (String, [Option])
- sPgm_lc :: Settings -> (String, [Option])
- sPgm_lcc :: Settings -> (String, [Option])
- sPgm_i :: Settings -> String
- sOpt_L :: Settings -> [String]
- sOpt_P :: Settings -> [String]
- sOpt_P_fingerprint :: Settings -> Fingerprint
- sOpt_F :: Settings -> [String]
- sOpt_c :: Settings -> [String]
- sOpt_cxx :: Settings -> [String]
- sOpt_a :: Settings -> [String]
- sOpt_l :: Settings -> [String]
- sOpt_lm :: Settings -> [String]
- sOpt_windres :: Settings -> [String]
- sOpt_lo :: Settings -> [String]
- sOpt_lc :: Settings -> [String]
- sOpt_lcc :: Settings -> [String]
- sOpt_i :: Settings -> [String]
- sExtraGccViaCFlags :: Settings -> [String]
- sTargetPlatformString :: Settings -> String
- sGhcWithInterpreter :: Settings -> Bool
- sLibFFI :: Settings -> Bool
- data GhcNameVersion = GhcNameVersion {}
- data FileSettings = FileSettings {}
- data PlatformMisc = PlatformMisc {}
- settings :: DynFlags -> Settings
- programName :: DynFlags -> String
- projectVersion :: DynFlags -> String
- ghcUsagePath :: DynFlags -> FilePath
- ghciUsagePath :: DynFlags -> FilePath
- topDir :: DynFlags -> FilePath
- versionedAppDir :: String -> ArchOS -> MaybeT IO FilePath
- versionedFilePath :: ArchOS -> FilePath
- extraGccViaCFlags :: DynFlags -> [String]
- globalPackageDatabasePath :: DynFlags -> FilePath
- pgm_L :: DynFlags -> String
- pgm_P :: DynFlags -> (String, [Option])
- pgm_F :: DynFlags -> String
- pgm_c :: DynFlags -> String
- pgm_cxx :: DynFlags -> String
- pgm_a :: DynFlags -> (String, [Option])
- pgm_l :: DynFlags -> (String, [Option])
- pgm_lm :: DynFlags -> Maybe (String, [Option])
- pgm_dll :: DynFlags -> (String, [Option])
- pgm_T :: DynFlags -> String
- pgm_windres :: DynFlags -> String
- pgm_ar :: DynFlags -> String
- pgm_ranlib :: DynFlags -> String
- pgm_lo :: DynFlags -> (String, [Option])
- pgm_lc :: DynFlags -> (String, [Option])
- pgm_lcc :: DynFlags -> (String, [Option])
- pgm_i :: DynFlags -> String
- opt_L :: DynFlags -> [String]
- opt_P :: DynFlags -> [String]
- opt_F :: DynFlags -> [String]
- opt_c :: DynFlags -> [String]
- opt_cxx :: DynFlags -> [String]
- opt_a :: DynFlags -> [String]
- opt_l :: DynFlags -> [String]
- opt_lm :: DynFlags -> [String]
- opt_i :: DynFlags -> [String]
- opt_P_signature :: DynFlags -> ([String], Fingerprint)
- opt_windres :: DynFlags -> [String]
- opt_lo :: DynFlags -> [String]
- opt_lc :: DynFlags -> [String]
- opt_lcc :: DynFlags -> [String]
- updatePlatformConstants :: DynFlags -> Maybe PlatformConstants -> IO DynFlags
- addPluginModuleName :: String -> DynFlags -> DynFlags
- defaultDynFlags :: Settings -> DynFlags
- initDynFlags :: DynFlags -> IO DynFlags
- defaultFatalMessager :: FatalMessager
- defaultFlushOut :: FlushOut
- setOutputFile :: Maybe String -> DynFlags -> DynFlags
- setDynOutputFile :: Maybe String -> DynFlags -> DynFlags
- setOutputHi :: Maybe String -> DynFlags -> DynFlags
- setDynOutputHi :: Maybe String -> DynFlags -> DynFlags
- augmentByWorkingDirectory :: DynFlags -> FilePath -> FilePath
- getOpts :: DynFlags -> (DynFlags -> [a]) -> [a]
- getVerbFlags :: DynFlags -> [String]
- updOptLevel :: Int -> DynFlags -> DynFlags
- setTmpDir :: FilePath -> DynFlags -> DynFlags
- setUnitId :: String -> DynFlags -> DynFlags
- type TurnOnFlag = Bool
- turnOn :: TurnOnFlag
- turnOff :: TurnOnFlag
- impliedGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)]
- impliedOffGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)]
- impliedXFlags :: [(Extension, TurnOnFlag, Extension)]
- newtype CmdLineP s a = CmdLineP (forall m. Monad m => StateT s m a)
- runCmdLineP :: CmdLineP s a -> s -> (a, s)
- getCmdLineState :: CmdLineP s s
- putCmdLineState :: s -> CmdLineP s ()
- processCmdLineP :: forall s m. MonadIO m => [Flag (CmdLineP s)] -> s -> [Located String] -> m (([Located String], [Err], [Warn]), s)
- parseDynamicFlagsCmdLine :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn])
- parseDynamicFilePragma :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn])
- parseDynamicFlagsFull :: forall m. MonadIO m => [Flag (CmdLineP DynFlags)] -> Bool -> DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn])
- allNonDeprecatedFlags :: [String]
- flagsAll :: [Flag (CmdLineP DynFlags)]
- flagsDynamic :: [Flag (CmdLineP DynFlags)]
- flagsPackage :: [Flag (CmdLineP DynFlags)]
- flagsForCompletion :: Bool -> [String]
- supportedLanguagesAndExtensions :: ArchOS -> [String]
- languageExtensions :: Maybe Language -> [Extension]
- picCCOpts :: DynFlags -> [String]
- picPOpts :: DynFlags -> [String]
- pieCCLDOpts :: DynFlags -> [String]
- compilerInfo :: DynFlags -> [(String, String)]
- wordAlignment :: Platform -> Alignment
- setUnsafeGlobalDynFlags :: DynFlags -> IO ()
- isSse4_2Enabled :: DynFlags -> Bool
- isBmiEnabled :: DynFlags -> Bool
- isBmi2Enabled :: DynFlags -> Bool
- isAvxEnabled :: DynFlags -> Bool
- isAvx2Enabled :: DynFlags -> Bool
- isAvx512cdEnabled :: DynFlags -> Bool
- isAvx512erEnabled :: DynFlags -> Bool
- isAvx512fEnabled :: DynFlags -> Bool
- isAvx512pfEnabled :: DynFlags -> Bool
- data LinkerInfo
- data CompilerInfo
- useXLinkerRPath :: DynFlags -> OS -> Bool
- 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
Instances
Enum DumpFlag Source # | |
Defined in GHC.Driver.Flags 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
Instances
Enum GeneralFlag Source # | |
Defined in GHC.Driver.Flags 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 (==) :: GeneralFlag -> GeneralFlag -> Bool # (/=) :: GeneralFlag -> GeneralFlag -> Bool # |
data WarningFlag Source #
Instances
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.
WarningWithoutFlag | Born as a warning. |
WarningWithFlag !WarningFlag | Warning was enabled with the flag. |
ErrorWithoutFlag | Born as an error. |
Instances
Show DiagnosticReason Source # | |
Defined in GHC.Types.Error | |
Outputable DiagnosticReason Source # | |
Defined in GHC.Types.Error ppr :: DiagnosticReason -> SDoc Source # | |
Eq DiagnosticReason Source # | |
Defined in GHC.Types.Error (==) :: DiagnosticReason -> DiagnosticReason -> Bool # (/=) :: DiagnosticReason -> DiagnosticReason -> Bool # |
Instances
Bounded Language Source # | |
Enum Language Source # | |
Defined in GHC.Driver.Flags 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
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 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 # | |
glasgowExtsFlags :: [Extension] 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
setGeneralFlag' :: GeneralFlag -> DynFlags -> DynFlags Source #
unSetGeneralFlag' :: GeneralFlag -> DynFlags -> DynFlags Source #
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
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 #
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.Session | |
Eq DynamicTooState Source # | |
Defined in GHC.Driver.Session (==) :: DynamicTooState -> DynamicTooState -> Bool # (/=) :: DynamicTooState -> DynamicTooState -> Bool # | |
Ord DynamicTooState Source # | |
Defined in GHC.Driver.Session 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 #
sccProfilingEnabled :: DynFlags -> Bool Source #
Indicate if cost-centre profiling is enabled
needSourceNotes :: DynFlags -> Bool Source #
Indicate whether we need to generate source notes
Contains not only a collection of GeneralFlag
s but also a plethora of
information relating to the compilation of a single file or GHC session
DynFlags | |
|
FlagSpec | |
|
class HasDynFlags m where Source #
getDynFlags :: m DynFlags Source #
Instances
class ContainsDynFlags t where Source #
extractDynFlags :: t -> DynFlags Source #
Instances
ContainsDynFlags HscEnv Source # | |
Defined in GHC.Driver.Env.Types extractDynFlags :: HscEnv -> DynFlags Source # | |
ContainsDynFlags (Env gbl lcl) Source # | |
Defined in GHC.Tc.Types extractDynFlags :: Env gbl lcl -> DynFlags Source # |
data RtsOptsEnabled Source #
Instances
Show RtsOptsEnabled Source # | |
Defined in GHC.Driver.Session |
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.
CompManager |
|
OneShot | ghc -c Foo.hs |
MkDepend |
|
What to do in the link step, if there is one.
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.
ExposePackage String PackageArg ModRenaming |
|
HidePackage String | -hide-package |
Instances
Outputable PackageFlag Source # | |
Defined in GHC.Driver.Session ppr :: PackageFlag -> SDoc Source # | |
Eq PackageFlag Source # | |
Defined in GHC.Driver.Session (==) :: PackageFlag -> PackageFlag -> Bool # (/=) :: PackageFlag -> PackageFlag -> Bool # |
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.
PackageArg String |
|
UnitIdArg Unit |
|
Instances
Show PackageArg Source # | |
Defined in GHC.Driver.Session | |
Outputable PackageArg Source # | |
Defined in GHC.Driver.Session ppr :: PackageArg -> SDoc Source # | |
Eq PackageArg Source # | |
Defined in GHC.Driver.Session (==) :: PackageArg -> PackageArg -> Bool # (/=) :: PackageArg -> PackageArg -> Bool # |
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
:
ModRenaming | |
|
Instances
Outputable ModRenaming Source # | |
Defined in GHC.Driver.Session ppr :: ModRenaming -> SDoc Source # | |
Eq ModRenaming Source # | |
Defined in GHC.Driver.Session (==) :: ModRenaming -> ModRenaming -> Bool # (/=) :: ModRenaming -> ModRenaming -> Bool # |
newtype IgnorePackageFlag Source #
Flags for manipulating the set of non-broken packages.
IgnorePackage String | -ignore-package |
Instances
Eq IgnorePackageFlag Source # | |
Defined in GHC.Driver.Session (==) :: IgnorePackageFlag -> IgnorePackageFlag -> Bool # (/=) :: IgnorePackageFlag -> IgnorePackageFlag -> Bool # |
Flags for manipulating package trust.
TrustPackage String | -trust |
DistrustPackage String | -distrust |
data PackageDBFlag Source #
Instances
Eq PackageDBFlag Source # | |
Defined in GHC.Driver.Session (==) :: PackageDBFlag -> PackageDBFlag -> Bool # (/=) :: PackageDBFlag -> PackageDBFlag -> Bool # |
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.
data DynLibLoader Source #
Instances
Eq DynLibLoader Source # | |
Defined in GHC.Driver.Session (==) :: DynLibLoader -> DynLibLoader -> Bool # (/=) :: DynLibLoader -> DynLibLoader -> 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>
wWarningFlags :: [FlagSpec WarningFlag] Source #
These -W<blah>
flags can all be reversed with -Wno-<blah>
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)
codeGenFlags :: EnumSet GeneralFlag Source #
The set of flags which affect code generation and can change a program's runtime behavior (other than performance). These include flags which affect:
- user visible debugging information (e.g. info table provenance)
- the ability to catch runtime errors (e.g. -fignore-asserts)
- the runtime result of the program (e.g. -fomit-yields)
- which code or interface file declarations are emitted
We also considered placing flags which affect asympototic space behavior (e.g. -ffull-laziness) however this would mean that changing optimisation levels would trigger recompilation even with -fignore-optim-changes, regressing #13604.
Also, arguably Opt_IgnoreAsserts should be here as well; however, we place
it instead in optimisationFlags
since it is implied by -O[12]
and
therefore would also break #13604.
See #23369.
setFlagsFromEnvFile :: FilePath -> String -> DynP () Source #
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.
flagSpecOf :: WarningFlag -> Maybe (FlagSpec WarningFlag) Source #
Find the FlagSpec
for a WarningFlag
.
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
Settings | |
|
sProgramName :: Settings -> String Source #
sProjectVersion :: Settings -> String Source #
sGhcUsagePath :: Settings -> FilePath Source #
sGhciUsagePath :: Settings -> FilePath Source #
sLdSupportsFilelist :: Settings -> Bool Source #
sLdIsGnuLd :: Settings -> Bool Source #
sGccSupportsNoPie :: Settings -> Bool Source #
sPgm_windres :: Settings -> String Source #
sPgm_ranlib :: Settings -> String Source #
sOpt_windres :: Settings -> [String] Source #
sExtraGccViaCFlags :: Settings -> [String] Source #
sGhcWithInterpreter :: Settings -> Bool Source #
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).
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 #
pgm_windres :: DynFlags -> String Source #
pgm_ranlib :: DynFlags -> String Source #
opt_P_signature :: DynFlags -> ([String], Fingerprint) Source #
opt_windres :: DynFlags -> [String] Source #
Manipulating DynFlags
defaultDynFlags :: Settings -> DynFlags Source #
:: DynFlags |
|
-> (DynFlags -> [a]) | Relevant record accessor: one of the |
-> [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
type TurnOnFlag = Bool Source #
turnOn :: TurnOnFlag Source #
turnOff :: TurnOnFlag Source #
impliedGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)] Source #
impliedOffGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)] Source #
impliedXFlags :: [(Extension, TurnOnFlag, Extension)] Source #
State
Instances
Applicative (CmdLineP s) Source # | |
Defined in GHC.Driver.Session 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 # | |
Monad (CmdLineP s) Source # | |
runCmdLineP :: CmdLineP s a -> s -> (a, s) Source #
getCmdLineState :: CmdLineP s s Source #
putCmdLineState :: s -> CmdLineP s () Source #
:: 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 #
:: MonadIO m | |
=> DynFlags | |
-> [Located String] | |
-> m (DynFlags, [Located String], [Warn]) | Updated |
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 #
:: MonadIO m | |
=> DynFlags | |
-> [Located String] | |
-> m (DynFlags, [Located String], [Warn]) | Updated |
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 #
:: 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
pieCCLDOpts :: DynFlags -> [String] Source #
Compiler configuration suitable for display to the user
wordAlignment :: Platform -> Alignment Source #
setUnsafeGlobalDynFlags :: DynFlags -> IO () Source #
SSE and AVX
isSse4_2Enabled :: DynFlags -> Bool Source #
isBmiEnabled :: DynFlags -> Bool Source #
isBmi2Enabled :: DynFlags -> Bool Source #
isAvxEnabled :: DynFlags -> Bool Source #
isAvx2Enabled :: DynFlags -> Bool Source #
isAvx512cdEnabled :: DynFlags -> Bool Source #
isAvx512erEnabled :: DynFlags -> Bool Source #
isAvx512fEnabled :: DynFlags -> Bool Source #
isAvx512pfEnabled :: DynFlags -> Bool Source #
Linker/compiler information
data LinkerInfo Source #
GnuLD [Option] | |
GnuGold [Option] | |
LlvmLLD [Option] | |
DarwinLD [Option] | |
SolarisLD [Option] | |
AixLD [Option] | |
UnknownLD |
Instances
Eq LinkerInfo Source # | |
Defined in GHC.Driver.Session (==) :: LinkerInfo -> LinkerInfo -> Bool # (/=) :: LinkerInfo -> LinkerInfo -> Bool # |
data CompilerInfo Source #
Instances
Eq CompilerInfo Source # | |
Defined in GHC.Driver.Session (==) :: CompilerInfo -> CompilerInfo -> Bool # (/=) :: CompilerInfo -> CompilerInfo -> Bool # |
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.
IncludeSpecs | |
|
Instances
Show IncludeSpecs Source # | |
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