scc-0.7: Streaming component combinators

Control.Concurrent.SCC.Configurable

Contents

Description

The Components module defines thin wrappers around the Transducer and Splitter primitives and combinators, relying on the Control.Concurrent.SCC.ComponentTypes module.

Synopsis

Sink and Source types

data Sink m a x Source

A Sink can be used to yield values from any nested Coroutine computation whose functor provably descends from the functor a. It's the write-only end of a communication channel created by pipe.

data Source m a x Source

A Source can be used to read values into any nested Coroutine computation whose functor provably descends from the functor a. It's the read-only end of a communication channel created by pipe.

class (Functor a, Functor d) => AncestorFunctor a d

Class of functors that can be lifted.

Instances

Sink and Source constructors

pipe :: forall m a a1 a2 x r1 r2. (Monad m, Functor a, a1 ~ SinkFunctor a x, a2 ~ SourceFunctor a x) => (Sink m a1 x -> Coroutine a1 m r1) -> (Source m a2 x -> Coroutine a2 m r2) -> Coroutine a m (r1, r2)Source

The pipe function splits the computation into two concurrent parts, producer and consumer. The producer is given a Sink to put values into, and consumer a Source to get those values from. Once producer and consumer both complete, pipe returns their paired results.

pipeP :: forall m a a1 a2 x r1 r2. (MonadParallel m, Functor a, a1 ~ SinkFunctor a x, a2 ~ SourceFunctor a x) => (Sink m a1 x -> Coroutine a1 m r1) -> (Source m a2 x -> Coroutine a2 m r2) -> Coroutine a m (r1, r2)Source

The pipeP function is equivalent to pipe, except it runs the producer and the consumer in parallel.

pipeG :: forall m a a1 a2 x r1 r2. (Monad m, Functor a, a1 ~ SinkFunctor a x, a2 ~ SourceFunctor a x) => PairBinder m -> (Sink m a1 x -> Coroutine a1 m r1) -> (Source m a2 x -> Coroutine a2 m r2) -> Coroutine a m (r1, r2)Source

A generic version of pipe. The first argument is used to combine two computation steps.

nullSink :: forall m a x. Monad m => Sink m a xSource

A disconnected sink that ignores all values put into it.

nullSource :: forall m a x. Monad m => Source m a xSource

An empty source whose get always returns Nothing.

Operations on sinks and sources

Singleton operations

get :: forall m a d x. (Monad m, AncestorFunctor a d) => Source m a x -> Coroutine d m (Maybe x)Source

Function get tries to get a value from the given Source argument. The intervening Coroutine computations suspend all the way to the pipe function invocation that created the source. The function returns Nothing if the argument source is empty.

getWith :: forall m a d x. (Monad m, AncestorFunctor a d) => (x -> Coroutine d m ()) -> Source m a x -> Coroutine d m ()Source

Invokes its first argument with the value it gets from the source, if there is any to get.

peek :: forall m a d x. (Monad m, AncestorFunctor a d) => Source m a x -> Coroutine d m (Maybe x)Source

Function peek acts the same way as get, but doesn't actually consume the value from the source; sequential calls to peek will always return the same value.

put :: forall m a d x. (Monad m, AncestorFunctor a d) => Sink m a x -> x -> Coroutine d m ()Source

This function puts a value into the given Sink. The intervening Coroutine computations suspend up to the pipe invocation that has created the argument sink.

tryPut :: forall m a d x. (Monad m, AncestorFunctor a d) => Sink m a x -> x -> Coroutine d m BoolSource

Like put, but returns a Bool that determines if the sink is still active.

Lifting functions

liftSink :: forall m a d x. (Monad m, AncestorFunctor a d) => Sink m a x -> Sink m d xSource

Converts a Sink on the ancestor functor a into a sink on the descendant functor d.

liftSource :: forall m a d x. (Monad m, AncestorFunctor a d) => Source m a x -> Source m d xSource

Converts a Source on the ancestor functor a into a source on the descendant functor d.

Bulk operations

Fetching and moving data

pour :: forall m a1 a2 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => Source m a1 x -> Sink m a2 x -> Coroutine d m ()Source

Copies all data from the source argument into the sink argument.

tee :: forall m a1 a2 a3 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d, AncestorFunctor a3 d) => Source m a1 x -> Sink m a2 x -> Sink m a3 x -> Coroutine d m ()Source

tee is similar to pour except it distributes every input value from its source argument into its both sink arguments.

teeSink :: forall m a1 a2 a3 x. (Monad m, AncestorFunctor a1 a3, AncestorFunctor a2 a3) => Sink m a1 x -> Sink m a2 x -> Sink m a3 xSource

Every value put into a teeSink result sink goes into its both argument sinks: put (teeSink s1 s2) x is equivalent to put s1 x >> put s2 x. The putChunk method returns the list of values that couldn't fit into the second sink.

getList :: forall m a d x. (Monad m, AncestorFunctor a d) => Source m a x -> Coroutine d m [x]Source

getList returns the list of all values generated by the source.

putList :: forall m a d x. (Monad m, AncestorFunctor a d) => [x] -> Sink m a x -> Coroutine d m [x]Source

putList puts an entire list into its sink argument. If the coroutine fed by the sink dies, the remainder of the argument list is returned.

putQueue :: forall m a d x. (Monad m, AncestorFunctor a d) => Seq x -> Sink m a x -> Coroutine d m [x]Source

Like putList, except it puts the contents of the given Seq into the sink.

