Safe Haskell | None |
---|
Parser utilities.
- module Text.Parsec
- type Parser k a = Eq k => ParsecT [Token k] (ParserState k) Identity a
- data ParserState k = ParseState {
- stateTokenShow :: k -> String
- stateFileName :: String
- data SourcePos
- runTokenParser :: Eq k => (k -> String) -> String -> Parser k a -> [Token k] -> Either ParseError a
- pTokMaybe :: (k -> Maybe a) -> Parser k a
- pTokMaybeSP :: (k -> Maybe a) -> Parser k (a, SourcePos)
- pTokAs :: Eq k => k -> t -> Parser k t
- pTokAsSP :: Eq k => k -> t -> Parser k (t, SourcePos)
- pTok :: Eq k => k -> Parser k ()
- pTokSP :: Eq k => k -> Parser k SourcePos
Documentation
module Text.Parsec
type Parser k a = Eq k => ParsecT [Token k] (ParserState k) Identity aSource
A generic parser, parameterised over token and return types.
data ParserState k Source
A parser state that keeps track of the name of the source file.
ParseState | |
|
A position in a source file.
If there is no file path then we assume that the input has been read from an interactive session and display ''<interactive>'' when pretty printing.
:: Eq k | |
=> (k -> String) | Show a token. |
-> String | File name for error messages. |
-> Parser k a | Parser to run. |
-> [Token k] | Tokens to parse. |
-> Either ParseError a |
Run a generic parser.
pTokMaybeSP :: (k -> Maybe a) -> Parser k (a, SourcePos)Source
Accept a token if the function return Just
,
also returning the source position of that token.