| Copyright | (c) 2017 Harendra Kumar | 
|---|---|
| License | BSD3 | 
| Maintainer | harendra.kumar@gmail.com | 
| Stability | experimental | 
| Portability | GHC | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Streamly
Contents
Description
- type MonadAsync m = (MonadIO m, MonadBaseControl IO m, MonadThrow m)
- class Streaming t
- data StreamT m a
- data InterleavedT m a
- data AsyncT m a
- data ParallelT m a
- data ZipStream m a
- data ZipAsync m a
- (<=>) :: Streaming t => t m a -> t m a -> t m a
- (<|) :: (Streaming t, MonadAsync m) => t m a -> t m a -> t m a
- async :: (Streaming t, MonadAsync m) => t m a -> m (t m a)
- serially :: StreamT m a -> StreamT m a
- interleaving :: InterleavedT m a -> InterleavedT m a
- asyncly :: AsyncT m a -> AsyncT m a
- parallely :: ParallelT m a -> ParallelT m a
- zipping :: ZipStream m a -> ZipStream m a
- zippingAsync :: ZipAsync m a -> ZipAsync m a
- adapt :: (Streaming t1, Streaming t2) => t1 m a -> t2 m a
- runStreaming :: (Monad m, Streaming t) => t m a -> m ()
- runStreamT :: Monad m => StreamT m a -> m ()
- runInterleavedT :: Monad m => InterleavedT m a -> m ()
- runAsyncT :: Monad m => AsyncT m a -> m ()
- runParallelT :: Monad m => ParallelT m a -> m ()
- runZipStream :: Monad m => ZipStream m a -> m ()
- runZipAsync :: Monad m => ZipAsync m a -> m ()
- foldWith :: (Streaming t, Foldable f) => (t m a -> t m a -> t m a) -> f (t m a) -> t m a
- foldMapWith :: (Streaming t, Foldable f) => (t m b -> t m b -> t m b) -> (a -> t m b) -> f a -> t m b
- forEachWith :: (Streaming t, Foldable f) => (t m b -> t m b -> t m b) -> f a -> (a -> t m b) -> t m b
- class Monoid a where
- class Semigroup a where
- class Applicative f => Alternative f where
- class (Alternative m, Monad m) => MonadPlus m where
- class Monad m => MonadIO m where
- class MonadTrans t where
Background
Streamly provides a monad transformer that extends the product style
 composition of monads to streams of many elements of the same type; it is a
 functional programming equivalent of nested loops from imperative
 programming. Composing each element in one stream with each element in the
 other stream generalizes the monadic product of single elements. You can
 think of the IO monad as a special case of the more general StreamT IO
 monad; with single element streams.  List transformers and logic programming
 monads also provide a similar product style composition of streams, however
 streamly generalizes it with the time dimension; allowing streams to be
 composed in an asynchronous and concurrent fashion in many different ways.
 It also provides multiple alternative ways of composing streams e.g.
 serial, interleaved or concurrent.
The seemingly simple addition of asynchronicity and concurrency to product style streaming composition unifies a number of disparate abstractions into one powerful and elegant abstraction. A wide variety of programming problems can be solved elegantly with this abstraction. In particular, it unifies three major programming domains namely non-deterministic (logic) programming, concurrent programming and functional reactive programming. In other words, you can do everything with this one abstraction that you could with list transformers (e.g. list-t), logic programming monads (e.g. logict), streaming libraries (a lot of what conduit or pipes can do), concurrency libraries (e.g. async) and FRP libraries (e.g. Yampa or reflex).
Overview
Streamly provides six distinct stream types i.e. StreamT, InterleavedT,
 AsyncT and ParallelT, ZipStream and ZipAsync, each representing a
 stream of elements.  All these types have the same underlying representation
 and can be adapted from one to another using type adaptor combinators
 described later. Each of these types belongs to the Streaming type class
 which helps converting the specific type to and from the underlying generic
 stream type.
