base-4.9.0.0: Basic libraries

CopyrightRoss Paterson 2005
LicenseBSD-style (see the LICENSE file in the distribution)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Foldable

Contents

Description

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

Synopsis

Folds

class Foldable t where Source

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)

Minimal complete definition

foldMap | foldr

Methods

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

Right-associative fold of a structure.

In the case of lists, foldr, when applied to a binary operator, a starting value (typically the right-identity of the operator), and a list, reduces the list using the binary operator, from right to left:

foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)

Note that, since the head of the resulting expression is produced by an application of the operator to the first element of the list, foldr can produce a terminating expression from an infinite list.

For a general Foldable structure this should be semantically identical to,

foldr f z = foldr f z . toList

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

Left-associative fold of a structure.

In the case of lists, foldl, when applied to a binary operator, a starting value (typically the left-identity of the operator), and a list, reduces the list using the binary operator, from left to right:

foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn

Note that to produce the outermost application of the operator the entire input list must be traversed. This means that foldl' will diverge if given an infinite list.

Also note that if you want an efficient left-fold, you probably want to use foldl' instead of foldl. The reason for this is that latter does not force the "inner" results (e.g. z f x1 in the above example) before applying them to the operator (e.g. to (f x2)). This results in a thunk chain O(n) elements long, which then must be evaluated from the outside-in.

For a general Foldable structure this should be semantically identical to,

foldl f z = foldl f z . toList

foldl' :: (b -> a -> b) -> b -> t a -> b Source

Left-associative fold of a structure but with strict application of the operator.

This ensures that each step of the fold is forced to weak head normal form before being applied, avoiding the collection of thunks that would otherwise occur. This is often what you want to strictly reduce a finite list to a single, monolithic result (e.g. length).

For a general Foldable structure this should be semantically identical to,

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

toList :: t a -> [a] Source

List of elements of a structure, from left to right.

null :: t a -> Bool Source

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.

length :: t a -> Int Source

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.

Instances

Foldable [] 

Methods

fold :: Monoid m => [m] -> m Source

foldMap :: Monoid m => (a -> m) -> [a] -> m Source

foldr :: (a -> b -> b) -> b -> [a] -> b Source

foldr' :: (a -> b -> b) -> b -> [a] -> b Source

foldl :: (b -> a -> b) -> b -> [a] -> b Source

foldl' :: (b -> a -> b) -> b -> [a] -> b Source

foldr1 :: (a -> a -> a) -> [a] -> a Source

foldl1 :: (a -> a -> a) -> [a] -> a Source

toList :: [a] -> [a] Source

null :: [a] -> Bool Source

length :: [a] -> Int Source

elem :: Eq a => a -> [a] -> Bool Source

maximum :: Ord a => [a] -> a Source

minimum :: Ord a => [a] -> a Source

sum :: Num a => [a] -> a Source

product :: Num a => [a] -> a Source

Foldable Maybe 

Methods

fold :: Monoid m => Maybe m -> m Source

foldMap :: Monoid m => (a -> m) -> Maybe a -> m Source

foldr :: (a -> b -> b) -> b -> Maybe a -> b Source

foldr' :: (a -> b -> b) -> b -> Maybe a -> b Source

foldl :: (b -> a -> b) -> b -> Maybe a -> b Source

foldl' :: (b -> a -> b) -> b -> Maybe a -> b Source

foldr1 :: (a -> a -> a) -> Maybe a -> a Source

foldl1 :: (a -> a -> a) -> Maybe a -> a Source

toList :: Maybe a -> [a] Source

null :: Maybe a -> Bool Source

length :: Maybe a -> Int Source

elem :: Eq a => a -> Maybe a -> Bool Source

maximum :: Ord a => Maybe a -> a Source

minimum :: Ord a => Maybe a -> a Source

sum :: Num a => Maybe a -> a Source

product :: Num a => Maybe a -> a Source

Foldable Last 

Methods

fold :: Monoid m => Last m -> m Source

foldMap :: Monoid m => (a -> m) -> Last a -> m Source

foldr :: (a -> b -> b) -> b -> Last a -> b Source