getTicked :: forall m a d x. (Monad m, AncestorFunctor a d) => Parser [x] [x] -> Source m a x -> Coroutine d m [x]Source

Consumes values from the source as long as the parser accepts them.

getWhile :: forall m a d x. (Monad m, AncestorFunctor a d) => (x -> Bool) -> Source m a x -> Coroutine d m [x]Source

Consumes values from the source as long as each satisfies the predicate, then returns their list.

getUntil :: forall m a d x. (Monad m, AncestorFunctor a d) => (x -> Bool) -> Source m a x -> Coroutine d m ([x], Maybe x)Source

Consumes values from the source until one of them satisfies the predicate or the source is emptied, then returns the pair of the list of preceding values and maybe the one value that satisfied the predicate. The latter is not consumed.

pourTicked :: forall m a1 a2 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => Parser [x] [x] -> Source m a1 x -> Sink m a2 x -> Coroutine d m ()Source

Like pour, copies data from the source to the sink, but only as long as it satisfies the predicate.

pourParsed :: forall m a1 a2 d x y. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => Parser [x] [y] -> Source m a1 x -> Sink m a2 y -> Coroutine d m ()Source

Parses the input data using the given parser and copies the results to output.

pourWhile :: forall m a1 a2 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Bool) -> Source m a1 x -> Sink m a2 x -> Coroutine d m ()Source

Like pour, copies data from the source to the sink, but only as long as it satisfies the predicate.

pourUntil :: forall m a1 a2 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Bool) -> Source m a1 x -> Sink m a2 x -> Coroutine d m (Maybe x)Source

Like pour, copies data from the source to the sink, but only until one value satisfies the predicate. That value is returned rather than copied.

Stream transformations

mapSink :: forall m a x y. Monad m => (x -> y) -> Sink m a y -> Sink m a xSource

An equivalent of Data.List.map that works on a Sink instead of a list. The argument function is applied to every value vefore it's written to the sink argument.

mapStream :: forall m a1 a2 d x y. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> y) -> Source m a1 x -> Sink m a2 y -> Coroutine d m ()Source

mapStream is like pour that applies the function f to each argument before passing it into the sink.

mapMaybeStream :: forall m a1 a2 d x y. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Maybe y) -> Source m a1 x -> Sink m a2 y -> Coroutine d m ()Source

mapMaybeStream is to mapStream like mapMaybe is to Data.List.map.

concatMapStream :: forall m a1 a2 d x y. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> [y]) -> Source m a1 x -> Sink m a2 y -> Coroutine d m ()Source

concatMapStream is to mapStream like Data.List.concatMap is to Data.List.map.

mapStreamChunks :: forall m a1 a2 d x y. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => ([x] -> [y]) -> Source m a1 x -> Sink m a2 y -> Coroutine d m ()Source

Like mapStream except it runs the argument function on whole chunks read from the input.

foldStream :: forall m a d x acc. (Monad m, AncestorFunctor a d) => (acc -> x -> acc) -> acc -> Source m a x -> Coroutine d m accSource

Similar to Data.List.foldl, but reads the values from a Source instead of a list.

mapAccumStream :: forall m a1 a2 d x y acc. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (acc -> x -> (acc, y)) -> acc -> Source m a1 x -> Sink m a2 y -> Coroutine d m accSource

mapAccumStream is similar to mapAccumL except it reads the values from a Source instead of a list and writes the mapped values into a Sink instead of returning another list.

concatMapAccumStream :: forall m a1 a2 d x y acc. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (acc -> x -> (acc, [y])) -> acc -> Source m a1 x -> Sink m a2 y -> Coroutine d m accSource

concatMapAccumStream is a love child of concatMapStream and mapAccumStream: it threads the accumulator like the latter, but its argument function returns not a single value, but a list of values to write into the sink.

partitionStream :: forall m a1 a2 a3 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d, AncestorFunctor a3 d) => (x -> Bool) -> Source m a1 x -> Sink m a2 x -> Sink m a3 x -> Coroutine d m ()Source

Equivalent to Data.List.partition. Takes a Source instead of a list argument and partitions its contents into the two Sink arguments.

Monadic stream transformations

mapMStream :: forall m a1 a2 d x y. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Coroutine d m y) -> Source m a1 x -> Sink m a2 y -> Coroutine d m ()Source

mapMStream is similar to mapM. It draws the values from a Source instead of a list, writes the mapped values to a Sink, and returns a Coroutine.

mapMStream_ :: forall m a d x. (Monad m, AncestorFunctor a d) => (x -> Coroutine d m ()) -> Source m a x -> Coroutine d m ()Source

mapMStream_ is similar to mapM_ except it draws the values from a Source instead of a list and works with Coroutine instead of an arbitrary monad.

mapMStreamChunks_ :: forall m a d x. (Monad m, AncestorFunctor a d) => ([x] -> Coroutine d m ()) -> Source m a x -> Coroutine d m ()Source

Like mapMStream_ except it runs the argument function on whole chunks read from the input.

filterMStream :: forall m a1 a2 d x. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d) => (x -> Coroutine d m Bool) -> Source m a1 x -> Sink m a2 x -> Coroutine d m ()Source

An equivalent of filterM. Draws the values from a Source instead of a list, writes the filtered values to a Sink, and returns a Coroutine.

foldMStream :: forall m a d x acc. (Monad m, AncestorFunctor a d) => (acc -> x -> Coroutine d m acc) -> acc -> Source m a x -> Coroutine d m accSource

