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

Text.ParserCombinators.Poly.Base

Contents

Synopsis

The PolyParse class

class (Functor p, Monad p) => PolyParse p whereSource

The PolyParse class is an abstraction over all the current concrete representations of monadic parser combinators in this package. The common feature is two-level error-handling. Some primitives must be implemented specific to each parser type (e.g. depending on whether the parser has a running state, or whether it is lazy). But given those primitives, large numbers of combinators do not depend any further on the internal structure of the particular parser.

There are two additional basic combinators that we expect to be implemented afresh for every concrete type, but which (for technical reasons) cannot be class methods. They are next and satisfy.

Methods

commit :: p a -> p 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.

adjustErr :: p a -> (String -> String) -> p aSource

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

onFail :: p a -> p a -> p 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' :: [(String, p a)] -> p 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.

apply :: p (a -> b) -> p a -> p bSource

Apply a parsed function to a parsed value. Rather like ordinary function application lifted into parsers.

Instances

Combinators general to all parser types.

Simple combinators

discard :: PolyParse p => p a -> p b -> p aSource

x discard y parses both x and y, but discards the result of y. Rather like const lifted into parsers.

Error-handling

failBad :: PolyParse p => String -> p aSource

When a simple fail is not strong enough, use failBad for emphasis. An emphasised (severe) error cannot be overridden by choice operators.

adjustErrBad :: PolyParse p => p a -> (String -> String) -> p 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

oneOf :: PolyParse p => [p a] -> p aSource

Parse the first alternative in the list that succeeds.

optional :: PolyParse p => p a -> p (Maybe a)Source

optional indicates whether the parser succeeded through the Maybe type.

Sequences

exactly :: PolyParse p => Int -> p a -> p [a]Source

'exactly n p' parses precisely n items, using the parser p, in sequence.

many :: PolyParse p => p a -> p [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 :: PolyParse p => p a -> p [a]Source

Parse a non-empty list of items.

sepBy :: PolyParse p => p a -> p sep -> p [a]Source

Parse a list of items separated by discarded junk.

sepBy1 :: PolyParse p => p a -> p sep -> p [a]Source

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

bracketSep :: PolyParse p => p bra -> p sep -> p ket -> p a -> p [a]Source

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

bracket :: PolyParse p => p bra -> p ket -> p a -> p aSource

Parse a bracketed item, discarding the brackets.

manyFinally :: PolyParse p => p a -> p z -> p [a]Source

'manyFinally e t' parses a possibly-empty sequence of e's, terminated by a t. The final t is discarded. Any parse failures could be due either to a badly-formed terminator or a badly-formed element, so it raises both possible errors.