foldr' :: (a -> b -> b) -> b -> Last a -> b Source

foldl :: (b -> a -> b) -> b -> Last a -> b Source

foldl' :: (b -> a -> b) -> b -> Last a -> b Source

foldr1 :: (a -> a -> a) -> Last a -> a Source

foldl1 :: (a -> a -> a) -> Last a -> a Source

toList :: Last a -> [a] Source

null :: Last a -> Bool Source

length :: Last a -> Int Source

elem :: Eq a => a -> Last a -> Bool Source

maximum :: Ord a => Last a -> a Source

minimum :: Ord a => Last a -> a Source

sum :: Num a => Last a -> a Source

product :: Num a => Last a -> a Source

Foldable First 

Methods

fold :: Monoid m => First m -> m Source

foldMap :: Monoid m => (a -> m) -> First a -> m Source

foldr :: (a -> b -> b) -> b -> First a -> b Source

foldr' :: (a -> b -> b) -> b -> First a -> b Source

foldl :: (b -> a -> b) -> b -> First a -> b Source

foldl' :: (b -> a -> b) -> b -> First a -> b Source

foldr1 :: (a -> a -> a) -> First a -> a Source

foldl1 :: (a -> a -> a) -> First a -> a Source

toList :: First a -> [a] Source

null :: First a -> Bool Source

length :: First a -> Int Source

elem :: Eq a => a -> First a -> Bool Source

maximum :: Ord a => First a -> a Source

minimum :: Ord a => First a -> a Source

sum :: Num a => First a -> a Source

product :: Num a => First a -> a Source

Foldable Product 

Methods

fold :: Monoid m => Product m -> m Source

foldMap :: Monoid m => (a -> m) -> Product a -> m Source

foldr :: (a -> b -> b) -> b -> Product a -> b Source

foldr' :: (a -> b -> b) -> b -> Product a -> b Source

foldl :: (b -> a -> b) -> b -> Product a -> b Source

foldl' :: (b -> a -> b) -> b -> Product a -> b Source

foldr1 :: (a -> a -> a) -> Product a -> a Source

foldl1 :: (a -> a -> a) -> Product a -> a Source

toList :: Product a -> [a] Source

null :: Product a -> Bool Source

length :: Product a -> Int Source

elem :: Eq a => a -> Product a -> Bool Source

maximum :: Ord a => Product a -> a Source

minimum :: Ord a => Product a -> a Source

sum :: Num a => Product a -> a Source

product :: Num a => Product a -> a Source

Foldable Sum 

Methods

fold :: Monoid m => Sum m -> m Source

foldMap :: Monoid m => (a -> m) -> Sum a -> m Source

foldr :: (a -> b -> b) -> b -> Sum a -> b Source

foldr' :: (a -> b -> b) -> b -> Sum a -> b Source

foldl :: (b -> a -> b) -> b -> Sum a -> b Source

foldl' :: (b -> a -> b) -> b -> Sum a -> b Source

foldr1 :: (a -> a -> a) -> Sum a -> a Source

foldl1 :: (a -> a -> a) -> Sum a -> a Source

toList :: Sum a -> [a] Source

null :: Sum a -> Bool Source

length :: Sum a -> Int Source

elem :: Eq a => a -> Sum a -> Bool Source

maximum :: Ord a => Sum a -> a Source

minimum :: Ord a => Sum a -> a Source

sum :: Num a => Sum a -> a Source

product :: Num a => Sum a -> a Source

Foldable Dual 

Methods

fold :: Monoid m => Dual m -> m Source

foldMap :: Monoid m => (a -> m) -> Dual a -> m Source

foldr :: (a -> b -> b) -> b -> Dual a -> b Source

foldr' :: (a -> b -> b) -> b -> Dual a -> b Source

foldl :: (b -> a -> b) -> b -> Dual a -> b Source

foldl' :: (b -> a -> b) -> b -> Dual a -> b Source

foldr1 :: (a -> a -> a) -> Dual a -> a Source

foldl1 :: (a -> a -> a) -> Dual a -> a Source

