Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data DumpFlag
- = Opt_D_dump_cmm
- | Opt_D_dump_cmm_from_stg
- | Opt_D_dump_cmm_raw
- | Opt_D_dump_cmm_verbose_by_proc
- | Opt_D_dump_cmm_verbose
- | Opt_D_dump_cmm_cfg
- | Opt_D_dump_cmm_cbe
- | Opt_D_dump_cmm_switch
- | Opt_D_dump_cmm_proc
- | Opt_D_dump_cmm_sp
- | Opt_D_dump_cmm_sink
- | Opt_D_dump_cmm_caf
- | Opt_D_dump_cmm_procmap
- | Opt_D_dump_cmm_split
- | Opt_D_dump_cmm_info
- | Opt_D_dump_cmm_cps
- | Opt_D_dump_cmm_thread_sanitizer
- | Opt_D_dump_cfg_weights
- | Opt_D_dump_asm
- | Opt_D_dump_asm_native
- | Opt_D_dump_asm_liveness
- | Opt_D_dump_asm_regalloc
- | Opt_D_dump_asm_regalloc_stages
- | Opt_D_dump_asm_conflicts
- | Opt_D_dump_asm_stats
- | Opt_D_dump_c_backend
- | Opt_D_dump_llvm
- | Opt_D_dump_js
- | Opt_D_dump_core_stats
- | Opt_D_dump_deriv
- | Opt_D_dump_ds
- | Opt_D_dump_ds_preopt
- | Opt_D_dump_foreign
- | Opt_D_dump_inlinings
- | Opt_D_dump_verbose_inlinings
- | Opt_D_dump_rule_firings
- | Opt_D_dump_rule_rewrites
- | Opt_D_dump_simpl_trace
- | Opt_D_dump_occur_anal
- | Opt_D_dump_parsed
- | Opt_D_dump_parsed_ast
- | Opt_D_dump_rn
- | Opt_D_dump_rn_ast
- | Opt_D_dump_simpl
- | Opt_D_dump_simpl_iterations
- | Opt_D_dump_spec
- | Opt_D_dump_prep
- | Opt_D_dump_late_cc
- | Opt_D_dump_stg_from_core
- | Opt_D_dump_stg_unarised
- | Opt_D_dump_stg_cg
- | Opt_D_dump_stg_tags
- | Opt_D_dump_stg_final
- | Opt_D_dump_call_arity
- | Opt_D_dump_exitify
- | Opt_D_dump_stranal
- | Opt_D_dump_str_signatures
- | Opt_D_dump_cpranal
- | Opt_D_dump_cpr_signatures
- | Opt_D_dump_tc
- | Opt_D_dump_tc_ast
- | Opt_D_dump_hie
- | Opt_D_dump_types
- | Opt_D_dump_rules
- | Opt_D_dump_cse
- | Opt_D_dump_worker_wrapper
- | Opt_D_dump_rn_trace
- | Opt_D_dump_rn_stats
- | Opt_D_dump_opt_cmm
- | Opt_D_dump_simpl_stats
- | Opt_D_dump_cs_trace
- | Opt_D_dump_tc_trace
- | Opt_D_dump_ec_trace
- | Opt_D_dump_if_trace
- | Opt_D_dump_splices
- | Opt_D_th_dec_file
- | Opt_D_dump_BCOs
- | Opt_D_dump_ticked
- | Opt_D_dump_rtti
- | Opt_D_source_stats
- | Opt_D_verbose_stg2stg
- | Opt_D_dump_hi
- | Opt_D_dump_hi_diffs
- | Opt_D_dump_mod_cycles
- | Opt_D_dump_mod_map
- | Opt_D_dump_timings
- | Opt_D_dump_view_pattern_commoning
- | Opt_D_verbose_core2core
- | Opt_D_dump_debug
- | Opt_D_dump_json
- | Opt_D_ppr_debug
- | Opt_D_no_debug_output
- | Opt_D_dump_faststrings
- | Opt_D_faststring_stats
- | Opt_D_ipe_stats
- getDumpFlagFrom :: (a -> Int) -> (a -> EnumSet DumpFlag) -> DumpFlag -> a -> Bool
- enabledIfVerbose :: DumpFlag -> Bool
- data GeneralFlag
- = Opt_DumpToFile
- | Opt_DumpWithWays
- | Opt_D_dump_minimal_imports
- | Opt_DoCoreLinting
- | Opt_DoLinearCoreLinting
- | Opt_DoStgLinting
- | Opt_DoCmmLinting
- | Opt_DoAsmLinting
- | Opt_DoAnnotationLinting
- | Opt_DoBoundsChecking
- | Opt_NoLlvmMangler
- | Opt_FastLlvm
- | Opt_NoTypeableBinds
- | Opt_DistinctConstructorTables
- | Opt_InfoTableMap
- | Opt_InfoTableMapWithFallback
- | Opt_InfoTableMapWithStack
- | Opt_WarnIsError
- | Opt_ShowWarnGroups
- | Opt_HideSourcePaths
- | Opt_PrintExplicitForalls
- | Opt_PrintExplicitKinds
- | Opt_PrintExplicitCoercions
- | Opt_PrintExplicitRuntimeReps
- | Opt_PrintEqualityRelations
- | Opt_PrintAxiomIncomps
- | Opt_PrintUnicodeSyntax
- | Opt_PrintExpandedSynonyms
- | Opt_PrintPotentialInstances
- | Opt_PrintRedundantPromotionTicks
- | Opt_PrintTypecheckerElaboration
- | Opt_CallArity
- | Opt_Exitification
- | Opt_Strictness
- | Opt_LateDmdAnal
- | Opt_KillAbsence
- | Opt_KillOneShot
- | Opt_FullLaziness
- | Opt_FloatIn
- | Opt_LocalFloatOut
- | Opt_LocalFloatOutTopLevel
- | Opt_LateSpecialise
- | Opt_Specialise
- | Opt_SpecialiseAggressively
- | Opt_CrossModuleSpecialise
- | Opt_PolymorphicSpecialisation
- | Opt_InlineGenerics
- | Opt_InlineGenericsAggressively
- | Opt_StaticArgumentTransformation
- | Opt_CSE
- | Opt_StgCSE
- | Opt_StgLiftLams
- | Opt_LiberateCase
- | Opt_SpecConstr
- | Opt_SpecConstrKeen
- | Opt_DoLambdaEtaExpansion
- | Opt_IgnoreAsserts
- | Opt_DoEtaReduction
- | Opt_CaseMerge
- | Opt_CaseFolding
- | Opt_UnboxStrictFields
- | Opt_UnboxSmallStrictFields
- | Opt_DictsCheap
- | Opt_EnableRewriteRules
- | Opt_EnableThSpliceWarnings
- | Opt_RegsGraph
- | Opt_RegsIterative
- | Opt_PedanticBottoms
- | Opt_LlvmTBAA
- | Opt_LlvmFillUndefWithGarbage
- | Opt_IrrefutableTuples
- | Opt_CmmSink
- | Opt_CmmStaticPred
- | Opt_CmmElimCommonBlocks
- | Opt_CmmControlFlow
- | Opt_AsmShortcutting
- | Opt_OmitYields
- | Opt_FunToThunk
- | Opt_DictsStrict
- | Opt_DmdTxDictSel
- | Opt_Loopification
- | Opt_CfgBlocklayout
- | Opt_WeightlessBlocklayout
- | Opt_CprAnal
- | Opt_WorkerWrapper
- | Opt_WorkerWrapperUnlift
- | Opt_SolveConstantDicts
- | Opt_AlignmentSanitisation
- | Opt_CatchNonexhaustiveCases
- | Opt_NumConstantFolding
- | Opt_CoreConstantFolding
- | Opt_FastPAPCalls
- | Opt_DoTagInferenceChecks
- | Opt_SimplPreInlining
- | Opt_IgnoreInterfacePragmas
- | Opt_OmitInterfacePragmas
- | Opt_ExposeAllUnfoldings
- | Opt_WriteInterface
- | Opt_WriteHie
- | Opt_AutoSccsOnIndividualCafs
- | Opt_ProfCountEntries
- | Opt_ProfLateInlineCcs
- | Opt_ProfLateCcs
- | Opt_ProfManualCcs
- | Opt_Pp
- | Opt_ForceRecomp
- | Opt_IgnoreOptimChanges
- | Opt_IgnoreHpcChanges
- | Opt_ExcessPrecision
- | Opt_EagerBlackHoling
- | Opt_NoHsMain
- | Opt_SplitSections
- | Opt_StgStats
- | Opt_HideAllPackages
- | Opt_HideAllPluginPackages
- | Opt_PrintBindResult
- | Opt_Haddock
- | Opt_HaddockOptions
- | Opt_BreakOnException
- | Opt_BreakOnError
- | Opt_PrintEvldWithShow
- | Opt_PrintBindContents
- | Opt_GenManifest
- | Opt_EmbedManifest
- | Opt_SharedImplib
- | Opt_BuildingCabalPackage
- | Opt_IgnoreDotGhci
- | Opt_GhciSandbox
- | Opt_GhciHistory
- | Opt_GhciLeakCheck
- | Opt_ValidateHie
- | Opt_LocalGhciHistory
- | Opt_NoIt
- | Opt_HelpfulErrors
- | Opt_DeferTypeErrors
- | Opt_DeferTypedHoles
- | Opt_DeferOutOfScopeVariables
- | Opt_PIC
- | Opt_PIE
- | Opt_PICExecutable
- | Opt_ExternalDynamicRefs
- | Opt_Ticky
- | Opt_Ticky_Allocd
- | Opt_Ticky_LNE
- | Opt_Ticky_Dyn_Thunk
- | Opt_Ticky_Tag
- | Opt_Ticky_AP
- | Opt_CmmThreadSanitizer
- | Opt_RPath
- | Opt_RelativeDynlibPaths
- | Opt_CompactUnwind
- | Opt_Hpc
- | Opt_FamAppCache
- | Opt_ExternalInterpreter
- | Opt_OptimalApplicativeDo
- | Opt_VersionMacros
- | Opt_WholeArchiveHsLibs
- | Opt_SingleLibFolder
- | Opt_ExposeInternalSymbols
- | Opt_KeepCAFs
- | Opt_KeepGoing
- | Opt_ByteCode
- | Opt_ByteCodeAndObjectCode
- | Opt_LinkRts
- | Opt_ErrorSpans
- | Opt_DeferDiagnostics
- | Opt_DiagnosticsShowCaret
- | Opt_PprCaseAsLet
- | Opt_PprShowTicks
- | Opt_ShowHoleConstraints
- | Opt_ShowValidHoleFits
- | Opt_SortValidHoleFits
- | Opt_SortBySizeHoleFits
- | Opt_SortBySubsumHoleFits
- | Opt_AbstractRefHoleFits
- | Opt_UnclutterValidHoleFits
- | Opt_ShowTypeAppOfHoleFits
- | Opt_ShowTypeAppVarsOfHoleFits
- | Opt_ShowDocsOfHoleFits
- | Opt_ShowTypeOfHoleFits
- | Opt_ShowProvOfHoleFits
- | Opt_ShowMatchesOfHoleFits
- | Opt_ShowLoadedModules
- | Opt_HexWordLiterals
- | Opt_SuppressCoercions
- | Opt_SuppressCoercionTypes
- | Opt_SuppressVarKinds
- | Opt_SuppressModulePrefixes
- | Opt_SuppressTypeApplications
- | Opt_SuppressIdInfo
- | Opt_SuppressUnfoldings
- | Opt_SuppressTypeSignatures
- | Opt_SuppressUniques
- | Opt_SuppressStgExts
- | Opt_SuppressStgReps
- | Opt_SuppressTicks
- | Opt_SuppressTimestamps
- | Opt_SuppressCoreSizes
- | Opt_ShowErrorContext
- | Opt_AutoLinkPackages
- | Opt_ImplicitImportQualified
- | Opt_KeepHscppFiles
- | Opt_KeepHiDiffs
- | Opt_KeepHcFiles
- | Opt_KeepSFiles
- | Opt_KeepTmpFiles
- | Opt_KeepRawTokenStream
- | Opt_KeepLlvmFiles
- | Opt_KeepHiFiles
- | Opt_KeepOFiles
- | Opt_BuildDynamicToo
- | Opt_WriteIfSimplifiedCore
- | Opt_UseBytecodeRatherThanObjects
- | Opt_DistrustAllPackages
- | Opt_PackageTrust
- | Opt_PluginTrustworthy
- | Opt_G_NoStateHack
- | Opt_G_NoOptCoercion
- data Language
- optimisationFlags :: EnumSet GeneralFlag
- codeGenFlags :: EnumSet GeneralFlag
- data WarningFlag
- = Opt_WarnDuplicateExports
- | Opt_WarnDuplicateConstraints
- | Opt_WarnRedundantConstraints
- | Opt_WarnHiShadows
- | Opt_WarnImplicitPrelude
- | Opt_WarnIncompletePatterns
- | Opt_WarnIncompleteUniPatterns
- | Opt_WarnIncompletePatternsRecUpd
- | Opt_WarnOverflowedLiterals
- | Opt_WarnEmptyEnumerations
- | Opt_WarnMissingFields
- | Opt_WarnMissingImportList
- | Opt_WarnMissingMethods
- | Opt_WarnMissingSignatures
- | Opt_WarnMissingLocalSignatures
- | Opt_WarnNameShadowing
- | Opt_WarnOverlappingPatterns
- | Opt_WarnTypeDefaults
- | Opt_WarnMonomorphism
- | Opt_WarnUnusedTopBinds
- | Opt_WarnUnusedLocalBinds
- | Opt_WarnUnusedPatternBinds
- | Opt_WarnUnusedImports
- | Opt_WarnUnusedMatches
- | Opt_WarnUnusedTypePatterns
- | Opt_WarnUnusedForalls
- | Opt_WarnUnusedRecordWildcards
- | Opt_WarnRedundantBangPatterns
- | Opt_WarnRedundantRecordWildcards
- | Opt_WarnWarningsDeprecations
- | Opt_WarnDeprecatedFlags
- | Opt_WarnMissingMonadFailInstances
- | Opt_WarnSemigroup
- | Opt_WarnDodgyExports
- | Opt_WarnDodgyImports
- | Opt_WarnOrphans
- | Opt_WarnAutoOrphans
- | Opt_WarnIdentities
- | Opt_WarnTabs
- | Opt_WarnUnrecognisedPragmas
- | Opt_WarnMisplacedPragmas
- | Opt_WarnDodgyForeignImports
- | Opt_WarnUnusedDoBind
- | Opt_WarnWrongDoBind
- | Opt_WarnAlternativeLayoutRuleTransitional
- | Opt_WarnUnsafe
- | Opt_WarnSafe
- | Opt_WarnTrustworthySafe
- | Opt_WarnMissedSpecs
- | Opt_WarnAllMissedSpecs
- | Opt_WarnUnsupportedCallingConventions
- | Opt_WarnUnsupportedLlvmVersion
- | Opt_WarnMissedExtraSharedLib
- | Opt_WarnInlineRuleShadowing
- | Opt_WarnTypedHoles
- | Opt_WarnPartialTypeSignatures
- | Opt_WarnMissingExportedSignatures
- | Opt_WarnUntickedPromotedConstructors
- | Opt_WarnDerivingTypeable
- | Opt_WarnDeferredTypeErrors
- | Opt_WarnDeferredOutOfScopeVariables
- | Opt_WarnNonCanonicalMonadInstances
- | Opt_WarnNonCanonicalMonadFailInstances
- | Opt_WarnNonCanonicalMonoidInstances
- | Opt_WarnMissingPatternSynonymSignatures
- | Opt_WarnUnrecognisedWarningFlags
- | Opt_WarnSimplifiableClassConstraints
- | Opt_WarnCPPUndef
- | Opt_WarnUnbangedStrictPatterns
- | Opt_WarnMissingHomeModules
- | Opt_WarnPartialFields
- | Opt_WarnMissingExportList
- | Opt_WarnInaccessibleCode
- | Opt_WarnStarIsType
- | Opt_WarnStarBinder
- | Opt_WarnImplicitKindVars
- | Opt_WarnSpaceAfterBang
- | Opt_WarnMissingDerivingStrategies
- | Opt_WarnPrepositiveQualifiedModule
- | Opt_WarnUnusedPackages
- | Opt_WarnInferredSafeImports
- | Opt_WarnMissingSafeHaskellMode
- | Opt_WarnCompatUnqualifiedImports
- | Opt_WarnDerivingDefaults
- | Opt_WarnInvalidHaddock
- | Opt_WarnOperatorWhitespaceExtConflict
- | Opt_WarnOperatorWhitespace
- | Opt_WarnAmbiguousFields
- | Opt_WarnImplicitLift
- | Opt_WarnMissingKindSignatures
- | Opt_WarnMissingExportedPatternSynonymSignatures
- | Opt_WarnRedundantStrictnessFlags
- | Opt_WarnForallIdentifier
- | Opt_WarnUnicodeBidirectionalFormatCharacters
- | Opt_WarnGADTMonoLocalBinds
- | Opt_WarnTypeEqualityOutOfScope
- | Opt_WarnTypeEqualityRequiresOperators
- | Opt_WarnLoopySuperclassSolve
- warnFlagNames :: WarningFlag -> NonEmpty String
- warningGroups :: [(String, [WarningFlag])]
- warningHierarchies :: [[String]]
- smallestWarningGroups :: WarningFlag -> [String]
- standardWarnings :: [WarningFlag]
- minusWOpts :: [WarningFlag]
- minusWallOpts :: [WarningFlag]
- minusWeverythingOpts :: [WarningFlag]
- minusWcompatOpts :: [WarningFlag]
- unusedBindsFlags :: [WarningFlag]
Documentation
Debugging flags
Instances
Enum DumpFlag Source # | |
Defined in GHC.Driver.Flags succ :: DumpFlag -> DumpFlag Source # pred :: DumpFlag -> DumpFlag Source # toEnum :: Int -> DumpFlag Source # fromEnum :: DumpFlag -> Int Source # enumFrom :: DumpFlag -> [DumpFlag] Source # enumFromThen :: DumpFlag -> DumpFlag -> [DumpFlag] Source # enumFromTo :: DumpFlag -> DumpFlag -> [DumpFlag] Source # enumFromThenTo :: DumpFlag -> DumpFlag -> DumpFlag -> [DumpFlag] Source # | |
Show DumpFlag Source # | |
Eq DumpFlag Source # | |
:: (a -> Int) | Getter for verbosity setting |
-> (a -> EnumSet DumpFlag) | Getter for the set of enabled dump flags |
-> DumpFlag | |
-> a | |
-> Bool |
Helper function to query whether a given DumpFlag
is enabled or not.
enabledIfVerbose :: DumpFlag -> Bool Source #
Is the flag implicitly enabled when the verbosity is high enough?
data GeneralFlag Source #
Enumerates the simple on-or-off dynamic flags
Instances
Enum GeneralFlag Source # | |
Defined in GHC.Driver.Flags succ :: GeneralFlag -> GeneralFlag Source # pred :: GeneralFlag -> GeneralFlag Source # toEnum :: Int -> GeneralFlag Source # fromEnum :: GeneralFlag -> Int Source # enumFrom :: GeneralFlag -> [GeneralFlag] Source # enumFromThen :: GeneralFlag -> GeneralFlag -> [GeneralFlag] Source # enumFromTo :: GeneralFlag -> GeneralFlag -> [GeneralFlag] Source # enumFromThenTo :: GeneralFlag -> GeneralFlag -> GeneralFlag -> [GeneralFlag] Source # | |
Show GeneralFlag Source # | |
Defined in GHC.Driver.Flags | |
Eq GeneralFlag Source # | |
Defined in GHC.Driver.Flags (==) :: GeneralFlag -> GeneralFlag -> Bool # (/=) :: GeneralFlag -> GeneralFlag -> Bool # |
Instances
Bounded Language Source # | |
Enum Language Source # | |
Defined in GHC.Driver.Flags succ :: Language -> Language Source # pred :: Language -> Language Source # toEnum :: Int -> Language Source # fromEnum :: Language -> Int Source # enumFrom :: Language -> [Language] Source # enumFromThen :: Language -> Language -> [Language] Source # enumFromTo :: Language -> Language -> [Language] Source # enumFromThenTo :: Language -> Language -> Language -> [Language] Source # | |
Show Language Source # | |
NFData Language Source # | |
Defined in GHC.Driver.Flags | |
Binary Language Source # | |
Outputable Language Source # | |
Eq Language Source # | |
optimisationFlags :: EnumSet GeneralFlag Source #
The set of flags which affect optimisation for the purposes of recompilation avoidance. Specifically, these include flags which affect code generation but not the semantics of the program.
See Note [Ignoring some flag changes] in GHC.Iface.Recomp.Flags)
codeGenFlags :: EnumSet GeneralFlag Source #
The set of flags which affect code generation and can change a program's runtime behavior (other than performance). These include flags which affect:
- user visible debugging information (e.g. info table provenance)
- the ability to catch runtime errors (e.g. -fignore-asserts)
- the runtime result of the program (e.g. -fomit-yields)
- which code or interface file declarations are emitted
We also considered placing flags which affect asympototic space behavior (e.g. -ffull-laziness) however this would mean that changing optimisation levels would trigger recompilation even with -fignore-optim-changes, regressing #13604.
Also, arguably Opt_IgnoreAsserts should be here as well; however, we place
it instead in optimisationFlags
since it is implied by -O[12]
and
therefore would also break #13604.
See #23369.
Warnings
data WarningFlag Source #
Instances
warnFlagNames :: WarningFlag -> NonEmpty String Source #
Return the names of a WarningFlag
One flag may have several names because of US/UK spelling. The first one is the "preferred one" that will be displayed in warning messages.
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.
smallestWarningGroups :: WarningFlag -> [String] Source #
Find the smallest group in every hierarchy which a warning belongs to, excluding Weverything.
standardWarnings :: [WarningFlag] Source #
Warnings enabled unless specified otherwise
minusWOpts :: [WarningFlag] Source #
Things you get with -W
minusWallOpts :: [WarningFlag] Source #
Things you get with -Wall
minusWeverythingOpts :: [WarningFlag] Source #
Things you get with -Weverything, i.e. *all* known warnings flags
minusWcompatOpts :: [WarningFlag] Source #
Things you get with -Wcompat.
This is intended to group together warnings that will be enabled by default at some point in the future, so that library authors eager to make their code future compatible to fix issues before they even generate warnings.
unusedBindsFlags :: [WarningFlag] Source #
Things you get with -Wunused-binds