Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Element-agnostic parsing utilities for pipes
See Pipes.Parse.Tutorial for an extended tutorial
Synopsis
- type Parser a m r = forall x. StateT (Producer a m x) m r
- draw :: Monad m => Parser a m (Maybe a)
- skip :: Monad m => Parser a m Bool
- drawAll :: Monad m => Parser a m [a]
- skipAll :: Monad m => Parser a m ()
- unDraw :: Monad m => a -> Parser a m ()
- peek :: Monad m => Parser a m (Maybe a)
- isEndOfInput :: Monad m => Parser a m Bool
- foldAll :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Parser a m b
- foldAllM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Parser a m b
- span :: Monad m => (a -> Bool) -> Lens' (Producer a m x) (Producer a m (Producer a m x))
- splitAt :: Monad m => Int -> Lens' (Producer a m x) (Producer a m (Producer a m x))
- groupBy :: Monad m => (a -> a -> Bool) -> Lens' (Producer a m x) (Producer a m (Producer a m x))
- group :: (Monad m, Eq a) => Lens' (Producer a m x) (Producer a m (Producer a m x))
- toParser :: Monad m => Consumer (Maybe a) m r -> Parser a m r
- toParser_ :: Monad m => Consumer a m X -> Parser a m ()
- parsed :: Monad m => Parser a m (Either e b) -> Producer a m r -> Producer b m (e, Producer a m r)
- parsed_ :: Monad m => Parser a m (Maybe b) -> Producer a m r -> Producer b m (Producer a m r)
- parseForever :: Monad m => (forall n. Monad n => Parser a n (Either r b)) -> Pipe a b m r
- parseForever_ :: Monad m => (forall n. Monad n => Parser a n (Maybe b)) -> Pipe a b m ()
- lift :: (MonadTrans t, Monad m) => m a -> t m a
- newtype StateT s (m :: Type -> Type) a = StateT {
- runStateT :: s -> m (a, s)
- evalStateT :: Monad m => StateT s m a -> s -> m a
- execStateT :: Monad m => StateT s m a -> s -> m s
- next :: Monad m => Producer a m r -> m (Either r (a, Producer a m r))
- yield :: forall (m :: Type -> Type) a x' x. Functor m => a -> Proxy x' x () a m ()
- type Producer b = Proxy X () () b
Parsing
pipes-parse
handles end-of-input and pushback by storing a Producer
in
a StateT
layer.
Connect Parser
s to Producer
s using either runStateT
, evalStateT
, or
execStateT
:
runStateT :: Parser a m r -> Producer a m x -> m (r, Producer a m x) evalStateT :: Parser a m r -> Producer a m x -> m r execStateT :: Parser a m r -> Producer a m x -> m (Producer a m x) ^^^^^^^^^^^^^^ Leftovers
drawAll :: Monad m => Parser a m [a] Source #
Draw all elements from the underlying Producer
Note that drawAll
is not an idiomatic use of pipes-parse
, but I provide
it for simple testing purposes. Idiomatic pipes-parse
style consumes the
elements immediately as they are generated instead of loading all elements
into memory. For example, you can use foldAll
or foldAllM
for this
purpose.
isEndOfInput :: Monad m => Parser a m Bool Source #
Check if the underlying Producer
is empty
isEndOfInput = fmap isNothing peek
:: Monad m | |
=> (x -> a -> x) | Step function |
-> x | Initial accumulator |
-> (x -> b) | Extraction function |
-> Parser a m b |
Fold all input values
Control.Foldl.purely foldAll :: Monad m => Fold a b -> Parser a m b
:: Monad m | |
=> (x -> a -> m x) | Step function |
-> m x | Initial accumulator |
-> (x -> m b) | Extraction function |
-> Parser a m b |
Fold all input values monadically
Control.Foldl.impurely foldAllM :: Monad m => FoldM a m b -> Parser a m b
Parsing Lenses
Connect lenses to Producer
s using (^.
) or
view
:
(^.) :: Producer a m x -> Lens' (Producer a m x) (Producer b m y) -> Producer b m y
Connect lenses to Parser
s using zoom
:
zoom :: Lens' (Producer a m x) (Producer b m y) -> Parser b m r -> Parser a m r
Connect lenses to each other using (.
) (i.e. function composition):
(.) :: Lens' (Producer a m x) (Producer b m y) -> Lens' (Producer b m y) (Producer c m z) -> Lens' (Producer a m y) (Producer c m z)
groupBy :: Monad m => (a -> a -> Bool) -> Lens' (Producer a m x) (Producer a m (Producer a m x)) Source #
Utilities
parsed :: Monad m => Parser a m (Either e b) -> Producer a m r -> Producer b m (e, Producer a m r) Source #
parsed_ :: Monad m => Parser a m (Maybe b) -> Producer a m r -> Producer b m (Producer a m r) Source #
parseForever_ :: Monad m => (forall n. Monad n => Parser a n (Maybe b)) -> Pipe a b m () Source #
Deprecated: Use parsed_
instead
Variant of parseForever
for parsers which return a Maybe
instead of an Either
Re-exports
Control.Monad.Trans.Class re-exports lift
.
Control.Monad.Trans.State.Strict re-exports StateT
, runStateT
,
evalStateT
, and execStateT
.
lift :: (MonadTrans t, Monad m) => m a -> t m a #
Lift a computation from the argument monad to the constructed monad.
newtype StateT s (m :: Type -> Type) a #
A state transformer monad parameterized by:
s
- The state.m
- The inner monad.
The return
function leaves the state unchanged, while >>=
uses
the final state of the first computation as the initial state of
the second.
Instances
MonadTrans (StateT s) | |
Defined in Control.Monad.Trans.State.Strict | |
MFunctor (StateT s :: (Type -> Type) -> Type -> Type) | |
Monad m => Monad (StateT s m) | |
Functor m => Functor (StateT s m) | |
MonadFix m => MonadFix (StateT s m) | |
Defined in Control.Monad.Trans.State.Strict | |
MonadFail m => MonadFail (StateT s m) | |
Defined in Control.Monad.Trans.State.Strict | |
(Functor m, Monad m) => Applicative (StateT s m) | |
Defined in Control.Monad.Trans.State.Strict | |
Contravariant m => Contravariant (StateT s m) | |
MonadIO m => MonadIO (StateT s m) | |
Defined in Control.Monad.Trans.State.Strict | |
(Functor m, MonadPlus m) => Alternative (StateT s m) | |
MonadPlus m => MonadPlus (StateT s m) | |
evalStateT :: Monad m => StateT s m a -> s -> m a #
Evaluate a state computation with the given initial state and return the final value, discarding the final state.
evalStateT
m s =liftM
fst
(runStateT
m s)
execStateT :: Monad m => StateT s m a -> s -> m s #
Evaluate a state computation with the given initial state and return the final state, discarding the final value.
execStateT
m s =liftM
snd
(runStateT
m s)