Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- newtype ParserT (m :: Type -> Type) (g :: (Type -> Type) -> Type) s r = Parser {
- applyParser :: [(s, g (ResultListT m g s))] -> ResultListT m g s r
- data ResultListT (m :: Type -> Type) (g :: (Type -> Type) -> Type) s r = ResultList ![ResultsOfLengthT m g s r] (ParseFailure Pos s)
- newtype ResultsOfLengthT (m :: Type -> Type) (g :: (Type -> Type) -> Type) s r = ResultsOfLengthT {
- getResultsOfLength :: ResultsOfLength m g s (m r)
- data ResultsOfLength (m :: Type -> Type) (g :: (Type -> Type) -> Type) s a = ROL !Int ![(s, g (ResultListT m g s))] !(NonEmpty a)
- tbind :: forall m (g :: (Type -> Type) -> Type) s a b. Monad m => ParserT m g s a -> (a -> m b) -> ParserT m g s b
- lift :: forall s m a (g :: (Type -> Type) -> Type). Ord s => m a -> ParserT m g s a
- tmap :: forall m a b (g :: (Type -> Type) -> Type) s. (m a -> m b) -> ParserT m g s a -> ParserT m g s b
- longest :: ParserT Identity g s a -> Parser g [(s, g (ResultListT Identity g s))] a
- peg :: forall (m :: Type -> Type) s g a. (Applicative m, Ord s) => Parser g [(s, g (ResultListT m g s))] a -> ParserT m g s a
- terminalPEG :: forall (m :: Type -> Type) s (g :: (Type -> Type) -> Type) a. (Applicative m, Monoid s, Ord s) => Parser g s a -> ParserT m g s a
Documentation
newtype ParserT (m :: Type -> Type) (g :: (Type -> Type) -> Type) 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
data ResultListT (m :: Type -> Type) (g :: (Type -> Type) -> Type) s r Source #
Constructors
ResultList ![ResultsOfLengthT m g s r] (ParseFailure Pos s) |
Instances
(Applicative m, Ord s) => Alternative (ResultListT m g s) Source # | |
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 # | |
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 # | |
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 # | |
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 # drain :: ResultListT (StateT state m) g s a -> ResultListT (StateT state m) g s b # | |
Traversable m => Filterable (ResultListT m g s) Source # | |
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 # drain :: ResultListT m g s a -> ResultListT m g s b # | |
Ord s => Monoid (ResultListT m g s r) Source # | |
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 # | |
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 :: Type -> Type) (g :: (Type -> Type) -> Type) s r Source #
Constructors
ResultsOfLengthT | |
Fields
|
Instances
(Applicative m, Ord s) => Applicative (ResultsOfLengthT m g s) Source # | |
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 # | |
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 :: Type -> Type) (g :: (Type -> Type) -> Type) s a Source #
Constructors
ROL !Int ![(s, g (ResultListT m g s))] !(NonEmpty a) |
Instances
(Applicative m, Ord s) => Applicative (ResultsOfLength m g s) Source # | |
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 # | |
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 :: forall m (g :: (Type -> Type) -> Type) s a b. 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 :: forall s m a (g :: (Type -> Type) -> Type). Ord s => m a -> ParserT m g s a Source #
Lift a parse-free computation into the parser.
tmap :: forall m a b (g :: (Type -> Type) -> Type) s. (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 :: forall (m :: Type -> Type) s g a. (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