{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeFamilies #-}
module GHC.Parser.Errors.Types where
import GHC.Prelude
import GHC.Core.TyCon (Role)
import GHC.Data.FastString
import GHC.Hs
import GHC.Parser.Types
import GHC.Parser.Errors.Basic
import GHC.Types.Error
import GHC.Types.Hint
import GHC.Types.Name.Occurrence (OccName)
import GHC.Types.Name.Reader
import Data.List.NonEmpty (NonEmpty)
import GHC.Types.SrcLoc (PsLoc)
import GHC.Generics ( Generic )
type PsWarning = PsMessage
type PsError = PsMessage
data
= PsErrParseLanguagePragma
| PsErrUnsupportedExt !String ![String]
| PsErrParseOptionsPragma !String
| PsErrUnknownOptionsPragma !String
deriving forall x. Rep PsHeaderMessage x -> PsHeaderMessage
forall x. PsHeaderMessage -> Rep PsHeaderMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PsHeaderMessage x -> PsHeaderMessage
$cfrom :: forall x. PsHeaderMessage -> Rep PsHeaderMessage x
Generic
data PsMessage
=
PsUnknownMessage UnknownDiagnostic
| !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
| 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
| PsErrLambdaCaseInPat LamCaseVariant
| 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)
| PsErrLambdaCaseCmdInFunAppCmd !LamCaseVariant !(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 !LamCaseVariant !(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
| PsErrInPat !(PatBuilder GhcPs) !PsErrInPatDetails
| PsErrParseRightOpSectionInPat !RdrName !(PatBuilder GhcPs)
| PsErrIllegalGadtRecordMultiplicity !(HsArrow GhcPs)
| PsErrInvalidCApiImport
| PsErrMultipleConForNewtype !RdrName !Int
| PsErrUnicodeCharLooksLike
Char
Char
String
deriving forall x. Rep PsMessage x -> PsMessage
forall x. PsMessage -> Rep PsMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PsMessage x -> PsMessage
$cfrom :: forall x. PsMessage -> Rep PsMessage x
Generic
data PsErrParseDetails
= PsErrParseDetails
{ PsErrParseDetails -> Bool
ped_th_enabled :: !Bool
, PsErrParseDetails -> Bool
ped_do_in_last_100 :: !Bool
, PsErrParseDetails -> Bool
ped_mdo_in_last_100 :: !Bool
, PsErrParseDetails -> Bool
ped_pat_syn_enabled :: !Bool
, PsErrParseDetails -> Bool
ped_pattern_parsed :: !Bool
}
data PatIsRecursive
= YesPatIsRecursive
| NoPatIsRecursive
data PatIncompleteDoBlock
= YesIncompleteDoBlock
| NoIncompleteDoBlock
deriving PatIncompleteDoBlock -> PatIncompleteDoBlock -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PatIncompleteDoBlock -> PatIncompleteDoBlock -> Bool
$c/= :: PatIncompleteDoBlock -> PatIncompleteDoBlock -> Bool
== :: PatIncompleteDoBlock -> PatIncompleteDoBlock -> Bool
$c== :: PatIncompleteDoBlock -> PatIncompleteDoBlock -> Bool
Eq
data ParseContext
= ParseContext
{ ParseContext -> Maybe RdrName
is_infix :: !(Maybe RdrName)
, ParseContext -> PatIncompleteDoBlock
incomplete_do_block :: !PatIncompleteDoBlock
} deriving ParseContext -> ParseContext -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParseContext -> ParseContext -> Bool
$c/= :: ParseContext -> ParseContext -> Bool
== :: ParseContext -> ParseContext -> Bool
$c== :: ParseContext -> ParseContext -> Bool
Eq
data PsErrInPatDetails
= PEIP_NegApp
| PEIP_TypeArgs [HsConPatTyArg GhcPs]
| PEIP_RecPattern [LPat GhcPs]
!PatIsRecursive
!ParseContext
| PEIP_OtherPatDetails !ParseContext
noParseContext :: ParseContext
noParseContext :: ParseContext
noParseContext = Maybe RdrName -> PatIncompleteDoBlock -> ParseContext
ParseContext forall a. Maybe a
Nothing PatIncompleteDoBlock
NoIncompleteDoBlock
incompleteDoBlock :: ParseContext
incompleteDoBlock :: ParseContext
incompleteDoBlock = Maybe RdrName -> PatIncompleteDoBlock -> ParseContext
ParseContext forall a. Maybe a
Nothing PatIncompleteDoBlock
YesIncompleteDoBlock
fromParseContext :: ParseContext -> PsErrInPatDetails
fromParseContext :: ParseContext -> PsErrInPatDetails
fromParseContext = ParseContext -> PsErrInPatDetails
PEIP_OtherPatDetails
data NumUnderscoreReason
= NumUnderscore_Integral
| NumUnderscore_Float
deriving (Int -> NumUnderscoreReason -> ShowS
[NumUnderscoreReason] -> ShowS
NumUnderscoreReason -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NumUnderscoreReason] -> ShowS
$cshowList :: [NumUnderscoreReason] -> ShowS
show :: NumUnderscoreReason -> String
$cshow :: NumUnderscoreReason -> String
showsPrec :: Int -> NumUnderscoreReason -> ShowS
$cshowsPrec :: Int -> NumUnderscoreReason -> ShowS
Show,NumUnderscoreReason -> NumUnderscoreReason -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NumUnderscoreReason -> NumUnderscoreReason -> Bool
$c/= :: NumUnderscoreReason -> NumUnderscoreReason -> Bool
== :: NumUnderscoreReason -> NumUnderscoreReason -> Bool
$c== :: NumUnderscoreReason -> NumUnderscoreReason -> Bool
Eq,Eq NumUnderscoreReason
NumUnderscoreReason -> NumUnderscoreReason -> Bool
NumUnderscoreReason -> NumUnderscoreReason -> Ordering
NumUnderscoreReason -> NumUnderscoreReason -> NumUnderscoreReason
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NumUnderscoreReason -> NumUnderscoreReason -> NumUnderscoreReason
$cmin :: NumUnderscoreReason -> NumUnderscoreReason -> NumUnderscoreReason
max :: NumUnderscoreReason -> NumUnderscoreReason -> NumUnderscoreReason
$cmax :: NumUnderscoreReason -> NumUnderscoreReason -> NumUnderscoreReason
>= :: NumUnderscoreReason -> NumUnderscoreReason -> Bool
$c>= :: NumUnderscoreReason -> NumUnderscoreReason -> Bool
> :: NumUnderscoreReason -> NumUnderscoreReason -> Bool
$c> :: NumUnderscoreReason -> NumUnderscoreReason -> Bool
<= :: NumUnderscoreReason -> NumUnderscoreReason -> Bool
$c<= :: NumUnderscoreReason -> NumUnderscoreReason -> Bool
< :: NumUnderscoreReason -> NumUnderscoreReason -> Bool
$c< :: NumUnderscoreReason -> NumUnderscoreReason -> Bool
compare :: NumUnderscoreReason -> NumUnderscoreReason -> Ordering
$ccompare :: NumUnderscoreReason -> NumUnderscoreReason -> Ordering
Ord)
data LexErrKind
= LexErrKind_EOF
| LexErrKind_UTF8
| LexErrKind_Char !Char
deriving (Int -> LexErrKind -> ShowS
[LexErrKind] -> ShowS
LexErrKind -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LexErrKind] -> ShowS
$cshowList :: [LexErrKind] -> ShowS
show :: LexErrKind -> String
$cshow :: LexErrKind -> String
showsPrec :: Int -> LexErrKind -> ShowS
$cshowsPrec :: Int -> LexErrKind -> ShowS
Show,LexErrKind -> LexErrKind -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LexErrKind -> LexErrKind -> Bool
$c/= :: LexErrKind -> LexErrKind -> Bool
== :: LexErrKind -> LexErrKind -> Bool
$c== :: LexErrKind -> LexErrKind -> Bool
Eq,Eq LexErrKind
LexErrKind -> LexErrKind -> Bool
LexErrKind -> LexErrKind -> Ordering
LexErrKind -> LexErrKind -> LexErrKind
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LexErrKind -> LexErrKind -> LexErrKind
$cmin :: LexErrKind -> LexErrKind -> LexErrKind
max :: LexErrKind -> LexErrKind -> LexErrKind
$cmax :: LexErrKind -> LexErrKind -> LexErrKind
>= :: LexErrKind -> LexErrKind -> Bool
$c>= :: LexErrKind -> LexErrKind -> Bool
> :: LexErrKind -> LexErrKind -> Bool
$c> :: LexErrKind -> LexErrKind -> Bool
<= :: LexErrKind -> LexErrKind -> Bool
$c<= :: LexErrKind -> LexErrKind -> Bool
< :: LexErrKind -> LexErrKind -> Bool
$c< :: LexErrKind -> LexErrKind -> Bool
compare :: LexErrKind -> LexErrKind -> Ordering
$ccompare :: LexErrKind -> LexErrKind -> Ordering
Ord)
data LexErr
= LexError
| LexUnknownPragma
| LexErrorInPragma
| LexNumEscapeRange
| LexStringCharLit
| LexStringCharLitEOF
|
| LexUnterminatedOptions
| LexUnterminatedQQ
data CmmParserError
= CmmUnknownPrimitive !FastString
| CmmUnknownMacro !FastString
| CmmUnknownCConv !String
| CmmUnrecognisedSafety !String
| CmmUnrecognisedHint !String
data TransLayoutReason
= TransLayout_Where
| TransLayout_Pipe
data
= OptionsPrag
| IncludePrag
| LanguagePrag
| DocOptionsPrag