Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Token
- = ITas
- | ITcase
- | ITclass
- | ITdata
- | ITdefault
- | ITderiving
- | ITdo (Maybe FastString)
- | ITelse
- | IThiding
- | ITforeign
- | ITif
- | ITimport
- | ITin
- | ITinfix
- | ITinfixl
- | ITinfixr
- | ITinstance
- | ITlet
- | ITmodule
- | ITnewtype
- | ITof
- | ITqualified
- | ITthen
- | ITtype
- | ITwhere
- | ITforall IsUnicodeSyntax
- | ITexport
- | ITlabel
- | ITdynamic
- | ITsafe
- | ITinterruptible
- | ITunsafe
- | ITstdcallconv
- | ITccallconv
- | ITcapiconv
- | ITprimcallconv
- | ITjavascriptcallconv
- | ITmdo (Maybe FastString)
- | ITfamily
- | ITrole
- | ITgroup
- | ITby
- | ITusing
- | ITpattern
- | ITstatic
- | ITstock
- | ITanyclass
- | ITvia
- | ITunit
- | ITsignature
- | ITdependency
- | ITrequires
- | ITinline_prag SourceText InlineSpec RuleMatchInfo
- | ITopaque_prag SourceText
- | ITspec_prag SourceText
- | ITspec_inline_prag SourceText Bool
- | ITsource_prag SourceText
- | ITrules_prag SourceText
- | ITwarning_prag SourceText
- | ITdeprecated_prag SourceText
- | ITline_prag SourceText
- | ITcolumn_prag SourceText
- | ITscc_prag SourceText
- | ITunpack_prag SourceText
- | ITnounpack_prag SourceText
- | ITann_prag SourceText
- | ITcomplete_prag SourceText
- | ITclose_prag
- | IToptions_prag String
- | ITinclude_prag String
- | ITlanguage_prag
- | ITminimal_prag SourceText
- | IToverlappable_prag SourceText
- | IToverlapping_prag SourceText
- | IToverlaps_prag SourceText
- | ITincoherent_prag SourceText
- | ITctype SourceText
- | ITcomment_line_prag
- | ITdotdot
- | ITcolon
- | ITdcolon IsUnicodeSyntax
- | ITequal
- | ITlam
- | ITlcase
- | ITlcases
- | ITvbar
- | ITlarrow IsUnicodeSyntax
- | ITrarrow IsUnicodeSyntax
- | ITdarrow IsUnicodeSyntax
- | ITlolly
- | ITminus
- | ITprefixminus
- | ITbang
- | ITtilde
- | ITat
- | ITtypeApp
- | ITpercent
- | ITstar IsUnicodeSyntax
- | ITdot
- | ITproj Bool
- | ITbiglam
- | ITocurly
- | ITccurly
- | ITvocurly
- | ITvccurly
- | ITobrack
- | ITopabrack
- | ITcpabrack
- | ITcbrack
- | IToparen
- | ITcparen
- | IToubxparen
- | ITcubxparen
- | ITsemi
- | ITcomma
- | ITunderscore
- | ITbackquote
- | ITsimpleQuote
- | ITvarid FastString
- | ITconid FastString
- | ITvarsym FastString
- | ITconsym FastString
- | ITqvarid (FastString, FastString)
- | ITqconid (FastString, FastString)
- | ITqvarsym (FastString, FastString)
- | ITqconsym (FastString, FastString)
- | ITdupipvarid FastString
- | ITlabelvarid SourceText FastString
- | ITchar SourceText Char
- | ITstring SourceText FastString
- | ITinteger IntegralLit
- | ITrational FractionalLit
- | ITprimchar SourceText Char
- | ITprimstring SourceText ByteString
- | ITprimint SourceText Integer
- | ITprimword SourceText Integer
- | ITprimfloat FractionalLit
- | ITprimdouble FractionalLit
- | ITopenExpQuote HasE IsUnicodeSyntax
- | ITopenPatQuote
- | ITopenDecQuote
- | ITopenTypQuote
- | ITcloseQuote IsUnicodeSyntax
- | ITopenTExpQuote HasE
- | ITcloseTExpQuote
- | ITdollar
- | ITdollardollar
- | ITtyQuote
- | ITquasiQuote (FastString, FastString, PsSpan)
- | ITqQuasiQuote (FastString, FastString, FastString, PsSpan)
- | ITproc
- | ITrec
- | IToparenbar IsUnicodeSyntax
- | ITcparenbar IsUnicodeSyntax
- | ITlarrowtail IsUnicodeSyntax
- | ITrarrowtail IsUnicodeSyntax
- | ITLarrowtail IsUnicodeSyntax
- | ITRarrowtail IsUnicodeSyntax
- | ITunknown String
- | ITeof
- | ITdocComment HsDocString PsSpan
- | ITdocOptions String PsSpan
- | ITlineComment String PsSpan
- | ITblockComment String PsSpan
- lexer :: Bool -> (Located Token -> P a) -> P a
- lexerDbg :: Bool -> (Located Token -> P a) -> P a
- data ParserOpts = ParserOpts {
- pExtsBitmap :: !ExtsBitmap
- pDiagOpts :: !DiagOpts
- pSupportedExts :: [String]
- mkParserOpts :: EnumSet Extension -> DiagOpts -> [String] -> Bool -> Bool -> Bool -> Bool -> ParserOpts
- data PState = PState {
- buffer :: StringBuffer
- options :: ParserOpts
- warnings :: Messages PsMessage
- errors :: Messages PsMessage
- tab_first :: Maybe RealSrcSpan
- tab_count :: !Word
- last_tk :: Maybe (PsLocated Token)
- prev_loc :: PsSpan
- prev_loc2 :: PsSpan
- last_loc :: PsSpan
- last_len :: !Int
- loc :: PsLoc
- context :: [LayoutContext]
- lex_state :: [Int]
- srcfiles :: [FastString]
- alr_pending_implicit_tokens :: [PsLocated Token]
- alr_next_token :: Maybe (PsLocated Token)
- alr_last_loc :: PsSpan
- alr_context :: [ALRContext]
- alr_expecting_ocurly :: Maybe ALRLayout
- alr_justClosedExplicitLetBlock :: Bool
- eof_pos :: Maybe (Pair RealSrcSpan RealSrcSpan)
- header_comments :: Maybe [LEpaComment]
- comment_q :: [LEpaComment]
- hdk_comments :: OrdList (PsLocated HdkComment)
- initParserState :: ParserOpts -> StringBuffer -> RealSrcLoc -> PState
- initPragState :: ParserOpts -> StringBuffer -> RealSrcLoc -> PState
- newtype P a = P {
- unP :: PState -> ParseResult a
- data ParseResult a where
- pattern POk :: PState -> a -> ParseResult a
- pattern PFailed :: PState -> ParseResult a
- allocateComments :: RealSrcSpan -> [LEpaComment] -> ([LEpaComment], [LEpaComment])
- allocatePriorComments :: RealSrcSpan -> [LEpaComment] -> Maybe [LEpaComment] -> (Maybe [LEpaComment], [LEpaComment], [LEpaComment])
- allocateFinalComments :: RealSrcSpan -> [LEpaComment] -> Maybe [LEpaComment] -> (Maybe [LEpaComment], [LEpaComment], [LEpaComment])
- class Monad m => MonadP m where
- addError :: MsgEnvelope PsMessage -> m ()
- addWarning :: MsgEnvelope PsMessage -> m ()
- addFatalError :: MsgEnvelope PsMessage -> m a
- getBit :: ExtBits -> m Bool
- allocateCommentsP :: RealSrcSpan -> m EpAnnComments
- allocatePriorCommentsP :: RealSrcSpan -> m EpAnnComments
- allocateFinalCommentsP :: RealSrcSpan -> m EpAnnComments
- getRealSrcLoc :: P RealSrcLoc
- getPState :: P PState
- failMsgP :: (SrcSpan -> MsgEnvelope PsMessage) -> P a
- failLocMsgP :: RealSrcLoc -> RealSrcLoc -> (SrcSpan -> MsgEnvelope PsMessage) -> P a
- srcParseFail :: P a
- getPsErrorMessages :: PState -> Messages PsMessage
- getPsMessages :: PState -> (Messages PsMessage, Messages PsMessage)
- popContext :: P ()
- pushModuleContext :: P ()
- setLastToken :: PsSpan -> Int -> P ()
- setSrcLoc :: RealSrcLoc -> P ()
- activeContext :: P Bool
- nextIsEOF :: P Bool
- getLexState :: P Int
- popLexState :: P Int
- pushLexState :: Int -> P ()
- data ExtBits
- = FfiBit
- | InterruptibleFfiBit
- | CApiFfiBit
- | ArrowsBit
- | ThBit
- | ThQuotesBit
- | IpBit
- | OverloadedLabelsBit
- | ExplicitForallBit
- | BangPatBit
- | PatternSynonymsBit
- | HaddockBit
- | MagicHashBit
- | RecursiveDoBit
- | QualifiedDoBit
- | UnicodeSyntaxBit
- | UnboxedParensBit
- | DatatypeContextsBit
- | MonadComprehensionsBit
- | TransformComprehensionsBit
- | QqBit
- | RawTokenStreamBit
- | AlternativeLayoutRuleBit
- | ALRTransitionalBit
- | RelaxedLayoutBit
- | NondecreasingIndentationBit
- | SafeHaskellBit
- | TraditionalRecordSyntaxBit
- | ExplicitNamespacesBit
- | LambdaCaseBit
- | BinaryLiteralsBit
- | NegativeLiteralsBit
- | HexFloatLiteralsBit
- | StaticPointersBit
- | NumericUnderscoresBit
- | StarIsTypeBit
- | BlockArgumentsBit
- | NPlusKPatternsBit
- | DoAndIfThenElseBit
- | MultiWayIfBit
- | GadtSyntaxBit
- | ImportQualifiedPostBit
- | LinearTypesBit
- | NoLexicalNegationBit
- | OverloadedRecordDotBit
- | OverloadedRecordUpdateBit
- | InRulePragBit
- | InNestedCommentBit
- | UsePosPragsBit
- xtest :: ExtBits -> ExtsBitmap -> Bool
- xunset :: ExtBits -> ExtsBitmap -> ExtsBitmap
- xset :: ExtBits -> ExtsBitmap -> ExtsBitmap
- disableHaddock :: ParserOpts -> ParserOpts
- lexTokenStream :: ParserOpts -> StringBuffer -> RealSrcLoc -> ParseResult [Located Token]
- mkParensEpAnn :: RealSrcSpan -> (AddEpAnn, AddEpAnn)
- getCommentsFor :: MonadP m => SrcSpan -> m EpAnnComments
- getPriorCommentsFor :: MonadP m => SrcSpan -> m EpAnnComments
- getFinalCommentsFor :: MonadP m => SrcSpan -> m EpAnnComments
- getEofPos :: P (Maybe (Pair RealSrcSpan RealSrcSpan))
- commentToAnnotation :: RealLocated Token -> LEpaComment
- data HdkComment
- warnopt :: WarningFlag -> ParserOpts -> Bool
- adjustChar :: Char -> Word8
- addPsMessage :: SrcSpan -> PsMessage -> P ()
Documentation
data ParserOpts Source #
Parser options.
See mkParserOpts
to construct this.
ParserOpts | |
|
:: EnumSet Extension | permitted language extensions enabled |
-> DiagOpts | diagnostic options |
-> [String] | Supported Languages and Extensions |
-> Bool | are safe imports on? |
-> Bool | keeping Haddock comment tokens |
-> Bool | keep regular comment tokens |
-> Bool | If this is enabled, '{-# LINE ... -#}' and '{-# COLUMN ... #-}' update
the internal position kept by the parser. Otherwise, those pragmas are
lexed as |
-> ParserOpts |
Given exactly the information needed, set up the ParserOpts
PState | |
|
initParserState :: ParserOpts -> StringBuffer -> RealSrcLoc -> PState Source #
Creates a parse state from a ParserOpts
value
initPragState :: ParserOpts -> StringBuffer -> RealSrcLoc -> PState Source #
Set parser options for parsing OPTIONS pragmas
The parsing monad, isomorphic to StateT PState Maybe
.
P | |
|
Instances
Applicative P Source # | |
Functor P Source # | |
Monad P Source # | |
MonadP P Source # | |
Defined in GHC.Parser.Lexer addError :: MsgEnvelope PsMessage -> P () Source # addWarning :: MsgEnvelope PsMessage -> P () Source # addFatalError :: MsgEnvelope PsMessage -> P a Source # getBit :: ExtBits -> P Bool Source # allocateCommentsP :: RealSrcSpan -> P EpAnnComments Source # allocatePriorCommentsP :: RealSrcSpan -> P EpAnnComments Source # allocateFinalCommentsP :: RealSrcSpan -> P EpAnnComments Source # |
data ParseResult a where Source #
The result of running a parser.
pattern POk :: PState -> a -> ParseResult a | The parser has consumed a (possibly empty) prefix of the input and produced
a result. Use The carried parsing state can be used to resume parsing. |
pattern PFailed :: PState -> ParseResult a | The parser has consumed a (possibly empty) prefix of the input and failed. The carried parsing state can be used to resume parsing. It is the state
right before failure, including the fatal parse error. |
allocateComments :: RealSrcSpan -> [LEpaComment] -> ([LEpaComment], [LEpaComment]) Source #
allocatePriorComments :: RealSrcSpan -> [LEpaComment] -> Maybe [LEpaComment] -> (Maybe [LEpaComment], [LEpaComment], [LEpaComment]) Source #
allocateFinalComments :: RealSrcSpan -> [LEpaComment] -> Maybe [LEpaComment] -> (Maybe [LEpaComment], [LEpaComment], [LEpaComment]) Source #
class Monad m => MonadP m where Source #
An mtl-style class for monads that support parsing-related operations. For example, sometimes we make a second pass over the parsing results to validate, disambiguate, or rearrange them, and we do so in the PV monad which cannot consume input but can report parsing errors, check for extension bits, and accumulate parsing annotations. Both P and PV are instances of MonadP.
MonadP grants us convenient overloading. The other option is to have separate operations for each monad: addErrorP vs addErrorPV, getBitP vs getBitPV, and so on.
addError :: MsgEnvelope PsMessage -> m () Source #
Add a non-fatal error. Use this when the parser can produce a result despite the error.
For example, when GHC encounters a forall
in a type,
but -XExplicitForAll
is disabled, the parser constructs ForAllTy
as if -XExplicitForAll
was enabled, adding a non-fatal error to
the accumulator.
Control flow wise, non-fatal errors act like warnings: they are added to the accumulator and parsing continues. This allows GHC to report more than one parse error per file.
addWarning :: MsgEnvelope PsMessage -> m () Source #
Add a warning to the accumulator.
Use getPsMessages
to get the accumulated warnings.
addFatalError :: MsgEnvelope PsMessage -> m a Source #
Add a fatal error. This will be the last error reported by the parser, and
the parser will not produce any result, ending in a PFailed
state.
getBit :: ExtBits -> m Bool Source #
Check if a given flag is currently set in the bitmap.
allocateCommentsP :: RealSrcSpan -> m EpAnnComments Source #
Go through the comment_q
in PState
and remove all comments
that belong within the given span
allocatePriorCommentsP :: RealSrcSpan -> m EpAnnComments Source #
Go through the comment_q
in PState
and remove all comments
that come before or within the given span
allocateFinalCommentsP :: RealSrcSpan -> m EpAnnComments Source #
Go through the comment_q
in PState
and remove all comments
that come after the given span
Instances
MonadP P Source # | |
Defined in GHC.Parser.Lexer addError :: MsgEnvelope PsMessage -> P () Source # addWarning :: MsgEnvelope PsMessage -> P () Source # addFatalError :: MsgEnvelope PsMessage -> P a Source # getBit :: ExtBits -> P Bool Source # allocateCommentsP :: RealSrcSpan -> P EpAnnComments Source # allocatePriorCommentsP :: RealSrcSpan -> P EpAnnComments Source # allocateFinalCommentsP :: RealSrcSpan -> P EpAnnComments Source # | |
MonadP PV Source # | |
Defined in GHC.Parser.PostProcess addError :: MsgEnvelope PsMessage -> PV () Source # addWarning :: MsgEnvelope PsMessage -> PV () Source # addFatalError :: MsgEnvelope PsMessage -> PV a Source # getBit :: ExtBits -> PV Bool Source # allocateCommentsP :: RealSrcSpan -> PV EpAnnComments Source # allocatePriorCommentsP :: RealSrcSpan -> PV EpAnnComments Source # allocateFinalCommentsP :: RealSrcSpan -> PV EpAnnComments Source # |
failLocMsgP :: RealSrcLoc -> RealSrcLoc -> (SrcSpan -> MsgEnvelope PsMessage) -> P a Source #
srcParseFail :: P a Source #
getPsErrorMessages :: PState -> Messages PsMessage Source #
Get a bag of the errors that have been accumulated so far. Does not take -Werror into account.
getPsMessages :: PState -> (Messages PsMessage, Messages PsMessage) Source #
Get the warnings and errors accumulated so far. Does not take -Werror into account.
popContext :: P () Source #
pushModuleContext :: P () Source #
setSrcLoc :: RealSrcLoc -> P () Source #
activeContext :: P Bool Source #
getLexState :: P Int Source #
popLexState :: P Int Source #
pushLexState :: Int -> P () Source #
Various boolean flags, mostly language extensions, that impact lexing and parsing. Note that a handful of these can change during lexing/parsing.
FfiBit | |
InterruptibleFfiBit | |
CApiFfiBit | |
ArrowsBit | |
ThBit | |
ThQuotesBit | |
IpBit | |
OverloadedLabelsBit | |
ExplicitForallBit | |
BangPatBit | |
PatternSynonymsBit | |
HaddockBit | |
MagicHashBit | |
RecursiveDoBit | |
QualifiedDoBit | |
UnicodeSyntaxBit | |
UnboxedParensBit | |
DatatypeContextsBit | |
MonadComprehensionsBit | |
TransformComprehensionsBit | |
QqBit | |
RawTokenStreamBit | |
AlternativeLayoutRuleBit | |
ALRTransitionalBit | |
RelaxedLayoutBit | |
NondecreasingIndentationBit | |
SafeHaskellBit | |
TraditionalRecordSyntaxBit | |
ExplicitNamespacesBit | |
LambdaCaseBit | |
BinaryLiteralsBit | |
NegativeLiteralsBit | |
HexFloatLiteralsBit | |
StaticPointersBit | |
NumericUnderscoresBit | |
StarIsTypeBit | |
BlockArgumentsBit | |
NPlusKPatternsBit | |
DoAndIfThenElseBit | |
MultiWayIfBit | |
GadtSyntaxBit | |
ImportQualifiedPostBit | |
LinearTypesBit | |
NoLexicalNegationBit | |
OverloadedRecordDotBit | |
OverloadedRecordUpdateBit | |
InRulePragBit | |
InNestedCommentBit | |
UsePosPragsBit | If this is enabled, '{-# LINE ... -#}' and '{-# COLUMN ... #-}' update the internal position. Otherwise, those pragmas are lexed as tokens of their own. |
Instances
Enum ExtBits Source # | |
Defined in GHC.Parser.Lexer succ :: ExtBits -> ExtBits Source # pred :: ExtBits -> ExtBits Source # toEnum :: Int -> ExtBits Source # fromEnum :: ExtBits -> Int Source # enumFrom :: ExtBits -> [ExtBits] Source # enumFromThen :: ExtBits -> ExtBits -> [ExtBits] Source # enumFromTo :: ExtBits -> ExtBits -> [ExtBits] Source # enumFromThenTo :: ExtBits -> ExtBits -> ExtBits -> [ExtBits] Source # |
lexTokenStream :: ParserOpts -> StringBuffer -> RealSrcLoc -> ParseResult [Located Token] Source #
mkParensEpAnn :: RealSrcSpan -> (AddEpAnn, AddEpAnn) Source #
Given a RealSrcSpan
that surrounds a HsPar
or HsParTy
, generate
AddEpAnn
values for the opening and closing bordering on the start
and end of the span
getCommentsFor :: MonadP m => SrcSpan -> m EpAnnComments Source #
getPriorCommentsFor :: MonadP m => SrcSpan -> m EpAnnComments Source #
getFinalCommentsFor :: MonadP m => SrcSpan -> m EpAnnComments Source #
getEofPos :: P (Maybe (Pair RealSrcSpan RealSrcSpan)) Source #
data HdkComment Source #
Haddock comment as produced by the lexer. These are accumulated in PState
and then processed in GHC.Parser.PostProcess.Haddock. The location of the
HsDocString
s spans over the contents of the docstring - i.e. it does not
include the decorator ("-- |", "{-|" etc.)
HdkCommentNext HsDocString | |
HdkCommentPrev HsDocString | |
HdkCommentNamed String HsDocString | |
HdkCommentSection Int HsDocString |
Instances
Show HdkComment Source # | |
Defined in GHC.Parser.Lexer |
warnopt :: WarningFlag -> ParserOpts -> Bool Source #
Test whether a WarningFlag
is set
adjustChar :: Char -> Word8 Source #