foldMStream is similar to foldM except it draws the values from a Source instead of a list and works with Coroutine instead of an arbitrary monad.

foldMStream_ :: forall m a d x acc. (Monad m, AncestorFunctor a d) => (acc -> x -> Coroutine d m acc) -> acc -> Source m a x -> Coroutine d m ()Source

A variant of foldMStream that discards the final result value.

unfoldMStream :: forall m a d x acc. (Monad m, AncestorFunctor a d) => (acc -> Coroutine d m (Maybe (x, acc))) -> acc -> Sink m a x -> Coroutine d m accSource

unfoldMStream is a version of Data.List.unfoldr that writes the generated values into a Sink instead of returning a list.

unmapMStream_ :: forall m a d x. (Monad m, AncestorFunctor a d) => Coroutine d m (Maybe x) -> Sink m a x -> Coroutine d m ()Source

unmapMStream_ is opposite of mapMStream_; it takes a Sink instead of a Source argument and writes the generated values into it.

unmapMStreamChunks_ :: forall m a d x. (Monad m, AncestorFunctor a d) => Coroutine d m [x] -> Sink m a x -> Coroutine d m ()Source

Like unmapMStream_ but writing whole chunks of generated data into the argument sink.

zipWithMStream :: forall m a1 a2 a3 d x y z. (Monad m, AncestorFunctor a1 d, AncestorFunctor a2 d, AncestorFunctor a3 d) => (x -> y -> Coroutine d m z) -> Source m a1 x -> Source m a2 y -> Sink m a3 z -> Coroutine d m ()Source

zipWithMStream is similar to zipWithM except it draws the values from two Source arguments instead of two lists, sends the results into a Sink, and works with Coroutine instead of an arbitrary monad.

parZipWithMStream :: forall m a1 a2 a3 d x y z. (MonadParallel m, AncestorFunctor a1 d, AncestorFunctor a2 d, AncestorFunctor a3 d) => (x -> y -> Coroutine d m z) -> Source m a1 x -> Source m a2 y -> Sink m a3 z -> Coroutine d m ()Source

parZipWithMStream is equivalent to zipWithMStream, but it consumes the two sources in parallel.

Component types

newtype Performer m r Source

A coroutine that has no inputs nor outputs - and therefore may not suspend at all, which means it's not really a coroutine.

Constructors

Performer 

Fields

perform :: m r
 

Instances

Monad m => PipeableComponentPair m x (Producer m x ()) (Consumer m x ()) (Performer m ()) 
Monad m => JoinableComponentPair TransducerType (PerformerType r) TransducerType m [x] [y] (Transducer m x y) (Performer m r) (Transducer m x y) 
Monad m => JoinableComponentPair (PerformerType r) TransducerType TransducerType m [x] [y] (Performer m r) (Transducer m x y) (Transducer m x y) 
Monad m => JoinableComponentPair (PerformerType r1) (PerformerType r2) (PerformerType r2) m () () (Performer m r1) (Performer m r2) (Performer m r2) 
Monad m => JoinableComponentPair (PerformerType r1) (ProducerType r2) (ProducerType r2) m () [x] (Performer m r1) (Producer m x r2) (Producer m x r2) 
Monad m => JoinableComponentPair (ProducerType r1) (PerformerType r2) (ProducerType r2) m () [x] (Producer m x r1) (Performer m r2) (Producer m x r2) 
Monad m => JoinableComponentPair (PerformerType r1) (ConsumerType r2) (ConsumerType r2) m [x] () (Performer m r1) (Consumer m x r2) (Consumer m x r2) 
Monad m => JoinableComponentPair (ConsumerType r1) (PerformerType r2) (ConsumerType r2) m [x] () (Consumer m x r1) (Performer m r2) (Consumer m x r2) 
(AnyListOrUnit x, AnyListOrUnit y) => CompatibleSignature (Performer m r) (PerformerType r) m x y 
(AnyListOrUnit x, AnyListOrUnit y) => CompatibleSignature (Performer m r) (PerformerType r) m x y 

newtype Consumer m x r Source

A coroutine that consumes values from a Source.

Constructors

Consumer 

Fields

consume :: forall a d. OpenConsumer m a d x r
 

Instances

Monad m => PipeableComponentPair m x (Producer m x ()) (Consumer m x ()) (Performer m ()) 
Monad m => PipeableComponentPair m y (Transducer m x y) (Consumer m y r) (Consumer m x r) 
Monad m => JoinableComponentPair TransducerType (ConsumerType ()) TransducerType m [x] [y] (Transducer m x y) (Consumer m x ()) (Transducer m x y) 
Monad m => JoinableComponentPair (ConsumerType ()) TransducerType TransducerType m [x] [y] (Consumer m x ()) (Transducer m x y) (Transducer m x y) 
Monad m => JoinableComponentPair (ProducerType ()) (ConsumerType ()) TransducerType m [x] [y] (Producer m y ()) (Consumer m x ()) (Transducer m x y) 
Monad m => JoinableComponentPair (ConsumerType ()) (ProducerType ()) TransducerType m [x] [y] (Consumer m x ()) (Producer m y ()) (Transducer m x y) 
Monad m => JoinableComponentPair (PerformerType r1) (ConsumerType r2) (ConsumerType r2) m [x] () (Performer m r1) (Consumer m x r2) (Consumer m x r2) 
Monad m => JoinableComponentPair (ConsumerType r1) (PerformerType r2) (ConsumerType r2) m [x] () (Consumer m x r1) (Performer m r2) (Consumer m x r2) 
Monad m => JoinableComponentPair (ConsumerType ()) (ConsumerType ()) (ConsumerType ()) m [x] () (Consumer m x ()) (Consumer m x ()) (Consumer m x ()) 
Monad m => Branching (Consumer m x r) m x r 
AnyListOrUnit y => CompatibleSignature (Consumer m x r) (ConsumerType r) m [x] y 
AnyListOrUnit y => CompatibleSignature (Consumer m x r) (ConsumerType r) m [x] y 

