streamly-0.1.2: Beautiful Streaming, Concurrent and Reactive Composition

Copyright(c) 2017 Harendra Kumar
LicenseBSD3
Maintainerharendra.kumar@gmail.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Streamly

Contents

Description

 

Synopsis

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 Streaming t Source #

Class of types that can represent a stream of elements of some type a in some monad m.

Minimal complete definition

toStream, fromStream

Instances

Streaming ZipAsync Source # 

Methods

toStream :: ZipAsync m a -> Stream m a

fromStream :: Stream m a -> ZipAsync m a

Streaming ZipStream Source # 

Methods

toStream :: ZipStream m a -> Stream m a

fromStream :: Stream m a -> ZipStream m a

Streaming ParallelT Source # 

Methods

toStream :: ParallelT m a -> Stream m a

fromStream :: Stream m a -> ParallelT m a

Streaming AsyncT Source # 

Methods

toStream :: AsyncT m a -> Stream m a

fromStream :: Stream m a -> AsyncT m a

Streaming InterleavedT Source # 

Methods

toStream :: InterleavedT m a -> Stream m a

fromStream :: Stream m a -> InterleavedT m a

Streaming StreamT Source # 

Methods

toStream :: StreamT m a -> Stream m a

fromStream :: Stream m a -> StreamT m a

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.

data StreamT m a Source #

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 # 

Methods

lift :: Monad m => m a -> StreamT m a #

Streaming StreamT Source # 

Methods

toStream :: StreamT m a -> Stream m a

fromStream :: Stream m a -> StreamT m a

(MonadBase b m, Monad m) => MonadBase b (StreamT m) Source # 

Methods

liftBase :: b α -> StreamT m α #

MonadState s m => MonadState s (StreamT m) Source # 

Methods

get :: StreamT m s #

put :: s -> StreamT m () #

state :: (s -> (a, s)) -> StreamT m a #

MonadReader r m => MonadReader r (StreamT m) Source # 

Methods

ask :: StreamT m r #

local :: (r -> r) -> StreamT m a -> StreamT m a #

reader :: (r -> a) -> StreamT m a #

MonadError e m => MonadError e (StreamT m) Source # 

Methods

throwError :: e -> StreamT m a #

catchError :: StreamT m a -> (e -> StreamT m a) -> StreamT m a #

Monad m => Monad (StreamT m) Source # 

Methods

(>>=) :: StreamT m a -> (a -> StreamT m b) -> StreamT m b #

(>>) :: StreamT m a -> StreamT m b -> StreamT m b #

return :: a -> StreamT m a #

fail :: String -> StreamT m a #

Monad m => Functor (StreamT m) Source # 

Methods

fmap :: (a -> b) -> StreamT m a -> StreamT m b #

(<$) :: a -> StreamT m b -> StreamT m a #

Monad m => Applicative (StreamT m) Source # 

Methods

pure :: a -> StreamT m a #

(<*>) :: StreamT m (a -> b) -> StreamT m a -> StreamT m b #

liftA2 :: (a -> b -> c) -> StreamT m a -> StreamT m b -> StreamT m c #

(*>) :: StreamT m a -> StreamT m b -> StreamT m b #

(<*) :: StreamT m a -> StreamT m b -> StreamT m a #

MonadIO m => MonadIO (StreamT m) Source # 

Methods

liftIO :: IO a -> StreamT m a #

MonadAsync m => Alternative (StreamT m) Source # 

Methods

empty :: StreamT m a #

(<|>) :: StreamT m a -> StreamT m a -> StreamT m a #

some :: StreamT m a -> StreamT m [a] #

many :: StreamT m a -> StreamT m [a] #

MonadAsync m => MonadPlus (StreamT m) Source # 

Methods

mzero :: StreamT m a #

mplus :: StreamT m a -> StreamT m a -> StreamT m a #

MonadThrow m => MonadThrow (StreamT m) Source # 

Methods

throwM :: Exception e => e -> StreamT m a #

(Monad m, Floating a) => Floating (StreamT m a) Source # 

Methods

pi :: StreamT m a #

exp :: StreamT m a -> StreamT m a #

log :: StreamT m a -> StreamT m a #

sqrt :: StreamT m a -> StreamT m a #

(**) :: StreamT m a -> StreamT m a -> StreamT m a #

logBase :: StreamT m a -> StreamT m a -> StreamT m a #

sin :: StreamT m a -> StreamT m a #

cos :: StreamT m a -> StreamT m a #

tan :: StreamT m a -> StreamT m a #

asin :: StreamT m a -> StreamT m a #

acos :: StreamT m a -> StreamT m a #

atan :: StreamT m a -> StreamT m a #

sinh :: StreamT m a -> StreamT m a #

cosh :: StreamT m a -> StreamT m a #

tanh :: StreamT m a -> StreamT m a #

asinh :: StreamT m a -> StreamT m a #

acosh :: StreamT m a -> StreamT m a #

atanh :: StreamT m a -> StreamT m a #

log1p :: StreamT m a -> StreamT m a #

expm1 :: StreamT m a -> StreamT m a #

log1pexp :: StreamT m a -> StreamT m a #

log1mexp :: StreamT m a -> StreamT m a #

(Monad m, Fractional a) => Fractional (StreamT m a) Source # 

Methods

(/) :: StreamT m a -> StreamT m a -> StreamT m a #

recip :: StreamT m a -> StreamT m a #

fromRational :: Rational -> StreamT m a #

(Monad m, Num a) => Num (StreamT m a) Source # 

Methods

(+) :: StreamT m a -> StreamT m a -> StreamT m a #

(-) :: StreamT m a -> StreamT m a -> StreamT m a #

(*) :: StreamT m a -> StreamT m a -> StreamT m a #

negate :: StreamT m a -> StreamT m a #

abs :: StreamT m a -> StreamT m a #

signum :: StreamT m a -> StreamT m a #

fromInteger :: Integer -> StreamT m a #

Semigroup (StreamT m a) Source # 

Methods

(<>) :: StreamT m a -> StreamT m a -> StreamT m a #

sconcat :: NonEmpty (StreamT m a) -> StreamT m a #

stimes :: Integral b => b -> StreamT m a -> StreamT m a #

Monoid (StreamT m a) Source # 

Methods

mempty :: StreamT m a #

mappend :: StreamT m a -> StreamT m a -> StreamT m a #

mconcat :: [StreamT m a] -> StreamT m a #

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 # 

Methods

lift :: Monad m => m a -> InterleavedT m a #

Streaming InterleavedT Source # 

Methods

toStream :: InterleavedT m a -> Stream m a

fromStream :: Stream m a -> InterleavedT m a

(MonadBase b m, Monad m) => MonadBase b (InterleavedT m) Source # 

Methods

liftBase :: b α -> InterleavedT m α #

MonadState s m => MonadState s (InterleavedT m) Source # 

Methods

get :: InterleavedT m s #

put :: s -> InterleavedT m () #

state :: (s -> (a, s)) -> InterleavedT m a #

MonadReader r m => MonadReader r (InterleavedT m) Source # 

Methods

ask :: InterleavedT m r #

local :: (r -> r) -> InterleavedT m a -> InterleavedT m a #

reader :: (r -> a) -> InterleavedT m a #

MonadError e m => MonadError e (InterleavedT m) Source # 

Methods

throwError :: e -> InterleavedT m a #

catchError :: InterleavedT m a -> (e -> InterleavedT m a) -> InterleavedT m a #

Monad m => Monad (InterleavedT m) Source # 

Methods

(>>=) :: InterleavedT m a -> (a -> InterleavedT m b) -> InterleavedT m b #

(>>) :: InterleavedT m a -> InterleavedT m b -> InterleavedT m b #

return :: a -> InterleavedT m a #

fail :: String -> InterleavedT m a #

Monad m => Functor (InterleavedT m) Source # 

Methods

fmap :: (a -> b) -> InterleavedT m a -> InterleavedT m b #

(<$) :: a -> InterleavedT m b -> InterleavedT m a #

Monad m => Applicative (InterleavedT m) Source # 

Methods

pure :: a -> InterleavedT m a #

(<*>) :: InterleavedT m (a -> b) -> InterleavedT m a -> InterleavedT m b #

liftA2 :: (a -> b -> c) -> InterleavedT m a -> InterleavedT m b -> InterleavedT m c #