toList :: Dual a -> [a] Source

null :: Dual a -> Bool Source

length :: Dual a -> Int Source

elem :: Eq a => a -> Dual a -> Bool Source

maximum :: Ord a => Dual a -> a Source

minimum :: Ord a => Dual a -> a Source

sum :: Num a => Dual a -> a Source

product :: Num a => Dual a -> a Source

Foldable ZipList 

Methods

fold :: Monoid m => ZipList m -> m Source

foldMap :: Monoid m => (a -> m) -> ZipList a -> m Source

foldr :: (a -> b -> b) -> b -> ZipList a -> b Source

foldr' :: (a -> b -> b) -> b -> ZipList a -> b Source

foldl :: (b -> a -> b) -> b -> ZipList a -> b Source

foldl' :: (b -> a -> b) -> b -> ZipList a -> b Source

foldr1 :: (a -> a -> a) -> ZipList a -> a Source

foldl1 :: (a -> a -> a) -> ZipList a -> a Source

toList :: ZipList a -> [a] Source

null :: ZipList a -> Bool Source

length :: ZipList a -> Int Source

elem :: Eq a => a -> ZipList a -> Bool Source

maximum :: Ord a => ZipList a -> a Source

minimum :: Ord a => ZipList a -> a Source

sum :: Num a => ZipList a -> a Source

product :: Num a => ZipList a -> a Source

Foldable Complex 

Methods

fold :: Monoid m => Complex m -> m Source

foldMap :: Monoid m => (a -> m) -> Complex a -> m Source

foldr :: (a -> b -> b) -> b -> Complex a -> b Source

foldr' :: (a -> b -> b) -> b -> Complex a -> b Source

foldl :: (b -> a -> b) -> b -> Complex a -> b Source

foldl' :: (b -> a -> b) -> b -> Complex a -> b Source

foldr1 :: (a -> a -> a) -> Complex a -> a Source

foldl1 :: (a -> a -> a) -> Complex a -> a Source

toList :: Complex a -> [a] Source

null :: Complex a -> Bool Source

length :: Complex a -> Int Source

elem :: Eq a => a -> Complex a -> Bool Source

maximum :: Ord a => Complex a -> a Source

minimum :: Ord a => Complex a -> a Source

sum :: Num a => Complex a -> a Source

product :: Num a => Complex a -> a Source

Foldable NonEmpty 

Methods

fold :: Monoid m => NonEmpty m -> m Source

foldMap :: Monoid m => (a -> m) -> NonEmpty a -> m Source

foldr :: (a -> b -> b) -> b -> NonEmpty a -> b Source

foldr' :: (a -> b -> b) -> b -> NonEmpty a -> b Source

foldl :: (b -> a -> b) -> b -> NonEmpty a -> b Source

foldl' :: (b -> a -> b) -> b -> NonEmpty a -> b Source

foldr1 :: (a -> a -> a) -> NonEmpty a -> a Source

foldl1 :: (a -> a -> a) -> NonEmpty a -> a Source

toList :: NonEmpty a -> [a] Source

null :: NonEmpty a -> Bool Source

length :: NonEmpty a -> Int Source

elem :: Eq a => a -> NonEmpty a -> Bool Source

maximum :: Ord a => NonEmpty a -> a Source

minimum :: Ord a => NonEmpty a -> a Source

sum :: Num a => NonEmpty a -> a Source

product :: Num a => NonEmpty a -> a Source

Foldable Option 

Methods

fold :: Monoid m => Option m -> m Source

foldMap :: Monoid m => (a -> m) -> Option a -> m Source

foldr :: (a -> b -> b) -> b -> Option a -> b Source

foldr' :: (a -> b -> b) -> b -> Option a -> b Source

foldl :: (b -> a -> b) -> b -> Option a -> b Source

foldl' :: (b -> a -> b) -> b -> Option a -> b Source

foldr1 :: (a -> a -> a) -> Option a -> a Source

foldl1 :: (a -> a -> a) -> Option a -> a Source

toList :: Option a -> [a] Source

null :: Option a -> Bool Source

length :: Option a -> Int Source

