streamly-0.8.3: Dataflow programming and declarative concurrency
Copyright(c) 2018 Composewell Technologies
(c) Roman Leshchinskiy 2008-2010
LicenseBSD-3-Clause
Maintainerstreamly@composewell.com
Stabilityexperimental
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Streamly.Internal.Data.Stream.StreamD.Nesting

Description

This module contains transformations involving multiple streams, unfolds or folds. There are two types of transformations generational or eliminational. Generational transformations are like the Generate module but they generate a stream by combining streams instead of elements. Eliminational transformations are like the Eliminate module but they transform a stream by eliminating parts of the stream instead of eliminating the whole stream.

These combinators involve transformation, generation, elimination so can be classified under any of those.

Ultimately these operations should be supported by Unfolds, Pipes and Folds, and this module may become redundant.

Synopsis

Generate

Combining streams to generate streams.

Combine Two Streams

Functions ending in the shape:

t m a -> t m a -> t m a.

Appending

Append a stream after another. A special case of concatMap or unfoldMany.

data AppendState s1 s2 Source #

Constructors

AppendFirst s1 
AppendSecond s2 

append :: Monad m => Stream m a -> Stream m a -> Stream m a Source #

Interleaving

Interleave elements from two streams alternately. A special case of unfoldManyInterleave.

interleave :: Monad m => Stream m a -> Stream m a -> Stream m a Source #

interleaveMin :: Monad m => Stream m a -> Stream m a -> Stream m a Source #

interleaveSuffix :: Monad m => Stream m a -> Stream m a -> Stream m a Source #

interleaveInfix :: Monad m => Stream m a -> Stream m a -> Stream m a Source #

Scheduling

Execute streams alternately irrespective of whether they generate elements or not. Note interleave would execute a stream until it yields an element. A special case of unfoldManyRoundRobin.

roundRobin :: Monad m => Stream m a -> Stream m a -> Stream m a Source #

Zipping

Zip corresponding elements of two streams.

zipWith :: Monad m => (a -> b -> c) -> Stream m a -> Stream m b -> Stream m c Source #

zipWithM :: Monad m => (a -> b -> m c) -> Stream m a -> Stream m b -> Stream m c Source #

Merging

Interleave elements from two streams based on a condition.

mergeBy :: Monad m => (a -> a -> Ordering) -> Stream m a -> Stream m a -> Stream m a Source #

mergeByM :: Monad m => (a -> a -> m Ordering) -> Stream m a -> Stream m a -> Stream m a Source #

Combine N Streams

Functions generally ending in these shapes:

concat: f (t m a) -> t m a
concatMap: (a -> t m b) -> t m a -> t m b
unfoldMany: Unfold m a b -> t m a -> t m b

ConcatMap

Generate streams by mapping a stream generator on each element of an input stream, append the resulting streams and flatten.

concatMap :: Monad m => (a -> Stream m b) -> Stream m a -> Stream m b Source #

concatMapM :: Monad m => (a -> m (Stream m b)) -> Stream m a -> Stream m b Source #

ConcatUnfold

Generate streams by using an unfold on each element of an input stream, append the resulting streams and flatten. A special case of gintercalate.

unfoldMany :: Monad m => Unfold m a b -> Stream m a -> Stream m b Source #

unfoldMany unfold stream uses unfold to map the input stream elements to streams and then flattens the generated streams into a single output stream.

unfoldManyInterleave :: Monad m => Unfold m a b -> Stream m a -> Stream m b Source #

This does not pair streams like concatPairsWith, instead, it goes through each stream one by one and yields one element from each stream. After it goes to the last stream it reverses the traversal to come back to the first stream yielding elements from each stream on its way back to the first stream and so on.

>>> input = Stream.fromList [[1,1],[2,2],[3,3],[4,4],[5,5]]
>>> Stream.toList $ Stream.unfoldManyInterleave Unfold.fromList input
[1,2,3,4,5,5,4,3,2,1]

Note that this is order of magnitude more efficient than "concatPairsWith wSerial"

unfoldManyRoundRobin :: Monad m => Unfold m a b -> Stream m a -> Stream m b Source #

Interpose

Like unfoldMany but intersperses an effect between the streams. A special case of gintercalate.

interpose :: Monad m => m c -> Unfold m b c -> Stream m b -> Stream m c Source #

interposeSuffix :: Monad m => m c -> Unfold m b c -> Stream m b -> Stream m c Source #

Intercalate

Like unfoldMany but intersperses streams from another source between the streams from the first source.

