ghc-6.12.2: The GHC APISource codeContentsIndex
Lexer
Documentation
data Token Source
Constructors
ITas
ITcase
ITclass
ITdata
ITdefault
ITderiving
ITdo
ITelse
IThiding
ITif
ITimport
ITin
ITinfix
ITinfixl
ITinfixr
ITinstance
ITlet
ITmodule
ITnewtype
ITof
ITqualified
ITthen
ITtype
ITwhere
ITscc
ITforall
ITforeign
ITexport
ITlabel
ITdynamic
ITsafe
ITthreadsafe
ITunsafe
ITstdcallconv
ITccallconv
ITprimcallconv
ITmdo
ITfamily
ITgroup
ITby
ITusing
ITinline_prag Bool
ITinline_conlike_prag Bool
ITspec_prag
ITspec_inline_prag Bool
ITsource_prag
ITrules_prag
ITwarning_prag
ITdeprecated_prag
ITline_prag
ITscc_prag
ITgenerated_prag
ITcore_prag
ITunpack_prag
ITann_prag
ITclose_prag
IToptions_prag String
ITinclude_prag String
ITlanguage_prag
ITdotdot
ITcolon
ITdcolon
ITequal
ITlam
ITvbar
ITlarrow
ITrarrow
ITat
ITtilde
ITdarrow
ITminus
ITbang
ITstar
ITdot
ITbiglam
ITocurly
ITccurly
ITocurlybar
ITccurlybar
ITvocurly}, for type applications
ITvccurly
ITobrack
ITopabrack
ITcpabrack
ITcbrack
IToparen
ITcparen
IToubxparen
ITcubxparen
ITsemi
ITcomma
ITunderscore
ITbackquote
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 Char
ITstring FastString
ITinteger Integer
ITrational Rational
ITprimchar Char
ITprimstring FastString
ITprimint Integer
ITprimword Integer
ITprimfloat Rational
ITprimdouble Rational
ITopenExpQuote
ITopenPatQuote
ITopenDecQuote
ITopenTypQuote
ITcloseQuote
ITidEscape FastString
ITparenEscape
ITvarQuote
ITtyQuote
ITquasiQuote (FastString, FastString, SrcSpan)
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 :: (Located Token -> P a) -> P aSource
pragState :: DynFlags -> StringBuffer -> SrcLoc -> PStateSource
mkPState :: StringBuffer -> SrcLoc -> DynFlags -> PStateSource
data PState Source
Constructors
PState
buffer :: StringBuffer
dflags :: DynFlags
messages :: Messages
last_loc :: SrcSpan
last_offs :: !Int
last_len :: !Int
last_line_len :: !Int
loc :: SrcLoc
extsBitmap :: !Int
context :: [LayoutContext]
lex_state :: [Int]
newtype P a Source
Constructors
P
unP :: PState -> ParseResult a
show/hide Instances
data ParseResult a Source
Constructors
POk PState a
PFailed SrcSpan Message
getSrcLoc :: P SrcLocSource
getPState :: P PStateSource
failLocMsgP :: SrcLoc -> SrcLoc -> String -> P aSource
failSpanMsgP :: SrcSpan -> SDoc -> P aSource
srcParseFail :: P aSource
getMessages :: PState -> MessagesSource
popContext :: P ()Source
pushCurrentContext :: P ()Source
setLastToken :: SrcSpan -> Int -> Int -> P ()Source
setSrcLoc :: SrcLoc -> P ()Source
getLexState :: P IntSource
popLexState :: P IntSource
pushLexState :: Int -> P ()Source
extension :: (Int -> Bool) -> P BoolSource
standaloneDerivingEnabled :: Int -> BoolSource
bangPatEnabled :: Int -> BoolSource
addWarning :: DynFlag -> SrcSpan -> SDoc -> P ()Source
lexTokenStream :: StringBuffer -> SrcLoc -> DynFlags -> ParseResult [Located Token]Source
Produced by Haddock version 2.6.1