newtype Producer m x r Source

A coroutine that produces values and puts them into a Sink.

Constructors

Producer 

Fields

produce :: forall a d. OpenProducer m a d x r
 

Instances

Monad m => PipeableComponentPair m x (Producer m x ()) (Consumer m x ()) (Performer m ()) 
Monad m => PipeableComponentPair m x (Producer m x r) (Transducer m x y) (Producer m y r) 
Monad m => JoinableComponentPair TransducerType (ProducerType ()) TransducerType m [x] [y] (Transducer m x y) (Producer m y ()) (Transducer m x y) 
Monad m => JoinableComponentPair (ProducerType ()) TransducerType TransducerType m [x] [y] (Producer m y ()) (Transducer m x y) (Transducer m x y) 
Monad m => JoinableComponentPair (ProducerType ()) (ConsumerType ()) TransducerType m [x] [y] (Producer m y ()) (Consumer m x ()) (Transducer m x y) 
Monad m => JoinableComponentPair (ConsumerType ()) (ProducerType ()) TransducerType m [x] [y] (Consumer m x ()) (Producer m y ()) (Transducer m x y) 
Monad m => JoinableComponentPair (PerformerType r1) (ProducerType r2) (ProducerType r2) m () [x] (Performer m r1) (Producer m x r2) (Producer m x r2) 
Monad m => JoinableComponentPair (ProducerType r1) (PerformerType r2) (ProducerType r2) m () [x] (Producer m x r1) (Performer m r2) (Producer m x r2) 
Monad m => JoinableComponentPair (ProducerType r1) (ProducerType r2) (ProducerType r2) m () [x] (Producer m x r1) (Producer m x r2) (Producer m x r2) 
AnyListOrUnit y => CompatibleSignature (Producer m x r) (ProducerType r) m y [x] 
AnyListOrUnit y => CompatibleSignature (Producer m x r) (ProducerType r) m y [x] 

newtype Transducer m x y Source

The Transducer type represents coroutines that transform a data stream. Execution of transduce must continue consuming the given Source and feeding the Sink as long as there is any data in the source.

Constructors

Transducer 

Fields

transduce :: forall a1 a2 d. OpenTransducer m a1 a2 d x y ()
 

Instances

Monad m => JoinableComponentPair TransducerType TransducerType TransducerType m [x] [y] (Transducer m x y) (Transducer m x y) (Transducer m x y) 
Monad m => PipeableComponentPair m y (Transducer m x y) (Transducer m y z) (Transducer m x z) 
Monad m => PipeableComponentPair m x (Producer m x r) (Transducer m x y) (Producer m y r) 
Monad m => PipeableComponentPair m y (Transducer m x y) (Consumer m y r) (Consumer m x r) 
Monad m => JoinableComponentPair TransducerType (PerformerType r) TransducerType m [x] [y] (Transducer m x y) (Performer m r) (Transducer m x y) 
Monad m => JoinableComponentPair TransducerType (ProducerType ()) TransducerType m [x] [y] (Transducer m x y) (Producer m y ()) (Transducer m x y) 
Monad m => JoinableComponentPair TransducerType (ConsumerType ()) TransducerType m [x] [y] (Transducer m x y) (Consumer m x ()) (Transducer m x y) 
Monad m => Category (Transducer m) 
Monad m => JoinableComponentPair (PerformerType r) TransducerType TransducerType m [x] [y] (Performer m r) (Transducer m x y) (Transducer m x y) 
Monad m => JoinableComponentPair (ProducerType ()) TransducerType TransducerType m [x] [y] (Producer m y ()) (Transducer m x y) (Transducer m x y) 
Monad m => JoinableComponentPair (ConsumerType ()) TransducerType TransducerType m [x] [y] (Consumer m x ()) (Transducer m x y) (Transducer m x y) 
Monad m => JoinableComponentPair (ProducerType ()) (ConsumerType ()) TransducerType m [x] [y] (Producer m y ()) (Consumer m x ()) (Transducer m x y) 
Monad m => JoinableComponentPair (ConsumerType ()) (ProducerType ()) TransducerType m [x] [y] (Consumer m x ()) (Producer m y ()) (Transducer m x y) 
Monad m => Branching (Transducer m x y) m x () 
CompatibleSignature (Transducer m x y) TransducerType m [x] [y] 
CompatibleSignature (Transducer m x y) TransducerType m [x] [y] 

newtype Splitter m x b Source

The Splitter type represents coroutines that distribute the input stream 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. Furthermore, the input source should be entirely consumed and fed into the first two sinks. The third sink can be used to supply extra information at arbitrary points in the input.

A splitter can be used in two ways: as a predicate to determine which portions of its input stream satisfy a certain property, or as a chunker to divide the input stream into chunks. In the former case, the predicate is considered true for exactly those parts of the input that are written to its true sink. In the latter case, a chunk is a contiguous section of the input stream that is written exclusively to one sink, either true or false. Anything written to the third sink also terminates the chunk.

