module GHC.Driver.Flags
( DumpFlag(..)
, GeneralFlag(..)
, WarningFlag(..)
, WarnReason (..)
, Language(..)
, optimisationFlags
)
where
import GHC.Prelude
import GHC.Utils.Outputable
import GHC.Data.EnumSet as EnumSet
import GHC.Utils.Json
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_unarised
| 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_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
deriving (DumpFlag -> DumpFlag -> Bool
(DumpFlag -> DumpFlag -> Bool)
-> (DumpFlag -> DumpFlag -> Bool) -> Eq DumpFlag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DumpFlag -> DumpFlag -> Bool
$c/= :: DumpFlag -> DumpFlag -> Bool
== :: DumpFlag -> DumpFlag -> Bool
$c== :: DumpFlag -> DumpFlag -> Bool
Eq, Int -> DumpFlag -> ShowS
[DumpFlag] -> ShowS
DumpFlag -> String
(Int -> DumpFlag -> ShowS)
-> (DumpFlag -> String) -> ([DumpFlag] -> ShowS) -> Show DumpFlag
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DumpFlag] -> ShowS
$cshowList :: [DumpFlag] -> ShowS
show :: DumpFlag -> String
$cshow :: DumpFlag -> String
showsPrec :: Int -> DumpFlag -> ShowS
$cshowsPrec :: Int -> DumpFlag -> ShowS
Show, Int -> DumpFlag
DumpFlag -> Int
DumpFlag -> [DumpFlag]
DumpFlag -> DumpFlag
DumpFlag -> DumpFlag -> [DumpFlag]
DumpFlag -> DumpFlag -> DumpFlag -> [DumpFlag]
(DumpFlag -> DumpFlag)
-> (DumpFlag -> DumpFlag)
-> (Int -> DumpFlag)
-> (DumpFlag -> Int)
-> (DumpFlag -> [DumpFlag])
-> (DumpFlag -> DumpFlag -> [DumpFlag])
-> (DumpFlag -> DumpFlag -> [DumpFlag])
-> (DumpFlag -> DumpFlag -> DumpFlag -> [DumpFlag])
-> Enum DumpFlag
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: DumpFlag -> DumpFlag -> DumpFlag -> [DumpFlag]
$cenumFromThenTo :: DumpFlag -> DumpFlag -> DumpFlag -> [DumpFlag]
enumFromTo :: DumpFlag -> DumpFlag -> [DumpFlag]
$cenumFromTo :: DumpFlag -> DumpFlag -> [DumpFlag]
enumFromThen :: DumpFlag -> DumpFlag -> [DumpFlag]
$cenumFromThen :: DumpFlag -> DumpFlag -> [DumpFlag]
enumFrom :: DumpFlag -> [DumpFlag]
$cenumFrom :: DumpFlag -> [DumpFlag]
fromEnum :: DumpFlag -> Int
$cfromEnum :: DumpFlag -> Int
toEnum :: Int -> DumpFlag
$ctoEnum :: Int -> DumpFlag
pred :: DumpFlag -> DumpFlag
$cpred :: DumpFlag -> DumpFlag
succ :: DumpFlag -> DumpFlag
$csucc :: DumpFlag -> DumpFlag
External instance of the constraint type Enum Int
External instance of the constraint type Show Int
External instance of the constraint type Show Int
External instance of the constraint type Ord Int
External instance of the constraint type Ord Int
External instance of the constraint type Num Int
External instance of the constraint type Eq Int
Enum)
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_EnableThSpliceWarnings
| Opt_RegsGraph
| Opt_RegsIterative
| Opt_PedanticBottoms
| Opt_LlvmTBAA
| Opt_LlvmFillUndefWithGarbage
| Opt_IrrefutableTuples
| Opt_CmmSink
| Opt_CmmStaticPred
| 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
deriving (GeneralFlag -> GeneralFlag -> Bool
(GeneralFlag -> GeneralFlag -> Bool)
-> (GeneralFlag -> GeneralFlag -> Bool) -> Eq GeneralFlag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GeneralFlag -> GeneralFlag -> Bool
$c/= :: GeneralFlag -> GeneralFlag -> Bool
== :: GeneralFlag -> GeneralFlag -> Bool
$c== :: GeneralFlag -> GeneralFlag -> Bool
Eq, Int -> GeneralFlag -> ShowS
[GeneralFlag] -> ShowS
GeneralFlag -> String
(Int -> GeneralFlag -> ShowS)
-> (GeneralFlag -> String)
-> ([GeneralFlag] -> ShowS)
-> Show GeneralFlag
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GeneralFlag] -> ShowS
$cshowList :: [GeneralFlag] -> ShowS
show :: GeneralFlag -> String
$cshow :: GeneralFlag -> String
showsPrec :: Int -> GeneralFlag -> ShowS
$cshowsPrec :: Int -> GeneralFlag -> ShowS
Show, Int -> GeneralFlag
GeneralFlag -> Int
GeneralFlag -> [GeneralFlag]
GeneralFlag -> GeneralFlag
GeneralFlag -> GeneralFlag -> [GeneralFlag]
GeneralFlag -> GeneralFlag -> GeneralFlag -> [GeneralFlag]
(GeneralFlag -> GeneralFlag)
-> (GeneralFlag -> GeneralFlag)
-> (Int -> GeneralFlag)
-> (GeneralFlag -> Int)
-> (GeneralFlag -> [GeneralFlag])
-> (GeneralFlag -> GeneralFlag -> [GeneralFlag])
-> (GeneralFlag -> GeneralFlag -> [GeneralFlag])
-> (GeneralFlag -> GeneralFlag -> GeneralFlag -> [GeneralFlag])
-> Enum GeneralFlag
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: GeneralFlag -> GeneralFlag -> GeneralFlag -> [GeneralFlag]
$cenumFromThenTo :: GeneralFlag -> GeneralFlag -> GeneralFlag -> [GeneralFlag]
enumFromTo :: GeneralFlag -> GeneralFlag -> [GeneralFlag]
$cenumFromTo :: GeneralFlag -> GeneralFlag -> [GeneralFlag]
enumFromThen :: GeneralFlag -> GeneralFlag -> [GeneralFlag]
$cenumFromThen :: GeneralFlag -> GeneralFlag -> [GeneralFlag]
enumFrom :: GeneralFlag -> [GeneralFlag]
$cenumFrom :: GeneralFlag -> [GeneralFlag]
fromEnum :: GeneralFlag -> Int
$cfromEnum :: GeneralFlag -> Int
toEnum :: Int -> GeneralFlag
$ctoEnum :: Int -> GeneralFlag
pred :: GeneralFlag -> GeneralFlag
$cpred :: GeneralFlag -> GeneralFlag
succ :: GeneralFlag -> GeneralFlag
$csucc :: GeneralFlag -> GeneralFlag
External instance of the constraint type Show Int
External instance of the constraint type Ord Int
External instance of the constraint type Enum Int
External instance of the constraint type Show Int
External instance of the constraint type Ord Int
External instance of the constraint type Num Int
External instance of the constraint type Eq Int
Enum)
optimisationFlags :: EnumSet GeneralFlag
optimisationFlags :: EnumSet GeneralFlag
optimisationFlags = [GeneralFlag] -> EnumSet GeneralFlag
forall a. Enum a => [a] -> EnumSet a
Instance of class: Enum of the constraint type Enum GeneralFlag
EnumSet.fromList
[ GeneralFlag
Opt_CallArity
, GeneralFlag
Opt_Strictness
, GeneralFlag
Opt_LateDmdAnal
, GeneralFlag
Opt_KillAbsence
, GeneralFlag
Opt_KillOneShot
, GeneralFlag
Opt_FullLaziness
, GeneralFlag
Opt_FloatIn
, GeneralFlag
Opt_LateSpecialise
, GeneralFlag
Opt_Specialise
, GeneralFlag
Opt_SpecialiseAggressively
, GeneralFlag
Opt_CrossModuleSpecialise
, GeneralFlag
Opt_StaticArgumentTransformation
, GeneralFlag
Opt_CSE
, GeneralFlag
Opt_StgCSE
, GeneralFlag
Opt_StgLiftLams
, GeneralFlag
Opt_LiberateCase
, GeneralFlag
Opt_SpecConstr
, GeneralFlag
Opt_SpecConstrKeen
, GeneralFlag
Opt_DoLambdaEtaExpansion
, GeneralFlag
Opt_IgnoreAsserts
, GeneralFlag
Opt_DoEtaReduction
, GeneralFlag
Opt_CaseMerge
, GeneralFlag
Opt_CaseFolding
, GeneralFlag
Opt_UnboxStrictFields
, GeneralFlag
Opt_UnboxSmallStrictFields
, GeneralFlag
Opt_DictsCheap
, GeneralFlag
Opt_EnableRewriteRules
, GeneralFlag
Opt_RegsGraph
, GeneralFlag
Opt_RegsIterative
, GeneralFlag
Opt_PedanticBottoms
, GeneralFlag
Opt_LlvmTBAA
, GeneralFlag
Opt_LlvmFillUndefWithGarbage
, GeneralFlag
Opt_IrrefutableTuples
, GeneralFlag
Opt_CmmSink
, GeneralFlag
Opt_CmmElimCommonBlocks
, GeneralFlag
Opt_AsmShortcutting
, GeneralFlag
Opt_OmitYields
, GeneralFlag
Opt_FunToThunk
, GeneralFlag
Opt_DictsStrict
, GeneralFlag
Opt_DmdTxDictSel
, GeneralFlag
Opt_Loopification
, GeneralFlag
Opt_CfgBlocklayout
, GeneralFlag
Opt_WeightlessBlocklayout
, GeneralFlag
Opt_CprAnal
, GeneralFlag
Opt_WorkerWrapper
, GeneralFlag
Opt_SolveConstantDicts
, GeneralFlag
Opt_CatchBottoms
, GeneralFlag
Opt_IgnoreAsserts
]
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_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
deriving (WarningFlag -> WarningFlag -> Bool
(WarningFlag -> WarningFlag -> Bool)
-> (WarningFlag -> WarningFlag -> Bool) -> Eq WarningFlag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WarningFlag -> WarningFlag -> Bool
$c/= :: WarningFlag -> WarningFlag -> Bool
== :: WarningFlag -> WarningFlag -> Bool
$c== :: WarningFlag -> WarningFlag -> Bool
Eq, Int -> WarningFlag -> ShowS
[WarningFlag] -> ShowS
WarningFlag -> String
(Int -> WarningFlag -> ShowS)
-> (WarningFlag -> String)
-> ([WarningFlag] -> ShowS)
-> Show WarningFlag
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WarningFlag] -> ShowS
$cshowList :: [WarningFlag] -> ShowS
show :: WarningFlag -> String
$cshow :: WarningFlag -> String
showsPrec :: Int -> WarningFlag -> ShowS
$cshowsPrec :: Int -> WarningFlag -> ShowS
Show, Int -> WarningFlag
WarningFlag -> Int
WarningFlag -> [WarningFlag]
WarningFlag -> WarningFlag
WarningFlag -> WarningFlag -> [WarningFlag]
WarningFlag -> WarningFlag -> WarningFlag -> [WarningFlag]
(WarningFlag -> WarningFlag)
-> (WarningFlag -> WarningFlag)
-> (Int -> WarningFlag)
-> (WarningFlag -> Int)
-> (WarningFlag -> [WarningFlag])
-> (WarningFlag -> WarningFlag -> [WarningFlag])
-> (WarningFlag -> WarningFlag -> [WarningFlag])
-> (WarningFlag -> WarningFlag -> WarningFlag -> [WarningFlag])
-> Enum WarningFlag
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: WarningFlag -> WarningFlag -> WarningFlag -> [WarningFlag]
$cenumFromThenTo :: WarningFlag -> WarningFlag -> WarningFlag -> [WarningFlag]
enumFromTo :: WarningFlag -> WarningFlag -> [WarningFlag]
$cenumFromTo :: WarningFlag -> WarningFlag -> [WarningFlag]
enumFromThen :: WarningFlag -> WarningFlag -> [WarningFlag]
$cenumFromThen :: WarningFlag -> WarningFlag -> [WarningFlag]
enumFrom :: WarningFlag -> [WarningFlag]
$cenumFrom :: WarningFlag -> [WarningFlag]
fromEnum :: WarningFlag -> Int
$cfromEnum :: WarningFlag -> Int
toEnum :: Int -> WarningFlag
$ctoEnum :: Int -> WarningFlag
pred :: WarningFlag -> WarningFlag
$cpred :: WarningFlag -> WarningFlag
succ :: WarningFlag -> WarningFlag
$csucc :: WarningFlag -> WarningFlag
External instance of the constraint type Show Int
External instance of the constraint type Ord Int
External instance of the constraint type Enum Int
External instance of the constraint type Show Int
External instance of the constraint type Ord Int
External instance of the constraint type Num Int
External instance of the constraint type Eq Int
Enum)
data WarnReason
= NoReason
| Reason !WarningFlag
| ErrReason !(Maybe WarningFlag)
deriving Int -> WarnReason -> ShowS
[WarnReason] -> ShowS
WarnReason -> String
(Int -> WarnReason -> ShowS)
-> (WarnReason -> String)
-> ([WarnReason] -> ShowS)
-> Show WarnReason
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WarnReason] -> ShowS
$cshowList :: [WarnReason] -> ShowS
show :: WarnReason -> String
$cshow :: WarnReason -> String
showsPrec :: Int -> WarnReason -> ShowS
$cshowsPrec :: Int -> WarnReason -> ShowS
External instance of the constraint type forall a. Show a => Show (Maybe a)
Instance of class: Show of the constraint type Show WarningFlag
External instance of the constraint type Ord Int
External instance of the constraint type Ord Int
Instance of class: Show of the constraint type Show WarningFlag
Show
instance Outputable WarnReason where
ppr :: WarnReason -> SDoc
ppr = String -> SDoc
text (String -> SDoc) -> (WarnReason -> String) -> WarnReason -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WarnReason -> String
forall a. Show a => a -> String
Instance of class: Show of the constraint type Show WarnReason
show
instance ToJson WarnReason where
json :: WarnReason -> JsonDoc
json WarnReason
NoReason = JsonDoc
JSNull
json (Reason WarningFlag
wf) = String -> JsonDoc
JSString (WarningFlag -> String
forall a. Show a => a -> String
Instance of class: Show of the constraint type Show WarningFlag
show WarningFlag
wf)
json (ErrReason Maybe WarningFlag
Nothing) = String -> JsonDoc
JSString String
"Opt_WarnIsError"
json (ErrReason (Just WarningFlag
wf)) = String -> JsonDoc
JSString (WarningFlag -> String
forall a. Show a => a -> String
Instance of class: Show of the constraint type Show WarningFlag
show WarningFlag
wf)
data Language = Haskell98 | Haskell2010
deriving (Language -> Language -> Bool
(Language -> Language -> Bool)
-> (Language -> Language -> Bool) -> Eq Language
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Language -> Language -> Bool
$c/= :: Language -> Language -> Bool
== :: Language -> Language -> Bool
$c== :: Language -> Language -> Bool
Eq, Int -> Language
Language -> Int
Language -> [Language]
Language -> Language
Language -> Language -> [Language]
Language -> Language -> Language -> [Language]
(Language -> Language)
-> (Language -> Language)
-> (Int -> Language)
-> (Language -> Int)
-> (Language -> [Language])
-> (Language -> Language -> [Language])
-> (Language -> Language -> [Language])
-> (Language -> Language -> Language -> [Language])
-> Enum Language
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Language -> Language -> Language -> [Language]
$cenumFromThenTo :: Language -> Language -> Language -> [Language]
enumFromTo :: Language -> Language -> [Language]
$cenumFromTo :: Language -> Language -> [Language]
enumFromThen :: Language -> Language -> [Language]
$cenumFromThen :: Language -> Language -> [Language]
enumFrom :: Language -> [Language]
$cenumFrom :: Language -> [Language]
fromEnum :: Language -> Int
$cfromEnum :: Language -> Int
toEnum :: Int -> Language
$ctoEnum :: Int -> Language
pred :: Language -> Language
$cpred :: Language -> Language
succ :: Language -> Language
$csucc :: Language -> Language
External instance of the constraint type Show Int
External instance of the constraint type Ord Int
External instance of the constraint type Enum Int
External instance of the constraint type Show Int
External instance of the constraint type Ord Int
External instance of the constraint type Num Int
External instance of the constraint type Eq Int
Enum, Int -> Language -> ShowS
[Language] -> ShowS
Language -> String
(Int -> Language -> ShowS)
-> (Language -> String) -> ([Language] -> ShowS) -> Show Language
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Language] -> ShowS
$cshowList :: [Language] -> ShowS
show :: Language -> String
$cshow :: Language -> String
showsPrec :: Int -> Language -> ShowS
$cshowsPrec :: Int -> Language -> ShowS
Show)
instance Outputable Language where
ppr :: Language -> SDoc
ppr = String -> SDoc
text (String -> SDoc) -> (Language -> String) -> Language -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Language -> String
forall a. Show a => a -> String
Instance of class: Show of the constraint type Show Language
show