| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
DynFlags
Contents
Description
Dynamic flags
Most flags are dynamic flags, which means they can change from compilation
 to compilation using OPTIONS_GHC pragmas, and in a multi-session GHC each
 session can be using different dynamic flags. Dynamic flags can also be set
 at the prompt in GHCi.
(c) The University of Glasgow 2005
Synopsis
- 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_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_asm_expanded
- | Opt_D_dump_llvm
- | 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_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_stg
- | 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_tc
- | Opt_D_dump_tc_ast
- | Opt_D_dump_types
- | Opt_D_dump_rules
- | Opt_D_dump_cse
- | Opt_D_dump_worker_wrapper
- | Opt_D_dump_rn_trace
- | Opt_D_dump_rn_stats
- | Opt_D_dump_opt_cmm
- | Opt_D_dump_simpl_stats
- | Opt_D_dump_cs_trace
- | Opt_D_dump_tc_trace
- | Opt_D_dump_ec_trace
- | Opt_D_dump_if_trace
- | Opt_D_dump_vt_trace
- | Opt_D_dump_splices
- | Opt_D_th_dec_file
- | Opt_D_dump_BCOs
- | Opt_D_dump_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
 
- data GeneralFlag- = Opt_DumpToFile
- | Opt_D_faststring_stats
- | Opt_D_dump_minimal_imports
- | Opt_DoCoreLinting
- | Opt_DoStgLinting
- | Opt_DoCmmLinting
- | Opt_DoAsmLinting
- | Opt_DoAnnotationLinting
- | Opt_NoLlvmMangler
- | Opt_FastLlvm
- | Opt_NoTypeableBinds
- | 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_PrintTypecheckerElaboration
- | Opt_CallArity
- | Opt_Exitification
- | Opt_Strictness
- | Opt_LateDmdAnal
- | Opt_KillAbsence
- | Opt_KillOneShot
- | Opt_FullLaziness
- | Opt_FloatIn
- | Opt_LateSpecialise
- | Opt_Specialise
- | Opt_SpecialiseAggressively
- | Opt_CrossModuleSpecialise
- | 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_RegsGraph
- | Opt_RegsIterative
- | Opt_PedanticBottoms
- | Opt_LlvmTBAA
- | Opt_LlvmFillUndefWithGarbage
- | Opt_IrrefutableTuples
- | Opt_CmmSink
- | Opt_CmmElimCommonBlocks
- | Opt_AsmShortcutting
- | Opt_OmitYields
- | Opt_FunToThunk
- | Opt_DictsStrict
- | Opt_DmdTxDictSel
- | Opt_Loopification
- | Opt_CfgBlocklayout
- | Opt_WeightlessBlocklayout
- | Opt_CprAnal
- | Opt_WorkerWrapper
- | Opt_SolveConstantDicts
- | Opt_AlignmentSanitisation
- | Opt_CatchBottoms
- | Opt_NumConstantFolding
- | Opt_SimplPreInlining
- | Opt_IgnoreInterfacePragmas
- | Opt_OmitInterfacePragmas
- | Opt_ExposeAllUnfoldings
- | Opt_WriteInterface
- | Opt_WriteHie
- | Opt_AutoSccsOnIndividualCafs
- | Opt_ProfCountEntries
- | 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_SccProfilingOn
- | Opt_Ticky
- | Opt_Ticky_Allocd
- | Opt_Ticky_LNE
- | Opt_Ticky_Dyn_Thunk
- | Opt_RPath
- | Opt_RelativeDynlibPaths
- | Opt_Hpc
- | Opt_FlatCache
- | Opt_ExternalInterpreter
- | Opt_OptimalApplicativeDo
- | Opt_VersionMacros
- | Opt_WholeArchiveHsLibs
- | Opt_SingleLibFolder
- | Opt_KeepCAFs
- | Opt_KeepGoing
- | Opt_ByteCode
- | 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_SuppressVarKinds
- | Opt_SuppressModulePrefixes
- | Opt_SuppressTypeApplications
- | Opt_SuppressIdInfo
- | Opt_SuppressUnfoldings
- | Opt_SuppressTypeSignatures
- | Opt_SuppressUniques
- | Opt_SuppressStgExts
- | Opt_SuppressTicks
- | Opt_SuppressTimestamps
- | 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_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_WarnRedundantRecordWildcards
- | Opt_WarnWarningsDeprecations
- | Opt_WarnDeprecatedFlags
- | Opt_WarnMissingMonadFailInstances
- | Opt_WarnSemigroup
- | Opt_WarnDodgyExports
- | Opt_WarnDodgyImports
- | Opt_WarnOrphans
- | Opt_WarnAutoOrphans
- | Opt_WarnIdentities
- | Opt_WarnTabs
- | Opt_WarnUnrecognisedPragmas
- | Opt_WarnDodgyForeignImports
- | Opt_WarnUnusedDoBind
- | Opt_WarnWrongDoBind
- | Opt_WarnAlternativeLayoutRuleTransitional
- | Opt_WarnUnsafe
- | Opt_WarnSafe
- | Opt_WarnTrustworthySafe
- | Opt_WarnMissedSpecs
- | Opt_WarnAllMissedSpecs
- | Opt_WarnUnsupportedCallingConventions
- | Opt_WarnUnsupportedLlvmVersion
- | Opt_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_WarnDerivingDefaults
 
- data WarnReason- = NoReason
- | Reason !WarningFlag
- | ErrReason !(Maybe WarningFlag)
 
