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

Text.Grampa.ContextFree.SortedMemoizing.Transformer

Description

A context-free memoizing parser that handles all alternatives in parallel and carries a monadic computation with each parsing result.

Synopsis

Documentation

newtype ParserT m g s r Source #

Parser for a context-free grammar with packrat-like sharing that carries a monadic computation as part of the parse result.

Constructors

Parser 

Fields

Instances

Instances details
(Monad m, Traversable m, Ord s) => MonadFail (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

fail :: String -> ParserT m g s a #

(Applicative m, Ord s) => Alternative (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

empty :: ParserT m g s a #

(<|>) :: ParserT m g s a -> ParserT m g s a -> ParserT m g s a #

some :: ParserT m g s a -> ParserT m g s [a] #

many :: ParserT m g s a -> ParserT m g s [a] #

(Applicative m, Ord s) => Applicative (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

pure :: a -> ParserT m g s a #

(<*>) :: ParserT m g s (a -> b) -> ParserT m g s a -> ParserT m g s b #

liftA2 :: (a -> b -> c) -> ParserT m g s a -> ParserT m g s b -> ParserT m g s c #

(*>) :: ParserT m g s a -> ParserT m g s b -> ParserT m g s b #

(<*) :: ParserT m g s a -> ParserT m g s b -> ParserT m g s a #

Functor m => Functor (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

fmap :: (a -> b) -> ParserT m g s a -> ParserT m g s b #

(<$) :: a -> ParserT m g s b -> ParserT m g s a #

(Monad m, Traversable m, Ord s) => Monad (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

(>>=) :: ParserT m g s a -> (a -> ParserT m g s b) -> ParserT m g s b #

(>>) :: ParserT m g s a -> ParserT m g s b -> ParserT m g s b #

return :: a -> ParserT m g s a #

(Foldable m, Monad m, Traversable m, Ord s) => MonadPlus (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

mzero :: ParserT m g s a #

mplus :: ParserT m g s a -> ParserT m g s a -> ParserT m g s a #

(Applicative m, Eq (m ()), Ord s) => AmbiguousParsing (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

ambiguous :: ParserT m g s a -> ParserT m g s (Ambiguous a) Source #

(Applicative m, Traversable m, Ord s) => CommittedParsing (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Associated Types

type CommittedResults (ParserT m g s) :: Type -> Type Source #

Methods

commit :: ParserT m g s a -> ParserT m g s (CommittedResults (ParserT m g s) a) Source #

admit :: ParserT m g s (CommittedResults (ParserT m g s) a) -> ParserT m g s a Source #

(Applicative m, Ord s, LeftReductive s, FactorialMonoid s) => GrammarParsing (ParserT m g s) Source #

Memoizing parser that carries an applicative computation. Can be wrapped with Fixed to provide left recursion support.

Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Associated Types

type ParserGrammar (ParserT m g s) :: (Type -> Type) -> Type Source #

type GrammarFunctor (ParserT m g s) :: Type -> Type Source #

Methods

parsingResult :: ParserInput (ParserT m g s) -> GrammarFunctor (ParserT m g s) a -> ResultFunctor (ParserT m g s) (ParserInput (ParserT m g s), a) Source #

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

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

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

recursive :: ParserT m g s a -> ParserT m g s a Source #

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

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

(Applicative m, LeftReductive s, FactorialMonoid s, Ord s) => MultiParsing (ParserT m g s) Source #

Memoizing parser that carries an applicative computation. Can be wrapped with Fixed to provide left recursion support.

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

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Associated Types

type ResultFunctor (ParserT m g s) :: Type -> Type Source #

type GrammarConstraint (ParserT m g s) g Source #

Methods

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

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

(InputParsing (ParserT m g s), FactorialMonoid s) => TraceableParsing (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

traceInput :: (ParserInput (ParserT m g s) -> String) -> ParserT m g s a -> ParserT m g s a Source #

traceAs :: Show (ParserInput (ParserT m g s)) => String -> ParserT m g s a -> ParserT m g s a Source #

(Applicative m, MonoidNull s, Ord s) => DeterministicParsing (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

(<<|>) :: ParserT m g s a -> ParserT m g s a -> ParserT m g s a #

takeOptional :: ParserT m g s a -> ParserT m g s (Maybe a) #

takeMany :: ParserT m g s a -> ParserT m g s [a] #

takeSome :: ParserT m g s a -> ParserT m g s [a] #

concatAll :: Monoid a => ParserT m g s a -> ParserT m g s a #

skipAll :: ParserT m g s a -> ParserT m g s () #

(Applicative m, LeftReductive s, FactorialMonoid s, Ord s) => ConsumedInputParsing (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

match :: ParserT m g s a -> ParserT m g s (ParserInput (ParserT m g s), a) #

(Applicative m, Ord s, Show s, TextualMonoid s) => InputCharParsing (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

satisfyCharInput :: (Char -> Bool) -> ParserT m g s (ParserInput (ParserT m g s)) #

notSatisfyChar :: (Char -> Bool) -> ParserT m g s () #

scanChars :: state -> (state -> Char -> Maybe state) -> ParserT m g s (ParserInput (ParserT m g s)) #

takeCharsWhile :: (Char -> Bool) -> ParserT m g s (ParserInput (ParserT m g s)) #

takeCharsWhile1 :: (Char -> Bool) -> ParserT m g s (ParserInput (ParserT m g s)) #

(Applicative m, LeftReductive s, FactorialMonoid s, Ord s) => InputParsing (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Associated Types

type ParserInput (ParserT m g s) #

type ParserPosition (ParserT m g s) #

Methods

getInput :: ParserT m g s (ParserInput (ParserT m g s)) #

getSourcePos :: ParserT m g s (ParserPosition (ParserT m g s)) #

anyToken :: ParserT m g s (ParserInput (ParserT m g s)) #

take :: Int -> ParserT m g s (ParserInput (ParserT m g s)) #

satisfy :: (ParserInput (ParserT m g s) -> Bool) -> ParserT m g s (ParserInput (ParserT m g s)) #

notSatisfy :: (ParserInput (ParserT m g s) -> Bool) -> ParserT m g s () #

scan :: state -> (state -> ParserInput (ParserT m g s) -> Maybe state) -> ParserT m g s (ParserInput (ParserT m g s)) #

string :: ParserInput (ParserT m g s) -> ParserT m g s (ParserInput (ParserT m g s)) #

takeWhile :: (ParserInput (ParserT m g s) -> Bool) -> ParserT m g s (ParserInput (ParserT m g s)) #

takeWhile1 :: (ParserInput (ParserT m g s) -> Bool) -> ParserT m g s (ParserInput (ParserT m g s)) #

(Applicative m, Ord s, Show s, TextualMonoid s) => CharParsing (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

satisfy :: (Char -> Bool) -> ParserT m g s Char #

char :: Char -> ParserT m g s Char #

notChar :: Char -> ParserT m g s Char #

anyChar :: ParserT m g s Char #

string :: String -> ParserT m g s String #

text :: Text -> ParserT m g s Text #

(Applicative m, MonoidNull s, Ord s) => Parsing (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

try :: ParserT m g s a -> ParserT m g s a #

(<?>) :: ParserT m g s a -> String -> ParserT m g s a #

skipMany :: ParserT m g s a -> ParserT m g s () #

skipSome :: ParserT m g s a -> ParserT m g s () #

unexpected :: String -> ParserT m g s a #

eof :: ParserT m g s () #

notFollowedBy :: Show a => ParserT m g s a -> ParserT m g s () #

(Applicative m, MonoidNull s, Ord s) => LookAheadParsing (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

lookAhead :: ParserT m g s a -> ParserT m g s a #

(Monad m, Traversable m, Monoid state) => Filterable (ParserT (StateT state m) g s) Source #

The StateT instance dangerously assumes that the filtered parser is stateless.

Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

mapMaybe :: (a -> Maybe b) -> ParserT (StateT state m) g s a -> ParserT (StateT state m) g s b #

catMaybes :: ParserT (StateT state m) g s (Maybe a) -> ParserT (StateT state m) g s a #

filter :: (a -> Bool) -> ParserT (StateT state m) g s a -> ParserT (StateT state m) g s a #

(Applicative m, Traversable m) => Filterable (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

mapMaybe :: (a -> Maybe b) -> ParserT m g s a -> ParserT m g s b #

catMaybes :: ParserT m g s (Maybe a) -> ParserT m g s a #

filter :: (a -> Bool) -> ParserT m g s a -> ParserT m g s a #

(Applicative m, Monoid x, Ord s) => Monoid (ParserT m g s x) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

mempty :: ParserT m g s x #

mappend :: ParserT m g s x -> ParserT m g s x -> ParserT m g s x #

mconcat :: [ParserT m g s x] -> ParserT m g s x #

(Applicative m, Semigroup x, Ord s) => Semigroup (ParserT m g s x) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

(<>) :: ParserT m g s x -> ParserT m g s x -> ParserT m g s x #

sconcat :: NonEmpty (ParserT m g s x) -> ParserT m g s x #

stimes :: Integral b => b -> ParserT m g s x -> ParserT m g s x #

type CommittedResults (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

type GrammarFunctor (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

type GrammarFunctor (ParserT m g s) = ResultListT m g s
type ParserGrammar (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

type ParserGrammar (ParserT m g s) = g
type ResultFunctor (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

type ParserInput (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

type ParserInput (ParserT m g s) = s
type ParserPosition (ParserT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

type GrammarConstraint (ParserT m g s) g' Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

type GrammarConstraint (ParserT m g s) g' = (g ~ g', Functor g)

data ResultListT m g s r Source #

Constructors

ResultList ![ResultsOfLengthT m g s r] (ParseFailure Pos s) 

Instances

Instances details
(Applicative m, Ord s) => Alternative (ResultListT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

empty :: ResultListT m g s a #

(<|>) :: ResultListT m g s a -> ResultListT m g s a -> ResultListT m g s a #

some :: ResultListT m g s a -> ResultListT m g s [a] #

many :: ResultListT m g s a -> ResultListT m g s [a] #

(Applicative m, Ord s) => Applicative (ResultListT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

pure :: a -> ResultListT m g s a #

(<*>) :: ResultListT m g s (a -> b) -> ResultListT m g s a -> ResultListT m g s b #

liftA2 :: (a -> b -> c) -> ResultListT m g s a -> ResultListT m g s b -> ResultListT m g s c #

(*>) :: ResultListT m g s a -> ResultListT m g s b -> ResultListT m g s b #

(<*) :: ResultListT m g s a -> ResultListT m g s b -> ResultListT m g s a #

Functor m => Functor (ResultListT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

fmap :: (a -> b) -> ResultListT m g s a -> ResultListT m g s b #

(<$) :: a -> ResultListT m g s b -> ResultListT m g s a #

(Monad m, Traversable m, Monoid state) => Filterable (ResultListT (StateT state m) g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

mapMaybe :: (a -> Maybe b) -> ResultListT (StateT state m) g s a -> ResultListT (StateT state m) g s b #

catMaybes :: ResultListT (StateT state m) g s (Maybe a) -> ResultListT (StateT state m) g s a #

filter :: (a -> Bool) -> ResultListT (StateT state m) g s a -> ResultListT (StateT state m) g s a #

Traversable m => Filterable (ResultListT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

mapMaybe :: (a -> Maybe b) -> ResultListT m g s a -> ResultListT m g s b #

catMaybes :: ResultListT m g s (Maybe a) -> ResultListT m g s a #

filter :: (a -> Bool) -> ResultListT m g s a -> ResultListT m g s a #

Ord s => Monoid (ResultListT m g s r) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

mempty :: ResultListT m g s r #

mappend :: ResultListT m g s r -> ResultListT m g s r -> ResultListT m g s r #

mconcat :: [ResultListT m g s r] -> ResultListT m g s r #

Ord s => Semigroup (ResultListT m g s r) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

(<>) :: ResultListT m g s r -> ResultListT m g s r -> ResultListT m g s r #

sconcat :: NonEmpty (ResultListT m g s r) -> ResultListT m g s r #

stimes :: Integral b => b -> ResultListT m g s r -> ResultListT m g s r #

newtype ResultsOfLengthT m g s r Source #

Constructors

ResultsOfLengthT 

Fields

Instances

Instances details
(Applicative m, Ord s) => Applicative (ResultsOfLengthT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

pure :: a -> ResultsOfLengthT m g s a #

(<*>) :: ResultsOfLengthT m g s (a -> b) -> ResultsOfLengthT m g s a -> ResultsOfLengthT m g s b #

liftA2 :: (a -> b -> c) -> ResultsOfLengthT m g s a -> ResultsOfLengthT m g s b -> ResultsOfLengthT m g s c #

(*>) :: ResultsOfLengthT m g s a -> ResultsOfLengthT m g s b -> ResultsOfLengthT m g s b #

(<*) :: ResultsOfLengthT m g s a -> ResultsOfLengthT m g s b -> ResultsOfLengthT m g s a #

Functor m => Functor (ResultsOfLengthT m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

fmap :: (a -> b) -> ResultsOfLengthT m g s a -> ResultsOfLengthT m g s b #

(<$) :: a -> ResultsOfLengthT m g s b -> ResultsOfLengthT m g s a #

data ResultsOfLength m g s a Source #

Constructors

ROL !Int ![(s, g (ResultListT m g s))] !(NonEmpty a) 

Instances

Instances details
(Applicative m, Ord s) => Applicative (ResultsOfLength m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

pure :: a -> ResultsOfLength m g s a #

(<*>) :: ResultsOfLength m g s (a -> b) -> ResultsOfLength m g s a -> ResultsOfLength m g s b #

liftA2 :: (a -> b -> c) -> ResultsOfLength m g s a -> ResultsOfLength m g s b -> ResultsOfLength m g s c #

(*>) :: ResultsOfLength m g s a -> ResultsOfLength m g s b -> ResultsOfLength m g s b #

(<*) :: ResultsOfLength m g s a -> ResultsOfLength m g s b -> ResultsOfLength m g s a #

Functor (ResultsOfLength m g s) Source # 
Instance details

Defined in Text.Grampa.ContextFree.SortedMemoizing.Transformer

Methods

fmap :: (a -> b) -> ResultsOfLength m g s a -> ResultsOfLength m g s b #

(<$) :: a -> ResultsOfLength m g s b -> ResultsOfLength m g s a #

tbind :: Monad m => 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 (>>=).

lift :: Ord s => m a -> ParserT m g s a Source #

Lift a parse-free computation into the parser.

tmap :: (m a -> m b) -> ParserT m g s a -> ParserT m g s b Source #

Transform the computation carried by the parser.

longest :: ParserT Identity g s a -> Parser g [(s, g (ResultListT Identity 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 :: (Applicative m, Ord s) => Parser g [(s, g (ResultListT m g s))] a -> ParserT m g s a Source #

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

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

Turns a backtracking PEG parser into a context-free parser