Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
- newtype Parser t a = P ([t] -> Result [t] a)
- data Result z a
- runParser :: Parser t a -> [t] -> (Either String a, [t])
- next :: Parser t t
- eof :: Parser t ()
- satisfy :: (t -> Bool) -> Parser t t
- satisfyMsg :: Show t => (t -> Bool) -> String -> Parser t t
- onFail :: Parser t a -> Parser t a -> Parser t a
- reparse :: [t] -> Parser t ()
- module Text.ParserCombinators.Poly.Base
- module Control.Applicative
The Parser datatype
This Parser
datatype is a fairly generic parsing monad with error
reporting. It can be used for arbitrary token types, not just
String input. (If you require a running state, use module Poly.State
instead)
Alternative (Parser t) | |
Monad (Parser t) | |
Functor (Parser t) | |
Applicative (Parser t) | |
PolyParse (Parser t) | |
Commitment (Parser t) |
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 t a -> [t] -> (Either String a, [t]) Source
Apply a parser to an input token sequence.
Basic parsers
satisfy :: (t -> Bool) -> Parser t t Source
Return the next token if it satisfies the given predicate.
satisfyMsg :: Show t => (t -> Bool) -> String -> Parser t t Source
Return the next token if it satisfies the given predicate. The String argument describes the function, for better error messages.
onFail :: Parser t a -> Parser t a -> Parser t a infixl 6 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
Re-parsing
reparse :: [t] -> Parser 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.
Re-export all more general combinators
module Control.Applicative