elem :: Eq a => a -> Option a -> Bool Source

maximum :: Ord a => Option a -> a Source

minimum :: Ord a => Option a -> a Source

sum :: Num a => Option a -> a Source

product :: Num a => Option a -> a Source

Foldable Last 

Methods

fold :: Monoid m => Last m -> m Source

foldMap :: Monoid m => (a -> m) -> Last a -> m Source

foldr :: (a -> b -> b) -> b -> Last a -> b Source

foldr' :: (a -> b -> b) -> b -> Last a -> b Source

foldl :: (b -> a -> b) -> b -> Last a -> b Source

foldl' :: (b -> a -> b) -> b -> Last a -> b Source

foldr1 :: (a -> a -> a) -> Last a -> a Source

foldl1 :: (a -> a -> a) -> Last a -> a Source

toList :: Last a -> [a] Source

null :: Last a -> Bool Source

length :: Last a -> Int Source

elem :: Eq a => a -> Last a -> Bool Source

maximum :: Ord a => Last a -> a Source

minimum :: Ord a => Last a -> a Source

sum :: Num a => Last a -> a Source

product :: Num a => Last a -> a Source

Foldable First 

Methods

fold :: Monoid m => First m -> m Source

foldMap :: Monoid m => (a -> m) -> First a -> m Source

foldr :: (a -> b -> b) -> b -> First a -> b Source

foldr' :: (a -> b -> b) -> b -> First a -> b Source

foldl :: (b -> a -> b) -> b -> First a -> b Source

foldl' :: (b -> a -> b) -> b -> First a -> b Source

foldr1 :: (a -> a -> a) -> First a -> a Source

foldl1 :: (a -> a -> a) -> First a -> a Source

toList :: First a -> [a] Source

null :: First a -> Bool Source

length :: First a -> Int Source

elem :: Eq a => a -> First a -> Bool Source

maximum :: Ord a => First a -> a Source

minimum :: Ord a => First a -> a Source

sum :: Num a => First a -> a Source

product :: Num a => First a -> a Source

Foldable Max 

Methods

fold :: Monoid m => Max m -> m Source

foldMap :: Monoid m => (a -> m) -> Max a -> m Source

foldr :: (a -> b -> b) -> b -> Max a -> b Source

foldr' :: (a -> b -> b) -> b -> Max a -> b Source

foldl :: (b -> a -> b) -> b -> Max a -> b Source

foldl' :: (b -> a -> b) -> b -> Max a -> b Source

foldr1 :: (a -> a -> a) -> Max a -> a Source

foldl1 :: (a -> a -> a) -> Max a -> a Source

toList :: Max a -> [a] Source

null :: Max a -> Bool Source

length :: Max a -> Int Source

elem :: Eq a => a -> Max a -> Bool Source

maximum :: Ord a => Max a -> a Source

minimum :: Ord a => Max a -> a Source

sum :: Num a => Max a -> a Source

product :: Num a => Max a -> a Source

Foldable Min 

Methods

fold :: Monoid m => Min m -> m Source

foldMap :: Monoid m => (a -> m) -> Min a -> m Source

foldr :: (a -> b -> b) -> b -> Min a -> b Source

foldr' :: (a -> b -> b) -> b -> Min a -> b Source

foldl :: (b -> a -> b) -> b -> Min a -> b Source

foldl' :: (b -> a -> b) -> b -> Min a -> b Source

foldr1 :: (a -> a -> a) -> Min a -> a Source

foldl1 :: (a -> a -> a) -> Min a -> a Source

toList :: Min a -> [a] Source

null :: Min a -> Bool Source

length :: Min a -> Int Source

elem :: Eq a => a -> Min a -> Bool Source

maximum :: Ord a => Min a -> a Source

minimum :: Ord a => Min a -> a Source

sum :: Num a => Min a -> a Source

product :: Num a => Min a -> a Source

Foldable Identity 

Methods

fold :: Monoid m => Identity m -> m Source

foldMap :: Monoid m => (a -> m) -> Identity a -> m Source

foldr :: (a -> b -> b) -> b -> Identity a -> b Source

