Copyright | (c) 2017 Composewell Technologies |
---|---|
License | BSD3 |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Continuation passing style (CPS) stream implementation. The symbol K
below
denotes a function as well as a Kontinuation.
Synopsis
- type Stream = StreamK
- newtype StreamK m a = MkStream (forall r. State StreamK m a -> (a -> StreamK m a -> m r) -> (a -> m r) -> m r -> m r)
- data CrossStreamK m a
- unCross :: CrossStreamK m a -> StreamK m a
- mkCross :: StreamK m a -> CrossStreamK m a
- mkStream :: (forall r. State StreamK m a -> (a -> StreamK m a -> m r) -> (a -> m r) -> m r -> m r) -> StreamK m a
- foldStream :: State StreamK m a -> (a -> StreamK m a -> m r) -> (a -> m r) -> m r -> StreamK m a -> m r
- foldStreamShared :: State StreamK m a -> (a -> StreamK m a -> m r) -> (a -> m r) -> m r -> StreamK m a -> m r
- foldrM :: (a -> m b -> m b) -> m b -> StreamK m a -> m b
- foldrS :: (a -> StreamK m b -> StreamK m b) -> StreamK m b -> StreamK m a -> StreamK m b
- foldrSShared :: (a -> StreamK m b -> StreamK m b) -> StreamK m b -> StreamK m a -> StreamK m b
- foldrSM :: Monad m => (m a -> StreamK m b -> StreamK m b) -> StreamK m b -> StreamK m a -> StreamK m b
- build :: forall m a. (forall b. (a -> b -> b) -> b -> b) -> StreamK m a
- buildS :: ((a -> StreamK m a -> StreamK m a) -> StreamK m a -> StreamK m a) -> StreamK m a
- buildM :: Monad m => (forall r. (a -> StreamK m a -> m r) -> (a -> m r) -> m r -> m r) -> StreamK m a
- buildSM :: Monad m => ((m a -> StreamK m a -> StreamK m a) -> StreamK m a -> StreamK m a) -> StreamK m a
- augmentS :: ((a -> StreamK m a -> StreamK m a) -> StreamK m a -> StreamK m a) -> StreamK m a -> StreamK m a
- augmentSM :: Monad m => ((m a -> StreamK m a -> StreamK m a) -> StreamK m a -> StreamK m a) -> StreamK m a -> StreamK m a
- unShare :: StreamK m a -> StreamK m a
- fromStopK :: StopK m -> StreamK m a
- fromYieldK :: YieldK m a -> StreamK m a
- consK :: YieldK m a -> StreamK m a -> StreamK m a
- cons :: a -> StreamK m a -> StreamK m a
- (.:) :: a -> StreamK m a -> StreamK m a
- consM :: Monad m => m a -> StreamK m a -> StreamK m a
- consMBy :: Monad m => (StreamK m a -> StreamK m a -> StreamK m a) -> m a -> StreamK m a -> StreamK m a
- nil :: StreamK m a
- nilM :: Applicative m => m b -> StreamK m a
- unfoldr :: (b -> Maybe (a, b)) -> b -> StreamK m a
- unfoldrMWith :: Monad m => (m a -> StreamK m a -> StreamK m a) -> (b -> m (Maybe (a, b))) -> b -> StreamK m a
- unfoldrM :: Monad m => (b -> m (Maybe (a, b))) -> b -> StreamK m a
- fromEffect :: Monad m => m a -> StreamK m a
- fromPure :: a -> StreamK m a
- repeat :: a -> StreamK m a
- repeatMWith :: (m a -> t m a -> t m a) -> m a -> t m a
- replicateMWith :: (m a -> StreamK m a -> StreamK m a) -> Int -> m a -> StreamK m a
- fromIndicesMWith :: (m a -> StreamK m a -> StreamK m a) -> (Int -> m a) -> StreamK m a
- iterateMWith :: Monad m => (m a -> StreamK m a -> StreamK m a) -> (a -> m a) -> m a -> StreamK m a
- fromFoldable :: Foldable f => f a -> StreamK m a
- fromFoldableM :: (Foldable f, Monad m) => f (m a) -> StreamK m a
- mfix :: Monad m => (m a -> StreamK m a) -> StreamK m a
- uncons :: Applicative m => StreamK m a -> m (Maybe (a, StreamK m a))
- foldl' :: Monad m => (b -> a -> b) -> b -> StreamK m a -> m b
- foldlx' :: forall m a b x. Monad m => (x -> a -> x) -> x -> (x -> b) -> StreamK m a -> m b
- foldr :: Monad m => (a -> b -> b) -> b -> StreamK m a -> m b
- drain :: Monad m => StreamK m a -> m ()
- null :: Monad m => StreamK m a -> m Bool
- tail :: Applicative m => StreamK m a -> m (Maybe (StreamK m a))
- init :: Applicative m => StreamK m a -> m (Maybe (StreamK m a))
- map :: (a -> b) -> StreamK m a -> StreamK m b
- mapMWith :: (m b -> StreamK m b -> StreamK m b) -> (a -> m b) -> StreamK m a -> StreamK m b
- mapMSerial :: Monad m => (a -> m b) -> StreamK m a -> StreamK m b
- conjoin :: Monad m => StreamK m a -> StreamK m a -> StreamK m a
- append :: StreamK m a -> StreamK m a -> StreamK m a
- interleave :: StreamK m a -> StreamK m a -> StreamK m a
- interleaveFst :: StreamK m a -> StreamK m a -> StreamK m a
- interleaveMin :: StreamK m a -> StreamK m a -> StreamK m a
- crossApplyWith :: (StreamK m b -> StreamK m b -> StreamK m b) -> StreamK m (a -> b) -> StreamK m a -> StreamK m b
- crossApply :: StreamK m (a -> b) -> StreamK m a -> StreamK m b
- crossApplySnd :: StreamK m a -> StreamK m b -> StreamK m b
- crossApplyFst :: StreamK m a -> StreamK m b -> StreamK m a
- crossWith :: Monad m => (a -> b -> c) -> StreamK m a -> StreamK m b -> StreamK m c
- cross :: Monad m => StreamK m a -> StreamK m b -> StreamK m (a, b)
- before :: Monad m => m b -> StreamK m a -> StreamK m a
- concatEffect :: Monad m => m (StreamK m a) -> StreamK m a
- concatMapEffect :: Monad m => (b -> StreamK m a) -> m b -> StreamK m a
- concatMapWith :: (StreamK m b -> StreamK m b -> StreamK m b) -> (a -> StreamK m b) -> StreamK m a -> StreamK m b
- concatMap :: (a -> StreamK m b) -> StreamK m a -> StreamK m b
- bindWith :: (StreamK m b -> StreamK m b -> StreamK m b) -> StreamK m a -> (a -> StreamK m b) -> StreamK m b
- concatIterateWith :: (StreamK m a -> StreamK m a -> StreamK m a) -> (a -> StreamK m a) -> StreamK m a -> StreamK m a
- concatIterateLeftsWith :: b ~ Either a c => (StreamK m b -> StreamK m b -> StreamK m b) -> (a -> StreamK m b) -> StreamK m b -> StreamK m b
- concatIterateScanWith :: Monad m => (StreamK m a -> StreamK m a -> StreamK m a) -> (b -> a -> m (b, StreamK m a)) -> m b -> StreamK m a -> StreamK m a
- mergeMapWith :: (StreamK m b -> StreamK m b -> StreamK m b) -> (a -> StreamK m b) -> StreamK m a -> StreamK m b
- mergeIterateWith :: (StreamK m a -> StreamK m a -> StreamK m a) -> (a -> StreamK m a) -> StreamK m a -> StreamK m a
- foldlS :: (StreamK m b -> a -> StreamK m b) -> StreamK m b -> StreamK m a -> StreamK m b
- reverse :: StreamK m a -> StreamK m a
StreamK type
type Stream = StreamK Source #
Deprecated: Please use StreamK instead.
Continuation Passing Style (CPS) version of Streamly.Data.Stream.Stream.
Unlike Streamly.Data.Stream.Stream, StreamK
can be composed recursively
without affecting performance.
Semigroup instance appends two streams:
>>>
(<>) = Stream.append
Instances
CrossStreamK type wrapper
data CrossStreamK m a Source #
A newtype wrapper for the StreamK
type adding a cross product style
monad instance.
A Monad
bind behaves like a for
loop:
>>>
:{
Stream.fold Fold.toList $ StreamK.toStream $ StreamK.unCross $ do x <- StreamK.mkCross $ StreamK.fromStream $ Stream.fromList [1,2] -- Perform the following actions for each x in the stream return x :} [1,2]
Nested monad binds behave like nested for
loops:
>>>
:{
Stream.fold Fold.toList $ StreamK.toStream $ StreamK.unCross $ do x <- StreamK.mkCross $ StreamK.fromStream $ Stream.fromList [1,2] y <- StreamK.mkCross $ StreamK.fromStream $ Stream.fromList [3,4] -- Perform the following actions for each x, for each y return (x, y) :} [(1,3),(1,4),(2,3),(2,4)]
Instances
unCross :: CrossStreamK m a -> StreamK m a Source #
Unwrap the StreamK
type from CrossStreamK
newtype.
This is a type level operation with no runtime overhead.
mkCross :: StreamK m a -> CrossStreamK m a Source #
Wrap the StreamK
type in a CrossStreamK
newtype to enable cross
product style applicative and monad instances.
This is a type level operation with no runtime overhead.
foldr/build Fusion
mkStream :: (forall r. State StreamK m a -> (a -> StreamK m a -> m r) -> (a -> m r) -> m r -> m r) -> StreamK m a Source #
foldStream :: State StreamK m a -> (a -> StreamK m a -> m r) -> (a -> m r) -> m r -> StreamK m a -> m r Source #
Fold a stream by providing a State, stop continuation, a singleton continuation and a yield continuation. The stream will not use the SVar passed via State.
foldStreamShared :: State StreamK m a -> (a -> StreamK m a -> m r) -> (a -> m r) -> m r -> StreamK m a -> m r Source #
Fold a stream by providing an SVar, a stop continuation, a singleton continuation and a yield continuation. The stream would share the current SVar passed via the State.
foldrM :: (a -> m b -> m b) -> m b -> StreamK m a -> m b Source #
Lazy right fold with a monadic step function.
foldrS :: (a -> StreamK m b -> StreamK m b) -> StreamK m b -> StreamK m a -> StreamK m b Source #
Right fold to a streaming monad.
foldrS StreamK.cons StreamK.nil === id
foldrS
can be used to perform stateless stream to stream transformations
like map and filter in general. It can be coupled with a scan to perform
stateful transformations. However, note that the custom map and filter
routines can be much more efficient than this due to better stream fusion.
>>>
input = StreamK.fromStream $ Stream.fromList [1..5]
>>>
Stream.fold Fold.toList $ StreamK.toStream $ StreamK.foldrS StreamK.cons StreamK.nil input
[1,2,3,4,5]
Find if any element in the stream is True
:
>>>
step x xs = if odd x then StreamK.fromPure True else xs
>>>
input = StreamK.fromStream (Stream.fromList (2:4:5:undefined)) :: StreamK IO Int
>>>
Stream.fold Fold.toList $ StreamK.toStream $ StreamK.foldrS step (StreamK.fromPure False) input
[True]
Map (+2) on odd elements and filter out the even elements:
>>>
step x xs = if odd x then (x + 2) `StreamK.cons` xs else xs
>>>
input = StreamK.fromStream (Stream.fromList [1..5]) :: StreamK IO Int
>>>
Stream.fold Fold.toList $ StreamK.toStream $ StreamK.foldrS step StreamK.nil input
[3,5,7]
Pre-release
foldrSShared :: (a -> StreamK m b -> StreamK m b) -> StreamK m b -> StreamK m a -> StreamK m b Source #
Fold sharing the SVar state within the reconstructed stream
foldrSM :: Monad m => (m a -> StreamK m b -> StreamK m b) -> StreamK m b -> StreamK m a -> StreamK m b Source #
buildM :: Monad m => (forall r. (a -> StreamK m a -> m r) -> (a -> m r) -> m r -> m r) -> StreamK m a Source #
buildSM :: Monad m => ((m a -> StreamK m a -> StreamK m a) -> StreamK m a -> StreamK m a) -> StreamK m a Source #
augmentS :: ((a -> StreamK m a -> StreamK m a) -> StreamK m a -> StreamK m a) -> StreamK m a -> StreamK m a Source #
augmentSM :: Monad m => ((m a -> StreamK m a -> StreamK m a) -> StreamK m a -> StreamK m a) -> StreamK m a -> StreamK m a Source #
Construction
Primitives
fromYieldK :: YieldK m a -> StreamK m a Source #
Make a singleton stream from a callback function. The callback function calls the one-shot yield continuation to yield an element.
consK :: YieldK m a -> StreamK m a -> StreamK m a Source #
Add a yield function at the head of the stream.
cons :: a -> StreamK m a -> StreamK m a infixr 5 Source #
A right associative prepend operation to add a pure value at the head of an existing stream::
>>>
s = 1 `StreamK.cons` 2 `StreamK.cons` 3 `StreamK.cons` StreamK.nil
>>>
Stream.fold Fold.toList (StreamK.toStream s)
[1,2,3]
It can be used efficiently with foldr
:
>>>
fromFoldable = Prelude.foldr StreamK.cons StreamK.nil
Same as the following but more efficient:
>>>
cons x xs = return x `StreamK.consM` xs
(.:) :: a -> StreamK m a -> StreamK m a infixr 5 Source #
Operator equivalent of cons
.
> toList $ 1 .: 2 .: 3 .: nil [1,2,3]
consM :: Monad m => m a -> StreamK m a -> StreamK m a infixr 5 Source #
A right associative prepend operation to add an effectful value at the head of an existing stream::
>>>
s = putStrLn "hello" `StreamK.consM` putStrLn "world" `StreamK.consM` StreamK.nil
>>>
Stream.fold Fold.drain (StreamK.toStream s)
hello world
It can be used efficiently with foldr
:
>>>
fromFoldableM = Prelude.foldr StreamK.consM StreamK.nil
Same as the following but more efficient:
>>>
consM x xs = StreamK.fromEffect x `StreamK.append` xs
consMBy :: Monad m => (StreamK m a -> StreamK m a -> StreamK m a) -> m a -> StreamK m a -> StreamK m a Source #
A stream that terminates without producing any output or side effect.
>>>
Stream.fold Fold.toList (StreamK.toStream StreamK.nil)
[]
nilM :: Applicative m => m b -> StreamK m a Source #
A stream that terminates without producing any output, but produces a side effect.
>>>
Stream.fold Fold.toList (StreamK.toStream (StreamK.nilM (print "nil")))
"nil" []
Pre-release
Unfolding
unfoldrMWith :: Monad m => (m a -> StreamK m a -> StreamK m a) -> (b -> m (Maybe (a, b))) -> b -> StreamK m a Source #
From Values
fromEffect :: Monad m => m a -> StreamK m a Source #
Create a singleton stream from a monadic action.
>>>
fromEffect m = m `StreamK.consM` StreamK.nil
>>>
Stream.fold Fold.drain $ StreamK.toStream $ StreamK.fromEffect (putStrLn "hello")
hello
fromPure :: a -> StreamK m a Source #
Create a singleton stream from a pure value.
>>>
fromPure a = a `StreamK.cons` StreamK.nil
>>>
fromPure = pure
>>>
fromPure = StreamK.fromEffect . pure
repeat :: a -> StreamK m a Source #
Generate an infinite stream by repeating a pure value.
Pre-release
repeatMWith :: (m a -> t m a -> t m a) -> m a -> t m a Source #
Like repeatM
but takes a stream cons
operation to combine the actions
in a stream specific manner. A serial cons would repeat the values serially
while an async cons would repeat concurrently.
Pre-release
From Indices
Iteration
iterateMWith :: Monad m => (m a -> StreamK m a -> StreamK m a) -> (a -> m a) -> m a -> StreamK m a Source #
From Containers
fromFoldable :: Foldable f => f a -> StreamK m a Source #
>>>
fromFoldable = Prelude.foldr StreamK.cons StreamK.nil
Construct a stream from a Foldable
containing pure values:
Cyclic
mfix :: Monad m => (m a -> StreamK m a) -> StreamK m a Source #
We can define cyclic structures using let
:
>>>
let (a, b) = ([1, b], head a) in (a, b)
([1,1],1)
The function fix
defined as:
>>>
fix f = let x = f x in x
ensures that the argument of a function and its output refer to the same
lazy value x
i.e. the same location in memory. Thus x
can be defined
in terms of itself, creating structures with cyclic references.
>>>
f ~(a, b) = ([1, b], head a)
>>>
fix f
([1,1],1)
mfix
is essentially the same as fix
but for monadic
values.
Using mfix
for streams we can construct a stream in which each element of
the stream is defined in a cyclic fashion. The argument of the function
being fixed represents the current element of the stream which is being
returned by the stream monad. Thus, we can use the argument to construct
itself.
In the following example, the argument action
of the function f
represents the tuple (x,y)
returned by it in a given iteration. We define
the first element of the tuple in terms of the second.
>>>
import System.IO.Unsafe (unsafeInterleaveIO)
>>>
:{
main = Stream.fold (Fold.drainMapM print) $ StreamK.toStream $ StreamK.mfix f where f action = StreamK.unCross $ do let incr n act = fmap ((+n) . snd) $ unsafeInterleaveIO act x <- StreamK.mkCross $ StreamK.fromStream $ Stream.sequence $ Stream.fromList [incr 1 action, incr 2 action] y <- StreamK.mkCross $ StreamK.fromStream $ Stream.fromList [4,5] return (x, y) :}
Note: you cannot achieve this by just changing the order of the monad statements because that would change the order in which the stream elements are generated.
Note that the function f
must be lazy in its argument, that's why we use
unsafeInterleaveIO
on action
because IO monad is strict.
Pre-release
Elimination
Primitives
Strict Left Folds
foldlx' :: forall m a b x. Monad m => (x -> a -> x) -> x -> (x -> b) -> StreamK m a -> m b Source #
Strict left fold with an extraction function. Like the standard strict
left fold, but applies a user supplied extraction function (the third
argument) to the folded value at the end. This is designed to work with the
foldl
library. The suffix x
is a mnemonic for extraction.
Note that the accumulator is always evaluated including the initial value.
Lazy Right Folds
Specific Folds
drain :: Monad m => StreamK m a -> m () Source #
drain = foldl' (\_ _ -> ()) () drain = mapM_ (\_ -> return ())
init :: Applicative m => StreamK m a -> m (Maybe (StreamK m a)) Source #
Extract all but the last element of the stream, if any.
Note: This will end up buffering the entire stream.
Pre-release
Mapping
mapMWith :: (m b -> StreamK m b -> StreamK m b) -> (a -> m b) -> StreamK m a -> StreamK m b Source #
Combining Two Streams
Appending
append :: StreamK m a -> StreamK m a -> StreamK m a infixr 6 Source #
Appends two streams sequentially, yielding all elements from the first stream, and then all elements from the second stream.
>>>
s1 = StreamK.fromStream $ Stream.fromList [1,2]
>>>
s2 = StreamK.fromStream $ Stream.fromList [3,4]
>>>
Stream.fold Fold.toList $ StreamK.toStream $ s1 `StreamK.append` s2
[1,2,3,4]
This has O(n) append performance where n
is the number of streams. It can
be used to efficiently fold an infinite lazy container of streams using
concatMapWith
et. al.
Interleave
interleave :: StreamK m a -> StreamK m a -> StreamK m a infixr 6 Source #
Interleaves two streams, yielding one element from each stream alternately. When one stream stops the rest of the other stream is used in the output stream.
When joining many streams in a left associative manner earlier streams will
get exponential priority than the ones joining later. Because of exponential
weighting it can be used with concatMapWith
even on a large number of
streams.
interleaveFst :: StreamK m a -> StreamK m a -> StreamK m a infixr 6 Source #
Like interleave
but stops interleaving as soon as the first stream stops.
interleaveMin :: StreamK m a -> StreamK m a -> StreamK m a infixr 6 Source #
Like interleave
but stops interleaving as soon as any of the two streams
stops.
Cross Product
crossApplyWith :: (StreamK m b -> StreamK m b -> StreamK m b) -> StreamK m (a -> b) -> StreamK m a -> StreamK m b Source #
crossApply :: StreamK m (a -> b) -> StreamK m a -> StreamK m b Source #
Apply a stream of functions to a stream of values and flatten the results.
Note that the second stream is evaluated multiple times.
Definition:
>>>
crossApply = StreamK.crossApplyWith StreamK.append
>>>
crossApply = Stream.crossWith id
crossWith :: Monad m => (a -> b -> c) -> StreamK m a -> StreamK m b -> StreamK m c Source #
Definition:
>>>
crossWith f m1 m2 = fmap f m1 `StreamK.crossApply` m2
Note that the second stream is evaluated multiple times.
cross :: Monad m => StreamK m a -> StreamK m b -> StreamK m (a, b) Source #
Given a StreamK m a
and StreamK m b
generate a stream with all possible
combinations of the tuple (a, b)
.
Definition:
>>>
cross = StreamK.crossWith (,)
The second stream is evaluated multiple times. If that is not desired it can
be cached in an Array
and then generated from the array before
calling this function. Caching may also improve performance if the stream is
expensive to evaluate.
See cross
for a much faster fused
alternative.
Time: O(m x n)
Pre-release
Concat
before :: Monad m => m b -> StreamK m a -> StreamK m a Source #
Run an action before evaluating the stream.
concatMapWith :: (StreamK m b -> StreamK m b -> StreamK m b) -> (a -> StreamK m b) -> StreamK m a -> StreamK m b Source #
Perform a concatMap
using a specified concat strategy. The first
argument specifies a merge or concat function that is used to merge the
streams generated by the map function.
bindWith :: (StreamK m b -> StreamK m b -> StreamK m b) -> StreamK m a -> (a -> StreamK m b) -> StreamK m b Source #
concatIterateWith :: (StreamK m a -> StreamK m a -> StreamK m a) -> (a -> StreamK m a) -> StreamK m a -> StreamK m a Source #
Yield an input element in the output stream, map a stream generator on it
and repeat the process on the resulting stream. Resulting streams are
flattened using the concatMapWith
combinator. This can be used for a depth
first style (DFS) traversal of a tree like structure.
Example, list a directory tree using DFS:
>>>
f = StreamK.fromStream . either Dir.readEitherPaths (const Stream.nil)
>>>
input = StreamK.fromPure (Left ".")
>>>
ls = StreamK.concatIterateWith StreamK.append f input
Note that iterateM
is a special case of concatIterateWith
:
>>>
iterateM f = StreamK.concatIterateWith StreamK.append (StreamK.fromEffect . f) . StreamK.fromEffect
Pre-release
concatIterateLeftsWith :: b ~ Either a c => (StreamK m b -> StreamK m b -> StreamK m b) -> (a -> StreamK m b) -> StreamK m b -> StreamK m b Source #
In an Either
stream iterate on Left
s. This is a special case of
concatIterateWith
:
>>>
concatIterateLeftsWith combine f = StreamK.concatIterateWith combine (either f (const StreamK.nil))
To traverse a directory tree:
>>>
input = StreamK.fromPure (Left ".")
>>>
ls = StreamK.concatIterateLeftsWith StreamK.append (StreamK.fromStream . Dir.readEither) input
Pre-release
concatIterateScanWith :: Monad m => (StreamK m a -> StreamK m a -> StreamK m a) -> (b -> a -> m (b, StreamK m a)) -> m b -> StreamK m a -> StreamK m a Source #
Like iterateMap
but carries a state in the stream generation function.
This can be used to traverse graph like structures, we can remember the
visited nodes in the state to avoid cycles.
Note that a combination of iterateMap
and usingState
can also be used to
traverse graphs. However, this function provides a more localized state
instead of using a global state.
See also: mfix
Pre-release
Merge
mergeMapWith :: (StreamK m b -> StreamK m b -> StreamK m b) -> (a -> StreamK m b) -> StreamK m a -> StreamK m b Source #
Combine streams in pairs using a binary combinator, the resulting streams are then combined again in pairs recursively until we get to a single combined stream. The composition would thus form a binary tree.
For example, you can sort a stream using merge sort like this:
>>>
s = StreamK.fromStream $ Stream.fromList [5,1,7,9,2]
>>>
generate = StreamK.fromPure
>>>
combine = StreamK.mergeBy compare
>>>
Stream.fold Fold.toList $ StreamK.toStream $ StreamK.mergeMapWith combine generate s
[1,2,5,7,9]
Note that if the stream length is not a power of 2, the binary tree composed by mergeMapWith would not be balanced, which may or may not be important depending on what you are trying to achieve.
Caution: the stream of streams must be finite
Pre-release
mergeIterateWith :: (StreamK m a -> StreamK m a -> StreamK m a) -> (a -> StreamK m a) -> StreamK m a -> StreamK m a Source #
Like concatIterateWith
but uses the pairwise flattening combinator
mergeMapWith
for flattening the resulting streams. This can be used for a
balanced traversal of a tree like structure.
Example, list a directory tree using balanced traversal:
>>>
f = StreamK.fromStream . either Dir.readEitherPaths (const Stream.nil)
>>>
input = StreamK.fromPure (Left ".")
>>>
ls = StreamK.mergeIterateWith StreamK.interleave f input
Pre-release