base-4.5.0.0: Basic libraries

Portabilityportable
Stabilityexperimental
Maintainerlibraries@haskell.org
Safe HaskellTrustworthy

Data.Foldable

Contents

Description

Class of data structures that can be folded to a summary value.

Many of these functions generalize Prelude, Control.Monad and Data.List functions of the same names from lists to any Foldable functor. To avoid ambiguity, either import those modules hiding these names or qualify uses of these function names with an alias for this module.

Synopsis

Folds

class Foldable t whereSource

Data structures that can be folded.

Minimal complete definition: foldMap or foldr.

For example, given a data type

 data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)

a suitable instance would be

 instance Foldable Tree where
    foldMap f Empty = mempty
    foldMap f (Leaf x) = f x
    foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r

This is suitable even for abstract types, as the monoid is assumed to satisfy the monoid laws. Alternatively, one could define foldr:

 instance Foldable Tree where
    foldr f z Empty = z
    foldr f z (Leaf x) = f x z
    foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l

Methods

fold :: Monoid m => t m -> mSource

Combine the elements of a structure using a monoid.

foldMap :: Monoid m => (a -> m) -> t a -> mSource

Map each element of the structure to a monoid, and combine the results.

foldr :: (a -> b -> b) -> b -> t a -> bSource

Right-associative fold of a structure.

foldr f z = foldr f z . toList

foldl :: (a -> b -> a) -> a -> t b -> aSource

Left-associative fold of a structure.

foldl f z = foldl f z . toList

foldr1 :: (a -> a -> a) -> t a -> aSource

A variant of foldr that has no base case, and thus may only be applied to non-empty structures.

foldr1 f = foldr1 f . toList

foldl1 :: (a -> a -> a) -> t a -> aSource

A variant of foldl that has no base case, and thus may only be applied to non-empty structures.

foldl1 f = foldl1 f . toList

Instances

Foldable [] 
Foldable Maybe 
Ix i => Foldable (Array i) 

Special biased folds

foldr' :: Foldable t => (a -> b -> b) -> b -> t a -> bSource

Fold over the elements of a structure, associating to the right, but strictly.

foldl' :: Foldable t => (a -> b -> a) -> a -> t b -> aSource

Fold over the elements of a structure, associating to the left, but strictly.

foldrM :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m bSource

Monadic fold over the elements of a structure, associating to the right, i.e. from right to left.

foldlM :: (Foldable t, Monad m) => (a -> b -> m a) -> a -> t b -> m aSource

Monadic fold over the elements of a structure, associating to the left, i.e. from left to right.

Folding actions

Applicative actions

traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f ()Source

Map each element of a structure to an action, evaluate these actions from left to right, and ignore the results.

for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f ()Source

for_ is traverse_ with its arguments flipped.

sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f ()Source

Evaluate each action in the structure from left to right, and ignore the results.

asum :: (Foldable t, Alternative f) => t (f a) -> f aSource

The sum of a collection of actions, generalizing concat.

Monadic actions

mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()Source

Map each element of a structure to a monadic action, evaluate these actions from left to right, and ignore the results.

forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m ()Source

forM_ is mapM_ with its arguments flipped.

sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()Source

Evaluate each monadic action in the structure from left to right, and ignore the results.

msum :: (Foldable t, MonadPlus m) => t (m a) -> m aSource

The sum of a collection of actions, generalizing concat.

Specialized folds

toList :: Foldable t => t a -> [a]Source

List of elements of a structure.

concat :: Foldable t => t [a] -> [a]Source

The concatenation of all the elements of a container of lists.

concatMap :: Foldable t => (a -> [b]) -> t a -> [b]Source

Map a function over all the elements of a container and concatenate the resulting lists.

and :: Foldable t => t Bool -> BoolSource

and returns the conjunction of a container of Bools. For the result to be True, the container must be finite; False, however, results from a False value finitely far from the left end.

or :: Foldable t => t Bool -> BoolSource

or returns the disjunction of a container of Bools. For the result to be False, the container must be finite; True, however, results from a True value finitely far from the left end.

any :: Foldable t => (a -> Bool) -> t a -> BoolSource

Determines whether any element of the structure satisfies the predicate.

all :: Foldable t => (a -> Bool) -> t a -> BoolSource

Determines whether all elements of the structure satisfy the predicate.

sum :: (Foldable t, Num a) => t a -> aSource

The sum function computes the sum of the numbers of a structure.

product :: (Foldable t, Num a) => t a -> aSource

The product function computes the product of the numbers of a structure.

maximum :: (Foldable t, Ord a) => t a -> aSource

The largest element of a non-empty structure.

maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> aSource

The largest element of a non-empty structure with respect to the given comparison function.

minimum :: (Foldable t, Ord a) => t a -> aSource

The least element of a non-empty structure.

minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> aSource

The least element of a non-empty structure with respect to the given comparison function.

Searches

elem :: (Foldable t, Eq a) => a -> t a -> BoolSource

Does the element occur in the structure?

notElem :: (Foldable t, Eq a) => a -> t a -> BoolSource

notElem is the negation of elem.

find :: Foldable t => (a -> Bool) -> t a -> Maybe aSource

The find function takes a predicate and a structure and returns the leftmost element of the structure matching the predicate, or Nothing if there is no such element.