Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type ParserT m = Fixed (ParserT m)
- data SeparatedParser p (g :: (* -> *) -> *) s a
- = FrontParser (p g s a)
- | CycleParser {
- cycleParser :: p g s a
- backParser :: p g s a
- appendResultsArrow :: ResultAppend p g s a
- dependencies :: Dependencies g
- | BackParser {
- backParser :: p g s a
- class AmbiguityDecidable a
- lift :: Applicative m => m a -> ParserT m g s a
- liftPositive :: p g s a -> Fixed p g s a
- tbind :: (Monad m, AmbiguityDecidable b) => ParserT m g s a -> (a -> m b) -> ParserT m g s b
- tmap :: AmbiguityDecidable b => (m a -> m b) -> ParserT m g s a -> ParserT m g s b
- parseSeparated :: forall p g rl s. (Apply g, Foldable g, Eq s, FactorialMonoid s, LeftReductive s, TailsParsing (p g s), GrammarConstraint (p g s) g, GrammarFunctor (p g s) ~ rl s, FallibleResults rl, s ~ ParserInput (p g s)) => g (SeparatedParser p g s) -> s -> [(s, g (GrammarFunctor (p g s)))]
- separated :: forall p g s. (Alternative (p g s), Apply g, Distributive g, Traversable g, AmbiguousAlternative (GrammarFunctor (p g s))) => g (Fixed p g s) -> g (SeparatedParser p g s)
Documentation
data SeparatedParser p (g :: (* -> *) -> *) s a Source #
FrontParser (p g s a) | |
CycleParser | |
| |
BackParser | |
|
class AmbiguityDecidable a Source #
ambiguityWitness
Instances
AmbiguityDecidable a Source # | |
Defined in Text.Grampa.Internal ambiguityWitness :: Maybe (AmbiguityWitness a) | |
AmbiguityDecidable (Ambiguous a) Source # | |
Defined in Text.Grampa.Internal ambiguityWitness :: Maybe (AmbiguityWitness (Ambiguous a)) |
lift :: Applicative m => m a -> ParserT m g s a Source #
Lift a parse-free computation into the parser.
liftPositive :: p g s a -> Fixed p g s a Source #
Lifts a primitive positive parser (i.e., one that always consumes some input) into a left-recursive one
tbind :: (Monad m, AmbiguityDecidable b) => ParserT m g s a -> (a -> m b) -> ParserT m g s b Source #
Transform the computation carried by the parser using the monadic bind (>>=
).
tmap :: AmbiguityDecidable b => (m a -> m b) -> ParserT m g s a -> ParserT m g s b Source #
Transform the computation carried by the parser.
parseSeparated :: forall p g rl s. (Apply g, Foldable g, Eq s, FactorialMonoid s, LeftReductive s, TailsParsing (p g s), GrammarConstraint (p g s) g, GrammarFunctor (p g s) ~ rl s, FallibleResults rl, s ~ ParserInput (p g s)) => g (SeparatedParser p g s) -> s -> [(s, g (GrammarFunctor (p g s)))] Source #
Parse the given input using a context-free grammar separated into two parts: the first specifying all the left-recursive productions, the second all others. The first function argument specifies the left-recursive dependencies among the grammar productions.
separated :: forall p g s. (Alternative (p g s), Apply g, Distributive g, Traversable g, AmbiguousAlternative (GrammarFunctor (p g s))) => g (Fixed p g s) -> g (SeparatedParser p g s) Source #