tubes-0.2.2.3: Effectful, iteratee-inspired stream processing based on a free monad.

Safe HaskellSafe
LanguageHaskell2010

Tubes.Core

Contents

Synopsis

Basic definitions

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

A Tube is a computation which can

  • yield an intermediate value downstream and suspend execution; and
  • await a value from upstream, deferring execution until it is received.

Moreover, individual Tubes may be freely composed into larger ones, so long as their types match. Thus, one may write small, reusable building blocks and construct efficient stream process pipelines.

Since a much better engineered, more popular, and decidedly more mature library already uses the term "pipes" I have opted instead to think of my work as a series of tubes.

newtype TubeF a b k Source

TubeF is the union of unary functions and binary products into a single type, here defined with a Boehm-Berarducci encoding.

This type is equivalent to the following:

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

The type signatures for the two value constructors should bear a strong resemblance to the actual type signature of runT. Instead of encoding tubes as structures which build up when composed, a TubeF is a control flow mechanism which picks one of two provided continuations.

People using this library should never have to contend with these details but it is worth mentioning.

Constructors

TubeF 

Fields

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

Instances

Type aliases

type Source b m r = forall x. Tube x b m r Source

A computation which only yields and never awaits

type Sink a m r = forall x. Tube a x m r Source

A computation which only awaits and never yields.

Core commands

run :: FreeT f m a -> m (FreeF f a (FreeT f m a)) Source

run is shorter than runFreeT and who knows, maybe it'll change some day

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

Command to wait for a new value upstream

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

Command to send a value downstream

Control mechanisms

each :: (Monad m, Foldable t) => t b -> Tube a b m () Source

Convert a list to a Source

for :: Monad m => Tube a b m r -> (b -> Tube a c m s) -> Tube a c m r Source

Enumerate yielded values into a continuation, creating a new Source

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

Compose two tubes into a new tube.

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

Connect a task to a continuation yielding another task; see ><

(~>) :: Monad m => Tube a b m r -> (b -> Tube a c m s) -> Tube a c m r Source

Infix version of for

(-<) :: Monad m => a -> Sink a m b -> Sink a m b Source

Insert a value into a Sink

(|>) :: Monad m => Tube x b m r -> Sink (Maybe b) m s -> Sink (Maybe b) m s Source

Connects a Source to a Sink, finishing when either the Source is exhausted or the Sink terminates.

TubeF value constructors

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

Constructor for source computations

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

Constructor for sink computations

Miscellaneous

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

This performs a neat trick: a Tube with a return type a will be turned into a new Tube containing the underlying TubeF value.

In this way the >< and >- functions can replace the () return value with a continuation and recursively traverse the computation until a final result is reached.