foldl-1.2.5: 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

Taking the sum, the sum of squares, ..., upto the sum of x^5

>>> import Data.Traversable
>>> let powerSums = sequenceA [L.premap (^n) L.sum | n <- [1..5]]
>>> L.fold powerSums [1..10]
[55,385,3025,25333,220825]

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)

You might want to try enabling the -flate-dmd-anal flag when compiling executables that use this library to further improve performance.

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

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

Fold step initial extract

Instances

Profunctor Fold Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> Fold b c -> Fold a d #

lmap :: (a -> b) -> Fold b c -> Fold a c #

rmap :: (b -> c) -> Fold a b -> Fold a c #

(#.) :: Coercible * c b => (b -> c) -> Fold a b -> Fold a c #

(.#) :: Coercible * b a => Fold b c -> (a -> b) -> Fold a c #

Functor (Fold a) Source # 

Methods

fmap :: (a -> b) -> Fold a a -> Fold a b #

(<$) :: a -> Fold a b -> Fold a a #

Applicative (Fold a) Source # 

Methods

pure :: a -> Fold a a #

(<*>) :: Fold a (a -> b) -> Fold a a -> Fold a b #

(*>) :: Fold a a -> Fold a b -> Fold a b #

(<*) :: Fold a a -> Fold a b -> Fold a a #

Comonad (Fold a) Source # 

Methods

extract :: Fold a a -> a #

duplicate :: Fold a a -> Fold a (Fold a a) #

extend :: (Fold a a -> b) -> Fold a a -> Fold a b #

Floating b => Floating (Fold a b) Source # 

Methods

pi :: Fold a b #

exp :: Fold a b -> Fold a b #

log :: Fold a b -> Fold a b #

sqrt :: Fold a b -> Fold a b #

(**) :: Fold a b -> Fold a b -> Fold a b #

logBase :: Fold a b -> Fold a b -> Fold a b #

sin :: Fold a b -> Fold a b #

cos :: Fold a b -> Fold a b #

tan :: Fold a b -> Fold a b #

asin :: Fold a b -> Fold a b #

acos :: Fold a b -> Fold a b #

atan :: Fold a b -> Fold a b #

sinh :: Fold a b -> Fold a b #

cosh :: Fold a b -> Fold a b #

tanh :: Fold a b -> Fold a b #

asinh :: Fold a b -> Fold a b #

acosh :: Fold a b -> Fold a b #

atanh :: Fold a b -> Fold a b #

log1p :: Fold a b -> Fold a b #

expm1 :: Fold a b -> Fold a b #

log1pexp :: Fold a b -> Fold a b #

log1mexp :: Fold a b -> Fold a b #

Fractional b => Fractional (Fold a b) Source # 

Methods

(/) :: Fold a b -> Fold a b -> Fold a b #

recip :: Fold a b -> Fold a b #

fromRational :: Rational -> Fold a b #

Num b => Num (Fold a b) Source # 

Methods

(+) :: Fold a b -> Fold a b -> Fold a b #

(-) :: Fold a b -> Fold a b -> Fold a b #

(*) :: Fold a b -> Fold a b -> Fold a b #

negate :: Fold a b -> Fold a b #

abs :: Fold a b -> Fold a b #

signum :: Fold a b -> Fold a b #

fromInteger :: Integer -> Fold a b #

Monoid b => Monoid (Fold a b) Source # 

Methods

mempty :: Fold a b #

mappend :: Fold a b -> Fold a b -> Fold a b #

mconcat :: [Fold a b] -> 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

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

FoldM step initial extract

Instances

Monad m => Profunctor (FoldM m) Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> FoldM m b c -> FoldM m a d #

lmap :: (a -> b) -> FoldM m b c -> FoldM m a c #

rmap :: (b -> c) -> FoldM m a b -> FoldM m a c #

(#.) :: Coercible * c b => (b -> c) -> FoldM m a b -> FoldM m a c #

(.#) :: Coercible * b a => FoldM m b c -> (a -> b) -> FoldM m a c #

Monad m => Functor (FoldM m a) Source # 

Methods

fmap :: (a -> b) -> FoldM m a a -> FoldM m a b #

(<$) :: a -> FoldM m a b -> FoldM m a a #

Monad m => Applicative (FoldM m a) Source # 

Methods

pure :: a -> FoldM m a a #

(<*>) :: FoldM m a (a -> b) -> FoldM m a a -> FoldM m a b #

(*>) :: FoldM m a a -> FoldM m a b -> FoldM m a b #

(<*) :: FoldM m a a -> FoldM m a b -> FoldM m a a #

(Monad m, Floating b) => Floating (FoldM m a b) Source # 

Methods

pi :: FoldM m a b #

exp :: FoldM m a b -> FoldM m a b #

log :: FoldM m a b -> FoldM m a b #

sqrt :: FoldM m a b -> FoldM m a b #

(**) :: FoldM m a b -> FoldM m a b -> FoldM m a b #

logBase :: FoldM m a b -> FoldM m a b -> FoldM m a b #

sin :: FoldM m a b -> FoldM m a b #

cos :: FoldM m a b -> FoldM m a b #

tan :: FoldM m a b -> FoldM m a b #

asin :: FoldM m a b -> FoldM m a b #

acos :: FoldM m a b -> FoldM m a b #

atan :: FoldM m a b -> FoldM m a b #

sinh :: FoldM m a b -> FoldM m a b #

cosh :: FoldM m a b -> FoldM m a b #

tanh :: FoldM m a b -> FoldM m a b #

asinh :: FoldM m a b -> FoldM m a b #

acosh :: FoldM m a b -> FoldM m a b #

atanh :: FoldM m a b -> FoldM m a b #

log1p :: FoldM m a b -> FoldM m a b #

expm1 :: FoldM m a b -> FoldM m a b #

log1pexp :: FoldM m a b -> FoldM m a b #

log1mexp :: FoldM m a b -> FoldM m a b #

(Monad m, Fractional b) => Fractional (FoldM m a b) Source # 

Methods

(/) :: FoldM m a b -> FoldM m a b -> FoldM m a b #

recip :: FoldM m a b -> FoldM m a b #

fromRational :: Rational -> FoldM m a b #

(Monad m, Num b) => Num (FoldM m a b) Source # 

Methods

(+) :: FoldM m a b -> FoldM m a b -> FoldM m a b #

(-) :: FoldM m a b -> FoldM m a b -> FoldM m a b #

(*) :: FoldM m a b -> FoldM m a b -> FoldM m a b #

negate :: FoldM m a b -> FoldM m a b #

abs :: FoldM m a b -> FoldM m a b #

signum :: FoldM m a b -> FoldM m a b #

fromInteger :: Integer -> FoldM m a b #

(Monoid b, Monad m) => Monoid (FoldM m a b) Source # 

Methods

mempty :: FoldM m a b #

mappend :: FoldM m a b -> FoldM m a b -> FoldM m a b #

mconcat :: [FoldM m a b] -> 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

prescan :: Traversable t => Fold a b -> t a -> t b Source #

Convert a Fold into a prescan for any Traversable type

"Prescan" means that the last element of the scan is not included

postscan :: Traversable t => Fold a b -> t a -> t b Source #

Convert a Fold into a postscan for any Traversable type

"Postscan" means that the first element of the scan is not included

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

lastN :: Int -> Fold a [a] Source #

Return the last N elements

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 of all elements

mean :: Fractional a => Fold a a Source #

Compute a numerically stable arithmetic mean of all elements

variance :: Fractional a => Fold a a Source #

Compute a numerically stable (population) variance over all elements

std :: Floating a => Fold a a Source #

Compute a numerically stable (population) standard deviation over all elements

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

Computes the maximum element

maximumBy :: (a -> a -> Ordering) -> Fold a (Maybe a) Source #

Computes the maximum element with respect to the given comparison function

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

Computes the minimum element

minimumBy :: (a -> a -> Ordering) -> Fold a (Maybe a) Source #

Computes the minimum element with respect to the given comparison function

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

lookup :: Eq a => a -> Fold (a, b) (Maybe b) Source #

(lookup a) returns the element paired with the first matching item, or Nothing if none matches

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

randomN :: Vector v a => Int -> FoldM IO a (Maybe (v a)) Source #

Pick several random elements, using reservoir sampling

mapM_ :: Monad m => (a -> m ()) -> FoldM m a () Source #

Converts an effectful function to a fold. Specialized version of sink.

sink :: (Monoid w, Monad m) => (a -> m w) -> FoldM m a w Source #

Converts an effectful function to a fold

sink (f <> g) = sink f <> sink g -- if `(<>)` is commutative
sink mempty = mempty

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

hashSet :: (Eq a, Hashable a) => Fold a (HashSet a) Source #

Fold values into a hash-set

map :: Ord a => Fold (a, b) (Map a b) Source #

Fold pairs into a map.

hashMap :: (Eq a, Hashable a) => Fold (a, b) (HashMap a b) Source #

Fold pairs into a hash-map.

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 fold and foldM functions in Pipes.Prelude with the following type:

Pipes.Prelude.fold
    :: Monad m
    -> (x -> a -> x) -> x -> (x -> b) -> Producer a m () -> m b

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

Both fold and foldM is set up so that you can wrap them with either purely or impurely to accept a Fold or FoldM, respectively:

purely Pipes.Prelude.fold
    :: Monad m => Fold a b -> Producer a m () -> m b

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

Other streaming libraries supporting purely and impurely include io-streams and streaming. So for example we have:

purely System.IO.Streams.fold_ 
    :: Fold a b -> Streams.InputStream a -> IO b

impurely System.IO.Streams.foldM_ 
    :: FoldM IO a b -> Streams.InputStream a -> IO b

The monotraversable package makes it convenient to apply a Fold or FoldM to pure containers that do not allow a general Foldable instance, like unboxed vectors:

purely ofoldlUnwrap
    :: MonoFoldable mono
    => Fold (Element mono) b -> mono -> b

impurely ofoldMUnwrap
    :: MonoFoldable mono
    => FoldM m (Element mono) b -> mono -> 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

purely_ :: (forall x. (x -> a -> x) -> x -> x) -> Fold a b -> b Source #

Upgrade a more traditional fold to accept the Fold type

impurely :: (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

impurely_ :: Monad m => (forall x. (x -> a -> m x) -> m x -> m x) -> FoldM m a b -> m b Source #

Upgrade a more traditional 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

hoists :: (forall x. m x -> n x) -> FoldM m a b -> FoldM n a b Source #

Shift a FoldM from one monad to another with a morphism such as lift or liftIO; the effect is the same as hoist.

duplicateM :: Applicative m => FoldM m a b -> FoldM m a (FoldM m a b) Source #

Allows to continue feeding a FoldM even after passing it to a function that closes it.

For pure Folds, this is provided by the Comonad instance.

_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 :: (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

type Handler a b = forall x. (b -> Const (Dual (Endo x)) b) -> a -> Const (Dual (Endo x)) a Source #

A handler for the upstream input of a Fold

Any lens, traversal, or prism will type-check as a Handler

handles :: Handler a b -> Fold b r -> Fold a r Source #

(handles t folder) transforms the input of a Fold using a lens, traversal, or prism:

handles _1       :: Fold a r -> Fold (a, b) r
handles _Left    :: Fold a r -> Fold (Either a b) r
handles traverse :: Traversable t => Fold a r -> Fold (t a) r
handles folded   :: Foldable    t => Fold a r -> Fold (t a) r
>>> fold (handles traverse sum) [[1..5],[6..10]]
55
>>> fold (handles (traverse.traverse) sum) [[Nothing, Just 2, Just 7],[Just 13, Nothing, Just 20]]
42
>>> fold (handles (filtered even) sum) [1..10]
30
>>> fold (handles _2 mconcat) [(1,"Hello "),(2,"World"),(3,"!")]
"Hello World!"
handles id = id

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

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

foldOver :: Handler s a -> Fold a b -> s -> b Source #

(foldOver f folder xs) folds all values from a Lens, Traversal, Prism or Fold with the given folder

>>> foldOver (_Just . both) L.sum (Just (2, 3))
5
>>> foldOver (_Just . both) L.sum Nothing
0
L.foldOver f folder xs == L.fold folder (xs^..f)
L.foldOver (folded.f) folder == L.fold (handles f folder)
L.foldOver folded == L.fold

newtype EndoM m a Source #

instance Monad m => Monoid (EndoM m a) where
    mempty = EndoM return
    mappend (EndoM f) (EndoM g) = EndoM (f <=< g)

Constructors

EndoM 

Fields

Instances

Monad m => Monoid (EndoM m a) Source # 

Methods

mempty :: EndoM m a #

mappend :: EndoM m a -> EndoM m a -> EndoM m a #

mconcat :: [EndoM m a] -> EndoM m a #

type HandlerM m a b = forall x. (b -> Const (Dual (EndoM m x)) b) -> a -> Const (Dual (EndoM m x)) a Source #

A Handler for the upstream input of FoldM

Any lens, traversal, or prism will type-check as a HandlerM

handlesM :: HandlerM m a b -> FoldM m b r -> FoldM m a r Source #

(handlesM t folder) transforms the input of a FoldM using a lens, traversal, or prism:

handlesM _1       :: FoldM m a r -> FoldM (a, b) r
handlesM _Left    :: FoldM m a r -> FoldM (Either a b) r
handlesM traverse :: Traversable t => FoldM m a r -> FoldM m (t a) r
handlesM folded   :: Foldable    t => FoldM m a r -> FoldM m (t a) r

handlesM obeys these laws:

handlesM id = id

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

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

foldOverM :: Monad m => HandlerM m s a -> FoldM m a b -> s -> m b Source #

(foldOverM f folder xs) folds all values from a Lens, Traversal, Prism or Fold monadically with the given folder

L.foldOverM (folded.f) folder == L.foldM (handlesM f folder)
L.foldOverM folded == L.foldM

folded :: (Contravariant f, Applicative f, Foldable t) => (a -> f a) -> t a -> f (t a) Source #

folded :: Foldable t => Fold (t a) a

handles folded :: Foldable t => Fold a r -> Fold (t a) r

filtered :: Monoid m => (a -> Bool) -> (a -> m) -> a -> m Source #

>>> fold (handles (filtered even) sum) [1..10]
30
>>> foldM (handlesM (filtered even) (mapM_ print)) [1..10]
2
4
6
8
10

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