Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- type PsWarning = PsMessage
- type PsError = PsMessage
- data PsHeaderMessage
- data PsMessage
- = PsUnknownMessage (UnknownDiagnostic (DiagnosticOpts PsMessage))
- | PsHeaderMessage !PsHeaderMessage
- | PsWarnBidirectionalFormatChars (NonEmpty (PsLoc, Char, String))
- | PsWarnTab !Word
- | PsWarnTransitionalLayout !TransLayoutReason
- | PsWarnUnrecognisedPragma !String ![String]
- | PsWarnMisplacedPragma !FileHeaderPragmaType
- | PsWarnHaddockInvalidPos
- | PsWarnHaddockIgnoreMulti
- | PsWarnStarBinder
- | PsWarnStarIsType
- | PsWarnImportPreQualified
- | PsWarnOperatorWhitespaceExtConflict !OperatorWhitespaceSymbol
- | PsWarnOperatorWhitespace !FastString !OperatorWhitespaceOccurrence
- | PsWarnViewPatternSignatures !(LPat GhcPs) !(LPat GhcPs)
- | PsErrLambdaCase
- | PsErrEmptyLambda
- | PsErrNumUnderscores !NumUnderscoreReason
- | PsErrPrimStringInvalidChar
- | PsErrMissingBlock
- | PsErrLexer !LexErr !LexErrKind
- | PsErrSuffixAT
- | PsErrParse !String !PsErrParseDetails
- | PsErrCmmLexer
- | PsErrUnsupportedBoxedSumExpr !(SumOrTuple (HsExpr GhcPs))
- | PsErrUnsupportedBoxedSumPat !(SumOrTuple (PatBuilder GhcPs))
- | PsErrUnexpectedQualifiedConstructor !RdrName
- | PsErrTupleSectionInPat
- | PsErrIllegalBangPattern !(Pat GhcPs)
- | PsErrOpFewArgs !StarIsType !RdrName
- | PsErrImportQualifiedTwice
- | PsErrImportPostQualified
- | PsErrIllegalExplicitNamespace
- | PsErrVarForTyCon !RdrName
- | PsErrIllegalPatSynExport
- | PsErrMalformedEntityString
- | PsErrDotsInRecordUpdate
- | PsErrPrecedenceOutOfRange !Int
- | PsErrOverloadedRecordDotInvalid
- | PsErrOverloadedRecordUpdateNotEnabled
- | PsErrOverloadedRecordUpdateNoQualifiedFields
- | PsErrInvalidDataCon !(HsType GhcPs)
- | PsErrInvalidInfixDataCon !(HsType GhcPs) !RdrName !(HsType GhcPs)
- | PsErrIllegalPromotionQuoteDataCon !RdrName
- | PsErrUnpackDataCon
- | PsErrUnexpectedKindAppInDataCon !DataConBuilder !(HsType GhcPs)
- | PsErrInvalidRecordCon !(PatBuilder GhcPs)
- | PsErrIllegalUnboxedStringInPat !(HsLit GhcPs)
- | PsErrIllegalUnboxedFloatingLitInPat !(HsLit GhcPs)
- | PsErrDoNotationInPat
- | PsErrIfThenElseInPat
- | PsErrLambdaInPat HsLamVariant
- | PsErrCaseInPat
- | PsErrLetInPat
- | PsErrArrowExprInPat !(HsExpr GhcPs)
- | PsErrArrowCmdInPat !(HsCmd GhcPs)
- | PsErrArrowCmdInExpr !(HsCmd GhcPs)
- | PsErrOrPatInExpr !(LPat GhcPs)
- | PsErrTypeAppWithoutSpace !RdrName !(LHsExpr GhcPs)
- | PsErrLazyPatWithoutSpace !(LHsExpr GhcPs)
- | PsErrBangPatWithoutSpace !(LHsExpr GhcPs)
- | PsErrUnallowedPragma !(HsPragE GhcPs)
- | PsErrQualifiedDoInCmd !ModuleName
- | PsErrInvalidInfixHole
- | PsErrSemiColonsInCondExpr !(HsExpr GhcPs) !Bool !(HsExpr GhcPs) !Bool !(HsExpr GhcPs)
- | PsErrSemiColonsInCondCmd !(HsExpr GhcPs) !Bool !(HsCmd GhcPs) !Bool !(HsCmd GhcPs)
- | PsErrAtInPatPos
- | PsErrCaseCmdInFunAppCmd !(LHsCmd GhcPs)
- | PsErrLambdaCmdInFunAppCmd !HsLamVariant !(LHsCmd GhcPs)
- | PsErrIfCmdInFunAppCmd !(LHsCmd GhcPs)
- | PsErrLetCmdInFunAppCmd !(LHsCmd GhcPs)
- | PsErrDoCmdInFunAppCmd !(LHsCmd GhcPs)
- | PsErrDoInFunAppExpr !(Maybe ModuleName) !(LHsExpr GhcPs)
- | PsErrMDoInFunAppExpr !(Maybe ModuleName) !(LHsExpr GhcPs)
- | PsErrCaseInFunAppExpr !(LHsExpr GhcPs)
- | PsErrLambdaInFunAppExpr !HsLamVariant !(LHsExpr GhcPs)
- | PsErrLetInFunAppExpr !(LHsExpr GhcPs)
- | PsErrIfInFunAppExpr !(LHsExpr GhcPs)
- | PsErrProcInFunAppExpr !(LHsExpr GhcPs)
- | PsErrMalformedTyOrClDecl !(LHsType GhcPs)
- | PsErrIllegalWhereInDataDecl
- | PsErrIllegalDataTypeContext !(LHsContext GhcPs)
- | PsErrParseErrorOnInput !OccName
- | PsErrMalformedDecl !SDoc !RdrName
- | PsErrNotADataCon !RdrName
- | PsErrRecordSyntaxInPatSynDecl !(LPat GhcPs)
- | PsErrEmptyWhereInPatSynDecl !RdrName
- | PsErrInvalidWhereBindInPatSynDecl !RdrName !(HsDecl GhcPs)
- | PsErrNoSingleWhereBindInPatSynDecl !RdrName !(HsDecl GhcPs)
- | PsErrDeclSpliceNotAtTopLevel !(SpliceDecl GhcPs)
- | PsErrInferredTypeVarNotAllowed
- | PsErrMultipleNamesInStandaloneKindSignature [LIdP GhcPs]
- | PsErrIllegalImportBundleForm
- | PsErrIllegalRoleName !FastString [Role]
- | PsErrInvalidTypeSignature !PsInvalidTypeSignature !(LHsExpr GhcPs)
- | PsErrUnexpectedTypeInDecl !(LHsType GhcPs) !SDoc !RdrName [LHsTypeArg GhcPs] !SDoc
- | PsErrExpectedHyphen
- | PsErrSpaceInSCC
- | PsErrEmptyDoubleQuotes !Bool
- | PsErrInvalidPackageName !FastString
- | PsErrInvalidRuleActivationMarker
- | PsErrLinearFunction
- | PsErrMultiWayIf
- | PsErrExplicitForall !Bool
- | PsErrIllegalQualifiedDo !SDoc
- | PsErrCmmParser !CmmParserError
- | PsErrIllegalTraditionalRecordSyntax !SDoc
- | PsErrParseErrorInCmd !SDoc
- | PsErrInPat !(PatBuilder GhcPs) !PsErrInPatDetails
- | PsErrParseRightOpSectionInPat !RdrName !(PatBuilder GhcPs)
- | PsErrIllegalGadtRecordMultiplicity !(HsArrow GhcPs)
- | PsErrInvalidCApiImport
- | PsErrMultipleConForNewtype !RdrName !Int
- | PsErrUnicodeCharLooksLike Char Char String
- | PsErrInvalidPun !PsErrPunDetails
- | PsErrIllegalOrPat (LPat GhcPs)
- | PsErrTypeSyntaxInPat !PsErrTypeSyntaxDetails
- data PsErrParseDetails = PsErrParseDetails {}
- data PsInvalidTypeSignature
- data PatIsRecursive
- data PatIncompleteDoBlock
- data ParseContext = ParseContext {}
- data PsErrInPatDetails
- data PsErrPunDetails
- data PsErrTypeSyntaxDetails
- = PETS_FunctionArrow !(LocatedA (PatBuilder GhcPs)) !(HsArrowOf (LocatedA (PatBuilder GhcPs)) GhcPs) !(LocatedA (PatBuilder GhcPs))
- | PETS_Multiplicity !(EpToken "%") !(LocatedA (PatBuilder GhcPs))
- | PETS_ForallTelescope !(HsForAllTelescope GhcPs) !(LocatedA (PatBuilder GhcPs))
- | PETS_ConstraintContext !(LocatedA (PatBuilder GhcPs))
- noParseContext :: ParseContext
- incompleteDoBlock :: ParseContext
- fromParseContext :: ParseContext -> PsErrInPatDetails
- data NumUnderscoreReason
- data LexErrKind
- data LexErr
- data CmmParserError
- data TransLayoutReason
- data FileHeaderPragmaType
Documentation
data PsHeaderMessage Source #
PsErrParseLanguagePragma | |
PsErrUnsupportedExt !String ![String] | |
PsErrParseOptionsPragma !String | |
PsErrUnknownOptionsPragma !String | PsErrUnsupportedOptionsPragma is an error that occurs when an unknown OPTIONS_GHC pragma is supplied is found. Example(s): {-# OPTIONS_GHC foo #-} Test case(s): testssafeHaskellflags/SafeFlags28 testssafeHaskellflags/SafeFlags19 testssafeHaskellflags/SafeFlags29 testsparsershould_fail/T19923c testsparsershould_fail/T19923b testsparsershould_fail/readFail044 testsdriverT2499 |
Instances
PsUnknownMessage (UnknownDiagnostic (DiagnosticOpts PsMessage)) | An "unknown" message from the parser. This type constructor allows arbitrary messages to be embedded. The typical use case would be GHC plugins willing to emit custom diagnostics. |
PsHeaderMessage !PsHeaderMessage | A group of parser messages emitted in |
PsWarnBidirectionalFormatChars (NonEmpty (PsLoc, Char, String)) | PsWarnBidirectionalFormatChars is a warning (controlled by the -Wwarn-bidirectional-format-characters flag) that occurs when unicode bi-directional format characters are found within in a file The |
PsWarnTab | PsWarnTab is a warning (controlled by the -Wwarn-tabs flag) that occurs when tabulations (tabs) are found within a file. Test case(s): parsershould_failT12610 parsershould_compileT9723b parsershould_compileT9723a parsershould_compileread043 parsershould_failT16270 warningsshould_compileT9230 |
| |
PsWarnTransitionalLayout !TransLayoutReason | PsWarnTransitionalLayout is a warning (controlled by the -Walternative-layout-rule-transitional flag) that occurs when pipes ('|') or 'where' are at the same depth of an implicit layout block. Example(s): f :: IO () f | True = do let x = () y = () return () | True = return () Test case(s): layout/layout006 layout/layout003 layout/layout001 |
PsWarnUnrecognisedPragma !String ![String] | Unrecognised pragma. First field is the actual pragma name which might be empty. Second field is the set of valid candidate pragmas. |
PsWarnMisplacedPragma !FileHeaderPragmaType | |
PsWarnHaddockInvalidPos | Invalid Haddock comment position |
PsWarnHaddockIgnoreMulti | Multiple Haddock comment for the same entity |
PsWarnStarBinder | Found binding occurrence of "*" while StarIsType is enabled |
PsWarnStarIsType | Using "*" for Type without StarIsType enabled |
PsWarnImportPreQualified | Pre qualified import with |
PsWarnOperatorWhitespaceExtConflict !OperatorWhitespaceSymbol | |
PsWarnOperatorWhitespace !FastString !OperatorWhitespaceOccurrence | |
PsWarnViewPatternSignatures !(LPat GhcPs) !(LPat GhcPs) | PsWarnViewPatternSignatures is a warning triggered by view patterns whose RHS is an unparenthesised pattern signature. It warns on code that is highly likely to break when the precedence of view patterns relative to pattern signatures is changed per GHC Proposal #281. The suggested fix is to add parentheses. Example: f1 (isJust -> True :: Bool) = () Suggested fix: f1 (isJust -> (True :: Bool)) = () Test cases: T24159_viewpat |
PsErrLambdaCase | LambdaCase syntax used without the extension enabled |
PsErrEmptyLambda | A lambda requires at least one parameter |
PsErrNumUnderscores !NumUnderscoreReason | Underscores in literals without the extension enabled |
PsErrPrimStringInvalidChar | Invalid character in primitive string |
PsErrMissingBlock | Missing block |
PsErrLexer !LexErr !LexErrKind | Lexer error |
PsErrSuffixAT | Suffix occurrence of |
PsErrParse !String !PsErrParseDetails | Parse errors |
PsErrCmmLexer | Cmm lexer error |
PsErrUnsupportedBoxedSumExpr !(SumOrTuple (HsExpr GhcPs)) | Unsupported boxed sum in expression |
PsErrUnsupportedBoxedSumPat !(SumOrTuple (PatBuilder GhcPs)) | Unsupported boxed sum in pattern |
PsErrUnexpectedQualifiedConstructor !RdrName | Unexpected qualified constructor |
PsErrTupleSectionInPat | Tuple section in pattern context |
PsErrIllegalBangPattern !(Pat GhcPs) | Bang-pattern without BangPattterns enabled |
PsErrOpFewArgs !StarIsType !RdrName | Operator applied to too few arguments |
PsErrImportQualifiedTwice | Import: multiple occurrences of |
PsErrImportPostQualified | Post qualified import without |
PsErrIllegalExplicitNamespace | Explicit namespace keyword without |
PsErrVarForTyCon !RdrName | Expecting a type constructor but found a variable |
PsErrIllegalPatSynExport | Illegal export form allowed by PatternSynonyms |
PsErrMalformedEntityString | Malformed entity string |
PsErrDotsInRecordUpdate | Dots used in record update |
PsErrPrecedenceOutOfRange !Int | Precedence out of range |
PsErrOverloadedRecordDotInvalid | Invalid use of record dot syntax |
PsErrOverloadedRecordUpdateNotEnabled |
|
PsErrOverloadedRecordUpdateNoQualifiedFields | Can't use qualified fields when OverloadedRecordUpdate is enabled. |
PsErrInvalidDataCon !(HsType GhcPs) | Cannot parse data constructor in a data/newtype declaration |
PsErrInvalidInfixDataCon !(HsType GhcPs) !RdrName !(HsType GhcPs) | Cannot parse data constructor in a data/newtype declaration |
PsErrIllegalPromotionQuoteDataCon !RdrName | Illegal DataKinds quote mark in data/newtype constructor declaration |
PsErrUnpackDataCon | UNPACK applied to a data constructor |
PsErrUnexpectedKindAppInDataCon !DataConBuilder !(HsType GhcPs) | Unexpected kind application in data/newtype declaration |
PsErrInvalidRecordCon !(PatBuilder GhcPs) | Not a record constructor |
PsErrIllegalUnboxedStringInPat !(HsLit GhcPs) | Illegal unboxed string literal in pattern |
PsErrIllegalUnboxedFloatingLitInPat !(HsLit GhcPs) | Illegal primitive floating point literal in pattern |
PsErrDoNotationInPat | Do-notation in pattern |
PsErrIfThenElseInPat | If-then-else syntax in pattern |
PsErrLambdaInPat HsLamVariant | Lambda or Lambda-case in pattern |
PsErrCaseInPat | case..of in pattern |
PsErrLetInPat | let-syntax in pattern |
PsErrArrowExprInPat !(HsExpr GhcPs) | Arrow expression-syntax in pattern |
PsErrArrowCmdInPat !(HsCmd GhcPs) | Arrow command-syntax in pattern |
PsErrArrowCmdInExpr !(HsCmd GhcPs) | Arrow command-syntax in expression |
PsErrOrPatInExpr !(LPat GhcPs) | Or-pattern in expression |
PsErrTypeAppWithoutSpace !RdrName !(LHsExpr GhcPs) | Type-application without space before |
PsErrLazyPatWithoutSpace !(LHsExpr GhcPs) | Lazy-pattern ( |
PsErrBangPatWithoutSpace !(LHsExpr GhcPs) | Bang-pattern ( |
PsErrUnallowedPragma !(HsPragE GhcPs) | Pragma not allowed in this position |
PsErrQualifiedDoInCmd !ModuleName | Qualified do block in command |
PsErrInvalidInfixHole | Invalid infix hole, expected an infix operator |
PsErrSemiColonsInCondExpr | Unexpected semi-colons in conditional expression |
PsErrSemiColonsInCondCmd | Unexpected semi-colons in conditional command |
PsErrAtInPatPos | @-operator in a pattern position |
PsErrCaseCmdInFunAppCmd !(LHsCmd GhcPs) | Unexpected case command in function application |
PsErrLambdaCmdInFunAppCmd !HsLamVariant !(LHsCmd GhcPs) | Unexpected lambda or case(s) command in function application |
PsErrIfCmdInFunAppCmd !(LHsCmd GhcPs) | Unexpected if command in function application |
PsErrLetCmdInFunAppCmd !(LHsCmd GhcPs) | Unexpected let command in function application |
PsErrDoCmdInFunAppCmd !(LHsCmd GhcPs) | Unexpected do command in function application |
PsErrDoInFunAppExpr !(Maybe ModuleName) !(LHsExpr GhcPs) | Unexpected do block in function application |
PsErrMDoInFunAppExpr !(Maybe ModuleName) !(LHsExpr GhcPs) | Unexpected mdo block in function application |
PsErrCaseInFunAppExpr !(LHsExpr GhcPs) | Unexpected case expression in function application |
PsErrLambdaInFunAppExpr !HsLamVariant !(LHsExpr GhcPs) | Unexpected lambda or case(s) expression in function application |
PsErrLetInFunAppExpr !(LHsExpr GhcPs) | Unexpected let expression in function application |
PsErrIfInFunAppExpr !(LHsExpr GhcPs) | Unexpected if expression in function application |
PsErrProcInFunAppExpr !(LHsExpr GhcPs) | Unexpected proc expression in function application |
PsErrMalformedTyOrClDecl !(LHsType GhcPs) | Malformed head of type or class declaration |
PsErrIllegalWhereInDataDecl | Illegal 'where' keyword in data declaration |
PsErrIllegalDataTypeContext !(LHsContext GhcPs) | Illegal datatype context |
PsErrParseErrorOnInput !OccName | Parse error on input |
PsErrMalformedDecl !SDoc !RdrName | Malformed ... declaration for ... |
PsErrNotADataCon !RdrName | Not a data constructor |
PsErrRecordSyntaxInPatSynDecl !(LPat GhcPs) | Record syntax used in pattern synonym declaration |
PsErrEmptyWhereInPatSynDecl !RdrName | Empty 'where' clause in pattern-synonym declaration |
PsErrInvalidWhereBindInPatSynDecl !RdrName !(HsDecl GhcPs) | Invalid binding name in 'where' clause of pattern-synonym declaration |
PsErrNoSingleWhereBindInPatSynDecl !RdrName !(HsDecl GhcPs) | Multiple bindings in 'where' clause of pattern-synonym declaration |
PsErrDeclSpliceNotAtTopLevel !(SpliceDecl GhcPs) | Declaration splice not a top-level |
PsErrInferredTypeVarNotAllowed | Inferred type variables not allowed here |
PsErrMultipleNamesInStandaloneKindSignature [LIdP GhcPs] | Multiple names in standalone kind signatures |
PsErrIllegalImportBundleForm | Illegal import bundle form |
PsErrIllegalRoleName !FastString [Role] | Illegal role name |
PsErrInvalidTypeSignature !PsInvalidTypeSignature !(LHsExpr GhcPs) | Invalid type signature |
PsErrUnexpectedTypeInDecl !(LHsType GhcPs) !SDoc !RdrName [LHsTypeArg GhcPs] !SDoc | Unexpected type in declaration |
PsErrExpectedHyphen | Expected a hyphen |
PsErrSpaceInSCC | Found a space in a SCC |
PsErrEmptyDoubleQuotes | Found two single quotes |
| |
PsErrInvalidPackageName !FastString | Invalid package name |
PsErrInvalidRuleActivationMarker | Invalid rule activation marker |
PsErrLinearFunction | Linear function found but LinearTypes not enabled |
PsErrMultiWayIf | Multi-way if-expression found but MultiWayIf not enabled |
PsErrExplicitForall | Explicit forall found but no extension allowing it is enabled |
| |
PsErrIllegalQualifiedDo !SDoc | Found qualified-do without QualifiedDo enabled |
PsErrCmmParser !CmmParserError | Cmm parser error |
PsErrIllegalTraditionalRecordSyntax !SDoc | Illegal traditional record syntax TODO: distinguish errors without using SDoc |
PsErrParseErrorInCmd !SDoc | Parse error in command TODO: distinguish errors without using SDoc |
PsErrInPat !(PatBuilder GhcPs) !PsErrInPatDetails | Parse error in pattern |
PsErrParseRightOpSectionInPat !RdrName !(PatBuilder GhcPs) | Parse error in right operator section pattern TODO: embed the proper operator, if possible |
PsErrIllegalGadtRecordMultiplicity !(HsArrow GhcPs) | Illegal linear arrow or multiplicity annotation in GADT record syntax |
PsErrInvalidCApiImport | |
PsErrMultipleConForNewtype !RdrName !Int | |
PsErrUnicodeCharLooksLike | |
PsErrInvalidPun !PsErrPunDetails | |
PsErrIllegalOrPat (LPat GhcPs) | Or pattern used without -XOrPatterns |
PsErrTypeSyntaxInPat !PsErrTypeSyntaxDetails | Temporary error until GHC gains support for type syntax in patterns. Test cases: T24159_pat_parse_error_1 T24159_pat_parse_error_2 T24159_pat_parse_error_3 T24159_pat_parse_error_4 T24159_pat_parse_error_5 T24159_pat_parse_error_6 |
Instances
Diagnostic PsMessage Source # | |||||
Defined in GHC.Parser.Errors.Ppr
| |||||
Generic PsMessage Source # | |||||
Defined in GHC.Parser.Errors.Types
| |||||
type DiagnosticOpts PsMessage Source # | |||||
Defined in GHC.Parser.Errors.Ppr | |||||
type Rep PsMessage Source # | |||||
Defined in GHC.Parser.Errors.Types type Rep PsMessage = D1 ('MetaData "PsMessage" "GHC.Parser.Errors.Types" "ghc-9.13-inplace" 'False) ((((((C1 ('MetaCons "PsUnknownMessage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UnknownDiagnostic (DiagnosticOpts PsMessage)))) :+: (C1 ('MetaCons "PsHeaderMessage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PsHeaderMessage)) :+: C1 ('MetaCons "PsWarnBidirectionalFormatChars" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (PsLoc, Char, String)))))) :+: ((C1 ('MetaCons "PsWarnTab" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word)) :+: C1 ('MetaCons "PsWarnTransitionalLayout" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TransLayoutReason))) :+: (C1 ('MetaCons "PsWarnUnrecognisedPragma" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [String])) :+: C1 ('MetaCons "PsWarnMisplacedPragma" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FileHeaderPragmaType))))) :+: ((C1 ('MetaCons "PsWarnHaddockInvalidPos" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PsWarnHaddockIgnoreMulti" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsWarnStarBinder" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PsWarnStarIsType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsWarnImportPreQualified" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PsWarnOperatorWhitespaceExtConflict" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OperatorWhitespaceSymbol)) :+: C1 ('MetaCons "PsWarnOperatorWhitespace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FastString) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OperatorWhitespaceOccurrence)))))) :+: (((C1 ('MetaCons "PsWarnViewPatternSignatures" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LPat GhcPs)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LPat GhcPs))) :+: (C1 ('MetaCons "PsErrLambdaCase" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrEmptyLambda" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PsErrNumUnderscores" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NumUnderscoreReason)) :+: C1 ('MetaCons "PsErrPrimStringInvalidChar" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PsErrMissingBlock" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrLexer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LexErr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LexErrKind))))) :+: (((C1 ('MetaCons "PsErrSuffixAT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrParse" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PsErrParseDetails))) :+: (C1 ('MetaCons "PsErrCmmLexer" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrUnsupportedBoxedSumExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SumOrTuple (HsExpr GhcPs)))))) :+: ((C1 ('MetaCons "PsErrUnsupportedBoxedSumPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SumOrTuple (PatBuilder GhcPs)))) :+: C1 ('MetaCons "PsErrUnexpectedQualifiedConstructor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName))) :+: (C1 ('MetaCons "PsErrTupleSectionInPat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrIllegalBangPattern" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Pat GhcPs)))))))) :+: ((((C1 ('MetaCons "PsErrOpFewArgs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StarIsType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName)) :+: (C1 ('MetaCons "PsErrImportQualifiedTwice" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrImportPostQualified" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PsErrIllegalExplicitNamespace" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrVarForTyCon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName))) :+: (C1 ('MetaCons "PsErrIllegalPatSynExport" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrMalformedEntityString" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PsErrDotsInRecordUpdate" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PsErrPrecedenceOutOfRange" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "PsErrOverloadedRecordDotInvalid" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PsErrOverloadedRecordUpdateNotEnabled" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrOverloadedRecordUpdateNoQualifiedFields" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PsErrInvalidDataCon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsType GhcPs))) :+: C1 ('MetaCons "PsErrInvalidInfixDataCon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsType GhcPs)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsType GhcPs)))))))) :+: (((C1 ('MetaCons "PsErrIllegalPromotionQuoteDataCon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName)) :+: (C1 ('MetaCons "PsErrUnpackDataCon" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrUnexpectedKindAppInDataCon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DataConBuilder) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsType GhcPs))))) :+: ((C1 ('MetaCons "PsErrInvalidRecordCon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PatBuilder GhcPs))) :+: C1 ('MetaCons "PsErrIllegalUnboxedStringInPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsLit GhcPs)))) :+: (C1 ('MetaCons "PsErrIllegalUnboxedFloatingLitInPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsLit GhcPs))) :+: C1 ('MetaCons "PsErrDoNotationInPat" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "PsErrIfThenElseInPat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrLambdaInPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HsLamVariant))) :+: (C1 ('MetaCons "PsErrCaseInPat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrLetInPat" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PsErrArrowExprInPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsExpr GhcPs))) :+: C1 ('MetaCons "PsErrArrowCmdInPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsCmd GhcPs)))) :+: (C1 ('MetaCons "PsErrArrowCmdInExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsCmd GhcPs))) :+: C1 ('MetaCons "PsErrOrPatInExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LPat GhcPs))))))))) :+: (((((C1 ('MetaCons "PsErrTypeAppWithoutSpace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs))) :+: (C1 ('MetaCons "PsErrLazyPatWithoutSpace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs))) :+: C1 ('MetaCons "PsErrBangPatWithoutSpace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs))))) :+: ((C1 ('MetaCons "PsErrUnallowedPragma" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsPragE GhcPs))) :+: C1 ('MetaCons "PsErrQualifiedDoInCmd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ModuleName))) :+: (C1 ('MetaCons "PsErrInvalidInfixHole" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrSemiColonsInCondExpr" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsExpr GhcPs)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsExpr GhcPs)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsExpr GhcPs)))))))) :+: ((C1 ('MetaCons "PsErrSemiColonsInCondCmd" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsExpr GhcPs)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsCmd GhcPs)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsCmd GhcPs))))) :+: (C1 ('MetaCons "PsErrAtInPatPos" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrCaseCmdInFunAppCmd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsCmd GhcPs))))) :+: ((C1 ('MetaCons "PsErrLambdaCmdInFunAppCmd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HsLamVariant) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsCmd GhcPs))) :+: C1 ('MetaCons "PsErrIfCmdInFunAppCmd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsCmd GhcPs)))) :+: (C1 ('MetaCons "PsErrLetCmdInFunAppCmd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsCmd GhcPs))) :+: C1 ('MetaCons "PsErrDoCmdInFunAppCmd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsCmd GhcPs))))))) :+: (((C1 ('MetaCons "PsErrDoInFunAppExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ModuleName)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs))) :+: (C1 ('MetaCons "PsErrMDoInFunAppExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ModuleName)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs))) :+: C1 ('MetaCons "PsErrCaseInFunAppExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs))))) :+: ((C1 ('MetaCons "PsErrLambdaInFunAppExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HsLamVariant) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs))) :+: C1 ('MetaCons "PsErrLetInFunAppExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs)))) :+: (C1 ('MetaCons "PsErrIfInFunAppExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs))) :+: C1 ('MetaCons "PsErrProcInFunAppExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs)))))) :+: (((C1 ('MetaCons "PsErrMalformedTyOrClDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsType GhcPs))) :+: C1 ('MetaCons "PsErrIllegalWhereInDataDecl" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PsErrIllegalDataTypeContext" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsContext GhcPs))) :+: C1 ('MetaCons "PsErrParseErrorOnInput" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OccName)))) :+: ((C1 ('MetaCons "PsErrMalformedDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SDoc) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName)) :+: C1 ('MetaCons "PsErrNotADataCon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName))) :+: (C1 ('MetaCons "PsErrRecordSyntaxInPatSynDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LPat GhcPs))) :+: C1 ('MetaCons "PsErrEmptyWhereInPatSynDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName))))))) :+: ((((C1 ('MetaCons "PsErrInvalidWhereBindInPatSynDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsDecl GhcPs))) :+: (C1 ('MetaCons "PsErrNoSingleWhereBindInPatSynDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsDecl GhcPs))) :+: C1 ('MetaCons "PsErrDeclSpliceNotAtTopLevel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SpliceDecl GhcPs))))) :+: ((C1 ('MetaCons "PsErrInferredTypeVarNotAllowed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrMultipleNamesInStandaloneKindSignature" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [LIdP GhcPs]))) :+: (C1 ('MetaCons "PsErrIllegalImportBundleForm" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrIllegalRoleName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FastString) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Role]))))) :+: (((C1 ('MetaCons "PsErrInvalidTypeSignature" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PsInvalidTypeSignature) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsExpr GhcPs))) :+: C1 ('MetaCons "PsErrUnexpectedTypeInDecl" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LHsType GhcPs)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SDoc)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [LHsTypeArg GhcPs]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SDoc))))) :+: (C1 ('MetaCons "PsErrExpectedHyphen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrSpaceInSCC" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PsErrEmptyDoubleQuotes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "PsErrInvalidPackageName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FastString))) :+: (C1 ('MetaCons "PsErrInvalidRuleActivationMarker" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrLinearFunction" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "PsErrMultiWayIf" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PsErrExplicitForall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "PsErrIllegalQualifiedDo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SDoc)))) :+: ((C1 ('MetaCons "PsErrCmmParser" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CmmParserError)) :+: C1 ('MetaCons "PsErrIllegalTraditionalRecordSyntax" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SDoc))) :+: (C1 ('MetaCons "PsErrParseErrorInCmd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SDoc)) :+: C1 ('MetaCons "PsErrInPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PatBuilder GhcPs)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PsErrInPatDetails))))) :+: (((C1 ('MetaCons "PsErrParseRightOpSectionInPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PatBuilder GhcPs))) :+: C1 ('MetaCons "PsErrIllegalGadtRecordMultiplicity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HsArrow GhcPs)))) :+: (C1 ('MetaCons "PsErrInvalidCApiImport" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PsErrMultipleConForNewtype" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RdrName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)))) :+: ((C1 ('MetaCons "PsErrUnicodeCharLooksLike" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: C1 ('MetaCons "PsErrInvalidPun" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PsErrPunDetails))) :+: (C1 ('MetaCons "PsErrIllegalOrPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LPat GhcPs))) :+: C1 ('MetaCons "PsErrTypeSyntaxInPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PsErrTypeSyntaxDetails))))))))) |
data PsErrParseDetails Source #
Extra details about a parse error, which helps us in determining which should be the hints to suggest.
PsErrParseDetails | |
|
data PatIncompleteDoBlock Source #
Instances
Eq PatIncompleteDoBlock Source # | |
Defined in GHC.Parser.Errors.Types (==) :: PatIncompleteDoBlock -> PatIncompleteDoBlock -> Bool # (/=) :: PatIncompleteDoBlock -> PatIncompleteDoBlock -> Bool # |
data ParseContext Source #
Extra information for the expression GHC is currently inspecting/parsing. It can be used to generate more informative parser diagnostics and hints.
ParseContext | |
|
Instances
Eq ParseContext Source # | |
Defined in GHC.Parser.Errors.Types (==) :: ParseContext -> ParseContext -> Bool # (/=) :: ParseContext -> ParseContext -> Bool # |
data PsErrInPatDetails Source #
PEIP_NegApp | Negative application pattern? |
PEIP_TypeArgs [HsConPatTyArg GhcPs] | The list of type arguments for the pattern |
PEIP_RecPattern | |
| |
PEIP_OtherPatDetails !ParseContext |
data PsErrTypeSyntaxDetails Source #
PETS_FunctionArrow !(LocatedA (PatBuilder GhcPs)) !(HsArrowOf (LocatedA (PatBuilder GhcPs)) GhcPs) !(LocatedA (PatBuilder GhcPs)) | |
PETS_Multiplicity !(EpToken "%") !(LocatedA (PatBuilder GhcPs)) | |
PETS_ForallTelescope !(HsForAllTelescope GhcPs) !(LocatedA (PatBuilder GhcPs)) | |
PETS_ConstraintContext !(LocatedA (PatBuilder GhcPs)) |
fromParseContext :: ParseContext -> PsErrInPatDetails Source #
Builds a PsErrInPatDetails
with the information provided by the ParseContext
.
data NumUnderscoreReason Source #
Instances
Show NumUnderscoreReason Source # | |
Defined in GHC.Parser.Errors.Types showsPrec :: Int -> NumUnderscoreReason -> ShowS # show :: NumUnderscoreReason -> String # showList :: [NumUnderscoreReason] -> ShowS # | |
Eq NumUnderscoreReason Source # | |
Defined in GHC.Parser.Errors.Types (==) :: NumUnderscoreReason -> NumUnderscoreReason -> Bool # (/=) :: NumUnderscoreReason -> NumUnderscoreReason -> Bool # | |
Ord NumUnderscoreReason Source # | |
Defined in GHC.Parser.Errors.Types compare :: NumUnderscoreReason -> NumUnderscoreReason -> Ordering # (<) :: NumUnderscoreReason -> NumUnderscoreReason -> Bool # (<=) :: NumUnderscoreReason -> NumUnderscoreReason -> Bool # (>) :: NumUnderscoreReason -> NumUnderscoreReason -> Bool # (>=) :: NumUnderscoreReason -> NumUnderscoreReason -> Bool # max :: NumUnderscoreReason -> NumUnderscoreReason -> NumUnderscoreReason # min :: NumUnderscoreReason -> NumUnderscoreReason -> NumUnderscoreReason # |
data LexErrKind Source #
LexErrKind_EOF | End of input |
LexErrKind_UTF8 | UTF-8 decoding error |
LexErrKind_Char !Char | Error at given character |
Instances
Show LexErrKind Source # | |
Defined in GHC.Parser.Errors.Types showsPrec :: Int -> LexErrKind -> ShowS # show :: LexErrKind -> String # showList :: [LexErrKind] -> ShowS # | |
Eq LexErrKind Source # | |
Defined in GHC.Parser.Errors.Types (==) :: LexErrKind -> LexErrKind -> Bool # (/=) :: LexErrKind -> LexErrKind -> Bool # | |
Ord LexErrKind Source # | |
Defined in GHC.Parser.Errors.Types compare :: LexErrKind -> LexErrKind -> Ordering # (<) :: LexErrKind -> LexErrKind -> Bool # (<=) :: LexErrKind -> LexErrKind -> Bool # (>) :: LexErrKind -> LexErrKind -> Bool # (>=) :: LexErrKind -> LexErrKind -> Bool # max :: LexErrKind -> LexErrKind -> LexErrKind # min :: LexErrKind -> LexErrKind -> LexErrKind # |
LexError | Lexical error |
LexUnknownPragma | Unknown pragma |
LexErrorInPragma | Lexical error in pragma |
LexNumEscapeRange | Numeric escape sequence out of range |
LexUnterminatedComment | Unterminated `{-' |
LexUnterminatedOptions | Unterminated OPTIONS pragma |
LexUnterminatedQQ | Unterminated quasiquotation |
data CmmParserError Source #
Errors from the Cmm parser
CmmUnknownPrimitive !FastString | Unknown Cmm primitive |
CmmUnknownMacro !FastString | Unknown macro |
CmmUnknownCConv !String | Unknown calling convention |
CmmUnrecognisedSafety !String | Unrecognised safety |
CmmUnrecognisedHint !String | Unrecognised hint |
data TransLayoutReason Source #
TransLayout_Where | "`where' clause at the same depth as implicit layout block" |
TransLayout_Pipe | "`|' at the same depth as implicit layout block") |