(*>) :: InterleavedT m a -> InterleavedT m b -> InterleavedT m b #

(<*) :: InterleavedT m a -> InterleavedT m b -> InterleavedT m a #

MonadIO m => MonadIO (InterleavedT m) Source # 

Methods

liftIO :: IO a -> InterleavedT m a #

MonadAsync m => Alternative (InterleavedT m) Source # 

Methods

empty :: InterleavedT m a #

(<|>) :: InterleavedT m a -> InterleavedT m a -> InterleavedT m a #

some :: InterleavedT m a -> InterleavedT m [a] #

many :: InterleavedT m a -> InterleavedT m [a] #

MonadAsync m => MonadPlus (InterleavedT m) Source # 

Methods

mzero :: InterleavedT m a #

mplus :: InterleavedT m a -> InterleavedT m a -> InterleavedT m a #

MonadThrow m => MonadThrow (InterleavedT m) Source # 

Methods

throwM :: Exception e => e -> InterleavedT m a #

(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 # 

Methods

(<>) :: InterleavedT m a -> InterleavedT m a -> InterleavedT m a #

sconcat :: NonEmpty (InterleavedT m a) -> InterleavedT m a #

stimes :: Integral b => b -> InterleavedT m a -> InterleavedT m a #

Monoid (InterleavedT m a) Source # 

data AsyncT 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 # 

Methods

lift :: Monad m => m a -> AsyncT m a #

Streaming AsyncT Source # 

Methods

toStream :: AsyncT m a -> Stream m a

fromStream :: Stream m a -> AsyncT m a

(MonadBase b m, MonadAsync m) => MonadBase b (AsyncT m) Source # 

Methods

liftBase :: b α -> AsyncT m α #

(MonadState s m, MonadAsync m) => MonadState s (AsyncT m) Source # 

Methods

get :: AsyncT m s #

put :: s -> AsyncT m () #

state :: (s -> (a, s)) -> AsyncT m a #

(MonadReader r m, MonadAsync m) => MonadReader r (AsyncT m) Source # 

Methods

ask :: AsyncT m r #

local :: (r -> r) -> AsyncT m a -> AsyncT m a #

reader :: (r -> a) -> AsyncT m a #

(MonadError e m, MonadAsync m) => MonadError e (AsyncT m) Source # 

Methods

throwError :: e -> AsyncT m a #

catchError :: AsyncT m a -> (e -> AsyncT m a) -> AsyncT m a #

MonadAsync m => Monad (AsyncT m) Source # 

Methods

(>>=) :: AsyncT m a -> (a -> AsyncT m b) -> AsyncT m b #

(>>) :: AsyncT m a -> AsyncT m b -> AsyncT m b #

return :: a -> AsyncT m a #

fail :: String -> AsyncT m a #

Monad m => Functor (AsyncT m) Source # 

Methods

fmap :: (a -> b) -> AsyncT m a -> AsyncT m b #

(<$) :: a -> AsyncT m b -> AsyncT m a #

MonadAsync m => Applicative (AsyncT m) Source # 

Methods

pure :: a -> AsyncT m a #

(<*>) :: AsyncT m (a -> b) -> AsyncT m a -> AsyncT m b #

liftA2 :: (a -> b -> c) -> AsyncT m a -> AsyncT m b -> AsyncT m c #

(*>) :: AsyncT m a -> AsyncT m b -> AsyncT m b #

(<*) :: AsyncT m a -> AsyncT m b -> AsyncT m a #

MonadAsync m => MonadIO (AsyncT m) Source # 

Methods

liftIO :: IO a -> AsyncT m a #

MonadAsync m => Alternative (AsyncT m) Source # 

Methods

empty :: AsyncT m a #

(<|>) :: AsyncT m a -> AsyncT m a -> AsyncT m a #

some :: AsyncT m a -> AsyncT m [a] #

many :: AsyncT m a -> AsyncT m [a] #

MonadAsync m => MonadPlus (AsyncT m) Source # 

Methods

mzero :: AsyncT m a #

mplus :: AsyncT m a -> AsyncT m a -> AsyncT m a #

MonadAsync m => MonadThrow (AsyncT m) Source # 

Methods

throwM :: Exception e => e -> AsyncT m a #

(MonadAsync m, Floating a) => Floating (AsyncT m a) Source # 

Methods

pi :: AsyncT m a #

exp :: AsyncT m a -> AsyncT m a #

log :: AsyncT m a -> AsyncT m a #

sqrt :: AsyncT m a -> AsyncT m a #

(**) :: AsyncT m a -> AsyncT m a -> AsyncT m a #

logBase :: AsyncT m a -> AsyncT m a -> AsyncT m a #

sin :: AsyncT m a -> AsyncT m a #

cos :: AsyncT m a -> AsyncT m a #

tan :: AsyncT m a -> AsyncT m a #

asin :: AsyncT m a -> AsyncT m a #

acos :: AsyncT m a -> AsyncT m a #

atan :: AsyncT m a -> AsyncT m a #

sinh :: AsyncT m a -> AsyncT m a #

cosh :: AsyncT m a -> AsyncT m a #

tanh :: AsyncT m a -> AsyncT m a #

asinh :: AsyncT m a -> AsyncT m a #

acosh :: AsyncT m a -> AsyncT m a #

atanh :: AsyncT m a -> AsyncT m a #

log1p :: AsyncT m a -> AsyncT m a #

expm1 :: AsyncT m a -> AsyncT m a #

log1pexp :: AsyncT m a -> AsyncT m a #

log1mexp :: AsyncT m a -> AsyncT m a #

(MonadAsync m, Fractional a) => Fractional (AsyncT m a) Source # 

Methods

(/) :: AsyncT m a -> AsyncT m a -> AsyncT m a #

recip :: AsyncT m a -> AsyncT m a #

fromRational :: Rational -> AsyncT m a #

(MonadAsync m, Num a) => Num (AsyncT m a) Source # 

Methods

(+) :: AsyncT m a -> AsyncT m a -> AsyncT m a #

(-) :: AsyncT m a -> AsyncT m a -> AsyncT m a #

(*) :: AsyncT m a -> AsyncT m a -> AsyncT m a #

negate :: AsyncT m a -> AsyncT m a #

abs :: AsyncT m a -> AsyncT m a #

signum :: AsyncT m a -> AsyncT m a #

fromInteger :: Integer -> AsyncT m a #

Semigroup (AsyncT m a) Source # 

Methods

(<>) :: AsyncT m a -> AsyncT m a -> AsyncT m a #

sconcat :: NonEmpty (AsyncT m a) -> AsyncT m a #

stimes :: Integral b => b -> AsyncT m a -> AsyncT m a #

Monoid (AsyncT m a) Source # 

Methods

mempty :: AsyncT m a #

mappend :: AsyncT m a -> AsyncT m a -> AsyncT m a #

mconcat :: [AsyncT m a] -> AsyncT m a #

data ParallelT 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 # 

Methods

lift :: Monad m => m a -> ParallelT m a #

Streaming ParallelT Source # 

Methods

toStream :: ParallelT m a -> Stream m a

fromStream :: Stream m a -> ParallelT m a

(MonadBase b m, MonadAsync m) => MonadBase b (ParallelT m) Source # 

Methods

liftBase :: b α -> ParallelT m α #

(MonadState s m, MonadAsync m) => MonadState s (ParallelT m) Source # 

Methods

get :: ParallelT m s #

put :: s -> ParallelT m () #

state :: (s -> (a, s)) -> ParallelT m a #

(MonadReader r m, MonadAsync m) => MonadReader r (ParallelT m) Source # 

Methods

ask :: ParallelT m r #

local :: (r -> r) -> ParallelT m a -> ParallelT m a #

reader :: (r -> a) -> ParallelT m a #

(MonadError e m, MonadAsync m) => MonadError e (ParallelT m) Source # 

Methods

throwError :: e -> ParallelT m a #

catchError :: ParallelT m a -> (e -> ParallelT m a) -> ParallelT m a #

MonadAsync m => Monad (ParallelT m) Source # 

Methods

(>>=) :: ParallelT m a -> (a -> ParallelT m b) -> ParallelT m b #

(>>) :: ParallelT m a -> ParallelT m b -> ParallelT m b #

return :: a -> ParallelT m a #

fail :: String -> ParallelT m a #

Monad m => Functor (ParallelT m) Source # 

Methods

fmap :: (a -> b) -> ParallelT m a -> ParallelT m b #

(<$) :: a -> ParallelT m b -> ParallelT m a #

MonadAsync m => Applicative (ParallelT m) Source # 

Methods

pure :: a -> ParallelT m a #

(<*>) :: ParallelT m (a -> b) -> ParallelT m a -> ParallelT m b #

liftA2 :: (a -> b -> c) -> ParallelT m a -> ParallelT m b -> ParallelT m c #

(*>) :: ParallelT m a -> ParallelT m b -> ParallelT m b #

(<*) :: ParallelT m a -> ParallelT m b -> ParallelT m a #

MonadAsync m => MonadIO (ParallelT m) Source # 

Methods

liftIO :: IO a -> ParallelT m a #

MonadAsync m => Alternative (ParallelT m) Source # 

Methods

empty :: ParallelT m a #

(<|>) :: ParallelT m a -> ParallelT m a -> ParallelT m a #

some :: ParallelT m a -> ParallelT m [a] #

many :: ParallelT m a -> ParallelT m [a] #

MonadAsync m => MonadPlus (ParallelT m) Source # 

Methods

mzero :: ParallelT m a #

mplus :: ParallelT m a -> ParallelT m a -> ParallelT m a #

MonadAsync m => MonadThrow (ParallelT m) Source # 

Methods

throwM :: Exception e => e -> ParallelT m a #

(MonadAsync m, Floating a) => Floating (ParallelT m a) Source # 

Methods

pi :: ParallelT m a #

exp :: ParallelT m a -> ParallelT m a #

log :: ParallelT m a -> ParallelT m a #

sqrt :: ParallelT m a -> ParallelT m a #

(**) :: ParallelT m a -> ParallelT m a -> ParallelT m a #

logBase :: ParallelT m a -> ParallelT m a -> ParallelT m a #

sin :: ParallelT m a -> ParallelT m a #

cos :: ParallelT m a -> ParallelT m a #

tan :: ParallelT m a -> ParallelT m a #

asin :: ParallelT m a -> ParallelT m a #

acos :: ParallelT m a -> ParallelT m a #

atan :: ParallelT m a -> ParallelT m a #

sinh :: ParallelT m a -> ParallelT m a #

cosh :: ParallelT m a -> ParallelT m a #

tanh :: ParallelT m a -> ParallelT m a #

asinh :: ParallelT m a -> ParallelT m a #

acosh :: ParallelT m a -> ParallelT m a #

atanh :: ParallelT m a -> ParallelT m a #

log1p :: ParallelT m a -> ParallelT m a #

expm1 :: ParallelT m a -> ParallelT m a #

log1pexp :: ParallelT m a -> ParallelT m a #

log1mexp :: ParallelT m a -> ParallelT m a #

(MonadAsync m, Fractional a) => Fractional (ParallelT m a) Source # 

Methods

(/) :: ParallelT m a -> ParallelT m a -> ParallelT m a #

recip :: ParallelT m a -> ParallelT m a #

fromRational :: Rational -> ParallelT m a #

(MonadAsync m, Num a) => Num (ParallelT m a) Source # 

Methods

(+) :: ParallelT m a -> ParallelT m a -> ParallelT m a #

(-) :: ParallelT m a -> ParallelT m a -> ParallelT m a #

(*) :: ParallelT m a -> ParallelT m a -> ParallelT m a #

negate :: ParallelT m a -> ParallelT m a #

abs :: ParallelT m a -> ParallelT m a #

signum :: ParallelT m a -> ParallelT m a #

fromInteger :: Integer -> ParallelT m a #

Semigroup (ParallelT m a) Source # 

Methods

(<>) :: ParallelT m a -> ParallelT m a -> ParallelT m a #

sconcat :: NonEmpty (ParallelT m a) -> ParallelT m a #

stimes :: Integral b => b -> ParallelT m a -> ParallelT m a #

Monoid (ParallelT m a) Source # 

Methods

mempty :: ParallelT m a #

mappend :: ParallelT m a -> ParallelT m a -> ParallelT m a #

mconcat :: [ParallelT m a] -> ParallelT m a #

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.

data ZipStream m a Source #

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 # 

Methods

toStream :: ZipStream m a -> Stream m a

fromStream :: Stream m a -> ZipStream m a

Monad m => Functor (ZipStream m) Source # 

Methods

fmap :: (a -> b) -> ZipStream m a -> ZipStream m b #

(<$) :: a -> ZipStream m b -> ZipStream m a #

Monad m => Applicative (ZipStream m) Source # 

Methods

pure :: a -> ZipStream m a #

(<*>) :: ZipStream m (a -> b) -> ZipStream m a -> ZipStream m b #

liftA2 :: (a -> b -> c) -> ZipStream m a -> ZipStream m b -> ZipStream m c #

(*>) :: ZipStream m a -> ZipStream m b -> ZipStream m b #

(<*) :: ZipStream m a -> ZipStream m b -> ZipStream m a #

MonadAsync m => Alternative (ZipStream m) Source # 

Methods

empty :: ZipStream m a #

(<|>) :: ZipStream m a -> ZipStream m a -> ZipStream m a #

some :: ZipStream m a -> ZipStream m [a] #

many :: ZipStream m a -> ZipStream m [a] #

(Monad m, Floating a) => Floating (ZipStream m a) Source # 

Methods

pi :: ZipStream m a #

exp :: ZipStream m a -> ZipStream m a #

log :: ZipStream m a -> ZipStream m a #

sqrt :: ZipStream m a -> ZipStream m a #

(**) :: ZipStream m a -> ZipStream m a -> ZipStream m a #

logBase :: ZipStream m a -> ZipStream m a -> ZipStream m a #

sin :: ZipStream m a -> ZipStream m a #

cos :: ZipStream m a -> ZipStream m a #

tan :: ZipStream m a -> ZipStream m a #

asin :: ZipStream m a -> ZipStream m a #

acos :: ZipStream m a -> ZipStream m a #

atan :: ZipStream m a -> ZipStream m a #

sinh :: ZipStream m a -> ZipStream m a #

cosh :: ZipStream m a -> ZipStream m a #

tanh :: ZipStream m a -> ZipStream m a #

asinh :: ZipStream m a -> ZipStream m a #

acosh :: ZipStream m a -> ZipStream m a #

atanh :: ZipStream m a -> ZipStream m a #

log1p :: ZipStream m a -> ZipStream m a #

expm1 :: ZipStream m a -> ZipStream m a #

log1pexp :: ZipStream m a -> ZipStream m a #

log1mexp :: ZipStream m a -> ZipStream m a #

(Monad m, Fractional a) => Fractional (ZipStream m a) Source # 

Methods

(/) :: ZipStream m a -> ZipStream m a -> ZipStream m a #

recip :: ZipStream m a -> ZipStream m a #

fromRational :: Rational -> ZipStream m a #

(Monad m, Num a) => Num (ZipStream m a) Source # 

Methods

(+) :: ZipStream m a -> ZipStream m a -> ZipStream m a #

(-) :: ZipStream m a -> ZipStream m a -> ZipStream m a #

(*) :: ZipStream m a -> ZipStream m a -> ZipStream m a #

negate :: ZipStream m a -> ZipStream m a #

abs :: ZipStream m a -> ZipStream m a #

signum :: ZipStream m a -> ZipStream m a #

fromInteger :: Integer -> ZipStream m a #

Semigroup (ZipStream m a) Source # 

Methods

(<>) :: ZipStream m a -> ZipStream m a -> ZipStream m a #

sconcat :: NonEmpty (ZipStream m a) -> ZipStream m a #

stimes :: Integral b => b -> ZipStream m a -> ZipStream m a #

Monoid (ZipStream m a) Source # 

Methods

mempty :: ZipStream m a #

mappend :: ZipStream m a -> ZipStream m a -> ZipStream m a #

mconcat :: [ZipStream m a] -> ZipStream m a #

data ZipAsync 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 # 

Methods

toStream :: ZipAsync m a -> Stream m a

fromStream :: Stream m a -> ZipAsync m a

Monad m => Functor (ZipAsync m) Source # 

Methods

fmap :: (a -> b) -> ZipAsync m a -> ZipAsync m b #

(<$) :: a -> ZipAsync m b -> ZipAsync m a #

MonadAsync m => Applicative (ZipAsync m) Source # 

Methods

pure :: a -> ZipAsync m a #

(<*>) :: ZipAsync m (a -> b) -> ZipAsync m a -> ZipAsync m b #

liftA2 :: (a -> b -> c) -> ZipAsync m a -> ZipAsync m b -> ZipAsync m c #

(*>) :: ZipAsync m a -> ZipAsync m b -> ZipAsync m b #

(<*) :: ZipAsync m a -> ZipAsync m b -> ZipAsync m a #

MonadAsync m => Alternative (ZipAsync m) Source # 

Methods

empty :: ZipAsync m a #

(<|>) :: ZipAsync m a -> ZipAsync m a -> ZipAsync m a #

some :: ZipAsync m a -> ZipAsync m [a] #

many :: ZipAsync m a -> ZipAsync m [a] #

(MonadAsync m, Floating a) => Floating (ZipAsync m a) Source # 

Methods

pi :: ZipAsync m a #

exp :: ZipAsync m a -> ZipAsync m a #

log :: ZipAsync m a -> ZipAsync m a #

sqrt :: ZipAsync m a -> ZipAsync m a #

(**) :: ZipAsync m a -> ZipAsync m a -> ZipAsync m a #

logBase :: ZipAsync m a -> ZipAsync m a -> ZipAsync m a #

sin :: ZipAsync m a -> ZipAsync m a #

cos :: ZipAsync m a -> ZipAsync m a #

tan :: ZipAsync m a -> ZipAsync m a #

asin :: ZipAsync m a -> ZipAsync m a #

acos :: ZipAsync m a -> ZipAsync m a #

atan :: ZipAsync m a -> ZipAsync m a #

sinh :: ZipAsync m a -> ZipAsync m a #

cosh :: ZipAsync m a -> ZipAsync m a #

tanh :: ZipAsync m a -> ZipAsync m a #

asinh :: ZipAsync m a -> ZipAsync m a #

acosh :: ZipAsync m a -> ZipAsync m a #

atanh :: ZipAsync m a -> ZipAsync m a #

log1p :: ZipAsync m a -> ZipAsync m a #

expm1 :: ZipAsync m a -> ZipAsync m a #

log1pexp :: ZipAsync m a -> ZipAsync m a #

log1mexp :: ZipAsync m a -> ZipAsync m a #

(MonadAsync m, Fractional a) => Fractional (ZipAsync m a) Source # 

Methods

(/) :: ZipAsync m a -> ZipAsync m a -> ZipAsync m a #

recip :: ZipAsync m a -> ZipAsync m a #

fromRational :: Rational -> ZipAsync m a #

(MonadAsync m, Num a) => Num (ZipAsync m a) Source # 

Methods

(+) :: ZipAsync m a -> ZipAsync m a -> ZipAsync m a #

(-) :: ZipAsync m a -> ZipAsync m a -> ZipAsync m a #

(*) :: ZipAsync m a -> ZipAsync m a -> ZipAsync m a #

negate :: ZipAsync m a -> ZipAsync m a #

abs :: ZipAsync m a -> ZipAsync m a #

signum :: ZipAsync m a -> ZipAsync m a #

fromInteger :: Integer -> ZipAsync m a #

Semigroup (ZipAsync m a) Source # 

Methods

(<>) :: ZipAsync m a -> ZipAsync m a -> ZipAsync m a #

sconcat :: NonEmpty (ZipAsync m a) -> ZipAsync m a #

stimes :: Integral b => b -> ZipAsync m a -> ZipAsync m a #

Monoid (ZipAsync m a) Source # 

Methods

mempty :: ZipAsync m a #

mappend :: ZipAsync m a -> ZipAsync m a -> ZipAsync m a #

mconcat :: [ZipAsync m a] -> ZipAsync m a #

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.

serially :: StreamT m a -> StreamT m a Source #

Interpret an ambiguously typed stream as StreamT.

interleaving :: InterleavedT m a -> InterleavedT m a Source #

Interpret an ambiguously typed stream as InterleavedT.

asyncly :: AsyncT m a -> AsyncT m a Source #

Interpret an ambiguously typed stream as AsyncT.

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.

runAsyncT :: Monad m => AsyncT m a -> m () Source #

Same as runStreaming . asyncly.

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

class Monoid a where #

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 = foldr mappend 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.

Minimal complete definition

mempty, mappend

Methods

mempty :: a #

Identity of mappend

mappend :: a -> a -> a #

An associative operation

mconcat :: [a] -> a #

Fold a list using the monoid. For most types, the default definition for mconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types.

Instances

Monoid Ordering

Since: 2.1

Monoid ()

Since: 2.1

Methods

mempty :: () #

mappend :: () -> () -> () #

mconcat :: [()] -> () #

Monoid All

Since: 2.1

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Monoid Any

Since: 2.1

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Monoid [a]

Since: 2.1

Methods

mempty :: [a] #

mappend :: [a] -> [a] -> [a] #

mconcat :: [[a]] -> [a] #

Monoid a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S." Since there used to be no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Since: 2.1

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

Monoid a => Monoid (IO a)

Since: 4.9.0.0

Methods

mempty :: IO a #

mappend :: IO a -> IO a -> IO a #

mconcat :: [IO a] -> IO a #

(Ord a, Bounded a) => Monoid (Min a)

Since: 4.9.0.0

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

(Ord a, Bounded a) => Monoid (Max a)

Since: 4.9.0.0

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

Monoid m => Monoid (WrappedMonoid m)

Since: 4.9.0.0

Semigroup a => Monoid (Option a)

Since: 4.9.0.0

Methods

mempty :: Option a #

mappend :: Option a -> Option a -> Option a #

mconcat :: [Option a] -> Option a #

Monoid a => Monoid (Identity a) 

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

Monoid a => Monoid (Dual a)

Since: 2.1

Methods

mempty :: Dual a #

mappend :: Dual a -> Dual a -> Dual a #

mconcat :: [Dual a] -> Dual a #

Monoid (Endo a)

Since: 2.1

Methods

mempty :: Endo a #

mappend :: Endo a -> Endo a -> Endo a #

mconcat :: [Endo a] -> Endo a #

Num a => Monoid (Sum a)

Since: 2.1

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

Num a => Monoid (Product a)

Since: 2.1

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

Monoid (First a)

Since: 2.1

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

mconcat :: [First a] -> First a #

Monoid (Last a)

Since: 2.1

Methods

mempty :: Last a #

mappend :: Last a -> Last a -> Last a #

mconcat :: [Last a] -> Last a #

Ord a => Monoid (Set a) 

Methods

mempty :: Set a #

mappend :: Set a -> Set a -> Set a #

mconcat :: [Set a] -> Set a #

Monoid (Array a) 

Methods

mempty :: Array a #

mappend :: Array a -> Array a -> Array a #

mconcat :: [Array a] -> Array a #

Monoid b => Monoid (a -> b)

Since: 2.1

Methods

mempty :: a -> b #

mappend :: (a -> b) -> (a -> b) -> a -> b #

mconcat :: [a -> b] -> a -> b #

(Monoid a, Monoid b) => Monoid (a, b)

Since: 2.1

Methods

mempty :: (a, b) #

mappend :: (a, b) -> (a, b) -> (a, b) #

mconcat :: [(a, b)] -> (a, b) #

Monoid (Proxy k s)

Since: 4.7.0.0

Methods

mempty :: Proxy k s #

mappend :: Proxy k s -> Proxy k s -> Proxy k s #

mconcat :: [Proxy k s] -> Proxy k s #

Monoid (ZipAsync m a) # 

Methods

mempty :: ZipAsync m a #

mappend :: ZipAsync m a -> ZipAsync m a -> ZipAsync m a #

mconcat :: [ZipAsync m a] -> ZipAsync m a #

Monoid (ZipStream m a) # 

Methods

mempty :: ZipStream m a #

mappend :: ZipStream m a -> ZipStream m a -> ZipStream m a #

mconcat :: [ZipStream m a] -> ZipStream m a #

Monoid (ParallelT m a) # 

Methods

mempty :: ParallelT m a #

mappend :: ParallelT m a -> ParallelT m a -> ParallelT m a #

mconcat :: [ParallelT m a] -> ParallelT m a #

Monoid (AsyncT m a) # 

Methods

mempty :: AsyncT m a #

mappend :: AsyncT m a -> AsyncT m a -> AsyncT m a #

mconcat :: [AsyncT m a] -> AsyncT m a #

Monoid (InterleavedT m a) # 
Monoid (StreamT m a) # 

Methods

mempty :: StreamT m a #

mappend :: StreamT m a -> StreamT m a -> StreamT m a #

mconcat :: [StreamT m a] -> StreamT m a #

(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c)

Since: 2.1

Methods

mempty :: (a, b, c) #

mappend :: (a, b, c) -> (a, b, c) -> (a, b, c) #

mconcat :: [(a, b, c)] -> (a, b, c) #

Alternative f => Monoid (Alt * f a)

Since: 4.8.0.0

Methods

mempty :: Alt * f a #

mappend :: Alt * f a -> Alt * f a -> Alt * f a #

mconcat :: [Alt * f a] -> Alt * f a #

(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d)

Since: 2.1

Methods

mempty :: (a, b, c, d) #

mappend :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

mconcat :: [(a, b, c, d)] -> (a, b, c, d) #

(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e)

Since: 2.1

Methods

mempty :: (a, b, c, d, e) #

mappend :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e) #