Constructors

Splitter 

Fields

split :: forall a1 a2 a3 a4 d. OpenSplitter m a1 a2 a3 a4 d x b ()
 

Instances

Monad m => Branching (Splitter m x b) m x () 

data Boundary y Source

A Boundary value is produced to mark either a Start and End of a region of data, or an arbitrary Point in data. A Point is semantically equivalent to a Start immediately followed by End.

Constructors

Start y 
End y 
Point y 

Instances

Functor Boundary 
Eq y => Eq (Boundary y) 
Show y => Show (Boundary y) 

data Markup y x Source

Type of values in a markup-up stream. The Content constructor wraps the actual data.

Constructors

Content x 
Markup (Boundary y) 

Instances

Functor (Markup y) 
(Eq y, Eq x) => Eq (Markup y x) 
(Show x, Show y) => Show (Markup y x) 
Coercible x y => Coercible (Markup b x) y 

type Parser m x b = Transducer m x (Markup b x)Source

A parser is a transducer that marks up its input.

class Branching c m x r | c -> m x whereSource

Branching is a type class representing all types that can act as consumers, namely Consumer, Transducer, and Splitter.

Methods

combineBranches :: (forall d. PairBinder m -> (forall a d'. AncestorFunctor d d' => OpenConsumer m a d' x r) -> (forall a d'. AncestorFunctor d d' => OpenConsumer m a d' x r) -> forall a. OpenConsumer m a d x r) -> PairBinder m -> c -> c -> cSource

combineBranches is used to combine two values of Branch class into one, using the given Consumer binary combinator.

Instances

Monad m => Branching (Splitter m x b) m x () 
Monad m => Branching (Transducer m x y) m x () 
Monad m => Branching (Consumer m x r) m x r 

Component constructors

isolateConsumer :: forall m x r. Monad m => (forall d. Functor d => Source m d x -> Coroutine d m r) -> Consumer m x rSource

Creates a proper Consumer from a function that is, but can't be proven to be, an OpenConsumer.

isolateProducer :: forall m x r. Monad m => (forall d. Functor d => Sink m d x -> Coroutine d m r) -> Producer m x rSource

Creates a proper Producer from a function that is, but can't be proven to be, an OpenProducer.

isolateTransducer :: forall m x y. Monad m => (forall d. Functor d => Source m d x -> Sink m d y -> Coroutine d m ()) -> Transducer m x ySource

Creates a proper Transducer from a function that is, but can't be proven to be, an OpenTransducer.

isolateSplitter :: forall m x b. Monad m => (forall d. Functor d => Source m d x -> Sink m d x -> Sink m d x -> Sink m d b -> Coroutine d m ()) -> Splitter m x bSource

Creates a proper Splitter from a function that is, but can't be proven to be, an OpenSplitter.

oneToOneTransducer :: Monad m => (x -> y) -> Transducer m x ySource

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

statelessTransducer :: Monad m => (x -> [y]) -> Transducer m x ySource

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

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

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

statelessSplitter :: Monad m => (x -> Bool) -> Splitter m x bSource

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

statefulSplitter :: Monad m => (state -> x -> (state, Bool)) -> state -> Splitter m x ()Source

Function statefulSplitter takes a state-converting function that also assigns a Boolean value to each input item and lifts it into a Splitter.

Configurable component types

type PerformerComponent m r = Component (Performer m r)Source

A component that performs a computation with no inputs nor outputs is a PerformerComponent.

type ConsumerComponent m x r = Component (Consumer m x r)Source

A component that consumes values from a Source is called ConsumerComponent.

type ProducerComponent m x r = Component (Producer m x r)Source

A component that produces values and puts them into a Sink is called ProducerComponent.

type TransducerComponent m x y = Component (Transducer m x y)Source

The TransducerComponent type represents computations that transform a data stream.

type SplitterComponent m x b = Component (Splitter m x b)Source

The SplitterComponent 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 c x' arguments of a splitter are the same, the splitter must act as an identity transform.

ioCost :: IntSource

The constant cost of each I/O-performing component.

Coercible class

coerce :: (Monad m, Coercible x y) => TransducerComponent m x ySource

A TransducerComponent that converts a stream of one type to another.

adaptConsumer :: (Monad m, Coercible x y) => ConsumerComponent m y r -> ConsumerComponent m x rSource

Adjusts the argument consumer to consume the stream of a data type coercible to the type it was meant to consume.

adaptProducer :: (Monad m, Coercible x y) => ProducerComponent m x r -> ProducerComponent m y rSource

Adjusts the argument producer to produce the stream of a data type coercible from the type it was meant to produce.

Splitter isomorphism

adaptSplitter :: (Monad m, Coercible x y, Coercible y x) => SplitterComponent m x b -> SplitterComponent m y bSource

Adjusts the argument splitter to split the stream of a data type isomorphic to the type it was meant to split.

I/O components

I/O producers

fromStdIn :: ProducerComponent IO Char ()Source

ProducerComponent fromStdIn feeds the given sink from the standard input.

fromFile :: String -> ProducerComponent IO Char ()Source

ProducerComponent fromFile opens the named file and feeds the given sink from its contents.

fromHandle :: Handle -> ProducerComponent IO Char ()Source

ProducerComponent fromHandle feeds the given sink from the open file handle.

