Safe Haskell | None |
---|---|
Language | Haskell98 |
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.
- errorC :: (Monad m, Monad (t (ErrorT e m)), MonadTrans t, Error e, MFunctor t) => t m (Either e b) -> t (ErrorT e m) b
- runErrorC :: (Monad m, Error e) => ConduitM i o (ErrorT e m) r -> ConduitM i o m (Either e r)
- 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) r
- runCatchC :: Monad m => ConduitM i o (CatchT m) r -> ConduitM i o m (Either SomeException r)
- catchCatchC :: Monad m => ConduitM i o (CatchT m) r -> (SomeException -> ConduitM i o (CatchT m) r) -> ConduitM i o (CatchT m) r
- maybeC :: (Monad m, Monad (t (MaybeT m)), MonadTrans t, MFunctor t) => t m (Maybe b) -> t (MaybeT m) b
- runMaybeC :: Monad m => ConduitM i o (MaybeT m) r -> ConduitM i o m (Maybe r)
- readerC :: (Monad m, Monad (t1 (ReaderT t m)), MonadTrans t1, MFunctor t1) => (t -> t1 m b) -> t1 (ReaderT t m) b
- runReaderC :: Monad m => r -> ConduitM i o (ReaderT r m) res -> ConduitM i o m res
- stateLC :: (Monad m, Monad (t1 (StateT t m)), MonadTrans t1, MFunctor t1) => (t -> t1 m (b, t)) -> t1 (StateT t m) b
- runStateLC :: Monad m => s -> ConduitM i o (StateT s m) r -> ConduitM i o m (r, s)
- evalStateLC :: Monad m => s -> ConduitM i o (StateT s m) r -> ConduitM i o m r
- execStateLC :: Monad m => s -> ConduitM i o (StateT s m) r -> ConduitM i o m s
- stateC :: (Monad m, Monad (t1 (StateT t m)), MonadTrans t1, MFunctor t1) => (t -> t1 m (b, t)) -> t1 (StateT t m) b
- runStateC :: Monad m => s -> ConduitM i o (StateT s m) r -> ConduitM i o m (r, s)
- evalStateC :: Monad m => s -> ConduitM i o (StateT s m) r -> ConduitM i o m r
- execStateC :: Monad m => s -> ConduitM i o (StateT s m) r -> ConduitM i o m s
- writerLC :: (Monad m, Monad (t (WriterT w m)), MonadTrans t, Monoid w, MFunctor t) => t m (b, w) -> t (WriterT w m) b
- runWriterLC :: (Monad m, Monoid w) => ConduitM i o (WriterT w m) r -> ConduitM i o m (r, w)
- execWriterLC :: (Monad m, Monoid w) => ConduitM i o (WriterT w m) r -> ConduitM i o m w
- writerC :: (Monad m, Monad (t (WriterT w m)), MonadTrans t, Monoid w, MFunctor t) => t m (b, w) -> t (WriterT w m) b
- runWriterC :: (Monad m, Monoid w) => ConduitM i o (WriterT w m) r -> ConduitM i o m (r, w)
- execWriterC :: (Monad m, Monoid w) => ConduitM i o (WriterT w m) r -> ConduitM i o m w
- rwsLC :: (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) b
- runRWSLC :: (Monad m, Monoid w) => r -> s -> ConduitM i o (RWST r w s m) res -> ConduitM i o m (res, s, w)
- evalRWSLC :: (Monad m, Monoid w) => r -> s -> ConduitM i o (RWST r w s m) res -> ConduitM i o m (res, w)
- execRWSLC :: (Monad m, Monoid w) => r -> s -> ConduitM i o (RWST r w s m) res -> ConduitM i o m (s, w)
- 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) b
- runRWSC :: (Monad m, Monoid w) => r -> s -> ConduitM i o (RWST r w s m) res -> ConduitM i o m (res, s, w)
- evalRWSC :: (Monad m, Monoid w) => r -> s -> ConduitM i o (RWST r w s m) res -> ConduitM i o m (res, w)
- execRWSC :: (Monad m, Monoid w) => r -> s -> ConduitM i o (RWST r w s m) res -> ConduitM i o m (s, w)
- 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) ()
ErrorT
errorC :: (Monad m, Monad (t (ErrorT e m)), MonadTrans t, Error e, MFunctor t) => t m (Either e b) -> t (ErrorT e m) b Source
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) r Source
Catch an error in the base monad
Since 1.0.11
CatchT
runCatchC :: Monad m => ConduitM i o (CatchT m) r -> ConduitM i o m (Either SomeException r) Source
Run CatchT
in the base monad
Since 1.1.0
catchCatchC :: Monad m => ConduitM i o (CatchT m) r -> (SomeException -> ConduitM i o (CatchT m) r) -> ConduitM i o (CatchT m) r Source
Catch an exception in the base monad
Since 1.1.0
MaybeT
maybeC :: (Monad m, Monad (t (MaybeT m)), MonadTrans t, MFunctor t) => t m (Maybe b) -> t (MaybeT m) b Source
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) b Source
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 res Source
Run ReaderT
in the base monad
Since 1.0.11
StateT, lazy
stateLC :: (Monad m, Monad (t1 (StateT t m)), MonadTrans t1, MFunctor t1) => (t -> t1 m (b, t)) -> t1 (StateT t m) b Source
Wrap the base monad in StateT
Since 1.0.11
runStateLC :: 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
evalStateLC :: Monad m => s -> ConduitM i o (StateT s m) r -> ConduitM i o m r Source
Evaluate StateT
in the base monad
Since 1.0.11
execStateLC :: Monad m => s -> ConduitM i o (StateT s m) r -> ConduitM i o m s Source
Execute StateT
in the base monad
Since 1.0.11
Strict
stateC :: (Monad m, Monad (t1 (StateT t m)), MonadTrans t1, MFunctor t1) => (t -> t1 m (b, t)) -> t1 (StateT t m) b Source
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 r Source
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 s Source
Execute StateT
in the base monad
Since 1.0.11
WriterT, lazy
writerLC :: (Monad m, Monad (t (WriterT w m)), MonadTrans t, Monoid w, MFunctor t) => t m (b, w) -> t (WriterT w m) b Source
Wrap the base monad in WriterT
Since 1.0.11
runWriterLC :: (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
execWriterLC :: (Monad m, Monoid w) => ConduitM i o (WriterT w m) r -> ConduitM i o m w Source
Execute WriterT
in the base monad
Since 1.0.11
Strict
writerC :: (Monad m, Monad (t (WriterT w m)), MonadTrans t, Monoid w, MFunctor t) => t m (b, w) -> t (WriterT w m) b Source
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 w Source
Execute WriterT
in the base monad
Since 1.0.11
RWST, lazy
rwsLC :: (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) b Source
Wrap the base monad in RWST
Since 1.0.11
runRWSLC :: (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
evalRWSLC :: (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
execRWSLC :: (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
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) b Source
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
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