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

Safe HaskellTrustworthy

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 [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)

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

Profunctor Fold 
Functor (Fold a) 
Applicative (Fold a) 
Comonad (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 => Profunctor (FoldM m) 
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 -> bSource

Apply a strict left Fold to a Foldable container

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

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 aSource

Fold all values within a container using mappend and mempty

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

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 aSource

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 BoolSource

Returns True if the container is empty, False otherwise

length :: Fold a IntSource

Return the length of the container

and :: Fold Bool BoolSource

Returns True if all elements are True, False otherwise

or :: Fold Bool BoolSource

Returns True if any element is True, False otherwise

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

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

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

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

sum :: Num a => Fold a aSource

Computes the sum of all elements

product :: Num a => Fold a aSource

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 BoolSource

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

notElem :: Eq a => a -> Fold a BoolSource

(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

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 wSource

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 bSource

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 -> rSource

Upgrade a fold to accept the Fold type

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

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

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 bSource

Upgrade a more traditional monadic fold to accept the FoldM type

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

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 bSource

Simplify a pure FoldM to a Fold

 simplify (pure r) = pure r

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

hoists :: Monad m => (forall x. m x -> n x) -> FoldM m a b -> FoldM n a bSource

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 rSource

(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 rSource

(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 -> Constant (Endo x) b) -> a -> Constant (Endo x) aSource

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 rSource

(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
>>> 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,3,5,7,21,21]
42
>>> 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

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

appEndoM :: a -> m a
 

Instances

Monad m => Monoid (EndoM m a) 

type HandlerM m a b = forall x. (b -> Constant (EndoM m x) b) -> a -> Constant (EndoM m x) aSource

A Handler for the upstream input of FoldM

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

handlesM :: Monad m => HandlerM m a b -> FoldM m b r -> FoldM m a rSource

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

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