Copyright | (c) 2017 Harendra Kumar |
---|---|
License | BSD3 |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
This module is designed to be imported qualified:
import qualified Streamly.Prelude as S
Functions with the suffix M
are general functions that work on monadic
arguments. The corresponding functions without the suffix M
work on pure
arguments and can in general be derived from their monadic versions but are
provided for convenience and for consistency with other pure APIs in the
base
package.
In many cases, short definitions of the combinators are provided in the documentation for illustration. The actual implementation may differ for performance reasons.
Functions having a MonadAsync
constraint work concurrently when used with
appropriate stream type combinator. Please be careful to not use parallely
with infinite streams.
Deconstruction and folds accept a SerialT
type instead of a polymorphic
type to ensure that streams always have a concrete monomorphic type by
default, reducing type errors. In case you want to use any other type of
stream you can use one of the type combinators provided in the Streamly
module to convert the stream type.
Synopsis
- nil :: IsStream t => t m a
- cons :: IsStream t => a -> t m a -> t m a
- (.:) :: IsStream t => a -> t m a -> t m a
- consM :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a
- (|:) :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a
- yield :: IsStream t => a -> t m a
- yieldM :: (Monad m, IsStream t) => m a -> t m a
- repeat :: (IsStream t, Monad m) => a -> t m a
- repeatM :: (IsStream t, MonadAsync m) => m a -> t m a
- replicate :: (IsStream t, Monad m) => Int -> a -> t m a
- replicateM :: (IsStream t, MonadAsync m) => Int -> m a -> t m a
- class Enum a => Enumerable a where
- enumerateFrom :: (IsStream t, Monad m) => a -> t m a
- enumerateFromTo :: (IsStream t, Monad m) => a -> a -> t m a
- enumerateFromThen :: (IsStream t, Monad m) => a -> a -> t m a
- enumerateFromThenTo :: (IsStream t, Monad m) => a -> a -> a -> t m a
- enumerate :: (IsStream t, Monad m, Bounded a, Enumerable a) => t m a
- enumerateTo :: (IsStream t, Monad m, Bounded a, Enumerable a) => a -> t m a
- unfoldr :: (Monad m, IsStream t) => (b -> Maybe (a, b)) -> b -> t m a
- unfoldrM :: (IsStream t, MonadAsync m) => (b -> m (Maybe (a, b))) -> b -> t m a
- unfold :: (IsStream t, Monad m) => Unfold m a b -> a -> t m b
- iterate :: (IsStream t, Monad m) => (a -> a) -> a -> t m a
- iterateM :: (IsStream t, MonadAsync m) => (a -> m a) -> m a -> t m a
- fromIndices :: (IsStream t, Monad m) => (Int -> a) -> t m a
- fromIndicesM :: (IsStream t, MonadAsync m) => (Int -> m a) -> t m a
- fromList :: (Monad m, IsStream t) => [a] -> t m a
- fromListM :: (MonadAsync m, IsStream t) => [m a] -> t m a
- fromFoldable :: (IsStream t, Foldable f) => f a -> t m a
- fromFoldableM :: (IsStream t, MonadAsync m, Foldable f) => f (m a) -> t m a
- uncons :: (IsStream t, Monad m) => SerialT m a -> m (Maybe (a, t m a))
- tail :: (IsStream t, Monad m) => SerialT m a -> m (Maybe (t m a))
- init :: (IsStream t, Monad m) => SerialT m a -> m (Maybe (t m a))
- foldrM :: Monad m => (a -> m b -> m b) -> m b -> SerialT m a -> m b
- foldr :: Monad m => (a -> b -> b) -> b -> SerialT m a -> m b
- foldl' :: Monad m => (b -> a -> b) -> b -> SerialT m a -> m b
- foldl1' :: Monad m => (a -> a -> a) -> SerialT m a -> m (Maybe a)
- foldlM' :: Monad m => (b -> a -> m b) -> b -> SerialT m a -> m b
- fold :: Monad m => Fold m a b -> SerialT m a -> m b
- drain :: Monad m => SerialT m a -> m ()
- last :: Monad m => SerialT m a -> m (Maybe a)
- length :: Monad m => SerialT m a -> m Int
- sum :: (Monad m, Num a) => SerialT m a -> m a
- product :: (Monad m, Num a) => SerialT m a -> m a
- maximumBy :: Monad m => (a -> a -> Ordering) -> SerialT m a -> m (Maybe a)
- maximum :: (Monad m, Ord a) => SerialT m a -> m (Maybe a)
- minimumBy :: Monad m => (a -> a -> Ordering) -> SerialT m a -> m (Maybe a)
- minimum :: (Monad m, Ord a) => SerialT m a -> m (Maybe a)
- the :: (Eq a, Monad m) => SerialT m a -> m (Maybe a)
- toList :: Monad m => SerialT m a -> m [a]
- drainN :: Monad m => Int -> SerialT m a -> m ()
- drainWhile :: Monad m => (a -> Bool) -> SerialT m a -> m ()
- (!!) :: Monad m => SerialT m a -> Int -> m (Maybe a)
- head :: Monad m => SerialT m a -> m (Maybe a)
- findM :: Monad m => (a -> m Bool) -> SerialT m a -> m (Maybe a)
- find :: Monad m => (a -> Bool) -> SerialT m a -> m (Maybe a)
- lookup :: (Monad m, Eq a) => a -> SerialT m (a, b) -> m (Maybe b)
- findIndex :: Monad m => (a -> Bool) -> SerialT m a -> m (Maybe Int)
- elemIndex :: (Monad m, Eq a) => a -> SerialT m a -> m (Maybe Int)
- null :: Monad m => SerialT m a -> m Bool
- elem :: (Monad m, Eq a) => a -> SerialT m a -> m Bool
- notElem :: (Monad m, Eq a) => a -> SerialT m a -> m Bool
- all :: Monad m => (a -> Bool) -> SerialT m a -> m Bool
- any :: Monad m => (a -> Bool) -> SerialT m a -> m Bool
- and :: Monad m => SerialT m Bool -> m Bool
- or :: Monad m => SerialT m Bool -> m Bool
- 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
- isPrefixOf :: (Eq a, IsStream t, Monad m) => t m a -> t m a -> m Bool
- isSubsequenceOf :: (Eq a, IsStream t, Monad m) => t m a -> t m a -> m Bool
- stripPrefix :: (Eq a, IsStream t, Monad m) => t m a -> t m a -> m (Maybe (t m a))
- map :: (IsStream t, Monad m) => (a -> b) -> t m a -> t m b
- sequence :: (IsStream t, MonadAsync m) => t m (m a) -> t m a
- mapM :: (IsStream t, MonadAsync m) => (a -> m b) -> t m a -> t m b
- mapM_ :: Monad m => (a -> m b) -> SerialT m a -> m ()
- trace :: (IsStream t, MonadAsync m) => (a -> m b) -> t m a -> t m a
- tap :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m a
- scanl' :: (IsStream t, Monad m) => (b -> a -> b) -> b -> t m a -> t m b
- scanlM' :: (IsStream t, Monad m) => (b -> a -> m b) -> b -> t m a -> t m b
- postscanl' :: (IsStream t, Monad m) => (b -> a -> b) -> b -> t m a -> t m b
- postscanlM' :: (IsStream t, Monad m) => (b -> a -> m b) -> b -> t m a -> t m b
- scanl1' :: (IsStream t, Monad m) => (a -> a -> a) -> t m a -> t m a
- scanl1M' :: (IsStream t, Monad m) => (a -> a -> m a) -> t m a -> t m a
- scan :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m b
- postscan :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m b
- filter :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a
- filterM :: (IsStream t, Monad m) => (a -> m Bool) -> t m a -> t m a
- mapMaybe :: (IsStream t, Monad m) => (a -> Maybe b) -> t m a -> t m b
- mapMaybeM :: (IsStream t, MonadAsync m, Functor (t m)) => (a -> m (Maybe b)) -> t m a -> t m b
- deleteBy :: (IsStream t, Monad m) => (a -> a -> Bool) -> a -> t m a -> t m a
- uniq :: (Eq a, IsStream t, Monad m) => t m a -> t m a
- insertBy :: (IsStream t, Monad m) => (a -> a -> Ordering) -> a -> t m a -> t m a
- intersperseM :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a
- intersperse :: (IsStream t, MonadAsync m) => a -> t m a -> t m a
- indexed :: (IsStream t, Monad m) => t m a -> t m (Int, a)
- indexedR :: (IsStream t, Monad m) => Int -> t m a -> t m (Int, a)
- reverse :: (IsStream t, Monad m) => t m a -> t m a
- take :: (IsStream t, Monad m) => Int -> t m a -> t m a
- takeWhile :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a
- takeWhileM :: (IsStream t, Monad m) => (a -> m Bool) -> t m a -> t m a
- drop :: (IsStream t, Monad m) => Int -> t m a -> t m a
- dropWhile :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a
- dropWhileM :: (IsStream t, Monad m) => (a -> m Bool) -> t m a -> t m a
- chunksOf :: (IsStream t, Monad m) => Int -> Fold m a b -> t m a -> t m b
- intervalsOf :: (IsStream t, MonadAsync m) => Double -> Fold m a b -> t m a -> t m b
- findIndices :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m Int
- elemIndices :: (IsStream t, Eq a, Monad m) => a -> t m a -> t m Int
- splitOn :: (IsStream t, Monad m) => (a -> Bool) -> Fold m a b -> t m a -> t m b
- splitOnSuffix :: (IsStream t, Monad m) => (a -> Bool) -> Fold m a b -> t m a -> t m b
- splitWithSuffix :: (IsStream t, Monad m) => (a -> Bool) -> Fold m a b -> t m a -> t m b
- wordsBy :: (IsStream t, Monad m) => (a -> Bool) -> Fold m a b -> t m a -> t m b
- groups :: (IsStream t, Monad m, Eq a) => Fold m a b -> t m a -> t m b
- groupsBy :: (IsStream t, Monad m) => (a -> a -> Bool) -> Fold m a b -> t m a -> t m b
- groupsByRolling :: (IsStream t, Monad m) => (a -> a -> Bool) -> Fold m a b -> t m a -> t m b
- mergeBy :: (IsStream t, Monad m) => (a -> a -> Ordering) -> t m a -> t m a -> t m a
- mergeByM :: (IsStream t, Monad m) => (a -> a -> m Ordering) -> t m a -> t m a -> t m a
- mergeAsyncBy :: (IsStream t, MonadAsync m) => (a -> a -> Ordering) -> t m a -> t m a -> t m a
- mergeAsyncByM :: (IsStream t, MonadAsync m) => (a -> a -> m Ordering) -> t m a -> t m a -> t m a
- zipWith :: (IsStream t, Monad m) => (a -> b -> c) -> t m a -> t m b -> t m c
- zipWithM :: (IsStream t, Monad m) => (a -> b -> m c) -> t m a -> t m b -> t m c
- zipAsyncWith :: (IsStream t, MonadAsync m) => (a -> b -> c) -> t m a -> t m b -> t m c
- zipAsyncWithM :: (IsStream t, MonadAsync m) => (a -> b -> m c) -> t m a -> t m b -> t m c
- concatMapWith :: IsStream t => (forall c. t m c -> t m c -> t m c) -> (a -> t m b) -> t m a -> t m b
- concatMap :: (IsStream t, Monad m) => (a -> t m b) -> t m a -> t m b
- concatMapM :: (IsStream t, Monad m) => (a -> m (t m b)) -> t m a -> t m b
- concatUnfold :: (IsStream t, Monad m) => Unfold m a b -> t m a -> t m b
- before :: (IsStream t, Monad m) => m b -> t m a -> t m a
- after :: (IsStream t, Monad m) => m b -> t m a -> t m a
- bracket :: (IsStream t, MonadCatch m) => m b -> (b -> m c) -> (b -> t m a) -> t m a
- onException :: (IsStream t, MonadCatch m) => m b -> t m a -> t m a
- finally :: (IsStream t, MonadCatch m) => m b -> t m a -> t m a
- handle :: (IsStream t, MonadCatch m, Exception e) => (e -> t m a) -> t m a -> t m a
- once :: (Monad m, IsStream t) => m a -> t m a
- each :: (IsStream t, Foldable f) => f a -> t m a
- scanx :: (IsStream t, Monad m) => (x -> a -> x) -> x -> (x -> b) -> t m a -> t m b
- foldx :: Monad m => (x -> a -> x) -> x -> (x -> b) -> SerialT m a -> m b
- foldxM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> SerialT m a -> m b
- foldr1 :: Monad m => (a -> a -> a) -> SerialT m a -> m (Maybe a)
- runStream :: Monad m => SerialT m a -> m ()
- runN :: Monad m => Int -> SerialT m a -> m ()
- runWhile :: Monad m => (a -> Bool) -> SerialT m a -> m ()
- fromHandle :: (IsStream t, MonadIO m) => Handle -> t m String
- toHandle :: MonadIO m => Handle -> SerialT m String -> m ()
Construction
Primitives
Primitives to construct a stream from pure values or monadic actions. All other stream construction and generation combinators described later can be expressed in terms of these primitives. However, the special versions provided in this module can be much more efficient in most cases. Users can create custom combinators using these primitives.
cons :: IsStream t => a -> t m a -> t m a infixr 5 Source #
Construct a stream by adding a pure value at the head of an existing
stream. For serial streams this is the same as (return a) `consM` r
but
more efficient. For concurrent streams this is not concurrent whereas
consM
is concurrent. For example:
> toList $ 1 `cons` 2 `cons` 3 `cons` nil [1,2,3]
Since: 0.1.0
consM :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a infixr 5 Source #
Constructs a stream by adding a monadic action at the head of an existing stream. For example:
> toList $ getLine `consM` getLine `consM` nil hello world ["hello","world"]
Concurrent (do not use parallely
to construct infinite streams)
Since: 0.2.0
(|:) :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a infixr 5 Source #
Operator equivalent of consM
. We can read it as "parallel colon
"
to remember that |
comes before :
.
> toList $ getLine |: getLine |: nil hello world ["hello","world"]
let delay = threadDelay 1000000 >> print 1 drain $ serially $ delay |: delay |: delay |: nil drain $ parallely $ delay |: delay |: delay |: nil
Concurrent (do not use parallely
to construct infinite streams)
Since: 0.2.0
From Values
Generate a monadic stream from a seed value or values.
yield :: IsStream t => a -> t m a Source #
yield a = a `cons` nil
Create a singleton stream from a pure value.
The following holds in monadic streams, but not in Zip streams:
yield = pure yield = yieldM . pure
In Zip applicative streams yield
is not the same as pure
because in that
case pure
is equivalent to repeat
instead. yield
and pure
are
equally efficient, in other cases yield
may be slightly more efficient
than the other equivalent definitions.
Since: 0.4.0
yieldM :: (Monad m, IsStream t) => m a -> t m a Source #
yieldM m = m `consM` nil
Create a singleton stream from a monadic action.
> toList $ yieldM getLine hello ["hello"]
Since: 0.4.0
repeat :: (IsStream t, Monad m) => a -> t m a Source #
Generate an infinite stream by repeating a pure value.
Since: 0.4.0
repeatM :: (IsStream t, MonadAsync m) => m a -> t m a Source #
repeatM = fix . consM repeatM = cycle1 . yieldM
Generate a stream by repeatedly executing a monadic action forever.
drain $ serially $ S.take 10 $ S.repeatM $ (threadDelay 1000000 >> print 1) drain $ asyncly $ S.take 10 $ S.repeatM $ (threadDelay 1000000 >> print 1)
Concurrent, infinite (do not use with parallely
)
Since: 0.2.0
replicate :: (IsStream t, Monad m) => Int -> a -> t m a Source #
replicate = take n . repeat
Generate a stream of length n
by repeating a value n
times.
Since: 0.6.0
replicateM :: (IsStream t, MonadAsync m) => Int -> m a -> t m a Source #
replicateM = take n . repeatM
Generate a stream by performing a monadic action n
times. Same as:
drain $ serially $ S.replicateM 10 $ (threadDelay 1000000 >> print 1) drain $ asyncly $ S.replicateM 10 $ (threadDelay 1000000 >> print 1)
Concurrent
Since: 0.1.1
Enumeration
We can use the Enum
type class to enumerate a type producing a list
and then convert it to a stream:
fromList
$enumFromThen
from then
However, this is not particularly efficient.
The Enumerable
type class provides corresponding functions that
generate a stream instead of a list, efficiently.
class Enum a => Enumerable a where Source #
Types that can be enumerated as a stream. The operations in this type
class are equivalent to those in the Enum
type class, except that these
generate a stream instead of a list. Use the functions in
Streamly.Internal.Data.Stream.Enumeration module to define new instances.
Since: 0.6.0
enumerateFrom :: (IsStream t, Monad m) => a -> t m a Source #
enumerateFrom from
generates a stream starting with the element
from
, enumerating up to maxBound
when the type is Bounded
or
generating an infinite stream when the type is not Bounded
.
> S.toList $ S.take 4 $ S.enumerateFrom (0 :: Int) [0,1,2,3]
For Fractional
types, enumeration is numerically stable. However, no
overflow or underflow checks are performed.
> S.toList $ S.take 4 $ S.enumerateFrom 1.1 [1.1,2.1,3.1,4.1]
Since: 0.6.0
enumerateFromTo :: (IsStream t, Monad m) => a -> a -> t m a Source #
Generate a finite stream starting with the element from
, enumerating
the type up to the value to
. If to
is smaller than from
then an
empty stream is returned.
> S.toList $ S.enumerateFromTo 0 4 [0,1,2,3,4]
For Fractional
types, the last element is equal to the specified to
value after rounding to the nearest integral value.
> S.toList $ S.enumerateFromTo 1.1 4 [1.1,2.1,3.1,4.1] > S.toList $ S.enumerateFromTo 1.1 4.6 [1.1,2.1,3.1,4.1,5.1]
Since: 0.6.0
enumerateFromThen :: (IsStream t, Monad m) => a -> a -> t m a Source #
enumerateFromThen from then
generates a stream whose first element
is from
, the second element is then
and the successive elements are
in increments of then - from
. Enumeration can occur downwards or
upwards depending on whether then
comes before or after from
. For
Bounded
types the stream ends when maxBound
is reached, for
unbounded types it keeps enumerating infinitely.
> S.toList $ S.take 4 $ S.enumerateFromThen 0 2 [0,2,4,6] > S.toList $ S.take 4 $ S.enumerateFromThen 0 (-2) [0,-2,-4,-6]
Since: 0.6.0
enumerateFromThenTo :: (IsStream t, Monad m) => a -> a -> a -> t m a Source #
enumerateFromThenTo from then to
generates a finite stream whose
first element is from
, the second element is then
and the successive
elements are in increments of then - from
up to to
. Enumeration can
occur downwards or upwards depending on whether then
comes before or
after from
.
> S.toList $ S.enumerateFromThenTo 0 2 6 [0,2,4,6] > S.toList $ S.enumerateFromThenTo 0 (-2) (-6) [0,-2,-4,-6]
Since: 0.6.0
Instances
enumerateTo :: (IsStream t, Monad m, Bounded a, Enumerable a) => a -> t m a Source #
From Generators
Generate a monadic stream from a seed value and a generator function.
unfoldr :: (Monad m, IsStream t) => (b -> Maybe (a, b)) -> b -> t m a Source #
unfoldr step s =
case step s of
Nothing -> nil
Just (a, b) -> a `cons` unfoldr step b
Build a stream by unfolding a pure step function step
starting from a
seed s
. The step function returns the next element in the stream and the
next seed value. When it is done it returns Nothing
and the stream ends.
For example,
let f b = if b > 3 then Nothing else Just (b, b + 1) in toList $ unfoldr f 0
[0,1,2,3]
Since: 0.1.0
unfoldrM :: (IsStream t, MonadAsync m) => (b -> m (Maybe (a, b))) -> b -> t m a Source #
Build a stream by unfolding a monadic step function starting from a
seed. The step function returns the next element in the stream and the next
seed value. When it is done it returns Nothing
and the stream ends. For
example,
let f b = if b > 3 then return Nothing else print b >> return (Just (b, b + 1)) in drain $ unfoldrM f 0
0 1 2 3
When run concurrently, the next unfold step can run concurrently with the processing of the output of the previous step. Note that more than one step cannot run concurrently as the next step depends on the output of the previous step.
(asyncly $ S.unfoldrM (\n -> liftIO (threadDelay 1000000) >> return (Just (n, n + 1))) 0) & S.foldlM' (\_ a -> threadDelay 1000000 >> print a) ()
Concurrent
Since: 0.1.0
unfold :: (IsStream t, Monad m) => Unfold m a b -> a -> t m b Source #
Convert an Unfold
into a stream by supplying it an input seed.
>>>
unfold (UF.replicateM 10) (putStrLn "hello")
Since: 0.7.0
iterate :: (IsStream t, Monad m) => (a -> a) -> a -> t m a Source #
iterate f x = x `cons` iterate f x
Generate an infinite stream with x
as the first element and each
successive element derived by applying the function f
on the previous
element.
> S.toList $ S.take 5 $ S.iterate (+1) 1 [1,2,3,4,5]
Since: 0.1.2
iterateM :: (IsStream t, MonadAsync m) => (a -> m a) -> m a -> t m a Source #
iterateM f m = m >>= a -> return a `consM` iterateM f (f a)
Generate an infinite stream with the first element generated by the action
m
and each successive element derived by applying the monadic function
f
on the previous element.
When run concurrently, the next iteration can run concurrently with the processing of the previous iteration. Note that more than one iteration cannot run concurrently as the next iteration depends on the output of the previous iteration.
drain $ serially $ S.take 10 $ S.iterateM (\x -> threadDelay 1000000 >> print x >> return (x + 1)) (return 0) drain $ asyncly $ S.take 10 $ S.iterateM (\x -> threadDelay 1000000 >> print x >> return (x + 1)) (return 0)
Concurrent
Since: 0.7.0 (signature change)
Since: 0.1.2
fromIndices :: (IsStream t, Monad m) => (Int -> a) -> t m a Source #
fromIndices f = let g i = f i `cons` g (i + 1) in g 0
Generate an infinite stream, whose values are the output of a function f
applied on the corresponding index. Index starts at 0.
> S.toList $ S.take 5 $ S.fromIndices id [0,1,2,3,4]
Since: 0.6.0
fromIndicesM :: (IsStream t, MonadAsync m) => (Int -> m a) -> t m a Source #
fromIndicesM f = let g i = f i `consM` g (i + 1) in g 0
Generate an infinite stream, whose values are the output of a monadic
function f
applied on the corresponding index. Index starts at 0.
Concurrent
Since: 0.6.0
From Containers
Convert an input structure, container or source into a stream. All of these can be expressed in terms of primitives.
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
fromListM :: (MonadAsync m, IsStream t) => [m a] -> t m a Source #
fromListM =foldr
consM
nil
Construct a stream from a list of monadic actions. This is more efficient
than fromFoldableM
for serial streams.
Since: 0.4.0
fromFoldable :: (IsStream t, Foldable f) => f a -> t m a Source #
fromFoldableM :: (IsStream t, MonadAsync m, Foldable f) => f (m a) -> t m a Source #
fromFoldableM =foldr
consM
nil
Construct a stream from a Foldable
containing monadic actions.
drain $ serially $ S.fromFoldableM $ replicateM 10 (threadDelay 1000000 >> print 1) drain $ asyncly $ S.fromFoldableM $ replicateM 10 (threadDelay 1000000 >> print 1)
Concurrent (do not use with parallely
on infinite containers)
Since: 0.3.0
Elimination
Deconstruction
It is easy to express all the folds in terms of the uncons
primitive,
however the specific implementations provided later are generally more
efficient.
uncons :: (IsStream t, Monad m) => SerialT m a -> m (Maybe (a, t m a)) Source #
Decompose a stream into its head and tail. If the stream is empty, returns
Nothing
. If the stream is non-empty, returns Just (a, ma)
, where a
is
the head of the stream and ma
its tail.
This is a brute force primitive. Avoid using it as long as possible, use it when no other combinator can do the job. This can be used to do pretty much anything in an imperative manner, as it just breaks down the stream into individual elements and we can loop over them as we deem fit. For example, this can be used to convert a streamly stream into other stream types.
Since: 0.1.0
tail :: (IsStream t, Monad m) => SerialT m a -> m (Maybe (t m a)) Source #
tail = fmap (fmap snd) . uncons
Extract all but the first element of the stream, if any.
Since: 0.1.1
init :: (IsStream t, Monad m) => SerialT m a -> m (Maybe (t m a)) Source #
Extract all but the last element of the stream, if any.
Since: 0.5.0
Folding
In imperative terms a fold can be considered as a loop over the stream
that reduces the stream to a single value.
Left and right folds use a fold function f
and an identity element z
(zero
) to recursively deconstruct a structure and then combine and reduce
the values or transform and reconstruct a new container.
In general, a right fold is suitable for transforming and reconstructing a right associated structure (e.g. cons lists and streamly streams) and a left fold is suitable for reducing a right associated structure. The behavior of right and left folds are described in detail in the individual fold's documentation. To illustrate the two folds for cons lists:
foldr :: (a -> b -> b) -> b -> [a] -> b foldr f z [] = z foldr f z (x:xs) = x `f` foldr f z xs foldl :: (b -> a -> b) -> b -> [a] -> b foldl f z [] = z foldl f z (x:xs) = foldl f (z `f` x) xs
foldr
is conceptually equivalent to:
foldr f z [] = z foldr f z [x] = f x z foldr f z xs = foldr f (foldr f z (tail xs)) [head xs]
foldl
is conceptually equivalent to:
foldl f z [] = z foldl f z [x] = f z x foldl f z xs = foldl f (foldl f z (init xs)) [last xs]
Left and right folds are duals of each other.
foldr f z xs = foldl (flip f) z (reverse xs) foldl f z xs = foldr (flip f) z (reverse xs)
More generally:
foldr f z xs = foldl g id xs z where g k x = k . f x foldl f z xs = foldr g id xs z where g x k = k . flip f x
Right Folds
Let's take a closer look at the foldr
definition for lists, as given
earlier:
foldr f z (x:xs) = x `f` foldr f z xs
foldr
invokes the fold step function f
as f x (foldr f z xs)
. At each
invocation of f
, foldr
gives us the next element in the input container
x
and a recursive expression foldr f z xs
representing the yet unbuilt
(lazy thunk) part of the output.
When f x xs
is lazy in xs
it can consume the input one element at a time
in FIFO order to build a lazy output expression. For example,
f x remaining = show x : remaining
take 2 $ foldr f [] (1:2:undefined)
would consume the input lazily on
demand, consuming only first two elements and resulting in ["1", "2"]. f
can terminate recursion by not evaluating the remaining
part:
f 2 remaining = show 2 : [] f x remaining = show x : remaining
f
would terminate recursion whenever it sees element 2
in the input.
Therefore, take 2 $ foldr f [] (1:2:undefined)
would work without any
problem.
On the other hand, if f a b
is strict in b
it would end up consuming the
whole input right away and expanding the recursive expression b
(i.e.
foldr f z xs
) fully before it yields an output expression, resulting in
the following right associated expression:
foldr f z xs == x1 `f` (x2 `f` ...(xn `f` z))
For example,
f x remaining = x + remaining
With this definition, foldr f 0 [1..1000]
, would recurse completely until
it reaches the terminating case ...
, and then
start reducing the whole expression from right to left, therefore, consuming
the input elements in LIFO order. Thus, such an evaluation would require
memory proportional to the size of input. Try out f
(1000 f
0)foldr (+) 0 (map (\x ->
trace (show x) x) [1..10])
.
Notice the order of the arguments to the step function f a b
. It follows
the order of a
and b
in the right associative recursive expression
generated by expanding a `f` b
.
A right fold is a pull fold, the step function is the puller, it can pull more data from the input container by using its second argument in the output expression or terminate pulling by not using it. As a corollary:
- a step function which is lazy in its second argument (usually functions
or constructors that build a lazy structure e.g.
(:)
) can pull lazily on demand. - a step function strict in its second argument (usually reducers e.g. (+)) would end up pulling all of its input and buffer it in memory before potentially reducing it.
A right fold is suitable for lazy reconstructions e.g. transformation, mapping, filtering of right associated input structures (e.g. cons lists). Whereas a left fold is suitable for reductions (e.g. summing a stream of numbers) of right associated structures. Note that these roles will reverse for left associated structures (e.g. snoc lists). Most of our observations here assume right associated structures, lists being the canonical example.
- A lazy FIFO style pull using a right fold allows pulling a potentially infinite input stream lazily, perform transformations on it, and reconstruct a new structure without having to buffer the whole structure. In contrast, a left fold would buffer the entire structure before the reconstructed structure can be consumed.
- Even if buffering the entire input structure is ok, we need to keep in mind that a right fold reconstructs structures in a FIFO style, whereas a left fold reconstructs in a LIFO style, thereby reversing the order of elements..
- A right fold has termination control and therefore can terminate early
without going through the entire input, a left fold cannot terminate
without consuming all of its input. For example, a right fold
implementation of
or
can terminate as soon as it finds the firstTrue
element, whereas a left fold would necessarily go through the entire input irrespective of that. - Reduction (e.g. using (+) on a stream of numbers) using a right fold occurs in a LIFO style, which means that the entire input gets buffered before reduction starts. Whereas with a strict left fold reductions occur incrementally in FIFO style. Therefore, a strict left fold is more suitable for reductions.
foldrM :: Monad m => (a -> m b -> m b) -> m b -> SerialT m a -> m b Source #
Right associative/lazy pull fold. foldrM build final stream
constructs
an output structure using the step function build
. build
is invoked with
the next input element and the remaining (lazy) tail of the output
structure. It builds a lazy output expression using the two. When the "tail
structure" in the output expression is evaluated it calls build
again thus
lazily consuming the input stream
until either the output expression built
by build
is free of the "tail" or the input is exhausted in which case
final
is used as the terminating case for the output structure. For more
details see the description in the previous section.
Example, determine if any element is odd
in a stream:
>>>
S.foldrM (\x xs -> if odd x then return True else xs) (return False) $ S.fromList (2:4:5:undefined)
> True
Since: 0.7.0 (signature changed)
Since: 0.2.0 (signature changed)
Since: 0.1.0
foldr :: Monad m => (a -> b -> b) -> b -> SerialT m a -> m b Source #
Right fold, lazy for lazy monads and pure streams, and strict for strict monads.
Please avoid using this routine in strict monads like IO unless you need a
strict right fold. This is provided only for use in lazy monads (e.g.
Identity) or pure streams. Note that with this signature it is not possible
to implement a lazy foldr when the monad m
is strict. In that case it
would be strict in its accumulator and therefore would necessarily consume
all its input.
Since: 0.1.0
Left Folds
Note that the observations below about the behavior of a left fold assume that we are working on a right associated structure like cons lists and streamly streams. If we are working on a left associated structure (e.g. snoc lists) the roles of right and left folds would reverse.
Let's take a closer look at the foldl
definition for lists given above:
foldl f z (x:xs) = foldl f (z `f` x) xs
foldl
calls itself recursively, in each call it invokes f
as f z x
providing it with the result accumulated till now z
(the state) and the
next element from the input container. First call to f
is supplied with
the initial value of the accumulator z
and each subsequent call uses the
output of the previous call to f z x
.
> foldl' (+) 0 [1,2,3] 6
The recursive call at the head of the output expression is bound to be evaluated until recursion terminates, therefore, a left fold always consumes the whole input container. The following would result in an error, even though the fold is not using the values at all:
> foldl' (\_ _ -> 0) 0 (1:undefined) *** Exception: Prelude.undefined
As foldl
recurses, it builds the left associated expression shown below.
Notice, the order of the arguments to the step function f b a
. It follows
the left associative recursive expression generated by expanding b `f` a
.
foldl f z xs == (((z `f` x1) `f` x2) ...) `f` xn
The strict left fold foldl'
forces the reduction of its argument z `f`
x
before using it, therefore it never builds the whole expression in
memory. Thus, z `f` x1
would get reduced to z1
and then z1 `f` x2
would get reduced to z2
and so on, incrementally reducing the expression
from left to right as it recurses, consuming the input in FIFO order. Try
out foldl' (+) 0 (map (\x -> trace (show x) x) [1..10])
to see how it
works. For example:
> S.foldl' (+) 0 $ S.fromList [1,2,3,4] 10
0 + 1 = 1 1 + 2 = 3 3 + 3 = 6 6 + 4 = 10
However, foldl'
evaluates the accumulator only to WHNF. It may further
help if the step function uses a strict data structure as accumulator to
improve performance and to keep the expression fully reduced at all times
during the fold.
A left fold can also build a new structure instead of reducing one if a constructor is used as a fold step. However, it may not be very useful because it will consume the whole input and construct the new structure in memory before we can consume it. Thus the whole structure gets buffered in memory. When the list constructor is used it would build a new list in reverse (LIFO) order:
> S.foldl' (flip (:)) [] $ S.fromList [1,2,3,4] [4,3,2,1]
A left fold is a push fold. The producer pushes its contents to the step function of the fold. The step function therefore has no control to stop the input, it can only discard it if it does not need it. We can also consider a left fold as a state machine where the state is store in the accumulator, the state can be modified based on new inputs that are pushed to the fold.
In general, a strict left fold is a reducing fold, whereas a right fold is a
constructing fold. A strict left fold reduces in a FIFO order whereas it
constructs in a LIFO order, and vice-versa for the right fold. See the
documentation of foldrM
for a discussion on where a left or right fold is
suitable.
To perform a left fold lazily without having to consume all the input one
can use scanl
to stream the intermediate results of the fold and consume
the resulting stream lazily.
foldl' :: Monad m => (b -> a -> b) -> b -> SerialT m a -> m b Source #
Left associative/strict push fold. foldl' reduce initial stream
invokes
reduce
with the accumulator and the next input in the input stream, using
initial
as the initial value of the current value of the accumulator. When
the input is exhausted the current value of the accumulator is returned.
Make sure to use a strict data structure for accumulator to not build
unnecessary lazy expressions unless that's what you want. See the previous
section for more details.
Since: 0.2.0
foldl1' :: Monad m => (a -> a -> a) -> SerialT m a -> m (Maybe a) Source #
Strict left fold, for non-empty streams, using first element as the
starting value. Returns Nothing
if the stream is empty.
Since: 0.5.0
foldlM' :: Monad m => (b -> a -> m b) -> b -> SerialT m a -> m b Source #
Like foldl'
but with a monadic step function.
Since: 0.2.0
Composable Left Folds
Streamly.Data.Fold module defines composable left folds which can be combined
together in many interesting ways. Those folds can be run using fold
.
The following two ways of folding are equivalent in functionality and
performance,
>>>
S.fold FL.sum (S.enumerateFromTo 1 100)
5050>>>
S.sum (S.enumerateFromTo 1 100)
5050
However, left folds cannot terminate early even if it does not need to
consume more input to determine the result. Therefore, the performance is
equivalent only for full folds like sum
and length
. For partial folds
like head
or any
the the folds defined in this module may be much more
efficient because they are implemented as right folds that terminate as soon
as we get the result. Note that when a full fold is composed with a partial
fold in parallel the performance is not impacted as we anyway have to
consume the whole stream due to the full fold.
>>>
S.head (1 `S.cons` undefined)
Just 1>>>
S.fold FL.head (1 `S.cons` undefined)
*** Exception: Prelude.undefined
However, we can wrap the fold in a scan to convert it into a lazy stream of fold steps. We can then terminate the stream whenever we want. For example,
>>>
S.toList $ S.take 1 $ S.scan FL.head (1 `S.cons` undefined)
[Nothing]
The following example extracts the input stream up to a point where the running average of elements is no more than 10:
> S.toList $ S.map (fromJust . fst) $ S.takeWhile (\(_,x) -> x <= 10) $ S.postscan ((,) <$> FL.last <*> avg) (S.enumerateFromTo 1.0 100.0)
[1.0,2.0,3.0,4.0,5.0,6.0,7.0,8.0,9.0,10.0,11.0,12.0,13.0,14.0,15.0,16.0,17.0,18.0,19.0]
fold :: Monad m => Fold m a b -> SerialT m a -> m b Source #
Fold a stream using the supplied left fold.
>>>
S.fold FL.sum (S.enumerateFromTo 1 100)
5050
Since: 0.7.0
Full Folds
Folds that are guaranteed to evaluate the whole stream.
drain :: Monad m => SerialT m a -> m () Source #
drain = mapM_ (\_ -> return ())
Run a stream, discarding the results. By default it interprets the stream
as SerialT
, to run other types of streams use the type adapting
combinators for example drain .
.asyncly
Since: 0.7.0
last :: Monad m => SerialT m a -> m (Maybe a) Source #
Extract the last element of the stream, if any.
last xs = xs !! (length xs - 1)
Since: 0.1.1
sum :: (Monad m, Num a) => SerialT m a -> m a Source #
Determine the sum of all elements of a stream of numbers. Returns 0
when
the stream is empty. Note that this is not numerically stable for floating
point numbers.
Since: 0.1.0
product :: (Monad m, Num a) => SerialT m a -> m a Source #
Determine the product of all elements of a stream of numbers. Returns 1
when the stream is empty.
Since: 0.1.1
maximumBy :: Monad m => (a -> a -> Ordering) -> SerialT m a -> m (Maybe a) Source #
Determine the maximum element in a stream using the supplied comparison function.
Since: 0.6.0
minimumBy :: Monad m => (a -> a -> Ordering) -> SerialT m a -> m (Maybe a) Source #
Determine the minimum element in a stream using the supplied comparison function.
Since: 0.6.0
the :: (Eq a, Monad m) => SerialT m a -> m (Maybe a) Source #
Ensures that all the elements of the stream are identical and then returns that unique element.
Since: 0.6.0
Lazy Folds
Folds that generate a lazy structure. Note that the generated structure may not be lazy if the underlying monad is strict.
toList :: Monad m => SerialT m a -> m [a] Source #
toList = S.foldr (:) []
Convert a stream into a list in the underlying monad. The list can be
consumed lazily in a lazy monad (e.g. Identity
). In a strict monad (e.g.
IO) the whole list is generated and buffered before it can be consumed.
Warning! working on large lists accumulated as buffers in memory could be very inefficient, consider using Streamly.Array instead.
Since: 0.1.0
Partial Folds
Folds that may terminate before evaluating the whole stream. These folds strictly evaluate the stream until the result is determined.
drainN :: Monad m => Int -> SerialT m a -> m () Source #
drainN n = drain . take n
Run maximum up to n
iterations of a stream.
Since: 0.7.0
drainWhile :: Monad m => (a -> Bool) -> SerialT m a -> m () Source #
drainWhile p = drain . takeWhile p
Run a stream as long as the predicate holds true.
Since: 0.7.0
(!!) :: Monad m => SerialT m a -> Int -> m (Maybe a) Source #
Lookup the element at the given index.
Since: 0.6.0
head :: Monad m => SerialT m a -> m (Maybe a) Source #
Extract the first element of the stream, if any.
head = (!! 0)
Since: 0.1.0
findM :: Monad m => (a -> m Bool) -> SerialT m a -> m (Maybe a) Source #
Returns the first element that satisfies the given predicate.
Since: 0.6.0
lookup :: (Monad m, Eq a) => a -> SerialT m (a, b) -> m (Maybe b) Source #
In a stream of (key-value) pairs (a, b)
, return the value b
of the
first pair where the key equals the given value a
.
lookup = snd <$> find ((==) . fst)
Since: 0.5.0
findIndex :: Monad m => (a -> Bool) -> SerialT m a -> m (Maybe Int) Source #
Returns the first index that satisfies the given predicate.
Since: 0.5.0
elemIndex :: (Monad m, Eq a) => a -> SerialT m a -> m (Maybe Int) Source #
Returns the first index where a given value is found in the stream.
elemIndex a = findIndex (== a)
Since: 0.5.0
elem :: (Monad m, Eq a) => a -> SerialT m a -> m Bool Source #
Determine whether an element is present in the stream.
Since: 0.1.0
notElem :: (Monad m, Eq a) => a -> SerialT m a -> m Bool Source #
Determine whether an element is not present in the stream.
Since: 0.1.0
all :: Monad m => (a -> Bool) -> SerialT m a -> m Bool Source #
Determine whether all elements of a stream satisfy a predicate.
Since: 0.1.0
any :: Monad m => (a -> Bool) -> SerialT m a -> m Bool Source #
Determine whether any of the elements of a stream satisfy a predicate.
Since: 0.1.0
and :: Monad m => SerialT m Bool -> m Bool Source #
Determines if all elements of a boolean stream are True.
Since: 0.5.0
or :: Monad m => SerialT m Bool -> m Bool Source #
Determines whether at least one element of a boolean stream is True.
Since: 0.5.0
Multi-Stream folds
eqBy :: (IsStream t, Monad m) => (a -> b -> Bool) -> t m a -> t m b -> m Bool Source #
Compare two streams for equality using an equality function.
Since: 0.6.0
cmpBy :: (IsStream t, Monad m) => (a -> b -> Ordering) -> t m a -> t m b -> m Ordering Source #
Compare two streams lexicographically using a comparison function.
Since: 0.6.0
isPrefixOf :: (Eq a, IsStream t, Monad m) => t m a -> t m a -> m Bool Source #
Returns True
if the first stream is the same as or a prefix of the
second. A stream is a prefix of itself.
> S.isPrefixOf (S.fromList "hello") (S.fromList "hello" :: SerialT IO Char) True
Since: 0.6.0
isSubsequenceOf :: (Eq a, IsStream t, Monad m) => t m a -> t m a -> m Bool Source #
Returns True
if all the elements of the first stream occur, in order, in
the second stream. The elements do not have to occur consecutively. A stream
is a subsequence of itself.
> S.isSubsequenceOf (S.fromList "hlo") (S.fromList "hello" :: SerialT IO Char) True
Since: 0.6.0
stripPrefix :: (Eq a, IsStream t, Monad m) => t m a -> t m a -> m (Maybe (t m a)) Source #
Drops the given prefix from a stream. Returns Nothing
if the stream does
not start with the given prefix. Returns Just nil
when the prefix is the
same as the stream.
Since: 0.6.0
Transformation
Mapping
In imperative terms a map operation can be considered as a loop over the stream that transforms the stream into another stream by performing an operation on each element of the stream.
map
is the least powerful transformation operation with strictest
guarantees. A map, (1) is a stateless loop which means that no state is
allowed to be carried from one iteration to another, therefore,
operations on different elements are guaranteed to not affect each
other, (2) is a strictly one-to-one transformation of stream elements
which means it guarantees that no elements can be added or removed from
the stream, it can merely transform them.
sequence :: (IsStream t, MonadAsync m) => t m (m a) -> t m a Source #
sequence = mapM id
Replace the elements of a stream of monadic actions with the outputs of those actions.
> drain $ S.sequence $ S.fromList [putStr "a", putStr "b", putStrLn "c"] abc drain $ S.replicateM 10 (return $ threadDelay 1000000 >> print 1) & (serially . S.sequence) drain $ S.replicateM 10 (return $ threadDelay 1000000 >> print 1) & (asyncly . S.sequence)
Concurrent (do not use with parallely
on infinite streams)
Since: 0.1.0
mapM :: (IsStream t, MonadAsync m) => (a -> m b) -> t m a -> t m b Source #
mapM f = sequence . map f
Apply a monadic function to each element of the stream and replace it with the output of the resulting action.
> drain $ S.mapM putStr $ S.fromList ["a", "b", "c"] abc drain $ S.replicateM 10 (return 1) & (serially . S.mapM (\x -> threadDelay 1000000 >> print x)) drain $ S.replicateM 10 (return 1) & (asyncly . S.mapM (\x -> threadDelay 1000000 >> print x))
Concurrent (do not use with parallely
on infinite streams)
Since: 0.1.0
Special Maps
mapM_ :: Monad m => (a -> m b) -> SerialT m a -> m () Source #
mapM_ = drain . mapM
Apply a monadic action to each element of the stream and discard the output of the action. This is not really a pure transformation operation but a transformation followed by fold.
Since: 0.1.0
trace :: (IsStream t, MonadAsync m) => (a -> m b) -> t m a -> t m a Source #
Apply a monadic function to each element flowing through the stream and discard the results.
> S.drain $ S.trace print (S.enumerateFromTo 1 2) 1 2
Compare with tap
.
Since: 0.7.0
tap :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m a Source #
Tap the data flowing through a stream into a Fold
. For example, you may
add a tap to log the contents flowing through the stream. The fold is used
only for effects, its result is discarded.
Fold m a b | -----stream m a ---------------stream m a-----
> S.drain $ S.tap (FL.drainBy print) (S.enumerateFromTo 1 2) 1 2
Compare with trace
.
Since: 0.7.0
Scanning
A scan is more powerful than map. While a map
is a stateless loop, a
scan
is a stateful loop which means that a state can be shared across
all the loop iterations, therefore, future iterations can be impacted by
the state changes made by the past iterations. A scan yields the state
of the loop after each iteration. Like a map, a postscan
or prescan
does not add or remove elements in the stream, it just transforms them.
However, a scan
adds one extra element to the stream.
A left associative scan, also known as a prefix sum, can be thought of as a stream transformation consisting of left folds of all prefixes of a stream. Another way of thinking about it is that it streams all the intermediate values of the accumulator while applying a left fold on the input stream. A right associative scan, on the other hand, can be thought of as a stream consisting of right folds of all the suffixes of a stream.
The following equations hold for lists:
scanl f z xs == map (foldl f z) $ inits xs scanr f z xs == map (foldr f z) $ tails xs
> scanl (+) 0 [1,2,3,4] 0 = 0 0 + 1 = 1 0 + 1 + 2 = 3 0 + 1 + 2 + 3 = 6 0 + 1 + 2 + 3 + 4 = 10 > scanr (+) 0 [1,2,3,4] 1 + 2 + 3 + 4 + 0 = 10 2 + 3 + 4 + 0 = 9 3 + 4 + 0 = 7 4 + 0 = 4 0 = 0
Left and right scans are duals:
scanr f z xs == reverse $ scanl (flip f) z (reverse xs) scanl f z xs == reverse $ scanr (flip f) z (reverse xs)
A scan is a stateful map i.e. a combination of map and fold:
map f xs = tail $ scanl (\_ x -> f x) z xs map f xs = reverse $ head $ scanr (\_ x -> f x) z xs
foldl f z xs = last $ scanl f z xs foldr f z xs = head $ scanr f z xs
Left scans
scanl' :: (IsStream t, Monad m) => (b -> a -> b) -> b -> t m a -> t m b Source #
Strict left scan. Like map
, scanl'
too is a one to one transformation,
however it adds an extra element.
> S.toList $ S.scanl' (+) 0 $ fromList [1,2,3,4] [0,1,3,6,10]
> S.toList $ S.scanl' (flip (:)) [] $ S.fromList [1,2,3,4] [[],[1],[2,1],[3,2,1],[4,3,2,1]]
The output of scanl'
is the initial value of the accumulator followed by
all the intermediate steps and the final result of foldl'
.
By streaming the accumulated state after each fold step, we can share the state across multiple stages of stream composition. Each stage can modify or extend the state, do some processing with it and emit it for the next stage, thus modularizing the stream processing. This can be useful in stateful or event-driven programming.
Consider the following monolithic example, computing the sum and the product
of the elements in a stream in one go using a foldl'
:
> S.foldl' (\(s, p) x -> (s + x, p * x)) (0,1) $ S.fromList [1,2,3,4] (10,24)
Using scanl'
we can make it modular by computing the sum in the first
stage and passing it down to the next stage for computing the product:
> S.foldl' (\(_, p) (s, x) -> (s, p * x)) (0,1) $ S.scanl' (\(s, _) x -> (s + x, x)) (0,1) $ S.fromList [1,2,3,4] (10,24)
IMPORTANT: scanl'
evaluates the accumulator to WHNF. To avoid building
lazy expressions inside the accumulator, it is recommended that a strict
data structure is used for accumulator.
Since: 0.2.0
scanlM' :: (IsStream t, Monad m) => (b -> a -> m b) -> b -> t m a -> t m b Source #
Like scanl'
but with a monadic fold function.
Since: 0.4.0
postscanl' :: (IsStream t, Monad m) => (b -> a -> b) -> b -> t m a -> t m b Source #
Like scanl'
but does not stream the initial value of the accumulator.
postscanl' f z xs = S.drop 1 $ S.scanl' f z xs
Since: 0.7.0
postscanlM' :: (IsStream t, Monad m) => (b -> a -> m b) -> b -> t m a -> t m b Source #
Like postscanl'
but with a monadic step function.
Since: 0.7.0
scanl1' :: (IsStream t, Monad m) => (a -> a -> a) -> t m a -> t m a Source #
Like scanl'
but for a non-empty stream. The first element of the stream
is used as the initial value of the accumulator. Does nothing if the stream
is empty.
> S.toList $ S.scanl1 (+) $ fromList [1,2,3,4] [1,3,6,10]
Since: 0.6.0
scanl1M' :: (IsStream t, Monad m) => (a -> a -> m a) -> t m a -> t m a Source #
Like scanl1'
but with a monadic step function.
Since: 0.6.0
Scan Using Fold
scan :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m b Source #
Scan a stream using the given monadic fold.
Since: 0.7.0
postscan :: (IsStream t, Monad m) => Fold m a b -> t m a -> t m b Source #
Postscan a stream using the given monadic fold.
Since: 0.7.0
Filtering
Remove some elements from the stream based on a predicate. In
imperative terms a filter over a stream corresponds to a loop with a
continue
clause for the cases when the predicate fails.
filter :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a Source #
Include only those elements that pass a predicate.
Since: 0.1.0
filterM :: (IsStream t, Monad m) => (a -> m Bool) -> t m a -> t m a Source #
Same as filter
but with a monadic predicate.
Since: 0.4.0
Mapping Filters
Mapping along with filtering
mapMaybeM :: (IsStream t, MonadAsync m, Functor (t m)) => (a -> m (Maybe b)) -> t m a -> t m b Source #
Deleting Elements
Deleting elements is a special case of de-interleaving streams.
deleteBy :: (IsStream t, Monad m) => (a -> a -> Bool) -> a -> t m a -> t m a Source #
Deletes the first occurrence of the element in the stream that satisfies the given equality predicate.
> S.toList $ S.deleteBy (==) 3 $ S.fromList [1,3,3,5] [1,3,5]
Since: 0.6.0
uniq :: (Eq a, IsStream t, Monad m) => t m a -> t m a Source #
Drop repeated elements that are adjacent to each other.
Since: 0.6.0
Inserting Elements
Inserting elements is a special case of interleaving/merging streams.
intersperseM :: (IsStream t, MonadAsync m) => m a -> t m a -> t m a Source #
Generate a stream by inserting the result of a monadic action between consecutive elements of the given stream. Note that the monadic action is performed after the stream action before which its result is inserted.
> S.toList $ S.intersperseM (return ',') $ S.fromList "hello" "h,e,l,l,o"
Since: 0.5.0
intersperse :: (IsStream t, MonadAsync m) => a -> t m a -> t m a Source #
Generate a stream by inserting a given element between consecutive elements of the given stream.
> S.toList $ S.intersperse ',' $ S.fromList "hello" "h,e,l,l,o"
Since: 0.7.0
Indexing
Indexing can be considered as a special type of zipping where we zip a stream with an index stream.
indexed :: (IsStream t, Monad m) => t m a -> t m (Int, a) Source #
indexed = S.postscanl' (\(i, _) x -> (i + 1, x)) (-1,undefined) indexed = S.zipWith (,) (S.enumerateFrom 0)
Pair each element in a stream with its index, starting from index 0.
> S.toList $ S.indexed $ S.fromList "hello" [(0,h
),(1,e
),(2,l
),(3,l
),(4,o
)]
Since: 0.6.0
indexedR :: (IsStream t, Monad m) => Int -> t m a -> t m (Int, a) Source #
indexedR n = S.postscanl' (\(i, _) x -> (i - 1, x)) (n + 1,undefined) indexedR n = S.zipWith (,) (S.enumerateFromThen n (n - 1))
Pair each element in a stream with its index, starting from the
given index n
and counting down.
> S.toList $ S.indexedR 10 $ S.fromList "hello" [(10,h
),(9,e
),(8,l
),(7,l
),(6,o
)]
Since: 0.6.0
Reordering Elements
reverse :: (IsStream t, Monad m) => t m a -> t m a Source #
Returns the elements of the stream in reverse order. The stream must be finite. Note that this necessarily buffers the entire stream in memory.
Since 0.7.0 (Monad m constraint)
Since: 0.1.1
Trimming
Take or remove elements from one or both ends of a stream.
take :: (IsStream t, Monad m) => Int -> t m a -> t m a Source #
Take first n
elements from the stream and discard the rest.
Since: 0.1.0
takeWhile :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a Source #
End the stream as soon as the predicate fails on an element.
Since: 0.1.0
takeWhileM :: (IsStream t, Monad m) => (a -> m Bool) -> t m a -> t m a Source #
Same as takeWhile
but with a monadic predicate.
Since: 0.4.0
drop :: (IsStream t, Monad m) => Int -> t m a -> t m a Source #
Discard first n
elements from the stream and take the rest.
Since: 0.1.0
dropWhile :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m a Source #
Drop elements in the stream as long as the predicate succeeds and then take the rest of the stream.
Since: 0.1.0
dropWhileM :: (IsStream t, Monad m) => (a -> m Bool) -> t m a -> t m a Source #
Same as dropWhile
but with a monadic predicate.
Since: 0.4.0
Slicing
Streams can be sliced into segments in space or in time. We use the
term chunk
to refer to a spatial length of the stream (spatial window)
and the term session
to refer to a length in time (time window).
chunksOf :: (IsStream t, Monad m) => Int -> Fold m a b -> t m a -> t m b Source #
Group the input stream into groups of n
elements each and then fold each
group using the provided fold function.
> S.toList $ S.chunksOf 2 FL.sum (S.enumerateFromTo 1 10) [3,7,11,15,19]
This can be considered as an n-fold version of ltake
where we apply
ltake
repeatedly on the leftover stream until the stream exhausts.
Since: 0.7.0
intervalsOf :: (IsStream t, MonadAsync m) => Double -> Fold m a b -> t m a -> t m b Source #
Group the input stream into windows of n
second each and then fold each
group using the provided fold function.
Since: 0.7.0
Searching
Finding the presence or location of an element, a sequence of elements or another stream within a stream.
findIndices :: (IsStream t, Monad m) => (a -> Bool) -> t m a -> t m Int Source #
Find all the indices where the element in the stream satisfies the given predicate.
Since: 0.5.0
elemIndices :: (IsStream t, Eq a, Monad m) => a -> t m a -> t m Int Source #
Find all the indices where the value of the element in the stream is equal to the given value.
Since: 0.5.0
Splitting
In general we can express splitting in terms of parser combinators. These are some common use functions for convenience and efficiency. While parsers can fail these functions are designed to transform a stream without failure with a predefined behavior for all cases.
In general, there are three possible ways of combining stream segments
with a separator. The separator could be prefixed to each segment,
suffixed to each segment, or it could be infixed between segments.
intersperse
and intercalate
operations are examples of infixed
combining whereas unlines
is an example of suffixed combining. When we
split a stream with separators we can split in three different ways,
each being an opposite of the three ways of combining.
Splitting may keep the separator or drop it. Depending on how we split,
the separator may be kept attached to the stream segments in prefix or
suffix position or as a separate element in infix position. Combinators
like splitOn
that use On
in their names drop the separator and
combinators that use With
in their names keep the separator. When a
segment is missing it is considered as empty, therefore, we never
encounter an error in parsing.
splitOn :: (IsStream t, Monad m) => (a -> Bool) -> Fold m a b -> t m a -> t m b Source #
Split on an infixed separator element, dropping the separator. Splits the
stream on separator elements determined by the supplied predicate, separator
is considered as infixed between two segments, if one side of the separator
is missing then it is parsed as an empty stream. The supplied Fold
is
applied on the split segments. With -
representing non-separator elements
and .
as separator, splitOn
splits as follows:
"--.--" => "--" "--" "--." => "--" "" ".--" => "" "--"
splitOn (== x)
is an inverse of intercalate (S.yield x)
Let's use the following definition for illustration:
splitOn' p xs = S.toList $ S.splitOn p (FL.toList) (S.fromList xs)
>>>
splitOn' (== '.') ""
[""]
>>>
splitOn' (== '.') "."
["",""]
>>>
splitOn' (== '.') ".a"
> ["","a"]
>>>
splitOn' (== '.') "a."
> ["a",""]
>>>
splitOn' (== '.') "a.b"
> ["a","b"]
>>>
splitOn' (== '.') "a..b"
> ["a","","b"]
Since: 0.7.0
splitOnSuffix :: (IsStream t, Monad m) => (a -> Bool) -> Fold m a b -> t m a -> t m b Source #
Like splitOn
but the separator is considered as suffixed to the segments
in the stream. A missing suffix at the end is allowed. A separator at the
beginning is parsed as empty segment. With -
representing elements and
.
as separator, splitOnSuffix
splits as follows:
"--.--." => "--" "--" "--.--" => "--" "--" ".--." => "" "--"
splitOnSuffix' p xs = S.toList $ S.splitSuffixBy p (FL.toList) (S.fromList xs)
>>>
splitOnSuffix' (== '.') ""
[]
>>>
splitOnSuffix' (== '.') "."
[""]
>>>
splitOnSuffix' (== '.') "a"
["a"]
>>>
splitOnSuffix' (== '.') ".a"
> ["","a"]
>>>
splitOnSuffix' (== '.') "a."
> ["a"]
>>>
splitOnSuffix' (== '.') "a.b"
> ["a","b"]
>>>
splitOnSuffix' (== '.') "a.b."
> ["a","b"]
>>>
splitOnSuffix' (== '.') "a..b.."
> ["a","","b",""]
lines = splitOnSuffix (== '\n')
Since: 0.7.0
splitWithSuffix :: (IsStream t, Monad m) => (a -> Bool) -> Fold m a b -> t m a -> t m b Source #
Like splitOnSuffix
but keeps the suffix attached to the resulting
splits.
splitWithSuffix' p xs = S.toList $ S.splitWithSuffix p (FL.toList) (S.fromList xs)
>>>
splitWithSuffix' (== '.') ""
[]
>>>
splitWithSuffix' (== '.') "."
["."]
>>>
splitWithSuffix' (== '.') "a"
["a"]
>>>
splitWithSuffix' (== '.') ".a"
> [".","a"]
>>>
splitWithSuffix' (== '.') "a."
> ["a."]
>>>
splitWithSuffix' (== '.') "a.b"
> ["a.","b"]
>>>
splitWithSuffix' (== '.') "a.b."
> ["a.","b."]
>>>
splitWithSuffix' (== '.') "a..b.."
> ["a.",".","b.","."]
Since: 0.7.0
wordsBy :: (IsStream t, Monad m) => (a -> Bool) -> Fold m a b -> t m a -> t m b Source #
Like splitOn
after stripping leading, trailing, and repeated separators.
Therefore, ".a..b."
with .
as the separator would be parsed as
["a","b"]
. In other words, its like parsing words from whitespace
separated text.
wordsBy' p xs = S.toList $ S.wordsBy p (FL.toList) (S.fromList xs)
>>>
wordsBy' (== ',') ""
> []
>>>
wordsBy' (== ',') ","
> []
>>>
wordsBy' (== ',') ",a,,b,"
> ["a","b"]
words = wordsBy isSpace
Since: 0.7.0
Grouping
Splitting a stream by combining multiple contiguous elements into groups using some criterion.
groups :: (IsStream t, Monad m, Eq a) => Fold m a b -> t m a -> t m b Source #
groups = groupsBy (==) groups = groupsByRolling (==)
Groups contiguous spans of equal elements together in individual groups.
>>>
S.toList $ S.groups FL.toList $ S.fromList [1,1,2,2]
> [[1,1],[2,2]]
Since: 0.7.0
groupsBy :: (IsStream t, Monad m) => (a -> a -> Bool) -> Fold m a b -> t m a -> t m b Source #
groupsBy cmp f $ S.fromList [a,b,c,...]
assigns the element a
to the
first group, if a `cmp` b
is True
then b
is also assigned to the same
group. If a `cmp` c
is True
then c
is also assigned to the same
group and so on. When the comparison fails a new group is started. Each
group is folded using the fold f
and the result of the fold is emitted in
the output stream.
>>>
S.toList $ S.groupsBy (>) FL.toList $ S.fromList [1,3,7,0,2,5]
> [[1,3,7],[0,2,5]]
Since: 0.7.0
groupsByRolling :: (IsStream t, Monad m) => (a -> a -> Bool) -> Fold m a b -> t m a -> t m b Source #
Unlike groupsBy
this function performs a rolling comparison of two
successive elements in the input stream. groupsByRolling cmp f $ S.fromList
[a,b,c,...]
assigns the element a
to the first group, if a `cmp` b
is
True
then b
is also assigned to the same group. If b `cmp` c
is
True
then c
is also assigned to the same group and so on. When the
comparison fails a new group is started. Each group is folded using the fold
f
.
>>>
S.toList $ S.groupsByRolling (\a b -> a + 1 == b) FL.toList $ S.fromList [1,2,3,7,8,9]
> [[1,2,3],[7,8,9]]
Since: 0.7.0
Combining Streams
New streams can be constructed by appending, merging or zipping existing streams.
Appending
Streams form a Semigroup
and a Monoid
under the append
operation. Appending can be considered as a generalization of the cons
operation to consing a stream to a stream.
-------Stream m a------|-------Stream m a------|=>----Stream m a---
>> S.toList $ S.fromList [1,2] <> S.fromList [3,4] [1,2,3,4] >> S.toList $ fold $ [S.fromList [1,2], S.fromList [3,4]] [1,2,3,4]
Merging
Streams form a commutative semigroup under the merge operation. Merging can be considered as a generalization of inserting an element in a stream to interleaving a stream with another stream.
-------Stream m a------| |=>----Stream m a--- -------Stream m a------|
mergeBy :: (IsStream t, Monad m) => (a -> a -> Ordering) -> t m a -> t m a -> t m a Source #
Merge two streams using a comparison function. The head elements of both the streams are compared and the smaller of the two elements is emitted, if both elements are equal then the element from the first stream is used first.
If the streams are sorted in ascending order, the resulting stream would also remain sorted in ascending order.
> S.toList $ S.mergeBy compare (S.fromList [1,3,5]) (S.fromList [2,4,6,8]) [1,2,3,4,5,6,8]
Since: 0.6.0
mergeByM :: (IsStream t, Monad m) => (a -> a -> m Ordering) -> t m a -> t m a -> t m a Source #
Like mergeBy
but with a monadic comparison function.
Merge two streams randomly:
> randomly _ _ = randomIO >>= x -> return $ if x then LT else GT > S.toList $ S.mergeByM randomly (S.fromList [1,1,1,1]) (S.fromList [2,2,2,2]) [2,1,2,2,2,1,1,1]
Merge two streams in a proportion of 2:1:
proportionately m n = do ref <- newIORef $ cycle $ concat [replicate m LT, replicate n GT] return $ \_ _ -> do r <- readIORef ref writeIORef ref $ tail r return $ head r main = do f <- proportionately 2 1 xs <- S.toList $ S.mergeByM f (S.fromList [1,1,1,1,1,1]) (S.fromList [2,2,2]) print xs
[1,1,2,1,1,2,1,1,2]
Since: 0.6.0
mergeAsyncBy :: (IsStream t, MonadAsync m) => (a -> a -> Ordering) -> t m a -> t m a -> t m a Source #
Like mergeBy
but merges concurrently (i.e. both the elements being
merged are generated concurrently).
Since: 0.6.0
mergeAsyncByM :: (IsStream t, MonadAsync m) => (a -> a -> m Ordering) -> t m a -> t m a -> t m a Source #
Like mergeByM
but merges concurrently (i.e. both the elements being
merged are generated concurrently).
Since: 0.6.0
Zipping
-------Stream m a------| |=>----Stream m c--- -------Stream m b------|
zipWith :: (IsStream t, Monad m) => (a -> b -> c) -> t m a -> t m b -> t m c Source #
Zip two streams serially using a pure zipping function.
> S.toList $ S.zipWith (+) (S.fromList [1,2,3]) (S.fromList [4,5,6]) [5,7,9]
Since: 0.1.0
zipWithM :: (IsStream t, Monad m) => (a -> b -> m c) -> t m a -> t m b -> t m c Source #
Like zipWith
but using a monadic zipping function.
Since: 0.4.0
zipAsyncWith :: (IsStream t, MonadAsync m) => (a -> b -> c) -> t m a -> t m b -> t m c Source #
Like zipWith
but zips concurrently i.e. both the streams being zipped
are generated concurrently.
Since: 0.1.0
zipAsyncWithM :: (IsStream t, MonadAsync m) => (a -> b -> m c) -> t m a -> t m b -> t m c Source #
Like zipWithM
but zips concurrently i.e. both the streams being zipped
are generated concurrently.
Since: 0.4.0
Folding Streams of Streams
Stream operations like map and filter represent loop processing in
imperative programming terms. Similarly, the imperative concept of
nested loops are represented by streams of streams. The concatMap
operation represents nested looping.
A concatMap
operation loops over the input stream and then for each
element of the input stream generates another stream and then loops over
that inner stream as well producing effects and generating a single
output stream.
The Monad
instances of different stream types provide a more
convenient way of writing nested loops. Note that the monad bind
operation is just flip concatMap
.
One dimension loops are just a special case of nested loops. For
example, concatMap
can degenerate to a simple map operation:
map f m = S.concatMap (\x -> S.yield (f x)) m
Similarly, concatMap
can perform filtering by mapping an element to a
nil
stream:
filter p m = S.concatMap (\x -> if p x then S.yield x else S.nil) m
concatMapWith :: IsStream t => (forall c. t m c -> t m c -> t m c) -> (a -> t m b) -> t m a -> t m b Source #
concatMapWith merge map stream
is a two dimensional looping combinator.
The first argument specifies a merge or concat function that is used to
merge the streams generated by applying the second argument i.e. the map
function to each element of the input stream. The concat function could be
serial
, parallel
, async
, ahead
or any other zip or merge function
and the second argument could be any stream generation function using a
seed.
Compare foldMapWith
Since: 0.7.0
concatMap :: (IsStream t, Monad m) => (a -> t m b) -> t m a -> t m b Source #
Map a stream producing function on each element of the stream and then flatten the results into a single stream.
concatMap =concatMapWith
serial
concatMap f =concatMapM
(return . f)
Since: 0.6.0
concatMapM :: (IsStream t, Monad m) => (a -> m (t m b)) -> t m a -> t m b Source #
Map a stream producing monadic function on each element of the stream
and then flatten the results into a single stream. Since the stream
generation function is monadic, unlike concatMap
, it can produce an
effect at the beginning of each iteration of the inner loop.
Since: 0.6.0
Exceptions
before :: (IsStream t, Monad m) => m b -> t m a -> t m a Source #
Run a side effect before the stream yields its first element.
Since: 0.7.0
after :: (IsStream t, Monad m) => m b -> t m a -> t m a Source #
Run a side effect whenever the stream stops normally.
Prefer afterIO
over this as the after
action in this combinator is not
executed if the unfold is partially evaluated lazily and then garbage
collected.
Since: 0.7.0
bracket :: (IsStream t, MonadCatch m) => m b -> (b -> m c) -> (b -> t m a) -> t m a Source #
Run the first action before the stream starts and remember its output, generate a stream using the output, run the second action using the remembered value as an argument whenever the stream ends normally or due to an exception.
Prefer bracketIO
over this as the after
action in this combinator is not
executed if the unfold is partially evaluated lazily and then garbage
collected.
Since: 0.7.0
onException :: (IsStream t, MonadCatch m) => m b -> t m a -> t m a Source #
Run a side effect whenever the stream aborts due to an exception.
Since: 0.7.0
finally :: (IsStream t, MonadCatch m) => m b -> t m a -> t m a Source #
Run a side effect whenever the stream stops normally or aborts due to an exception.
Prefer finallyIO
over this as the after
action in this combinator is not
executed if the unfold is partially evaluated lazily and then garbage
collected.
Since: 0.7.0
handle :: (IsStream t, MonadCatch m, Exception e) => (e -> t m a) -> t m a -> t m a Source #
When evaluating a stream if an exception occurs, stream evaluation aborts and the specified exception handler is run with the exception as argument.
Since: 0.7.0
Deprecated
once :: (Monad m, IsStream t) => m a -> t m a Source #
Deprecated: Please use yieldM instead.
Same as yieldM
Since: 0.2.0
each :: (IsStream t, Foldable f) => f a -> t m a Source #
Deprecated: Please use fromFoldable instead.
Same as fromFoldable
.
Since: 0.1.0
scanx :: (IsStream t, Monad m) => (x -> a -> x) -> x -> (x -> b) -> t m a -> t m b Source #
Deprecated: Please use scanl followed by map instead.
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 (Monad m constraint)
Since 0.2.0
foldx :: Monad m => (x -> a -> x) -> x -> (x -> b) -> SerialT m a -> m b Source #
Deprecated: Please use foldl' followed by fmap instead.
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.2.0
foldxM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> SerialT m a -> m b Source #
Deprecated: Please use foldlM' followed by fmap instead.
Like foldx
, but with a monadic step function.
Since: 0.2.0
foldr1 :: Monad m => (a -> a -> a) -> SerialT m a -> m (Maybe a) Source #
Deprecated: Use foldrM instead.
Lazy right fold for non-empty streams, using first element as the starting
value. Returns Nothing
if the stream is empty.
Since: 0.5.0
runStream :: Monad m => SerialT m a -> m () Source #
Deprecated: Please use "drain" instead
Run a stream, discarding the results. By default it interprets the stream
as SerialT
, to run other types of streams use the type adapting
combinators for example runStream .
.asyncly
Since: 0.2.0
runN :: Monad m => Int -> SerialT m a -> m () Source #
Deprecated: Please use "drainN" instead
runN n = runStream . take n
Run maximum up to n
iterations of a stream.
Since: 0.6.0
runWhile :: Monad m => (a -> Bool) -> SerialT m a -> m () Source #
Deprecated: Please use "drainWhile" instead
runWhile p = runStream . takeWhile p
Run a stream as long as the predicate holds true.
Since: 0.6.0