The types StreamT, InterleavedT, AsyncT and ParallelT are Monad
 transformers with the monadic bind operation combining streams in a product
 style in much the same way as a list monad or a list transformer i.e. each
 element from one stream is combined with every element of the other stream.
 However, the applicative and monadic composition of these types differ in
 terms of the ordering and time sequence in which the elements from two
 streams are combined. StreamT and InterleavedT compose streams serially
 whereas AsyncT and ParallelT are their concurrent counterparts. See the
 documentation of the respective types for more details.
The types ZipStream and ZipAsync provide Applicative instances to zip
 two streams together i.e.  each element in one stream is combined with the
 corresponding element in the other stream. ZipStream generates the streams
 being zipped serially whereas ZipAsync produces both the elements being
 zipped concurrently.
Two streams of the same type can be combined using a sum style composition
 to generate a stream of the same type where the output stream would contain
 all elements of both the streams. However, the sequence in which the
 elements in the resulting stream are produced depends on the combining
 operator. Four distinct sum style operators, <>, <=>, <| and <|>
 combine two streams in different ways, each corresponding to the one of the
 four ways of combining monadically. See the respective section below for
 more details.
Concurrent composition types AsyncT, ParallelT, ZipAsync and
 concurrent composition operators <| and <|> require the underlying monad
 of the streaming monad transformer to be MonadAsync.
For more details please see the Streamly.Tutorial and Streamly.Examples
 (the latter is available only when built with the examples build flag).
type MonadAsync m = (MonadIO m, MonadBaseControl IO m, MonadThrow m) Source #
A monad that can perform asynchronous/concurrent IO operations. Streams
 that can be composed concurrently require the underlying monad to be
 MonadAsync.
Class of types that can represent a stream of elements of some type a in
 some monad m.
Minimal complete definition
toStream, fromStream
Product Style Composition
Streams that compose serially or non-concurrently come in two flavors i.e.
 StreamT and InterleavedT.  Both of these serial flavors have
 corresponding concurrent equivalents, those are AsyncT and ParallelT
 respectively.
The Monad instance of StreamT runs the monadic continuation for each
 element of the stream, serially.
main = runStreamT $ do
    x <- return 1 <> return 2
    liftIO $ print x
1 2
StreamT nests streams serially in a depth first manner.
main = runStreamT $ do
    x <- return 1 <> return 2
    y <- return 3 <> return 4
    liftIO $ print (x, y)
(1,3) (1,4) (2,3) (2,4)
This behavior is exactly like a list transformer. We call the monadic code
 being run for each element of the stream a monadic continuation. In
 imperative paradigm we can think of this composition as nested for loops
 and the monadic continuation is the body of the loop. The loop iterates for
 all elements of the stream.
Instances
| MonadTrans StreamT Source # | |
| Streaming StreamT Source # | |
| (MonadBase b m, Monad m) => MonadBase b (StreamT m) Source # | |
| MonadError e m => MonadError e (StreamT m) Source # | |
| MonadReader r m => MonadReader r (StreamT m) Source # | |
| MonadState s m => MonadState s (StreamT m) Source # | |
| Monad m => Monad (StreamT m) Source # | |
| Monad m => Functor (StreamT m) Source # | |
| Monad m => Applicative (StreamT m) Source # | |
| MonadIO m => MonadIO (StreamT m) Source # | |
| MonadAsync m => Alternative (StreamT m) Source # | |
| MonadAsync m => MonadPlus (StreamT m) Source # | |
| MonadThrow m => MonadThrow (StreamT m) Source # | |
| (Monad m, Floating a) => Floating (StreamT m a) Source # | |
| (Monad m, Fractional a) => Fractional (StreamT m a) Source # | |
| (Monad m, Num a) => Num (StreamT m a) Source # | |
| Semigroup (StreamT m a) Source # | |
| Monoid (StreamT m a) Source # | |
data InterleavedT m a Source #
Like StreamT but different in nesting behavior. It fairly interleaves
 the iterations of the inner and the outer loop, nesting loops in a breadth
 first manner.
