incremental-parser-0.1: Generic parser library capable of providing partial results from partial input.

Text.ParserCombinators.Incremental

Contents

Description

This module defines incremental parsers.

The exported Parser type can provide partial parsing results from partial input, as long as the output is a Monoid. Construct a parser using the primitives and combinators, supply it with input using functions feed and feedEof, and extract the parsed output using results.

Implementation is based on Brzozowski derivatives.

Synopsis

The Parser type

data Parser s r Source

The central parser type. Its first parameter is the input monoid, the second the output.

Instances

Monoid s => Monad (Parser s)

Usage of >>= destroys the incrementality of its left argument's parsing results, but >> is safe to use.

Monoid s => Functor (Parser s)

Usage of fmap destroys the incrementality of parsing results, if you need it use mapIncremental instead.

Monoid s => MonadPlus (Parser s)

The MonadPlus and the Alternative instance differ: the former's mplus combinator equals the asymmetric <<|> choice.

Monoid s => Applicative (Parser s)

The <*> combinator requires its both arguments to provide complete parsing results, takeWhile *> and <* preserve the incremental results.

Monoid s => Alternative (Parser s)

The <|> choice combinator is symmetric.

(Monoid s, Monoid r) => Monoid (Parser s r)

Two parsers can be sequentially joined.

Using a Parser

feed :: Monoid s => s -> Parser s r -> Parser s rSource

Feeds a chunk of the input to the parser.

feedEof :: Monoid s => Parser s r -> Parser s rSource

Signals the end of the input.

results :: Monoid r => Parser s r -> ([(r, s)], Maybe (r, Parser s r))Source

Extracts all available parsing results. The first component of the result pair is a list of complete results together with the unconsumed remainder of the input. If the parsing can continue further, the second component of the pair provides the partial result prefix together with the parser for the rest of the input.

completeResults :: Parser s r -> [(r, s)]Source

Like results, but returns only the complete results with the corresponding unconsumed inputs.

resultPrefix :: Monoid r => Parser s r -> (r, Parser s r)Source

Like results, but returns only the partial result prefix.

Parser primitives

eof :: (MonoidNull s, Monoid r) => Parser s rSource

A parser that fails on any input and succeeds at its end.

anyToken :: FactorialMonoid s => Parser s sSource

A parser that accepts any single input atom.

token :: (Eq s, FactorialMonoid s) => s -> Parser s sSource

A parser that accepts a specific input atom.

satisfy :: FactorialMonoid s => (s -> Bool) -> Parser s sSource

A parser that accepts an input atom only if it satisfies the given predicate.

acceptAll :: Monoid s => Parser s sSource

A parser that accepts all input.

string :: (LeftCancellativeMonoid s, MonoidNull s) => s -> Parser s sSource

A parser that consumes and returns the given prefix of the input.

takeWhile :: (FactorialMonoid s, MonoidNull s) => (s -> Bool) -> Parser s sSource

A parser accepting the longest sequence of input atoms that match the given predicate; an optimized version of 'many0 . satisfy'.

takeWhile1 :: (FactorialMonoid s, MonoidNull s) => (s -> Bool) -> Parser s sSource

A parser accepting the longest non-empty sequence of input atoms that match the given predicate; an optimized version of 'many1 . satisfy'.

Parser combinators

count :: (Monoid s, Monoid r) => Int -> Parser s r -> Parser s rSource

Accepts the given number of occurrences of the argument parser.

skip :: (Monoid s, Monoid r) => Parser s r' -> Parser s rSource

Discards the results of the argument parser.

option :: (Monoid s, Monoid r) => Parser s r -> Parser s rSource

Like optional, but restricted to Monoid results.

many0 :: (Monoid s, Monoid r) => Parser s r -> Parser s rSource

Zero or more argument occurrences like many, but matches the longest possible input sequence.

many1 :: (Monoid s, Monoid r) => Parser s r -> Parser s rSource

One or more argument occurrences like some, but matches the longest possible input sequence.

manyTill :: (Monoid s, Monoid r) => Parser s r -> Parser s r' -> Parser s rSource

Repeats matching the first argument until the second one succeeds.

mapIncremental :: (Monoid s, Monoid a, Monoid b) => (a -> b) -> Parser s a -> Parser s bSource

Like fmap, but capable of mapping partial results, being restricted to Monoid types only.

(><) :: (Monoid s, Monoid r) => Parser s r -> Parser s r -> Parser s rSource

Join operator on parsers of same type, preserving the incremental results.

(<<|>) :: Parser s r -> Parser s r -> Parser s rSource

Left-weighted choice. The right parser is used only if the left one utterly fails.

lookAhead :: Monoid s => Parser s r -> Parser s rSource

Behaves like the argument parser, but without consuming any input.

notFollowedBy :: (Monoid s, Monoid r) => Parser s r' -> Parser s rSource

Does not consume any input; succeeds (with mempty result) iff the argument parser fails.

and :: (Monoid s, Monoid r1, Monoid r2) => Parser s r1 -> Parser s r2 -> Parser s (r1, r2)Source

Parallel parser conjunction: the combined parser keeps accepting input as long as both arguments do.

andThen :: (Monoid s, Monoid r1, Monoid r2) => Parser s r1 -> Parser s r2 -> Parser s (r1, r2)Source

Parser sequence that preserves incremental results, otherwise equivalent to liftA2 (,)

Utilities

showWith :: (Monoid s, Monoid r, Show s) => ((s -> Parser s r) -> String) -> (r -> String) -> Parser s r -> StringSource