I/O consumers

toStdOut :: ConsumerComponent IO Char ()Source

ConsumerComponent toStdOut copies the given source into the standard output.

toFile :: String -> ConsumerComponent IO Char ()Source

ConsumerComponent toFile opens the named file and copies the given source into it.

appendFile :: String -> ConsumerComponent IO Char ()Source

ConsumerComponent appendFile opens the name file and appends the given source to it.

toHandle :: Handle -> ConsumerComponent IO Char ()Source

ConsumerComponent toHandle copies the given source into the open file handle.

Generic components

fromList :: Monad m => [x] -> ProducerComponent m x ()Source

fromList produces the contents of the given list argument.

Generic consumers

toList :: Monad m => ConsumerComponent m x [x]Source

ConsumerComponent toList copies the given source into a list.

suppress :: Monad m => ConsumerComponent m x ()Source

The suppress consumer suppresses all input it receives. It is equivalent to substitute []

erroneous :: Monad m => String -> ConsumerComponent m x ()Source

The erroneous consumer reports an error if any input reaches it.

Generic transducers

id :: Monad m => TransducerComponent m x xSource

TransducerComponent id passes its input through unmodified.

unparse :: Monad m => TransducerComponent m (Markup b x) xSource

TransducerComponent unparse removes all markup from its input and passes the content through.

parse :: Monad m => TransducerComponent m x (Markup y x)Source

TransducerComponent parse prepares input content for subsequent parsing.

lowercase :: Monad m => TransducerComponent m Char CharSource

The lowercase transforms all uppercase letters in the input to lowercase, leaving the rest unchanged.

uppercase :: Monad m => TransducerComponent m Char CharSource

The uppercase transforms all lowercase letters in the input to uppercase, leaving the rest unchanged.

count :: Monad m => TransducerComponent m x IntegerSource

The count transducer counts all its input values and outputs the final tally.

toString :: (Monad m, Show x) => TransducerComponent m x StringSource

Converts each input value x to show x.

parseSubstring :: (Monad m, Eq x) => [x] -> ParserComponent m x OccurenceTagSource

Performs the same task as the substring splitter, but instead of splitting it outputs the input as Markup x OccurenceTag in order to distinguish overlapping strings.

List stream transducers

group :: Monad m => TransducerComponent m x [x]Source

TransducerComponent group collects all its input values into a single list.

concatenate :: Monad m => TransducerComponent m [x] xSource

TransducerComponent concatenate flattens the input stream of lists of values into the output stream of values.

concatSeparate :: Monad m => [x] -> TransducerComponent m [x] xSource

Same as concatenate except it inserts the given separator list between every two input lists.

Generic splitters

everything :: Monad m => SplitterComponent m x ()Source

SplitterComponent everything feeds its entire input into its true sink.

nothing :: Monad m => SplitterComponent m x ()Source

SplitterComponent nothing feeds its entire input into its false sink.

marked :: (Monad m, Eq y) => SplitterComponent m (Markup y x) ()Source

SplitterComponent marked passes all marked-up input sections to its true sink, and all unmarked input to its false sink.

markedContent :: (Monad m, Eq y) => SplitterComponent m (Markup y x) ()Source

SplitterComponent markedContent passes the content of all marked-up input sections to its true sink, while the outermost tags and all unmarked input go to its false sink.

markedWith :: (Monad m, Eq y) => (y -> Bool) -> SplitterComponent m (Markup y x) ()Source

SplitterComponent markedWith passes input sections marked-up with the appropriate tag to its true sink, and the rest of the input to its false sink. The argument select determines if the tag is appropriate.

contentMarkedWith :: (Monad m, Eq y) => (y -> Bool) -> SplitterComponent m (Markup y x) ()Source

SplitterComponent contentMarkedWith passes the content of input sections marked-up with the appropriate tag to its true sink, and the rest of the input to its false sink. The argument select determines if the tag is appropriate.

one :: Monad m => SplitterComponent m x ()Source

SplitterComponent one feeds all input values to its true sink, treating every value as a separate section.

substring :: (Monad m, Eq x) => [x] -> SplitterComponent m x ()Source

SplitterComponent substring feeds to its true sink all input parts that match the contents of the given list argument. If two overlapping parts of the input both match the argument, both are sent to true and each is preceded by an edge.

Character stream components

whitespace :: Monad m => SplitterComponent m Char ()Source

SplitterComponent whitespace feeds all white-space characters into its true sink, all others into false.

letters :: Monad m => SplitterComponent m Char ()Source

SplitterComponent letters feeds all alphabetical characters into its true sink, all other characters into | false.

digits :: Monad m => SplitterComponent m Char ()Source

SplitterComponent digits feeds all digits into its true sink, all other characters into false.

nonEmptyLine :: Monad m => SplitterComponent m Char ()Source

SplitterComponent nonEmptyLine feeds line-ends into its false sink, and all other characters into true.

line :: Monad m => SplitterComponent m Char ()Source

The sectioning splitter line feeds line-ends into its false sink, and line contents into true. A single line-end can be formed by any of the character sequences "\n", "\r", "\r\n", or "\n\r".

Consumer, producer, and transducer combinators

consumeBy :: Monad m => ConsumerComponent m x r -> TransducerComponent m x ySource

Converts a ConsumerComponent into a TransducerComponent with no output.

(>->) :: (MonadParallel m, PipeableComponentPair m w c1 c2 c3) => Component c1 -> Component c2 -> Component c3Source

