module GHC.Parser.Errors
( PsWarning(..)
, TransLayoutReason(..)
, OperatorWhitespaceSymbol(..)
, OperatorWhitespaceOccurrence(..)
, NumUnderscoreReason(..)
, PsError(..)
, PsErrorDesc(..)
, LexErr(..)
, CmmParserError(..)
, LexErrKind(..)
, Hint(..)
, StarIsType (..)
)
where
import GHC.Prelude
import GHC.Types.SrcLoc
import GHC.Types.Name.Reader (RdrName)
import GHC.Types.Name.Occurrence (OccName)
import GHC.Parser.Types
import Language.Haskell.Syntax.Extension
import GHC.Hs.Extension
import GHC.Hs.Expr
import GHC.Hs.Pat
import GHC.Hs.Type
import GHC.Hs.Lit
import GHC.Hs.Decls
import GHC.Core.Coercion.Axiom (Role)
import GHC.Utils.Outputable (SDoc)
import GHC.Data.FastString
import GHC.Unit.Module.Name
data PsWarning
= PsWarnTab
{ tabFirst :: !SrcSpan
, tabCount :: !Word
}
| PsWarnTransitionalLayout !SrcSpan !TransLayoutReason
| PsWarnUnrecognisedPragma !SrcSpan
| PsWarnHaddockInvalidPos !SrcSpan
| PsWarnHaddockIgnoreMulti !SrcSpan
| PsWarnStarBinder !SrcSpan
| PsWarnStarIsType !SrcSpan
| PsWarnImportPreQualified !SrcSpan
| PsWarnOperatorWhitespaceExtConflict !SrcSpan !OperatorWhitespaceSymbol
| PsWarnOperatorWhitespace !SrcSpan !FastString !OperatorWhitespaceOccurrence
data OperatorWhitespaceSymbol
= OperatorWhitespaceSymbol_PrefixPercent
| OperatorWhitespaceSymbol_PrefixDollar
| OperatorWhitespaceSymbol_PrefixDollarDollar
data OperatorWhitespaceOccurrence
= OperatorWhitespaceOccurrence_Prefix
| OperatorWhitespaceOccurrence_Suffix
| OperatorWhitespaceOccurrence_TightInfix
data TransLayoutReason
= TransLayout_Where
| TransLayout_Pipe
data PsError = PsError
{ errDesc :: !PsErrorDesc
, errHints :: ![Hint]
, errLoc :: !SrcSpan
}
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
newtype StarIsType = StarIsType Bool
data NumUnderscoreReason
= NumUnderscore_Integral
| NumUnderscore_Float
deriving (Show,Eq,Ord)
data Hint
= SuggestTH
| SuggestRecursiveDo
| SuggestDo
| SuggestMissingDo
| SuggestLetInDo
| SuggestPatternSynonyms
| SuggestInfixBindMaybeAtPat !RdrName
| TypeApplicationsInPatternsOnlyDataCons
data LexErrKind
= LexErrKind_EOF
| LexErrKind_UTF8
| LexErrKind_Char !Char
deriving (Show,Eq,Ord)
data LexErr
= LexError
| LexUnknownPragma
| LexErrorInPragma
| LexNumEscapeRange
| LexStringCharLit
| LexStringCharLitEOF
| LexUnterminatedComment
| LexUnterminatedOptions
| LexUnterminatedQQ
data CmmParserError
= CmmUnknownPrimitive !FastString
| CmmUnknownMacro !FastString
| CmmUnknownCConv !String
| CmmUnrecognisedSafety !String
| CmmUnrecognisedHint !String