pipes-4.0.1: Compositional pipelines

Safe HaskellSafe-Inferred

Pipes.Lift

Contents

Description

Many actions in base monad transformers cannot be automatically lifted. These functions lift these remaining actions so that they work in the Proxy monad transformer.

Synopsis

ErrorT

errorP :: (Monad m, Error e) => Proxy a' a b' b m (Either e r) -> Proxy a' a b' b (ErrorT e m) rSource

Wrap the base monad in ErrorT

runErrorP :: (Monad m, Error e) => Proxy a' a b' b (ErrorT e m) r -> Proxy a' a b' b m (Either e r)Source

Run ErrorT in the base monad

catchErrorSource

Arguments

:: (Monad m, Error e) 
=> Proxy a' a b' b (ErrorT e m) r 
-> (e -> Proxy a' a b' b (ErrorT e m) r) 
-> Proxy a' a b' b (ErrorT e m) r 

Catch an error in the base monad

liftCatchErrorSource

Arguments

:: Monad m 
=> (m (Proxy a' a b' b m r) -> (e -> m (Proxy a' a b' b m r)) -> m (Proxy a' a b' b m r)) 
-> Proxy a' a b' b m r -> (e -> Proxy a' a b' b m r) -> Proxy a' a b' b m r 

Catch an error using a catch function for the base monad

MaybeT

maybeP :: Monad m => Proxy a' a b' b m (Maybe r) -> Proxy a' a b' b (M.MaybeT m) rSource

Wrap the base monad in M.MaybeT

runMaybeP :: Monad m => Proxy a' a b' b (M.MaybeT m) r -> Proxy a' a b' b m (Maybe r)Source

Run M.MaybeT in the base monad

ReaderT

readerP :: Monad m => (i -> Proxy a' a b' b m r) -> Proxy a' a b' b (ReaderT i m) rSource

Wrap the base monad in ReaderT

runReaderP :: Monad m => i -> Proxy a' a b' b (ReaderT i m) r -> Proxy a' a b' b m rSource

Run ReaderT in the base monad

StateT

stateP :: Monad m => (s -> Proxy a' a b' b m (r, s)) -> Proxy a' a b' b (StateT s m) rSource

Wrap the base monad in StateT

runStateP :: Monad m => s -> Proxy a' a b' b (StateT s m) r -> Proxy a' a b' b m (r, s)Source

Run StateT in the base monad

evalStateP :: Monad m => s -> Proxy a' a b' b (StateT s m) r -> Proxy a' a b' b m rSource

Evaluate StateT in the base monad

execStateP :: Monad m => s -> Proxy a' a b' b (StateT s m) r -> Proxy a' a b' b m sSource

Execute StateT in the base monad

WriterT

Note that runWriterP and execWriterP will keep the accumulator in weak-head-normal form so that folds run in constant space when possible.

This means that until transformers adds a truly strict WriterT, you should consider unwrapping WriterT first using runWriterP or execWriterP before running your Proxy. You will get better performance this way and eliminate space leaks if your accumulator doesn't have any lazy fields.

writerP :: (Monad m, Monoid w) => Proxy a' a b' b m (r, w) -> Proxy a' a b' b (WriterT w m) rSource

Wrap the base monad in WriterT

runWriterP :: (Monad m, Monoid w) => Proxy a' a b' b (WriterT w m) r -> Proxy a' a b' b m (r, w)Source

Run WriterT in the base monad

execWriterP :: (Monad m, Monoid w) => Proxy a' a b' b (WriterT w m) r -> Proxy a' a b' b m wSource

Execute WriterT in the base monad

RWST

rwsP :: (Monad m, Monoid w) => (i -> s -> Proxy a' a b' b m (r, s, w)) -> Proxy a' a b' b (RWST i w s m) rSource

Wrap the base monad in RWST

runRWSP :: (Monad m, Monoid w) => r -> s -> Proxy a' a b' b (RWST r w s m) d -> Proxy a' a b' b m (d, s, w)Source

Run RWST in the base monad

evalRWSP :: (Monad m, Monoid w) => r -> s -> Proxy a' a b' b (RWST r w s m) d -> Proxy a' a b' b m (d, w)Source

Evaluate RWST in the base monad

execRWSP :: (Monad m, Monoid w) => r -> s -> Proxy a' a b' b (RWST r w s m) d -> Proxy a' a b' b m (s, w)Source

Execute RWST in the base monad

Utilities

distributeSource

Arguments

:: (Monad m, MonadTrans t, MFunctor t, Monad (t m), Monad (t (Proxy a' a b' b m))) 
=> Proxy a' a b' b (t m) r 
-> t (Proxy a' a b' b m) r 

Distribute Proxy over a monad transformer