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

Safe HaskellSafe-Inferred

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)

You can also unpack the Fold type if you want to extract the individual components of combined folds for use with your own customized folding utilities:

 case ((/) <$> L.sum <*> L.genericLength) of
     L.Foldl step begin done -> ...

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

Constructors

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

Instances

Functor (Fold a) 
Applicative (Fold a) 
Monoid b => Monoid (Fold a b) 

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

Apply a strict left Fold to a Foldable container

Much slower than fold on lists because Foldable operations currently do not trigger build/foldr fusion

data FoldM m a b Source

Like Fold, but monadic

Constructors

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

Instances

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

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

Like fold, but monadic

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

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

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

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

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

Re-exports

Data.Foldable re-exports the Foldable type