class Semigroup a where #

The class of semigroups (types with an associative binary operation).

Since: 4.9.0.0

Methods

(<>) :: a -> a -> a infixr 6 #

An associative operation.

(a <> b) <> c = a <> (b <> c)

If a is also a Monoid we further require

(<>) = mappend

sconcat :: NonEmpty a -> a #

Reduce a non-empty list with <>

The default definition should be sufficient, but this can be overridden for efficiency.

stimes :: Integral b => b -> a -> a #

Repeat a value n times.

Given that this works on a Semigroup it is allowed to fail if you request 0 or fewer repetitions, and the default definition will do so.

By making this a member of the class, idempotent semigroups and monoids can upgrade this to execute in O(1) by picking stimes = stimesIdempotent or stimes = stimesIdempotentMonoid respectively.

Instances

Semigroup Ordering

Since: 4.9.0.0

Semigroup ()

Since: 4.9.0.0

Methods

(<>) :: () -> () -> () #

sconcat :: NonEmpty () -> () #

stimes :: Integral b => b -> () -> () #

Semigroup Void

Since: 4.9.0.0

Methods

(<>) :: Void -> Void -> Void #

sconcat :: NonEmpty Void -> Void #

stimes :: Integral b => b -> Void -> Void #

Semigroup Event

Since: 4.10.0.0

