Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- newtype MinBound = MinBound Integer
- newtype MaxBound = MaxBound Integer
- type MaxUncoveredPatterns = Int
- type MaxPmCheckModels = Int
- data DsMessage
- = DsUnknownMessage (UnknownDiagnostic (DiagnosticOpts DsMessage))
- | DsEmptyEnumeration
- | DsIdentitiesFound !Id !Type
- | DsOverflowedLiterals !Integer !Name !(Maybe (MinBound, MaxBound)) !NegLiteralExtEnabled
- | DsRedundantBangPatterns !HsMatchContextRn !SDoc
- | DsOverlappingPatterns !HsMatchContextRn !SDoc
- | DsInaccessibleRhs !HsMatchContextRn !SDoc
- | DsMaxPmCheckModelsReached !MaxPmCheckModels
- | DsNonExhaustivePatterns !HsMatchContextRn !ExhaustivityCheckType !MaxUncoveredPatterns [Id] [Nabla]
- | DsTopLevelBindsNotAllowed !BindsType !(HsBindLR GhcTc GhcTc)
- | DsUselessSpecialiseForClassMethodSelector !Id
- | DsUselessSpecialiseForNoInlineFunction !Id
- | DsMultiplicityCoercionsNotSupported
- | DsOrphanRule !CoreRule
- | DsRuleLhsTooComplicated !CoreExpr !CoreExpr
- | DsRuleIgnoredDueToConstructor !DataCon
- | DsRuleBindersNotBound ![Var] ![Var] !CoreExpr !CoreExpr
- | DsLazyPatCantBindVarsOfUnliftedType [Var]
- | DsNotYetHandledByTH !ThRejectionReason
- | DsAggregatedViewExpressions [[LHsExpr GhcTc]]
- | DsUnbangedStrictPatterns !(HsBindLR GhcTc GhcTc)
- | DsCannotMixPolyAndUnliftedBindings !(HsBindLR GhcTc GhcTc)
- | DsWrongDoBind !(LHsExpr GhcTc) !Type
- | DsUnusedDoBind !(LHsExpr GhcTc) !Type
- | DsRecBindsNotAllowedForUnliftedTys ![LHsBindLR GhcTc GhcTc]
- | DsRuleMightInlineFirst !RuleName !Var !Activation
- | DsAnotherRuleMightFireFirst !RuleName !RuleName !Var
- | DsIncompleteRecordSelector !Name ![ConLike] !Bool
- newtype DsArgNum = DsArgNum Int
- data ThRejectionReason
- = ThAmbiguousRecordUpdates !(HsRecUpdField GhcRn GhcRn)
- | ThAbstractClosedTypeFamily !(LFamilyDecl GhcRn)
- | ThForeignLabel !CLabelString
- | ThForeignExport !(LForeignDecl GhcRn)
- | ThMinimalPragmas
- | ThSCCPragmas
- | ThNoUserInline
- | ThExoticFormOfType !(HsType GhcRn)
- | ThAmbiguousRecordSelectors !(HsExpr GhcRn)
- | ThMonadComprehensionSyntax !(HsExpr GhcRn)
- | ThCostCentres !(HsExpr GhcRn)
- | ThExpressionForm !(HsExpr GhcRn)
- | ThExoticStatement [Stmt GhcRn (LHsExpr GhcRn)]
- | ThExoticLiteral !(HsLit GhcRn)
- | ThExoticPattern !(Pat GhcRn)
- | ThGuardedLambdas !(Match GhcRn (LHsExpr GhcRn))
- | ThNegativeOverloadedPatterns !(Pat GhcRn)
- | ThHaddockDocumentation
- | ThWarningAndDeprecationPragmas [LIdP GhcRn]
- | ThSplicesWithinDeclBrackets
- | ThNonLinearDataCon
- data NegLiteralExtEnabled
- negLiteralExtEnabled :: DynFlags -> NegLiteralExtEnabled
- newtype ExhaustivityCheckType = ExhaustivityCheckType (Maybe WarningFlag)
- data BindsType
Documentation
type MaxUncoveredPatterns = Int Source #
type MaxPmCheckModels = Int Source #
Diagnostics messages emitted during desugaring.
DsUnknownMessage (UnknownDiagnostic (DiagnosticOpts DsMessage)) | Simply wraps a generic |
DsEmptyEnumeration | DsEmptyEnumeration is a warning (controlled by the -Wempty-enumerations flag) that is emitted if an enumeration is empty. Example(s): main :: IO () main = do let enum = [5 .. 3] print enum Here Test case(s): warningsshould_compileT10930 warningsshould_compileT18402 warningsshould_compileT10930b numericshould_compileT10929 numericshould_compileT7881 deSugarshould_runT18172 |
DsIdentitiesFound !Id !Type | DsIdentitiesFound is a warning (controlled by the -Widentities flag) that is emitted on uses of Prelude numeric conversions that are probably the identity (and hence could be omitted). Example(s): main :: IO () main = do let x = 10 print $ conv 10 where conv :: Int -> Int conv x = fromIntegral x Here calling Test case(s): deSugarshould_compileT4488 |
DsOverflowedLiterals !Integer !Name !(Maybe (MinBound, MaxBound)) !NegLiteralExtEnabled | |
DsRedundantBangPatterns !HsMatchContextRn !SDoc | |
DsOverlappingPatterns !HsMatchContextRn !SDoc | |
DsInaccessibleRhs !HsMatchContextRn !SDoc | |
DsMaxPmCheckModelsReached !MaxPmCheckModels | |
DsNonExhaustivePatterns !HsMatchContextRn !ExhaustivityCheckType !MaxUncoveredPatterns [Id] [Nabla] | |
DsTopLevelBindsNotAllowed !BindsType !(HsBindLR GhcTc GhcTc) | |
DsUselessSpecialiseForClassMethodSelector !Id | |
DsUselessSpecialiseForNoInlineFunction !Id | |
DsMultiplicityCoercionsNotSupported | |
DsOrphanRule !CoreRule | |
DsRuleLhsTooComplicated !CoreExpr !CoreExpr | |
DsRuleIgnoredDueToConstructor !DataCon | |
DsRuleBindersNotBound | |
DsLazyPatCantBindVarsOfUnliftedType [Var] | |
DsNotYetHandledByTH !ThRejectionReason | |
DsAggregatedViewExpressions [[LHsExpr GhcTc]] | |
DsUnbangedStrictPatterns !(HsBindLR GhcTc GhcTc) | |
DsCannotMixPolyAndUnliftedBindings !(HsBindLR GhcTc GhcTc) | |
DsWrongDoBind !(LHsExpr GhcTc) !Type | |
DsUnusedDoBind !(LHsExpr GhcTc) !Type | |
DsRecBindsNotAllowedForUnliftedTys ![LHsBindLR GhcTc GhcTc] | |
DsRuleMightInlineFirst !RuleName !Var !Activation | |
DsAnotherRuleMightFireFirst !RuleName !RuleName !Var | |
DsIncompleteRecordSelector !Name ![ConLike] !Bool | DsIncompleteRecordSelector is a warning triggered when we are not certain whether a record selector application will be successful. Currently, this means that the warning is triggered when there is a record selector of a data type that does not have that field in all its constructors. Example(s): data T = T1 | T2 {x :: Bool} f :: T -> Bool f a = x a Test cases: DsIncompleteRecSel1 DsIncompleteRecSel2 DsIncompleteRecSel3 |
Instances
data ThRejectionReason Source #
Why TemplateHaskell rejected the splice. Used in the DsNotYetHandledByTH
constructor of a DsMessage
.
ThAmbiguousRecordUpdates !(HsRecUpdField GhcRn GhcRn) | |
ThAbstractClosedTypeFamily !(LFamilyDecl GhcRn) | |
ThForeignLabel !CLabelString | |
ThForeignExport !(LForeignDecl GhcRn) | |
ThMinimalPragmas | |
ThSCCPragmas | |
ThNoUserInline | |
ThExoticFormOfType !(HsType GhcRn) | |
ThAmbiguousRecordSelectors !(HsExpr GhcRn) | |
ThMonadComprehensionSyntax !(HsExpr GhcRn) | |
ThCostCentres !(HsExpr GhcRn) | |
ThExpressionForm !(HsExpr GhcRn) | |
ThExoticStatement [Stmt GhcRn (LHsExpr GhcRn)] | |
ThExoticLiteral !(HsLit GhcRn) | |
ThExoticPattern !(Pat GhcRn) | |
ThGuardedLambdas !(Match GhcRn (LHsExpr GhcRn)) | |
ThNegativeOverloadedPatterns !(Pat GhcRn) | |
ThHaddockDocumentation | |
ThWarningAndDeprecationPragmas [LIdP GhcRn] | |
ThSplicesWithinDeclBrackets | |
ThNonLinearDataCon |