scc-0.1: Streaming component combinators

Control.Concurrent.SCC.ComponentTypes

Contents

Synopsis

Types

data Monad m => Splitter m x Source

The Splitter type represents computations that distribute data acording to some criteria. A splitter should distribute only the original input data, and feed it into the sinks in the same order it has been read from the source. If the two sink arguments of a splitter are the same, the splitter must act as an identity transform.

Constructors

Splitter 

Fields

split :: forall c1 c2 c3 context. Source c1 x -> Sink c2 x -> Sink c3 x -> Pipe context m [x]
 
splitSections :: forall c1 c2 c3 context. Source c1 x -> Sink c2 (Maybe x) -> Sink c3 (Maybe x) -> Pipe context m [x]
 

newtype Monad m => Transducer m x y Source

The Transducer type represents computations that transform data and return no result. A transducer must continue consuming the given source and feeding the sink while there is data.

Constructors

Transducer 

Fields

transduce :: forall c1 c2 context. Source c1 x -> Sink c2 y -> Pipe context m [x]
 

Lifting functions

lift121Transducer :: (Monad m, Typeable x, Typeable y) => (x -> y) -> Transducer m x ySource

Function lift121Transducer takes a function that maps one input value to one output value each, and lifts it into a Transducer.

liftStatelessTransducer :: (Monad m, Typeable x, Typeable y) => (x -> [y]) -> Transducer m x ySource

Function liftStatelessTransducer takes a function that maps one input value into a list of output values, and lifts it into a Transducer.

liftFoldTransducer :: (Monad m, Typeable x, Typeable y) => (y -> x -> y) -> y -> Transducer m x ySource

Function liftFoldTransducer creates a stateful transducer that produces only one output value after consuming the entire input. Similar to Data.List.foldl

liftStatefulTransducer :: (Monad m, Typeable x, Typeable y) => (state -> x -> (state, [y])) -> state -> Transducer m x ySource

Function liftStatefulTransducer constructs a Transducer from a state-transition function and the initial state. The transition function may produce arbitrary output at any transition step.

liftSimpleSplitter :: (Monad m, Typeable x) => (forall c1 c2 c3 context. Source c1 x -> Sink c2 x -> Sink c3 x -> Pipe context m [x]) -> Splitter m xSource

Function liftSimpleSplitter lifts a simple, non-sectioning splitter function into a full Splitter

liftSectionSplitter :: (Monad m, Typeable x) => (forall c1 c2 c3 context. Source c1 x -> Sink c2 (Maybe x) -> Sink c3 (Maybe x) -> Pipe context m [x]) -> Splitter m xSource

Function liftSectionSplitter lifts a sectioning splitter function into a full Splitter

liftStatelessSplitter :: (Monad m, Typeable x) => (x -> Bool) -> Splitter m xSource

Function liftStatelessSplitter takes a function that assigns a Boolean value to each input item and lifts it into a Splitter