incremental-parser-0.5.0.5: Generic parser library capable of providing partial results from partial input.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.ParserCombinators.Incremental

Description

This module defines parsing combinators for 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.

If your parser only ever uses the symmetric choice <||>, import the Text.ParserCombinators.Incremental.Symmetric module instead. Vice versa, if you always use the shortcutting <<|> choice, import Text.ParserCombinators.Incremental.LeftBiasedLocal instead of this module.

Implementation is based on Brzozowski derivatives.

Synopsis

The Parser type

data Parser t s r Source #

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

Instances

Instances details
Monoid s => MonadFail (Parser t s) Source # 
Instance details

Defined in Text.ParserCombinators.Incremental

Methods

fail :: String -> Parser t s a #

Monoid s => MonadFix (Parser t s) Source # 
Instance details

Defined in Text.ParserCombinators.Incremental

Methods

mfix :: (a -> Parser t s a) -> Parser t s a #

Monoid s => Alternative (Parser LeftBiasedLocal s) Source #

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

Instance details

Defined in Text.ParserCombinators.Incremental.LeftBiasedLocal

Monoid s => Alternative (Parser Symmetric s) Source #

The symmetric version of the <|> choice combinator.

Instance details

Defined in Text.ParserCombinators.Incremental.Symmetric

Monoid s => Applicative (Parser t s) Source #

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

Instance details

Defined in Text.ParserCombinators.Incremental

Methods

pure :: a -> Parser t s a #

(<*>) :: Parser t s (a -> b) -> Parser t s a -> Parser t s b #

liftA2 :: (a -> b -> c) -> Parser t s a -> Parser t s b -> Parser t s c #

(*>) :: Parser t s a -> Parser t s b -> Parser t s b #

(<*) :: Parser t s a -> Parser t s b -> Parser t s a #

Monoid s => Functor (Parser t s) Source #

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

Instance details

Defined in Text.ParserCombinators.Incremental

Methods

fmap :: (a -> b) -> Parser t s a -> Parser t s b #

(<$) :: a -> Parser t s b -> Parser t s a #

Monoid s => Monad (Parser t s) Source #

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

Instance details

Defined in Text.ParserCombinators.Incremental

Methods

(>>=) :: Parser t s a -> (a -> Parser t s b) -> Parser t s b #

(>>) :: Parser t s a -> Parser t s b -> Parser t s b #

return :: a -> Parser t s a #

Monoid s => MonadPlus (Parser LeftBiasedLocal s) Source #

The MonadPlus instances are the same as the Alternative instances.

Instance details

Defined in Text.ParserCombinators.Incremental.LeftBiasedLocal

Monoid s => MonadPlus (Parser Symmetric s) Source #

The MonadPlus instances are the same as the Alternative instances.

Instance details

Defined in Text.ParserCombinators.Incremental.Symmetric

(Alternative (Parser t s), Monoid s) => MonoidAlternative (Parser t s) Source # 
Instance details

Defined in Text.ParserCombinators.Incremental

Methods

moptional :: (Semigroup a, Monoid a) => Parser t s a -> Parser t s a Source #

concatMany :: (Semigroup a, Monoid a) => Parser t s a -> Parser t s a Source #

concatSome :: (Semigroup a, Monoid a) => Parser t s a -> Parser t s a Source #

Monoid s => MonoidApplicative (Parser t s) Source #

The +<*> operator is specialized to return incremental parsing results.

Instance details

Defined in Text.ParserCombinators.Incremental

Methods

(+<*>) :: Parser t s (a -> a) -> Parser t s a -> Parser t s a Source #

(><) :: Semigroup a => Parser t s a -> Parser t s a -> Parser t s a Source #

(Alternative (Parser t s), MonoidNull s) => DeterministicParsing (Parser t s) Source # 
Instance details

Defined in Text.ParserCombinators.Incremental

Methods

(<<|>) :: Parser t s a -> Parser t s a -> Parser t s a #

takeOptional :: Parser t s a -> Parser t s (Maybe a) #

takeMany :: Parser t s a -> Parser t s [a] #

takeSome :: Parser t s a -> Parser t s [a] #

concatAll :: Monoid a => Parser t s a -> Parser t s a #

skipAll :: Parser t s a -> Parser t s () #

(TextualMonoid s, LeftReductive s, LookAheadParsing (Parser t s)) => InputCharParsing (Parser t s) Source # 
Instance details

Defined in Text.ParserCombinators.Incremental

Methods

satisfyCharInput :: (Char -> Bool) -> Parser t s (ParserInput (Parser t s)) #

notSatisfyChar :: (Char -> Bool) -> Parser t s () #

scanChars :: state -> (state -> Char -> Maybe state) -> Parser t s (ParserInput (Parser t s)) #

takeCharsWhile :: (Char -> Bool) -> Parser t s (ParserInput (Parser t s)) #

