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

Safe HaskellSafe-Inferred

Text.ParserCombinators.Poly.Base

Contents

Synopsis

The PolyParse classes

class Commitment p whereSource

The Commitment class is an abstraction over all the current concrete representations of monadic/applicative 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.

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.

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.

class (Functor p, Monad p, Applicative p, Alternative p, Commitment p) => PolyParse p Source

The PolyParse class is an abstraction gathering all of the common features that a two-level error-handling parser requires: the applicative parsing interface, the monadic interface, and commitment.

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.

Combinators general to all parser types.

Simple combinators

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

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

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.

Sequences

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

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

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

'upto n p' parses n or fewer items, using the parser p, in sequence.

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. If everything matches except the closing bracket, the whole parse fails soft, which can give less-than-satisfying error messages. If you want better error messages, try calling with e.g. bracket open (commit close) item

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.

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

manyFinally' is like manyFinally, except when the terminator parser overlaps with the element parser. In manyFinally e t, the parser t is tried only when parser e fails, whereas in manyFinally' e t, the parser t is always tried first, then parser e only if the terminator is not found. For instance, manyFinally (accept 01) (accept 0) on input 0101010 returns [01,01,01], whereas manyFinally' with the same arguments and input returns [].