Copyright | (c) 2006-2011 Harvard University (c) 2011-2013 Geoffrey Mainland |
---|---|
License | BSD-style |
Maintainer | mainland@drexel.edu |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- data P a
- runP :: P a -> PState -> Either SomeException (a, PState)
- evalP :: P a -> PState -> Either SomeException a
- data PState
- emptyPState :: [Extensions] -> [String] -> ByteString -> Maybe Pos -> PState
- getInput :: P AlexInput
- setInput :: AlexInput -> P ()
- pushLexState :: Int -> P ()
- popLexState :: P Int
- getLexState :: P Int
- pushbackToken :: L Token -> P ()
- getPushbackToken :: P (Maybe (L Token))
- getCurToken :: P (L Token)
- setCurToken :: L Token -> P ()
- addTypedef :: String -> P ()
- addClassdef :: String -> P ()
- addVariable :: String -> P ()
- isTypedef :: String -> P Bool
- isClassdef :: String -> P Bool
- pushScope :: P ()
- popScope :: P ()
- c99Exts :: ExtensionsInt
- c11Exts :: ExtensionsInt
- gccExts :: ExtensionsInt
- blocksExts :: ExtensionsInt
- cudaExts :: ExtensionsInt
- openCLExts :: ExtensionsInt
- objcExts :: ExtensionsInt
- useExts :: ExtensionsInt -> P Bool
- antiquotationExts :: ExtensionsInt
- useC99Exts :: P Bool
- useC11Exts :: P Bool
- useGccExts :: P Bool
- useBlocksExts :: P Bool
- useCUDAExts :: P Bool
- useOpenCLExts :: P Bool
- useObjCExts :: P Bool
- data LexerException = LexerException (Maybe Pos) Doc
- data ParserException = ParserException Loc Doc
- quoteTok :: Doc -> 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] -> Maybe String -> P b
- expectedAt :: L Token -> [String] -> Maybe String -> P b
- data AlexInput = AlexInput {
- alexPos :: !(Maybe Pos)
- alexPrevChar :: !Char
- alexInput :: !ByteString
- alexOff :: !Int
- alexGetChar :: AlexInput -> Maybe (Char, AlexInput)
- alexGetByte :: AlexInput -> Maybe (Word8, AlexInput)
- alexInputPrevChar :: AlexInput -> Char
- alexLoc :: AlexInput -> AlexInput -> Loc
- 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 -> Maybe Pos -> PState Source #
pushLexState :: Int -> P () Source #
popLexState :: P Int Source #
getLexState :: P Int Source #
addTypedef :: String -> P () Source #
addClassdef :: String -> P () Source #
addVariable :: String -> P () Source #
useC99Exts :: P Bool Source #
useC11Exts :: P Bool Source #
useGccExts :: P Bool Source #
useBlocksExts :: P Bool Source #
useCUDAExts :: P Bool Source #
useOpenCLExts :: P Bool Source #
useObjCExts :: P Bool Source #
data LexerException Source #
Instances
Exception LexerException Source # | |
Defined in Language.C.Parser.Monad | |
Show LexerException Source # | |
Defined in Language.C.Parser.Monad showsPrec :: Int -> LexerException -> ShowS # show :: LexerException -> String # showList :: [LexerException] -> ShowS # |
data ParserException Source #
Instances
Exception ParserException Source # | |
Defined in Language.C.Parser.Monad | |
Show ParserException Source # | |
Defined in Language.C.Parser.Monad showsPrec :: Int -> ParserException -> ShowS # show :: ParserException -> String # showList :: [ParserException] -> ShowS # |
unexpectedEOF :: AlexInput -> P a Source #
emptyCharacterLiteral :: AlexInput -> P a Source #
illegalCharacterLiteral :: AlexInput -> P a Source #
illegalNumericalLiteral :: AlexInput -> P a Source #
AlexInput | |
|
alexInputPrevChar :: AlexInput -> Char Source #
type AlexPredicate = PState -> AlexInput -> Int -> AlexInput -> Bool Source #
The components of an AlexPredicate
are the predicate state, input stream
before the token, length of the token, input stream after the token.