Copyright | Ross Paterson 2005 |
---|---|
License | BSD-style (see the LICENSE file in the distribution) |
Maintainer | libraries@haskell.org |
Stability | experimental |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Class of data structures that can be folded to a summary value.
- class Foldable t where
- fold :: Monoid m => t m -> m
- foldMap :: Monoid m => (a -> m) -> t a -> m
- foldr :: (a -> b -> b) -> b -> t a -> b
- foldr' :: (a -> b -> b) -> b -> t a -> b
- foldl :: (b -> a -> b) -> b -> t a -> b
- foldl' :: (b -> a -> b) -> b -> t a -> b
- foldr1 :: (a -> a -> a) -> t a -> a
- foldl1 :: (a -> a -> a) -> t a -> a
- toList :: t a -> [a]
- null :: t a -> Bool
- length :: t a -> Int
- elem :: Eq a => a -> t a -> Bool
- maximum :: forall a. Ord a => t a -> a
- minimum :: forall a. Ord a => t a -> a
- sum :: Num a => t a -> a
- product :: Num a => t a -> a
- foldrM :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m b
- foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
- traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f ()
- for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f ()
- sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f ()
- asum :: (Foldable t, Alternative f) => t (f a) -> f a
- mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m ()
- sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
- msum :: (Foldable t, MonadPlus m) => t (m a) -> m 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
- maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
- minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
- notElem :: (Foldable t, Eq a) => a -> t a -> Bool
- find :: Foldable t => (a -> Bool) -> t a -> Maybe a
Folds
Data structures that can be folded.
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
Foldable
instances are expected to satisfy the following laws:
foldr f z t = appEndo (foldMap (Endo . f) t ) z
foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
fold = foldMap id
sum
, product
, maximum
, and minimum
should all be essentially
equivalent to foldMap
forms, such as
sum = getSum . foldMap Sum
but may be less defined.
If the type is also a Functor
instance, it should satisfy
foldMap f = fold . fmap f
which implies that
foldMap f . fmap g = foldMap (f . g)
fold :: Monoid m => t m -> m Source
Combine the elements of a structure using a monoid.
foldMap :: Monoid m => (a -> m) -> t a -> m Source
Map each element of the structure to a monoid, and combine the results.
foldr :: (a -> b -> b) -> b -> t a -> b Source
foldr' :: (a -> b -> b) -> b -> t a -> b Source
Right-associative fold of a structure, but with strict application of the operator.
foldl :: (b -> a -> b) -> b -> t a -> b Source
foldl' :: (b -> a -> b) -> b -> t a -> b Source
Left-associative fold of a structure. but with strict application of the operator.
foldl
f z =foldl'
f z .toList
foldr1 :: (a -> a -> a) -> t a -> a Source
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 Source
A variant of foldl
that has no base case,
and thus may only be applied to non-empty structures.
foldl1
f =foldl1
f .toList
List of elements of a structure, from left to right.
Test whether the structure is empty. The default implementation is optimized for structures that are similar to cons-lists, because there is no general way to do better.
Returns the size/length of a finite structure as an Int
. The
default implementation is optimized for structures that are similar to
cons-lists, because there is no general way to do better.
elem :: Eq a => a -> t a -> Bool infix 4 Source
Does the element occur in the structure?
maximum :: forall a. Ord a => t a -> a Source
The largest element of a non-empty structure.
minimum :: forall a. Ord a => t a -> a Source
The least element of a non-empty structure.
sum :: Num a => t a -> a Source
The sum
function computes the sum of the numbers of a structure.
product :: Num a => t a -> a Source
The product
function computes the product of the numbers of a
structure.
Special biased folds
foldrM :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m b Source
Monadic fold over the elements of a structure, associating to the right, i.e. from right to left.
foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b Source
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 a version
that doesn't ignore the results see traverse
.
for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f () Source
sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f () Source
Evaluate each action in the structure from left to right, and
ignore the results. For a version that doesn't ignore the results
see sequenceA
.
asum :: (Foldable t, Alternative f) => t (f a) -> f a Source
The sum of a collection of actions, generalizing concat
.
Monadic actions
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. For a version that doesn't ignore the
results see sequence
.
As of base 4.8.0.0, sequence_
is just sequenceA_
, specialized
to Monad
.
Specialized folds
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.
any :: Foldable t => (a -> Bool) -> t a -> Bool Source
Determines whether any element of the structure satisfies the predicate.
all :: Foldable t => (a -> Bool) -> t a -> Bool Source
Determines whether all elements of the structure satisfy the predicate.
maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a Source
The largest element of a non-empty structure with respect to the given comparison function.
minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a Source
The least element of a non-empty structure with respect to the given comparison function.