foldl-1.0.10: Composable, streaming, and efficient left folds

Safe HaskellTrustworthy
LanguageHaskell98

Control.Foldl

Contents

Description

This module provides efficient and streaming left folds that you can combine using Applicative style.

Import this module qualified to avoid clashing with the Prelude:

>>> import qualified Control.Foldl as L

Use fold to apply a Fold to a list:

>>> L.fold L.sum [1..100]
5050

Folds are Applicatives, so you can combine them using Applicative combinators:

>>> import Control.Applicative
>>> let average = (/) <$> L.sum <*> L.genericLength

These combined folds will still traverse the list only once, streaming efficiently over the list in constant space without space leaks:

>>> L.fold average [1..10000000]
5000000.5
>>> L.fold ((,) <$> L.minimum <*> L.maximum) [1..10000000]
(Just 1,Just 10000000)

Synopsis

Fold Types

data Fold a b Source

Efficient representation of a left fold that preserves the fold's step function, initial accumulator, and extraction function

This allows the Applicative instance to assemble derived folds that traverse the container only once

A 'Fold a b' processes elements of type a and results in a value of type b.

Constructors

forall x . Fold (x -> a -> x) x (x -> b)

Fold step initial extract

Instances

Functor (Fold a) 
Applicative (Fold a) 
Floating b => Floating (Fold a b) 
Fractional b => Fractional (Fold a b) 
Num b => Num (Fold a b) 
Monoid b => Monoid (Fold a b) 

data FoldM m a b Source

Like Fold, but monadic.

A 'FoldM m a b' processes elements of type a and results in a monadic value of type m b.

Constructors

forall x . FoldM (x -> a -> m x) (m x) (x -> m b)

FoldM step initial extract

Instances

Monad m => Functor (FoldM m a) 
Monad m => Applicative (FoldM m a) 
(Monad m, Floating b) => Floating (FoldM m a b) 
(Monad m, Fractional b) => Fractional (FoldM m a b) 
(Monad m, Num b) => Num (FoldM m a b) 
(Monoid b, Monad m) => Monoid (FoldM m a b) 

Folding

fold :: Foldable f => Fold a b -> f a -> b Source

Apply a strict left Fold to a Foldable container

foldM :: (Foldable f, Monad m) => FoldM m a b -> f a -> m b Source

Like fold, but monadic

scan :: Fold a b -> [a] -> [b] Source

Convert a strict left Fold into a scan

Folds

mconcat :: Monoid a => Fold a a Source

Fold all values within a container using mappend and mempty

foldMap :: Monoid w => (a -> w) -> (w -> b) -> Fold a b Source

Convert a "foldMap" to a Fold

head :: Fold a (Maybe a) Source

Get the first element of a container or return Nothing if the container is empty

last :: Fold a (Maybe a) Source

Get the last element of a container or return Nothing if the container is empty

lastDef :: a -> Fold a a Source

Get the last element of a container or return a default value if the container is empty

null :: Fold a Bool Source

Returns True if the container is empty, False otherwise

length :: Fold a Int Source

Return the length of the container

and :: Fold Bool Bool Source

Returns True if all elements are True, False otherwise

or :: Fold Bool Bool Source

Returns True if any element is True, False otherwise

all :: (a -> Bool) -> Fold a Bool Source

(all predicate) returns True if all elements satisfy the predicate, False otherwise

any :: (a -> Bool) -> Fold a Bool Source

(any predicate) returns True if any element satisfies the predicate, False otherwise

sum :: Num a => Fold a a Source

Computes the sum of all elements

product :: Num a => Fold a a Source

Computes the product all elements

maximum :: Ord a => Fold a (Maybe a) Source

Computes the maximum element

minimum :: Ord a => Fold a (Maybe a) Source

Computes the minimum element

elem :: Eq a => a -> Fold a Bool Source

(elem a) returns True if the container has an element equal to a, False otherwise

notElem :: Eq a => a -> Fold a Bool Source

(notElem a) returns False if the container has an element equal to a, True otherwise

find :: (a -> Bool) -> Fold a (Maybe a) Source

(find predicate) returns the first element that satisfies the predicate or Nothing if no element satisfies the predicate

index :: Int -> Fold a (Maybe a) Source

(index n) returns the nth element of the container, or Nothing if the container has an insufficient number of elements

elemIndex :: Eq a => a -> Fold a (Maybe Int) Source

(elemIndex a) returns the index of the first element that equals a, or Nothing if no element matches

findIndex :: (a -> Bool) -> Fold a (Maybe Int) Source

(findIndex predicate) returns the index of the first element that satisfies the predicate, or Nothing if no element satisfies the predicate

random :: FoldM IO a (Maybe a) Source

Pick a random element, using reservoir sampling

Generic Folds

