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

Text.ParserCombinators.PolyLazy

Contents

Synopsis

The Parser datatype.

When applied, these parsers do not return explicit failure. An exception is raised instead. This allows partial results to be returned before a full parse is complete. One of the key ways to ensure that your parser is properly lazy, is to parse the initial portion of text returning a function, then use the apply combinator to build the final value.

newtype Parser t a Source

The 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 PolyStateLazy instead.)

Constructors

P ([t] -> (Either String a, [t])) 

Instances

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

Apply a parser to an 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).

failBad :: String -> Parser t aSource

Simple failure can be corrected, but when a simple fail is not strong enough, use failBad for emphasis. It guarantees parsing will terminate with an exception.

commit :: Parser t a -> Parser 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 t tSource

One token

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

One token satifying a predicate

apply :: Parser t (a -> b) -> Parser t a -> Parser t bSource

Apply a parsed function to a parsed value

discard :: Parser t a -> Parser t b -> Parser t aSource

x discard y parses both x and y, but discards the result of y

Error-handling

adjustErr :: Parser t a -> (String -> String) -> Parser t aSource

p adjustErr f applies the transformation f to any error message generated in p, having no effect if p succeeds.

adjustErrBad :: Parser t a -> (String -> String) -> Parser 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 t a -> Parser t a -> Parser 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 t a] -> Parser t aSource

Parse the first alternative in the list that succeeds.

oneOf' :: [(String, Parser t a)] -> Parser 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.

optional :: Parser t a -> Parser t (Maybe a)Source

optional indicates whether the parser succeeded through the Maybe type.

Sequences

many :: Parser t a -> Parser 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 t a -> Parser t [a]Source

Parse a non-empty list of items.

sepBy :: Parser t a -> Parser t sep -> Parser t [a]Source

Parse a list of items separated by discarded junk.

sepBy1 :: Parser t a -> Parser t sep -> Parser t [a]Source

Parse a non-empty list of items separated by discarded junk.

bracketSep :: Parser t bra -> Parser t sep -> Parser t ket -> Parser t a -> Parser t [a]Source

Parse a list of items, discarding the start, end, and separator items.

bracket :: Parser t bra -> Parser t ket -> Parser t a -> Parser t aSource

Parse a bracketed item, discarding the brackets.

manyFinally :: Parser t a -> Parser t z -> Parser 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.

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.