Methods

(<>) :: Event -> Event -> Event #

sconcat :: NonEmpty Event -> Event #

stimes :: Integral b => b -> Event -> Event #

Semigroup Lifetime

Since: 4.10.0.0

Semigroup All

Since: 4.9.0.0

Methods

(<>) :: All -> All -> All #

sconcat :: NonEmpty All -> All #

stimes :: Integral b => b -> All -> All #

Semigroup Any

Since: 4.9.0.0

Methods

(<>) :: Any -> Any -> Any #

sconcat :: NonEmpty Any -> Any #

stimes :: Integral b => b -> Any -> Any #

Semigroup [a]

Since: 4.9.0.0

Methods

(<>) :: [a] -> [a] -> [a] #

sconcat :: NonEmpty [a] -> [a] #

stimes :: Integral b => b -> [a] -> [a] #

Semigroup a => Semigroup (Maybe a)

Since: 4.9.0.0

Methods

(<>) :: Maybe a -> Maybe a -> Maybe a #

sconcat :: NonEmpty (Maybe a) -> Maybe a #

stimes :: Integral b => b -> Maybe a -> Maybe a #

Semigroup a => Semigroup (IO a)

Since: 4.10.0.0

Methods

(<>) :: IO a -> IO a -> IO a #

sconcat :: NonEmpty (IO a) -> IO a #