main = runInterleavedT $ do
    x <- return 1 <> return 2
    y <- return 3 <> return 4
    liftIO $ print (x, y)
(1,3) (2,3) (1,4) (2,4)
Instances
| MonadTrans InterleavedT Source # | |
| Streaming InterleavedT Source # | |
| (MonadBase b m, Monad m) => MonadBase b (InterleavedT m) Source # | |
| MonadError e m => MonadError e (InterleavedT m) Source # | |
| MonadReader r m => MonadReader r (InterleavedT m) Source # | |
| MonadState s m => MonadState s (InterleavedT m) Source # | |
| Monad m => Monad (InterleavedT m) Source # | |
| Monad m => Functor (InterleavedT m) Source # | |
| Monad m => Applicative (InterleavedT m) Source # | |
| MonadIO m => MonadIO (InterleavedT m) Source # | |
| MonadAsync m => Alternative (InterleavedT m) Source # | |
| MonadAsync m => MonadPlus (InterleavedT m) Source # | |
| MonadThrow m => MonadThrow (InterleavedT m) Source # | |
| (Monad m, Floating a) => Floating (InterleavedT m a) Source # | |
| (Monad m, Fractional a) => Fractional (InterleavedT m a) Source # | |
| (Monad m, Num a) => Num (InterleavedT m a) Source # | |
| Semigroup (InterleavedT m a) Source # | |
| Monoid (InterleavedT m a) Source # | |
Like StreamT but may run each iteration concurrently using demand
 driven concurrency.  More concurrent iterations are started only if the
 previous iterations are not able to produce enough output for the consumer.
import Streamly
import Control.Concurrent
main = runAsyncT $ do
    n <- return 3 <> return 2 <> return 1
    liftIO $ do
         threadDelay (n * 1000000)
         myThreadId >>= \tid -> putStrLn (show tid ++ ": Delay " ++ show n)
ThreadId 40: Delay 1 ThreadId 39: Delay 2 ThreadId 38: Delay 3
All iterations may run in the same thread if they do not block.
Instances
| MonadTrans AsyncT Source # | |
| Streaming AsyncT Source # | |
| (MonadBase b m, MonadAsync m) => MonadBase b (AsyncT m) Source # | |
| (MonadError e m, MonadAsync m) => MonadError e (AsyncT m) Source # | |
| (MonadReader r m, MonadAsync m) => MonadReader r (AsyncT m) Source # | |
| (MonadState s m, MonadAsync m) => MonadState s (AsyncT m) Source # | |
| MonadAsync m => Monad (AsyncT m) Source # | |
| Monad m => Functor (AsyncT m) Source # | |
| MonadAsync m => Applicative (AsyncT m) Source # | |
| MonadAsync m => MonadIO (AsyncT m) Source # | |
| MonadAsync m => Alternative (AsyncT m) Source # | |
| MonadAsync m => MonadPlus (AsyncT m) Source # | |
| MonadAsync m => MonadThrow (AsyncT m) Source # | |
| (MonadAsync m, Floating a) => Floating (AsyncT m a) Source # | |
| (MonadAsync m, Fractional a) => Fractional (AsyncT m a) Source # | |
| (MonadAsync m, Num a) => Num (AsyncT m a) Source # | |
| Semigroup (AsyncT m a) Source # | |
| Monoid (AsyncT m a) Source # | |
Like StreamT but runs all iterations fairly concurrently using a round
 robin scheduling.
import Streamly
import Control.Concurrent
main = runParallelT $ do
    n <- return 3 <> return 2 <> return 1
    liftIO $ do
         threadDelay (n * 1000000)
         myThreadId >>= \tid -> putStrLn (show tid ++ ": Delay " ++ show n)
ThreadId 40: Delay 1 ThreadId 39: Delay 2 ThreadId 38: Delay 3
Unlike AsyncT all iterations are guaranteed to run fairly concurrently,
 unconditionally.