takeCharsWhile1 :: (Char -> Bool) -> Parser t s (ParserInput (Parser t s)) #

(Alternative (Parser t s), FactorialMonoid s, LeftReductive s) => InputParsing (Parser t s) Source # 
Instance details

Defined in Text.ParserCombinators.Incremental

Associated Types

type ParserInput (Parser t s) #

type ParserPosition (Parser t s) #

Methods

getInput :: Parser t s (ParserInput (Parser t s)) #

getSourcePos :: Parser t s (ParserPosition (Parser t s)) #

anyToken :: Parser t s (ParserInput (Parser t s)) #

take :: Int -> Parser t s (ParserInput (Parser t s)) #

satisfy :: (ParserInput (Parser t s) -> Bool) -> Parser t s (ParserInput (Parser t s)) #

notSatisfy :: (ParserInput (Parser t s) -> Bool) -> Parser t s () #

scan :: state -> (state -> ParserInput (Parser t s) -> Maybe state) -> Parser t s (ParserInput (Parser t s)) #

string :: ParserInput (Parser t s) -> Parser t s (ParserInput (Parser t s)) #

takeWhile :: (ParserInput (Parser t s) -> Bool) -> Parser t s (ParserInput (Parser t s)) #

takeWhile1 :: (ParserInput (Parser t s) -> Bool) -> Parser t s (ParserInput (Parser t s)) #

(Alternative (Parser t s), TextualMonoid s) => CharParsing (Parser t s) Source # 
Instance details

Defined in Text.ParserCombinators.Incremental

Methods

satisfy :: (Char -> Bool) -> Parser t s Char #

char :: Char -> Parser t s Char #

notChar :: Char -> Parser t s Char #

anyChar :: Parser t s Char #

string :: String -> Parser t s String #

text :: Text -> Parser t s Text #

(Alternative (Parser t s), MonoidNull s) => Parsing (Parser t s) Source # 
Instance details

Defined in Text.ParserCombinators.Incremental

Methods

try :: Parser t s a -> Parser t s a #

(<?>) :: Parser t s a -> String -> Parser t s a #

skipMany :: Parser t s a -> Parser t s () #

skipSome :: Parser t s a -> Parser t s () #

unexpected :: String -> Parser t s a #

eof :: Parser t s () #

notFollowedBy :: Show a => Parser t s a -> Parser t s () #

(Alternative (Parser t s), MonoidNull s) => LookAheadParsing (Parser t s) Source # 
Instance details

Defined in Text.ParserCombinators.Incremental

Methods

lookAhead :: Parser t s a -> Parser t s a #

(Monoid s, Monoid r, Semigroup r) => Monoid (Parser t s r) Source # 
Instance details

Defined in Text.ParserCombinators.Incremental

Methods

mempty :: Parser t s r #

mappend :: Parser t s r -> Parser t s r -> Parser t s r #

mconcat :: [Parser t s r] -> Parser t s r #

(Monoid s, Semigroup r) => Semigroup (Parser t s r) Source #

Two parsers can be sequentially joined.

Instance details

Defined in Text.ParserCombinators.Incremental

Methods

(<>) :: Parser t s r -> Parser t s r -> Parser t s r #

sconcat :: NonEmpty (Parser t s r) -> Parser t s r #

stimes :: Integral b => b -> Parser t s r -> Parser t s r #

type ParserInput (Parser t s) Source # 
Instance details

Defined in Text.ParserCombinators.Incremental

type ParserInput (Parser t s) = s
type ParserPosition (Parser t s) Source # 
Instance details

Defined in Text.ParserCombinators.Incremental

Using a Parser

feed :: Monoid s => s -> Parser t s r -> Parser t s r Source #

Feeds a chunk of the input to the parser.

feedEof :: Monoid s => Parser t s r -> Parser t s r Source #

Signals the end of the input.

inspect :: Parser t s r -> Either String ([(r, s)], Maybe (Maybe (r -> r), Parser t s r)) Source #

Like results, but more general: doesn't assume that the result type is a Monoid.

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

Extracts all available parsing results from a Parser. 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 :: Monoid s => Parser t s r -> [(r, s)] Source #

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

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

Like results, but returns only the partial result prefix.

Parser primitives

(<?>) :: Monoid s => Parser t s r -> String -> Parser t s r infix 0 Source #

Name a parser for error reporting in case it fails.

more :: (s -> Parser t s r) -> Parser t s r Source #

eof :: (MonoidNull s, Monoid r, Semigroup r) => Parser t s r Source #

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

anyToken :: FactorialMonoid s => Parser t s s Source #

A parser that accepts any single input atom.

token :: (Eq s, FactorialMonoid s) => s -> Parser t s s Source #

A parser that accepts a specific input atom.

satisfy :: FactorialMonoid s => (s -> Bool) -> Parser t s s Source #

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

