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
- data DumpFlag
- = Opt_D_dump_cmm
- | Opt_D_dump_cmm_raw
- | Opt_D_dump_cmm_cfg
- | Opt_D_dump_cmm_cbe
- | Opt_D_dump_cmm_proc
- | Opt_D_dump_cmm_sink
- | Opt_D_dump_cmm_sp
- | Opt_D_dump_cmm_procmap
- | Opt_D_dump_cmm_split
- | Opt_D_dump_cmm_info
- | Opt_D_dump_cmm_cps
- | Opt_D_dump_asm
- | Opt_D_dump_asm_native
- | Opt_D_dump_asm_liveness
- | Opt_D_dump_asm_regalloc
- | Opt_D_dump_asm_regalloc_stages
- | Opt_D_dump_asm_conflicts
- | Opt_D_dump_asm_stats
- | Opt_D_dump_asm_expanded
- | Opt_D_dump_llvm
- | Opt_D_dump_core_stats
- | Opt_D_dump_deriv
- | Opt_D_dump_ds
- | Opt_D_dump_foreign
- | Opt_D_dump_inlinings
- | Opt_D_dump_rule_firings
- | Opt_D_dump_rule_rewrites
- | Opt_D_dump_simpl_trace
- | Opt_D_dump_occur_anal
- | Opt_D_dump_parsed
- | Opt_D_dump_rn
- | Opt_D_dump_simpl
- | Opt_D_dump_simpl_iterations
- | Opt_D_dump_spec
- | Opt_D_dump_prep
- | Opt_D_dump_stg
- | Opt_D_dump_call_arity
- | Opt_D_dump_stranal
- | Opt_D_dump_strsigs
- | Opt_D_dump_tc
- | 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_if_trace
- | Opt_D_dump_vt_trace
- | Opt_D_dump_splices
- | Opt_D_th_dec_file
- | Opt_D_dump_BCOs
- | Opt_D_dump_vect
- | Opt_D_dump_ticked
- | Opt_D_dump_rtti
- | Opt_D_source_stats
- | Opt_D_verbose_stg2stg
- | Opt_D_dump_hi
- | Opt_D_dump_hi_diffs
- | Opt_D_dump_mod_cycles
- | Opt_D_dump_mod_map
- | Opt_D_dump_view_pattern_commoning
- | Opt_D_verbose_core2core
- | Opt_D_dump_debug
- 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_WarnIsError
- | Opt_PrintExplicitForalls
- | Opt_PrintExplicitKinds
- | Opt_CallArity
- | Opt_Strictness
- | Opt_LateDmdAnal
- | Opt_KillAbsence
- | Opt_KillOneShot
- | Opt_FullLaziness
- | Opt_FloatIn
- | Opt_Specialise
- | Opt_SpecialiseAggressively
- | Opt_StaticArgumentTransformation
- | Opt_CSE
- | Opt_LiberateCase
- | Opt_SpecConstr
- | Opt_DoLambdaEtaExpansion
- | Opt_IgnoreAsserts
- | Opt_DoEtaReduction
- | Opt_CaseMerge
- | Opt_UnboxStrictFields
- | Opt_UnboxSmallStrictFields
- | Opt_DictsCheap
- | Opt_EnableRewriteRules
- | Opt_Vectorise
- | Opt_VectorisationAvoidance
- | Opt_RegsGraph
- | Opt_RegsIterative
- | Opt_PedanticBottoms
- | Opt_LlvmTBAA
- | Opt_LlvmPassVectorsInRegisters
- | Opt_IrrefutableTuples
- | Opt_CmmSink
- | Opt_CmmElimCommonBlocks
- | Opt_OmitYields
- | Opt_SimpleListLiterals
- | Opt_FunToThunk
- | Opt_DictsStrict
- | Opt_DmdTxDictSel
- | Opt_Loopification
- | Opt_IgnoreInterfacePragmas
- | Opt_OmitInterfacePragmas
- | Opt_ExposeAllUnfoldings
- | Opt_WriteInterface
- | Opt_AutoSccsOnIndividualCafs
- | Opt_ProfCountEntries
- | Opt_Pp
- | Opt_ForceRecomp
- | Opt_ExcessPrecision
- | Opt_EagerBlackHoling
- | Opt_NoHsMain
- | Opt_SplitObjs
- | Opt_StgStats
- | Opt_HideAllPackages
- | Opt_PrintBindResult
- | Opt_Haddock
- | Opt_HaddockOptions
- | Opt_Hpc_No_Auto
- | Opt_BreakOnException
- | Opt_BreakOnError
- | Opt_PrintEvldWithShow
- | Opt_PrintBindContents
- | Opt_GenManifest
- | Opt_EmbedManifest
- | Opt_EmitExternalCore
- | Opt_SharedImplib
- | Opt_BuildingCabalPackage
- | Opt_IgnoreDotGhci
- | Opt_GhciSandbox
- | Opt_GhciHistory
- | Opt_HelpfulErrors
- | Opt_DeferTypeErrors
- | Opt_DeferTypedHoles
- | Opt_Parallel
- | Opt_GranMacros
- | Opt_PIC
- | Opt_SccProfilingOn
- | Opt_Ticky
- | Opt_Ticky_Allocd
- | Opt_Ticky_LNE
- | Opt_Ticky_Dyn_Thunk
- | Opt_Static
- | Opt_RPath
- | Opt_RelativeDynlibPaths
- | Opt_Hpc
- | Opt_FlatCache
- | Opt_SimplPreInlining
- | Opt_ErrorSpans
- | Opt_PprCaseAsLet
- | Opt_PprShowTicks
- | Opt_SuppressCoercions
- | Opt_SuppressVarKinds
- | Opt_SuppressModulePrefixes
- | Opt_SuppressTypeApplications
- | Opt_SuppressIdInfo
- | Opt_SuppressTypeSignatures
- | Opt_SuppressUniques
- | Opt_AutoLinkPackages
- | Opt_ImplicitImportQualified
- | Opt_KeepHiDiffs
- | Opt_KeepHcFiles
- | Opt_KeepSFiles
- | Opt_KeepTmpFiles
- | Opt_KeepRawTokenStream
- | Opt_KeepLlvmFiles
- | Opt_BuildDynamicToo
- | Opt_DistrustAllPackages
- | Opt_PackageTrust
- | Opt_Debug
- data WarningFlag
- = Opt_WarnDuplicateExports
- | Opt_WarnDuplicateConstraints
- | Opt_WarnHiShadows
- | Opt_WarnImplicitPrelude
- | Opt_WarnIncompletePatterns
- | Opt_WarnIncompleteUniPatterns
- | Opt_WarnIncompletePatternsRecUpd
- | Opt_WarnOverflowedLiterals
- | Opt_WarnEmptyEnumerations
- | Opt_WarnMissingFields
- | Opt_WarnMissingImportList
- | Opt_WarnMissingMethods
- | Opt_WarnMissingSigs
- | Opt_WarnMissingLocalSigs
- | Opt_WarnNameShadowing
- | Opt_WarnOverlappingPatterns
- | Opt_WarnTypeDefaults
- | Opt_WarnMonomorphism
- | Opt_WarnUnusedBinds
- | Opt_WarnUnusedImports
- | Opt_WarnUnusedMatches
- | Opt_WarnContextQuantification
- | Opt_WarnWarningsDeprecations
- | Opt_WarnDeprecatedFlags
- | Opt_WarnAMP
- | 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_WarnPointlessPragmas
- | Opt_WarnUnsupportedCallingConventions
- | Opt_WarnUnsupportedLlvmVersion
- | Opt_WarnInlineRuleShadowing
- | Opt_WarnTypedHoles
- | Opt_WarnPartialTypeSignatures
- | Opt_WarnMissingExportedSigs
- | Opt_WarnUntickedPromotedConstructors
- | Opt_WarnDerivingTypeable
- data ExtensionFlag
- = Opt_Cpp
- | Opt_OverlappingInstances
- | Opt_UndecidableInstances
- | Opt_IncoherentInstances
- | Opt_MonomorphismRestriction
- | Opt_MonoPatBinds
- | Opt_MonoLocalBinds
- | Opt_RelaxedPolyRec
- | Opt_ExtendedDefaultRules
- | Opt_ForeignFunctionInterface
- | Opt_UnliftedFFITypes
- | Opt_InterruptibleFFI
- | Opt_CApiFFI
- | Opt_GHCForeignImportPrim
- | Opt_JavaScriptFFI
- | Opt_ParallelArrays
- | Opt_Arrows
- | Opt_TemplateHaskell
- | Opt_QuasiQuotes
- | Opt_ImplicitParams
- | Opt_ImplicitPrelude
- | Opt_ScopedTypeVariables
- | Opt_AllowAmbiguousTypes
- | Opt_UnboxedTuples
- | Opt_BangPatterns
- | Opt_TypeFamilies
- | Opt_OverloadedStrings
- | Opt_OverloadedLists
- | Opt_NumDecimals
- | Opt_DisambiguateRecordFields
- | Opt_RecordWildCards
- | Opt_RecordPuns
- | Opt_ViewPatterns
- | Opt_GADTs
- | Opt_GADTSyntax
- | Opt_NPlusKPatterns
- | Opt_DoAndIfThenElse
- | Opt_RebindableSyntax
- | Opt_ConstraintKinds
- | Opt_PolyKinds
- | Opt_DataKinds
- | Opt_InstanceSigs
- | Opt_StandaloneDeriving
- | Opt_DeriveDataTypeable
- | Opt_AutoDeriveTypeable
- | Opt_DeriveFunctor
- | Opt_DeriveTraversable
- | Opt_DeriveFoldable
- | Opt_DeriveGeneric
- | Opt_DefaultSignatures
- | Opt_DeriveAnyClass
- | Opt_TypeSynonymInstances
- | Opt_FlexibleContexts
- | Opt_FlexibleInstances
- | Opt_ConstrainedClassMethods
- | Opt_MultiParamTypeClasses
- | Opt_NullaryTypeClasses
- | Opt_FunctionalDependencies
- | Opt_UnicodeSyntax
- | Opt_ExistentialQuantification
- | Opt_MagicHash
- | Opt_EmptyDataDecls
- | Opt_KindSignatures
- | Opt_RoleAnnotations
- | Opt_ParallelListComp
- | Opt_TransformListComp
- | Opt_MonadComprehensions
- | Opt_GeneralizedNewtypeDeriving
- | Opt_RecursiveDo
- | Opt_PostfixOperators
- | Opt_TupleSections
- | Opt_PatternGuards
- | Opt_LiberalTypeSynonyms
- | Opt_RankNTypes
- | Opt_ImpredicativeTypes
- | Opt_TypeOperators
- | Opt_ExplicitNamespaces
- | Opt_PackageImports
- | Opt_ExplicitForAll
- | Opt_AlternativeLayoutRule
- | Opt_AlternativeLayoutRuleTransitional
- | Opt_DatatypeContexts
- | Opt_NondecreasingIndentation
- | Opt_RelaxedLayout
- | Opt_TraditionalRecordSyntax
- | Opt_LambdaCase
- | Opt_MultiWayIf
- | Opt_BinaryLiterals
- | Opt_NegativeLiterals
- | Opt_EmptyCase
- | Opt_PatternSynonyms
- | Opt_PartialTypeSignatures
- | Opt_NamedWildCards
- | Opt_StaticPointers
- data Language
- data PlatformConstants = PlatformConstants {
- pc_platformConstants :: ()
- pc_STD_HDR_SIZE :: Int
- pc_PROF_HDR_SIZE :: Int
- pc_BLOCK_SIZE :: Int
- pc_BLOCKS_PER_MBLOCK :: 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_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_StgArrWords_NoHdr :: Int
- pc_OFFSET_StgArrWords_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 -> Severity -> SrcSpan -> PprStyle -> MsgDoc -> IO ()
- newtype FlushOut = FlushOut (IO ())
- newtype FlushErr = FlushErr (IO ())
- data ProfAuto
- glasgowExtsFlags :: [ExtensionFlag]
- dopt :: DumpFlag -> DynFlags -> Bool
- dopt_set :: DynFlags -> DumpFlag -> DynFlags
- dopt_unset :: DynFlags -> DumpFlag -> DynFlags
- gopt :: GeneralFlag -> DynFlags -> Bool
- gopt_set :: DynFlags -> GeneralFlag -> DynFlags
- gopt_unset :: DynFlags -> GeneralFlag -> DynFlags
- wopt :: WarningFlag -> DynFlags -> Bool
- wopt_set :: DynFlags -> WarningFlag -> DynFlags
- wopt_unset :: DynFlags -> WarningFlag -> DynFlags
- xopt :: ExtensionFlag -> DynFlags -> Bool
- xopt_set :: DynFlags -> ExtensionFlag -> DynFlags
- xopt_unset :: DynFlags -> ExtensionFlag -> DynFlags
- lang_set :: DynFlags -> Maybe Language -> DynFlags
- useUnicodeSyntax :: 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
- data DynFlags = DynFlags {
- ghcMode :: GhcMode
- ghcLink :: GhcLink
- hscTarget :: HscTarget
- settings :: Settings
- sigOf :: SigOf
- verbosity :: Int
- optLevel :: Int
- simplPhases :: Int
- maxSimplIterations :: Int
- ruleCheck :: Maybe String
- strictnessBefore :: [Int]
- parMakeCount :: Maybe Int
- enableTimeStats :: Bool
- ghcHeapSize :: Maybe Int
- maxRelevantBinds :: Maybe Int
- simplTickFactor :: Int
- specConstrThreshold :: Maybe Int
- specConstrCount :: Maybe Int
- specConstrRecursive :: Int
- liberateCaseThreshold :: Maybe Int
- floatLamArgs :: Maybe Int
- historySize :: Int
- cmdlineHcIncludes :: [String]
- importPaths :: [FilePath]
- mainModIs :: Module
- mainFunIs :: Maybe String
- ctxtStkDepth :: Int
- tyFunStkDepth :: Int
- thisPackage :: PackageKey
- ways :: [Way]
- buildTag :: String
- rtsBuildTag :: String
- splitInfo :: Maybe (String, Int)
- objectDir :: Maybe String
- dylibInstallName :: Maybe String
- hiDir :: Maybe String
- stubDir :: Maybe String
- dumpDir :: Maybe String
- objectSuf :: String
- hcSuf :: String
- hiSuf :: String
- canGenerateDynamicToo :: IORef Bool
- dynObjectSuf :: String
- dynHiSuf :: String
- dllSplitFile :: Maybe FilePath
- dllSplit :: Maybe [Set String]
- outputFile :: Maybe String
- dynOutputFile :: Maybe String
- outputHi :: Maybe String
- dynLibLoader :: DynLibLoader
- dumpPrefix :: Maybe FilePath
- dumpPrefixForce :: Maybe FilePath
- ldInputs :: [Option]
- includePaths :: [String]
- libraryPaths :: [String]
- frameworkPaths :: [String]
- cmdlineFrameworks :: [String]
- rtsOpts :: Maybe String
- rtsOptsEnabled :: RtsOptsEnabled
- hpcDir :: String
- pluginModNames :: [ModuleName]
- pluginModNameOpts :: [(ModuleName, String)]
- hooks :: Hooks
- depMakefile :: FilePath
- depIncludePkgDeps :: Bool
- depExcludeMods :: [ModuleName]
- depSuffixes :: [String]
- extraPkgConfs :: [PkgConfRef] -> [PkgConfRef]
- packageFlags :: [PackageFlag]
- packageEnv :: Maybe FilePath
- pkgDatabase :: Maybe [PackageConfig]
- pkgState :: PackageState
- filesToClean :: IORef [FilePath]
- dirsToClean :: IORef (Map FilePath FilePath)
- filesToNotIntermediateClean :: IORef [FilePath]
- nextTempSuffix :: IORef Int
- generatedDumps :: IORef (Set FilePath)
- dumpFlags :: IntSet
- generalFlags :: IntSet
- warningFlags :: IntSet
- 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 ExtensionFlag]
- extensionFlags :: IntSet
- ufCreationThreshold :: Int
- ufUseThreshold :: Int
- ufFunAppDiscount :: Int
- ufDictDiscount :: Int
- ufKeenessFactor :: Float
- ufDearOp :: Int
- maxWorkerArgs :: Int
- ghciHistSize :: Int
- log_action :: LogAction
- flushOut :: FlushOut
- flushErr :: FlushErr
- haddockOptions :: Maybe String
- ghciScripts :: [String]
- pprUserLength :: Int
- pprCols :: Int
- traceLevel :: Int
- useUnicode :: Bool
- profAuto :: ProfAuto
- interactivePrint :: Maybe String
- llvmVersion :: IORef Int
- nextWrapperNum :: IORef (ModuleEnv Int)
- sseVersion :: Maybe SseVersion
- 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
- 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
- replaceDynFlags :: t -> DynFlags -> t
- data RtsOptsEnabled
- data HscTarget
- isObjectTarget :: HscTarget -> Bool
- defaultObjectTarget :: Platform -> HscTarget
- targetRetainsAllBindings :: HscTarget -> Bool
- data GhcMode
- isOneShot :: GhcMode -> Bool
- data GhcLink
- isNoLink :: GhcLink -> Bool
- data PackageFlag
- data PackageArg
- data ModRenaming = ModRenaming Bool [(String, String)]
- data PkgConfRef
- data Option
- showOpt :: Option -> String
- data DynLibLoader
- fFlags :: [FlagSpec GeneralFlag]
- fWarningFlags :: [FlagSpec WarningFlag]
- fLangFlags :: [FlagSpec ExtensionFlag]
- xFlags :: [FlagSpec ExtensionFlag]
- dynFlagDependencies :: DynFlags -> [ModuleName]
- tablesNextToCode :: DynFlags -> Bool
- mkTablesNextToCode :: Bool -> Bool
- data SigOf
- getSigOf :: DynFlags -> ModuleName -> Maybe Module
- checkOptLevel :: Int -> DynFlags -> Either String DynFlags
- data Way
- mkBuildTag :: [Way] -> String
- wayRTSOnly :: Way -> Bool
- addWay' :: Way -> DynFlags -> DynFlags
- updateWays :: DynFlags -> DynFlags
- wayGeneralFlags :: Platform -> Way -> [GeneralFlag]
- wayUnsetGeneralFlags :: Platform -> Way -> [GeneralFlag]
- data SafeHaskellMode
- safeHaskellOn :: 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 {
- sTargetPlatform :: Platform
- sGhcUsagePath :: FilePath
- sGhciUsagePath :: FilePath
- sTopDir :: FilePath
- sTmpDir :: String
- sProgramName :: String
- sProjectVersion :: String
- sRawSettings :: [(String, String)]
- sExtraGccViaCFlags :: [String]
- sSystemPackageConfig :: FilePath
- sLdSupportsCompactUnwind :: Bool
- sLdSupportsBuildId :: Bool
- sLdSupportsFilelist :: Bool
- sLdIsGnuLd :: Bool
- sPgm_L :: String
- sPgm_P :: (String, [Option])
- sPgm_F :: String
- sPgm_c :: (String, [Option])
- sPgm_s :: (String, [Option])
- sPgm_a :: (String, [Option])
- sPgm_l :: (String, [Option])
- sPgm_dll :: (String, [Option])
- sPgm_T :: String
- sPgm_sysman :: String
- sPgm_windres :: String
- sPgm_libtool :: String
- sPgm_lo :: (String, [Option])
- sPgm_lc :: (String, [Option])
- sOpt_L :: [String]
- sOpt_P :: [String]
- sOpt_F :: [String]
- sOpt_c :: [String]
- sOpt_a :: [String]
- sOpt_l :: [String]
- sOpt_windres :: [String]
- sOpt_lo :: [String]
- sOpt_lc :: [String]
- sPlatformConstants :: PlatformConstants
- targetPlatform :: DynFlags -> Platform
- programName :: DynFlags -> String
- projectVersion :: DynFlags -> String
- ghcUsagePath :: DynFlags -> FilePath
- ghciUsagePath :: DynFlags -> FilePath
- topDir :: DynFlags -> FilePath
- tmpDir :: DynFlags -> String
- rawSettings :: DynFlags -> [(String, String)]
- versionedAppDir :: DynFlags -> IO FilePath
- extraGccViaCFlags :: DynFlags -> [String]
- systemPackageConfig :: DynFlags -> FilePath
- pgm_L :: DynFlags -> String
- pgm_P :: DynFlags -> (String, [Option])
- pgm_F :: DynFlags -> String
- pgm_c :: DynFlags -> (String, [Option])
- pgm_s :: DynFlags -> (String, [Option])
- pgm_a :: DynFlags -> (String, [Option])
- pgm_l :: DynFlags -> (String, [Option])
- pgm_dll :: DynFlags -> (String, [Option])
- pgm_T :: DynFlags -> String
- pgm_sysman :: DynFlags -> String
- pgm_windres :: DynFlags -> String
- pgm_libtool :: DynFlags -> String
- pgm_lo :: DynFlags -> (String, [Option])
- pgm_lc :: DynFlags -> (String, [Option])
- opt_L :: DynFlags -> [String]
- opt_P :: DynFlags -> [String]
- opt_F :: DynFlags -> [String]
- opt_c :: DynFlags -> [String]
- opt_a :: DynFlags -> [String]
- opt_l :: DynFlags -> [String]
- opt_windres :: DynFlags -> [String]
- opt_lo :: DynFlags -> [String]
- opt_lc :: DynFlags -> [String]
- defaultDynFlags :: Settings -> DynFlags
- defaultWays :: Settings -> [Way]
- interpWays :: [Way]
- 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
- setPackageKey :: String -> DynFlags -> DynFlags
- interpretPackageEnv :: DynFlags -> IO DynFlags
- parseDynamicFlagsCmdLine :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Located String])
- parseDynamicFilePragma :: MonadIO m => DynFlags -> [Located String] -> m (DynFlags, [Located String], [Located String])
- parseDynamicFlagsFull :: MonadIO m => [Flag (CmdLineP DynFlags)] -> Bool -> DynFlags -> [Located String] -> m (DynFlags, [Located String], [Located String])
- allFlags :: [String]
- flagsAll :: [Flag (CmdLineP DynFlags)]
- flagsDynamic :: [Flag (CmdLineP DynFlags)]
- flagsPackage :: [Flag (CmdLineP DynFlags)]
- flagsForCompletion :: Bool -> [String]
- supportedLanguagesAndExtensions :: [String]
- languageExtensions :: Maybe Language -> [ExtensionFlag]
- picCCOpts :: DynFlags -> [String]
- picPOpts :: DynFlags -> [String]
- data StgToDo
- getStgToDo :: DynFlags -> [StgToDo]
- compilerInfo :: DynFlags -> [(String, String)]
- rtsIsProfiled :: Bool
- dynamicGhc :: Bool
- sTD_HDR_SIZE :: DynFlags -> Int
- pROF_HDR_SIZE :: DynFlags -> Int
- bLOCK_SIZE :: DynFlags -> Int
- bLOCKS_PER_MBLOCK :: 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
- 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_StgArrWords_NoHdr :: DynFlags -> Int
- oFFSET_StgArrWords_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
- 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
- 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
Dynamic flags and associated configuration types
data DumpFlag
Constructors
data GeneralFlag
Enumerates the simple on-or-off dynamic flags
Constructors
Instances
data WarningFlag
Constructors
Instances
data ExtensionFlag
Constructors
Instances
data PlatformConstants
Constructors
Instances
type FatalMessager = String -> IO ()
data ProfAuto
Constructors
NoProfAuto | no SCC annotations added |
ProfAutoAll | top-level and nested functions are annotated |
ProfAutoTop | top-level functions annotated only |
ProfAutoExports | exported functions annotated only |
ProfAutoCalls | annotate call-sites |
dopt_unset :: DynFlags -> DumpFlag -> DynFlags
Unset a DumpFlag
gopt :: GeneralFlag -> DynFlags -> Bool
Test whether a GeneralFlag
is set
gopt_set :: DynFlags -> GeneralFlag -> DynFlags
Set a GeneralFlag
gopt_unset :: DynFlags -> GeneralFlag -> DynFlags
Unset a GeneralFlag
wopt :: WarningFlag -> DynFlags -> Bool
Test whether a WarningFlag
is set
wopt_set :: DynFlags -> WarningFlag -> DynFlags
Set a WarningFlag
wopt_unset :: DynFlags -> WarningFlag -> DynFlags
Unset a WarningFlag
xopt :: ExtensionFlag -> DynFlags -> Bool
Test whether a ExtensionFlag
is set
xopt_set :: DynFlags -> ExtensionFlag -> DynFlags
Set a ExtensionFlag
xopt_unset :: DynFlags -> ExtensionFlag -> DynFlags
Unset a ExtensionFlag
useUnicodeSyntax :: DynFlags -> Bool
whenGeneratingDynamicToo :: MonadIO m => DynFlags -> m () -> m ()
ifGeneratingDynamicToo :: MonadIO m => DynFlags -> m a -> m a -> m a
whenCannotGenerateDynamicToo :: MonadIO m => DynFlags -> m () -> m ()
data DynFlags
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
Constructors
data FlagSpec flag
Constructors
FlagSpec | |
Fields
|
class HasDynFlags m where
Methods
getDynFlags :: m DynFlags
Instances
class ContainsDynFlags t where
Instances
ContainsDynFlags HscEnv | |
ContainsDynFlags (Env gbl lcl) |
data HscTarget
The target code type of the compilation (if any).
Whenever you change the target, also make sure to set ghcLink
to
something sensible.
HscNothing
can be used to avoid generating any output, however, note
that:
- If a program uses Template Haskell the typechecker may try to run code
from an imported module. This will fail if no code has been generated
for this module. You can use
needsTemplateHaskell
to detect whether this might be the case and choose to either switch to a different target or avoid typechecking such modules. (The latter may be preferable for security reasons.)
Constructors
HscC | Generate C code. |
HscAsm | Generate assembly using the native code generator. |
HscLlvm | Generate assembly using the llvm code generator. |
HscInterpreted | Generate bytecode. (Requires |
HscNothing | Don't generate any code. See notes above. |
isObjectTarget :: HscTarget -> Bool
Will this target result in an object file on the disk?
defaultObjectTarget :: Platform -> HscTarget
The HscTarget
value corresponding to the default way to create
object files on the current platform.
targetRetainsAllBindings :: HscTarget -> Bool
Does this target retain *all* top-level bindings for a module, rather than just the exported bindings, in the TypeEnv and compiled code (if any)? In interpreted mode we do this, so that GHCi can call functions inside a module. In HscNothing mode we also do it, so that Haddock can get access to the GlobalRdrEnv for a module after typechecking it.
data GhcMode
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 |
|
Instances
data GhcLink
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
Constructors
ExposePackage PackageArg ModRenaming | |
HidePackage String | |
IgnorePackage String | |
TrustPackage String | |
DistrustPackage String |
Instances
data PkgConfRef
Constructors
GlobalPkgConf | |
UserPkgConf | |
PkgConfFile FilePath |
data Option
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 |
fFlags :: [FlagSpec GeneralFlag]
These -f<blah>
flags can all be reversed with -fno-<blah>
fWarningFlags :: [FlagSpec WarningFlag]
These -f<blah>
flags can all be reversed with -fno-<blah>
fLangFlags :: [FlagSpec ExtensionFlag]
These -f<blah>
flags can all be reversed with -fno-<blah>
xFlags :: [FlagSpec ExtensionFlag]
dynFlagDependencies :: DynFlags -> [ModuleName]
Some modules have dependencies on others through the DynFlags rather than textual imports
tablesNextToCode :: DynFlags -> Bool
mkTablesNextToCode :: Bool -> Bool
getSigOf :: DynFlags -> ModuleName -> Maybe Module
data Way
Constructors
WayCustom String | |
WayThreaded | |
WayDebug | |
WayProf | |
WayEventLog | |
WayPar | |
WayGran | |
WayNDP | |
WayDyn |
mkBuildTag :: [Way] -> String
wayRTSOnly :: Way -> Bool
updateWays :: DynFlags -> DynFlags
wayGeneralFlags :: Platform -> Way -> [GeneralFlag]
wayUnsetGeneralFlags :: Platform -> Way -> [GeneralFlag]
Safe Haskell
data SafeHaskellMode
The various Safe Haskell modes
Constructors
Sf_None | |
Sf_Unsafe | |
Sf_Trustworthy | |
Sf_Safe |
safeHaskellOn :: DynFlags -> Bool
Is Safe Haskell on in some way (including inference mode)
safeImportsOn :: DynFlags -> Bool
Test if Safe Imports are on in some form
safeLanguageOn :: DynFlags -> Bool
Is the Safe Haskell safe language in use
safeInferOn :: DynFlags -> Bool
Is the Safe Haskell safe inference mode active
packageTrustOn :: DynFlags -> Bool
Is the -fpackage-trust mode on
safeDirectImpsReq :: DynFlags -> Bool
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
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)]
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)]
A list of unsafe flags under Safe Haskell. Tuple elements are: * name of the flag * function to get srcspan that enabled the flag * function to test if the flag is on * function to turn the flag off
System tool settings and locations
data Settings
Constructors
Settings | |
Fields
|
targetPlatform :: DynFlags -> Platform
programName :: DynFlags -> String
projectVersion :: DynFlags -> String
ghcUsagePath :: DynFlags -> FilePath
ghciUsagePath :: DynFlags -> FilePath
rawSettings :: DynFlags -> [(String, String)]
versionedAppDir :: DynFlags -> IO FilePath
The directory for this version of ghc in the user's app directory
(typically something like ~.ghcx86_64-linux-7.6.3
)
extraGccViaCFlags :: DynFlags -> [String]
pgm_sysman :: DynFlags -> String
pgm_windres :: DynFlags -> String
pgm_libtool :: DynFlags -> String
opt_windres :: DynFlags -> [String]
Manipulating DynFlags
defaultDynFlags :: Settings -> DynFlags
defaultWays :: Settings -> [Way]
interpWays :: [Way]
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]
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
Sets the DynFlags
to be appropriate to the optimisation level
setPackageKey :: String -> DynFlags -> DynFlags
interpretPackageEnv :: DynFlags -> IO DynFlags
Find the package environment (if one exists)
We interpret the package environment as a set of package flags; to be specific, if we find a package environment
id1 id2 .. idn
we interpret this as
[ -hide-all-packages , -package-id id1 , -package-id id2 , .. , -package-id idn ]
Parsing DynFlags
Arguments
:: MonadIO m | |
=> DynFlags | |
-> [Located String] | |
-> m (DynFlags, [Located String], [Located String]) | Updated |
Parse dynamic flags from a list of command line arguments. Returns the
the parsed DynFlags
, the left-over arguments, and a list of warnings.
Throws a UsageError
if errors occurred during parsing (such as unknown
flags or missing arguments).
Arguments
:: MonadIO m | |
=> DynFlags | |
-> [Located String] | |
-> m (DynFlags, [Located String], [Located String]) | 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.
Arguments
:: MonadIO m | |
=> [Flag (CmdLineP DynFlags)] | valid flags to match against |
-> Bool | are the arguments from the command line? |
-> DynFlags | current dynamic flags |
-> [Located String] | arguments to parse |
-> m (DynFlags, [Located String], [Located String]) |
Parses the dynamically set flags for GHC. This is the most general form of the dynamic flag parser that the other methods simply wrap. It allows saying which flags are valid flags and indicating if we are parsing arguments from the command line or from a file pragma.
Available DynFlags
All dynamic flags option strings. These are the user facing strings for enabling and disabling options.
flagsDynamic :: [Flag (CmdLineP DynFlags)]
flagsPackage :: [Flag (CmdLineP DynFlags)]
flagsForCompletion :: Bool -> [String]
Make a list of flags for shell completion. Filter all available flags into two groups, for interactive GHC vs all other.
languageExtensions :: Maybe Language -> [ExtensionFlag]
DynFlags C compiler options
Configuration of the stg-to-stg passes
data StgToDo
Constructors
StgDoMassageForProfiling | |
D_stg_stats |
getStgToDo :: DynFlags -> [StgToDo]
Compiler configuration suitable for display to the user
compilerInfo :: DynFlags -> [(String, String)]
dynamicGhc :: Bool
sTD_HDR_SIZE :: DynFlags -> Int
pROF_HDR_SIZE :: DynFlags -> Int
bLOCK_SIZE :: DynFlags -> Int
bLOCKS_PER_MBLOCK :: 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_StgHeader_ccs :: DynFlags -> Int
oFFSET_StgHeader_ldvw :: DynFlags -> Int
oFFSET_StgTSO_cccs :: DynFlags -> Int
oFFSET_StgStack_sp :: DynFlags -> Int
oFFSET_StgStack_stack :: 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
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_STACK_WORDS :: DynFlags -> Int
aP_STACK_SPLIM :: DynFlags -> Int
dOUBLE_SIZE :: DynFlags -> Int
cLONG_SIZE :: DynFlags -> Int
cLONG_LONG_SIZE :: DynFlags -> Int
bITMAP_BITS_SHIFT :: DynFlags -> Int
wORDS_BIGENDIAN :: DynFlags -> Bool
dYNAMIC_BY_DEFAULT :: DynFlags -> Bool
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
mAX_PTR_TAG :: DynFlags -> Int
tARGET_MIN_INT :: DynFlags -> Integer
tARGET_MAX_INT :: DynFlags -> Integer
tARGET_MAX_WORD :: DynFlags -> Integer
setUnsafeGlobalDynFlags :: DynFlags -> IO ()
SSE and AVX
isSseEnabled :: DynFlags -> Bool
isSse2Enabled :: DynFlags -> Bool
isSse4_2Enabled :: DynFlags -> Bool
isAvxEnabled :: DynFlags -> Bool
isAvx2Enabled :: DynFlags -> Bool
isAvx512cdEnabled :: DynFlags -> Bool
isAvx512erEnabled :: DynFlags -> Bool
isAvx512fEnabled :: DynFlags -> Bool
isAvx512pfEnabled :: DynFlags -> Bool
Linker/compiler information
data LinkerInfo
Instances