| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Parser.Errors
Synopsis
- data PsWarning- = PsWarnTab { }
- | PsWarnTransitionalLayout !SrcSpan !TransLayoutReason
- | PsWarnUnrecognisedPragma !SrcSpan
- | PsWarnHaddockInvalidPos !SrcSpan
- | PsWarnHaddockIgnoreMulti !SrcSpan
- | PsWarnStarBinder !SrcSpan
- | PsWarnStarIsType !SrcSpan
- | PsWarnImportPreQualified !SrcSpan
- | PsWarnOperatorWhitespaceExtConflict !SrcSpan !OperatorWhitespaceSymbol
- | PsWarnOperatorWhitespace !SrcSpan !FastString !OperatorWhitespaceOccurrence
 
- data TransLayoutReason
- data OperatorWhitespaceSymbol
- data OperatorWhitespaceOccurrence
- data NumUnderscoreReason
- data PsError = PsError {}
- data PsErrorDesc- = PsErrLambdaCase
- | PsErrNumUnderscores !NumUnderscoreReason
- | PsErrPrimStringInvalidChar
- | PsErrMissingBlock
- | PsErrLexer !LexErr !LexErrKind
- | PsErrSuffixAT
- | PsErrParse !String
- | 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)
- | PsErrUnpackDataCon
- | PsErrUnexpectedKindAppInDataCon !DataConBuilder !(HsType GhcPs)
- | PsErrInvalidRecordCon !(PatBuilder GhcPs)
- | PsErrIllegalUnboxedStringInPat !(HsLit GhcPs)
- | PsErrDoNotationInPat
- | PsErrIfTheElseInPat
- | PsErrLambdaCaseInPat
- | PsErrCaseInPat
- | PsErrLetInPat
- | PsErrLambdaInPat
- | PsErrArrowExprInPat !(HsExpr GhcPs)
- | PsErrArrowCmdInPat !(HsCmd GhcPs)
- | PsErrArrowCmdInExpr !(HsCmd GhcPs)
- | PsErrViewPatInExpr !(LHsExpr GhcPs) !(LHsExpr 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
- | PsErrLambdaCmdInFunAppCmd !(LHsCmd GhcPs)
- | PsErrCaseCmdInFunAppCmd !(LHsCmd GhcPs)
- | PsErrIfCmdInFunAppCmd !(LHsCmd GhcPs)
- | PsErrLetCmdInFunAppCmd !(LHsCmd GhcPs)
- | PsErrDoCmdInFunAppCmd !(LHsCmd GhcPs)
- | PsErrDoInFunAppExpr !(Maybe ModuleName) !(LHsExpr GhcPs)
- | PsErrMDoInFunAppExpr !(Maybe ModuleName) !(LHsExpr GhcPs)
- | PsErrLambdaInFunAppExpr !(LHsExpr GhcPs)
- | PsErrCaseInFunAppExpr !(LHsExpr GhcPs)
- | PsErrLambdaCaseInFunAppExpr !(LHsExpr GhcPs)
- | PsErrLetInFunAppExpr !(LHsExpr GhcPs)
- | PsErrIfInFunAppExpr !(LHsExpr GhcPs)
- | PsErrProcInFunAppExpr !(LHsExpr GhcPs)
- | PsErrMalformedTyOrClDecl !(LHsType GhcPs)
- | PsErrIllegalWhereInDataDecl
- | PsErrIllegalDataTypeContext !(LHsContext GhcPs)
- | PsErrParseErrorOnInput !OccName
- | PsErrMalformedDecl !SDoc !RdrName
- | PsErrUnexpectedTypeAppInDecl !(LHsType GhcPs) !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 !(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
- | PsErrParseErrorInPat !SDoc
 
- data LexErr
- data CmmParserError
- data LexErrKind
- data Hint
- newtype StarIsType = StarIsType Bool
Documentation
A warning that might arise during parsing.
Constructors
| PsWarnTab | Warn when tabulations are found | 
| PsWarnTransitionalLayout !SrcSpan !TransLayoutReason | Transitional layout warnings | 
| PsWarnUnrecognisedPragma !SrcSpan | Unrecognised pragma | 
| PsWarnHaddockInvalidPos !SrcSpan | Invalid Haddock comment position | 
| PsWarnHaddockIgnoreMulti !SrcSpan | Multiple Haddock comment for the same entity | 
| PsWarnStarBinder !SrcSpan | Found binding occurrence of "*" while StarIsType is enabled | 
| PsWarnStarIsType !SrcSpan | Using "*" for Type without StarIsType enabled | 
| PsWarnImportPreQualified !SrcSpan | Pre qualified import with  | 
| PsWarnOperatorWhitespaceExtConflict !SrcSpan !OperatorWhitespaceSymbol | |
| PsWarnOperatorWhitespace !SrcSpan !FastString !OperatorWhitespaceOccurrence | |
data TransLayoutReason Source #
Constructors
| TransLayout_Where | "`where' clause at the same depth as implicit layout block" | 
| TransLayout_Pipe | "`|' at the same depth as implicit layout block") | 
data OperatorWhitespaceSymbol Source #
The operator symbol in the WarnOperatorWhitespaceExtConflict warning.
data OperatorWhitespaceOccurrence Source #
The operator occurrence type in the WarnOperatorWhitespace warning.
data NumUnderscoreReason Source #
Constructors
| NumUnderscore_Integral | |
| NumUnderscore_Float | 
Instances
| Eq NumUnderscoreReason Source # | |
| Defined in GHC.Parser.Errors Methods (==) :: NumUnderscoreReason -> NumUnderscoreReason -> Bool # (/=) :: NumUnderscoreReason -> NumUnderscoreReason -> Bool # | |
| Ord NumUnderscoreReason Source # | |
| Defined in GHC.Parser.Errors Methods compare :: NumUnderscoreReason -> NumUnderscoreReason -> Ordering # (<) :: NumUnderscoreReason -> NumUnderscoreReason -> Bool # (<=) :: NumUnderscoreReason -> NumUnderscoreReason -> Bool # (>) :: NumUnderscoreReason -> NumUnderscoreReason -> Bool # (>=) :: NumUnderscoreReason -> NumUnderscoreReason -> Bool # max :: NumUnderscoreReason -> NumUnderscoreReason -> NumUnderscoreReason # min :: NumUnderscoreReason -> NumUnderscoreReason -> NumUnderscoreReason # | |
| Show NumUnderscoreReason Source # | |
| Defined in GHC.Parser.Errors Methods showsPrec :: Int -> NumUnderscoreReason -> ShowS # show :: NumUnderscoreReason -> String # showList :: [NumUnderscoreReason] -> ShowS # | |
data PsErrorDesc Source #
Constructors
| PsErrLambdaCase | LambdaCase syntax used without the extension enabled | 
| 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 | 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 | 
| 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 | 
| PsErrDoNotationInPat | Do-notation in pattern | 
| PsErrIfTheElseInPat | If-then-else syntax in pattern | 
| PsErrLambdaCaseInPat | Lambda-case in pattern | 
| PsErrCaseInPat | case..of in pattern | 
| PsErrLetInPat | let-syntax in pattern | 
| PsErrLambdaInPat | Lambda-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 | 
| PsErrViewPatInExpr !(LHsExpr GhcPs) !(LHsExpr GhcPs) | View-pattern in expression | 
| PsErrTypeAppWithoutSpace !RdrName !(LHsExpr GhcPs) | Type-application without space before '@' | 
| PsErrLazyPatWithoutSpace !(LHsExpr GhcPs) | Lazy-pattern ('~') without space after it | 
| 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 | 
| PsErrLambdaCmdInFunAppCmd !(LHsCmd GhcPs) | Unexpected lambda command in function application | 
| PsErrCaseCmdInFunAppCmd !(LHsCmd GhcPs) | Unexpected case 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 | 
| PsErrLambdaInFunAppExpr !(LHsExpr GhcPs) | Unexpected lambda expression in function application | 
| PsErrCaseInFunAppExpr !(LHsExpr GhcPs) | Unexpected case expression in function application | 
| PsErrLambdaCaseInFunAppExpr !(LHsExpr GhcPs) | Unexpected lambda-case 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 datatyp context | 
| PsErrParseErrorOnInput !OccName | Parse error on input | 
| PsErrMalformedDecl !SDoc !RdrName | Malformed ... declaration for ... | 
| PsErrUnexpectedTypeAppInDecl !(LHsType GhcPs) !SDoc !RdrName | Unexpected type application in a declaration | 
| 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 !(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 !Bool | 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 !Bool | 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 | 
| PsErrParseErrorInPat !SDoc | Parse error in pattern TODO: distinguish errors without using SDoc | 
Constructors
| LexError | Lexical error | 
| LexUnknownPragma | Unknown pragma | 
| LexErrorInPragma | Lexical error in pragma | 
| LexNumEscapeRange | Numeric escape sequence out of range | 
| LexStringCharLit | Llexical error in string/character literal | 
| LexStringCharLitEOF | Unexpected end-of-file in string/character literal | 
| LexUnterminatedComment | Unterminated `{-' | 
| LexUnterminatedOptions | Unterminated OPTIONS pragma | 
| LexUnterminatedQQ | Unterminated quasiquotation | 
data CmmParserError Source #
Errors from the Cmm parser
Constructors
| CmmUnknownPrimitive !FastString | Unknown Cmm primitive | 
| CmmUnknownMacro !FastString | Unknown macro | 
| CmmUnknownCConv !String | Unknown calling convention | 
| CmmUnrecognisedSafety !String | Unrecognised safety | 
| CmmUnrecognisedHint !String | Unrecognised hint | 
data LexErrKind Source #
Constructors
| LexErrKind_EOF | End of input | 
| LexErrKind_UTF8 | UTF-8 decoding error | 
| LexErrKind_Char !Char | Error at given character | 
Instances
| Eq LexErrKind Source # | |
| Defined in GHC.Parser.Errors | |
| Ord LexErrKind Source # | |
| Defined in GHC.Parser.Errors Methods compare :: LexErrKind -> LexErrKind -> Ordering # (<) :: LexErrKind -> LexErrKind -> Bool # (<=) :: LexErrKind -> LexErrKind -> Bool # (>) :: LexErrKind -> LexErrKind -> Bool # (>=) :: LexErrKind -> LexErrKind -> Bool # max :: LexErrKind -> LexErrKind -> LexErrKind # min :: LexErrKind -> LexErrKind -> LexErrKind # | |
| Show LexErrKind Source # | |
| Defined in GHC.Parser.Errors Methods showsPrec :: Int -> LexErrKind -> ShowS # show :: LexErrKind -> String # showList :: [LexErrKind] -> ShowS # | |
Constructors
| SuggestTH | |
| SuggestRecursiveDo | |
| SuggestDo | |
| SuggestMissingDo | |
| SuggestLetInDo | |
| SuggestPatternSynonyms | |
| SuggestInfixBindMaybeAtPat !RdrName | |
| TypeApplicationsInPatternsOnlyDataCons | Type applications in patterns are only allowed on data constructors | 
newtype StarIsType Source #
Constructors
| StarIsType Bool |