streamly-core-0.1.0: Streaming, parsers, arrays and more
Copyright(c) 2020 Composewell Technologies
LicenseBSD-3-Clause
Maintainerstreamly@composewell.com
Stabilityexperimental
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Streamly.Internal.Data.Stream.StreamD.Top

Description

Top level module that can depend on all other lower level Stream modules.

Synopsis

Transformation

Sampling

Value agnostic filtering.

strideFromThen :: Monad m => Int -> Int -> Stream m a -> Stream m a Source #

strideFromthen offset stride takes the element at offset index and then every element at strides of stride.

>>> Stream.fold Fold.toList $ Stream.strideFromThen 2 3 $ Stream.enumerateFromTo 0 10
[2,5,8]

Nesting

Set like operations

These are not exactly set operations because streams are not necessarily sets, they may have duplicated elements. These operations are generic i.e. they work on streams of unconstrained types, therefore, they have quadratic performance characterstics. For better performance using Set structures see the Streamly.Internal.Data.Stream.Container module.

filterInStreamGenericBy :: Monad m => (a -> a -> Bool) -> Stream m a -> Stream m a -> Stream m a Source #

filterInStreamGenericBy retains only those elements in the second stream that are present in the first stream.

>>> Stream.fold Fold.toList $ Stream.filterInStreamGenericBy (==) (Stream.fromList [1,2,2,4]) (Stream.fromList [2,1,1,3])
[2,1,1]
>>> Stream.fold Fold.toList $ Stream.filterInStreamGenericBy (==) (Stream.fromList [2,1,1,3]) (Stream.fromList [1,2,2,4])
[1,2,2]

Similar to the list intersectBy operation but with the stream argument order flipped.

The first stream must be finite and must not block. Second stream is processed only after the first stream is fully realized.

Space: O(n) where n is the number of elements in the second stream.

Time: O(m x n) where m is the number of elements in the first stream and n is the number of elements in the second stream.

Pre-release

deleteInStreamGenericBy :: Monad m => (a -> a -> Bool) -> Stream m a -> Stream m a -> Stream m a Source #

Delete all elements of the first stream from the seconds stream. If an element occurs multiple times in the first stream as many occurrences of it are deleted from the second stream.

>>> Stream.fold Fold.toList $ Stream.deleteInStreamGenericBy (==) (Stream.fromList [1,2,3]) (Stream.fromList [1,2,2])
[2]

The following laws hold:

deleteInStreamGenericBy (==) s1 (s1 `append` s2) === s2
deleteInStreamGenericBy (==) s1 (s1 `interleave` s2) === s2

Same as the list // operation but with argument order flipped.

The first stream must be finite and must not block. Second stream is processed only after the first stream is fully realized.

Space: O(m) where m is the number of elements in the first stream.

Time: O(m x n) where m is the number of elements in the first stream and n is the number of elements in the second stream.

Pre-release

unionWithStreamGenericBy :: MonadIO m => (a -> a -> Bool) -> Stream m a -> Stream m a -> Stream m a Source #

This essentially appends to the second stream all the occurrences of elements in the first stream that are not already present in the second stream.

Equivalent to the following except that s2 is evaluated only once:

>>> unionWithStreamGenericBy eq s1 s2 = s2 `Stream.append` (Stream.deleteInStreamGenericBy eq s2 s1)

Example:

>>> Stream.fold Fold.toList $ Stream.unionWithStreamGenericBy (==) (Stream.fromList [1,1,2,3]) (Stream.fromList [1,2,2,4])
[1,2,2,4,3]

Space: O(n)

Time: O(m x n)

Pre-release

Set like operations on sorted streams

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

Like filterInStreamGenericBy but assumes that the input streams are sorted in ascending order. To use it on streams sorted in descending order pass an inverted comparison function returning GT for less than and LT for greater than.

Space: O(1)

Time: O(m+n)

Pre-release

deleteInStreamAscBy :: (a -> a -> Ordering) -> Stream m a -> Stream m a -> Stream m a Source #

A more efficient deleteInStreamGenericBy for streams sorted in ascending order.

Space: O(1)

Unimplemented

unionWithStreamAscBy :: (a -> a -> Ordering) -> Stream m a -> Stream m a -> Stream m a Source #

A more efficient unionWithStreamGenericBy for sorted streams.

Space: O(1)

Unimplemented

Join operations

joinInnerGeneric :: Monad m => (a -> b -> Bool) -> Stream m a -> Stream m b -> Stream m (a, b) Source #

Like cross but emits only those tuples where a == b using the supplied equality predicate.

Definition:

>>> joinInnerGeneric eq s1 s2 = Stream.filter (\(a, b) -> a `eq` b) $ Stream.cross s1 s2

You should almost always prefer joinInnerOrd over joinInnerGeneric if possible. joinInnerOrd is an order of magnitude faster but may take more space for caching the second stream.

See joinInnerGeneric for a much faster fused alternative.

Time: O(m x n)

Pre-release

Joins on sorted stream

joinInnerAscBy :: (a -> b -> Ordering) -> Stream m a -> Stream m b -> Stream m (a, b) Source #

A more efficient joinInner for sorted streams.

Space: O(1)

Time: O(m + n)

Unimplemented

joinLeftAscBy :: (a -> b -> Ordering) -> Stream m a -> Stream m b -> Stream m (a, Maybe b) Source #

A more efficient joinLeft for sorted streams.

Space: O(1)

Time: O(m + n)

Unimplemented

joinOuterAscBy :: (a -> b -> Ordering) -> Stream m a -> Stream m b -> Stream m (Maybe a, Maybe b) Source #

A more efficient joinOuter for sorted streams.

Space: O(1)

Time: O(m + n)

Unimplemented