Class PipeableComponentPair applies to any two components that can be combined into a third component with the following properties:

  • The input of the result, if any, becomes the input of the first component.
  • The output produced by the first child component is consumed by the second child component.
  • The result output, if any, is the output of the second component.

join :: (MonadParallel m, JoinableComponentPair t1 t2 t3 m x y c1 c2 c3) => Component c1 -> Component c2 -> Component c3Source

Class JoinableComponentPair applies to any two components that can be combined into a third component with the following properties:

  • if both argument components consume input, the input of the combined component gets distributed to both components in parallel,
  • if both argument components produce output, the output of the combined component is a concatenation of the complete output from the first component followed by the complete output of the second component, and

The join combinator may apply the components in any order.

sequence :: JoinableComponentPair t1 t2 t3 m x y c1 c2 c3 => Component c1 -> Component c2 -> Component c3Source

The sequence combinator makes sure its first argument has completed before using the second one.

prepend :: Monad m => ProducerComponent m x r -> TransducerComponent m x xSource

Combinator prepend converts the given producer to transducer that passes all its input through unmodified, except | for prepending the output of the argument producer to it. | prepend prefix = join (substitute prefix) asis

append :: Monad m => ProducerComponent m x r -> TransducerComponent m x xSource

Combinator append converts the given producer to transducer that passes all its input through unmodified, finally | appending to it the output of the argument producer. | append suffix = join asis (substitute suffix)

substitute :: Monad m => ProducerComponent m y r -> TransducerComponent m x ySource

The substitute combinator converts its argument producer to a transducer that produces the same output, while | consuming its entire input and ignoring it.

Splitter combinators

snot :: Monad m => SplitterComponent m x b -> SplitterComponent m x bSource

The snot (streaming not) combinator simply reverses the outputs of the argument splitter. In other words, data that the argument splitter sends to its true sink goes to the false sink of the result, and vice versa.

Pseudo-logic flow combinators

(>&) :: MonadParallel m => SplitterComponent m x b1 -> SplitterComponent m x b2 -> SplitterComponent m x (b1, b2)Source

The >& combinator sends the true sink output of its left operand to the input of its right operand for further splitting. Both operands' false sinks are connected to the false sink of the combined splitter, but any input value to reach the true sink of the combined component data must be deemed true by both splitters.

(>|) :: MonadParallel m => SplitterComponent m x b1 -> SplitterComponent m x b2 -> SplitterComponent m x (Either b1 b2)Source

A >| combinator's input value can reach its false sink only by going through both argument splitters' false sinks.

Zipping logic combinators

(&&) :: MonadParallel m => SplitterComponent m x b1 -> SplitterComponent m x b2 -> SplitterComponent m x (b1, b2)Source

Combinator && is a pairwise logical conjunction of two splitters run in parallel on the same input.

(||) :: MonadParallel m => SplitterComponent m x b1 -> SplitterComponent m x b2 -> SplitterComponent m x (Either b1 b2)Source

Combinator || is a pairwise logical disjunction of two splitters run in parallel on the same input.

Flow-control combinators

Recursive

while :: MonadParallel m => TransducerComponent m x x -> SplitterComponent m x b -> TransducerComponent m x xSource

The recursive combinator while feeds the true sink of the argument splitter back to itself, modified by the argument transducer. Data fed to the splitter's false sink is passed on unmodified.

nestedIn :: MonadParallel m => SplitterComponent m x b -> SplitterComponent m x b -> SplitterComponent m x bSource

The recursive combinator nestedIn combines two splitters into a mutually recursive loop acting as a single splitter. The true sink of one of the argument splitters and false sink of the other become the true and false sinks of the loop. The other two sinks are bound to the other splitter's source. The use of nestedIn makes sense only on hierarchically structured streams. If we gave it some input containing a flat sequence of values, and assuming both component splitters are deterministic and stateless, an input value would either not loop at all or it would loop forever.

Section-based combinators

foreach :: (MonadParallel m, Branching c m x ()) => SplitterComponent m x b -> Component c -> Component c -> Component cSource

The foreach combinator is similar to the combinator ifs in that it combines a splitter and two transducers into another transducer. However, in this case the transducers are re-instantiated for each consecutive portion of the input as the splitter chunks it up. Each contiguous portion of the input that the splitter sends to one of its two sinks gets transducered through the appropriate argument transducer as that transducer's whole input. As soon as the contiguous portion is finished, the transducer gets terminated.

having :: (MonadParallel m, Coercible x y) => SplitterComponent m x b1 -> SplitterComponent m y b2 -> SplitterComponent m x b1Source

The having combinator combines two pure splitters into a pure splitter. One splitter is used to chunk the input into contiguous portions. Its false sink is routed directly to the false sink of the combined splitter. The second splitter is instantiated and run on each portion of the input that goes to first splitter's true sink. If the second splitter sends any output at all to its true sink, the whole input portion is passed on to the true sink of the combined splitter, otherwise it goes to its false sink.

havingOnly :: (MonadParallel m, Coercible x y) => SplitterComponent m x b1 -> SplitterComponent m y b2 -> SplitterComponent m x b1Source

The havingOnly combinator is analogous to the having combinator, but it succeeds and passes each chunk of the input to its true sink only if the second splitter sends no part of it to its false sink.

followedBy :: MonadParallel m => SplitterComponent m x b1 -> SplitterComponent m x b2 -> SplitterComponent m x (b1, b2)Source