- data Language
- data PlatformConstants = PlatformConstants {- pc_CONTROL_GROUP_CONST_291 :: Int
- pc_STD_HDR_SIZE :: Int
- pc_PROF_HDR_SIZE :: Int
- pc_BLOCK_SIZE :: Int
- pc_BLOCKS_PER_MBLOCK :: Int
- pc_TICKY_BIN_COUNT :: Int
- pc_OFFSET_StgRegTable_rR1 :: Int
- pc_OFFSET_StgRegTable_rR2 :: Int
- pc_OFFSET_StgRegTable_rR3 :: Int
- pc_OFFSET_StgRegTable_rR4 :: Int
- pc_OFFSET_StgRegTable_rR5 :: Int
- pc_OFFSET_StgRegTable_rR6 :: Int
- pc_OFFSET_StgRegTable_rR7 :: Int
- pc_OFFSET_StgRegTable_rR8 :: Int
- pc_OFFSET_StgRegTable_rR9 :: Int
- pc_OFFSET_StgRegTable_rR10 :: Int
- pc_OFFSET_StgRegTable_rF1 :: Int
- pc_OFFSET_StgRegTable_rF2 :: Int
- pc_OFFSET_StgRegTable_rF3 :: Int
- pc_OFFSET_StgRegTable_rF4 :: Int
- pc_OFFSET_StgRegTable_rF5 :: Int
- pc_OFFSET_StgRegTable_rF6 :: Int
- pc_OFFSET_StgRegTable_rD1 :: Int
- pc_OFFSET_StgRegTable_rD2 :: Int
- pc_OFFSET_StgRegTable_rD3 :: Int
- pc_OFFSET_StgRegTable_rD4 :: Int
- pc_OFFSET_StgRegTable_rD5 :: Int
- pc_OFFSET_StgRegTable_rD6 :: Int
- pc_OFFSET_StgRegTable_rXMM1 :: Int
- pc_OFFSET_StgRegTable_rXMM2 :: Int
- pc_OFFSET_StgRegTable_rXMM3 :: Int
- pc_OFFSET_StgRegTable_rXMM4 :: Int
- pc_OFFSET_StgRegTable_rXMM5 :: Int
- pc_OFFSET_StgRegTable_rXMM6 :: Int
- pc_OFFSET_StgRegTable_rYMM1 :: Int
- pc_OFFSET_StgRegTable_rYMM2 :: Int
- pc_OFFSET_StgRegTable_rYMM3 :: Int
- pc_OFFSET_StgRegTable_rYMM4 :: Int
- pc_OFFSET_StgRegTable_rYMM5 :: Int
- pc_OFFSET_StgRegTable_rYMM6 :: Int
- pc_OFFSET_StgRegTable_rZMM1 :: Int
- pc_OFFSET_StgRegTable_rZMM2 :: Int
- pc_OFFSET_StgRegTable_rZMM3 :: Int
- pc_OFFSET_StgRegTable_rZMM4 :: Int
- pc_OFFSET_StgRegTable_rZMM5 :: Int
- pc_OFFSET_StgRegTable_rZMM6 :: Int
- pc_OFFSET_StgRegTable_rL1 :: Int
- pc_OFFSET_StgRegTable_rSp :: Int
- pc_OFFSET_StgRegTable_rSpLim :: Int
- pc_OFFSET_StgRegTable_rHp :: Int
- pc_OFFSET_StgRegTable_rHpLim :: Int
- pc_OFFSET_StgRegTable_rCCCS :: Int
- pc_OFFSET_StgRegTable_rCurrentTSO :: Int
- pc_OFFSET_StgRegTable_rCurrentNursery :: Int
- pc_OFFSET_StgRegTable_rHpAlloc :: Int
- pc_OFFSET_stgEagerBlackholeInfo :: Int
- pc_OFFSET_stgGCEnter1 :: Int
- pc_OFFSET_stgGCFun :: Int
- pc_OFFSET_Capability_r :: Int
- pc_OFFSET_bdescr_start :: Int
- pc_OFFSET_bdescr_free :: Int
- pc_OFFSET_bdescr_blocks :: Int
- pc_OFFSET_bdescr_flags :: Int
- pc_SIZEOF_CostCentreStack :: Int
- pc_OFFSET_CostCentreStack_mem_alloc :: Int
- pc_REP_CostCentreStack_mem_alloc :: Int
- pc_OFFSET_CostCentreStack_scc_count :: Int
- pc_REP_CostCentreStack_scc_count :: Int
- pc_OFFSET_StgHeader_ccs :: Int
- pc_OFFSET_StgHeader_ldvw :: Int
- pc_SIZEOF_StgSMPThunkHeader :: Int
- pc_OFFSET_StgEntCounter_allocs :: Int
- pc_REP_StgEntCounter_allocs :: Int
- pc_OFFSET_StgEntCounter_allocd :: Int
- pc_REP_StgEntCounter_allocd :: Int
- pc_OFFSET_StgEntCounter_registeredp :: Int
- pc_OFFSET_StgEntCounter_link :: Int
- pc_OFFSET_StgEntCounter_entry_count :: Int
- pc_SIZEOF_StgUpdateFrame_NoHdr :: Int
- pc_SIZEOF_StgMutArrPtrs_NoHdr :: Int
- pc_OFFSET_StgMutArrPtrs_ptrs :: Int
- pc_OFFSET_StgMutArrPtrs_size :: Int
- pc_SIZEOF_StgSmallMutArrPtrs_NoHdr :: Int
- pc_OFFSET_StgSmallMutArrPtrs_ptrs :: Int
- pc_SIZEOF_StgArrBytes_NoHdr :: Int
- pc_OFFSET_StgArrBytes_bytes :: Int
- pc_OFFSET_StgTSO_alloc_limit :: Int
- pc_OFFSET_StgTSO_cccs :: Int
- pc_OFFSET_StgTSO_stackobj :: Int
- pc_OFFSET_StgStack_sp :: Int
- pc_OFFSET_StgStack_stack :: Int
- pc_OFFSET_StgUpdateFrame_updatee :: Int
- pc_OFFSET_StgFunInfoExtraFwd_arity :: Int
- pc_REP_StgFunInfoExtraFwd_arity :: Int
- pc_SIZEOF_StgFunInfoExtraRev :: Int
- pc_OFFSET_StgFunInfoExtraRev_arity :: Int
- pc_REP_StgFunInfoExtraRev_arity :: Int
- pc_MAX_SPEC_SELECTEE_SIZE :: Int
- pc_MAX_SPEC_AP_SIZE :: Int
- pc_MIN_PAYLOAD_SIZE :: Int
- pc_MIN_INTLIKE :: Int
- pc_MAX_INTLIKE :: Int
- pc_MIN_CHARLIKE :: Int
- pc_MAX_CHARLIKE :: Int
- pc_MUT_ARR_PTRS_CARD_BITS :: Int
- pc_MAX_Vanilla_REG :: Int
- pc_MAX_Float_REG :: Int
- pc_MAX_Double_REG :: Int
- pc_MAX_Long_REG :: Int
- pc_MAX_XMM_REG :: Int
- pc_MAX_Real_Vanilla_REG :: Int
- pc_MAX_Real_Float_REG :: Int
- pc_MAX_Real_Double_REG :: Int
- pc_MAX_Real_XMM_REG :: Int
- pc_MAX_Real_Long_REG :: Int
- pc_RESERVED_C_STACK_BYTES :: Int
- pc_RESERVED_STACK_WORDS :: Int
- pc_AP_STACK_SPLIM :: Int
- pc_WORD_SIZE :: Int
- pc_DOUBLE_SIZE :: Int
- pc_CINT_SIZE :: Int
- pc_CLONG_SIZE :: Int
- pc_CLONG_LONG_SIZE :: Int
- pc_BITMAP_BITS_SHIFT :: Int
- pc_TAG_BITS :: Int
- pc_WORDS_BIGENDIAN :: Bool
- pc_DYNAMIC_BY_DEFAULT :: Bool
- pc_LDV_SHIFT :: Int
- pc_ILDV_CREATE_MASK :: Integer
- pc_ILDV_STATE_CREATE :: Integer
- pc_ILDV_STATE_USE :: Integer
 
- type FatalMessager = String -> IO ()
- type LogAction = DynFlags -> WarnReason -> Severity -> SrcSpan -> PprStyle -> MsgDoc -> IO ()
- newtype FlushOut = FlushOut (IO ())
- newtype FlushErr = FlushErr (IO ())
- data ProfAuto
- glasgowExtsFlags :: [Extension]
- warningGroups :: [(String, [WarningFlag])]
- warningHierarchies :: [[String]]
- 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
- lang_set :: DynFlags -> Maybe Language -> DynFlags
- useUnicodeSyntax :: DynFlags -> Bool
- useStarIsType :: DynFlags -> Bool
- whenGeneratingDynamicToo :: MonadIO m => DynFlags -> m () -> m ()
- ifGeneratingDynamicToo :: MonadIO m => DynFlags -> m a -> m a -> m a
- whenCannotGenerateDynamicToo :: MonadIO m => DynFlags -> m () -> m ()
- dynamicTooMkDynamicDynFlags :: DynFlags -> DynFlags
- dynamicOutputFile :: DynFlags -> FilePath -> FilePath
- data DynFlags = DynFlags {- ghcMode :: GhcMode
- ghcLink :: GhcLink
- hscTarget :: HscTarget
- ghcNameVersion :: !GhcNameVersion
- fileSettings :: !FileSettings
- targetPlatform :: Platform
- toolSettings :: !ToolSettings
- platformMisc :: !PlatformMisc
- platformConstants :: PlatformConstants
- rawSettings :: [(String, String)]
- integerLibrary :: IntegerLibrary
- llvmTargets :: LlvmTargets
- llvmPasses :: LlvmPasses
- verbosity :: Int
- optLevel :: Int
- debugLevel :: Int
- simplPhases :: Int
- maxSimplIterations :: Int
- ruleCheck :: Maybe String
- inlineCheck :: 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
- specConstrThreshold :: Maybe Int
- specConstrCount :: Maybe Int
- specConstrRecursive :: Int
- binBlobThreshold :: Word
- liberateCaseThreshold :: Maybe Int
- floatLamArgs :: Maybe Int
- liftLamsRecArgs :: Maybe Int
- liftLamsNonRecArgs :: Maybe Int
- liftLamsKnown :: Bool
- cmmProcAlignment :: Maybe Int
- historySize :: Int
- importPaths :: [FilePath]
- mainModIs :: Module
- mainFunIs :: Maybe String
- reductionDepth :: IntWithInf
- solverIterations :: IntWithInf
- thisInstalledUnitId :: InstalledUnitId
- thisComponentId_ :: Maybe ComponentId
- thisUnitIdInsts_ :: Maybe [(ModuleName, Module)]
- ways :: [Way]
- buildTag :: String
- 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
- canGenerateDynamicToo :: IORef Bool
- dynObjectSuf :: String
- dynHiSuf :: String
- outputFile :: Maybe String
- dynOutputFile :: Maybe String
- outputHi :: Maybe String
- dynLibLoader :: DynLibLoader
- dumpPrefix :: Maybe 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]
- cachedPlugins :: [LoadedPlugin]
- staticPlugins :: [StaticPlugin]
- hooks :: Hooks
- depMakefile :: FilePath
- depIncludePkgDeps :: Bool
- depIncludeCppDeps :: Bool
- depExcludeMods :: [ModuleName]
- depSuffixes :: [String]
- packageDBFlags :: [PackageDBFlag]
- ignorePackageFlags :: [IgnorePackageFlag]
- packageFlags :: [PackageFlag]
- pluginPackageFlags :: [PackageFlag]
- trustFlags :: [TrustFlag]
- packageEnv :: Maybe FilePath
- pkgDatabase :: Maybe [(FilePath, [PackageConfig])]
- pkgState :: PackageState
- filesToClean :: IORef FilesToClean
- dirsToClean :: IORef (Map FilePath FilePath)
- nextTempSuffix :: IORef Int
- generatedDumps :: IORef (Set 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
- overlapInstLoc :: SrcSpan
- incoherentOnLoc :: SrcSpan
- pkgTrustOnLoc :: SrcSpan
- warnSafeOnLoc :: SrcSpan
- warnUnsafeOnLoc :: SrcSpan
- trustworthyOnLoc :: SrcSpan
- extensions :: [OnOff Extension]
- extensionFlags :: EnumSet Extension
- ufCreationThreshold :: Int
- ufUseThreshold :: Int
- ufFunAppDiscount :: Int
- ufDictDiscount :: Int
- ufKeenessFactor :: Float
- ufDearOp :: Int
- ufVeryAggressive :: Bool
- maxWorkerArgs :: Int
- ghciHistSize :: Int
- log_action :: LogAction
- flushOut :: FlushOut
- flushErr :: FlushErr
- ghcVersionFile :: Maybe FilePath
- haddockOptions :: Maybe String
- ghciScripts :: [String]
- pprUserLength :: Int
- pprCols :: Int
- useUnicode :: Bool
- useColor :: OverridingBool
- canUseColor :: Bool
- colScheme :: Scheme
- profAuto :: ProfAuto
- interactivePrint :: Maybe String
- nextWrapperNum :: IORef (ModuleEnv Int)
- 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)
- maxInlineAllocSize :: Int
- maxInlineMemcpyInsns :: Int
- maxInlineMemsetInsns :: Int
- reverseErrors :: Bool
- maxErrors :: Maybe Int
- initialUnique :: Int
- uniqueIncrement :: Int
- cfgWeightInfo :: CfgWeights
 
- 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 HscTarget
- isObjectTarget :: HscTarget -> Bool
- defaultObjectTarget :: DynFlags -> HscTarget
- targetRetainsAllBindings :: HscTarget -> Bool
- 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 PkgConfRef
- data Option
- showOpt :: Option -> String
- data DynLibLoader
- fFlags :: [FlagSpec GeneralFlag]
- fLangFlags :: [FlagSpec Extension]
- xFlags :: [FlagSpec Extension]
- wWarningFlags :: [FlagSpec WarningFlag]
- dynFlagDependencies :: DynFlags -> [ModuleName]
- makeDynFlagsConsistent :: DynFlags -> (DynFlags, [Located String])
- shouldUseColor :: DynFlags -> Bool
- shouldUseHexWordLiterals :: DynFlags -> Bool
- positionIndependent :: DynFlags -> Bool
- optimisationFlags :: EnumSet GeneralFlag
- setFlagsFromEnvFile :: FilePath -> String -> DynP ()
- data Way
- mkBuildTag :: [Way] -> String
- wayRTSOnly :: Way -> Bool
- addWay' :: Way -> DynFlags -> DynFlags
- updateWays :: DynFlags -> DynFlags
- wayGeneralFlags :: Platform -> Way -> [GeneralFlag]
- wayUnsetGeneralFlags :: Platform -> Way -> [GeneralFlag]
- thisPackage :: DynFlags -> UnitId
- thisComponentId :: DynFlags -> ComponentId
- thisUnitIdInsts :: DynFlags -> [(ModuleName, Module)]
- putLogMsg :: DynFlags -> WarnReason -> Severity -> SrcSpan -> PprStyle -> MsgDoc -> IO ()
- data SafeHaskellMode
- 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 LlvmTarget = LlvmTarget {- lDataLayout :: String
- lCPU :: String
- lAttributes :: [String]
 
- type LlvmTargets = [(String, LlvmTarget)]
- type LlvmPasses = [(Int, String)]
- type LlvmConfig = (LlvmTargets, LlvmPasses)
- data Settings = Settings {}
- sProgramName :: Settings -> String
- sProjectVersion :: Settings -> String
- sGhcUsagePath :: Settings -> FilePath
- sGhciUsagePath :: Settings -> FilePath
- sToolDir :: Settings -> Maybe FilePath
- sTopDir :: Settings -> FilePath
- sTmpDir :: Settings -> String
- sSystemPackageConfig :: Settings -> FilePath
- sLdSupportsCompactUnwind :: Settings -> Bool
- sLdSupportsBuildId :: 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_a :: Settings -> (String, [Option])
- sPgm_l :: Settings -> (String, [Option])
- sPgm_dll :: Settings -> (String, [Option])
- sPgm_T :: Settings -> String
- sPgm_windres :: Settings -> String
- sPgm_libtool :: 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_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
- sIntegerLibrary :: Settings -> String
- sIntegerLibraryType :: Settings -> IntegerLibrary
- sGhcWithInterpreter :: Settings -> Bool
- sGhcWithNativeCodeGen :: Settings -> Bool
- sGhcWithSMP :: Settings -> Bool
- sGhcRTSWays :: Settings -> String
- sTablesNextToCode :: Settings -> Bool
- sLeadingUnderscore :: Settings -> Bool
- sLibFFI :: Settings -> Bool
- sGhcThreaded :: Settings -> Bool
- sGhcDebugged :: Settings -> Bool
- sGhcRtsWithLibdw :: Settings -> Bool
- data IntegerLibrary
- data GhcNameVersion = GhcNameVersion {}
- data FileSettings = FileSettings {}
- data PlatformMisc = PlatformMisc {- platformMisc_targetPlatformString :: String
- platformMisc_integerLibrary :: String
- platformMisc_integerLibraryType :: IntegerLibrary
- platformMisc_ghcWithInterpreter :: Bool
- platformMisc_ghcWithNativeCodeGen :: Bool
- platformMisc_ghcWithSMP :: Bool
- platformMisc_ghcRTSWays :: String
- platformMisc_tablesNextToCode :: Bool
- platformMisc_leadingUnderscore :: Bool
- platformMisc_libFFI :: Bool
- platformMisc_ghcThreaded :: Bool
- platformMisc_ghcDebugged :: Bool
- platformMisc_ghcRtsWithLibdw :: Bool
- platformMisc_llvmTarget :: String
 
- settings :: DynFlags -> Settings
- programName :: DynFlags -> String
- projectVersion :: DynFlags -> String
- ghcUsagePath :: DynFlags -> FilePath
- ghciUsagePath :: DynFlags -> FilePath
- topDir :: DynFlags -> FilePath
- tmpDir :: DynFlags -> String
- versionedAppDir :: DynFlags -> MaybeT IO FilePath
- versionedFilePath :: DynFlags -> FilePath
- extraGccViaCFlags :: DynFlags -> [String]
- systemPackageConfig :: DynFlags -> FilePath
- pgm_L :: DynFlags -> String
- pgm_P :: DynFlags -> (String, [Option])
- pgm_F :: DynFlags -> String
- pgm_c :: DynFlags -> String
- pgm_a :: DynFlags -> (String, [Option])
- pgm_l :: DynFlags -> (String, [Option])
- pgm_dll :: DynFlags -> (String, [Option])
- pgm_T :: DynFlags -> String
- pgm_windres :: DynFlags -> String
- pgm_libtool :: 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_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]
- tablesNextToCode :: DynFlags -> Bool
- addPluginModuleName :: String -> DynFlags -> DynFlags
- defaultDynFlags :: Settings -> LlvmConfig -> DynFlags
- defaultWays :: Settings -> [Way]
- interpWays :: [Way]
- interpreterProfiled :: DynFlags -> Bool
- interpreterDynamic :: DynFlags -> Bool
- initDynFlags :: DynFlags -> IO DynFlags
- defaultFatalMessager :: FatalMessager
- defaultLogAction :: LogAction
- defaultLogActionHPrintDoc :: DynFlags -> Handle -> SDoc -> PprStyle -> IO ()
- defaultLogActionHPutStrDoc :: DynFlags -> Handle -> SDoc -> PprStyle -> IO ()
- defaultFlushOut :: FlushOut
- defaultFlushErr :: FlushErr
- getOpts :: DynFlags -> (DynFlags -> [a]) -> [a]
- getVerbFlags :: DynFlags -> [String]
- updOptLevel :: Int -> DynFlags -> DynFlags
- setTmpDir :: FilePath -> DynFlags -> DynFlags
- setUnitId :: String -> DynFlags -> DynFlags
- canonicalizeHomeModule :: DynFlags -> ModuleName -> Module
- canonicalizeModuleIfHome :: DynFlags -> Module -> Module
- parseDynamicFlagsCmdLine :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn])
- parseDynamicFilePragma :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Warn])
- parseDynamicFlagsFull :: 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 :: [String]
- languageExtensions :: Maybe Language -> [Extension]
- picCCOpts :: DynFlags -> [String]
- picPOpts :: DynFlags -> [String]
- compilerInfo :: DynFlags -> [(String, String)]
- rtsIsProfiled :: Bool
- dynamicGhc :: Bool
- cONTROL_GROUP_CONST_291 :: DynFlags -> Int
- sTD_HDR_SIZE :: DynFlags -> Int
- pROF_HDR_SIZE :: DynFlags -> Int
- bLOCK_SIZE :: DynFlags -> Int
- bLOCKS_PER_MBLOCK :: DynFlags -> Int
- tICKY_BIN_COUNT :: DynFlags -> Int
- oFFSET_StgRegTable_rR1 :: DynFlags -> Int
- oFFSET_StgRegTable_rR2 :: DynFlags -> Int
- oFFSET_StgRegTable_rR3 :: DynFlags -> Int
- oFFSET_StgRegTable_rR4 :: DynFlags -> Int
- oFFSET_StgRegTable_rR5 :: DynFlags -> Int
- oFFSET_StgRegTable_rR6 :: DynFlags -> Int
- oFFSET_StgRegTable_rR7 :: DynFlags -> Int
- oFFSET_StgRegTable_rR8 :: DynFlags -> Int
- oFFSET_StgRegTable_rR9 :: DynFlags -> Int
- oFFSET_StgRegTable_rR10 :: DynFlags -> Int
- oFFSET_StgRegTable_rF1 :: DynFlags -> Int
- oFFSET_StgRegTable_rF2 :: DynFlags -> Int
- oFFSET_StgRegTable_rF3 :: DynFlags -> Int
- oFFSET_StgRegTable_rF4 :: DynFlags -> Int
- oFFSET_StgRegTable_rF5 :: DynFlags -> Int
- oFFSET_StgRegTable_rF6 :: DynFlags -> Int
- oFFSET_StgRegTable_rD1 :: DynFlags -> Int
- oFFSET_StgRegTable_rD2 :: DynFlags -> Int
- oFFSET_StgRegTable_rD3 :: DynFlags -> Int
- oFFSET_StgRegTable_rD4 :: DynFlags -> Int
- oFFSET_StgRegTable_rD5 :: DynFlags -> Int
- oFFSET_StgRegTable_rD6 :: DynFlags -> Int
- oFFSET_StgRegTable_rXMM1 :: DynFlags -> Int
- oFFSET_StgRegTable_rXMM2 :: DynFlags -> Int
- oFFSET_StgRegTable_rXMM3 :: DynFlags -> Int
- oFFSET_StgRegTable_rXMM4 :: DynFlags -> Int
- oFFSET_StgRegTable_rXMM5 :: DynFlags -> Int
- oFFSET_StgRegTable_rXMM6 :: DynFlags -> Int
- oFFSET_StgRegTable_rYMM1 :: DynFlags -> Int
- oFFSET_StgRegTable_rYMM2 :: DynFlags -> Int
- oFFSET_StgRegTable_rYMM3 :: DynFlags -> Int
- oFFSET_StgRegTable_rYMM4 :: DynFlags -> Int
- oFFSET_StgRegTable_rYMM5 :: DynFlags -> Int
- oFFSET_StgRegTable_rYMM6 :: DynFlags -> Int
- oFFSET_StgRegTable_rZMM1 :: DynFlags -> Int
- oFFSET_StgRegTable_rZMM2 :: DynFlags -> Int
- oFFSET_StgRegTable_rZMM3 :: DynFlags -> Int
- oFFSET_StgRegTable_rZMM4 :: DynFlags -> Int
- oFFSET_StgRegTable_rZMM5 :: DynFlags -> Int
- oFFSET_StgRegTable_rZMM6 :: DynFlags -> Int
- oFFSET_StgRegTable_rL1 :: DynFlags -> Int
- oFFSET_StgRegTable_rSp :: DynFlags -> Int
- oFFSET_StgRegTable_rSpLim :: DynFlags -> Int
- oFFSET_StgRegTable_rHp :: DynFlags -> Int
- oFFSET_StgRegTable_rHpLim :: DynFlags -> Int
- oFFSET_StgRegTable_rCCCS :: DynFlags -> Int
- oFFSET_StgRegTable_rCurrentTSO :: DynFlags -> Int
- oFFSET_StgRegTable_rCurrentNursery :: DynFlags -> Int
- oFFSET_StgRegTable_rHpAlloc :: DynFlags -> Int
- oFFSET_stgEagerBlackholeInfo :: DynFlags -> Int
- oFFSET_stgGCEnter1 :: DynFlags -> Int
- oFFSET_stgGCFun :: DynFlags -> Int
- oFFSET_Capability_r :: DynFlags -> Int
- oFFSET_bdescr_start :: DynFlags -> Int
- oFFSET_bdescr_free :: DynFlags -> Int
- oFFSET_bdescr_blocks :: DynFlags -> Int
- oFFSET_bdescr_flags :: DynFlags -> Int
- sIZEOF_CostCentreStack :: DynFlags -> Int
- oFFSET_CostCentreStack_mem_alloc :: DynFlags -> Int
- oFFSET_CostCentreStack_scc_count :: DynFlags -> Int
- oFFSET_StgHeader_ccs :: DynFlags -> Int
- oFFSET_StgHeader_ldvw :: DynFlags -> Int
- sIZEOF_StgSMPThunkHeader :: DynFlags -> Int
- oFFSET_StgEntCounter_allocs :: DynFlags -> Int
- oFFSET_StgEntCounter_allocd :: DynFlags -> Int
- oFFSET_StgEntCounter_registeredp :: DynFlags -> Int
- oFFSET_StgEntCounter_link :: DynFlags -> Int
- oFFSET_StgEntCounter_entry_count :: DynFlags -> Int
- sIZEOF_StgUpdateFrame_NoHdr :: DynFlags -> Int
- sIZEOF_StgMutArrPtrs_NoHdr :: DynFlags -> Int
- oFFSET_StgMutArrPtrs_ptrs :: DynFlags -> Int
- oFFSET_StgMutArrPtrs_size :: DynFlags -> Int
- sIZEOF_StgSmallMutArrPtrs_NoHdr :: DynFlags -> Int
- oFFSET_StgSmallMutArrPtrs_ptrs :: DynFlags -> Int
- sIZEOF_StgArrBytes_NoHdr :: DynFlags -> Int
- oFFSET_StgArrBytes_bytes :: DynFlags -> Int
- oFFSET_StgTSO_alloc_limit :: DynFlags -> Int
- oFFSET_StgTSO_cccs :: DynFlags -> Int
- oFFSET_StgTSO_stackobj :: DynFlags -> Int
- oFFSET_StgStack_sp :: DynFlags -> Int
- oFFSET_StgStack_stack :: DynFlags -> Int
- oFFSET_StgUpdateFrame_updatee :: DynFlags -> Int
- oFFSET_StgFunInfoExtraFwd_arity :: DynFlags -> Int
- sIZEOF_StgFunInfoExtraRev :: DynFlags -> Int
- oFFSET_StgFunInfoExtraRev_arity :: DynFlags -> Int
- mAX_SPEC_SELECTEE_SIZE :: DynFlags -> Int
- mAX_SPEC_AP_SIZE :: DynFlags -> Int
- mIN_PAYLOAD_SIZE :: DynFlags -> Int
- mIN_INTLIKE :: DynFlags -> Int
- mAX_INTLIKE :: DynFlags -> Int
- mIN_CHARLIKE :: DynFlags -> Int
- mAX_CHARLIKE :: DynFlags -> Int
- mUT_ARR_PTRS_CARD_BITS :: DynFlags -> Int
- mAX_Vanilla_REG :: DynFlags -> Int
- mAX_Float_REG :: DynFlags -> Int
- mAX_Double_REG :: DynFlags -> Int
- mAX_Long_REG :: DynFlags -> Int
- mAX_XMM_REG :: DynFlags -> Int
- mAX_Real_Vanilla_REG :: DynFlags -> Int
- mAX_Real_Float_REG :: DynFlags -> Int
- mAX_Real_Double_REG :: DynFlags -> Int
- mAX_Real_XMM_REG :: DynFlags -> Int
- mAX_Real_Long_REG :: DynFlags -> Int
- rESERVED_C_STACK_BYTES :: DynFlags -> Int
- rESERVED_STACK_WORDS :: DynFlags -> Int
- aP_STACK_SPLIM :: DynFlags -> Int
- wORD_SIZE :: DynFlags -> Int
- dOUBLE_SIZE :: DynFlags -> Int
- cINT_SIZE :: DynFlags -> Int
- cLONG_SIZE :: DynFlags -> Int
- cLONG_LONG_SIZE :: DynFlags -> Int
- bITMAP_BITS_SHIFT :: DynFlags -> Int
- tAG_BITS :: DynFlags -> Int
- wORDS_BIGENDIAN :: DynFlags -> Bool
- dYNAMIC_BY_DEFAULT :: DynFlags -> Bool
- lDV_SHIFT :: DynFlags -> Int
- iLDV_CREATE_MASK :: DynFlags -> Integer
- iLDV_STATE_CREATE :: DynFlags -> Integer
- iLDV_STATE_USE :: DynFlags -> Integer
- bLOCK_SIZE_W :: DynFlags -> Int
- wORD_SIZE_IN_BITS :: DynFlags -> Int
- wordAlignment :: DynFlags -> Alignment
- tAG_MASK :: DynFlags -> Int
- mAX_PTR_TAG :: DynFlags -> Int
- tARGET_MIN_INT :: DynFlags -> Integer
- tARGET_MAX_INT :: DynFlags -> Integer
- tARGET_MAX_WORD :: DynFlags -> Integer
- unsafeGlobalDynFlags :: DynFlags
- setUnsafeGlobalDynFlags :: DynFlags -> IO ()
- isSseEnabled :: DynFlags -> Bool
- isSse2Enabled :: DynFlags -> Bool
- 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- = GCC
- | Clang
- | AppleClang
- | AppleClang51
- | UnknownCC
 
