Safe Haskell | None |
---|---|
Language | Haskell2010 |
Text.ParserCombinators.Incremental.LeftBiasedLocal
Description
This module defines parsing combinators for incremental parsers with left-biased local choice.
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
- feed :: Monoid s => s -> Parser t s r -> Parser t s r
- takeWhile :: (FactorialMonoid s, MonoidNull s) => (s -> Bool) -> Parser t s s
- string :: (LeftReductive s, MonoidNull s, Semigroup s) => s -> Parser t s s
- (<?>) :: Monoid s => Parser t s r -> String -> Parser t s r
- manyTill :: (Monoid s, Monoid r, Semigroup r) => Parser t s r -> Parser t s r' -> Parser t s r
- count :: (Monoid s, Monoid r, Semigroup r) => Int -> Parser t s r -> Parser t s r
- lookAhead :: Monoid s => Parser t s r -> Parser t s r
- satisfy :: FactorialMonoid s => (s -> Bool) -> Parser t s s
- skip :: (Monoid s, Monoid r, Semigroup r) => Parser t s r' -> Parser t s r
- takeWhile1 :: (FactorialMonoid s, MonoidNull s) => (s -> Bool) -> Parser t s s
- and :: (Monoid s, Monoid r1, Monoid r2) => Parser t s r1 -> Parser t s r2 -> Parser t s (r1, r2)
- eof :: (MonoidNull s, Monoid r, Semigroup r) => Parser t s r
- (><) :: (MonoidApplicative f, Semigroup a) => f a -> f a -> f a
- (+<*>) :: MonoidApplicative f => f (a -> a) -> f a -> f a
- notFollowedBy :: (Monoid s, Monoid r) => Parser t s r' -> Parser t s r
- concatMany :: (MonoidAlternative f, Semigroup a, Monoid a) => f a -> f a
- moptional :: (MonoidAlternative f, Semigroup a, Monoid a) => f a -> f a
- concatSome :: (MonoidAlternative f, Semigroup a, Monoid a) => f a -> f a
- takeCharsWhile :: (TextualMonoid s, MonoidNull s) => (Char -> Bool) -> Parser t s s
- takeCharsWhile1 :: (TextualMonoid s, MonoidNull s) => (Char -> Bool) -> Parser t s s
- anyToken :: FactorialMonoid s => Parser t s s
- (<<|>) :: Monoid s => Parser t s r -> Parser t s r -> Parser t s r
- token :: (Eq s, FactorialMonoid s) => s -> Parser t s s
- (<||>) :: Parser t s r -> Parser t s r -> Parser t s r
- failure :: Parser t s r
- feedEof :: Monoid s => Parser t s r -> Parser t s r
- inspect :: Parser t s r -> Either String ([(r, s)], Maybe (Maybe (r -> r), Parser t s r))
- results :: Monoid r => Parser t s r -> ([(r, s)], Maybe (r, Parser t s r))
- completeResults :: Monoid s => Parser t s r -> [(r, s)]
- resultPrefix :: Monoid r => Parser t s r -> (r, Parser t s r)
- more :: (s -> Parser t s r) -> Parser t s r
- acceptAll :: (Semigroup s, Monoid s) => Parser t s s
- satisfyChar :: TextualMonoid s => (Char -> Bool) -> Parser t s s
- andThen :: (Monoid s, Monoid r1, Monoid r2) => Parser t s r1 -> Parser t s r2 -> Parser t s (r1, r2)
- record :: forall g (m :: Type -> Type) s t. (Traversable g, Applicative m, Monoid s) => g (Parser t s) -> Parser t s (g m)
- mapType :: (forall a. Parser t s a -> Parser b s a) -> Parser t s r -> Parser b s r
- mapIncremental :: (Monoid s, Monoid a, Monoid b) => (a -> b) -> Parser p s a -> Parser p s b
- mapInput :: (Monoid s, Monoid s') => (s -> s') -> (s' -> s) -> Parser t s r -> Parser t s' r
- mapMaybeInput :: (Monoid s, Monoid s') => (s -> Maybe s') -> (s' -> Maybe s) -> Parser t s r -> Parser t s' r
- isInfallible :: Parser t s r -> Bool
- showWith :: (Monoid s, Monoid r, Show s) => ((s -> Parser t s r) -> String) -> (r -> String) -> Parser t s r -> String
- defaultMany :: (Monoid s, Alternative (Parser t s)) => Parser t s r -> Parser t s [r]
- defaultSome :: (Monoid s, Alternative (Parser t s)) => Parser t s r -> Parser t s [r]
- type Parser = Parser LeftBiasedLocal
- data LeftBiasedLocal
- leftmost :: Parser s r -> Parser a s r
Documentation
feed :: Monoid s => s -> Parser t s r -> Parser t s r Source #
Feeds a chunk of the input to the parser.
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'.
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.
(<?>) :: Monoid s => Parser t s r -> String -> Parser t s r infix 0 Source #
Name a parser for error reporting in case it fails.
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.
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.
lookAhead :: Monoid s => Parser t s r -> Parser t s r Source #
Behaves like the argument parser, but without consuming any input.
satisfy :: FactorialMonoid s => (s -> Bool) -> Parser t s s Source #
A parser that accepts an input atom only if it satisfies the given predicate.
skip :: (Monoid s, Monoid r, Semigroup r) => Parser t s r' -> Parser t s r Source #
Discards the results of the argument parser.
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'.
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.
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.
(><) :: (MonoidApplicative f, Semigroup a) => f a -> f a -> f a infixl 5 Source #
Lifted and potentially optimized monoid mappend
operation from the parameter type.
(+<*>) :: MonoidApplicative f => f (a -> a) -> f a -> f a infixl 4 Source #
A variant of the Applicative's <*>
operator specialized for endomorphic functions.
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.
concatMany :: (MonoidAlternative f, Semigroup a, Monoid a) => f a -> f a Source #
Zero or more argument occurrences like many
, but concatenated.
moptional :: (MonoidAlternative f, Semigroup a, Monoid a) => f a -> f a Source #
Like optional
, but restricted to Monoid
results.
concatSome :: (MonoidAlternative f, Semigroup a, Monoid a) => f a -> f a Source #
One or more argument occurrences like some
, but concatenated.
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'.
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.
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.
acceptAll :: (Semigroup s, Monoid s) => Parser t s s Source #
A parser that accepts and consumes all input.
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.
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 :: forall g (m :: Type -> Type) s t. (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.
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 #
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)
isInfallible :: Parser t s r -> Bool Source #
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 #
type Parser = Parser LeftBiasedLocal Source #
data LeftBiasedLocal Source #
An empty type to specialize Parser
for the left-biased Alternative
instance.
Instances
Monoid s => Alternative (Parser LeftBiasedLocal s) Source # | Left-biased choice. The right parser is used only if the left one utterly fails. |
Defined in Text.ParserCombinators.Incremental.LeftBiasedLocal Methods empty :: Parser LeftBiasedLocal s a # (<|>) :: Parser LeftBiasedLocal s a -> Parser LeftBiasedLocal s a -> Parser LeftBiasedLocal s a # some :: Parser LeftBiasedLocal s a -> Parser LeftBiasedLocal s [a] # many :: Parser LeftBiasedLocal s a -> Parser LeftBiasedLocal s [a] # | |
Monoid s => MonadPlus (Parser LeftBiasedLocal s) Source # | The |
Defined in Text.ParserCombinators.Incremental.LeftBiasedLocal Methods mzero :: Parser LeftBiasedLocal s a # mplus :: Parser LeftBiasedLocal s a -> Parser LeftBiasedLocal s a -> Parser LeftBiasedLocal s a # |