Maintainer | mainland@eecs.harvard.edu |
---|---|
Safe Haskell | Safe-Infered |
- data P a
- runP :: P a -> PState -> Either SomeException (a, PState)
- evalP :: P a -> PState -> Either SomeException a
- data PState
- emptyPState :: [Extensions] -> [String] -> ByteString -> Pos -> PState
- getInput :: P AlexInput
- setInput :: AlexInput -> P ()
- pushLexState :: Int -> P ()
- popLexState :: P Int
- getLexState :: P Int
- getCurToken :: P (L Token)
- setCurToken :: L Token -> P ()
- addTypedef :: String -> P ()
- addVariable :: String -> P ()
- isTypedef :: String -> P Bool
- pushScope :: P ()
- popScope :: P ()
- gccExts :: ExtensionsInt
- cudaExts :: ExtensionsInt
- openCLExts :: ExtensionsInt
- useExts :: ExtensionsInt -> P Bool
- antiquotationExts :: ExtensionsInt
- useGccExts :: P Bool
- useCUDAExts :: P Bool
- useOpenCLExts :: P Bool
- data LexerException = LexerException Pos Doc
- data ParserException = ParserException Loc Doc
- failAt :: Loc -> String -> P a
- lexerError :: AlexInput -> Doc -> P a
- unexpectedEOF :: AlexInput -> P a
- emptyCharacterLiteral :: AlexInput -> P a
- illegalCharacterLiteral :: AlexInput -> P a
- illegalNumericalLiteral :: AlexInput -> P a
- parserError :: Loc -> Doc -> P a
- unclosed :: Loc -> String -> P a
- expected :: [String] -> P b
- data AlexInput = AlexInput {
- alexPos :: !Pos
- alexPrevChar :: !Char
- alexInp :: !ByteString
- alexOff :: !Int
- alexGetChar :: AlexInput -> Maybe (Char, AlexInput)
- alexGetByte :: AlexInput -> Maybe (Word8, AlexInput)
- alexInputPrevChar :: AlexInput -> Char
- nextChar :: P Char
- peekChar :: P Char
- maybePeekChar :: P (Maybe Char)
- skipChar :: P ()
- type AlexPredicate = PState -> AlexInput -> Int -> AlexInput -> Bool
- allowAnti :: AlexPredicate
- ifExtension :: ExtensionsInt -> AlexPredicate
Documentation
emptyPState :: [Extensions] -> [String] -> ByteString -> Pos -> PStateSource
pushLexState :: Int -> P ()Source
getCurToken :: P (L Token)Source
addTypedef :: String -> P ()Source
addVariable :: String -> P ()Source
useExts :: ExtensionsInt -> P BoolSource
data LexerException Source
data ParserException Source
lexerError :: AlexInput -> Doc -> P aSource
unexpectedEOF :: AlexInput -> P aSource
emptyCharacterLiteral :: AlexInput -> P aSource
illegalCharacterLiteral :: AlexInput -> P aSource
illegalNumericalLiteral :: AlexInput -> P aSource
parserError :: Loc -> Doc -> P aSource
AlexInput | |
|
maybePeekChar :: P (Maybe Char)Source
type AlexPredicate = PState -> AlexInput -> Int -> AlexInput -> BoolSource
The components of an AlexPredicate
are the predicate state, input stream
before the token, length of the token, input stream after the token.