Instances
| MonadTrans ParallelT Source # | |
| Streaming ParallelT Source # | |
| (MonadBase b m, MonadAsync m) => MonadBase b (ParallelT m) Source # | |
| (MonadError e m, MonadAsync m) => MonadError e (ParallelT m) Source # | |
| (MonadReader r m, MonadAsync m) => MonadReader r (ParallelT m) Source # | |
| (MonadState s m, MonadAsync m) => MonadState s (ParallelT m) Source # | |
| MonadAsync m => Monad (ParallelT m) Source # | |
| Monad m => Functor (ParallelT m) Source # | |
| MonadAsync m => Applicative (ParallelT m) Source # | |
| MonadAsync m => MonadIO (ParallelT m) Source # | |
| MonadAsync m => Alternative (ParallelT m) Source # | |
| MonadAsync m => MonadPlus (ParallelT m) Source # | |
| MonadAsync m => MonadThrow (ParallelT m) Source # | |
| (MonadAsync m, Floating a) => Floating (ParallelT m a) Source # | |
| (MonadAsync m, Fractional a) => Fractional (ParallelT m a) Source # | |
| (MonadAsync m, Num a) => Num (ParallelT m a) Source # | |
| Semigroup (ParallelT m a) Source # | |
| Monoid (ParallelT m a) Source # | |
Zip Style Composition
ZipStream and ZipAsync, provide Applicative instances for zipping the
 corresponding elements of two streams together. Note that these types are
 not monads.
ZipStream zips serially i.e. it produces one element from each stream
 serially and then zips the two elements. Note, for convenience we have used
 the zipping combinator in the following example instead of using a type
 annotation.
main = (toList . zipping $ (,) <$> s1 <*> s2) >>= print
    where s1 = pure 1 <> pure 2
          s2 = pure 3 <> pure 4
[(1,3),(2,4)]
This applicative operation can be seen as the zipping equivalent of
 interleaving with <=>.
Instances
| Streaming ZipStream Source # | |
| Monad m => Functor (ZipStream m) Source # | |
| Monad m => Applicative (ZipStream m) Source # | |
| MonadAsync m => Alternative (ZipStream m) Source # | |
| (Monad m, Floating a) => Floating (ZipStream m a) Source # | |
| (Monad m, Fractional a) => Fractional (ZipStream m a) Source # | |
| (Monad m, Num a) => Num (ZipStream m a) Source # | |
| Semigroup (ZipStream m a) Source # | |
| Monoid (ZipStream m a) Source # | |
Like ZipStream but zips in parallel, it generates both the elements to
 be zipped concurrently.
main = (toList . zippingAsync $ (,) <$> s1 <*> s2) >>= print
    where s1 = pure 1 <> pure 2
          s2 = pure 3 <> pure 4
[(1,3),(2,4)]
This applicative operation can be seen as the zipping equivalent of
 parallel composition with <|>.
Instances
| Streaming ZipAsync Source # | |
| Monad m => Functor (ZipAsync m) Source # | |
| MonadAsync m => Applicative (ZipAsync m) Source # | |
| MonadAsync m => Alternative (ZipAsync m) Source # | |
| (MonadAsync m, Floating a) => Floating (ZipAsync m a) Source # | |
| (MonadAsync m, Fractional a) => Fractional (ZipAsync m a) Source # | |
| (MonadAsync m, Num a) => Num (ZipAsync m a) Source # | |
| Semigroup (ZipAsync m a) Source # | |
| Monoid (ZipAsync m a) Source # | |
Sum Style Composition
Just like product style composition there are four distinct ways to combine streams in sum style each directly corresponding to one of the product style composition.
The standard semigroup append <> operator appends two streams serially,
 this style corresponds to the StreamT style of monadic composition.
main = (toList.serially$ (return 1 <> return 2) <> (return 3 <> return 4)) >>= print
[1,2,3,4]
The standard Alternative operator <|>  fairly interleaves two streams in
 parallel, this operator corresponds to the ParallelT style.
