conduit-1.0.13.1: Streaming data processing library.

Safe HaskellNone

Data.Conduit.Lift

Contents

Description

Allow monad transformers to be runevalexec in a section of conduit rather then needing to run across the whole conduit. The circumvents many of the problems with breaking the monad transformer laws. For more information, see the announcement blog post: http://www.yesodweb.com/blog/2014/01/conduit-transformer-exception

This module was added in conduit 1.0.11.

Synopsis

ErrorT

errorC :: (Monad m, Monad (t (ErrorT e m)), MonadTrans t, Error e, MFunctor t) => t m (Either e b) -> t (ErrorT e m) bSource

Run ErrorT in the base monad

Since 1.0.11

runErrorC :: (Monad m, Error e) => ConduitM i o (ErrorT e m) r -> ConduitM i o m (Either e r)Source

Run ErrorT in the base monad

Since 1.0.11

catchErrorC :: (Monad m, Error e) => ConduitM i o (ErrorT e m) r -> (e -> ConduitM i o (ErrorT e m) r) -> ConduitM i o (ErrorT e m) rSource

Catch an error in the base monad

Since 1.0.11

MaybeT

maybeC :: (Monad m, Monad (t (MaybeT m)), MonadTrans t, MFunctor t) => t m (Maybe b) -> t (MaybeT m) bSource

Wrap the base monad in MaybeT

Since 1.0.11

runMaybeC :: Monad m => ConduitM i o (MaybeT m) r -> ConduitM i o m (Maybe r)Source

Run MaybeT in the base monad

Since 1.0.11

ReaderT

readerC :: (Monad m, Monad (t1 (ReaderT t m)), MonadTrans t1, MFunctor t1) => (t -> t1 m b) -> t1 (ReaderT t m) bSource

Wrap the base monad in ReaderT

Since 1.0.11

runReaderC :: Monad m => r -> ConduitM i o (ReaderT r m) res -> ConduitM i o m resSource

Run ReaderT in the base monad

Since 1.0.11

StateT

stateC :: (Monad m, Monad (t1 (StateT t m)), MonadTrans t1, MFunctor t1) => (t -> t1 m (b, t)) -> t1 (StateT t m) bSource

Wrap the base monad in StateT

Since 1.0.11

runStateC :: Monad m => s -> ConduitM i o (StateT s m) r -> ConduitM i o m (r, s)Source

Run StateT in the base monad

Since 1.0.11

evalStateC :: Monad m => s -> ConduitM i o (StateT s m) r -> ConduitM i o m rSource

Evaluate StateT in the base monad

Since 1.0.11

execStateC :: Monad m => s -> ConduitM i o (StateT s m) r -> ConduitM i o m sSource

Execute StateT in the base monad

Since 1.0.11

Strict

stateSC :: (Monad m, Monad (t1 (StateT t m)), MonadTrans t1, MFunctor t1) => (t -> t1 m (b, t)) -> t1 (StateT t m) bSource

Wrap the base monad in StateT

Since 1.0.11

runStateSC :: Monad m => s -> ConduitM i o (StateT s m) r -> ConduitM i o m (r, s)Source

Run StateT in the base monad

Since 1.0.11

evalStateSC :: Monad m => s -> ConduitM i o (StateT s m) r -> ConduitM i o m rSource

Evaluate StateT in the base monad

Since 1.0.11

execStateSC :: Monad m => s -> ConduitM i o (StateT s m) r -> ConduitM i o m sSource

Execute StateT in the base monad

Since 1.0.11

WriterT

writerC :: (Monad m, Monad (t (WriterT w m)), MonadTrans t, Monoid w, MFunctor t) => t m (b, w) -> t (WriterT w m) bSource

Wrap the base monad in WriterT

Since 1.0.11

runWriterC :: (Monad m, Monoid w) => ConduitM i o (WriterT w m) r -> ConduitM i o m (r, w)Source

Run WriterT in the base monad

Since 1.0.11

execWriterC :: (Monad m, Monoid w) => ConduitM i o (WriterT w m) r -> ConduitM i o m wSource

Execute WriterT in the base monad

Since 1.0.11

Strict

writerSC :: (Monad m, Monad (t (WriterT w m)), MonadTrans t, Monoid w, MFunctor t) => t m (b, w) -> t (WriterT w m) bSource

Wrap the base monad in WriterT

Since 1.0.11

runWriterSC :: (Monad m, Monoid w) => ConduitM i o (WriterT w m) r -> ConduitM i o m (r, w)Source

Run WriterT in the base monad

Since 1.0.11

execWriterSC :: (Monad m, Monoid w) => ConduitM i o (WriterT w m) r -> ConduitM i o m wSource

Execute WriterT in the base monad

Since 1.0.11

RWST

rwsC :: (Monad m, Monad (t1 (RWST t w t2 m)), MonadTrans t1, Monoid w, MFunctor t1) => (t -> t2 -> t1 m (b, t2, w)) -> t1 (RWST t w t2 m) bSource

Wrap the base monad in RWST

Since 1.0.11

runRWSC :: (Monad m, Monoid w) => r -> s -> ConduitM i o (RWST r w s m) res -> ConduitM i o m (res, s, w)Source

Run RWST in the base monad

Since 1.0.11

evalRWSC :: (Monad m, Monoid w) => r -> s -> ConduitM i o (RWST r w s m) res -> ConduitM i o m (res, w)Source

Evaluate RWST in the base monad

Since 1.0.11

execRWSC :: (Monad m, Monoid w) => r -> s -> ConduitM i o (RWST r w s m) res -> ConduitM i o m (s, w)Source

Execute RWST in the base monad

Since 1.0.11

Strict

rwsSC :: (Monad m, Monad (t1 (RWST t w t2 m)), MonadTrans t1, Monoid w, MFunctor t1) => (t -> t2 -> t1 m (b, t2, w)) -> t1 (RWST t w t2 m) bSource

Wrap the base monad in RWST

Since 1.0.11

runRWSSC :: (Monad m, Monoid w) => r -> s -> ConduitM i o (RWST r w s m) res -> ConduitM i o m (res, s, w)Source

Run RWST in the base monad

Since 1.0.11

evalRWSSC :: (Monad m, Monoid w) => r -> s -> ConduitM i o (RWST r w s m) res -> ConduitM i o m (res, w)Source

Evaluate RWST in the base monad

Since 1.0.11

execRWSSC :: (Monad m, Monoid w) => r -> s -> ConduitM i o (RWST r w s m) res -> ConduitM i o m (s, w)Source

Execute RWST in the base monad

Since 1.0.11

Utilities

distribute :: (Monad (t (ConduitM b o m)), Monad m, Monad (t m), MonadTrans t, MFunctor t) => ConduitM b o (t m) () -> t (ConduitM b o m) ()Source