polyparse-1.1: A variety of alternative parser combinator libraries.

Text.ParserCombinators.Poly.StateLazy

Contents

Synopsis

The Parser datatype.

Parsers do not return explicit failure. An exception is raised instead. This allows partial results to be returned before a full parse is complete.

newtype Parser s t a Source

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] -> (Either String a, s, [t])) 

Instances

Monad (Parser s t) 
Functor (Parser s t) 
PolyParse (Parser s t) 

runParser :: Parser s t a -> s -> [t] -> (a, s, [t])Source

Apply a parser to an initial state and input token sequence. The parser cannot return an error value explicitly, so errors raise an exception. Thus, results can be partial (lazily constructed, but containing undefined).

Combinators:

Primitives

next :: Parser s t tSource

Yield one token.

satisfy :: (t -> Bool) -> Parser s t tSource

Yield one token if it satisfies a predicate.

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.

Re-export all more general combinators