Copyright | (c) 2017 Composewell Technologies |
---|---|
License | BSD3 |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- fromStreamS :: (IsStream t, Monad m) => Stream m a -> t m a
- toStreamS :: (IsStream t, Monad m) => t m a -> Stream m a
- drain :: (IsStream t, Monad m) => t m a -> m ()
- fromList :: (Monad m, IsStream t) => [a] -> t m a
- toList :: (Monad m, IsStream t) => t m a -> m [a]
- foldrM :: (Monad m, IsStream t) => (a -> m b -> m b) -> m b -> t m a -> m b
- foldrMx :: (Monad m, IsStream t) => (a -> m x -> m x) -> m x -> (m x -> m b) -> t m a -> m b
- foldr :: (Monad m, IsStream t) => (a -> b -> b) -> b -> t m a -> m b
- foldlx' :: (IsStream t, Monad m) => (x -> a -> x) -> x -> (x -> b) -> t m a -> m b
- foldlMx' :: (IsStream t, Monad m) => (x -> a -> m x) -> m x -> (x -> m b) -> t m a -> m b
- foldl' :: (Monad m, IsStream t) => (b -> a -> b) -> b -> t m a -> m b
- fold :: (Monad m, IsStream t) => Fold m a b -> t m a -> m b
- foldlS :: IsStream t => (t m b -> a -> t m b) -> t m b -> t m a -> t m b
- foldlT :: (Monad m, IsStream t, Monad (s m), MonadTrans s) => (s m b -> a -> s m b) -> s m b -> t m a -> s m b
- scanlx' :: (IsStream t, Monad m) => (x -> a -> x) -> x -> (x -> b) -> t m a -> t m b
- scanlMx' :: (IsStream t, Monad m) => (x -> a -> m x) -> m x -> (x -> m b) -> t m a -> t m b
- postscanlx' :: (IsStream t, Monad m) => (x -> a -> x) -> x -> (x -> b) -> t m a -> t m b
- postscanlMx' :: (IsStream t, Monad m) => (x -> a -> m x) -> m x -> (x -> m b) -> t m a -> t m b
- postscanOnce :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m b
- scanOnce :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m b
- eqBy :: (IsStream t, Monad m) => (a -> b -> Bool) -> t m a -> t m b -> m Bool
- cmpBy :: (IsStream t, Monad m) => (a -> b -> Ordering) -> t m a -> t m b -> m Ordering
- minimum :: (IsStream t, Monad m, Ord a) => t m a -> m (Maybe a)
- maximum :: (IsStream t, Monad m, Ord a) => t m a -> m (Maybe a)
- concatMapBy :: IsStream t => (t m b -> t m b -> t m b) -> (a -> t m b) -> t m a -> t m b
- concatMap :: IsStream t => (a -> t m b) -> t m a -> t m b
- concatFoldableWith :: (IsStream t, Foldable f) => (t m a -> t m a -> t m a) -> f (t m a) -> t m a
- concatMapFoldableWith :: (IsStream t, Foldable f) => (t m b -> t m b -> t m b) -> (a -> t m b) -> f a -> t m b
- concatForFoldableWith :: (IsStream t, Foldable f) => (t m b -> t m b -> t m b) -> f a -> (a -> t m b) -> t m b
Stream Conversion
Running Effects
Conversion operations
fromList :: (Monad m, IsStream t) => [a] -> t m a Source #
fromList =foldr
cons
nil
Construct a stream from a list of pure values. This is more efficient than
fromFoldable
for serial streams.
Since: 0.4.0
toList :: (Monad m, IsStream t) => t m a -> m [a] Source #
Convert a stream into a list in the underlying monad.
Since: 0.1.0
Fold operations
foldrMx :: (Monad m, IsStream t) => (a -> m x -> m x) -> m x -> (m x -> m b) -> t m a -> m b Source #
foldlx' :: (IsStream t, Monad m) => (x -> a -> x) -> x -> (x -> b) -> t 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.
Since: 0.7.0
foldlMx' :: (IsStream t, Monad m) => (x -> a -> m x) -> m x -> (x -> m b) -> t m a -> m b Source #
Like foldlx'
, but with a monadic step function.
Since: 0.7.0
foldl' :: (Monad m, IsStream t) => (b -> a -> b) -> b -> t m a -> m b Source #
Strict left associative fold.
Since: 0.2.0
foldlT :: (Monad m, IsStream t, Monad (s m), MonadTrans s) => (s m b -> a -> s m b) -> s m b -> t m a -> s m b Source #
Lazy left fold to a transformer monad.
For example, to reverse a stream:
S.toList $ S.foldlT (flip S.cons) S.nil $ (S.fromList [1..5] :: SerialT IO Int)
scanlx' :: (IsStream t, Monad m) => (x -> a -> x) -> x -> (x -> b) -> t m a -> t m b Source #
Strict left scan with an extraction function. Like scanl'
, but applies a
user supplied extraction function (the third argument) at each step. This is
designed to work with the foldl
library. The suffix x
is a mnemonic for
extraction.
Since: 0.7.0
scanlMx' :: (IsStream t, Monad m) => (x -> a -> m x) -> m x -> (x -> m b) -> t m a -> t m b Source #
postscanlx' :: (IsStream t, Monad m) => (x -> a -> x) -> x -> (x -> b) -> t m a -> t m b Source #
postscanlMx' :: (IsStream t, Monad m) => (x -> a -> m x) -> m x -> (x -> m b) -> t m a -> t m b Source #
Zip style operations
eqBy :: (IsStream t, Monad m) => (a -> b -> Bool) -> t m a -> t m b -> m Bool Source #
Compare two streams for equality
Since: 0.5.3
cmpBy :: (IsStream t, Monad m) => (a -> b -> Ordering) -> t m a -> t m b -> m Ordering Source #
Compare two streams
Since: 0.5.3
Foldable instance
Nesting
concatMapBy :: IsStream t => (t m b -> t m b -> t m b) -> (a -> t m b) -> t m a -> t m b Source #
Fold Utilities
concatFoldableWith :: (IsStream t, Foldable f) => (t m a -> t m a -> t m a) -> f (t m a) -> t m a Source #
A variant of fold
that allows you to fold a Foldable
container of streams using the specified stream sum operation.
concatFoldableWith async
$ map return [1..3]
Equivalent to:
concatFoldableWith f = Prelude.foldr f S.nil concatFoldableWith f = S.concatMapFoldableWith f id
Since: 0.8.0 (Renamed foldWith to concatFoldableWith)
Since: 0.1.0 (Streamly)
concatMapFoldableWith :: (IsStream t, Foldable f) => (t m b -> t m b -> t m b) -> (a -> t m b) -> f a -> t m b Source #
A variant of foldMap
that allows you to map a monadic streaming action
on a Foldable
container and then fold it using the specified stream merge
operation.
concatMapFoldableWith async
return [1..3]
Equivalent to:
concatMapFoldableWith f g = Prelude.foldr (f . g) S.nil concatMapFoldableWith f g xs = S.concatMapWith f g (S.fromFoldable xs)
Since: 0.8.0 (Renamed foldMapWith to concatMapFoldableWith)
Since: 0.1.0 (Streamly)
concatForFoldableWith :: (IsStream t, Foldable f) => (t m b -> t m b -> t m b) -> f a -> (a -> t m b) -> t m b Source #
Like concatMapFoldableWith
but with the last two arguments reversed i.e. the
monadic streaming function is the last argument.
Equivalent to:
concatForFoldableWith f xs g = Prelude.foldr (f . g) S.nil xs concatForFoldableWith = flip S.concatMapFoldableWith
Since: 0.8.0 (Renamed forEachWith to concatForFoldableWith)
Since: 0.1.0 (Streamly)