Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
- newtype Parser a = P (Text -> Result Text a)
- data Result z a
- runParser :: Parser a -> Text -> (Either String a, Text)
- next :: Parser Char
- eof :: Parser ()
- satisfy :: (Char -> Bool) -> Parser Char
- onFail :: Parser a -> Parser a -> Parser a
- manySatisfy :: (Char -> Bool) -> Parser Text
- many1Satisfy :: (Char -> Bool) -> Parser Text
- reparse :: Text -> Parser ()
- module Text.ParserCombinators.Poly.Base
- module Control.Applicative
The Parser datatype
This Parser
datatype is a specialised parsing monad with error
reporting. Whereas the standard version can be used for arbitrary
token types, this version is specialised to Text input only.
A return type like Either, that distinguishes not only between right and wrong answers, but also has commitment, so that a failure cannot be undone. This should only be used for writing very primitive parsers - really it is an internal detail of the library. The z type is the remaining unconsumed input.
runParser :: Parser a -> Text -> (Either String a, Text) Source
Apply a parser to an input token sequence.
Basic parsers
satisfy :: (Char -> Bool) -> Parser Char Source
Return the next token if it satisfies the given predicate.
onFail :: Parser a -> Parser a -> Parser a Source
p
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.onFail
q
Derived parsers (but implemented more efficiently)
manySatisfy :: (Char -> Bool) -> Parser Text Source
manySatisfy p
is a more efficient fused version of many (satisfy p)
many1Satisfy :: (Char -> Bool) -> Parser Text Source
many1Satisfy p
is a more efficient fused version of many1 (satisfy p)
Re-parsing
reparse :: Text -> Parser () 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.
Re-export all more general combinators
module Control.Applicative