| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Pipes.Lift
Description
- distribute :: (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
- errorP :: (Monad m, Error e) => Proxy a' a b' b m (Either e r) -> Proxy a' a b' b (ErrorT e m) r
- runErrorP :: (Monad m, Error e) => Proxy a' a b' b (ErrorT e m) r -> Proxy a' a b' b m (Either e r)
- catchError :: (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
- liftCatchError :: 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
- maybeP :: Monad m => Proxy a' a b' b m (Maybe r) -> Proxy a' a b' b (MaybeT m) r
- runMaybeP :: Monad m => Proxy a' a b' b (MaybeT m) r -> Proxy a' a b' b m (Maybe r)
- readerP :: Monad m => (i -> Proxy a' a b' b m r) -> Proxy a' a b' b (ReaderT i m) r
- runReaderP :: Monad m => i -> Proxy a' a b' b (ReaderT i m) r -> Proxy a' a b' b m r
- stateP :: Monad m => (s -> Proxy a' a b' b m (r, s)) -> Proxy a' a b' b (StateT s m) r
- runStateP :: Monad m => s -> Proxy a' a b' b (StateT s m) r -> Proxy a' a b' b m (r, s)
- evalStateP :: Monad m => s -> Proxy a' a b' b (StateT s m) r -> Proxy a' a b' b m r
- execStateP :: Monad m => s -> Proxy a' a b' b (StateT s m) r -> Proxy a' a b' b m s
- writerP :: (Monad m, Monoid w) => Proxy a' a b' b m (r, w) -> Proxy a' a b' b (WriterT w m) r
- runWriterP :: (Monad m, Monoid w) => Proxy a' a b' b (WriterT w m) r -> Proxy a' a b' b m (r, w)
- execWriterP :: (Monad m, Monoid w) => Proxy a' a b' b (WriterT w m) r -> Proxy a' a b' b m w
- 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) r
- 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)
- 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)
- 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)
Utilities
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
ErrorT
errorP :: (Monad m, Error e) => Proxy a' a b' b m (Either e r) -> Proxy a' a b' b (ErrorT e m) r Source
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
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
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 (MaybeT m) r Source
Wrap the base monad in MaybeT
runMaybeP :: Monad m => Proxy a' a b' b (MaybeT m) r -> Proxy a' a b' b m (Maybe r) Source
Run 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) r Source
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 r Source
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) r Source
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 r Source
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 s Source
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) r Source
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 w Source
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) r Source
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
Tutorial
Probably the most useful functionality in this module is lifted error
    handling.  Suppose that you have a Pipe whose base monad can fail
    using ErrorT:
 import Control.Monad.Trans.Error
 import Pipes
 example :: Monad m => Pipe Int Int (ErrorT String m) r
 example = for cat $ \n ->
     if n == 0
     then lift $ throwError "Zero is forbidden"
     else yield n
Without the tools in this module you cannot recover from any potential error until after you compose and run the pipeline:
>>>import qualified Pipes.Prelude as P>>>runErrorT $ runEffect $ P.readLn >-> example >-> P.print42<Enter> 42 1<Enter> 1 0<Enter> Zero is forbidden>>>
This module provides catchError, which lets you catch and recover from
    errors inside the Pipe:
 import qualified Pipes.Lift as Lift
 caught :: Pipe Int Int (ErrorT String IO) r
 caught = example `Lift.catchError` \str -> do
     liftIO (putStrLn str)
     caught
This lets you resume streaming in the face of errors raised within the base monad:
>>>runErrorT $ runEffect $ P.readLn >-> caught >-> P.print0<Enter> Zero is forbidden 42<Enter> 42 0<Enter> Zero is forbidden 1<Enter> 1 ...
Another common use case is running a base monad before running the pipeline.
    For example, the following contrived Producer uses StateT gratuitously
    to increment numbers:
import Control.Monad (forever)
import Control.Monad.Trans.State.Strict
import Pipes
numbers :: Monad m => Producer Int (StateT Int m) r
numbers = forever $ do
    n <- lift get
    yield n
    lift $ put $! n + 1
You can run the StateT monad by supplying an initial state, before you
    ever compose the Producer:
import Pipes.Lift naturals :: Monad m => Producer Int m r naturals = evalStateP 0 numbers
This deletes StateT from the base monad entirely, give you a completely
    pure Producer:
>>>Pipes.Prelude.toList naturals[0,1,2,3,4,5,6...]
Note that the convention for the StateT run functions is backwards from
    transformers for convenience: the initial state is the first argument.
All of these functions internally use distribute, which can pull out most
    monad transformers from the base monad.  For example, evalStateP is
    defined in terms of distribute:
evalStateP s p = evalStateT (distribute p) s
Therefore you can use distribute to run other monad transformers, too, as
    long as they implement the MFunctor type class from the mmorph library.