ghc-9.2.5: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Parser.Lexer

Synopsis

Documentation

data Token Source #

Constructors

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 
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 
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 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

Used when the lexer can't make sense of it

ITeof

end of file token

ITdocCommentNext String PsSpan

something beginning -- |

ITdocCommentPrev String PsSpan

something beginning -- ^

ITdocCommentNamed String PsSpan

something beginning -- $

ITdocSection Int String PsSpan

a section heading

ITdocOptions String PsSpan

doc options (prune, ignore-exports, etc)

ITlineComment String PsSpan

comment starting by "--"

ITblockComment String PsSpan

comment in {- -}

Instances

Instances details
Show Token Source # 
Instance details

Defined in GHC.Parser.Lexer

Outputable Token Source # 
Instance details

Defined in GHC.Parser.Lexer

Methods

ppr :: Token -> SDoc Source #

lexer :: Bool -> (Located Token -> P a) -> P a Source #

lexerDbg :: Bool -> (Located Token -> P a) -> P a Source #

data ParserOpts Source #

Parser options.

See mkParserOpts to construct this.

Constructors

ParserOpts 

Fields

mkParserOpts Source #

Arguments

:: EnumSet WarningFlag

warnings flags enabled

-> EnumSet Extension

permitted language extensions enabled

-> 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 ITline_prag and ITcolumn_prag tokens.

-> ParserOpts 

Given exactly the information needed, set up the ParserOpts

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

newtype P a Source #

The parsing monad, isomorphic to StateT PState Maybe.

Constructors

P 

Fields

Instances

Instances details
Applicative P Source # 
Instance details

Defined in GHC.Parser.Lexer

Methods

pure :: a -> P a Source #

(<*>) :: P (a -> b) -> P a -> P b Source #

liftA2 :: (a -> b -> c) -> P a -> P b -> P c Source #

(*>) :: P a -> P b -> P b Source #

(<*) :: P a -> P b -> P a Source #

Functor P Source # 
Instance details

Defined in GHC.Parser.Lexer

Methods

fmap :: (a -> b) -> P a -> P b Source #

(<$) :: a -> P b -> P a Source #

Monad P Source # 
Instance details

Defined in GHC.Parser.Lexer

Methods

(>>=) :: P a -> (a -> P b) -> P b Source #

(>>) :: P a -> P b -> P b Source #

return :: a -> P a Source #

MonadP P Source # 
Instance details

Defined in GHC.Parser.Lexer

data ParseResult a Source #

The result of running a parser.

Constructors

POk

The parser has consumed a (possibly empty) prefix of the input and produced a result. Use getMessages to check for accumulated warnings and non-fatal errors.

Fields

  • PState

    The resulting parsing state. Can be used to resume parsing.

  • a

    The resulting value.

PFailed

The parser has consumed a (possibly empty) prefix of the input and failed.

Fields

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.

Methods

addError :: PsError -> 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 :: WarningFlag -> PsWarning -> m () Source #

Add a warning to the accumulator. Use getMessages to get the accumulated warnings.

addFatalError :: PsError -> 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

getErrorMessages :: PState -> Bag PsError Source #

Get a bag of the errors that have been accumulated so far. Does not take -Werror into account.

getMessages :: PState -> (Bag PsWarning, Bag PsError) Source #

Get the warnings and errors accumulated so far. Does not take -Werror into account.

data ExtBits Source #

Various boolean flags, mostly language extensions, that impact lexing and parsing. Note that a handful of these can change during lexing/parsing.

xtest :: ExtBits -> ExtsBitmap -> Bool Source #

xunset :: ExtBits -> ExtsBitmap -> ExtsBitmap Source #

xset :: ExtBits -> ExtsBitmap -> ExtsBitmap Source #

mkParensEpAnn :: RealSrcSpan -> (AddEpAnn, AddEpAnn) Source #

Given a SrcSpan that surrounds a HsPar or HsParTy, generate AddEpAnn values for the opening and closing bordering on the start and end of the span

data HdkComment Source #

Haddock comment as produced by the lexer. These are accumulated in PState and then processed in GHC.Parser.PostProcess.Haddock.

Instances

Instances details
Show HdkComment Source # 
Instance details

Defined in GHC.Parser.Lexer

warnopt :: WarningFlag -> ParserOpts -> Bool Source #

Test whether a WarningFlag is set