ghc-lib-parser-0.20190909: The GHC API, decoupled from GHC versions

Safe HaskellNone
LanguageHaskell2010

Lexer

Synopsis

Documentation

data Token Source #

Constructors

ITas 
ITcase 
ITclass 
ITdata 
ITdefault 
ITderiving 
ITdo 
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 
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 
ITgenerated_prag SourceText 
ITcore_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 
ITat 
ITtilde 
ITdarrow IsUnicodeSyntax 
ITminus 
ITbang 
ITstar IsUnicodeSyntax 
ITdot 
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 
ITidEscape FastString 
ITparenEscape 
ITidTyEscape FastString 
ITparenTyEscape 
ITtyQuote 
ITquasiQuote (FastString, FastString, RealSrcSpan) 
ITqQuasiQuote (FastString, FastString, FastString, RealSrcSpan) 
ITproc 
ITrec 
IToparenbar IsUnicodeSyntax
(|
ITcparenbar IsUnicodeSyntax
|)
ITlarrowtail IsUnicodeSyntax
-<
ITrarrowtail IsUnicodeSyntax
>-
ITLarrowtail IsUnicodeSyntax
-<<
ITRarrowtail IsUnicodeSyntax
>>-
ITtypeApp

Type application '@' (lexed differently than as-pattern '@', due to checking for preceding whitespace)

ITunknown String

Used when the lexer can't make sense of it

ITeof

end of file token

ITdocCommentNext String

something beginning -- |

ITdocCommentPrev String

something beginning -- ^

ITdocCommentNamed String

something beginning -- $

ITdocSection Int String

a section heading

ITdocOptions String

doc options (prune, ignore-exports, etc)

ITlineComment String

comment starting by "--"

ITblockComment String

comment in {- -}

Instances
Show Token Source # 
Instance details

Defined in Lexer

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Outputable Token Source # 
Instance details

Defined in Lexer

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

mkPState :: DynFlags -> StringBuffer -> RealSrcLoc -> PState Source #

Creates a parse state from a DynFlags value

mkPStatePure :: ParserFlags -> StringBuffer -> RealSrcLoc -> PState Source #

Creates a parse state from a ParserFlags value

newtype P a Source #

The parsing monad, isomorphic to StateT PState Maybe.

Constructors

P 

Fields

Instances
Monad P Source # 
Instance details

Defined in Lexer

Methods

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

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

return :: a -> P a #

fail :: String -> P a #

Functor P Source # 
Instance details

Defined in Lexer

Methods

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

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

MonadFail P Source # 
Instance details

Defined in Lexer

Methods

fail :: String -> P a #

Applicative P Source # 
Instance details

Defined in Lexer

Methods

pure :: a -> P a #

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

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

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

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

MonadP P Source # 
Instance details

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

mkParserFlags :: DynFlags -> ParserFlags Source #

Extracts the flag information needed for parsing

mkParserFlags' Source #

Arguments

:: EnumSet WarningFlag

warnings flags enabled

-> EnumSet Extension

permitted language extensions enabled

-> UnitId

key of package currently being compiled

-> Bool

are safe imports on?

-> Bool

keeping Haddock comment tokens

-> Bool

keep regular comment tokens

-> Bool

If this is enabled, '{-}' and '{--}' update the internal position kept by the parser. Otherwise, those pragmas are lexed as ITline_prag and ITcolumn_prag tokens.

-> ParserFlags 

Given exactly the information needed, set up the ParserFlags

data ParserFlags Source #

The subset of the DynFlags used by the parser. See mkParserFlags or mkParserFlags' for ways to construct this.

Constructors

ParserFlags 

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 :: SrcSpan -> SDoc -> 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 -> SrcSpan -> SDoc -> m () Source #

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

addFatalError :: SrcSpan -> SDoc -> 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.

addAnnotation :: SrcSpan -> AnnKeywordId -> SrcSpan -> m () Source #

Given a location and a list of AddAnn, apply them all to the location.

Instances
MonadP P Source # 
Instance details

Defined in Lexer

MonadP PV Source # 
Instance details

Defined in RdrHsSyn

getErrorMessages :: PState -> DynFlags -> ErrorMessages Source #

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

getMessages :: PState -> DynFlags -> Messages Source #

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

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

data AddAnn Source #

Encapsulated call to addAnnotation, requiring only the SrcSpan of the AST construct the annotation belongs to; together with the AnnKeywordId, this is the key of the annotation map.

This type is useful for places in the parser where it is not yet known what SrcSpan an annotation should be added to. The most common situation is when we are parsing a list: the annotations need to be associated with the AST element that *contains* the list, not the list itself. AddAnn lets us defer adding the annotations until we finish parsing the list and are now parsing the enclosing element; we then apply the AddAnn to associate the annotations. Another common situation is where a common fragment of the AST has been factored out but there is no separate AST node for this fragment (this occurs in class and data declarations). In this case, the annotation belongs to the parent data declaration.

The usual way an AddAnn is created is using the mj ("make jump") function, and then it can be discharged using the ams function.

mkParensApiAnn :: SrcSpan -> [AddAnn] Source #

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

addAnnsAt :: MonadP m => SrcSpan -> [AddAnn] -> m () Source #