|
Control.Concurrent.SCC.Types |
|
|
|
|
Description |
This module defines various Control.Concurrent.SCC.Coroutine.Coroutine types that operate on
Sink and Source values. The simplest of the bunch
are Consumer and Producer types, which respectively operate on a single source or sink. A Transducer has access
both to a Source to read from and a Sink to write
into. Finally, a Splitter reads from a single source and writes all input into two sinks of the same type,
signalling interesting input boundaries by writing into the third sink.
|
|
Synopsis |
|
newtype Performer m r = Performer {} | | type OpenConsumer m a d x r = AncestorFunctor a d => Source m a x -> Coroutine d m r | | newtype Consumer m x r = Consumer {} | | type OpenProducer m a d x r = AncestorFunctor a d => Sink m a x -> Coroutine d m r | | newtype Producer m x r = Producer {} | | type OpenTransducer m a1 a2 d x y = (AncestorFunctor a1 d, AncestorFunctor a2 d) => Source m a1 x -> Sink m a2 y -> Coroutine d m [x] | | newtype Transducer m x y = Transducer {} | | type OpenSplitter m a1 a2 a3 a4 d x b = (AncestorFunctor a1 d, AncestorFunctor a2 d, AncestorFunctor a3 d, AncestorFunctor a4 d) => Source m a1 x -> Sink m a2 x -> Sink m a3 x -> Sink m a4 b -> Coroutine d m [x] | | newtype Splitter m x b = Splitter {} | | | | | | type Parser m x b = Transducer m x (Markup b x) | | class Branching c m x r | c -> m x where | | | isolateConsumer :: forall m x r. Monad m => (forall d. Functor d => Source m d x -> Coroutine d m r) -> Consumer m x r | | isolateProducer :: forall m x r. Monad m => (forall d. Functor d => Sink m d x -> Coroutine d m r) -> Producer m x r | | isolateTransducer :: forall m x y. Monad m => (forall d. Functor d => Source m d x -> Sink m d y -> Coroutine d m [x]) -> Transducer m x y | | 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 [x]) -> Splitter m x b | | oneToOneTransducer :: Monad m => (x -> y) -> Transducer m x y | | statelessTransducer :: Monad m => (x -> [y]) -> Transducer m x y | | foldingTransducer :: Monad m => (s -> x -> s) -> s -> (s -> y) -> Transducer m x y | | statefulTransducer :: Monad m => (state -> x -> (state, [y])) -> state -> Transducer m x y | | statelessSplitter :: Monad m => (x -> Bool) -> Splitter m x b | | statefulSplitter :: Monad m => (state -> x -> (state, Bool)) -> state -> Splitter m x () | | splitToConsumers :: (Functor d, Monad m, d1 ~ SinkFunctor d x, AncestorFunctor a (SinkFunctor (SinkFunctor d1 x) b)) => Splitter m x b -> Source m a x -> (Source m (SourceFunctor d x) x -> Coroutine (SourceFunctor d x) m r1) -> (Source m (SourceFunctor d1 x) x -> Coroutine (SourceFunctor d1 x) m r2) -> (Source m (SourceFunctor (SinkFunctor d1 x) b) b -> Coroutine (SourceFunctor (SinkFunctor d1 x) b) m r3) -> Coroutine d m ([x], r1, r2, r3) | | splitInputToConsumers :: forall m a d d1 x b. (ParallelizableMonad m, d1 ~ SinkFunctor d x, AncestorFunctor a d) => Bool -> Splitter m x b -> Source m a x -> (Source m (SourceFunctor d1 x) x -> Coroutine (SourceFunctor d1 x) m [x]) -> (Source m (SourceFunctor d x) x -> Coroutine (SourceFunctor d x) m [x]) -> Coroutine d m [x] | | pipePS :: forall m a a1 a2 x r1 r2. (ParallelizableMonad m, Functor a, a1 ~ SinkFunctor a x, a2 ~ SourceFunctor a x) => Bool -> (Sink m a1 x -> Coroutine a1 m r1) -> (Source m a2 x -> Coroutine a2 m r2) -> Coroutine a m (r1, r2) |
|
|
|
Types
|
|
|
A component that performs a computation with no inputs nor outputs.
| Constructors | | Instances | |
|
|
|
|
|
A component that consumes values from a Source.
| Constructors | | Instances | |
|
|
|
|
|
A component that produces values and puts them into a Sink.
| Constructors | | Instances | |
|
|
|
|
newtype Transducer m x y | Source |
|
The Transducer type represents computations that transform a data stream. Execution of transduce must continue
consuming the given Source and feeding the Sink as
long both can be resumed. If the sink dies first, transduce should return the list of all values it has consumed
from the source but hasn't managed to process and write into the sink.
| Constructors | | Instances | |
|
|
|
|
|
The SplitterComponent type represents computations 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. If any of the sinks dies before
all data is fed to them, split should return the list of all values it has consumed from the source but hasn't
managed to write into the sinks.
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 | | split :: forall a1 a2 a3 a4 d. OpenSplitter m a1 a2 a3 a4 d x b | |
|
| Instances | |
|
|
|
A Markup 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. The Content
constructor wraps the actual data.
| Constructors | | Instances | |
|
|
|
Constructors | | Instances | |
|
|
|
|
Type classes
|
|
class Branching c m x r | c -> m x where | Source |
|
|
|
Constructors
|
|
|
Creates a proper Consumer from a function that is, but can't be proven to be, an OpenConsumer.
|
|
|
Creates a proper Producer from a function that is, but can't be proven to be, an OpenProducer.
|
|
|
Creates a proper Transducer from a function that is, but can't be proven to be, an OpenTransducer.
|
|
|
Creates a proper Splitter from a function that is, but can't be proven to be, an OpenSplitter.
|
|
|
Function oneToOneTransducer takes a function that maps one input value to one output value each, and lifts it
into a Transducer.
|
|
|
Function statelessTransducer takes a function that maps one input value into a list of output values, and
lifts it into a Transducer.
|
|
|
Function foldingTransducer creates a stateful transducer that produces only one output value after consuming the
entire input. Similar to Data.List.foldl
|
|
|
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.
|
|
|
Function statelessSplitter takes a function that assigns a Boolean value to each input item and lifts it into
a Splitter.
|
|
|
Function statefulSplitter takes a state-converting function that also assigns a Boolean value to each input
item and lifts it into a Splitter.
|
|
Utility functions
|
|
|
Given a Splitter, a Source, and three consumer functions, splitToConsumers runs the splitter on the source
and feeds the splitter's outputs to its true, false, and edge sinks, respectively, to the three consumers.
|
|
|
Given a Splitter, a Source, and two consumer functions, splitInputToConsumers runs the splitter on the source
and feeds the splitter's true and false outputs, respectively, to the two consumers.
|
|
|
The pipePS function acts either as pipeP or as pipe, depending on the argument parallel.
|
|
Produced by Haddock version 2.6.0 |