drinkery-0.3: Boozy streaming library

Safe HaskellSafe
LanguageHaskell2010

Data.Drinkery.Tap

Contents

Synopsis

Tap

newtype Tap r s m Source #

Tap m r s is a non-monadic, endless producer of s. It takes a request r.

Constructors

Tap 

Fields

Instances

CloseRequest r => Closable (Tap r s) Source # 

Methods

close :: Monad m => Tap r s m -> m () Source #

consTap :: (Semigroup r, Applicative m) => s -> Tap r s m -> Tap r s m Source #

Prepend a new element, delaying requests.

orderTap :: Semigroup r => r -> Tap r s m -> Tap r s m Source #

Send a request to a Tap.

makeTap :: Monad m => m (Tap r s m) -> Tap r s m Source #

Involve an action.

repeatTap :: Applicative m => s -> Tap r s m Source #

repeatTapM :: Applicative m => m s -> Tap r s m Source #

repeatTapM' :: Applicative m => m s -> Tap () s m Source #

newtype Joint r m s Source #

(<*>) zips two taps.

Constructors

Joint 

Fields

Instances

Functor m => Functor (Joint r m) Source # 

Methods

fmap :: (a -> b) -> Joint r m a -> Joint r m b #

(<$) :: a -> Joint r m b -> Joint r m a #

Applicative m => Applicative (Joint r m) Source # 

Methods

pure :: a -> Joint r m a #

(<*>) :: Joint r m (a -> b) -> Joint r m a -> Joint r m b #

liftA2 :: (a -> b -> c) -> Joint r m a -> Joint r m b -> Joint r m c #

(*>) :: Joint r m a -> Joint r m b -> Joint r m b #

(<*) :: Joint r m a -> Joint r m b -> Joint r m a #

Producer

newtype Producer r s m a Source #

Monadic producer

Constructors

Producer 

Fields

Instances

MonadSink t m => MonadSink t (Producer p q m) Source # 

Methods

receiving :: (forall (n :: * -> *). Monad n => t n -> n (a, t n)) -> Producer p q m a Source #

MonadTrans (Producer r s) Source # 

Methods

lift :: Monad m => m a -> Producer r s m a #

Monad (Producer r s m) Source # 

Methods

(>>=) :: Producer r s m a -> (a -> Producer r s m b) -> Producer r s m b #

(>>) :: Producer r s m a -> Producer r s m b -> Producer r s m b #

return :: a -> Producer r s m a #

fail :: String -> Producer r s m a #

Functor (Producer r s m) Source # 

Methods

fmap :: (a -> b) -> Producer r s m a -> Producer r s m b #

(<$) :: a -> Producer r s m b -> Producer r s m a #

Applicative (Producer r s m) Source # 

Methods

pure :: a -> Producer r s m a #

(<*>) :: Producer r s m (a -> b) -> Producer r s m a -> Producer r s m b #

liftA2 :: (a -> b -> c) -> Producer r s m a -> Producer r s m b -> Producer r s m c #

(*>) :: Producer r s m a -> Producer r s m b -> Producer r s m b #

(<*) :: Producer r s m a -> Producer r s m b -> Producer r s m a #

MonadIO m => MonadIO (Producer r s m) Source # 

Methods

liftIO :: IO a -> Producer r s m a #

yield :: (Semigroup r, Applicative f, Applicative m) => s -> Producer r (f s) m () Source #

accept :: Monoid r => Producer r s m r Source #

Accept orders and clear the queue.

inexhaustible :: Producer r s m x -> Tap r s m Source #

Create a infinite Tap from a Producer.

inexhaustible :: Producer r s (Sink tap m) x -> Distiller tap m r s

tapProducer :: (Monoid r, Applicative m, Alternative f) => Producer r (f s) m a -> Tap r (f s) m Source #

Run a Producer action and terminate the stream with eof.

tapProducer' :: (Applicative m, Alternative f) => Producer () (f s) m a -> Tap () (f s) m Source #

Specialised runProducer

produce :: (Semigroup r, Applicative m) => s -> Producer r s m () Source #

Produce one element. Orders are put off.

ListT

newtype ListT r m s Source #

Backtracking producer a.k.a. "ListT done right".

Constructors

ListT 

Fields

Instances

MonadSink t m => MonadSink t (ListT p m) Source # 

Methods

receiving :: (forall (n :: * -> *). Monad n => t n -> n (a, t n)) -> ListT p m a Source #

MonadTrans (ListT r) Source # 

Methods

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

Monad (ListT r m) Source # 

Methods

(>>=) :: ListT r m a -> (a -> ListT r m b) -> ListT r m b #

(>>) :: ListT r m a -> ListT r m b -> ListT r m b #

return :: a -> ListT r m a #

fail :: String -> ListT r m a #

Functor (ListT r m) Source # 

Methods

fmap :: (a -> b) -> ListT r m a -> ListT r m b #

(<$) :: a -> ListT r m b -> ListT r m a #

Applicative (ListT r m) Source # 

Methods

pure :: a -> ListT r m a #

(<*>) :: ListT r m (a -> b) -> ListT r m a -> ListT r m b #

liftA2 :: (a -> b -> c) -> ListT r m a -> ListT r m b -> ListT r m c #

(*>) :: ListT r m a -> ListT r m b -> ListT r m b #

(<*) :: ListT r m a -> ListT r m b -> ListT r m a #

MonadIO m => MonadIO (ListT r m) Source # 

Methods

liftIO :: IO a -> ListT r m a #

Alternative (ListT r m) Source # 

Methods

empty :: ListT r m a #

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

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

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

MonadPlus (ListT r m) Source # 

Methods

mzero :: ListT r m a #

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

sample :: Foldable f => f s -> ListT r m s Source #

Take all the elements in a Foldable container.

inquire :: Monoid r => ListT r m r Source #

Get a request.

tapListT :: (Semigroup r, Applicative m, Alternative f) => ListT r m s -> Tap r (f s) m Source #

Run ListT and terminate the stream with eof.

tapListT' :: (Applicative m, Alternative f) => ListT () m s -> Tap () (f s) m Source #

Specialised runListT

retractListT :: Monad m => ListT () m s -> m () Source #

Sink

consume :: (Monoid r, MonadSink (Tap r s) m) => m s Source #

leftover :: (Semigroup r, MonadSink (Tap r s) m) => s -> m () Source #

request :: (Semigroup r, MonadSink (Tap r s) m) => r -> m () Source #

prefetch :: (Monoid r, Semigroup r, MonadSink (Tap r s) m) => m s Source #

Get one element without consuming.

End of stream

eof :: (Applicative m, Alternative f) => Tap r (f a) m Source #

End of stream