main = (toList.serially$ (return 1 <> return 2) <|> (return 3 <> return 4)) >>= print
[1,3,2,4]
Unlike <|, this operator cannot be used to fold infinite containers since
 that might accumulate too many partially drained streams.  To be clear, it
 can combine infinite streams but not infinite number of streams.
Two additional sum style composition operators that streamly introduces are described below.
(<=>) :: Streaming t => t m a -> t m a -> t m a infixr 5 Source #
Sequential interleaved composition, in contrast to <> this operator
 fairly interleaves two streams instead of appending them; yielding one
 element from each stream alternately.
main = (toList.serially$ (return 1 <> return 2) <=> (return 3 <> return 4)) >>= print
[1,3,2,4]
This operator corresponds to the InterleavedT style. Unlike <>, this
 operator cannot be used to fold infinite containers since that might
 accumulate too many partially drained streams.  To be clear, it can combine
 infinite streams but not infinite number of streams.
(<|) :: (Streaming t, MonadAsync m) => t m a -> t m a -> t m a Source #
Demand driven concurrent composition. In contrast to <|> this operator
 concurrently "merges" streams in a left biased manner rather than fairly
 interleaving them.  It keeps yielding from the stream on the left as long as
 it can. If the left stream blocks or cannot keep up with the pace of the
 consumer it can concurrently yield from the stream on the right in parallel.
main = (toList.serially$ (return 1 <> return 2) <| (return 3 <> return 4)) >>= print
[1,2,3,4]
Unlike <|> it can be used to fold infinite containers of streams. This
 operator corresponds to the AsyncT type for product style composition.
Transformation
async :: (Streaming t, MonadAsync m) => t m a -> m (t m a) Source #
Make a stream asynchronous, triggers the computation and returns a stream
 in the underlying monad representing the output generated by the original
 computation. The returned action is exhaustible and must be drained once. If
 not drained fully we may have a thread blocked forever and once exhausted it
 will always return empty.
Stream Type Adapters
Code using streamly is usually written such that it is agnostic of any
 specific streaming type.  We use a type variable (polymorphic type) with the
 Streaming class constraint. Finally, when running the monad we can specify
 the actual type that we want to use to interpret the code. However, in
 certain cases we may want to use a specific type to force a certain type of
 composition. These combinators can be used to convert the stream types from
 one to another at no cost as all the types have the same underlying
 representation.
If you see an ambiguous type variable error then most likely it is because
 you have not specified the stream type. You either need a type annotation or
 one of the following combinators to specify what type of stream you mean.
This code:
main = (toList $ (return 1 <> return 2)) >>= print
will result in a type error like this:
Ambiguous type variable ‘t0’ arising from a use of ...
To fix the error just tell toList what kind of stream are we feeding it:
main = (toList$serially$ (return 1 <> return 2)) >>= print
main = (toList $ (return 1 <> return 2 :: StreamT IO Int)) >>= print
Note that using the combinators is easier as you do not have to think about the specific types, they are just inferred.
interleaving :: InterleavedT m a -> InterleavedT m a Source #
Interpret an ambiguously typed stream as InterleavedT.
parallely :: ParallelT m a -> ParallelT m a Source #
Interpret an ambiguously typed stream as ParallelT.
zipping :: ZipStream m a -> ZipStream m a Source #
Interpret an ambiguously typed stream as ZipStream.
zippingAsync :: ZipAsync m a -> ZipAsync m a Source #
Interpret an ambiguously typed stream as ZipAsync.
adapt :: (Streaming t1, Streaming t2) => t1 m a -> t2 m a Source #
Adapt one streaming type to another.
Running Streams
runStreaming :: (Monad m, Streaming t) => t m a -> m () Source #
Run a streaming composition, discard the results.
runStreamT :: Monad m => StreamT m a -> m () Source #
Same as runStreaming . serially.
runInterleavedT :: Monad m => InterleavedT m a -> m () Source #
Same as runStreaming . interleaving.
runParallelT :: Monad m => ParallelT m a -> m () Source #
Same as runStreaming . parallely.
runZipStream :: Monad m => ZipStream m a -> m () Source #
Same as runStreaming . zipping.
runZipAsync :: Monad m => ZipAsync m a -> m () Source #
Same as runStreaming . zippingAsync.
Fold Utilities
These are some convenience functions to fold any Foldable container using
 one of the sum composition operators to convert it into a streamly stream.