stimes :: Integral b => b -> IO a -> IO a #

Ord a => Semigroup (Min a)

Since: 4.9.0.0

Methods

(<>) :: Min a -> Min a -> Min a #

sconcat :: NonEmpty (Min a) -> Min a #

stimes :: Integral b => b -> Min a -> Min a #

Ord a => Semigroup (Max a)

Since: 4.9.0.0

Methods

(<>) :: Max a -> Max a -> Max a #

sconcat :: NonEmpty (Max a) -> Max a #

stimes :: Integral b => b -> Max a -> Max a #

Semigroup (First a)

Since: 4.9.0.0

Methods

(<>) :: First a -> First a -> First a #

sconcat :: NonEmpty (First a) -> First a #

stimes :: Integral b => b -> First a -> First a #

Semigroup (Last a)

Since: 4.9.0.0

Methods

(<>) :: Last a -> Last a -> Last a #

sconcat :: NonEmpty (Last a) -> Last a #

stimes :: Integral b => b -> Last a -> Last a #

Monoid m => Semigroup (WrappedMonoid m)

Since: 4.9.0.0

Semigroup a => Semigroup (Option a)

Since: 4.9.0.0

Methods

(<>) :: Option a -> Option a -> Option a #

sconcat :: NonEmpty (Option a) -> Option a #

stimes :: Integral b => b -> Option a -> Option a #

Semigroup (NonEmpty a)

Since: 4.9.0.0

Methods

(<>) :: NonEmpty a -> NonEmpty a -> NonEmpty a #

sconcat :: NonEmpty (NonEmpty a) -> NonEmpty a #

stimes :: Integral b => b -> NonEmpty a -> NonEmpty a #

Semigroup a => Semigroup (Identity a)

Since: 4.9.0.0

Methods

(<>) :: Identity a -> Identity a -> Identity a #

sconcat :: NonEmpty (Identity a) -> Identity a #

stimes :: Integral b => b -> Identity a -> Identity a #

Semigroup a => Semigroup (Dual a)

Since: 4.9.0.0

Methods

(<>) :: Dual a -> Dual a -> Dual a #

sconcat :: NonEmpty (Dual a) -> Dual a #

stimes :: Integral b => b -> Dual a -> Dual a #

Semigroup (Endo a)

Since: 4.9.0.0

Methods

(<>) :: Endo a -> Endo a -> Endo a #

sconcat :: NonEmpty (Endo a) -> Endo a #

stimes :: Integral b => b -> Endo a -> Endo a #

Num a => Semigroup (Sum a)

Since: 4.9.0.0

Methods

(<>) :: Sum a -> Sum a -> Sum a #

sconcat :: NonEmpty (Sum a) -> Sum a #

stimes :: Integral b => b -> Sum a -> Sum a #

Num a => Semigroup (Product a)

Since: 4.9.0.0

Methods

(<>) :: Product a -> Product a -> Product a #

sconcat :: NonEmpty (Product a) -> Product a #

stimes :: Integral b => b -> Product a -> Product a #

Semigroup (First a)

Since: 4.9.0.0

Methods

(<>) :: First a -> First a -> First a #

sconcat :: NonEmpty (First a) -> First a #

stimes :: Integral b => b -> First a -> First a #

Semigroup (Last a)

Since: 4.9.0.0

Methods

(<>) :: Last a -> Last a -> Last a #

sconcat :: NonEmpty (Last a) -> Last a #

stimes :: Integral b => b -> Last a -> Last a #

Ord a => Semigroup (Set a) 

Methods

(<>) :: Set a -> Set a -> Set a #

sconcat :: NonEmpty (Set a) -> Set a #

stimes :: Integral b => b -> Set a -> Set a #

Semigroup (Array a) 

Methods

(<>) :: Array a -> Array a -> Array a #

sconcat :: NonEmpty (Array a) -> Array a #

stimes :: Integral b => b -> Array a -> Array a #

Semigroup b => Semigroup (a -> b)

Since: 4.9.0.0

Methods

(<>) :: (a -> b) -> (a -> b) -> a -> b #

sconcat :: NonEmpty (a -> b) -> a -> b #

stimes :: Integral b => b -> (a -> b) -> a -> b #

Semigroup (Either a b)

Since: 4.9.0.0

Methods

(<>) :: Either a b -> Either a b -> Either a b #

sconcat :: NonEmpty (Either a b) -> Either a b #

stimes :: Integral b => b -> Either a b -> Either a b #

(Semigroup a, Semigroup b) => Semigroup (a, b)

