grammatical-parsers-0.7: parsers that combine into grammars
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.Grampa.ContextFree.Memoizing.LeftRecursive

Description

A context-free memoizing parser that can handle left-recursive grammars.

Synopsis

Documentation

data Fixed p g s a Source #

A transformer that adds left-recursive powers to a memoizing parser p over grammar g

Instances

Instances details
(Apply g, Alternative (p g s), MonadFail (p g s)) => MonadFail (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Methods

fail :: String -> Fixed p g s a #

(Apply g, Alternative (p g s)) => Alternative (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Methods

empty :: Fixed p g s a #

(<|>) :: Fixed p g s a -> Fixed p g s a -> Fixed p g s a #

some :: Fixed p g s a -> Fixed p g s [a] #

many :: Fixed p g s a -> Fixed p g s [a] #

(Apply g, Alternative (p g s)) => Applicative (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Methods

pure :: a -> Fixed p g s a #

(<*>) :: Fixed p g s (a -> b) -> Fixed p g s a -> Fixed p g s b #

liftA2 :: (a -> b -> c) -> Fixed p g s a -> Fixed p g s b -> Fixed p g s c #

(*>) :: Fixed p g s a -> Fixed p g s b -> Fixed p g s b #

(<*) :: Fixed p g s a -> Fixed p g s b -> Fixed p g s a #

Functor (p g s) => Functor (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Methods

fmap :: (a -> b) -> Fixed p g s a -> Fixed p g s b #

(<$) :: a -> Fixed p g s b -> Fixed p g s a #

(Apply g, Alternative (p g s), Monad (p g s)) => Monad (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Methods

(>>=) :: Fixed p g s a -> (a -> Fixed p g s b) -> Fixed p g s b #

(>>) :: Fixed p g s a -> Fixed p g s b -> Fixed p g s b #

return :: a -> Fixed p g s a #

(Apply g, MonadPlus (p g s)) => MonadPlus (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Methods

mzero :: Fixed p g s a #

mplus :: Fixed p g s a -> Fixed p g s a -> Fixed p g s a #

(AmbiguousParsing (p g s), Apply g) => AmbiguousParsing (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Methods

ambiguous :: Fixed p g s a -> Fixed p g s (Ambiguous a) Source #

(Apply g, CommittedParsing (p g s), CommittedResults (p g s) ~ ParseResults s) => CommittedParsing (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Associated Types

type CommittedResults (Fixed p g s) :: Type -> Type Source #

Methods

commit :: Fixed p g s a -> Fixed p g s (CommittedResults (Fixed p g s) a) Source #

admit :: Fixed p g s (CommittedResults (Fixed p g s) a) -> Fixed p g s a Source #

(Apply g, GrammarFunctor (p g s) ~ f s, LeftRecParsing p g s f) => GrammarParsing (Fixed p g s) Source #

Parser transformer for left-recursive grammars.

Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Associated Types

type ParserGrammar (Fixed p g s) :: (Type -> Type) -> Type Source #

type GrammarFunctor (Fixed p g s) :: Type -> Type Source #

Methods

parsingResult :: ParserInput (Fixed p g s) -> GrammarFunctor (Fixed p g s) a -> ResultFunctor (Fixed p g s) (ParserInput (Fixed p g s), a) Source #

nonTerminal :: (g0 ~ ParserGrammar (Fixed p g s), GrammarConstraint (Fixed p g s) g0) => (g0 (GrammarFunctor (Fixed p g s)) -> GrammarFunctor (Fixed p g s) a) -> Fixed p g s a Source #

selfReferring :: (g0 ~ ParserGrammar (Fixed p g s), GrammarConstraint (Fixed p g s) g0, Distributive g0) => g0 (Fixed p g s) Source #

fixGrammar :: (g0 ~ ParserGrammar (Fixed p g s), GrammarConstraint (Fixed p g s) g0, Distributive g0) => (g0 (Fixed p g s) -> g0 (Fixed p g s)) -> g0 (Fixed p g s) Source #

recursive :: Fixed p g s a -> Fixed p g s a Source #

chainRecursive :: (g0 ~ ParserGrammar (Fixed p g s), f ~ GrammarFunctor (Fixed p g s), GrammarConstraint (Fixed p g s) g0) => (f a -> g0 f -> g0 f) -> Fixed p g s a -> Fixed p g s a -> Fixed p g s a Source #

chainLongestRecursive :: (g0 ~ ParserGrammar (Fixed p g s), f ~ GrammarFunctor (Fixed p g s), GrammarConstraint (Fixed p g s) g0) => (f a -> g0 f -> g0 f) -> Fixed p g s a -> Fixed p g s a -> Fixed p g s a Source #

(Apply g, GrammarFunctor (p g s) ~ f s, LeftRecParsing p g s f) => MultiParsing (Fixed p g s) Source #

Parser transformer for left-recursive grammars.

parseComplete :: (Rank2.Apply g, Rank2.Traversable g, FactorialMonoid s) =>
                 g (LeftRecursive.Parser g s) -> s -> g (Compose (ParseResults s) [])
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Associated Types

type ResultFunctor (Fixed p g s) :: Type -> Type Source #

type GrammarConstraint (Fixed p g s) g Source #

Methods

parseComplete :: (ParserInput (Fixed p g s) ~ s0, GrammarConstraint (Fixed p g s) g0, Eq s0, FactorialMonoid s0) => g0 (Fixed p g s) -> s0 -> g0 (ResultFunctor (Fixed p g s)) Source #

parsePrefix :: (ParserInput (Fixed p g s) ~ s0, GrammarConstraint (Fixed p g s) g0, Eq s0, FactorialMonoid s0) => g0 (Fixed p g s) -> s0 -> g0 (Compose (ResultFunctor (Fixed p g s)) ((,) s0)) Source #

(Apply g, LeftReductive s, FactorialMonoid s, Show s, TraceableParsing (p g s), ParserInput (p g s) ~ s) => TraceableParsing (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Methods

traceInput :: (ParserInput (Fixed p g s) -> String) -> Fixed p g s a -> Fixed p g s a Source #

traceAs :: Show (ParserInput (Fixed p g s)) => String -> Fixed p g s a -> Fixed p g s a Source #

(Apply g, InputParsing (Fixed p g s), DeterministicParsing (p g s)) => DeterministicParsing (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Methods

(<<|>) :: Fixed p g s a -> Fixed p g s a -> Fixed p g s a #

takeOptional :: Fixed p g s a -> Fixed p g s (Maybe a) #

takeMany :: Fixed p g s a -> Fixed p g s [a] #

takeSome :: Fixed p g s a -> Fixed p g s [a] #

concatAll :: Monoid a => Fixed p g s a -> Fixed p g s a #

skipAll :: Fixed p g s a -> Fixed p g s () #

(Apply g, LeftReductive s, FactorialMonoid s, ConsumedInputParsing (p g s), ParserInput (p g s) ~ s) => ConsumedInputParsing (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Methods

match :: Fixed p g s a -> Fixed p g s (ParserInput (Fixed p g s), a) #

(Apply g, Show s, TextualMonoid s, InputCharParsing (p g s), ParserInput (p g s) ~ s) => InputCharParsing (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Methods

satisfyCharInput :: (Char -> Bool) -> Fixed p g s (ParserInput (Fixed p g s)) #

notSatisfyChar :: (Char -> Bool) -> Fixed p g s () #

scanChars :: state -> (state -> Char -> Maybe state) -> Fixed p g s (ParserInput (Fixed p g s)) #

takeCharsWhile :: (Char -> Bool) -> Fixed p g s (ParserInput (Fixed p g s)) #

takeCharsWhile1 :: (Char -> Bool) -> Fixed p g s (ParserInput (Fixed p g s)) #

(Apply g, LeftReductive s, FactorialMonoid s, InputParsing (p g s), ParserInput (p g s) ~ s) => InputParsing (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Associated Types

type ParserInput (Fixed p g s) #

type ParserPosition (Fixed p g s) #

Methods

getInput :: Fixed p g s (ParserInput (Fixed p g s)) #

getSourcePos :: Fixed p g s (ParserPosition (Fixed p g s)) #

anyToken :: Fixed p g s (ParserInput (Fixed p g s)) #

take :: Int -> Fixed p g s (ParserInput (Fixed p g s)) #

satisfy :: (ParserInput (Fixed p g s) -> Bool) -> Fixed p g s (ParserInput (Fixed p g s)) #

notSatisfy :: (ParserInput (Fixed p g s) -> Bool) -> Fixed p g s () #

scan :: state -> (state -> ParserInput (Fixed p g s) -> Maybe state) -> Fixed p g s (ParserInput (Fixed p g s)) #

string :: ParserInput (Fixed p g s) -> Fixed p g s (ParserInput (Fixed p g s)) #

takeWhile :: (ParserInput (Fixed p g s) -> Bool) -> Fixed p g s (ParserInput (Fixed p g s)) #

takeWhile1 :: (ParserInput (Fixed p g s) -> Bool) -> Fixed p g s (ParserInput (Fixed p g s)) #

(Apply g, CharParsing (p g s), InputCharParsing (Fixed p g s), TextualMonoid s, s ~ ParserInput (Fixed p g s), Show s) => CharParsing (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Methods

satisfy :: (Char -> Bool) -> Fixed p g s Char #

char :: Char -> Fixed p g s Char #

notChar :: Char -> Fixed p g s Char #

anyChar :: Fixed p g s Char #

string :: String -> Fixed p g s String #

text :: Text -> Fixed p g s Text #

(Apply g, Parsing (p g s), InputParsing (Fixed p g s)) => Parsing (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Methods

try :: Fixed p g s a -> Fixed p g s a #

(<?>) :: Fixed p g s a -> String -> Fixed p g s a #

skipMany :: Fixed p g s a -> Fixed p g s () #

skipSome :: Fixed p g s a -> Fixed p g s () #

unexpected :: String -> Fixed p g s a #

eof :: Fixed p g s () #

notFollowedBy :: Show a => Fixed p g s a -> Fixed p g s () #

(Apply g, LookAheadParsing (p g s), InputParsing (Fixed p g s)) => LookAheadParsing (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Methods

lookAhead :: Fixed p g s a -> Fixed p g s a #

Filterable (p g s) => Filterable (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Methods

mapMaybe :: (a -> Maybe b) -> Fixed p g s a -> Fixed p g s b #

catMaybes :: Fixed p g s (Maybe a) -> Fixed p g s a #

filter :: (a -> Bool) -> Fixed p g s a -> Fixed p g s a #

(Apply g, Alternative (p g s), Monoid x) => Monoid (Fixed p g s x) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Methods

mempty :: Fixed p g s x #

mappend :: Fixed p g s x -> Fixed p g s x -> Fixed p g s x #

mconcat :: [Fixed p g s x] -> Fixed p g s x #

(Apply g, Alternative (p g s), Semigroup x) => Semigroup (Fixed p g s x) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

Methods

(<>) :: Fixed p g s x -> Fixed p g s x -> Fixed p g s x #

sconcat :: NonEmpty (Fixed p g s x) -> Fixed p g s x #

stimes :: Integral b => b -> Fixed p g s x -> Fixed p g s x #

type CommittedResults (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

type GrammarFunctor (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

type GrammarFunctor (Fixed p g s) = GrammarFunctor (p g s)
type ParserGrammar (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

type ParserGrammar (Fixed p g s) = g
type ResultFunctor (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

type ResultFunctor (Fixed p g s) = ResultFunctor (p g s)
type ParserInput (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

type ParserInput (Fixed p g s) = s
type ParserPosition (Fixed p g s) Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

type ParserPosition (Fixed p g s) = Down Int
type GrammarConstraint (Fixed p g s) g' Source # 
Instance details

Defined in Text.Grampa.Internal.LeftRecursive

type GrammarConstraint (Fixed p g s) g' = (GrammarConstraint (p g s) g', g ~ g', Apply g, Distributive g, Traversable g)

type Parser = Fixed Parser Source #

A parser for left-recursive grammars on top of the memoizing Parser

data SeparatedParser p (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

autochain :: forall p g s f rl (cb :: Type -> Type). (cb ~ Const (g (Const Bool)), 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.

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

liftPure :: Alternative (p g s) => p g s a -> Fixed p g s a Source #

Lifts a primitive pure parser (i.e., one that consumes no input) into a left-recursive one

mapPrimitive :: forall p g s a b. AmbiguityDecidable b => (p g s a -> p g s b) -> Fixed p g s a -> Fixed p g s b Source #

longest :: Fixed Parser g s a -> Fixed Parser g [(s, g (ResultList g s))] a Source #

Turns a context-free parser into a backtracking PEG parser that consumes the longest possible prefix of the list of input tails, opposite of peg

peg :: Ord s => Fixed Parser g [(s, g (ResultList g s))] a -> Fixed Parser g s a Source #

Turns a backtracking PEG parser of the list of input tails into a context-free parser, opposite of longest

terminalPEG :: (Monoid s, Ord s) => Fixed Parser g s a -> Fixed Parser g s a Source #

Turns a backtracking PEG parser into a context-free 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 left-recursive and other 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 #

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