gintercalate :: Monad m => Unfold m a c -> Stream m a -> Unfold m b c -> Stream m b -> Stream m c Source #

Interleave streams (full streams, not the elements) unfolded from two input streams and concat. Stop when the first stream stops. If the second stream ends before the first one then first stream still keeps running alone without any interleaving with the second stream.

a1, a2, ... an
[b1, b2 ...] => [streamA1, streamA2, ... streamAn] [streamB1, streamB2, ...] => [streamA1, streamB1, streamA2...StreamAn, streamBn] => [a11, a12, ...a1j, b11, b12, ...b1k, a21, a22, ...]

gintercalateSuffix :: Monad m => Unfold m a c -> Stream m a -> Unfold m b c -> Stream m b -> Stream m c Source #

Interleave streams (full streams, not the elements) unfolded from two input streams and concat. Stop when the first stream stops. If the second stream ends before the first one then first stream still keeps running alone without any interleaving with the second stream.

a1, a2, ... an
[b1, b2 ...] => [streamA1, streamA2, ... streamAn] [streamB1, streamB2, ...] => [streamA1, streamB1, streamA2...StreamAn, streamBn] => [a11, a12, ...a1j, b11, b12, ...b1k, a21, a22, ...]

Eliminate

Folding and Parsing chunks of streams to eliminate nested streams. Functions generally ending in these shapes:

f (Fold m a b) -> t m a -> t m b
f (Parser m a b) -> t m a -> t m b

Folding

Apply folds on a stream.

foldMany :: Monad m => Fold m a b -> Stream m a -> Stream m b Source #

Apply a fold multiple times until the stream ends. If the stream is empty the output would be empty.

foldMany f = parseMany (fromFold f)

A terminating fold may terminate even without accepting a single input. So we run the fold's initial action before evaluating the stream. However, this means that if later the stream does not yield anything we have to discard the fold's initial result which could have generated an effect.

refoldMany :: Monad m => Refold m x a b -> m x -> Stream m a -> Stream m b Source #

Like foldMany but for the Refold type. The supplied action is used as the initial value for each refold.

Internal

foldIterateM :: Monad m => (b -> m (Fold m a b)) -> m b -> Stream m a -> Stream m b Source #

refoldIterateM :: Monad m => Refold m b a b -> m b -> Stream m a -> Stream m b Source #

Like foldIterateM but using the Refold type instead. This could be much more efficient due to stream fusion.

Internal

Parsing

Parsing is opposite to flattening. parseMany is dual to concatMap or unfoldMany. concatMap generates a stream from single values in a stream and flattens, parseMany does the opposite of flattening by splitting the stream and then folds each such split to single value in the output stream.

parseMany :: MonadThrow m => Parser m a b -> Stream m a -> Stream m b Source #

parseIterate :: MonadThrow m => (b -> Parser m a b) -> b -> Stream m a -> Stream m b Source #

Grouping

Group segments of a stream and fold. Special case of parsing.

chunksOf :: Monad m => Int -> Fold m a b -> Stream m a -> Stream m b Source #

groupsBy :: Monad m => (a -> a -> Bool) -> Fold m a b -> Stream m a -> Stream m b Source #

groupsRollingBy :: Monad m => (a -> a -> Bool) -> Fold m a b -> Stream m a -> Stream m b Source #

Splitting

A special case of parsing.

wordsBy :: Monad m => (a -> Bool) -> Fold m a b -> Stream m a -> Stream m b Source #

splitOnSeq :: forall m a b. (MonadIO m, Storable a, Enum a, Eq a) => Array a -> Fold m a b -> Stream m a -> Stream m b Source #

splitOnSuffixSeq :: forall m a b. (MonadIO m, Storable a, Enum a, Eq a) => Bool -> Array a -> Fold m a b -> Stream m a -> Stream m b Source #

sliceOnSuffix :: Monad m => (a -> Bool) -> Stream m a -> Stream m (Int, Int) Source #

Transform (Nested Containers)

Opposite to compact in ArrayStream

splitInnerBy :: Monad m => (f a -> m (f a, Maybe (f a))) -> (f a -> f a -> m (f a)) -> Stream m (f a) -> Stream m (f a) Source #

Performs infix separator style splitting.

splitInnerBySuffix :: (Monad m, Eq (f a), Monoid (f a)) => (f a -> m (f a, Maybe (f a))) -> (f a -> f a -> m (f a)) -> Stream m (f a) -> Stream m (f a) Source #

Performs infix separator style splitting.

intersectBySorted :: Monad m => (a -> a -> Ordering) -> Stream m a -> Stream m a -> Stream m a Source #