Since: 4.9.0.0

Methods

(<>) :: (a, b) -> (a, b) -> (a, b) #

sconcat :: NonEmpty (a, b) -> (a, b) #

stimes :: Integral b => b -> (a, b) -> (a, b) #

Semigroup (Proxy k s)

Since: 4.9.0.0

Methods

(<>) :: Proxy k s -> Proxy k s -> Proxy k s #

sconcat :: NonEmpty (Proxy k s) -> Proxy k s #

stimes :: Integral b => b -> Proxy k s -> Proxy k s #

Semigroup (ZipAsync m a) # 

Methods

(<>) :: ZipAsync m a -> ZipAsync m a -> ZipAsync m a #

sconcat :: NonEmpty (ZipAsync m a) -> ZipAsync m a #

stimes :: Integral b => b -> ZipAsync m a -> ZipAsync m a #

Semigroup (ZipStream m a) # 

Methods

(<>) :: ZipStream m a -> ZipStream m a -> ZipStream m a #

sconcat :: NonEmpty (ZipStream m a) -> ZipStream m a #

stimes :: Integral b => b -> ZipStream m a -> ZipStream m a #

Semigroup (ParallelT m a) # 

Methods

(<>) :: ParallelT m a -> ParallelT m a -> ParallelT m a #

sconcat :: NonEmpty (ParallelT m a) -> ParallelT m a #

stimes :: Integral b => b -> ParallelT m a -> ParallelT m a #

Semigroup (AsyncT m a) # 

Methods

(<>) :: AsyncT m a -> AsyncT m a -> AsyncT m a #

sconcat :: NonEmpty (AsyncT m a) -> AsyncT m a #

stimes :: Integral b => b -> AsyncT m a -> AsyncT m a #

Semigroup (InterleavedT m a) # 

Methods

(<>) :: InterleavedT m a -> InterleavedT m a -> InterleavedT m a #

sconcat :: NonEmpty (InterleavedT m a) -> InterleavedT m a #

stimes :: Integral b => b -> InterleavedT m a -> InterleavedT m a #

Semigroup (StreamT m a) # 

Methods

(<>) :: StreamT m a -> StreamT m a -> StreamT m a #

sconcat :: NonEmpty (StreamT m a) -> StreamT m a #

stimes :: Integral b => b -> StreamT m a -> StreamT m a #

(Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c)

Since: 4.9.0.0

Methods

(<>) :: (a, b, c) -> (a, b, c) -> (a, b, c) #

sconcat :: NonEmpty (a, b, c) -> (a, b, c) #

stimes :: Integral b => b -> (a, b, c) -> (a, b, c) #

Semigroup a => Semigroup (Const k a b)

Since: 4.9.0.0

Methods

(<>) :: Const k a b -> Const k a b -> Const k a b #

sconcat :: NonEmpty (Const k a b) -> Const k a b #

stimes :: Integral b => b -> Const k a b -> Const k a b #

Alternative f => Semigroup (Alt * f a)

Since: 4.9.0.0

Methods

(<>) :: Alt * f a -> Alt * f a -> Alt * f a #

sconcat :: NonEmpty (Alt * f a) -> Alt * f a #

stimes :: Integral b => b -> Alt * f a -> Alt * f a #

(Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d)

Since: 4.9.0.0

Methods

(<>) :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

sconcat :: NonEmpty (a, b, c, d) -> (a, b, c, d) #

stimes :: Integral b => b -> (a, b, c, d) -> (a, b, c, d) #

(Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e)

Since: 4.9.0.0

Methods

(<>) :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

sconcat :: NonEmpty (a, b, c, d, e) -> (a, b, c, d, e) #

stimes :: Integral b => b -> (a, b, c, d, e) -> (a, b, c, d, e) #

class Applicative f => Alternative (f :: * -> *) where #

A monoid on applicative functors.

If defined, some and many should be the least solutions of the equations:

  • some v = (:) <$> v <*> many v
  • many v = some v <|> pure []

Minimal complete definition

empty, (<|>)

Methods

empty :: f a #

The identity of <|>

(<|>) :: f a -> f a -> f a infixl 3 #

An associative binary operation

some :: f a -> f [a] #

One or more.

many :: f a -> f [a] #

Zero or more.

Instances

Alternative []

Since: 2.1

Methods

empty :: [a] #

(<|>) :: [a] -> [a] -> [a] #

some :: [a] -> [[a]] #

many :: [a] -> [[a]] #

Alternative Maybe

Since: 2.1

Methods

empty :: Maybe a #

(<|>) :: Maybe a -> Maybe a -> Maybe a #

some :: Maybe a -> Maybe [a] #

many :: Maybe a -> Maybe [a] #

Alternative IO

Since: 4.9.0.0

Methods

empty :: IO a #

(<|>) :: IO a -> IO a -> IO a #

some :: IO a -> IO [a] #

many :: IO a -> IO [a] #

Alternative Option

Since: 4.9.0.0

Methods

empty :: Option a #

(<|>) :: Option a -> Option a -> Option a #

some :: Option a -> Option [a] #

many :: Option a -> Option [a] #

Alternative STM

Since: 4.8.0.0

Methods

empty :: STM a #

(<|>) :: STM a -> STM a -> STM a #

some :: STM a -> STM [a] #

many :: STM a -> STM [a] #

Alternative Array 

Methods

empty :: Array a #

(<|>) :: Array a -> Array a -> Array a #

some :: Array a -> Array [a] #

many :: Array a -> Array [a] #

Alternative (U1 *)

Since: 4.9.0.0

Methods

empty :: U1 * a #

(<|>) :: U1 * a -> U1 * a -> U1 * a #

some :: U1 * a -> U1 * [a] #

many :: U1 * a -> U1 * [a] #

MonadPlus m => Alternative (WrappedMonad m)

Since: 2.1

Methods

empty :: WrappedMonad m a #

(<|>) :: WrappedMonad m a -> WrappedMonad m a -> WrappedMonad m a #

some :: WrappedMonad m a -> WrappedMonad m [a] #

many :: WrappedMonad m a -> WrappedMonad m [a] #

ArrowPlus a => Alternative (ArrowMonad a)

Since: 4.6.0.0

Methods

empty :: ArrowMonad a a #

(<|>) :: ArrowMonad a a -> ArrowMonad a a -> ArrowMonad a a #

some :: ArrowMonad a a -> ArrowMonad a [a] #

many :: ArrowMonad a a -> ArrowMonad a [a] #

Alternative (Proxy *)

Since: 4.9.0.0

Methods

empty :: Proxy * a #

(<|>) :: Proxy * a -> Proxy * a -> Proxy * a #

some :: Proxy * a -> Proxy * [a] #

many :: Proxy * a -> Proxy * [a] #

(Functor m, Monad m) => Alternative (MaybeT m) 

Methods

empty :: MaybeT m a #

(<|>) :: MaybeT m a -> MaybeT m a -> MaybeT m a #

some :: MaybeT m a -> MaybeT m [a] #

many :: MaybeT m a -> MaybeT m [a] #

Applicative m => Alternative (ListT m) 

Methods

empty :: ListT m a #

(<|>) :: ListT m a -> ListT m a -> ListT m a #

some :: ListT m a -> ListT m [a] #

many :: ListT m a -> ListT m [a] #

MonadAsync m => Alternative (ZipAsync m) # 

Methods

empty :: ZipAsync m a #

(<|>) :: ZipAsync m a -> ZipAsync m a -> ZipAsync m a #

some :: ZipAsync m a -> ZipAsync m [a] #

many :: ZipAsync m a -> ZipAsync m [a] #

MonadAsync m => Alternative (ZipStream m) # 

Methods

empty :: ZipStream m a #

(<|>) :: ZipStream m a -> ZipStream m a -> ZipStream m a #

some :: ZipStream m a -> ZipStream m [a] #

many :: ZipStream m a -> ZipStream m [a] #

MonadAsync m => Alternative (ParallelT m) # 

Methods

empty :: ParallelT m a #

(<|>) :: ParallelT m a -> ParallelT m a -> ParallelT m a #

some :: ParallelT m a -> ParallelT m [a] #

many :: ParallelT m a -> ParallelT m [a] #

MonadAsync m => Alternative (AsyncT m) # 

Methods

empty :: AsyncT m a #

