Copyright | (c) 2019 Composewell Technologies |
---|---|
License | BSD3 |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Fold
type represents an effectful action that consumes a value from an
input stream and combines it with a single final value often called an
accumulator, returning the resulting output accumulator. Values from a
stream can be pushed to the fold and consumed one at a time. It can also
be called a consumer of stream or a sink. It is a data representation of
the standard foldl'
function. A Fold
can be turned
into an effect (m b
) using fold
by supplying it the
input stream.
Using this representation multiple folds can be combined efficiently using combinators; a stream can then be supplied to the combined fold and it would distribute the input to constituent folds according to the composition. For example, an applicative composition distributes the same input to the constituent folds and then combines the resulting fold outputs. Similarly, a partitioning combinator divides the input among constituent folds.
Performance Notes
Fold
representation is more efficient than using streams when splitting
streams. Fold m a b
can be considered roughly equivalent to a fold action
m b -> t m a -> m b
(where t
is a stream type and m
is a Monad
).
Instead of using a Fold
type one could just use a fold action of the shape
m b -> t m a -> m b
for folding streams. However, multiple such actions
cannot be composed into a single fold function in an efficient manner.
Using the Fold
type we can efficiently split the stream across mutliple
folds because it allows the compiler to perform stream fusion optimizations.
On the other hand, transformation operations (e.g. map
)
on stream types can be as efficient as transformations on Fold
(e.g.
lmap
).
Programmer Notes
import qualified Streamly.Data.Fold as FL
More, not yet exposed, fold combinators can be found in Streamly.Internal.Data.Fold.
Synopsis
- data Fold m a b
- drain :: Monad m => Fold m a ()
- drainBy :: Monad m => (a -> m b) -> Fold m a ()
- last :: Monad m => Fold m a (Maybe a)
- length :: Monad m => Fold m a Int
- sum :: (Monad m, Num a) => Fold m a a
- product :: (Monad m, Num a) => Fold m a a
- maximumBy :: Monad m => (a -> a -> Ordering) -> Fold m a (Maybe a)
- maximum :: (Monad m, Ord a) => Fold m a (Maybe a)
- minimumBy :: Monad m => (a -> a -> Ordering) -> Fold m a (Maybe a)
- minimum :: (Monad m, Ord a) => Fold m a (Maybe a)
- mean :: (Monad m, Fractional a) => Fold m a a
- variance :: (Monad m, Fractional a) => Fold m a a
- stdDev :: (Monad m, Floating a) => Fold m a a
- mconcat :: (Monad m, Monoid a) => Fold m a a
- foldMap :: (Monad m, Monoid b) => (a -> b) -> Fold m a b
- foldMapM :: (Monad m, Monoid b) => (a -> m b) -> Fold m a b
- toList :: Monad m => Fold m a [a]
- index :: Monad m => Int -> Fold m a (Maybe a)
- head :: Monad m => Fold m a (Maybe a)
- find :: Monad m => (a -> Bool) -> Fold m a (Maybe a)
- lookup :: (Eq a, Monad m) => a -> Fold m (a, b) (Maybe b)
- findIndex :: Monad m => (a -> Bool) -> Fold m a (Maybe Int)
- elemIndex :: (Eq a, Monad m) => a -> Fold m a (Maybe Int)
- null :: Monad m => Fold m a Bool
- elem :: (Eq a, Monad m) => a -> Fold m a Bool
- notElem :: (Eq a, Monad m) => a -> Fold m a Bool
- all :: Monad m => (a -> Bool) -> Fold m a Bool
- any :: Monad m => (a -> Bool) -> Fold m a Bool
- and :: Monad m => Fold m Bool Bool
- or :: Monad m => Fold m Bool Bool
- sequence :: Monad m => Fold m a (m b) -> Fold m a b
- mapM :: Monad m => (b -> m c) -> Fold m a b -> Fold m a c
- tee :: Monad m => Fold m a b -> Fold m a c -> Fold m a (b, c)
- distribute :: Monad m => [Fold m a b] -> Fold m a [b]
- partition :: Monad m => Fold m b x -> Fold m c y -> Fold m (Either b c) (x, y)
- unzip :: Monad m => Fold m a x -> Fold m b y -> Fold m (a, b) (x, y)
Fold Type
A Fold
can be run over a stream using the fold
combinator:
>>>
S.fold FL.sum (S.enumerateFromTo 1 100)
5050
Represents a left fold over an input stream of values of type a
to a
single value of type b
in Monad
m
.
The fold uses an intermediate state s
as accumulator. The step
function
updates the state and returns the new updated state. When the fold is done
the final result of the fold is extracted from the intermediate state
representation using the extract
function.
Since: 0.7.0
Instances
Applicative m => Functor (Fold m a) Source # | Maps a function on the output of the fold (the type |
Applicative m => Applicative (Fold m a) Source # | The fold resulting from |
(Monad m, Floating b) => Floating (Fold m a b) Source # | Combines the fold outputs using their |
Defined in Streamly.Internal.Data.Fold.Types exp :: Fold m a b -> Fold m a b # log :: Fold m a b -> Fold m a b # sqrt :: Fold m a b -> Fold m a b # (**) :: Fold m a b -> Fold m a b -> Fold m a b # logBase :: Fold m a b -> Fold m a b -> Fold m a b # sin :: Fold m a b -> Fold m a b # cos :: Fold m a b -> Fold m a b # tan :: Fold m a b -> Fold m a b # asin :: Fold m a b -> Fold m a b # acos :: Fold m a b -> Fold m a b # atan :: Fold m a b -> Fold m a b # sinh :: Fold m a b -> Fold m a b # cosh :: Fold m a b -> Fold m a b # tanh :: Fold m a b -> Fold m a b # asinh :: Fold m a b -> Fold m a b # acosh :: Fold m a b -> Fold m a b # atanh :: Fold m a b -> Fold m a b # log1p :: Fold m a b -> Fold m a b # expm1 :: Fold m a b -> Fold m a b # | |
(Monad m, Fractional b) => Fractional (Fold m a b) Source # | Combines the fold outputs (type |
(Monad m, Num b) => Num (Fold m a b) Source # | Combines the fold outputs (type |
Defined in Streamly.Internal.Data.Fold.Types | |
(Semigroup b, Monad m) => Semigroup (Fold m a b) Source # | Combines the outputs of the folds (the type |
(Semigroup b, Monoid b, Monad m) => Monoid (Fold m a b) Source # | Combines the outputs of the folds (the type |
Full Folds
drain :: Monad m => Fold m a () Source #
A fold that drains all its input, running the effects and discarding the results.
Since: 0.7.0
drainBy :: Monad m => (a -> m b) -> Fold m a () Source #
drainBy f = lmapM f drain
Drain all input after passing it through a monadic function. This is the dual of mapM_ on stream producers.
Since: 0.7.0
last :: Monad m => Fold m a (Maybe a) Source #
Extract the last element of the input stream, if any.
Since: 0.7.0
sum :: (Monad m, Num a) => Fold m a a Source #
Determine the sum of all elements of a stream of numbers. Returns additive
identity (0
) when the stream is empty. Note that this is not numerically
stable for floating point numbers.
Since: 0.7.0
product :: (Monad m, Num a) => Fold m a a Source #
Determine the product of all elements of a stream of numbers. Returns
multiplicative identity (1
) when the stream is empty.
Since: 0.7.0
maximumBy :: Monad m => (a -> a -> Ordering) -> Fold m a (Maybe a) Source #
Determine the maximum element in a stream using the supplied comparison function.
Since: 0.7.0
minimumBy :: Monad m => (a -> a -> Ordering) -> Fold m a (Maybe a) Source #
Computes the minimum element with respect to the given comparison function
Since: 0.7.0
minimum :: (Monad m, Ord a) => Fold m a (Maybe a) Source #
Determine the minimum element in a stream using the supplied comparison function.
Since: 0.7.0
mean :: (Monad m, Fractional a) => Fold m a a Source #
Compute a numerically stable arithmetic mean of all elements in the input stream.
Since: 0.7.0
variance :: (Monad m, Fractional a) => Fold m a a Source #
Compute a numerically stable (population) variance over all elements in the input stream.
Since: 0.7.0
stdDev :: (Monad m, Floating a) => Fold m a a Source #
Compute a numerically stable (population) standard deviation over all elements in the input stream.
Since: 0.7.0
Full Folds (Monoidal)
Full Folds (To Containers)
Avoid using these folds in scalable or performance critical applications, they buffer all the input in GC memory which can be detrimental to performance if the input is large.
toList :: Monad m => Fold m a [a] Source #
Folds the input stream to a list.
Warning! working on large lists accumulated as buffers in memory could be very inefficient, consider using Streamly.Array instead.
Since: 0.7.0
Partial Folds
index :: Monad m => Int -> Fold m a (Maybe a) Source #
Lookup the element at the given index.
Since: 0.7.0
head :: Monad m => Fold m a (Maybe a) Source #
Extract the first element of the stream, if any.
Since: 0.7.0
find :: Monad m => (a -> Bool) -> Fold m a (Maybe a) Source #
Returns the first element that satisfies the given predicate.
Since: 0.7.0
lookup :: (Eq a, Monad m) => a -> Fold m (a, b) (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
.
Since: 0.7.0
findIndex :: Monad m => (a -> Bool) -> Fold m a (Maybe Int) Source #
Returns the first index that satisfies the given predicate.
Since: 0.7.0
elemIndex :: (Eq a, Monad m) => a -> Fold m a (Maybe Int) Source #
Returns the first index where a given value is found in the stream.
Since: 0.7.0
elem :: (Eq a, Monad m) => a -> Fold m a Bool Source #
Return True
if the given element is present in the stream.
Since: 0.7.0
notElem :: (Eq a, Monad m) => a -> Fold m a Bool Source #
Returns True
if the given element is not present in the stream.
Since: 0.7.0
any :: Monad m => (a -> Bool) -> Fold m a Bool Source #
any p = lmap p or
| Returns True
if any of the elements of a stream satisfies a predicate.
Since: 0.7.0
Transformations
Unlike stream producer types (e.g. SerialT m a
) which have only
output side, folds have an input side as well as an output side. In the
type Fold m a b
, the input type is a
and the output type is b
.
Transformations can be applied either on the input side or on the output
side. The Functor
instance of a fold maps on the output of the fold:
>>>
S.fold (fmap show FL.sum) (S.enumerateFromTo 1 100)
"5050"
However, the input side or contravariant transformations are more
interesting for folds. The following sections describe the input
transformation operations on a fold. The names of the operations are
consistent with their covariant counterparts in Streamly.Prelude, the
only difference is that they are prefixed with l
which stands for
left
assuming left side is the input side, notice that in Fold m a b
the type variable a
is on the left side.
Covariant Operations
sequence :: Monad m => Fold m a (m b) -> Fold m a b Source #
Flatten the monadic output of a fold to pure output.
Since: 0.7.0
mapM :: Monad m => (b -> m c) -> Fold m a b -> Fold m a c Source #
Map a monadic function on the output of a fold.
Since: 0.7.0
Distributing
The Applicative
instance of a distributing Fold
distributes one copy
of the stream to each fold and combines the results using a function.
|-------Fold m a b--------| ---stream m a---| |---m (b,c,...) |-------Fold m a c--------| | | ...
To compute the average of numbers in a stream without going throught he stream twice:
>>>
let avg = (/) <$> FL.sum <*> fmap fromIntegral FL.length
>>>
S.fold avg (S.enumerateFromTo 1.0 100.0)
50.5
The Semigroup
and Monoid
instances of a distributing fold distribute
the input to both the folds and combines the outputs using Monoid or
Semigroup instances of the output types:
>>>
import Data.Monoid (Sum)
>>>
S.fold (FL.head <> FL.last) (fmap Sum $ S.enumerateFromTo 1.0 100.0)
Just (Sum {getSum = 101.0})
The Num
, Floating
, and Fractional
instances work in the same way.
tee :: Monad m => Fold m a b -> Fold m a c -> Fold m a (b, c) Source #
Distribute one copy of the stream to each fold and zip the results.
|-------Fold m a b--------| ---stream m a---| |---m (b,c) |-------Fold m a c--------|
>>>
S.fold (FL.tee FL.sum FL.length) (S.enumerateFromTo 1.0 100.0)
(5050.0,100)
Since: 0.7.0
distribute :: Monad m => [Fold m a b] -> Fold m a [b] Source #
Distribute one copy of the stream to each fold and collect the results in a container.
|-------Fold m a b--------| ---stream m a---| |---m [b] |-------Fold m a b--------| | | ...
>>>
S.fold (FL.distribute [FL.sum, FL.length]) (S.enumerateFromTo 1 5)
[15,5]
This is the consumer side dual of the producer side sequence
operation.
Since: 0.7.0
Partitioning
Direct items in the input stream to different folds using a binary fold selector.
Unzipping
unzip :: Monad m => Fold m a x -> Fold m b y -> Fold m (a, b) (x, y) Source #
Send the elements of tuples in a stream of tuples through two different folds.
|-------Fold m a x--------| ---------stream of (a,b)--| |----m (x,y) |-------Fold m b y--------|
This is the consumer side dual of the producer side zip
operation.
Since: 0.7.0