Combinator followedBy treats its argument SplitterComponents as patterns components and returns a SplitterComponent that matches their concatenation. A section of input is considered true by the result iff its prefix is considered true by argument s1 and the rest of the section is considered true by s2. The splitter s2 is started anew after every section split to true sink by s1.

even :: Monad m => SplitterComponent m x b -> SplitterComponent m x bSource

The even combinator takes every input section that its argument splitter deems true, and feeds even ones into its true sink. The odd sections and parts of input that are false according to its argument splitter are fed to even splitter's false sink.

first and its variants

first :: Monad m => SplitterComponent m x b -> SplitterComponent m x bSource

The result of combinator first behaves the same as the argument splitter up to and including the first portion of the input which goes into the argument's true sink. All input following the first true portion goes into the false sink.

uptoFirst :: Monad m => SplitterComponent m x b -> SplitterComponent m x bSource

The result of combinator uptoFirst takes all input up to and including the first portion of the input which goes into the argument's true sink and feeds it to the result splitter's true sink. All the rest of the input goes into the false sink. The only difference between first and uptoFirst combinators is in where they direct the false portion of the input preceding the first true part.

prefix :: Monad m => SplitterComponent m x b -> SplitterComponent m x bSource

The prefix combinator feeds its true sink only the prefix of the input that its argument feeds to its true sink. All the rest of the input is dumped into the false sink of the result.

last and its variants

last :: Monad m => SplitterComponent m x b -> SplitterComponent m x bSource

The result of the combinator last is a splitter which directs all input to its false sink, up to the last portion of the input which goes to its argument's true sink. That portion of the input is the only one that goes to the resulting component's true sink. The splitter returned by the combinator last has to buffer the previous two portions of its input, because it cannot know if a true portion of the input is the last one until it sees the end of the input or another portion succeeding the previous one.

lastAndAfter :: Monad m => SplitterComponent m x b -> SplitterComponent m x bSource

The result of the combinator lastAndAfter is a splitter which directs all input to its false sink, up to the last portion of the input which goes to its argument's true sink. That portion and the remainder of the input is fed to the resulting component's true sink. The difference between last and lastAndAfter combinators is where they feed the false portion of the input, if any, remaining after the last true part.

suffix :: Monad m => SplitterComponent m x b -> SplitterComponent m x bSource

The suffix combinator feeds its true sink only the suffix of the input that its argument feeds to its true sink. All the rest of the input is dumped into the false sink of the result.

positional splitters

startOf :: Monad m => SplitterComponent m x b -> SplitterComponent m x (Maybe b)Source

SplitterComponent startOf issues an empty true section at the beginning of every section considered true by its argument splitter, otherwise the entire input goes into its false sink.

endOf :: MonadParallel m => SplitterComponent m x b -> SplitterComponent m x (Maybe b)Source

SplitterComponent endOf issues an empty true section at the end of every section considered true by its argument splitter, otherwise the entire input goes into its false sink.

(...) :: MonadParallel m => SplitterComponent m x b1 -> SplitterComponent m x b2 -> SplitterComponent m x b1Source

Combinator ... tracks the running balance of difference between the number of preceding starts of sections considered true according to its first argument and the ones according to its second argument. The combinator passes to true all input values for which the difference balance is positive. This combinator is typically used with startOf and endOf in order to count entire input sections and ignore their lengths.

Parser support

parseRegions :: Monad m => SplitterComponent m x b -> ParserComponent m x bSource

Converts a splitter into a parser.

parseNestedRegions :: MonadParallel m => SplitterComponent m x (Boundary b) -> ParserComponent m x bSource

Converts a boundary-marking splitter into a parser.

Parsing XML

xmlTokens :: Monad m => SplitterComponent m Char (Boundary XMLToken)Source

This splitter splits XML markup from data content. It is used by parseXMLTokens.

xmlParseTokens :: MonadParallel m => TransducerComponent m Char (Markup XMLToken Text)Source

The XML token parser. This parser converts plain text to parsed text, which is a precondition for using the remaining XML components.

XML splitters

xmlElement :: Monad m => SplitterComponent m (Markup XMLToken Text) ()Source

Splits all top-level elements with all their content to true, all other input to false.

xmlElementContent :: Monad m => SplitterComponent m (Markup XMLToken Text) ()Source

Splits the content of all top-level elements to true, their tags and intervening input to false.

xmlElementHavingTagWith :: MonadParallel m => SplitterComponent m (Markup XMLToken Text) b -> SplitterComponent m (Markup XMLToken Text) bSource

Similiar to (Control.Concurrent.SCC.Combinators.having element), except it runs the argument splitter only on each element's start tag, not on the entire element with its content.

xmlAttribute :: Monad m => SplitterComponent m (Markup XMLToken Text) ()Source

Splits every attribute specification to true, everything else to false.

xmlElementName :: Monad m => SplitterComponent m (Markup XMLToken Text) ()Source

Splits every element name, including the names of nested elements and names in end tags, to true, all the rest of input to false.

xmlAttributeName :: Monad m => SplitterComponent m (Markup XMLToken Text) ()Source

Splits every attribute name to true, all the rest of input to false.

xmlAttributeValue :: Monad m => SplitterComponent m (Markup XMLToken Text) ()Source

Splits every attribute value, excluding the quote delimiters, to true, all the rest of input to false.

expandXMLEntity :: String -> StringSource

Converts an XML entity name into the text value it represents: expandXMLEntity "lt" = "<".