(<|>) :: AsyncT m a -> AsyncT m a -> AsyncT m a #

some :: AsyncT m a -> AsyncT m [a] #

many :: AsyncT m a -> AsyncT m [a] #

MonadAsync m => Alternative (InterleavedT m) # 

Methods

empty :: InterleavedT m a #

(<|>) :: InterleavedT m a -> InterleavedT m a -> InterleavedT m a #

some :: InterleavedT m a -> InterleavedT m [a] #

many :: InterleavedT m a -> InterleavedT m [a] #

MonadAsync m => Alternative (StreamT m) # 

Methods

empty :: StreamT m a #

(<|>) :: StreamT m a -> StreamT m a -> StreamT m a #

some :: StreamT m a -> StreamT m [a] #

many :: StreamT m a -> StreamT m [a] #

Alternative f => Alternative (Rec1 * f)

Since: 4.9.0.0

Methods

empty :: Rec1 * f a #

(<|>) :: Rec1 * f a -> Rec1 * f a -> Rec1 * f a #

some :: Rec1 * f a -> Rec1 * f [a] #

many :: Rec1 * f a -> Rec1 * f [a] #

(ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b)

Since: 2.1

Methods

empty :: WrappedArrow a b a #

(<|>) :: WrappedArrow a b a -> WrappedArrow a b a -> WrappedArrow a b a #

some :: WrappedArrow a b a -> WrappedArrow a b [a] #

many :: WrappedArrow a b a -> WrappedArrow a b [a] #

Alternative f => Alternative (Alt * f) 

Methods

empty :: Alt * f a #

(<|>) :: Alt * f a -> Alt * f a -> Alt * f a #

some :: Alt * f a -> Alt * f [a] #

many :: Alt * f a -> Alt * f [a] #

(Functor m, Monad m, Monoid e) => Alternative (ExceptT e m) 

Methods

empty :: ExceptT e m a #

(<|>) :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a #

some :: ExceptT e m a -> ExceptT e m [a] #

many :: ExceptT e m a -> ExceptT e m [a] #

(Monoid w, Alternative m) => Alternative (WriterT w m) 

Methods

empty :: WriterT w m a #

(<|>) :: WriterT w m a -> WriterT w m a -> WriterT w m a #

some :: WriterT w m a -> WriterT w m [a] #

many :: WriterT w m a -> WriterT w m [a] #

(Functor m, MonadPlus m) => Alternative (StateT s m) 

Methods

empty :: StateT s m a #

(<|>) :: StateT s m a -> StateT s m a -> StateT s m a #

some :: StateT s m a -> StateT s m [a] #

many :: StateT s m a -> StateT s m [a] #

(Functor m, Monad m, Error e) => Alternative (ErrorT e m) 

Methods

empty :: ErrorT e m a #

(<|>) :: ErrorT e m a -> ErrorT e m a -> ErrorT e m a #

some :: ErrorT e m a -> ErrorT e m [a] #

many :: ErrorT e m a -> ErrorT e m [a] #

Alternative m => Alternative (IdentityT * m) 

Methods

empty :: IdentityT * m a #

(<|>) :: IdentityT * m a -> IdentityT * m a -> IdentityT * m a #

some :: IdentityT * m a -> IdentityT * m [a] #

many :: IdentityT * m a -> IdentityT * m [a] #

(Functor m, MonadPlus m) => Alternative (StateT s m) 

Methods

empty :: StateT s m a #

(<|>) :: StateT s m a -> StateT s m a -> StateT s m a #

some :: StateT s m a -> StateT s m [a] #

many :: StateT s m a -> StateT s m [a] #

(Monoid w, Alternative m) => Alternative (WriterT w m) 

Methods

empty :: WriterT w m a #

(<|>) :: WriterT w m a -> WriterT w m a -> WriterT w m a #

some :: WriterT w m a -> WriterT w m [a] #

many :: WriterT w m a -> WriterT w m [a] #

(Alternative f, Alternative g) => Alternative ((:*:) * f g)

Since: 4.9.0.0

Methods

empty :: (* :*: f) g a #

(<|>) :: (* :*: f) g a -> (* :*: f) g a -> (* :*: f) g a #

some :: (* :*: f) g a -> (* :*: f) g [a] #

many :: (* :*: f) g a -> (* :*: f) g [a] #

(Alternative f, Alternative g) => Alternative (Product * f g)

Since: 4.9.0.0

Methods

empty :: Product * f g a #

(<|>) :: Product * f g a -> Product * f g a -> Product * f g a #

some :: Product * f g a -> Product * f g [a] #

many :: Product * f g a -> Product * f g [a] #

Alternative m => Alternative (ReaderT * r m) 

Methods

empty :: ReaderT * r m a #

(<|>) :: ReaderT * r m a -> ReaderT * r m a -> ReaderT * r m a #

some :: ReaderT * r m a -> ReaderT * r m [a] #

many :: ReaderT * r m a -> ReaderT * r m [a] #

Alternative f => Alternative (M1 * i c f)

Since: 4.9.0.0

Methods

empty :: M1 * i c f a #

(<|>) :: M1 * i c f a -> M1 * i c f a -> M1 * i c f a #

some :: M1 * i c f a -> M1 * i c f [a] #

many :: M1 * i c f a -> M1 * i c f [a] #

(Alternative f, Applicative g) => Alternative ((:.:) * * f g)

Since: 4.9.0.0

Methods

empty :: (* :.: *) f g a #

(<|>) :: (* :.: *) f g a -> (* :.: *) f g a -> (* :.: *) f g a #

some :: (* :.: *) f g a -> (* :.: *) f g [a] #

many :: (* :.: *) f g a -> (* :.: *) f g [a] #

(Alternative f, Applicative g) => Alternative (Compose * * f g)

Since: 4.9.0.0

Methods

empty :: Compose * * f g a #

(<|>) :: Compose * * f g a -> Compose * * f g a -> Compose * * f g a #

some :: Compose * * f g a -> Compose * * f g [a] #

many :: Compose * * f g a -> Compose * * f g [a] #

(Monoid w, Functor m, MonadPlus m) => Alternative (RWST r w s m) 

Methods

empty :: RWST r w s m a #

(<|>) :: RWST r w s m a -> RWST r w s m a -> RWST r w s m a #

some :: RWST r w s m a -> RWST r w s m [a] #

many :: RWST r w s m a -> RWST r w s m [a] #

(Monoid w, Functor m, MonadPlus m) => Alternative (RWST r w s m) 

Methods

empty :: RWST r w s m a #

(<|>) :: RWST r w s m a -> RWST r w s m a -> RWST r w s m a #

some :: RWST r w s m a -> RWST r w s m [a] #

many :: RWST r w s m a -> RWST r w s m [a] #

class (Alternative m, Monad m) => MonadPlus (m :: * -> *) where #

Monads that also support choice and failure.

Methods

mzero :: m a #

the identity of mplus. It should also satisfy the equations

mzero >>= f  =  mzero
v >> mzero   =  mzero

mplus :: m a -> m a -> m a #

an associative operation

Instances

MonadPlus []

Since: 2.1

Methods

mzero :: [a] #

mplus :: [a] -> [a] -> [a] #

MonadPlus Maybe

Since: 2.1

Methods

mzero :: Maybe a #

mplus :: Maybe a -> Maybe a -> Maybe a #

MonadPlus IO

Since: 4.9.0.0

Methods

mzero :: IO a #

mplus :: IO a -> IO a -> IO a #

MonadPlus Option

Since: 4.9.0.0

Methods

mzero :: Option a #

mplus :: Option a -> Option a -> Option a #

MonadPlus STM

Since: 4.3.0.0

Methods

mzero :: STM a #

mplus :: STM a -> STM a -> STM a #

MonadPlus Array 

Methods

mzero :: Array a #

mplus :: Array a -> Array a -> Array a #

MonadPlus (U1 *)

Since: 4.9.0.0

Methods

mzero :: U1 * a #

mplus :: U1 * a -> U1 * a -> U1 * a #

(ArrowApply a, ArrowPlus a) => MonadPlus (ArrowMonad a)

Since: 4.6.0.0

Methods

mzero :: ArrowMonad a a #

mplus :: ArrowMonad a a -> ArrowMonad a a -> ArrowMonad a a #

MonadPlus (Proxy *)

Since: 4.9.0.0