- data FilesToClean = FilesToClean {- ftcGhcSession :: !(Set FilePath)
- ftcCurrentModule :: !(Set FilePath)
 
- emptyFilesToClean :: FilesToClean
- data IncludeSpecs = IncludeSpecs {- includePathsQuote :: [String]
- includePathsGlobal :: [String]
 
- addGlobalInclude :: IncludeSpecs -> [String] -> IncludeSpecs
- addQuoteInclude :: IncludeSpecs -> [String] -> IncludeSpecs
- flattenIncludes :: IncludeSpecs -> [String]
- data CfgWeights = CFGWeights {}
- backendMaintainsCfg :: DynFlags -> Bool
Dynamic flags and associated configuration types
Constructors
Instances
| Enum DumpFlag Source # | |
| Eq DumpFlag Source # | |
| Show DumpFlag Source # | |
data GeneralFlag Source #
Enumerates the simple on-or-off dynamic flags
Constructors
Instances
| Enum GeneralFlag Source # | |
| Defined in DynFlags Methods succ :: GeneralFlag -> GeneralFlag # pred :: GeneralFlag -> GeneralFlag # toEnum :: Int -> GeneralFlag # fromEnum :: GeneralFlag -> Int # enumFrom :: GeneralFlag -> [GeneralFlag] # enumFromThen :: GeneralFlag -> GeneralFlag -> [GeneralFlag] # enumFromTo :: GeneralFlag -> GeneralFlag -> [GeneralFlag] # enumFromThenTo :: GeneralFlag -> GeneralFlag -> GeneralFlag -> [GeneralFlag] # | |
| Eq GeneralFlag Source # | |
| Defined in DynFlags | |
| Show GeneralFlag Source # | |
| Defined in DynFlags Methods showsPrec :: Int -> GeneralFlag -> ShowS # show :: GeneralFlag -> String # showList :: [GeneralFlag] -> ShowS # | |
data WarningFlag Source #
Constructors
Instances
| Enum WarningFlag Source # | |
| Defined in DynFlags Methods succ :: WarningFlag -> WarningFlag # pred :: WarningFlag -> WarningFlag # toEnum :: Int -> WarningFlag # fromEnum :: WarningFlag -> Int # enumFrom :: WarningFlag -> [WarningFlag] # enumFromThen :: WarningFlag -> WarningFlag -> [WarningFlag] # enumFromTo :: WarningFlag -> WarningFlag -> [WarningFlag] # enumFromThenTo :: WarningFlag -> WarningFlag -> WarningFlag -> [WarningFlag] # | |
| Eq WarningFlag Source # | |
| Defined in DynFlags | |
| Show WarningFlag Source # | |
| Defined in DynFlags Methods showsPrec :: Int -> WarningFlag -> ShowS # show :: WarningFlag -> String # showList :: [WarningFlag] -> ShowS # | |
data WarnReason Source #
Used when outputting warnings: if a reason is given, it is displayed. If a warning isn't controlled by a flag, this is made explicit at the point of use.
Constructors
| NoReason | |
| Reason !WarningFlag | Warning was enabled with the flag | 
| ErrReason !(Maybe WarningFlag) | Warning was made an error because of -Werror or -Werror=WarningFlag | 
Instances
| Show WarnReason Source # | |
| Defined in DynFlags Methods showsPrec :: Int -> WarnReason -> ShowS # show :: WarnReason -> String # showList :: [WarnReason] -> ShowS # | |
| Outputable WarnReason Source # | |
| ToJson WarnReason Source # | |
Constructors
| Haskell98 | |
| Haskell2010 | 
Instances
| Enum Language Source # | |
| Eq Language Source # | |
| Show Language Source # | |
| Outputable Language Source # | |
data PlatformConstants Source #
Constructors
Instances
| Read PlatformConstants Source # | |
| Defined in PlatformConstants Methods readsPrec :: Int -> ReadS PlatformConstants # readList :: ReadS [PlatformConstants] # | |
type FatalMessager = String -> IO () Source #
type LogAction = DynFlags -> WarnReason -> Severity -> SrcSpan -> PprStyle -> MsgDoc -> IO () Source #
Constructors
| NoProfAuto | no SCC annotations added | 
| ProfAutoAll | top-level and nested functions are annotated | 
| ProfAutoTop | top-level functions annotated only | 
| ProfAutoExports | exported functions annotated only | 
| ProfAutoCalls | annotate call-sites | 
Instances
| Enum ProfAuto Source # | |
| Eq ProfAuto Source # | |
glasgowExtsFlags :: [Extension] Source #
warningGroups :: [(String, [WarningFlag])] Source #
Warning groups.
As all warnings are in the Weverything set, it is ignored when displaying to the user which group a warning is in.
warningHierarchies :: [[String]] Source #
Warning group hierarchies, where there is an explicit inclusion relation.
Each inner list is a hierarchy of warning groups, ordered from smallest to largest, where each group is a superset of the one before it.
Separating this from warningGroups allows for multiple
 hierarchies with no inherent relation to be defined.
The special-case Weverything group is not included.
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
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.
useUnicodeSyntax :: DynFlags -> Bool Source #
An internal helper to check whether to use unicode syntax for output.
Note: You should very likely be using unicodeSyntax instead
 of this function.
useStarIsType :: DynFlags -> Bool Source #
whenGeneratingDynamicToo :: MonadIO m => DynFlags -> m () -> m () Source #
ifGeneratingDynamicToo :: MonadIO m => DynFlags -> m a -> m a -> m a Source #
whenCannotGenerateDynamicToo :: MonadIO m => DynFlags -> m () -> m () Source #
dynamicOutputFile :: DynFlags -> FilePath -> FilePath Source #
Compute the path of the dynamic object corresponding to an object file.
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 
 | |
Constructors
| FlagSpec | |
| Fields 
 | |
class HasDynFlags m where Source #
Methods
getDynFlags :: m DynFlags Source #
Instances
| HasDynFlags CoreM Source # | |
| HasDynFlags Hsc Source # | |
| HasDynFlags CompPipeline Source # | |
| Defined in PipelineMonad Methods | |
| HasDynFlags Ghc Source # | |
| (Monad m, HasDynFlags m) => HasDynFlags (MaybeT m) Source # | |
| ContainsDynFlags env => HasDynFlags (IOEnv env) Source # | |
| MonadIO m => HasDynFlags (GhcT m) Source # | |
| (Monoid a, Monad m, HasDynFlags m) => HasDynFlags (WriterT a m) Source # | |
| (Monad m, HasDynFlags m) => HasDynFlags (ExceptT e m) Source # | |
| (Monad m, HasDynFlags m) => HasDynFlags (ReaderT a m) Source # | |
class ContainsDynFlags t where Source #
Methods
extractDynFlags :: t -> DynFlags Source #
Instances
| ContainsDynFlags (Env gbl lcl) Source # | |
data RtsOptsEnabled Source #
Instances
| Show RtsOptsEnabled Source # | |
| Defined in DynFlags Methods showsPrec :: Int -> RtsOptsEnabled -> ShowS # show :: RtsOptsEnabled -> String # showList :: [RtsOptsEnabled] -> ShowS # | |
The target code type of the compilation (if any).
Whenever you change the target, also make sure to set ghcLink to
 something sensible.
HscNothing can be used to avoid generating any output, however, note
 that:
- If a program uses Template Haskell the typechecker may need to run code from an imported module. To facilitate this, code generation is enabled for modules imported by modules that use template haskell. See Note [-fno-code mode].
Constructors
| HscC | Generate C code. | 
| HscAsm | Generate assembly using the native code generator. | 
| HscLlvm | Generate assembly using the llvm code generator. | 
| HscInterpreted | Generate bytecode.  (Requires  | 
| HscNothing | Don't generate any code. See notes above. | 
isObjectTarget :: HscTarget -> Bool Source #
Will this target result in an object file on the disk?
targetRetainsAllBindings :: HscTarget -> Bool Source #
Does this target retain *all* top-level bindings for a module, rather than just the exported bindings, in the TypeEnv and compiled code (if any)? In interpreted mode we do this, so that GHCi can call functions inside a module. In HscNothing mode we also do it, so that Haddock can get access to the GlobalRdrEnv for a module after typechecking it.
The GhcMode tells us whether we're doing multi-module
 compilation (controlled via the GHC API) or one-shot
 (single-module) compilation.  This makes a difference primarily to
 the Finder: in one-shot mode we look for interface files for
 imported modules, but in multi-module mode we look for source files
 in order to check whether they need to be recompiled.
Constructors
| CompManager | 
 | 
| 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 | 
data PackageFlag Source #
Flags for manipulating packages visibility.
Constructors
| ExposePackage String PackageArg ModRenaming | 
 | 
| HidePackage String | -hide-package | 
Instances
| Eq PackageFlag Source # | |
| Defined in DynFlags | |
| Outputable PackageFlag Source # | |
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 UnitId | 
 | 
Instances
| Eq PackageArg Source # | |
| Defined in DynFlags | |
| Show PackageArg Source # | |
| Defined in DynFlags Methods showsPrec :: Int -> PackageArg -> ShowS # show :: PackageArg -> String # showList :: [PackageArg] -> ShowS # | |
| Outputable PackageArg Source # | |
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
| Eq ModRenaming Source # | |
| Defined in DynFlags | |
| Outputable ModRenaming Source # | |
newtype IgnorePackageFlag Source #
Flags for manipulating the set of non-broken packages.
Constructors
| IgnorePackage String | -ignore-package | 
Instances
| Eq IgnorePackageFlag Source # | |
| Defined in DynFlags Methods (==) :: IgnorePackageFlag -> IgnorePackageFlag -> Bool # (/=) :: IgnorePackageFlag -> IgnorePackageFlag -> Bool # | |
Flags for manipulating package trust.
Constructors
| TrustPackage String | -trust | 
| DistrustPackage String | -distrust | 
data PackageDBFlag Source #
Instances
| Eq PackageDBFlag Source # | |
| Defined in DynFlags Methods (==) :: PackageDBFlag -> PackageDBFlag -> Bool # (/=) :: PackageDBFlag -> PackageDBFlag -> Bool # | |
data PkgConfRef Source #
Constructors
| GlobalPkgConf | |
| UserPkgConf | |
| PkgConfFile FilePath | 
Instances
| Eq PkgConfRef Source # | |
| Defined in DynFlags | |
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 DynFlags | |
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>
dynFlagDependencies :: DynFlags -> [ModuleName] Source #
Some modules have dependencies on others through the DynFlags rather than textual imports
shouldUseColor :: DynFlags -> Bool Source #
positionIndependent :: DynFlags -> Bool Source #
Are we building with -fPIE or -fPIC enabled?
setFlagsFromEnvFile :: FilePath -> String -> DynP () Source #
Constructors
| WayCustom String | |
| WayThreaded | |
| WayDebug | |
| WayProf | |
| WayEventLog | |
| WayDyn | 
mkBuildTag :: [Way] -> String Source #
wayRTSOnly :: Way -> Bool Source #
updateWays :: DynFlags -> DynFlags Source #
wayGeneralFlags :: Platform -> Way -> [GeneralFlag] Source #
wayUnsetGeneralFlags :: Platform -> Way -> [GeneralFlag] Source #
thisPackage :: DynFlags -> UnitId Source #
thisUnitIdInsts :: DynFlags -> [(ModuleName, Module)] Source #
Log output
putLogMsg :: DynFlags -> WarnReason -> Severity -> SrcSpan -> PprStyle -> MsgDoc -> IO () Source #
Write an error or warning to the LogOutput.
Safe Haskell
data SafeHaskellMode Source #
The various Safe Haskell modes
Constructors
| Sf_None | inferred unsafe | 
| Sf_Unsafe | declared and checked | 
| Sf_Trustworthy | declared and checked | 
| Sf_Safe | declared and checked | 
| Sf_SafeInferred | inferred as safe | 
| Sf_Ignore | 
 | 
Instances
| Eq SafeHaskellMode Source # | |
| Defined in DynFlags Methods (==) :: SafeHaskellMode -> SafeHaskellMode -> Bool # (/=) :: SafeHaskellMode -> SafeHaskellMode -> Bool # | |
| Show SafeHaskellMode Source # | |
| Defined in DynFlags Methods showsPrec :: Int -> SafeHaskellMode -> ShowS # show :: SafeHaskellMode -> String # showList :: [SafeHaskellMode] -> ShowS # | |
| Outputable SafeHaskellMode Source # | |
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
LLVM Targets
data LlvmTarget Source #
Constructors
| LlvmTarget | |
| Fields 
 | |
type LlvmTargets = [(String, LlvmTarget)] Source #
type LlvmPasses = [(Int, String)] Source #
type LlvmConfig = (LlvmTargets, LlvmPasses) Source #
System tool settings and locations
Constructors
| Settings | |
| Fields | |
sProgramName :: Settings -> String Source #
sProjectVersion :: Settings -> String Source #
sGhcUsagePath :: Settings -> FilePath Source #
sGhciUsagePath :: Settings -> FilePath Source #
sLdSupportsBuildId :: Settings -> Bool Source #
sLdSupportsFilelist :: Settings -> Bool Source #
sLdIsGnuLd :: Settings -> Bool Source #
sGccSupportsNoPie :: Settings -> Bool Source #
sPgm_windres :: Settings -> String Source #
sPgm_libtool :: Settings -> String Source #
sPgm_ranlib :: Settings -> String Source #
sOpt_windres :: Settings -> [String] Source #
sExtraGccViaCFlags :: Settings -> [String] Source #
sIntegerLibrary :: Settings -> String Source #
sGhcWithInterpreter :: Settings -> Bool Source #
sGhcWithNativeCodeGen :: Settings -> Bool Source #
sGhcWithSMP :: Settings -> Bool Source #
sGhcRTSWays :: Settings -> String Source #
sTablesNextToCode :: Settings -> Bool Source #
sLeadingUnderscore :: Settings -> Bool Source #
sGhcThreaded :: Settings -> Bool Source #
sGhcDebugged :: Settings -> Bool Source #
sGhcRtsWithLibdw :: Settings -> Bool Source #
data IntegerLibrary Source #
Constructors
| IntegerGMP | |
| IntegerSimple | 
Instances
| Eq IntegerLibrary Source # | |
| Defined in GHC.Platform Methods (==) :: IntegerLibrary -> IntegerLibrary -> Bool # (/=) :: IntegerLibrary -> IntegerLibrary -> Bool # | |
| Read IntegerLibrary Source # | |
| Defined in GHC.Platform Methods readsPrec :: Int -> ReadS IntegerLibrary # readList :: ReadS [IntegerLibrary] # | |
| Show IntegerLibrary Source # | |
| Defined in GHC.Platform Methods showsPrec :: Int -> IntegerLibrary -> ShowS # show :: IntegerLibrary -> String # showList :: [IntegerLibrary] -> ShowS # | |
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).
Constructors
| PlatformMisc | |
| Fields 
 | |
programName :: DynFlags -> String Source #
projectVersion :: DynFlags -> String Source #
ghcUsagePath :: DynFlags -> FilePath Source #
ghciUsagePath :: DynFlags -> FilePath Source #
versionedAppDir :: DynFlags -> MaybeT IO FilePath Source #
The directory for this version of ghc in the user's app directory
 (typically something like ~.ghcx86_64-linux-7.6.3)
versionedFilePath :: DynFlags -> FilePath Source #
extraGccViaCFlags :: DynFlags -> [String] Source #
pgm_windres :: DynFlags -> String Source #
pgm_libtool :: DynFlags -> String Source #
pgm_ranlib :: DynFlags -> String Source #
opt_P_signature :: DynFlags -> ([String], Fingerprint) Source #
opt_windres :: DynFlags -> [String] Source #
tablesNextToCode :: DynFlags -> Bool Source #
Manipulating DynFlags
defaultDynFlags :: Settings -> LlvmConfig -> DynFlags Source #
defaultWays :: Settings -> [Way] Source #
interpWays :: [Way] Source #
interpreterProfiled :: DynFlags -> Bool Source #
interpreterDynamic :: DynFlags -> Bool Source #
defaultLogActionHPrintDoc :: DynFlags -> Handle -> SDoc -> PprStyle -> IO () Source #
Like defaultLogActionHPutStrDoc but appends an extra newline.
Arguments
| :: 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
canonicalizeHomeModule :: DynFlags -> ModuleName -> Module Source #
Given a ModuleName of a signature in the home library, find
 out how it is instantiated.  E.g., the canonical form of
 A in p[A=q[]:A] is q[]:A.
Parsing DynFlags
parseDynamicFlagsCmdLine Source #
Arguments
| :: MonadIO m | |
| => DynFlags | |
| -> [Located String] | |
| -> m (DynFlags, [Located String], [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 #
Arguments
| :: 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 #
Arguments
| :: MonadIO m | |
| => [Flag (CmdLineP DynFlags)] | valid flags to match against | 
| -> Bool | are the arguments from the command line? | 
| -> DynFlags | current dynamic flags | 
| -> [Located String] | arguments to parse | 
| -> m (DynFlags, [Located String], [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.
DynFlags C compiler options
Compiler configuration suitable for display to the user
rtsIsProfiled :: Bool Source #
Was the runtime system built with profiling enabled?
dynamicGhc :: Bool Source #
sTD_HDR_SIZE :: DynFlags -> Int Source #
pROF_HDR_SIZE :: DynFlags -> Int Source #
bLOCK_SIZE :: DynFlags -> Int Source #
bLOCKS_PER_MBLOCK :: DynFlags -> Int Source #
tICKY_BIN_COUNT :: DynFlags -> Int Source #
oFFSET_StgRegTable_rR1 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rR2 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rR3 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rR4 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rR5 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rR6 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rR7 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rR8 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rR9 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rF1 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rF2 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rF3 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rF4 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rF5 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rF6 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rD1 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rD2 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rD3 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rD4 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rD5 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rD6 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rL1 :: DynFlags -> Int Source #
oFFSET_StgRegTable_rSp :: DynFlags -> Int Source #
oFFSET_StgRegTable_rHp :: DynFlags -> Int Source #
oFFSET_stgGCEnter1 :: DynFlags -> Int Source #
oFFSET_stgGCFun :: DynFlags -> Int Source #
oFFSET_Capability_r :: DynFlags -> Int Source #
oFFSET_bdescr_start :: DynFlags -> Int Source #
oFFSET_bdescr_free :: DynFlags -> Int Source #
oFFSET_bdescr_blocks :: DynFlags -> Int Source #
oFFSET_bdescr_flags :: DynFlags -> Int Source #
sIZEOF_CostCentreStack :: DynFlags -> Int Source #
oFFSET_StgHeader_ccs :: DynFlags -> Int Source #
oFFSET_StgHeader_ldvw :: DynFlags -> Int Source #
oFFSET_StgTSO_cccs :: DynFlags -> Int Source #
oFFSET_StgTSO_stackobj :: DynFlags -> Int Source #
oFFSET_StgStack_sp :: DynFlags -> Int Source #
oFFSET_StgStack_stack :: DynFlags -> Int Source #
mAX_SPEC_SELECTEE_SIZE :: DynFlags -> Int Source #
mAX_SPEC_AP_SIZE :: DynFlags -> Int Source #
mIN_PAYLOAD_SIZE :: DynFlags -> Int Source #
mIN_INTLIKE :: DynFlags -> Int Source #
mAX_INTLIKE :: DynFlags -> Int Source #
mIN_CHARLIKE :: DynFlags -> Int Source #
mAX_CHARLIKE :: DynFlags -> Int Source #
mUT_ARR_PTRS_CARD_BITS :: DynFlags -> Int Source #
mAX_Vanilla_REG :: DynFlags -> Int Source #
mAX_Float_REG :: DynFlags -> Int Source #
mAX_Double_REG :: DynFlags -> Int Source #
mAX_Long_REG :: DynFlags -> Int Source #
mAX_XMM_REG :: DynFlags -> Int Source #
mAX_Real_Vanilla_REG :: DynFlags -> Int Source #
mAX_Real_Float_REG :: DynFlags -> Int Source #
mAX_Real_Double_REG :: DynFlags -> Int Source #
mAX_Real_XMM_REG :: DynFlags -> Int Source #
mAX_Real_Long_REG :: DynFlags -> Int Source #
rESERVED_C_STACK_BYTES :: DynFlags -> Int Source #
rESERVED_STACK_WORDS :: DynFlags -> Int Source #
aP_STACK_SPLIM :: DynFlags -> Int Source #
dOUBLE_SIZE :: DynFlags -> Int Source #
cLONG_SIZE :: DynFlags -> Int Source #
cLONG_LONG_SIZE :: DynFlags -> Int Source #
bITMAP_BITS_SHIFT :: DynFlags -> Int Source #
wORDS_BIGENDIAN :: DynFlags -> Bool Source #
dYNAMIC_BY_DEFAULT :: DynFlags -> Bool Source #
iLDV_CREATE_MASK :: DynFlags -> Integer Source #
iLDV_STATE_CREATE :: DynFlags -> Integer Source #
iLDV_STATE_USE :: DynFlags -> Integer Source #
bLOCK_SIZE_W :: DynFlags -> Int Source #
wORD_SIZE_IN_BITS :: DynFlags -> Int Source #
wordAlignment :: DynFlags -> Alignment Source #
mAX_PTR_TAG :: DynFlags -> Int Source #
tARGET_MIN_INT :: DynFlags -> Integer Source #
tARGET_MAX_INT :: DynFlags -> Integer Source #
tARGET_MAX_WORD :: DynFlags -> Integer Source #
setUnsafeGlobalDynFlags :: DynFlags -> IO () Source #
SSE and AVX
isSseEnabled :: DynFlags -> Bool Source #
isSse2Enabled :: DynFlags -> Bool Source #
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 #
Constructors
| GnuLD [Option] | |
| GnuGold [Option] | |
| LlvmLLD [Option] | |
| DarwinLD [Option] | |
| SolarisLD [Option] | |
| AixLD [Option] | |
| UnknownLD | 
Instances
| Eq LinkerInfo Source # | |
| Defined in DynFlags | |
data CompilerInfo Source #
Constructors
| GCC | |
| Clang | |
| AppleClang | |
| AppleClang51 | |
| UnknownCC | 
Instances
| Eq CompilerInfo Source # | |
| Defined in DynFlags | |
File cleanup
data FilesToClean Source #
A collection of files that must be deleted before ghc exits.
 The current collection
 is stored in an IORef in DynFlags, filesToClean.
Constructors
| FilesToClean | |
| Fields 
 | |
emptyFilesToClean :: FilesToClean Source #
An empty FilesToClean
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 DynFlags Methods showsPrec :: Int -> IncludeSpecs -> ShowS # show :: IncludeSpecs -> String # showList :: [IncludeSpecs] -> ShowS # | |
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.
Make use of the Cmm CFG
data CfgWeights Source #
Edge weights to use when generating a CFG from CMM
Constructors
| CFGWeights | |
| Fields 
 | |
backendMaintainsCfg :: DynFlags -> Bool Source #