scc-0.2: Streaming component combinatorsSource codeContentsIndex
Control.Concurrent.SCC.Combinators
Contents
Consumer, producer, and transducer combinators
Pseudo-logic splitter combinators
Zipping logic combinators
Flow-control combinators
Recursive
Section-based combinators
first and its variants
last and its variants
positional splitters
input ranges
Description
The Combinators module defines combinators applicable to Transducer and Splitter components defined in the ComponentTypes module.
Synopsis
consumeBy :: forall m x y r. (Monad m, Typeable x) => Consumer m x r -> Transducer m x y
prepend :: forall m x r. (Monad m, Typeable x) => Producer m x r -> Transducer m x x
append :: forall m x r. (Monad m, Typeable x) => Producer m x r -> Transducer m x x
substitute :: forall m x y r. (Monad m, Typeable x, Typeable y) => Producer m y r -> Transducer m x y
class PipeableComponentPair m w c1 c2 c3 | c1 c2 -> c3, c1 c3 -> c2, c2 c3 -> c2, c1 -> m w, c2 -> m w, c3 -> m where
(>->) :: c1 -> c2 -> c3
class (Monad m, CompatibleSignature c1 t1 m x y, CompatibleSignature c2 t2 m x y, CompatibleSignature c3 t3 m x y) => JoinableComponentPair t1 t2 t3 m x y c1 c2 c3 | c1 c2 -> c3, c1 -> t1 m, c2 -> t2 m, c3 -> t3 m x y, t1 m x y -> c1, t2 m x y -> c2, t3 m x y -> c3 where
join :: c1 -> c2 -> c3
sequence :: c1 -> c2 -> c3
snot :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x
(>&) :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x -> Splitter m x
(>|) :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x -> Splitter m x
(&&) :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x -> Splitter m x
(||) :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x -> Splitter m x
ifs :: (ParallelizableMonad m, Typeable x, BranchComponent cc m x [x]) => Splitter m x -> cc -> cc -> cc
wherever :: (ParallelizableMonad m, Typeable x) => Transducer m x x -> Splitter m x -> Transducer m x x
unless :: (ParallelizableMonad m, Typeable x) => Transducer m x x -> Splitter m x -> Transducer m x x
select :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Transducer m x x
while :: (ParallelizableMonad m, Typeable x) => Transducer m x x -> Splitter m x -> Transducer m x x
nestedIn :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x -> Splitter m x
foreach :: (ParallelizableMonad m, Typeable x, BranchComponent cc m x [x]) => Splitter m x -> cc -> cc -> cc
having :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x -> Splitter m x
havingOnly :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x -> Splitter m x
followedBy :: forall m x. (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x -> Splitter m x
even :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x
first :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x
uptoFirst :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x
prefix :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x
last :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x
lastAndAfter :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x
suffix :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x
startOf :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x
endOf :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x
(...) :: forall m x. (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x -> Splitter m x
Consumer, producer, and transducer combinators
consumeBy :: forall m x y r. (Monad m, Typeable x) => Consumer m x r -> Transducer m x ySource
prepend :: forall m x r. (Monad m, Typeable x) => Producer m x r -> Transducer 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 :: forall m x r. (Monad m, Typeable x) => Producer m x r -> Transducer 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 :: forall m x y r. (Monad m, Typeable x, Typeable y) => Producer m y r -> Transducer 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.
class PipeableComponentPair m w c1 c2 c3 | c1 c2 -> c3, c1 c3 -> c2, c2 c3 -> c2, c1 -> m w, c2 -> m w, c3 -> m whereSource
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.
Methods
(>->) :: c1 -> c2 -> c3Source
show/hide Instances
class (Monad m, CompatibleSignature c1 t1 m x y, CompatibleSignature c2 t2 m x y, CompatibleSignature c3 t3 m x y) => JoinableComponentPair t1 t2 t3 m x y c1 c2 c3 | c1 c2 -> c3, c1 -> t1 m, c2 -> t2 m, c3 -> t3 m x y, t1 m x y -> c1, t2 m x y -> c2, t3 m x y -> c3 whereSource
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 method may apply the components in any order, the sequence method makes sure its first argument | has completed before using the second one.
Methods
join :: c1 -> c2 -> c3Source
sequence :: c1 -> c2 -> c3Source
show/hide Instances
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair TransducerType TransducerType TransducerType m ([] x) ([] y) (Transducer m x y) (Transducer m x y) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair TransducerType TransducerType TransducerType m ([] x) ([] y) (Transducer m x y) (Transducer m x y) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair TransducerType TransducerType TransducerType m ([] x) ([] y) (Transducer m x y) (Transducer m x y) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair TransducerType (PerformerType r) TransducerType m ([] x) ([] y) (Transducer m x y) (Performer m r) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair TransducerType (PerformerType r) TransducerType m ([] x) ([] y) (Transducer m x y) (Performer m r) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair TransducerType (PerformerType r) TransducerType m ([] x) ([] y) (Transducer m x y) (Performer m r) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair TransducerType (PerformerType r) TransducerType m ([] x) ([] y) (Transducer m x y) (Performer m r) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair TransducerType (PerformerType r) TransducerType m ([] x) ([] y) (Transducer m x y) (Performer m r) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair TransducerType (ProducerType ()) TransducerType m ([] x) ([] y) (Transducer m x y) (Producer m y ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair TransducerType (ProducerType ()) TransducerType m ([] x) ([] y) (Transducer m x y) (Producer m y ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair TransducerType (ProducerType ()) TransducerType m ([] x) ([] y) (Transducer m x y) (Producer m y ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair TransducerType (ProducerType ()) TransducerType m ([] x) ([] y) (Transducer m x y) (Producer m y ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair TransducerType (ProducerType ()) TransducerType m ([] x) ([] y) (Transducer m x y) (Producer m y ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair TransducerType (ConsumerType ()) TransducerType m ([] x) ([] y) (Transducer m x y) (Consumer m x ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair TransducerType (ConsumerType ()) TransducerType m ([] x) ([] y) (Transducer m x y) (Consumer m x ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair TransducerType (ConsumerType ()) TransducerType m ([] x) ([] y) (Transducer m x y) (Consumer m x ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair TransducerType (ConsumerType ()) TransducerType m ([] x) ([] y) (Transducer m x y) (Consumer m x ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair TransducerType (ConsumerType ()) TransducerType m ([] x) ([] y) (Transducer m x y) (Consumer m x ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (PerformerType r) TransducerType TransducerType m ([] x) ([] y) (Performer m r) (Transducer m x y) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (PerformerType r) TransducerType TransducerType m ([] x) ([] y) (Performer m r) (Transducer m x y) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (PerformerType r) TransducerType TransducerType m ([] x) ([] y) (Performer m r) (Transducer m x y) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (PerformerType r) TransducerType TransducerType m ([] x) ([] y) (Performer m r) (Transducer m x y) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (PerformerType r) TransducerType TransducerType m ([] x) ([] y) (Performer m r) (Transducer m x y) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ProducerType ()) TransducerType TransducerType m ([] x) ([] y) (Producer m y ()) (Transducer m x y) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ProducerType ()) TransducerType TransducerType m ([] x) ([] y) (Producer m y ()) (Transducer m x y) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ProducerType ()) TransducerType TransducerType m ([] x) ([] y) (Producer m y ()) (Transducer m x y) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ProducerType ()) TransducerType TransducerType m ([] x) ([] y) (Producer m y ()) (Transducer m x y) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ProducerType ()) TransducerType TransducerType m ([] x) ([] y) (Producer m y ()) (Transducer m x y) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ConsumerType ()) TransducerType TransducerType m ([] x) ([] y) (Consumer m x ()) (Transducer m x y) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ConsumerType ()) TransducerType TransducerType m ([] x) ([] y) (Consumer m x ()) (Transducer m x y) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ConsumerType ()) TransducerType TransducerType m ([] x) ([] y) (Consumer m x ()) (Transducer m x y) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ConsumerType ()) TransducerType TransducerType m ([] x) ([] y) (Consumer m x ()) (Transducer m x y) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ConsumerType ()) TransducerType TransducerType m ([] x) ([] y) (Consumer m x ()) (Transducer m x y) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ProducerType ()) (ConsumerType ()) TransducerType m ([] x) ([] y) (Producer m y ()) (Consumer m x ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ProducerType ()) (ConsumerType ()) TransducerType m ([] x) ([] y) (Producer m y ()) (Consumer m x ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ProducerType ()) (ConsumerType ()) TransducerType m ([] x) ([] y) (Producer m y ()) (Consumer m x ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ProducerType ()) (ConsumerType ()) TransducerType m ([] x) ([] y) (Producer m y ()) (Consumer m x ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ProducerType ()) (ConsumerType ()) TransducerType m ([] x) ([] y) (Producer m y ()) (Consumer m x ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ProducerType ()) (ConsumerType ()) TransducerType m ([] x) ([] y) (Producer m y ()) (Consumer m x ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ProducerType ()) (ConsumerType ()) TransducerType m ([] x) ([] y) (Producer m y ()) (Consumer m x ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ConsumerType ()) (ProducerType ()) TransducerType m ([] x) ([] y) (Consumer m x ()) (Producer m y ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ConsumerType ()) (ProducerType ()) TransducerType m ([] x) ([] y) (Consumer m x ()) (Producer m y ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ConsumerType ()) (ProducerType ()) TransducerType m ([] x) ([] y) (Consumer m x ()) (Producer m y ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ConsumerType ()) (ProducerType ()) TransducerType m ([] x) ([] y) (Consumer m x ()) (Producer m y ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ConsumerType ()) (ProducerType ()) TransducerType m ([] x) ([] y) (Consumer m x ()) (Producer m y ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ConsumerType ()) (ProducerType ()) TransducerType m ([] x) ([] y) (Consumer m x ()) (Producer m y ()) (Transducer m x y)
(ParallelizableMonad m, Typeable x, Typeable y) => JoinableComponentPair (ConsumerType ()) (ProducerType ()) TransducerType m ([] x) ([] y) (Consumer m x ()) (Producer m y ()) (Transducer m x y)
ParallelizableMonad m => JoinableComponentPair (PerformerType r1) (PerformerType r2) (PerformerType r2) m () () (Performer m r1) (Performer m r2) (Performer m r2)
ParallelizableMonad m => JoinableComponentPair (PerformerType r1) (PerformerType r2) (PerformerType r2) m () () (Performer m r1) (Performer m r2) (Performer m r2)
ParallelizableMonad m => JoinableComponentPair (PerformerType r1) (PerformerType r2) (PerformerType r2) m () () (Performer m r1) (Performer m r2) (Performer m r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (PerformerType r1) (ProducerType r2) (ProducerType r2) m () ([] x) (Performer m r1) (Producer m x r2) (Producer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (PerformerType r1) (ProducerType r2) (ProducerType r2) m () ([] x) (Performer m r1) (Producer m x r2) (Producer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (PerformerType r1) (ProducerType r2) (ProducerType r2) m () ([] x) (Performer m r1) (Producer m x r2) (Producer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (PerformerType r1) (ProducerType r2) (ProducerType r2) m () ([] x) (Performer m r1) (Producer m x r2) (Producer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (PerformerType r1) (ProducerType r2) (ProducerType r2) m () ([] x) (Performer m r1) (Producer m x r2) (Producer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (PerformerType r1) (ProducerType r2) (ProducerType r2) m () ([] x) (Performer m r1) (Producer m x r2) (Producer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (ProducerType r1) (PerformerType r2) (ProducerType r2) m () ([] x) (Producer m x r1) (Performer m r2) (Producer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (ProducerType r1) (PerformerType r2) (ProducerType r2) m () ([] x) (Producer m x r1) (Performer m r2) (Producer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (ProducerType r1) (PerformerType r2) (ProducerType r2) m () ([] x) (Producer m x r1) (Performer m r2) (Producer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (ProducerType r1) (PerformerType r2) (ProducerType r2) m () ([] x) (Producer m x r1) (Performer m r2) (Producer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (ProducerType r1) (PerformerType r2) (ProducerType r2) m () ([] x) (Producer m x r1) (Performer m r2) (Producer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (ProducerType r1) (PerformerType r2) (ProducerType r2) m () ([] x) (Producer m x r1) (Performer m r2) (Producer m x r2)
(Monad m, Typeable x) => JoinableComponentPair (ProducerType r1) (ProducerType r2) (ProducerType r2) m () ([] x) (Producer m x r1) (Producer m x r2) (Producer m x r2)
(Monad m, Typeable x) => JoinableComponentPair (ProducerType r1) (ProducerType r2) (ProducerType r2) m () ([] x) (Producer m x r1) (Producer m x r2) (Producer m x r2)
(Monad m, Typeable x) => JoinableComponentPair (ProducerType r1) (ProducerType r2) (ProducerType r2) m () ([] x) (Producer m x r1) (Producer m x r2) (Producer m x r2)
(Monad m, Typeable x) => JoinableComponentPair (ProducerType r1) (ProducerType r2) (ProducerType r2) m () ([] x) (Producer m x r1) (Producer m x r2) (Producer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (PerformerType r1) (ConsumerType r2) (ConsumerType r2) m ([] x) () (Performer m r1) (Consumer m x r2) (Consumer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (PerformerType r1) (ConsumerType r2) (ConsumerType r2) m ([] x) () (Performer m r1) (Consumer m x r2) (Consumer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (PerformerType r1) (ConsumerType r2) (ConsumerType r2) m ([] x) () (Performer m r1) (Consumer m x r2) (Consumer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (PerformerType r1) (ConsumerType r2) (ConsumerType r2) m ([] x) () (Performer m r1) (Consumer m x r2) (Consumer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (PerformerType r1) (ConsumerType r2) (ConsumerType r2) m ([] x) () (Performer m r1) (Consumer m x r2) (Consumer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (PerformerType r1) (ConsumerType r2) (ConsumerType r2) m ([] x) () (Performer m r1) (Consumer m x r2) (Consumer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (ConsumerType r1) (PerformerType r2) (ConsumerType r2) m ([] x) () (Consumer m x r1) (Performer m r2) (Consumer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (ConsumerType r1) (PerformerType r2) (ConsumerType r2) m ([] x) () (Consumer m x r1) (Performer m r2) (Consumer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (ConsumerType r1) (PerformerType r2) (ConsumerType r2) m ([] x) () (Consumer m x r1) (Performer m r2) (Consumer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (ConsumerType r1) (PerformerType r2) (ConsumerType r2) m ([] x) () (Consumer m x r1) (Performer m r2) (Consumer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (ConsumerType r1) (PerformerType r2) (ConsumerType r2) m ([] x) () (Consumer m x r1) (Performer m r2) (Consumer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (ConsumerType r1) (PerformerType r2) (ConsumerType r2) m ([] x) () (Consumer m x r1) (Performer m r2) (Consumer m x r2)
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (ConsumerType ()) (ConsumerType ()) (ConsumerType ()) m ([] x) () (Consumer m x ()) (Consumer m x ()) (Consumer m x ())
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (ConsumerType ()) (ConsumerType ()) (ConsumerType ()) m ([] x) () (Consumer m x ()) (Consumer m x ()) (Consumer m x ())
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (ConsumerType ()) (ConsumerType ()) (ConsumerType ()) m ([] x) () (Consumer m x ()) (Consumer m x ()) (Consumer m x ())
(ParallelizableMonad m, Typeable x) => JoinableComponentPair (ConsumerType ()) (ConsumerType ()) (ConsumerType ()) m ([] x) () (Consumer m x ()) (Consumer m x ()) (Consumer m x ())
Pseudo-logic splitter combinators
Combinators >& and >| are only pseudo-logic. While the laws of double negation and De Morgan's laws hold, >& and >| are in general not commutative, associative, nor idempotent. In the special case when all argument splitters are stateless, such as those produced by Components.liftStatelessSplitter, these combinators do satisfy all laws of Boolean algebra.
snot :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m xSource
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.
(>&) :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x -> Splitter m xSource
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.
(>|) :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x -> Splitter m xSource
A >| combinator's input value can reach its false sink only by going through both argument splitters' false sinks.
Zipping logic combinators
The && and || combinators run the argument splitters in parallel and combine their logical outputs using the corresponding logical operation on each output pair, in a manner similar to zipWith. They fully satisfy the laws of Boolean algebra.
(&&) :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x -> Splitter m xSource
Combinator && is a pairwise logical conjunction of two splitters run in parallel on the same input.
(||) :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x -> Splitter m xSource
Combinator || is a pairwise logical disjunction of two splitters run in parallel on the same input.
Flow-control combinators

The following combinators resemble the common flow-control programming language constructs. Combinators wherever, unless, and select are just the special cases of the combinator ifs.

  • transducer `wherever` splitter = ifs splitter transducer Components.asis
  • transducer `unless` splitter = ifs splitter Components.asis transducer
  • select splitter = ifs splitter Components.asis Components.suppress
ifs :: (ParallelizableMonad m, Typeable x, BranchComponent cc m x [x]) => Splitter m x -> cc -> cc -> ccSource
wherever :: (ParallelizableMonad m, Typeable x) => Transducer m x x -> Splitter m x -> Transducer m x xSource
unless :: (ParallelizableMonad m, Typeable x) => Transducer m x x -> Splitter m x -> Transducer m x xSource
select :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Transducer m x xSource
Recursive
while :: (ParallelizableMonad m, Typeable x) => Transducer m x x -> Splitter m x -> Transducer 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 :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x -> Splitter m xSource
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, a value would either not loop at all or it would loop forever.
Section-based combinators
All combinators in this section use their Splitter argument to determine the structure of the input. Every contiguous portion of the input that gets passed to one or the other sink of the splitter is treated as one section in the logical structure of the input stream. What is done with the section depends on the combinator, but the sections, and therefore the logical structure of the input stream, are determined by the argument splitter alone.
foreach :: (ParallelizableMonad m, Typeable x, BranchComponent cc m x [x]) => Splitter m x -> cc -> cc -> ccSource
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 :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x -> Splitter m xSource
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 :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x -> Splitter m xSource
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 :: forall m x. (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x -> Splitter m xSource
Combinator followedBy treats its argument Splitters as patterns components and returns a Splitter 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 :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m xSource
The even combinator takes every input section that its argument splitters 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 :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m xSource
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 :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m xSource
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 last and lastAndAfter combinators is in where they direct the false portion of the input preceding the first true part.
prefix :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m xSource
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 :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m xSource
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 :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m xSource
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 :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m xSource
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 :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m xSource
Splitter 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 :: (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m xSource
Splitter 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.
input ranges
(...) :: forall m x. (ParallelizableMonad m, Typeable x) => Splitter m x -> Splitter m x -> Splitter m xSource
Combinator ... tracks the running balance of difference between the numbers of preceding inputs 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.
Produced by Haddock version 2.3.0