grammatical-parsers-0.7.2.1: parsers that combine into grammars
Safe HaskellNone
LanguageHaskell2010

Text.Grampa.ContextFree.SortedMemoizing.Transformer.LeftRecursive

Description

A context-free parser that can handle ambiguous left-recursive grammars and carry a monadic computation with each parsing result.

Synopsis

Documentation

type ParserT (m :: Type -> Type) = Fixed (ParserT m) Source #

Parser transformer for left-recursive grammars on top of ParserT.

data SeparatedParser (p :: ((Type -> Type) -> Type) -> Type -> Type -> Type) (g :: (Type -> Type) -> Type) s a Source #

A type of parsers analyzed for their left-recursion class

Constructors

FrontParser (p g s a)

a parser that no left-recursive nonterminal depends on

CycleParser

a left-recursive parser that may add to the set of parse results every time it's run

Fields

BackParser

a parser that doesn't start with any nonTerminal so it can run first

Fields

class AmbiguityDecidable a Source #

Minimal complete definition

ambiguityWitness

Instances

Instances details
AmbiguityDecidable a Source # 
Instance details

Defined in Text.Grampa.Internal

Methods

ambiguityWitness :: Maybe (AmbiguityWitness a)

AmbiguityDecidable (Ambiguous a) Source # 
Instance details

Defined in Text.Grampa.Internal

Methods

ambiguityWitness :: Maybe (AmbiguityWitness (Ambiguous a))

lift :: forall m s a (g :: (Type -> Type) -> Type). (Applicative m, Ord s) => m a -> ParserT m g s a Source #

Lift a parse-free computation into the parser.

liftPositive :: forall p (g :: (Type -> Type) -> Type) s a. 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 :: forall m b (g :: (Type -> Type) -> Type) s a. (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 :: forall b m a (g :: (Type -> Type) -> Type) s. AmbiguityDecidable b => (m a -> m b) -> ParserT m g s a -> ParserT m g s b Source #

Transform the computation carried by the parser.

autochain :: forall (p :: ((Type -> Type) -> Type) -> Type -> Type -> Type) g s (f :: Type -> Type) (rl :: Type -> Type -> Type) (cb :: Type -> Type). (cb ~ (Const (g (Const Bool :: Type -> Type)) :: Type -> Type), f ~ GrammarFunctor (p g s), f ~ rl s, LeftRecParsing p g s rl, DeterministicParsing (p g s), Apply g, Traversable g, Distributive g, Logistic g) => g (Fixed p g s) -> g (Fixed p g s) Source #

Automatically apply chainRecursive and chainLongestRecursive to left-recursive grammar productions where possible.

parseSeparated :: forall (p :: ((Type -> Type) -> Type) -> Type -> Type -> Type) g (rl :: Type -> Type -> Type) 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 left-recursive and other productions.

separated :: forall (p :: ((Type -> Type) -> Type) -> Type -> Type -> Type) 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 #

Analyze the grammar's production interdependencies and produce a SeparatedParser from each production's parser.