foldr' :: (a -> b -> b) -> b -> Identity a -> b Source

foldl :: (b -> a -> b) -> b -> Identity a -> b Source

foldl' :: (b -> a -> b) -> b -> Identity a -> b Source

foldr1 :: (a -> a -> a) -> Identity a -> a Source

foldl1 :: (a -> a -> a) -> Identity a -> a Source

toList :: Identity a -> [a] Source

null :: Identity a -> Bool Source

length :: Identity a -> Int Source

elem :: Eq a => a -> Identity a -> Bool Source

maximum :: Ord a => Identity a -> a Source

minimum :: Ord a => Identity a -> a Source

sum :: Num a => Identity a -> a Source

product :: Num a => Identity a -> a Source

Foldable (Either a) 

Methods

fold :: Monoid m => Either a m -> m Source

foldMap :: Monoid m => (a -> m) -> Either a a -> m Source

foldr :: (a -> b -> b) -> b -> Either a a -> b Source

foldr' :: (a -> b -> b) -> b -> Either a a -> b Source

foldl :: (b -> a -> b) -> b -> Either a a -> b Source

foldl' :: (b -> a -> b) -> b -> Either a a -> b Source

foldr1 :: (a -> a -> a) -> Either a a -> a Source

foldl1 :: (a -> a -> a) -> Either a a -> a Source

toList :: Either a a -> [a] Source

null :: Either a a -> Bool Source

length :: Either a a -> Int Source

elem :: Eq a => a -> Either a a -> Bool Source

maximum :: Ord a => Either a a -> a Source

minimum :: Ord a => Either a a -> a Source

sum :: Num a => Either a a -> a Source

product :: Num a => Either a a -> a Source

Foldable ((,) a) 

Methods

fold :: Monoid m => (a, m) -> m Source

foldMap :: Monoid m => (a -> m) -> (a, a) -> m Source

foldr :: (a -> b -> b) -> b -> (a, a) -> b Source

foldr' :: (a -> b -> b) -> b -> (a, a) -> b Source

foldl :: (b -> a -> b) -> b -> (a, a) -> b Source

foldl' :: (b -> a -> b) -> b -> (a, a) -> b Source

foldr1 :: (a -> a -> a) -> (a, a) -> a Source

foldl1 :: (a -> a -> a) -> (a, a) -> a Source

toList :: (a, a) -> [a] Source

null :: (a, a) -> Bool Source

length :: (a, a) -> Int Source

elem :: Eq a => a -> (a, a) -> Bool Source

maximum :: Ord a => (a, a) -> a Source

minimum :: Ord a => (a, a) -> a Source

sum :: Num a => (a, a) -> a Source

product :: Num a => (a, a) -> a Source

Foldable (Proxy (TYPE Lifted)) 

Methods

fold :: Monoid m => Proxy (TYPE Lifted) m -> m Source

foldMap :: Monoid m => (a -> m) -> Proxy (TYPE Lifted) a -> m Source

foldr :: (a -> b -> b) -> b -> Proxy (TYPE Lifted) a -> b Source

foldr' :: (a -> b -> b) -> b -> Proxy (TYPE Lifted) a -> b Source

foldl :: (b -> a -> b) -> b -> Proxy (TYPE Lifted) a -> b Source

foldl' :: (b -> a -> b) -> b -> Proxy (TYPE Lifted) a -> b Source

foldr1 :: (a -> a -> a) -> Proxy (TYPE Lifted) a -> a Source

foldl1 :: (a -> a -> a) -> Proxy (TYPE Lifted) a -> a Source

toList :: Proxy (TYPE Lifted) a -> [a] Source

null :: Proxy (TYPE Lifted) a -> Bool Source

length :: Proxy (TYPE Lifted) a -> Int Source

elem :: Eq a => a -> Proxy (TYPE Lifted) a -> Bool Source

maximum :: Ord a => Proxy (TYPE Lifted) a -> a Source

minimum :: Ord a => Proxy (TYPE Lifted) a -> a Source

sum :: Num a => Proxy (TYPE Lifted) a -> a Source

