sousit-0.4: Source/Sink/Transform: An alternative to lazy IO and iteratees.

Safe HaskellSafe-Inferred

Data.SouSiT.Sink

Contents

Synopsis

Documentation

data Sink i m r Source

Constructors

Sink 

Fields

sinkStatus :: m (SinkStatus i m r)
 

Instances

Monad m => Monad (Sink i m) 
Monad m => Functor (Sink i m) 
(Functor (Sink i m), Monad m) => Applicative (Sink i m) 

data SinkStatus i m r Source

Constructors

Cont (i -> m (Sink i m r)) (m r) 
Done (m r) 

closeSink :: Monad m => Sink i m r -> m rSource

Closes the sink and returns its result.

monadic functions

input :: Monad m => Sink a m aSource

Reads the next element. The sink returns a fail if it is closed before the input is received.

inputOr :: Monad m => m a -> Sink a m aSource

Reads the next element. If the sink is closed while waiting for the input, then the parameter is returned as the sinks result.

inputMap :: Monad m => (a -> m b) -> m b -> Sink a m bSource

Reads the next element. Returns (Just a) for the element or Nothing if the sink is closed before the input was available.

inputMaybe :: Monad m => Sink a m (Maybe a)Source

Reads the next element. Returns (Just a) for the element or Nothing if the sink is closed before the input was available.

skip :: (Eq n, Num n, Monad m) => n -> Sink a m ()Source

Skips n input elements. If the sink is closed before then the result will also be ().

utility functions

appendSink :: (Monad m, Monoid r) => Sink a m r -> Sink a m r -> Sink a m rSource

Concatenates two sinks that produce a monoid.

(=||=) :: (Monad m, Monoid r) => Sink a m r -> Sink a m r -> Sink a m rSource

Concatenates two sinks that produce a monoid.

feedList :: Monad m => [i] -> Sink i m r -> m (Sink i m r)Source

Feed a list of inputs to a sink.

liftSink :: (Monad m, Monad m') => (forall x. m x -> m' x) -> Sink i m r -> Sink i m' rSource

Changes the monad of a sink based upon a conversion function that maps the original monad to the new one.

sink construction

contSink :: Monad m => (i -> m (Sink i m r)) -> m r -> Sink i m rSource

contSink' :: Monad m => (i -> Sink i m r) -> m r -> Sink i m rSource

doneSink :: Monad m => m r -> Sink i m rSource

doneSink' :: Monad m => r -> Sink i m rSource

actionSink :: Monad m => (i -> m ()) -> Sink i m ()Source

Sink that executes a monadic action per input received. Does not terminate.

openCloseActionSink :: Monad m => m a -> (a -> m ()) -> (a -> i -> m ()) -> Sink i m ()Source

First calls open, then processes every input with process and when the sink is closed close is called. Does not terminate.

maybeSink :: Monad m => (i -> m (Maybe r)) -> Sink i m (Maybe r)Source

Sink that executes f for every input. The sink continues as long as the action returns Nothing, when the action returns Just, then that value is the result of the sink (and the sink is full).