genericLength :: Num b => Fold a b Source

Like length, except with a more general Num return value

genericIndex :: Integral i => i -> Fold a (Maybe a) Source

Like index, except with a more general Integral argument

Container folds

list :: Fold a [a] Source

Fold all values into a list

revList :: Fold a [a] Source

Fold all values into a list, in reverse order

nub :: Ord a => Fold a [a] Source

O(n log n). Fold values into a list with duplicates removed, while preserving their first occurrences

eqNub :: Eq a => Fold a [a] Source

O(n^2). Fold values into a list with duplicates removed, while preserving their first occurrences

set :: Ord a => Fold a (Set a) Source

Fold values into a set

vector :: (PrimMonad m, Vector v a) => FoldM m a (v a) Source

Fold all values into a vector

Utilities

purely and impurely allow you to write folds compatible with the foldl library without incurring a foldl dependency. Write your fold to accept three parameters corresponding to the step function, initial accumulator, and extraction function and then users can upgrade your function to accept a Fold or FoldM using the purely or impurely combinators.

For example, the pipes library implements a foldM function in Pipes.Prelude with the following type:

foldM
    :: Monad m
    => (x -> a -> m x) -> m x -> (x -> m b) -> Producer a m () -> m b

foldM is set up so that you can wrap it with impurely to accept a FoldM instead:

impurely foldM :: Monad m => FoldM m a b -> Producer a m () -> m b

purely :: (forall x. (x -> a -> x) -> x -> (x -> b) -> r) -> Fold a b -> r Source

Upgrade a fold to accept the Fold type

impurely :: Monad m => (forall x. (x -> a -> m x) -> m x -> (x -> m b) -> r) -> FoldM m a b -> r Source

Upgrade a monadic fold to accept the FoldM type

generalize :: Monad m => Fold a b -> FoldM m a b Source

Generalize a Fold to a FoldM

generalize (pure r) = pure r

generalize (f <*> x) = generalize f <*> generalize x

simplify :: FoldM Identity a b -> Fold a b Source

Simplify a pure FoldM to a Fold

simplify (pure r) = pure r

simplify (f <*> x) = simplify f <*> simplify x

_Fold1 :: (a -> a -> a) -> Fold a (Maybe a) Source

_Fold1 step returns a new Fold using just a step function that has the same type for the accumulator and the element. The result type is the accumulator type wrapped in Maybe. The initial accumulator is retrieved from the Foldable, the result is None for empty containers.

premap :: (a -> b) -> Fold b r -> Fold a r Source

(premap f folder) returns a new Fold where f is applied at each step

fold (premap f folder) list = fold folder (map f list)
>>> fold (premap Sum mconcat) [1..10]
Sum {getSum = 55}
>>> fold mconcat (map Sum [1..10])
Sum {getSum = 55}
premap id = id

premap (f . g) = premap g . premap f
premap k (pure r) = pure r

premap k (f <*> x) = premap k f <*> premap k x

premapM :: Monad m => (a -> b) -> FoldM m b r -> FoldM m a r Source

(premapM f folder) returns a new FoldM where f is applied to each input element

foldM (premapM f folder) list = foldM folder (map f list)
premapM id = id

premapM (f . g) = premap g . premap f
premapM k (pure r) = pure r

premapM k (f <*> x) = premapM k f <*> premapM k x

pretraverse :: Traversal' a b -> Fold b r -> Fold a r Source

(pretraverse t folder) traverses each incoming element using Traversal' t and folds every target of the Traversal'

>>> fold (pretraverse traverse sum) [[1..5],[6..10]]
55
>>> fold (pretraverse (traverse.traverse) sum) [[Nothing, Just 2, Just 7],[Just 13, Nothing, Just 20]]
42
>>> fold (pretraverse (filtered even) sum) [1,3,5,7,21,21]
42
>>> fold (pretraverse _2 mconcat) [(1,"Hello "),(2,"World"),(3,"!")]
"Hello World!"
pretraverse id = id

pretraverse (f . g) = pretraverse f . pretraverse g
pretraverse t (pure r) = pure r

pretraverse t (f <*> x) = pretraverse t f <*> pretraverse t x

pretraverseM :: Monad m => Traversal' a b -> FoldM m b r -> FoldM m a r Source

(pretraverseM t folder) traverses each incoming element using Traversal' t and folds every target of the Traversal'

pretraverseM id = id

pretraverseM (f . g) = pretraverseM f . pretraverseM g
pretraverseM t (pure r) = pure r

pretraverseM t (f <*> x) = pretraverseM t f <*> pretraverseM t x

Re-exports

Control.Monad.Primitive re-exports the PrimMonad type class

Data.Foldable re-exports the Foldable type class

Data.Vector.Generic re-exports the Vector type class