tubes-2.1.0.0: Write stream processing computations with side effects in a series of tubes.

Safe HaskellTrustworthy
LanguageHaskell2010

Tubes.Core

Synopsis

Documentation

type Tube a b = FreeT (TubeF a b) Source

The central data type. Tubes stacked on top of the same base monad m may be composed in series, so long as their type arguments agree.

newtype TubeF a b k Source

TubeF defines the language of Tubes - namely, yield and await.

This type is merely the CPS-encoded version of the following much friendlier data type:

    data TubeF a b k
        = Await (a -> k)
        | Yield (b  , k)
        deriving (Functor)

This says: a tube computation is either paused awaiting upstream data, or paused yielding data downstream. The free monad transformer fleshes out the other cases, namely having finished with a final result value or wrapping a lower monad.

Constructors

TubeF 

Fields

runTubeF :: forall r. ((a -> k) -> r) -> ((b, k) -> r) -> r
 

Instances

Functor (TubeF a b) Source 

await :: Monad m => Tube a b m a Source

Command telling a Tube computation to pause and await upstream data.

yield :: Monad m => b -> Tube a b m () Source

Command telling a Tube computation to yield data downstream and pause.

halt :: Monad m => Tube a b m () Source

Command telling a Tube with base type () to simply stop.

(>-) :: Monad m => Tube a b m r -> (b -> Tube b c m r) -> Tube a c m r infixl 3 Source

Compose a Tube emitting values of type b with a continuation producing a suitable successor.

Used primarily to define '(><)'.

(><) :: Monad m => Tube a b m r -> Tube b c m r -> Tube a c m r infixl 3 Source

Compose compatible tubes in series to produce a new Tube.

    each [1..10] >(*2)< pour display

liftT :: (MonadTrans t, Monad m) => FreeT f m a -> t m (FreeF f a (FreeT f m a)) Source

diverge :: a Source

Used only in situations where a dummy value is needed. Actively working to get rid of this.

awaitF :: (a -> k) -> TubeF a b k Source

Value constructor for the first TubeF case.

yieldF :: b -> k -> TubeF a b k Source

Value constructor for the second TubeF case.

type Pump b a = CofreeT (PumpF b a) Source

Pumps are the dual of Tubes. Where a Tube may either be awaiting or yielding, a Pump is always in a position to send or recv data. They are the machines which run Tubes, essentially.

Pumps may be used to formulate infinite streams and folds.

TODO: more examples!

Note the type arguments are "backward" from the Tube point of view: a Pump b a w r may be sent values of type a and you may receive b values from it.

data PumpF b a k Source

The basis for the Pump comonad transformer. This says that a pump computation can send and receive data.

Constructors

PumpF 

Fields

sendF :: a -> k
 
recvF :: (b, k)
 

Instances

Functor (PumpF b a) Source 

pumpT :: Comonad w => w r -> (w r -> b -> w r) -> (w r -> (a, w r)) -> Pump a b w r Source

Construct a Pump based on an arbitrary comonad.

send :: Comonad w => b -> Pump a b w r -> Pump a b w r Source

Send a Pump a value, yielding a new Pump.

recv :: Comonad w => Pump a b w r -> (a, Pump a b w r) Source

Receive a value from a Pump, along with a new Pump for the future.

stream :: (Monad m, Comonad w) => (a -> b -> r) -> Pump c d w a -> Tube c d m b -> m r Source

Process a Tube stream with a given Pump, and merge their results.

streamM :: (Monad m, Comonad w) => (a -> b -> r) -> Pump c d w (m a) -> Tube c d m b -> m r Source

Process a Tube stream with an effectful Pump, and merge their results.

runTube :: Monad m => Tube () () m r -> m r Source

Run a self-contained Tube computation.

runFreeT :: FreeT f m a -> m (FreeF f a (FreeT f m a))