|
| Data.Foldable | | Portability | portable | | Stability | experimental | | Maintainer | ross@soi.city.ac.uk |
|
|
|
|
|
| Description |
| Class of data structures that can be folded to a summary value.
|
|
| Synopsis |
|
| class Foldable t where | | | | foldr' :: Foldable t => (a -> b -> b) -> b -> t a -> b | | | foldl' :: Foldable t => (a -> b -> a) -> a -> t b -> a | | | foldrM :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m b | | | foldlM :: (Foldable t, Monad m) => (a -> b -> m a) -> a -> t b -> m a | | | traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f () | | | mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m () | | | sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f () | | | sequence_ :: (Foldable t, Monad m) => t (m a) -> m () | | | toList :: Foldable t => t a -> [a] | | | concat :: Foldable t => t [a] -> [a] | | | concatMap :: Foldable t => (a -> [b]) -> t a -> [b] | | | and :: Foldable t => t Bool -> Bool | | | or :: Foldable t => t Bool -> Bool | | | any :: Foldable t => (a -> Bool) -> t a -> Bool | | | all :: Foldable t => (a -> Bool) -> t a -> Bool | | | sum :: (Foldable t, Num a) => t a -> a | | | product :: (Foldable t, Num a) => t a -> a | | | maximum :: (Foldable t, Ord a) => t a -> a | | | maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a | | | minimum :: (Foldable t, Ord a) => t a -> a | | | minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a | | | elem :: (Foldable t, Eq a) => a -> t a -> Bool | | | notElem :: (Foldable t, Eq a) => a -> t a -> Bool | | | find :: Foldable t => (a -> Bool) -> t a -> Maybe a |
|
|
|
| Folds
|
|
| class Foldable t where |
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
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.
| | | Methods | | fold :: Monoid m => t m -> m | | Combine the elements of a structure using a monoid.
| | | foldMap :: Monoid m => (a -> m) -> t a -> m | | Map each element of the structure to a monoid,
and combine the results.
| | | foldr :: (a -> b -> b) -> b -> t a -> b | Right-associative fold of a structure.
foldr f z = foldr f z . toList | | | foldl :: (a -> b -> a) -> a -> t b -> a | Left-associative fold of a structure.
foldl f z = foldl f z . toList | | | foldr1 :: (a -> a -> a) -> t a -> a | 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 -> a | 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 | |
|
|
| Special biased folds
|
|
| foldr' :: Foldable t => (a -> b -> b) -> b -> t a -> b |
| Fold over the elements of a structure,
associating to the right, but strictly.
|
|
| foldl' :: Foldable t => (a -> b -> a) -> a -> t b -> a |
| 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 b |
| 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 a |
| Monadic fold over the elements of a structure,
associating to the left, i.e. from left to right.
|
|
| Folding actions
|
|
| traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f () |
| Map each element of a structure to an action, evaluate
these actions from left to right, and ignore the results.
|
|
| mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m () |
| Map each element of a structure to an monadic action, evaluate
these actions from left to right, and ignore the results.
|
|
| sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f () |
| Evaluate each action in the structure from left to right,
and ignore the results.
|
|
| sequence_ :: (Foldable t, Monad m) => t (m a) -> m () |
| Evaluate each monadic action in the structure from left to right,
and ignore the results.
|
|
| Specialized folds
|
|
| toList :: Foldable t => t a -> [a] |
| List of elements of a structure.
|
|
| concat :: Foldable t => t [a] -> [a] |
| The concatenation of all the elements of a container of lists.
|
|
| concatMap :: Foldable t => (a -> [b]) -> t a -> [b] |
|
| and :: Foldable t => t Bool -> Bool |
| 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 -> Bool |
| 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 -> Bool |
| Determines whether any element of the structure satisfies the predicate.
|
|
| all :: Foldable t => (a -> Bool) -> t a -> Bool |
| Determines whether all elements of the structure satisfy the predicate.
|
|
| sum :: (Foldable t, Num a) => t a -> a |
| The sum function computes the sum of the numbers of a structure.
|
|
| product :: (Foldable t, Num a) => t a -> a |
| The product function computes the product of the numbers of a structure.
|
|
| maximum :: (Foldable t, Ord a) => t a -> a |
| The largest element of the structure.
|
|
| maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a |
|
| minimum :: (Foldable t, Ord a) => t a -> a |
| The least element of the structure.
|
|
| minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a |
|
| Searches
|
|
| elem :: (Foldable t, Eq a) => a -> t a -> Bool |
| Does the element occur in the structure?
|
|
| notElem :: (Foldable t, Eq a) => a -> t a -> Bool |
|
| find :: Foldable t => (a -> Bool) -> t a -> Maybe a |
| 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.
|
|
| Produced by Haddock version 0.7 |