product :: Num a => Proxy (TYPE Lifted) a -> a Source

Foldable (Arg a) 

Methods

fold :: Monoid m => Arg a m -> m Source

foldMap :: Monoid m => (a -> m) -> Arg a a -> m Source

foldr :: (a -> b -> b) -> b -> Arg a a -> b Source

foldr' :: (a -> b -> b) -> b -> Arg a a -> b Source

foldl :: (b -> a -> b) -> b -> Arg a a -> b Source

foldl' :: (b -> a -> b) -> b -> Arg a a -> b Source

foldr1 :: (a -> a -> a) -> Arg a a -> a Source

foldl1 :: (a -> a -> a) -> Arg a a -> a Source

toList :: Arg a a -> [a] Source

null :: Arg a a -> Bool Source

length :: Arg a a -> Int Source

elem :: Eq a => a -> Arg a a -> Bool Source

maximum :: Ord a => Arg a a -> a Source

minimum :: Ord a => Arg a a -> a Source

sum :: Num a => Arg a a -> a Source

product :: Num a => Arg a a -> a Source

Foldable (Const (TYPE Lifted) m) 

Methods

fold :: Monoid m => Const (TYPE Lifted) m m -> m Source

foldMap :: Monoid m => (a -> m) -> Const (TYPE Lifted) m a -> m Source

foldr :: (a -> b -> b) -> b -> Const (TYPE Lifted) m a -> b Source

foldr' :: (a -> b -> b) -> b -> Const (TYPE Lifted) m a -> b Source

foldl :: (b -> a -> b) -> b -> Const (TYPE Lifted) m a -> b Source

foldl' :: (b -> a -> b) -> b -> Const (TYPE Lifted) m a -> b Source

foldr1 :: (a -> a -> a) -> Const (TYPE Lifted) m a -> a Source

foldl1 :: (a -> a -> a) -> Const (TYPE Lifted) m a -> a Source

toList :: Const (TYPE Lifted) m a -> [a] Source

null :: Const (TYPE Lifted) m a -> Bool Source

length :: Const (TYPE Lifted) m a -> Int Source

elem :: Eq a => a -> Const (TYPE Lifted) m a -> Bool Source

maximum :: Ord a => Const (TYPE Lifted) m a -> a Source

minimum :: Ord a => Const (TYPE Lifted) m a -> a Source

sum :: Num a => Const (TYPE Lifted) m a -> a Source

product :: Num a => Const (TYPE Lifted) m a -> a Source

(Foldable f, Foldable g) => Foldable (Product (TYPE Lifted) f g) 

Methods

fold :: Monoid m => Product (TYPE Lifted) f g m -> m Source

foldMap :: Monoid m => (a -> m) -> Product (TYPE Lifted) f g a -> m Source

foldr :: (a -> b -> b) -> b -> Product (TYPE Lifted) f g a -> b Source

foldr' :: (a -> b -> b) -> b -> Product (TYPE Lifted) f g a -> b Source

foldl :: (b -> a -> b) -> b -> Product (TYPE Lifted) f g a -> b Source

foldl' :: (b -> a -> b) -> b -> Product (TYPE Lifted) f g a -> b Source

foldr1 :: (a -> a -> a) -> Product (TYPE Lifted) f g a -> a Source

foldl1 :: (a -> a -> a) -> Product (TYPE Lifted) f g a -> a Source

toList :: Product (TYPE Lifted) f g a -> [a] Source

null :: Product (TYPE Lifted) f g a -> Bool Source

length :: Product (TYPE Lifted) f g a -> Int Source

elem :: Eq a => a -> Product (TYPE Lifted) f g a -> Bool Source

maximum :: Ord a => Product (TYPE Lifted) f g a -> a Source

minimum :: Ord a => Product (TYPE Lifted) f g a -> a Source

sum :: Num a => Product (TYPE Lifted) f g a -> a Source

product :: Num a => Product (TYPE Lifted) f g a -> a Source

(Foldable f, Foldable g) => Foldable (Sum (TYPE Lifted) f g) 

Methods

