polyparseSource codeContentsIndex
Text.ParserCombinators.PolyState
Contents
The Parser datatype
Combinators:
Primitives
Error-handling
Choices
Sequences
State-handling
Re-parsing
Synopsis
newtype Parser s t a = P (s -> [t] -> (EitherE String a, s, [t]))
runParser :: Parser s t a -> s -> [t] -> (Either String a, s, [t])
failBad :: String -> Parser s t a
commit :: Parser s t a -> Parser s t a
next :: Parser s t t
satisfy :: (t -> Bool) -> Parser s t t
apply :: Parser s t (a -> b) -> Parser s t a -> Parser s t b
discard :: Parser s t a -> Parser s t b -> Parser s t a
adjustErr :: Parser s t a -> (String -> String) -> Parser s t a
adjustErrBad :: Parser s t a -> (String -> String) -> Parser s t a
indent :: Int -> String -> String
onFail :: Parser s t a -> Parser s t a -> Parser s t a
oneOf :: [Parser s t a] -> Parser s t a
oneOf' :: [(String, Parser s t a)] -> Parser s t a
exactly :: Int -> Parser s t a -> Parser s t [a]
many :: Parser s t a -> Parser s t [a]
many1 :: Parser s t a -> Parser s t [a]
sepBy :: Parser s t a -> Parser s t sep -> Parser s t [a]
sepBy1 :: Parser s t a -> Parser s t sep -> Parser s t [a]
bracketSep :: Parser s t bra -> Parser s t sep -> Parser s t ket -> Parser s t a -> Parser s t [a]
bracket :: Parser s t bra -> Parser s t ket -> Parser s t a -> Parser s t a
manyFinally :: Parser s t a -> Parser s t z -> Parser s t [a]
stUpdate :: (s -> s) -> Parser s t ()
stQuery :: (s -> a) -> Parser s t a
stGet :: Parser s t s
reparse :: [t] -> Parser s t ()
The Parser datatype
newtype Parser s t aSource
The Parser datatype is a fairly generic parsing monad with error reporting and a running state. It can be used for arbitrary token types, not just String input.
Constructors
P (s -> [t] -> (EitherE String a, s, [t]))
show/hide Instances
Functor (Parser s t)
Monad (Parser s t)
runParser :: Parser s t a -> s -> [t] -> (Either String a, s, [t])Source
Apply a parser to an initial state and input token sequence.
failBad :: String -> Parser s t aSource
When a simple fail is not strong enough, use failBad for emphasis. An emphasised (severe) error can propagate out through choice operators.
commit :: Parser s t a -> Parser s t aSource
Commit is a way of raising the severity of any errors found within its argument. Used in the middle of a parser definition, it means that any operations prior to commitment fail softly, but after commitment, they fail hard.
Combinators:
Primitives
next :: Parser s t tSource
One token
satisfy :: (t -> Bool) -> Parser s t tSource
One token satifying a predicate
apply :: Parser s t (a -> b) -> Parser s t a -> Parser s t bSource
Apply a parsed function to a parsed value
discard :: Parser s t a -> Parser s t b -> Parser s t aSource
x discard y parses both x and y, but discards the result of y
Error-handling
adjustErr :: Parser s t a -> (String -> String) -> Parser s t aSource
p adjustErr f applies the transformation f to any error message generated in p, having no effect if p succeeds.
adjustErrBad :: Parser s t a -> (String -> String) -> Parser s t aSource
adjustErrBad is just like adjustErr except it also raises the severity of the error.
indent :: Int -> String -> StringSource
Helper for formatting error messages: indents all lines by a fixed amount.
Choices
onFail :: Parser s t a -> Parser s t a -> Parser s t aSource
p onFail q means parse p unless p fails in which case parse q instead. Can be chained together to give multiple attempts to parse something. (Note that q could itself be a failing parser, e.g. to change the error message from that defined in p to something different.) However, a severe failure in p cannot be ignored.
oneOf :: [Parser s t a] -> Parser s t aSource
Parse the first alternative in the list that succeeds.
oneOf' :: [(String, Parser s t a)] -> Parser s t aSource
Parse the first alternative that succeeds, but if none succeed, report only the severe errors, and if none of those, then report all the soft errors.
Sequences
exactly :: Int -> Parser s t a -> Parser s t [a]Source
'exactly n p' parses a precise number of items, n, using the parser p, in sequence.
many :: Parser s t a -> Parser s t [a]Source
'many p' parses a list of elements with individual parser p. Cannot fail, since an empty list is a valid return value.
many1 :: Parser s t a -> Parser s t [a]Source
Parse a non-empty list of items.
sepBy :: Parser s t a -> Parser s t sep -> Parser s t [a]Source
Parse a list of items separated by discarded junk.
sepBy1 :: Parser s t a -> Parser s t sep -> Parser s t [a]Source
Parse a non-empty list of items separated by discarded junk.
bracketSep :: Parser s t bra -> Parser s t sep -> Parser s t ket -> Parser s t a -> Parser s t [a]Source
Parse a list of items, discarding the start, end, and separator items.
bracket :: Parser s t bra -> Parser s t ket -> Parser s t a -> Parser s t aSource
Parse a bracketed item, discarding the brackets.
manyFinally :: Parser s t a -> Parser s t z -> Parser s t [a]Source
'manyFinally e t' parses a possibly-empty sequence of e's, terminated by a t. Any parse failures could be due either to a badly-formed terminator or a badly-formed element, so raise both possible errors.
State-handling
stUpdate :: (s -> s) -> Parser s t ()Source
Update the internal state.
stQuery :: (s -> a) -> Parser s t aSource
Query the internal state.
stGet :: Parser s t sSource
Deliver the entire internal state.
Re-parsing
reparse :: [t] -> Parser s t ()Source
Push some tokens back onto the front of the input stream and reparse. This is useful e.g. for recursively expanding macros. When the user-parser recognises a macro use, it can lookup the macro expansion from the parse state, lex it, and then stuff the lexed expansion back down into the parser.
Produced by Haddock version 0.8