Copyright | (c) 2017 Composewell Technologies |
---|---|
License | BSD3 |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Streamly.Internal.Data.Stream.Zip
Contents
Description
To run examples in this module:
>>>
import qualified Streamly.Prelude as Stream
Synopsis
- newtype ZipSerialM m a = ZipSerialM {
- getZipSerialM :: Stream m a
- type ZipSerial = ZipSerialM IO
- consMZip :: Monad m => m a -> ZipSerialM m a -> ZipSerialM m a
- zipWithK :: Monad m => (a -> b -> c) -> Stream m a -> Stream m b -> Stream m c
- zipWithMK :: Monad m => (a -> b -> m c) -> Stream m a -> Stream m b -> Stream m c
- newtype ZipAsyncM m a = ZipAsyncM {
- getZipAsyncM :: Stream m a
- type ZipAsync = ZipAsyncM IO
- consMZipAsync :: Monad m => m a -> ZipAsyncM m a -> ZipAsyncM m a
- zipAsyncWithK :: MonadAsync m => (a -> b -> c) -> Stream m a -> Stream m b -> Stream m c
- zipAsyncWithMK :: MonadAsync m => (a -> b -> m c) -> Stream m a -> Stream m b -> Stream m c
- type ZipStream = ZipSerialM
Documentation
newtype ZipSerialM m a Source #
For ZipSerialM
streams:
(<>) = serial
(*) = 'Streamly.Prelude.serial.zipWith' id
Applicative evaluates the streams being zipped serially:
>>>
s1 = Stream.fromFoldable [1, 2]
>>>
s2 = Stream.fromFoldable [3, 4]
>>>
s3 = Stream.fromFoldable [5, 6]
>>>
Stream.toList $ Stream.fromZipSerial $ (,,) <$> s1 <*> s2 <*> s3
[(1,3,5),(2,4,6)]
Since: 0.2.0 (Streamly)
Since: 0.8.0
Constructors
ZipSerialM | |
Fields
|
Instances
type ZipSerial = ZipSerialM IO Source #
consMZip :: Monad m => m a -> ZipSerialM m a -> ZipSerialM m a Source #
newtype ZipAsyncM m a Source #
For ZipAsyncM
streams:
(<>) = serial
(*) = 'Streamly.Prelude.serial.zipAsyncWith' id
Applicative evaluates the streams being zipped concurrently, the following would take half the time that it would take in serial zipping:
>>>
s = Stream.fromFoldableM $ Prelude.map delay [1, 1, 1]
>>>
Stream.toList $ Stream.fromZipAsync $ (,) <$> s <*> s
... [(1,1),(1,1),(1,1)]
Since: 0.2.0 (Streamly)
Since: 0.8.0
Constructors
ZipAsyncM | |
Fields
|
Instances
IsStream ZipAsyncM Source # | |
Defined in Streamly.Internal.Data.Stream.IsStream.Type Methods toStream :: forall (m :: Type -> Type) a. ZipAsyncM m a -> Stream m a Source # fromStream :: forall (m :: Type -> Type) a. Stream m a -> ZipAsyncM m a Source # consM :: MonadAsync m => m a -> ZipAsyncM m a -> ZipAsyncM m a Source # (|:) :: MonadAsync m => m a -> ZipAsyncM m a -> ZipAsyncM m a Source # | |
Monad m => Functor (ZipAsyncM m) Source # | |
MonadAsync m => Applicative (ZipAsyncM m) Source # | |
Defined in Streamly.Internal.Data.Stream.Zip | |
Semigroup (ZipAsyncM m a) Source # | |
Monoid (ZipAsyncM m a) Source # | |
zipAsyncWithK :: MonadAsync m => (a -> b -> c) -> Stream m a -> Stream m b -> Stream m c Source #
Like zipWith
but zips concurrently i.e. both the streams being zipped
are evaluated concurrently using the ParallelT
concurrent evaluation
style. The maximum number of elements of each stream evaluated in advance
can be controlled by maxBuffer
.
The stream ends if stream a
or stream b
ends. However, if stream b
ends while we are still evaluating stream a
and waiting for a result then
stream will not end until after the evaluation of stream a
finishes. This
behavior can potentially be changed in future to end the stream immediately
as soon as any of the stream end is detected.
Since: 0.1.0
zipAsyncWithMK :: MonadAsync m => (a -> b -> m c) -> Stream m a -> Stream m b -> Stream m c Source #
Like zipAsyncWith
but with a monadic zipping function.
Since: 0.4.0
Deprecated
type ZipStream = ZipSerialM Source #
Deprecated: Please use ZipSerialM
instead.
Since: 0.1.0