Methods

mzero :: Proxy * a #

mplus :: Proxy * a -> Proxy * a -> Proxy * a #

Monad m => MonadPlus (MaybeT m) 

Methods

mzero :: MaybeT m a #

mplus :: MaybeT m a -> MaybeT m a -> MaybeT m a #

Monad m => MonadPlus (ListT m) 

Methods

mzero :: ListT m a #

mplus :: ListT m a -> ListT m a -> ListT m a #

MonadAsync m => MonadPlus (ParallelT m) # 

Methods

mzero :: ParallelT m a #

mplus :: ParallelT m a -> ParallelT m a -> ParallelT m a #

MonadAsync m => MonadPlus (AsyncT m) # 

Methods

mzero :: AsyncT m a #

mplus :: AsyncT m a -> AsyncT m a -> AsyncT m a #

MonadAsync m => MonadPlus (InterleavedT m) # 

Methods

mzero :: InterleavedT m a #

mplus :: InterleavedT m a -> InterleavedT m a -> InterleavedT m a #

MonadAsync m => MonadPlus (StreamT m) # 

Methods

mzero :: StreamT m a #

mplus :: StreamT m a -> StreamT m a -> StreamT m a #

MonadPlus f => MonadPlus (Rec1 * f)

Since: 4.9.0.0

Methods

mzero :: Rec1 * f a #

mplus :: Rec1 * f a -> Rec1 * f a -> Rec1 * f a #

MonadPlus f => MonadPlus (Alt * f) 

Methods

mzero :: Alt * f a #

mplus :: Alt * f a -> Alt * f a -> Alt * f a #

(Monad m, Monoid e) => MonadPlus (ExceptT e m) 

Methods

mzero :: ExceptT e m a #

mplus :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a #

(Monoid w, MonadPlus m) => MonadPlus (WriterT w m) 

Methods

mzero :: WriterT w m a #

mplus :: WriterT w m a -> WriterT w m a -> WriterT w m a #

MonadPlus m => MonadPlus (StateT s m) 

Methods

mzero :: StateT s m a #

mplus :: StateT s m a -> StateT s m a -> StateT s m a #

(Monad m, Error e) => MonadPlus (ErrorT e m) 

Methods

mzero :: ErrorT e m a #

mplus :: ErrorT e m a -> ErrorT e m a -> ErrorT e m a #

MonadPlus m => MonadPlus (IdentityT * m) 

Methods

mzero :: IdentityT * m a #

mplus :: IdentityT * m a -> IdentityT * m a -> IdentityT * m a #

MonadPlus m => MonadPlus (StateT s m) 

Methods

mzero :: StateT s m a #

mplus :: StateT s m a -> StateT s m a -> StateT s m a #

(Monoid w, MonadPlus m) => MonadPlus (WriterT w m) 

Methods

mzero :: WriterT w m a #

mplus :: WriterT w m a -> WriterT w m a -> WriterT w m a #

(MonadPlus f, MonadPlus g) => MonadPlus ((:*:) * f g)

Since: 4.9.0.0

Methods

mzero :: (* :*: f) g a #

mplus :: (* :*: f) g a -> (* :*: f) g a -> (* :*: f) g a #

(MonadPlus f, MonadPlus g) => MonadPlus (Product * f g)

Since: 4.9.0.0

Methods

mzero :: Product * f g a #

mplus :: Product * f g a -> Product * f g a -> Product * f g a #

MonadPlus m => MonadPlus (ReaderT * r m) 

Methods

mzero :: ReaderT * r m a #

mplus :: ReaderT * r m a -> ReaderT * r m a -> ReaderT * r m a #

MonadPlus f => MonadPlus (M1 * i c f)

Since: 4.9.0.0

Methods

mzero :: M1 * i c f a #

mplus :: M1 * i c f a -> M1 * i c f a -> M1 * i c f a #

(Monoid w, MonadPlus m) => MonadPlus (RWST r w s m) 

Methods

mzero :: RWST r w s m a #

mplus :: RWST r w s m a -> RWST r w s m a -> RWST r w s m a #

(Monoid w, MonadPlus m) => MonadPlus (RWST r w s m) 

Methods

mzero :: RWST r w s m a #

mplus :: RWST r w s m a -> RWST r w s m a -> RWST r w s m a #

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:

Minimal complete definition

liftIO

Methods

liftIO :: IO a -> m a #

Lift a computation from the IO monad.

Instances

MonadIO IO

Since: 4.9.0.0

Methods

liftIO :: IO a -> IO a #

MonadIO m => MonadIO (MaybeT m) 

Methods

liftIO :: IO a -> MaybeT m a #

MonadIO m => MonadIO (ListT m) 

Methods

liftIO :: IO a -> ListT m a #

MonadAsync m => MonadIO (ParallelT m) # 

Methods

liftIO :: IO a -> ParallelT m a #

MonadAsync m => MonadIO (AsyncT m) # 

Methods

liftIO :: IO a -> AsyncT m a #

MonadIO m => MonadIO (InterleavedT m) # 

Methods

liftIO :: IO a -> InterleavedT m a #

MonadIO m => MonadIO (StreamT m) # 

Methods

liftIO :: IO a -> StreamT m a #

MonadIO m => MonadIO (ExceptT e m) 

Methods

liftIO :: IO a -> ExceptT e m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 

Methods

liftIO :: IO a -> WriterT w m a #

MonadIO m => MonadIO (StateT s m) 

Methods

liftIO :: IO a -> StateT s m a #

(Error e, MonadIO m) => MonadIO (ErrorT e m) 

Methods

liftIO :: IO a -> ErrorT e m a #

MonadIO m => MonadIO (IdentityT * m) 

Methods

liftIO :: IO a -> IdentityT * m a #

MonadIO m => MonadIO (StateT s m) 

Methods

liftIO :: IO a -> StateT s m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 

Methods

liftIO :: IO a -> WriterT w m a #

MonadIO m => MonadIO (ReaderT * r m) 

Methods

liftIO :: IO a -> ReaderT * r m a #

MonadIO m => MonadIO (ContT * r m) 

Methods

liftIO :: IO a -> ContT * r m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 

Methods

liftIO :: IO a -> RWST r w s m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 

Methods

liftIO :: IO a -> RWST r w s m a #

class MonadTrans (t :: (* -> *) -> * -> *) where #

The class of monad transformers. Instances should satisfy the following laws, which state that lift is a monad transformation:

Minimal complete definition

lift

Methods

lift :: Monad m => m a -> t m a #

Lift a computation from the argument monad to the constructed monad.

Instances

MonadTrans MaybeT 

Methods

lift :: Monad m => m a -> MaybeT m a #

MonadTrans ListT 

Methods

lift :: Monad m => m a -> ListT m a #

MonadTrans ParallelT # 

Methods

lift :: Monad m => m a -> ParallelT m a #

MonadTrans AsyncT # 

Methods

lift :: Monad m => m a -> AsyncT m a #

MonadTrans InterleavedT # 

Methods

lift :: Monad m => m a -> InterleavedT m a #

MonadTrans StreamT # 

Methods

lift :: Monad m => m a -> StreamT m a #

MonadTrans (ExceptT e) 

Methods

lift :: Monad m => m a -> ExceptT e m a #

Monoid w => MonadTrans (WriterT w) 

Methods

lift :: Monad m => m a -> WriterT w m a #

MonadTrans (StateT s) 

Methods

lift :: Monad m => m a -> StateT s m a #

MonadTrans (ErrorT e) 

Methods

lift :: Monad m => m a -> ErrorT e m a #

MonadTrans (IdentityT *) 

Methods

lift :: Monad m => m a -> IdentityT * m a #

MonadTrans (StateT s) 

Methods

lift :: Monad m => m a -> StateT s m a #

Monoid w => MonadTrans (WriterT w) 

Methods

lift :: Monad m => m a -> WriterT w m a #

MonadTrans (ReaderT * r) 

Methods

lift :: Monad m => m a -> ReaderT * r m a #

MonadTrans (ContT * r) 

Methods

lift :: Monad m => m a -> ContT * r m a #

Monoid w => MonadTrans (RWST r w s) 

Methods

lift :: Monad m => m a -> RWST r w s m a #

Monoid w => MonadTrans (RWST r w s) 

Methods

lift :: Monad m => m a -> RWST r w s m a #