fold :: Monoid m => Sum (TYPE Lifted) f g m -> m Source

foldMap :: Monoid m => (a -> m) -> Sum (TYPE Lifted) f g a -> m Source

foldr :: (a -> b -> b) -> b -> Sum (TYPE Lifted) f g a -> b Source

foldr' :: (a -> b -> b) -> b -> Sum (TYPE Lifted) f g a -> b Source

foldl :: (b -> a -> b) -> b -> Sum (TYPE Lifted) f g a -> b Source

foldl' :: (b -> a -> b) -> b -> Sum (TYPE Lifted) f g a -> b Source

foldr1 :: (a -> a -> a) -> Sum (TYPE Lifted) f g a -> a Source

foldl1 :: (a -> a -> a) -> Sum (TYPE Lifted) f g a -> a Source

toList :: Sum (TYPE Lifted) f g a -> [a] Source

null :: Sum (TYPE Lifted) f g a -> Bool Source

length :: Sum (TYPE Lifted) f g a -> Int Source

elem :: Eq a => a -> Sum (TYPE Lifted) f g a -> Bool Source

maximum :: Ord a => Sum (TYPE Lifted) f g a -> a Source

minimum :: Ord a => Sum (TYPE Lifted) f g a -> a Source

sum :: Num a => Sum (TYPE Lifted) f g a -> a Source

product :: Num a => Sum (TYPE Lifted) f g a -> a Source

(Foldable f, Foldable g) => Foldable (Compose (TYPE Lifted) (TYPE Lifted) f g) 

Methods

fold :: Monoid m => Compose (TYPE Lifted) (TYPE Lifted) f g m -> m Source

foldMap :: Monoid m => (a -> m) -> Compose (TYPE Lifted) (TYPE Lifted) f g a -> m Source

foldr :: (a -> b -> b) -> b -> Compose (TYPE Lifted) (TYPE Lifted) f g a -> b Source

foldr' :: (a -> b -> b) -> b -> Compose (TYPE Lifted) (TYPE Lifted) f g a -> b Source

foldl :: (b -> a -> b) -> b -> Compose (TYPE Lifted) (TYPE Lifted) f g a -> b Source

foldl' :: (b -> a -> b) -> b -> Compose (TYPE Lifted) (TYPE Lifted) f g a -> b Source

foldr1 :: (a -> a -> a) -> Compose (TYPE Lifted) (TYPE Lifted) f g a -> a Source

foldl1 :: (a -> a -> a) -> Compose (TYPE Lifted) (TYPE Lifted) f g a -> a Source

toList :: Compose (TYPE Lifted) (TYPE Lifted) f g a -> [a] Source

null :: Compose (TYPE Lifted) (TYPE Lifted) f g a -> Bool Source

length :: Compose (TYPE Lifted) (TYPE Lifted) f g a -> Int Source

elem :: Eq a => a -> Compose (TYPE Lifted) (TYPE Lifted) f g a -> Bool Source

maximum :: Ord a => Compose (TYPE Lifted) (TYPE Lifted) f g a -> a Source

minimum :: Ord a => Compose (TYPE Lifted) (TYPE Lifted) f g a -> a Source

sum :: Num a => Compose (TYPE Lifted) (TYPE Lifted) f g a -> a Source

product :: Num a => Compose (TYPE Lifted) (TYPE Lifted) f g a -> a Source

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

for_ is traverse_ with its arguments flipped. For a version that doesn't ignore the results see for.

>>> for_ [1..4] print
1
2
3
4

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

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. For a version that doesn't ignore the results see mapM.

As of base 4.8.0.0, mapM_ is just traverse_, specialized to Monad.

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

forM_ is mapM_ with its arguments flipped. For a version that doesn't ignore the results see forM.

As of base 4.8.0.0, forM_ is just for_, specialized to Monad.

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.

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

The sum of a collection of actions, generalizing concat. As of base 4.8.0.0, msum is just asum, specialized to MonadPlus.

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.

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

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 Source

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

Searches

notElem :: (Foldable t, Eq a) => a -> t a -> Bool infix 4 Source

notElem is the negation of elem.

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

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.