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

Copyright(c) 2014, 2015 Gatlin Johnson <gatlin@niltag.net>
LicenseGPL-3
Maintainergatlin@niltag.net
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Tubes

Contents

Description

This exists primarily for my own education. It is updated often as I try things and is probably, at this moment, wrong.

If you want to know more about iteratees:

http://okmij.org/ftp/Streams.html

My goals were to (1) learn more about iteratees and (2) see how far I could get using free monads.

Synopsis

Documentation

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.

Rather than using a normal ADT, which would certainly make the code a bit easier to read and write, a value of this type is actually a control flow mechanism accepting two continuations and choosing one or the other.

Client code should never actually have to deal with this.

Constructors

TubeF 

Fields

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

Instances

Functor (TubeF a b) 

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

A Tube is the free monad transformer arising from TubeF.

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

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

A computation which neither yields nor awaits

Re-exports

lift :: MonadTrans t => forall m a. Monad m => m a -> t m a

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

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

Core infrastructure

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

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

Constructor for sink computations

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

Constructor for source computations

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 -> (b -> Tube a c m s) -> Tube a c m r Source

Infix version of for

(>-) :: 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 -> Tube b c m r -> Tube a c m r infixl 3 Source

Compose two tasks in a pull-based stream

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

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.

Utilities

cat :: Monad m => Tube a a m r Source

Continuously relays any values it receives. Iteratee identity.

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

Transforms all incoming values according to some function.

drop :: Monad m => Int -> Tube a a m r Source

Refuses to yield the first n values it receives.

take :: Monad m => Int -> Tube a a m () Source

Relay only the first n elements of a stream.

takeWhile :: Monad m => (a -> Bool) -> Tube a a m () Source

Terminates the stream upon receiving a value violating the predicate

filter :: Monad m => (a -> Bool) -> Tube a a m r Source

Yields only values satisfying some predicate.

reduce Source

Arguments

:: Monad m 
=> (x -> a -> x)

step function

-> x

initial value

-> (x -> b)

final transformation

-> Source a m ()

stream source

-> m b 

Strict left-fold of a stream

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

Similar to each except it explicitly marks the stream as exhausted

unyield :: Monad m => Source b m () -> m (Maybe b) Source

Taps the next value from a source.

prompt :: Source String IO () Source

Source of Strings from stdin. This is mostly for debugging / ghci example purposes.

display :: Sink String IO () Source

Sink for Strings to stdout. This is mostly for debugging / ghci example purposes.