conduit-1.3.0.2: Streaming data processing library.

Safe HaskellNone
LanguageHaskell98

Data.Conduit.Lift

Contents

Description

Allow monad transformers to be run/eval/exec 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

ExceptT

exceptC :: Monad m => ConduitT i o m (Either e a) -> ConduitT i o (ExceptT e m) a Source #

Wrap the base monad in ExceptT

Since 1.2.12

runExceptC :: Monad m => ConduitT i o (ExceptT e m) r -> ConduitT i o m (Either e r) Source #

Run ExceptT in the base monad

Since 1.2.12

catchExceptC :: Monad m => ConduitT i o (ExceptT e m) r -> (e -> ConduitT i o (ExceptT e m) r) -> ConduitT i o (ExceptT e m) r Source #

Catch an error in the base monad

Since 1.2.12

CatchC

runCatchC :: Monad m => ConduitT i o (CatchT m) r -> ConduitT i o m (Either SomeException r) Source #

Run CatchT in the base monad

Since 1.1.0

catchCatchC :: Monad m => ConduitT i o (CatchT m) r -> (SomeException -> ConduitT i o (CatchT m) r) -> ConduitT i o (CatchT m) r Source #

Catch an exception in the base monad

Since 1.1.0

MaybeT

maybeC :: Monad m => ConduitT i o m (Maybe a) -> ConduitT i o (MaybeT m) a Source #

Wrap the base monad in MaybeT

Since 1.0.11

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

Run MaybeT in the base monad

Since 1.0.11

ReaderT

readerC :: Monad m => (r -> ConduitT i o m a) -> ConduitT i o (ReaderT r m) a Source #

Wrap the base monad in ReaderT

Since 1.0.11

runReaderC :: Monad m => r -> ConduitT i o (ReaderT r m) res -> ConduitT i o m res Source #

Run ReaderT in the base monad

Since 1.0.11

StateT, lazy

stateLC :: Monad m => (s -> ConduitT i o m (a, s)) -> ConduitT i o (StateT s m) a Source #

Wrap the base monad in StateT

Since 1.0.11

runStateLC :: Monad m => s -> ConduitT i o (StateT s m) r -> ConduitT i o m (r, s) Source #

Run StateT in the base monad

Since 1.0.11

evalStateLC :: Monad m => s -> ConduitT i o (StateT s m) r -> ConduitT i o m r Source #

Evaluate StateT in the base monad

Since 1.0.11

execStateLC :: Monad m => s -> ConduitT i o (StateT s m) r -> ConduitT i o m s Source #

Execute StateT in the base monad

Since 1.0.11

Strict

stateC :: Monad m => (s -> ConduitT i o m (a, s)) -> ConduitT i o (StateT s m) a Source #

Wrap the base monad in StateT

Since 1.0.11

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

Run StateT in the base monad

Since 1.0.11

evalStateC :: Monad m => s -> ConduitT i o (StateT s m) r -> ConduitT i o m r Source #

Evaluate StateT in the base monad

Since 1.0.11

execStateC :: Monad m => s -> ConduitT i o (StateT s m) r -> ConduitT i o m s Source #

Execute StateT in the base monad

Since 1.0.11

WriterT, lazy

writerLC :: (Monad m, Monoid w) => ConduitT i o m (b, w) -> ConduitT i o (WriterT w m) b Source #

Wrap the base monad in WriterT

Since 1.0.11

runWriterLC :: (Monad m, Monoid w) => ConduitT i o (WriterT w m) r -> ConduitT i o m (r, w) Source #

Run WriterT in the base monad

Since 1.0.11

execWriterLC :: (Monad m, Monoid w) => ConduitT i o (WriterT w m) r -> ConduitT i o m w Source #

Execute WriterT in the base monad

Since 1.0.11

Strict

writerC :: (Monad m, Monoid w) => ConduitT i o m (b, w) -> ConduitT i o (WriterT w m) b Source #

Wrap the base monad in WriterT

Since 1.0.11

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

Run WriterT in the base monad

Since 1.0.11

execWriterC :: (Monad m, Monoid w) => ConduitT i o (WriterT w m) r -> ConduitT i o m w Source #

Execute WriterT in the base monad

Since 1.0.11

RWST, lazy

rwsLC :: (Monad m, Monoid w) => (r -> s -> ConduitT i o m (a, s, w)) -> ConduitT i o (RWST r w s m) a Source #

Wrap the base monad in RWST

Since 1.0.11

runRWSLC :: (Monad m, Monoid w) => r -> s -> ConduitT i o (RWST r w s m) res -> ConduitT i o m (res, s, w) Source #

Run RWST in the base monad

Since 1.0.11

evalRWSLC :: (Monad m, Monoid w) => r -> s -> ConduitT i o (RWST r w s m) res -> ConduitT i o m (res, w) Source #

Evaluate RWST in the base monad

Since 1.0.11

execRWSLC :: (Monad m, Monoid w) => r -> s -> ConduitT i o (RWST r w s m) res -> ConduitT i o m (s, w) Source #

Execute RWST in the base monad

Since 1.0.11

Strict

rwsC :: (Monad m, Monoid w) => (r -> s -> ConduitT i o m (a, s, w)) -> ConduitT i o (RWST r w s m) a Source #

Wrap the base monad in RWST

Since 1.0.11

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

Run RWST in the base monad

Since 1.0.11

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

Evaluate RWST in the base monad

Since 1.0.11

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

Execute RWST in the base monad

Since 1.0.11