ghc-7.10.2: The GHC API

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 
ITexport 
ITlabel 
ITdynamic 
ITsafe 
ITinterruptible 
ITunsafe 
ITstdcallconv 
ITccallconv 
ITcapiconv 
ITprimcallconv 
ITjavascriptcallconv 
ITmdo 
ITfamily 
ITrole 
ITgroup 
ITby 
ITusing 
ITpattern 
ITstatic 
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 
ITscc_prag SourceText 
ITgenerated_prag SourceText 
ITcore_prag SourceText 
ITunpack_prag SourceText 
ITnounpack_prag SourceText 
ITann_prag SourceText 
ITclose_prag 
IToptions_prag String 
ITinclude_prag String 
ITlanguage_prag 
ITvect_prag SourceText 
ITvect_scalar_prag SourceText 
ITnovect_prag SourceText 
ITminimal_prag SourceText 
IToverlappable_prag SourceText 
IToverlapping_prag SourceText 
IToverlaps_prag SourceText 
ITincoherent_prag SourceText 
ITctype SourceText 
ITdotdot 
ITcolon 
ITdcolon 
ITequal 
ITlam 
ITlcase 
ITvbar 
ITlarrow 
ITrarrow 
ITat 
ITtilde 
ITtildehsh 
ITdarrow 
ITminus 
ITbang 
ITstar 
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) 
ITprefixqvarsym (FastString, FastString) 
ITprefixqconsym (FastString, FastString) 
ITdupipvarid FastString 
ITchar SourceText Char 
ITstring SourceText FastString 
ITinteger SourceText Integer 
ITrational FractionalLit 
ITprimchar SourceText Char 
ITprimstring SourceText ByteString 
ITprimint SourceText Integer 
ITprimword SourceText Integer 
ITprimfloat FractionalLit 
ITprimdouble FractionalLit 
ITopenExpQuote 
ITopenPatQuote 
ITopenDecQuote 
ITopenTypQuote 
ITcloseQuote 
ITopenTExpQuote 
ITcloseTExpQuote 
ITidEscape FastString 
ITparenEscape 
ITidTyEscape FastString 
ITparenTyEscape 
ITtyQuote 
ITquasiQuote (FastString, FastString, RealSrcSpan) 
ITqQuasiQuote (FastString, FastString, FastString, RealSrcSpan) 
ITproc 
ITrec 
IToparenbar 
ITcparenbar 
ITlarrowtail 
ITrarrowtail 
ITLarrowtail 
ITRarrowtail 
ITunknown String 
ITeof 
ITdocCommentNext String 
ITdocCommentPrev String 
ITdocCommentNamed String 
ITdocSection Int String 
ITdocOptions String 
ITdocOptionsOld String 
ITlineComment String 
ITblockComment String 

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

newtype P a Source

Constructors

P 

Fields

unP :: PState -> ParseResult a
 

extension :: (ExtsBitmap -> Bool) -> P Bool Source

bangPatEnabled :: ExtsBitmap -> Bool Source

inRulePrag :: ExtsBitmap -> Bool Source

sccProfilingOn :: ExtsBitmap -> Bool Source

hpcEnabled :: ExtsBitmap -> Bool Source

type AddAnn = SrcSpan -> P () Source

Encapsulated call to addAnnotation, requiring only the SrcSpan of the AST element the annotation belongs to

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