acceptAll :: (Semigroup s, Monoid s) => Parser t s s Source #

A parser that accepts and consumes all input.

string :: (LeftReductive s, MonoidNull s, Semigroup s) => s -> Parser t s s Source #

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

takeWhile :: (FactorialMonoid s, MonoidNull s) => (s -> Bool) -> Parser t s s Source #

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

takeWhile1 :: (FactorialMonoid s, MonoidNull s) => (s -> Bool) -> Parser t s s Source #

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

Character primitives

satisfyChar :: TextualMonoid s => (Char -> Bool) -> Parser t s s Source #

Specialization of satisfy on TextualMonoid inputs, accepting an input character only if it satisfies the given predicate.

takeCharsWhile :: (TextualMonoid s, MonoidNull s) => (Char -> Bool) -> Parser t s s Source #

Specialization of takeWhile on TextualMonoid inputs, accepting the longest sequence of input characters that match the given predicate; an optimized version of 'concatMany . satisfyChar'.

takeCharsWhile1 :: (TextualMonoid s, MonoidNull s) => (Char -> Bool) -> Parser t s s Source #

Specialization of takeWhile1 on TextualMonoid inputs, accepting the longest non-empty sequence of input atoms that match the given predicate; an optimized version of 'concatSome . satisfyChar'.

Parser combinators

count :: (Monoid s, Monoid r, Semigroup r) => Int -> Parser t s r -> Parser t s r Source #

Accepts the given number of occurrences of the argument parser.

skip :: (Monoid s, Monoid r, Semigroup r) => Parser t s r' -> Parser t s r Source #

Discards the results of the argument parser.

moptional :: (MonoidAlternative f, Semigroup a, Monoid a) => f a -> f a Source #

Like optional, but restricted to Monoid results.

concatMany :: (MonoidAlternative f, Semigroup a, Monoid a) => f a -> f a Source #

Zero or more argument occurrences like many, but concatenated.

concatSome :: (MonoidAlternative f, Semigroup a, Monoid a) => f a -> f a Source #

One or more argument occurrences like some, but concatenated.

manyTill :: (Monoid s, Monoid r, Semigroup r) => Parser t s r -> Parser t s r' -> Parser t s r Source #

Repeats matching the first argument until the second one succeeds.

(+<*>) :: MonoidApplicative f => f (a -> a) -> f a -> f a infixl 4 Source #

A variant of the Applicative's <*> operator specialized for endomorphic functions.

(<||>) :: Parser t s r -> Parser t s r -> Parser t s r infixl 3 Source #

(<<|>) :: Monoid s => Parser t s r -> Parser t s r -> Parser t s r infixl 3 Source #

(><) :: (MonoidApplicative f, Semigroup a) => f a -> f a -> f a infixl 5 Source #

Lifted and potentially optimized monoid mappend operation from the parameter type.

lookAhead :: Monoid s => Parser t s r -> Parser t s r Source #

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

notFollowedBy :: (Monoid s, Monoid r) => Parser t s r' -> Parser t s r Source #

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

and :: (Monoid s, Monoid r1, Monoid r2) => Parser t s r1 -> Parser t s r2 -> Parser t 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 t s r1 -> Parser t s r2 -> Parser t s (r1, r2) Source #

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

record :: (Traversable g, Applicative m, Monoid s) => g (Parser t s) -> Parser t s (g m) Source #

Combine a record of parsers into a record parser.

Parser mapping

mapType :: (forall a. Parser t s a -> Parser b s a) -> Parser t s r -> Parser b s r Source #

Modifies the parser type

mapIncremental :: (Monoid s, Monoid a, Monoid b) => (a -> b) -> Parser p s a -> Parser p s b Source #

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

mapInput :: (Monoid s, Monoid s') => (s -> s') -> (s' -> s) -> Parser t s r -> Parser t s' r Source #

Converts a parser accepting one input type to another. The argument functions forth and back must be inverses of each other and they must distribute through <>:

f (s1 <> s2) == f s1 <> f s2

mapMaybeInput :: (Monoid s, Monoid s') => (s -> Maybe s') -> (s' -> Maybe s) -> Parser t s r -> Parser t s' r Source #

Converts a parser accepting one input type to another, just like 'mapMaybeInput except the two argument functions can demand more input by returning Nothing. If 'mapMaybeInput is defined for the two input inputs, then

mapInput f g == mapMaybeInput (Just . f) (Just . g)

Utilities

showWith :: (Monoid s, Monoid r, Show s) => ((s -> Parser t s r) -> String) -> (r -> String) -> Parser t s r -> String Source #

defaultMany :: (Monoid s, Alternative (Parser t s)) => Parser t s r -> Parser t s [r] Source #

defaultSome :: (Monoid s, Alternative (Parser t s)) => Parser t s r -> Parser t s [r] Source #