foldWith :: (Streaming t, Foldable f) => (t m a -> t m a -> t m a) -> f (t m a) -> t m a Source #
Like the Prelude fold but allows you to specify a binary sum style
 stream composition operator to fold a container of streams.
foldWith (<>) $ map return [1..3]
foldMapWith :: (Streaming t, Foldable f) => (t m b -> t m b -> t m b) -> (a -> t m b) -> f a -> t m b Source #
Like foldMap but allows you to specify a binary sum style composition
 operator to fold a container of streams. Maps a monadic streaming action on
 the container before folding it.
foldMapWith (<>) return [1..3]
forEachWith :: (Streaming t, Foldable f) => (t m b -> t m b -> t m b) -> f a -> (a -> t m b) -> t m b Source #
Like foldMapWith but with the last two arguments reversed i.e. the
 monadic streaming function is the last argument.
Re-exports
The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:
- mappend mempty x = x 
- mappend x mempty = x 
- mappend x (mappend y z) = mappend (mappend x y) z 
- mconcat = - foldrmappend mempty
The method names refer to the monoid of lists under concatenation, but there are many other instances.
Some types can be viewed as a monoid in more than one way,
 e.g. both addition and multiplication on numbers.
 In such cases we often define newtypes and make those instances
 of Monoid, e.g. Sum and Product.
Instances
| Monoid Ordering | |
| Monoid () | |
| Monoid All | |
| Monoid Any | |
| Monoid ByteString | |
| Monoid ByteString | |
| Monoid IntSet | |
| Monoid Doc | |
| Monoid Buffer | |
| Monoid More | |
| Monoid Buffer | |
| Monoid CookieJar | |
| Monoid RequestBody | |
| Monoid String | |
| Monoid AsciiString | |
| Monoid Bitmap | |
| Monoid [a] | |
| Monoid a => Monoid (Maybe a) | Lift a semigroup into  | 
| Monoid a => Monoid (IO a) | |
| Ord a => Monoid (Max a) | |
| Ord a => Monoid (Min a) | |
| Monoid a => Monoid (Identity a) | |
| (Ord a, Bounded a) => Monoid (Min a) | |
| (Ord a, Bounded a) => Monoid (Max a) | |
| Monoid m => Monoid (WrappedMonoid m) | |
| Semigroup a => Monoid (Option a) | |
| Monoid a => Monoid (Dual a) | |
| Monoid (Endo a) | |
| Num a => Monoid (Sum a) | |
| Num a => Monoid (Product a) | |
| Monoid (First a) | |
| Monoid (Last a) | |
| Monoid (Seq a) | |
| Monoid (IntMap a) | |
| Ord a => Monoid (Set a) | |
| Monoid (Doc a) | |
| Monoid (Array a) | |
| Monoid (DList a) | |
| Monoid (Vector a) | |
| Monoid (Parser a) | |
| Monoid (Result a) | |
| Monoid (IResult a) | |
| Prim a => Monoid (Vector a) | |
| Storable a => Monoid (Vector a) | |
| (Hashable a, Eq a) => Monoid (HashSet a) | |
| Monoid (CountOf ty) | |
| PrimType ty => Monoid (Block ty) | |
| PrimType ty => Monoid (UArray ty) | |
| Monoid (Array a) | |
| Monoid (ChunkedUArray a) | |
| Monoid b => Monoid (a -> b) | |
| (Monoid a, Monoid b) => Monoid (a, b) | |
| Monoid (Proxy k s) | |
| Ord k => Monoid (Map k v) | |
| Monoid (ZipAsync m a) # | |
| Monoid (ZipStream m a) # | |
| Monoid (ParallelT m a) # | |
| Monoid (AsyncT m a) # | |
| Monoid (InterleavedT m a) # | |
| Monoid (StreamT m a) # | |
| Monoid (Parser i a) | |
| (Eq k, Hashable k) => Monoid (HashMap k v) | |
| (Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) | |
| Monoid a => Monoid (Const k a b) | |
| Alternative f => Monoid (Alt * f a) | |
| (Semigroup a, Monoid a) => Monoid (Tagged k s a) | |
| (Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) | |
| Monad m => Monoid (ConduitM i o m ()) | |
| (Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) | |
| Monad m => Monoid (Pipe l i o u m ()) | |
The class of semigroups (types with an associative binary operation).
Since: 4.9.0.0
Minimal complete definition
Nothing
Instances
class Applicative f => Alternative f where #
A monoid on applicative functors.
If defined, some and many should be the least solutions
 of the equations:
Instances
class (Alternative m, Monad m) => MonadPlus m where #
Monads that also support choice and failure.
Minimal complete definition
Nothing
Instances
class Monad m => MonadIO m where #
Monads in which IO computations may be embedded.
 Any monad built by applying a sequence of monad transformers to the
 IO monad will be an instance of this class.
Instances should satisfy the following laws, which state that liftIO
 is a transformer of monads:
Instances
| MonadIO IO | |
| MonadIO m => MonadIO (MaybeT m) | |
| MonadIO m => MonadIO (ListT m) | |
| MonadAsync m => MonadIO (ParallelT m) # | |
| MonadAsync m => MonadIO (AsyncT m) # | |
| MonadIO m => MonadIO (InterleavedT m) # | |
| MonadIO m => MonadIO (StreamT m) # | |
| MonadIO m => MonadIO (ResourceT m) | |
| (Monoid w, MonadIO m) => MonadIO (WriterT w m) | |
| (Monoid w, MonadIO m) => MonadIO (WriterT w m) | |
| MonadIO m => MonadIO (StateT s m) | |
| MonadIO m => MonadIO (StateT s m) | |
| MonadIO m => MonadIO (IdentityT * m) | |
| (Error e, MonadIO m) => MonadIO (ErrorT e m) | |
| MonadIO m => MonadIO (ExceptT e m) | |
| MonadIO m => MonadIO (ReaderT * r m) | |
| MonadIO m => MonadIO (ContT * r m) | |
| MonadIO m => MonadIO (ConduitM i o m) | |
| (Monoid w, MonadIO m) => MonadIO (RWST r w s m) | |
| (Monoid w, MonadIO m) => MonadIO (RWST r w s m) | |
| MonadIO m => MonadIO (Pipe l i o u m) | |
class MonadTrans t where #
The class of monad transformers.  Instances should satisfy the
 following laws, which state that lift is a monad transformation:
Instances
| MonadTrans MaybeT | |
| MonadTrans ListT | |
| MonadTrans ParallelT # | |
| MonadTrans AsyncT # | |
| MonadTrans InterleavedT # | |
| MonadTrans StreamT # | |
| MonadTrans ResourceT | |
| Monoid w => MonadTrans (WriterT w) | |
| Monoid w => MonadTrans (WriterT w) | |
| MonadTrans (StateT s) | |
| MonadTrans (StateT s) | |
| MonadTrans (IdentityT *) | |
| MonadTrans (ErrorT e) | |
| MonadTrans (ExceptT e) | |
| MonadTrans (ReaderT * r) | |
| MonadTrans (ContT * r) | |
| MonadTrans (ConduitM i o) | |
| Monoid w => MonadTrans (RWST r w s) | |
| Monoid w => MonadTrans (RWST r w s) | |
| MonadTrans (Pipe l i o u) | |