Data.Foldable (original) (raw)

Documentation

class Foldable t where Source #

The Foldable class represents data structures that can be reduced to a summary value one element at a time. Strict left-associative folds are a good fit for space-efficient reduction, while lazy right-associative folds are a good fit for corecursive iteration, or for folds that short-circuit after processing an initial subsequence of the structure's elements.

Instances can be derived automatically by enabling the DeriveFoldable extension. For example, a derived instance for a binary tree might be:

{-# LANGUAGE DeriveFoldable #-} data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a) deriving Foldable

A more detailed description can be found in the Overview section ofData.Foldable.

For the class laws see the Laws section of Data.Foldable.

Methods

fold :: Monoid m => t m -> m Source #

Given a structure with elements whose type is a [Monoid](Data-Monoid.html#t:Monoid "Data.Monoid"), combine them via the monoid's (`[<>](Data-Monoid.html#v:-60--62- "Data.Monoid")`) operator. This fold is right-associative and lazy in the accumulator. When you need a strict left-associative fold, use [foldMap'](Data-Foldable.html#v:foldMap-39- "Data.Foldable") instead, with [id](Data-Function.html#v:id "Data.Function") as the map.

Examples

Expand

Basic usage:

>>> fold [[1, 2, 3], [4, 5], [6], []]** **[1,2,3,4,5,6]

>>> **fold $ Node (Leaf (Sum 1)) (Sum 3) (Leaf (Sum 5))** ****Sum {getSum = 9}

Folds of unbounded structures do not terminate when the monoid's(`[<>](Data-Monoid.html#v:-60--62- "Data.Monoid")`) operator is strict:

>>> fold (repeat Nothing)** *** Hangs forever *

Lazy corecursive folds of unbounded structures are fine:

>>> take 12 $ fold $ map (\i -> [i..i+2]) [0..]** **[0,1,2,1,2,3,2,3,4,3,4,5] >>> **sum $ take 4000000 $ fold $ map (\i -> [i..i+2]) [0..]** ****2666668666666

foldMap :: Monoid m => (a -> m) -> t a -> m Source #

Map each element of the structure into a monoid, and combine the results with (`[<>](Data-Monoid.html#v:-60--62- "Data.Monoid")`). This fold is right-associative and lazy in the accumulator. For strict left-associative folds consider [foldMap'](Data-Foldable.html#v:foldMap-39- "Data.Foldable") instead.

Examples

Expand

Basic usage:

>>> **foldMap Sum [1, 3, 5]** ****Sum {getSum = 9}

>>> **foldMap Product [1, 3, 5]** ****Product {getProduct = 15}

>>> foldMap (replicate 3) [1, 2, 3]** **[1,1,1,2,2,2,3,3,3]

When a Monoid's (`[<>](Data-Monoid.html#v:-60--62- "Data.Monoid")`) is lazy in its second argument, [foldMap](Data-Foldable.html#v:foldMap "Data.Foldable") can return a result even from an unbounded structure. For example, lazy accumulation enables Data.ByteString.Builder to efficiently serialise large data structures and produce the output incrementally:

>>> import qualified Data.ByteString.Lazy as L** **>>> import qualified Data.ByteString.Builder as B** **>>> let bld :: Int -> B.Builder; bld i = B.intDec i <> B.word8 0x20** **>>> let lbs = B.toLazyByteString $ foldMap bld [0..]** **>>> L.take 64 lbs** **"0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24"

foldMap' :: Monoid m => (a -> m) -> t a -> m Source #

A left-associative variant of [foldMap](Data-Foldable.html#v:foldMap "Data.Foldable") that is strict in the accumulator. Use this method for strict reduction when partial results are merged via (`[<>](Data-Monoid.html#v:-60--62- "Data.Monoid")`).

Examples

Expand

Define a [Monoid](Data-Monoid.html#t:Monoid "Data.Monoid") over finite bit strings under xor. Use it to strictly compute the xor of a list of [Int](Data-Int.html#t:Int "Data.Int") values.

>>> :set -XGeneralizedNewtypeDeriving** **>>> import Data.Bits (Bits, FiniteBits, xor, zeroBits)** **>>> import Data.Foldable (foldMap')** **>>> import Numeric (showHex)** **>>> ** **>>> newtype X a = X a deriving (Eq, Bounded, Enum, Bits, FiniteBits)** **>>> `` instance Bits a => Semigroup (X a) where X a <> X b = X (a xor b) ``>>> instance Bits a => Monoid (X a) where mempty = X zeroBits** **>>> ** **>>> let bits :: [Int]; bits = [0xcafe, 0xfeed, 0xdeaf, 0xbeef, 0x5411]** **>>> (\ (X a) -> showString "0x" . showHex a $ "") $ foldMap' X bits** **"0x42"

Since: base-4.13.0.0

foldr :: (a -> b -> b) -> b -> t a -> b Source #

Right-associative fold of a structure, lazy in the accumulator.

In the case of lists, [foldr](Data-Foldable.html#v:foldr "Data.Foldable"), 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, given an operator lazy in its right argument, [foldr](Data-Foldable.html#v:foldr "Data.Foldable") can produce a terminating expression from an unbounded list.

For a general [Foldable](Data-Foldable.html#t:Foldable "Data.Foldable") structure this should be semantically identical to,

foldr f z = [foldr](GHC-List.html#v:foldr "GHC.List") f z . [toList](Data-Foldable.html#v:toList "Data.Foldable")

Examples

Expand

Basic usage:

>>> **foldr (||) False [False, True, False]** ****True

>>> **foldr (||) False []** ****False

>>> foldr (\c acc -> acc ++ [c]) "foo" ['a', 'b', 'c', 'd']** **"foodcba"

Infinite structures

⚠️ Applying [foldr](Data-Foldable.html#v:foldr "Data.Foldable") to infinite structures usually doesn't terminate.

It may still terminate under one of the following conditions:

Short-circuiting

(`[||](Data-Bool.html#v:-124--124- "Data.Bool")`) short-circuits on [True](Data-Bool.html#v:True "Data.Bool") values, so the following terminates because there is a [True](Data-Bool.html#v:True "Data.Bool") value finitely far from the left side:

>>> **foldr (||) False (True : repeat False)** ****True

But the following doesn't terminate:

>>> foldr (||) False (repeat False ++ [True])** *** Hangs forever *

Laziness in the second argument

Applying [foldr](Data-Foldable.html#v:foldr "Data.Foldable") to infinite structures terminates when the operator is lazy in its second argument (the initial accumulator is never used in this case, and so could be left [undefined](Prelude.html#v:undefined "Prelude"), but [] is more clear):

>>> take 5 $ foldr (\i acc -> i : fmap (+3) acc) [] (repeat 1)** **[1,4,7,10,13]

foldr' :: (a -> b -> b) -> b -> t a -> b Source #

Right-associative fold of a structure, strict in the accumulator. This is rarely what you want.

Since: base-4.6.0.0

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

Left-associative fold of a structure, lazy in the accumulator. This is rarely what you want, but can work well for structures with efficient right-to-left sequencing and an operator that is lazy in its left argument.

In the case of lists, [foldl](Data-Foldable.html#v:foldl "Data.Foldable"), 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. Like all left-associative folds,[foldl](Data-Foldable.html#v:foldl "Data.Foldable") will diverge if given an infinite list.

If you want an efficient strict left-fold, you probably want to use[foldl'](Data-Foldable.html#v:foldl-39- "Data.Foldable") instead of [foldl](Data-Foldable.html#v:foldl "Data.Foldable"). The reason for this is that the 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 \(\mathcal{O}(n)\) elements long, which then must be evaluated from the outside-in.

For a general [Foldable](Data-Foldable.html#t:Foldable "Data.Foldable") structure this should be semantically identical to:

foldl f z = [foldl](GHC-List.html#v:foldl "GHC.List") f z . [toList](Data-Foldable.html#v:toList "Data.Foldable")

Examples

Expand

The first example is a strict fold, which in practice is best performed with [foldl'](Data-Foldable.html#v:foldl-39- "Data.Foldable").

>>> **foldl (+) 42 [1,2,3,4]** ****52

Though the result below is lazy, the input is reversed before prepending it to the initial accumulator, so corecursion begins only after traversing the entire input string.

>>> foldl (\acc c -> c : acc) "abcd" "efgh"** **"hgfeabcd"

A left fold of a structure that is infinite on the right cannot terminate, even when for any finite input the fold just returns the initial accumulator:

>>> foldl (\a _ -> a) 0 $ repeat 1** *** Hangs forever *

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 structure to a single strict result (e.g. [sum](Data-Foldable.html#v:sum "Data.Foldable")).

For a general [Foldable](Data-Foldable.html#t:Foldable "Data.Foldable") structure this should be semantically identical to,

foldl' f z = [foldl'](GHC-List.html#v:foldl-39- "GHC.List") f z . [toList](Data-Foldable.html#v:toList "Data.Foldable")

Since: base-4.6.0.0

foldr1 :: (a -> a -> a) -> t a -> a Source #

A variant of [foldr](Data-Foldable.html#v:foldr "Data.Foldable") that has no base case, and thus may only be applied to non-empty structures.

This function is non-total and will raise a runtime exception if the structure happens to be empty.

Examples

Expand

Basic usage:

>>> **foldr1 (+) [1..4]** ****10

>>> **foldr1 (+) []** ****Exception: Prelude.foldr1: empty list

>>> foldr1 (+) Nothing** ***** Exception: foldr1: empty structure

>>> foldr1 (-) [1..4]** **-2

>>> **foldr1 (&&) [True, False, True, True]** ****False

>>> **foldr1 (||) [False, False, True, True]** ****True

>>> foldr1 (+) [1..]** *** Hangs forever *

foldl1 :: (a -> a -> a) -> t a -> a Source #

A variant of [foldl](Data-Foldable.html#v:foldl "Data.Foldable") that has no base case, and thus may only be applied to non-empty structures.

This function is non-total and will raise a runtime exception if the structure happens to be empty.

[foldl1](Data-Foldable.html#v:foldl1 "Data.Foldable") f = [foldl1](GHC-List.html#v:foldl1 "GHC.List") f . [toList](Data-Foldable.html#v:toList "Data.Foldable")

Examples

Expand

Basic usage:

>>> **foldl1 (+) [1..4]** ****10

>>> foldl1 (+) []** ***** Exception: Prelude.foldl1: empty list

>>> foldl1 (+) Nothing** ***** Exception: foldl1: empty structure

>>> foldl1 (-) [1..4]** **-8

>>> **foldl1 (&&) [True, False, True, True]** ****False

>>> **foldl1 (||) [False, False, True, True]** ****True

>>> foldl1 (+) [1..]** *** Hangs forever *

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

List of elements of a structure, from left to right. If the entire list is intended to be reduced via a fold, just fold the structure directly bypassing the list.

Examples

Expand

Basic usage:

>>> toList Nothing** **[]

>>> toList (Just 42)** **[42]

>>> toList (Left "foo")** **[]

>>> toList (Node (Leaf 5) 17 (Node Empty 12 (Leaf 8)))** **[5,17,12,8]

For lists, [toList](Data-Foldable.html#v:toList "Data.Foldable") is the identity:

>>> toList [1, 2, 3]** **[1,2,3]

Since: base-4.8.0.0

null :: t a -> Bool Source #

Test whether the structure is empty. The default implementation is Left-associative and lazy in both the initial element and the accumulator. Thus optimised for structures where the first element can be accessed in constant time. Structures where this is not the case should have a non-default implementation.

Examples

Expand

Basic usage:

>>> **null []** ****True

>>> **null [1]** ****False

[null](Data-Foldable.html#v:null "Data.Foldable") is expected to terminate even for infinite structures. The default implementation terminates provided the structure is bounded on the left (there is a leftmost element).

>>> **null [1..]** ****False

Since: base-4.8.0.0

length :: t a -> Int Source #

Returns the size/length of a finite structure as an [Int](Data-Int.html#t:Int "Data.Int"). The default implementation just counts elements starting with the leftmost. Instances for structures that can compute the element count faster than via element-by-element counting, should provide a specialised implementation.

Examples

Expand

Basic usage:

>>> **length []** ****0

>>> **length ['a', 'b', 'c']** ***3 >>> length [1..]** ** Hangs forever *

Since: base-4.8.0.0

elem :: Eq a => a -> t a -> Bool infix 4 Source #

Does the element occur in the structure?

Note: [elem](Data-Foldable.html#v:elem "Data.Foldable") is often used in infix form.

Examples

Expand

Basic usage:

>>> `` 3 elem [] **``**False

>>> `` 3 elem [1,2] **``**False

>>> `` 3 elem [1,2,3,4,5] **``**True

For infinite structures, the default implementation of [elem](Data-Foldable.html#v:elem "Data.Foldable") terminates if the sought-after value exists at a finite distance from the left side of the structure:

>>> `` 3 elem [1..] **``**True

>>> `` 3 elem ([4..] ++ [3]) ``* Hangs forever *

Since: base-4.8.0.0

maximum :: forall a. Ord a => t a -> a Source #

The largest element of a non-empty structure.

This function is non-total and will raise a runtime exception if the structure happens to be empty. A structure that supports random access and maintains its elements in order should provide a specialised implementation to return the maximum in faster than linear time.

Examples

Expand

Basic usage:

>>> **maximum [1..10]** ****10

>>> maximum []** ***** Exception: Prelude.maximum: empty list

>>> maximum Nothing** ***** Exception: maximum: empty structure

Since: base-4.8.0.0

minimum :: forall a. Ord a => t a -> a Source #

The least element of a non-empty structure.

This function is non-total and will raise a runtime exception if the structure happens to be empty. A structure that supports random access and maintains its elements in order should provide a specialised implementation to return the minimum in faster than linear time.

Examples

Expand

Basic usage:

>>> **minimum [1..10]** ****1

>>> minimum []** ***** Exception: Prelude.minimum: empty list

>>> minimum Nothing** ***** Exception: minimum: empty structure

Since: base-4.8.0.0

sum :: Num a => t a -> a Source #

The [sum](Data-Foldable.html#v:sum "Data.Foldable") function computes the sum of the numbers of a structure.

Examples

Expand

Basic usage:

>>> **sum []** ****0

>>> **sum [42]** ****42

>>> **sum [1..10]** ****55

>>> **sum [4.1, 2.0, 1.7]** ****7.8

>>> sum [1..]** *** Hangs forever *

Since: base-4.8.0.0

product :: Num a => t a -> a Source #

The [product](Data-Foldable.html#v:product "Data.Foldable") function computes the product of the numbers of a structure.

Examples

Expand

Basic usage:

>>> **product []** ****1

>>> **product [42]** ****42

>>> **product [1..10]** ****3628800

>>> **product [4.1, 2.0, 1.7]** ****13.939999999999998

>>> product [1..]** *** Hangs forever *

Since: base-4.8.0.0

Instances

Instances details

Foldable ZipList Source # Since: base-4.9.0.0
Instance detailsDefined in Control.Applicative Methodsfold :: Monoid m => ZipList m -> m Source #foldMap :: Monoid m => (a -> m) -> ZipList a -> 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 Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Complex Methodsfold :: Monoid m => Complex m -> m Source #foldMap :: Monoid m => (a -> m) -> Complex a -> 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 Identity Source # Since: base-4.8.0.0
Instance detailsDefined in Data.Functor.Identity Methodsfold :: Monoid m => Identity m -> m Source #foldMap :: Monoid m => (a -> m) -> Identity a -> 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 First Source # Since: base-4.8.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => First m -> m Source #foldMap :: Monoid m => (a -> m) -> First a -> 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 Last Source # Since: base-4.8.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => Last m -> m Source #foldMap :: Monoid m => (a -> m) -> Last a -> 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 Down Source # Since: base-4.12.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => Down m -> m Source #foldMap :: Monoid m => (a -> m) -> Down a -> m Source #foldMap' :: Monoid m => (a -> m) -> Down a -> m Source #foldr :: (a -> b -> b) -> b -> Down a -> b Source #foldr' :: (a -> b -> b) -> b -> Down a -> b Source #foldl :: (b -> a -> b) -> b -> Down a -> b Source #foldl' :: (b -> a -> b) -> b -> Down a -> b Source #foldr1 :: (a -> a -> a) -> Down a -> a Source #foldl1 :: (a -> a -> a) -> Down a -> a Source #toList :: Down a -> [a] Source #null :: Down a -> Bool Source #length :: Down a -> Int Source #elem :: Eq a => a -> Down a -> Bool Source #maximum :: Ord a => Down a -> a Source #minimum :: Ord a => Down a -> a Source #sum :: Num a => Down a -> a Source #product :: Num a => Down a -> a Source #
Foldable First Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Semigroup Methodsfold :: Monoid m => First m -> m Source #foldMap :: Monoid m => (a -> m) -> First a -> 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 Last Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Semigroup Methodsfold :: Monoid m => Last m -> m Source #foldMap :: Monoid m => (a -> m) -> Last a -> 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 Max Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Semigroup Methodsfold :: Monoid m => Max m -> m Source #foldMap :: Monoid m => (a -> m) -> Max a -> 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 Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Semigroup Methodsfold :: Monoid m => Min m -> m Source #foldMap :: Monoid m => (a -> m) -> Min a -> 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 Dual Source # Since: base-4.8.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => Dual m -> m Source #foldMap :: Monoid m => (a -> m) -> Dual a -> 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 Product Source # Since: base-4.8.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => Product m -> m Source #foldMap :: Monoid m => (a -> m) -> Product a -> 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 Source # Since: base-4.8.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => Sum m -> m Source #foldMap :: Monoid m => (a -> m) -> Sum a -> 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 Par1 Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => Par1 m -> m Source #foldMap :: Monoid m => (a -> m) -> Par1 a -> m Source #foldMap' :: Monoid m => (a -> m) -> Par1 a -> m Source #foldr :: (a -> b -> b) -> b -> Par1 a -> b Source #foldr' :: (a -> b -> b) -> b -> Par1 a -> b Source #foldl :: (b -> a -> b) -> b -> Par1 a -> b Source #foldl' :: (b -> a -> b) -> b -> Par1 a -> b Source #foldr1 :: (a -> a -> a) -> Par1 a -> a Source #foldl1 :: (a -> a -> a) -> Par1 a -> a Source #toList :: Par1 a -> [a] Source #null :: Par1 a -> Bool Source #length :: Par1 a -> Int Source #elem :: Eq a => a -> Par1 a -> Bool Source #maximum :: Ord a => Par1 a -> a Source #minimum :: Ord a => Par1 a -> a Source #sum :: Num a => Par1 a -> a Source #product :: Num a => Par1 a -> a Source #
Foldable NonEmpty Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => NonEmpty m -> m Source #foldMap :: Monoid m => (a -> m) -> NonEmpty a -> 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 Maybe Source # Since: base-2.1
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => Maybe m -> m Source #foldMap :: Monoid m => (a -> m) -> Maybe a -> 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 Solo Source # Since: base-4.15
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => Solo m -> m Source #foldMap :: Monoid m => (a -> m) -> Solo a -> m Source #foldMap' :: Monoid m => (a -> m) -> Solo a -> m Source #foldr :: (a -> b -> b) -> b -> Solo a -> b Source #foldr' :: (a -> b -> b) -> b -> Solo a -> b Source #foldl :: (b -> a -> b) -> b -> Solo a -> b Source #foldl' :: (b -> a -> b) -> b -> Solo a -> b Source #foldr1 :: (a -> a -> a) -> Solo a -> a Source #foldl1 :: (a -> a -> a) -> Solo a -> a Source #toList :: Solo a -> [a] Source #null :: Solo a -> Bool Source #length :: Solo a -> Int Source #elem :: Eq a => a -> Solo a -> Bool Source #maximum :: Ord a => Solo a -> a Source #minimum :: Ord a => Solo a -> a Source #sum :: Num a => Solo a -> a Source #product :: Num a => Solo a -> a Source #
Foldable [] Source # Since: base-2.1
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => [m] -> m Source #foldMap :: Monoid m => (a -> m) -> [a] -> 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 (Either a) Source # Since: base-4.7.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => Either a m -> m Source #foldMap :: Monoid m => (a0 -> m) -> Either a a0 -> m Source #foldMap' :: Monoid m => (a0 -> m) -> Either a a0 -> m Source #foldr :: (a0 -> b -> b) -> b -> Either a a0 -> b Source #foldr' :: (a0 -> b -> b) -> b -> Either a a0 -> b Source #foldl :: (b -> a0 -> b) -> b -> Either a a0 -> b Source #foldl' :: (b -> a0 -> b) -> b -> Either a a0 -> b Source #foldr1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 Source #foldl1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 Source #toList :: Either a a0 -> [a0] Source #null :: Either a a0 -> Bool Source #length :: Either a a0 -> Int Source #elem :: Eq a0 => a0 -> Either a a0 -> Bool Source #maximum :: Ord a0 => Either a a0 -> a0 Source #minimum :: Ord a0 => Either a a0 -> a0 Source #sum :: Num a0 => Either a a0 -> a0 Source #product :: Num a0 => Either a a0 -> a0 Source #
Foldable (Proxy :: TYPE LiftedRep -> Type) Source # Since: base-4.7.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => Proxy m -> m Source #foldMap :: Monoid m => (a -> m) -> Proxy a -> m Source #foldMap' :: Monoid m => (a -> m) -> Proxy a -> m Source #foldr :: (a -> b -> b) -> b -> Proxy a -> b Source #foldr' :: (a -> b -> b) -> b -> Proxy a -> b Source #foldl :: (b -> a -> b) -> b -> Proxy a -> b Source #foldl' :: (b -> a -> b) -> b -> Proxy a -> b Source #foldr1 :: (a -> a -> a) -> Proxy a -> a Source #foldl1 :: (a -> a -> a) -> Proxy a -> a Source #toList :: Proxy a -> [a] Source #null :: Proxy a -> Bool Source #length :: Proxy a -> Int Source #elem :: Eq a => a -> Proxy a -> Bool Source #maximum :: Ord a => Proxy a -> a Source #minimum :: Ord a => Proxy a -> a Source #sum :: Num a => Proxy a -> a Source #product :: Num a => Proxy a -> a Source #
Foldable (Arg a) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Semigroup Methodsfold :: Monoid m => Arg a m -> m Source #foldMap :: Monoid m => (a0 -> m) -> Arg a a0 -> m Source #foldMap' :: Monoid m => (a0 -> m) -> Arg a a0 -> m Source #foldr :: (a0 -> b -> b) -> b -> Arg a a0 -> b Source #foldr' :: (a0 -> b -> b) -> b -> Arg a a0 -> b Source #foldl :: (b -> a0 -> b) -> b -> Arg a a0 -> b Source #foldl' :: (b -> a0 -> b) -> b -> Arg a a0 -> b Source #foldr1 :: (a0 -> a0 -> a0) -> Arg a a0 -> a0 Source #foldl1 :: (a0 -> a0 -> a0) -> Arg a a0 -> a0 Source #toList :: Arg a a0 -> [a0] Source #null :: Arg a a0 -> Bool Source #length :: Arg a a0 -> Int Source #elem :: Eq a0 => a0 -> Arg a a0 -> Bool Source #maximum :: Ord a0 => Arg a a0 -> a0 Source #minimum :: Ord a0 => Arg a a0 -> a0 Source #sum :: Num a0 => Arg a a0 -> a0 Source #product :: Num a0 => Arg a a0 -> a0 Source #
Foldable (Array i) Source # Since: base-4.8.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => Array i m -> m Source #foldMap :: Monoid m => (a -> m) -> Array i a -> m Source #foldMap' :: Monoid m => (a -> m) -> Array i a -> m Source #foldr :: (a -> b -> b) -> b -> Array i a -> b Source #foldr' :: (a -> b -> b) -> b -> Array i a -> b Source #foldl :: (b -> a -> b) -> b -> Array i a -> b Source #foldl' :: (b -> a -> b) -> b -> Array i a -> b Source #foldr1 :: (a -> a -> a) -> Array i a -> a Source #foldl1 :: (a -> a -> a) -> Array i a -> a Source #toList :: Array i a -> [a] Source #null :: Array i a -> Bool Source #length :: Array i a -> Int Source #elem :: Eq a => a -> Array i a -> Bool Source #maximum :: Ord a => Array i a -> a Source #minimum :: Ord a => Array i a -> a Source #sum :: Num a => Array i a -> a Source #product :: Num a => Array i a -> a Source #
Foldable (U1 :: TYPE LiftedRep -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => U1 m -> m Source #foldMap :: Monoid m => (a -> m) -> U1 a -> m Source #foldMap' :: Monoid m => (a -> m) -> U1 a -> m Source #foldr :: (a -> b -> b) -> b -> U1 a -> b Source #foldr' :: (a -> b -> b) -> b -> U1 a -> b Source #foldl :: (b -> a -> b) -> b -> U1 a -> b Source #foldl' :: (b -> a -> b) -> b -> U1 a -> b Source #foldr1 :: (a -> a -> a) -> U1 a -> a Source #foldl1 :: (a -> a -> a) -> U1 a -> a Source #toList :: U1 a -> [a] Source #null :: U1 a -> Bool Source #length :: U1 a -> Int Source #elem :: Eq a => a -> U1 a -> Bool Source #maximum :: Ord a => U1 a -> a Source #minimum :: Ord a => U1 a -> a Source #sum :: Num a => U1 a -> a Source #product :: Num a => U1 a -> a Source #
Foldable (UAddr :: TYPE LiftedRep -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => UAddr m -> m Source #foldMap :: Monoid m => (a -> m) -> UAddr a -> m Source #foldMap' :: Monoid m => (a -> m) -> UAddr a -> m Source #foldr :: (a -> b -> b) -> b -> UAddr a -> b Source #foldr' :: (a -> b -> b) -> b -> UAddr a -> b Source #foldl :: (b -> a -> b) -> b -> UAddr a -> b Source #foldl' :: (b -> a -> b) -> b -> UAddr a -> b Source #foldr1 :: (a -> a -> a) -> UAddr a -> a Source #foldl1 :: (a -> a -> a) -> UAddr a -> a Source #toList :: UAddr a -> [a] Source #null :: UAddr a -> Bool Source #length :: UAddr a -> Int Source #elem :: Eq a => a -> UAddr a -> Bool Source #maximum :: Ord a => UAddr a -> a Source #minimum :: Ord a => UAddr a -> a Source #sum :: Num a => UAddr a -> a Source #product :: Num a => UAddr a -> a Source #
Foldable (UChar :: TYPE LiftedRep -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => UChar m -> m Source #foldMap :: Monoid m => (a -> m) -> UChar a -> m Source #foldMap' :: Monoid m => (a -> m) -> UChar a -> m Source #foldr :: (a -> b -> b) -> b -> UChar a -> b Source #foldr' :: (a -> b -> b) -> b -> UChar a -> b Source #foldl :: (b -> a -> b) -> b -> UChar a -> b Source #foldl' :: (b -> a -> b) -> b -> UChar a -> b Source #foldr1 :: (a -> a -> a) -> UChar a -> a Source #foldl1 :: (a -> a -> a) -> UChar a -> a Source #toList :: UChar a -> [a] Source #null :: UChar a -> Bool Source #length :: UChar a -> Int Source #elem :: Eq a => a -> UChar a -> Bool Source #maximum :: Ord a => UChar a -> a Source #minimum :: Ord a => UChar a -> a Source #sum :: Num a => UChar a -> a Source #product :: Num a => UChar a -> a Source #
Foldable (UDouble :: TYPE LiftedRep -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => UDouble m -> m Source #foldMap :: Monoid m => (a -> m) -> UDouble a -> m Source #foldMap' :: Monoid m => (a -> m) -> UDouble a -> m Source #foldr :: (a -> b -> b) -> b -> UDouble a -> b Source #foldr' :: (a -> b -> b) -> b -> UDouble a -> b Source #foldl :: (b -> a -> b) -> b -> UDouble a -> b Source #foldl' :: (b -> a -> b) -> b -> UDouble a -> b Source #foldr1 :: (a -> a -> a) -> UDouble a -> a Source #foldl1 :: (a -> a -> a) -> UDouble a -> a Source #toList :: UDouble a -> [a] Source #null :: UDouble a -> Bool Source #length :: UDouble a -> Int Source #elem :: Eq a => a -> UDouble a -> Bool Source #maximum :: Ord a => UDouble a -> a Source #minimum :: Ord a => UDouble a -> a Source #sum :: Num a => UDouble a -> a Source #product :: Num a => UDouble a -> a Source #
Foldable (UFloat :: TYPE LiftedRep -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => UFloat m -> m Source #foldMap :: Monoid m => (a -> m) -> UFloat a -> m Source #foldMap' :: Monoid m => (a -> m) -> UFloat a -> m Source #foldr :: (a -> b -> b) -> b -> UFloat a -> b Source #foldr' :: (a -> b -> b) -> b -> UFloat a -> b Source #foldl :: (b -> a -> b) -> b -> UFloat a -> b Source #foldl' :: (b -> a -> b) -> b -> UFloat a -> b Source #foldr1 :: (a -> a -> a) -> UFloat a -> a Source #foldl1 :: (a -> a -> a) -> UFloat a -> a Source #toList :: UFloat a -> [a] Source #null :: UFloat a -> Bool Source #length :: UFloat a -> Int Source #elem :: Eq a => a -> UFloat a -> Bool Source #maximum :: Ord a => UFloat a -> a Source #minimum :: Ord a => UFloat a -> a Source #sum :: Num a => UFloat a -> a Source #product :: Num a => UFloat a -> a Source #
Foldable (UInt :: TYPE LiftedRep -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => UInt m -> m Source #foldMap :: Monoid m => (a -> m) -> UInt a -> m Source #foldMap' :: Monoid m => (a -> m) -> UInt a -> m Source #foldr :: (a -> b -> b) -> b -> UInt a -> b Source #foldr' :: (a -> b -> b) -> b -> UInt a -> b Source #foldl :: (b -> a -> b) -> b -> UInt a -> b Source #foldl' :: (b -> a -> b) -> b -> UInt a -> b Source #foldr1 :: (a -> a -> a) -> UInt a -> a Source #foldl1 :: (a -> a -> a) -> UInt a -> a Source #toList :: UInt a -> [a] Source #null :: UInt a -> Bool Source #length :: UInt a -> Int Source #elem :: Eq a => a -> UInt a -> Bool Source #maximum :: Ord a => UInt a -> a Source #minimum :: Ord a => UInt a -> a Source #sum :: Num a => UInt a -> a Source #product :: Num a => UInt a -> a Source #
Foldable (UWord :: TYPE LiftedRep -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => UWord m -> m Source #foldMap :: Monoid m => (a -> m) -> UWord a -> m Source #foldMap' :: Monoid m => (a -> m) -> UWord a -> m Source #foldr :: (a -> b -> b) -> b -> UWord a -> b Source #foldr' :: (a -> b -> b) -> b -> UWord a -> b Source #foldl :: (b -> a -> b) -> b -> UWord a -> b Source #foldl' :: (b -> a -> b) -> b -> UWord a -> b Source #foldr1 :: (a -> a -> a) -> UWord a -> a Source #foldl1 :: (a -> a -> a) -> UWord a -> a Source #toList :: UWord a -> [a] Source #null :: UWord a -> Bool Source #length :: UWord a -> Int Source #elem :: Eq a => a -> UWord a -> Bool Source #maximum :: Ord a => UWord a -> a Source #minimum :: Ord a => UWord a -> a Source #sum :: Num a => UWord a -> a Source #product :: Num a => UWord a -> a Source #
Foldable (V1 :: TYPE LiftedRep -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => V1 m -> m Source #foldMap :: Monoid m => (a -> m) -> V1 a -> m Source #foldMap' :: Monoid m => (a -> m) -> V1 a -> m Source #foldr :: (a -> b -> b) -> b -> V1 a -> b Source #foldr' :: (a -> b -> b) -> b -> V1 a -> b Source #foldl :: (b -> a -> b) -> b -> V1 a -> b Source #foldl' :: (b -> a -> b) -> b -> V1 a -> b Source #foldr1 :: (a -> a -> a) -> V1 a -> a Source #foldl1 :: (a -> a -> a) -> V1 a -> a Source #toList :: V1 a -> [a] Source #null :: V1 a -> Bool Source #length :: V1 a -> Int Source #elem :: Eq a => a -> V1 a -> Bool Source #maximum :: Ord a => V1 a -> a Source #minimum :: Ord a => V1 a -> a Source #sum :: Num a => V1 a -> a Source #product :: Num a => V1 a -> a Source #
Foldable ((,) a) Source # Since: base-4.7.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => (a, m) -> m Source #foldMap :: Monoid m => (a0 -> m) -> (a, a0) -> m Source #foldMap' :: Monoid m => (a0 -> m) -> (a, a0) -> m Source #foldr :: (a0 -> b -> b) -> b -> (a, a0) -> b Source #foldr' :: (a0 -> b -> b) -> b -> (a, a0) -> b Source #foldl :: (b -> a0 -> b) -> b -> (a, a0) -> b Source #foldl' :: (b -> a0 -> b) -> b -> (a, a0) -> b Source #foldr1 :: (a0 -> a0 -> a0) -> (a, a0) -> a0 Source #foldl1 :: (a0 -> a0 -> a0) -> (a, a0) -> a0 Source #toList :: (a, a0) -> [a0] Source #null :: (a, a0) -> Bool Source #length :: (a, a0) -> Int Source #elem :: Eq a0 => a0 -> (a, a0) -> Bool Source #maximum :: Ord a0 => (a, a0) -> a0 Source #minimum :: Ord a0 => (a, a0) -> a0 Source #sum :: Num a0 => (a, a0) -> a0 Source #product :: Num a0 => (a, a0) -> a0 Source #
Foldable (Const m :: TYPE LiftedRep -> Type) Source # Since: base-4.7.0.0
Instance detailsDefined in Data.Functor.Const Methodsfold :: Monoid m0 => Const m m0 -> m0 Source #foldMap :: Monoid m0 => (a -> m0) -> Const m a -> m0 Source #foldMap' :: Monoid m0 => (a -> m0) -> Const m a -> m0 Source #foldr :: (a -> b -> b) -> b -> Const m a -> b Source #foldr' :: (a -> b -> b) -> b -> Const m a -> b Source #foldl :: (b -> a -> b) -> b -> Const m a -> b Source #foldl' :: (b -> a -> b) -> b -> Const m a -> b Source #foldr1 :: (a -> a -> a) -> Const m a -> a Source #foldl1 :: (a -> a -> a) -> Const m a -> a Source #toList :: Const m a -> [a] Source #null :: Const m a -> Bool Source #length :: Const m a -> Int Source #elem :: Eq a => a -> Const m a -> Bool Source #maximum :: Ord a => Const m a -> a Source #minimum :: Ord a => Const m a -> a Source #sum :: Num a => Const m a -> a Source #product :: Num a => Const m a -> a Source #
Foldable f => Foldable (Ap f) Source # Since: base-4.12.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => Ap f m -> m Source #foldMap :: Monoid m => (a -> m) -> Ap f a -> m Source #foldMap' :: Monoid m => (a -> m) -> Ap f a -> m Source #foldr :: (a -> b -> b) -> b -> Ap f a -> b Source #foldr' :: (a -> b -> b) -> b -> Ap f a -> b Source #foldl :: (b -> a -> b) -> b -> Ap f a -> b Source #foldl' :: (b -> a -> b) -> b -> Ap f a -> b Source #foldr1 :: (a -> a -> a) -> Ap f a -> a Source #foldl1 :: (a -> a -> a) -> Ap f a -> a Source #toList :: Ap f a -> [a] Source #null :: Ap f a -> Bool Source #length :: Ap f a -> Int Source #elem :: Eq a => a -> Ap f a -> Bool Source #maximum :: Ord a => Ap f a -> a Source #minimum :: Ord a => Ap f a -> a Source #sum :: Num a => Ap f a -> a Source #product :: Num a => Ap f a -> a Source #
Foldable f => Foldable (Alt f) Source # Since: base-4.12.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => Alt f m -> m Source #foldMap :: Monoid m => (a -> m) -> Alt f a -> m Source #foldMap' :: Monoid m => (a -> m) -> Alt f a -> m Source #foldr :: (a -> b -> b) -> b -> Alt f a -> b Source #foldr' :: (a -> b -> b) -> b -> Alt f a -> b Source #foldl :: (b -> a -> b) -> b -> Alt f a -> b Source #foldl' :: (b -> a -> b) -> b -> Alt f a -> b Source #foldr1 :: (a -> a -> a) -> Alt f a -> a Source #foldl1 :: (a -> a -> a) -> Alt f a -> a Source #toList :: Alt f a -> [a] Source #null :: Alt f a -> Bool Source #length :: Alt f a -> Int Source #elem :: Eq a => a -> Alt f a -> Bool Source #maximum :: Ord a => Alt f a -> a Source #minimum :: Ord a => Alt f a -> a Source #sum :: Num a => Alt f a -> a Source #product :: Num a => Alt f a -> a Source #
Foldable f => Foldable (Rec1 f) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => Rec1 f m -> m Source #foldMap :: Monoid m => (a -> m) -> Rec1 f a -> m Source #foldMap' :: Monoid m => (a -> m) -> Rec1 f a -> m Source #foldr :: (a -> b -> b) -> b -> Rec1 f a -> b Source #foldr' :: (a -> b -> b) -> b -> Rec1 f a -> b Source #foldl :: (b -> a -> b) -> b -> Rec1 f a -> b Source #foldl' :: (b -> a -> b) -> b -> Rec1 f a -> b Source #foldr1 :: (a -> a -> a) -> Rec1 f a -> a Source #foldl1 :: (a -> a -> a) -> Rec1 f a -> a Source #toList :: Rec1 f a -> [a] Source #null :: Rec1 f a -> Bool Source #length :: Rec1 f a -> Int Source #elem :: Eq a => a -> Rec1 f a -> Bool Source #maximum :: Ord a => Rec1 f a -> a Source #minimum :: Ord a => Rec1 f a -> a Source #sum :: Num a => Rec1 f a -> a Source #product :: Num a => Rec1 f a -> a Source #
(Foldable f, Foldable g) => Foldable (Product f g) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Product Methodsfold :: Monoid m => Product f g m -> m Source #foldMap :: Monoid m => (a -> m) -> Product f g a -> m Source #foldMap' :: Monoid m => (a -> m) -> Product f g a -> m Source #foldr :: (a -> b -> b) -> b -> Product f g a -> b Source #foldr' :: (a -> b -> b) -> b -> Product f g a -> b Source #foldl :: (b -> a -> b) -> b -> Product f g a -> b Source #foldl' :: (b -> a -> b) -> b -> Product f g a -> b Source #foldr1 :: (a -> a -> a) -> Product f g a -> a Source #foldl1 :: (a -> a -> a) -> Product f g a -> a Source #toList :: Product f g a -> [a] Source #null :: Product f g a -> Bool Source #length :: Product f g a -> Int Source #elem :: Eq a => a -> Product f g a -> Bool Source #maximum :: Ord a => Product f g a -> a Source #minimum :: Ord a => Product f g a -> a Source #sum :: Num a => Product f g a -> a Source #product :: Num a => Product f g a -> a Source #
(Foldable f, Foldable g) => Foldable (Sum f g) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Sum Methodsfold :: Monoid m => Sum f g m -> m Source #foldMap :: Monoid m => (a -> m) -> Sum f g a -> m Source #foldMap' :: Monoid m => (a -> m) -> Sum f g a -> m Source #foldr :: (a -> b -> b) -> b -> Sum f g a -> b Source #foldr' :: (a -> b -> b) -> b -> Sum f g a -> b Source #foldl :: (b -> a -> b) -> b -> Sum f g a -> b Source #foldl' :: (b -> a -> b) -> b -> Sum f g a -> b Source #foldr1 :: (a -> a -> a) -> Sum f g a -> a Source #foldl1 :: (a -> a -> a) -> Sum f g a -> a Source #toList :: Sum f g a -> [a] Source #null :: Sum f g a -> Bool Source #length :: Sum f g a -> Int Source #elem :: Eq a => a -> Sum f g a -> Bool Source #maximum :: Ord a => Sum f g a -> a Source #minimum :: Ord a => Sum f g a -> a Source #sum :: Num a => Sum f g a -> a Source #product :: Num a => Sum f g a -> a Source #
(Foldable f, Foldable g) => Foldable (f :*: g) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => (f :*: g) m -> m Source #foldMap :: Monoid m => (a -> m) -> (f :*: g) a -> m Source #foldMap' :: Monoid m => (a -> m) -> (f :*: g) a -> m Source #foldr :: (a -> b -> b) -> b -> (f :*: g) a -> b Source #foldr' :: (a -> b -> b) -> b -> (f :*: g) a -> b Source #foldl :: (b -> a -> b) -> b -> (f :*: g) a -> b Source #foldl' :: (b -> a -> b) -> b -> (f :*: g) a -> b Source #foldr1 :: (a -> a -> a) -> (f :*: g) a -> a Source #foldl1 :: (a -> a -> a) -> (f :*: g) a -> a Source #toList :: (f :*: g) a -> [a] Source #null :: (f :*: g) a -> Bool Source #length :: (f :*: g) a -> Int Source #elem :: Eq a => a -> (f :*: g) a -> Bool Source #maximum :: Ord a => (f :*: g) a -> a Source #minimum :: Ord a => (f :*: g) a -> a Source #sum :: Num a => (f :*: g) a -> a Source #product :: Num a => (f :*: g) a -> a Source #
(Foldable f, Foldable g) => Foldable (f :+: g) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => (f :+: g) m -> m Source #foldMap :: Monoid m => (a -> m) -> (f :+: g) a -> m Source #foldMap' :: Monoid m => (a -> m) -> (f :+: g) a -> m Source #foldr :: (a -> b -> b) -> b -> (f :+: g) a -> b Source #foldr' :: (a -> b -> b) -> b -> (f :+: g) a -> b Source #foldl :: (b -> a -> b) -> b -> (f :+: g) a -> b Source #foldl' :: (b -> a -> b) -> b -> (f :+: g) a -> b Source #foldr1 :: (a -> a -> a) -> (f :+: g) a -> a Source #foldl1 :: (a -> a -> a) -> (f :+: g) a -> a Source #toList :: (f :+: g) a -> [a] Source #null :: (f :+: g) a -> Bool Source #length :: (f :+: g) a -> Int Source #elem :: Eq a => a -> (f :+: g) a -> Bool Source #maximum :: Ord a => (f :+: g) a -> a Source #minimum :: Ord a => (f :+: g) a -> a Source #sum :: Num a => (f :+: g) a -> a Source #product :: Num a => (f :+: g) a -> a Source #
Foldable (K1 i c :: TYPE LiftedRep -> Type) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => K1 i c m -> m Source #foldMap :: Monoid m => (a -> m) -> K1 i c a -> m Source #foldMap' :: Monoid m => (a -> m) -> K1 i c a -> m Source #foldr :: (a -> b -> b) -> b -> K1 i c a -> b Source #foldr' :: (a -> b -> b) -> b -> K1 i c a -> b Source #foldl :: (b -> a -> b) -> b -> K1 i c a -> b Source #foldl' :: (b -> a -> b) -> b -> K1 i c a -> b Source #foldr1 :: (a -> a -> a) -> K1 i c a -> a Source #foldl1 :: (a -> a -> a) -> K1 i c a -> a Source #toList :: K1 i c a -> [a] Source #null :: K1 i c a -> Bool Source #length :: K1 i c a -> Int Source #elem :: Eq a => a -> K1 i c a -> Bool Source #maximum :: Ord a => K1 i c a -> a Source #minimum :: Ord a => K1 i c a -> a Source #sum :: Num a => K1 i c a -> a Source #product :: Num a => K1 i c a -> a Source #
(Foldable f, Foldable g) => Foldable (Compose f g) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Functor.Compose Methodsfold :: Monoid m => Compose f g m -> m Source #foldMap :: Monoid m => (a -> m) -> Compose f g a -> m Source #foldMap' :: Monoid m => (a -> m) -> Compose f g a -> m Source #foldr :: (a -> b -> b) -> b -> Compose f g a -> b Source #foldr' :: (a -> b -> b) -> b -> Compose f g a -> b Source #foldl :: (b -> a -> b) -> b -> Compose f g a -> b Source #foldl' :: (b -> a -> b) -> b -> Compose f g a -> b Source #foldr1 :: (a -> a -> a) -> Compose f g a -> a Source #foldl1 :: (a -> a -> a) -> Compose f g a -> a Source #toList :: Compose f g a -> [a] Source #null :: Compose f g a -> Bool Source #length :: Compose f g a -> Int Source #elem :: Eq a => a -> Compose f g a -> Bool Source #maximum :: Ord a => Compose f g a -> a Source #minimum :: Ord a => Compose f g a -> a Source #sum :: Num a => Compose f g a -> a Source #product :: Num a => Compose f g a -> a Source #
(Foldable f, Foldable g) => Foldable (f :.: g) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => (f :.: g) m -> m Source #foldMap :: Monoid m => (a -> m) -> (f :.: g) a -> m Source #foldMap' :: Monoid m => (a -> m) -> (f :.: g) a -> m Source #foldr :: (a -> b -> b) -> b -> (f :.: g) a -> b Source #foldr' :: (a -> b -> b) -> b -> (f :.: g) a -> b Source #foldl :: (b -> a -> b) -> b -> (f :.: g) a -> b Source #foldl' :: (b -> a -> b) -> b -> (f :.: g) a -> b Source #foldr1 :: (a -> a -> a) -> (f :.: g) a -> a Source #foldl1 :: (a -> a -> a) -> (f :.: g) a -> a Source #toList :: (f :.: g) a -> [a] Source #null :: (f :.: g) a -> Bool Source #length :: (f :.: g) a -> Int Source #elem :: Eq a => a -> (f :.: g) a -> Bool Source #maximum :: Ord a => (f :.: g) a -> a Source #minimum :: Ord a => (f :.: g) a -> a Source #sum :: Num a => (f :.: g) a -> a Source #product :: Num a => (f :.: g) a -> a Source #
Foldable f => Foldable (M1 i c f) Source # Since: base-4.9.0.0
Instance detailsDefined in Data.Foldable Methodsfold :: Monoid m => M1 i c f m -> m Source #foldMap :: Monoid m => (a -> m) -> M1 i c f a -> m Source #foldMap' :: Monoid m => (a -> m) -> M1 i c f a -> m Source #foldr :: (a -> b -> b) -> b -> M1 i c f a -> b Source #foldr' :: (a -> b -> b) -> b -> M1 i c f a -> b Source #foldl :: (b -> a -> b) -> b -> M1 i c f a -> b Source #foldl' :: (b -> a -> b) -> b -> M1 i c f a -> b Source #foldr1 :: (a -> a -> a) -> M1 i c f a -> a Source #foldl1 :: (a -> a -> a) -> M1 i c f a -> a Source #toList :: M1 i c f a -> [a] Source #null :: M1 i c f a -> Bool Source #length :: M1 i c f a -> Int Source #elem :: Eq a => a -> M1 i c f a -> Bool Source #maximum :: Ord a => M1 i c f a -> a Source #minimum :: Ord a => M1 i c f a -> a Source #sum :: Num a => M1 i c f a -> a Source #product :: Num a => M1 i c f a -> a Source #

Special biased folds

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

Right-to-left monadic fold over the elements of a structure.

Given a structure t with elements (a, b, c, ..., x, y), the result of a fold with an operator function f is equivalent to:

foldrM f z t = do yy <- f y z xx <- f x yy ... bb <- f b cc aa <- f a bb return aa -- Just @return z@ when the structure is empty

For a Monad m, given two functions f1 :: a -> m b and f2 :: b -> m c, their Kleisli composition (f1 >=> f2) :: a -> m c is defined by:

(f1 >=> f2) a = f1 a >>= f2

Another way of thinking about foldrM is that it amounts to an application to z of a Kleisli composition:

foldrM f z t = f y >=> f x >=> ... >=> f b >=> f a $ z

The monadic effects of foldrM are sequenced from right to left, and e.g. folds of infinite lists will diverge.

If at some step the bind operator (`[>>=](Control-Monad.html#v:-62--62--61- "Control.Monad")`) short-circuits (as with, e.g.,[mzero](Control-Monad.html#v:mzero "Control.Monad") in a [MonadPlus](Control-Monad.html#t:MonadPlus "Control.Monad")), the evaluated effects will be from a tail of the element sequence. If you want to evaluate the monadic effects in left-to-right order, or perhaps be able to short-circuit after an initial sequence of elements, you'll need to use [foldlM](Data-Foldable.html#v:foldlM "Data.Foldable") instead.

If the monadic effects don't short-circuit, the outermost application off is to the leftmost element a, so that, ignoring effects, the result looks like a right fold:

a f (b f (c f (... (x f (y f z))))).

Examples

Expand

Basic usage:

>>> let f i acc = do { print i ; return $ i : acc }** **>>> **foldrM f [] [0..3]** ****3 2 1 0 [0,1,2,3]

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

Left-to-right monadic fold over the elements of a structure.

Given a structure t with elements (a, b, ..., w, x, y), the result of a fold with an operator function f is equivalent to:

foldlM f z t = do aa <- f z a bb <- f aa b ... xx <- f ww x yy <- f xx y return yy -- Just @return z@ when the structure is empty

For a Monad m, given two functions f1 :: a -> m b and f2 :: b -> m c, their Kleisli composition (f1 >=> f2) :: a -> m c is defined by:

(f1 >=> f2) a = f1 a >>= f2

Another way of thinking about foldlM is that it amounts to an application to z of a Kleisli composition:

foldlM f z t = flip f a >=> flip f b >=> ... >=> flip f x >=> flip f y $ z

The monadic effects of foldlM are sequenced from left to right.

If at some step the bind operator (`[>>=](Control-Monad.html#v:-62--62--61- "Control.Monad")`) short-circuits (as with, e.g.,[mzero](Control-Monad.html#v:mzero "Control.Monad") in a [MonadPlus](Control-Monad.html#t:MonadPlus "Control.Monad")), the evaluated effects will be from an initial segment of the element sequence. If you want to evaluate the monadic effects in right-to-left order, or perhaps be able to short-circuit after processing a tail of the sequence of elements, you'll need to use [foldrM](Data-Foldable.html#v:foldrM "Data.Foldable") instead.

If the monadic effects don't short-circuit, the outermost application off is to the rightmost element y, so that, ignoring effects, the result looks like a left fold:

((((z f a) f b) ... f w) f x) f y

Examples

Expand

Basic usage:

>>> let f a e = do { print e ; return $ e : a }** **>>> **foldlM f [] [0..3]** ****0 1 2 3 [3,2,1,0]

Folding actionsApplicative actions

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

Map each element of a structure to an [Applicative](Control-Applicative.html#t:Applicative "Control.Applicative") action, evaluate these actions from left to right, and ignore the results. For a version that doesn't ignore the results see [traverse](Data-Traversable.html#v:traverse "Data.Traversable").

[traverse_](Data-Foldable.html#v:traverse%5F "Data.Foldable") is just like [mapM_](Data-Foldable.html#v:mapM%5F "Data.Foldable"), but generalised to [Applicative](Control-Applicative.html#t:Applicative "Control.Applicative") actions.

Examples

Expand

Basic usage:

>>> traverse_ print ["Hello", "world", "!"]** **"Hello" "world" "!"

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](Data-Traversable.html#v:sequenceA "Data.Traversable").

[sequenceA_](Data-Foldable.html#v:sequenceA%5F "Data.Foldable") is just like [sequence_](Data-Foldable.html#v:sequence%5F "Data.Foldable"), but generalised to [Applicative](Control-Applicative.html#t:Applicative "Control.Applicative") actions.

Examples

Expand

Basic usage:

>>> sequenceA_ [print "Hello", print "world", print "!"]** **"Hello" "world" "!"

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](Data-Traversable.html#v:mapM "Data.Traversable").

[mapM_](Data-Foldable.html#v:mapM%5F "Data.Foldable") is just like [traverse_](Data-Foldable.html#v:traverse%5F "Data.Foldable"), but specialised to 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](Data-Traversable.html#v:sequence "Data.Traversable").

[sequence_](Data-Foldable.html#v:sequence%5F "Data.Foldable") is just like [sequenceA_](Data-Foldable.html#v:sequenceA%5F "Data.Foldable"), but specialised to monadic actions.

Specialized folds

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

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

Examples

Expand

Basic usage:

>>> concat (Just [1, 2, 3])** **[1,2,3]

>>> concat (Left 42)** **[]

>>> concat [[1, 2, 3], [4, 5], [6], []]** **[1,2,3,4,5,6]

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

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

Examples

Expand

Basic usage:

>>> concatMap (take 3) [[1..], [10..], [100..], [1000..]]** **[1,2,3,10,11,12,100,101,102,1000,1001,1002]

>>> concatMap (take 3) (Just [1..])** **[1,2,3]

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

[and](Data-Foldable.html#v:and "Data.Foldable") returns the conjunction of a container of Bools. For the result to be [True](Data-Bool.html#v:True "Data.Bool"), the container must be finite; [False](Data-Bool.html#v:False "Data.Bool"), however, results from a [False](Data-Bool.html#v:False "Data.Bool") value finitely far from the left end.

Examples

Expand

Basic usage:

>>> **and []** ****True

>>> **and [True]** ****True

>>> **and [False]** ****False

>>> **and [True, True, False]** ****False

>>> **and (False : repeat True) -- Infinite list [False,True,True,True,...** ****False

>>> and (repeat True)** *** Hangs forever *

or :: Foldable t => t Bool -> Bool Source #

[or](Data-Foldable.html#v:or "Data.Foldable") returns the disjunction of a container of Bools. For the result to be [False](Data-Bool.html#v:False "Data.Bool"), the container must be finite; [True](Data-Bool.html#v:True "Data.Bool"), however, results from a [True](Data-Bool.html#v:True "Data.Bool") value finitely far from the left end.

Examples

Expand

Basic usage:

>>> **or []** ****False

>>> **or [True]** ****True

>>> **or [False]** ****False

>>> **or [True, True, False]** ****True

>>> **or (True : repeat False) -- Infinite list [True,False,False,False,...** ****True

>>> or (repeat False)** *** Hangs forever *

any :: Foldable t => (a -> Bool) -> t a -> Bool Source #

Determines whether any element of the structure satisfies the predicate.

Examples

Expand

Basic usage:

>>> **any (> 3) []** ****False

>>> **any (> 3) [1,2]** ****False

>>> **any (> 3) [1,2,3,4,5]** ****True

>>> **any (> 3) [1..]** ****True

>>> any (> 3) [0, -1..]** *** Hangs forever *

all :: Foldable t => (a -> Bool) -> t a -> Bool Source #

Determines whether all elements of the structure satisfy the predicate.

Examples

Expand

Basic usage:

>>> **all (> 3) []** ****True

>>> **all (> 3) [1,2]** ****False

>>> **all (> 3) [1,2,3,4,5]** ****False

>>> **all (> 3) [1..]** ****False

>>> all (> 3) [4..]** *** Hangs forever *

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.

Examples

Expand

Basic usage:

>>> `` maximumBy (compare on length) ["Hello", "World", "!", "Longest", "bar"] ``"Longest"

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.

Examples

Expand

Basic usage:

>>> `` minimumBy (compare on length) ["Hello", "World", "!", "Longest", "bar"] ``"!"

Searches

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

[notElem](Data-Foldable.html#v:notElem "Data.Foldable") is the negation of [elem](Data-Foldable.html#v:elem "Data.Foldable").

Examples

Expand

Basic usage:

>>> `` 3 notElem [] **``**True

>>> `` 3 notElem [1,2] **``**True

>>> `` 3 notElem [1,2,3,4,5] **``**False

For infinite structures, [notElem](Data-Foldable.html#v:notElem "Data.Foldable") terminates if the value exists at a finite distance from the left side of the structure:

>>> `` 3 notElem [1..] **``**False

>>> `` 3 notElem ([4..] ++ [3]) ``* Hangs forever *

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

The [find](Data-Foldable.html#v:find "Data.Foldable") function takes a predicate and a structure and returns the leftmost element of the structure matching the predicate, or[Nothing](Data-Maybe.html#v:Nothing "Data.Maybe") if there is no such element.

Examples

Expand

Basic usage:

>>> **find (> 42) [0, 5..]** ****Just 45

>>> **find (> 12) [1..7]** ****Nothing

Overview

The Foldabla class generalises some common Data.List functions to structures that can be reduced to a summary value one element at a time.

Left and right folds

The contribution of each element to the final result is combined with an accumulator via a suitable operator. The operator may be explicitly provided by the caller as with [foldr](Data-Foldable.html#v:foldr "Data.Foldable") or may be implicit as in [length](Data-Foldable.html#v:length "Data.Foldable"). In the case of [foldMap](Data-Foldable.html#v:foldMap "Data.Foldable"), the caller provides a function mapping each element into a suitable [Monoid](Data-Monoid.html#t:Monoid "Data.Monoid"), which makes it possible to merge the per-element contributions via that monoid's [mappend](Data-Monoid.html#v:mappend "Data.Monoid") function.

A key distinction is between left-associative and right-associative folds:

These two types of folds are typified by the left-associative strict[foldl'](Data-Foldable.html#v:foldl-39- "Data.Foldable") and the right-associative lazy [foldr](Data-Foldable.html#v:foldr "Data.Foldable").

[foldl'](Data-Foldable.html#v:foldl-39- "Data.Foldable") :: Foldable t => (b -> a -> b) -> b -> t a -> b [foldr](Data-Foldable.html#v:foldr "Data.Foldable") :: Foldable t => (a -> b -> b) -> b -> t a -> b

Example usage:

>>> **foldl' (+) 0 [1..100]** ****5050 >>> **foldr (&&) True (repeat False)** ****False

The first argument of both is an explicit operator that merges the contribution of an element of the structure with a partial fold over, respectively, either the preceding or following elements of the structure.

The second argument of both is an initial accumulator value z of typeb. This is the result of the fold when the structure is empty. When the structure is non-empty, this is the accumulator value merged with the first element in left-associative folds, or with the last element in right-associative folds.

The third and final argument is a Foldable structure containing elements(a, b, c, …).

Expectation of efficient left-to-right iteration

Foldable structures are generally expected to be efficiently iterable from left to right. Right-to-left iteration may be substantially more costly, or even impossible (as with, for example, infinite lists). The text in the sections that follow that suggests performance differences between left-associative and right-associative folds assumes left-handed structures in which left-to-right iteration is cheaper than right-to-left iteration.

In finite structures for which right-to-left sequencing no less efficient than left-to-right sequencing, there is no inherent performance distinction between left-associative and right-associative folds. If the structure'sFoldable instance takes advantage of this symmetry to also make strict right folds space-efficient and lazy left folds corecursive, one need only take care to choose either a strict or lazy method for the task at hand.

Foldable instances for symmetric structures should strive to provide equally performant left-associative and right-associative interfaces. The main limitations are:

Thus, for some foldable structures [foldr'](Data-Foldable.html#v:foldr-39- "Data.Foldable") is just as efficient as [foldl'](Data-Foldable.html#v:foldl-39- "Data.Foldable") for strict reduction, and [foldl](Data-Foldable.html#v:foldl "Data.Foldable") may be just as appropriate for corecursive folds as [foldr](Data-Foldable.html#v:foldr "Data.Foldable").

Finally, in some less common structures (e.g. snoc lists) right to left iterations are cheaper than left to right. Such structures are poor candidates for a Foldable instance, and are perhaps best handled via their type-specific interfaces. If nevertheless a Foldable instance is provided, the material in the sections that follow applies to these also, by replacing each method with one with the opposite associativity (when available) and switching the order of arguments in the fold's operator.

You may need to pay careful attention to strictness of the fold's operator when its strictness is different between its first and second argument. For example, while (`[+](Prelude.html#v:-43- "Prelude")`) is expected to be commutative and strict in both arguments, the list concatenation operator (`[++](GHC-List.html#v:-43--43- "GHC.List")`) is not commutative and is only strict in the initial constructor of its first argument. The fold:

myconcat xs = foldr (\a b -> a ++ b) [] xs

is subtantially cheaper (linear in the length of the consumed portion of the final list, thus e.g. constant time/space for just the first element) than:

revconcat xs = foldr (\a b -> b ++ a) [] xs

In which the total cost scales up with both the number of lists combined and the number of elements ultimately consumed. A more efficient way to combine lists in reverse order, is to use:

revconcat = foldr (++) [] . reverse

Recursive and corecursive reduction

As observed in the above description of left and right folds, there are three general ways in which a structure can be reduced to a summary value:

Whether a fold is recursive, corecursive or short-circuiting can depend on both the method chosen to perform the fold and on the operator passed to that method (which may be implicit, as with the [mappend](Data-Monoid.html#v:mappend "Data.Monoid") method of a monoid instance).

There are also hybrid cases, where the method and/or operator are not well suited to the task at hand, resulting in a fold that fails to yield incremental results until the entire input is processed, or fails to strictly evaluate results as it goes, deferring all the work to the evaluation of a large final thunk. Such cases should be avoided, either by selecting a more appropriate Foldable method, or by tailoring the operator to the chosen method.

The distinction between these types of folds is critical, both in deciding which Foldable method to use to perform the reduction efficiently, and in writing Foldable instances for new structures. Below is a more detailed overview of each type.

Strict recursive folds

Common examples of strict recursive reduction are the various aggregate functions, like [sum](Data-Foldable.html#v:sum "Data.Foldable"), [product](Data-Foldable.html#v:product "Data.Foldable"), [length](Data-Foldable.html#v:length "Data.Foldable"), as well as more complex summaries such as frequency counts. These functions return only a single value after processing the entire input structure. In such cases, lazy processing of the tail of the input structure is generally not only unnecessary, but also inefficient. Thus, these and similar folds should be implemented in terms of strict left-associative Foldable methods (typically[foldl'](Data-Foldable.html#v:foldl-39- "Data.Foldable")) to perform an efficient reduction in constant space.

Conversely, an implementation of Foldable for a new structure should ensure that [foldl'](Data-Foldable.html#v:foldl-39- "Data.Foldable") actually performs a strict left-associative reduction.

The [foldMap'](Data-Foldable.html#v:foldMap-39- "Data.Foldable") method is a special case of [foldl'](Data-Foldable.html#v:foldl-39- "Data.Foldable"), in which the initial accumulator is [mempty](Data-Monoid.html#v:mempty "Data.Monoid") and the operator is mappend . f, where f maps each input element into the [Monoid](Data-Monoid.html#t:Monoid "Data.Monoid") in question. Therefore, [foldMap'](Data-Foldable.html#v:foldMap-39- "Data.Foldable") is an appropriate choice under essentially the same conditions as [foldl'](Data-Foldable.html#v:foldl-39- "Data.Foldable"), and its implementation for a given Foldable structure should also be a strict left-associative reduction.

While the examples below are not necessarily the most optimal definitions of the intended functions, they are all cases in which [foldMap'](Data-Foldable.html#v:foldMap-39- "Data.Foldable") is far more appropriate (as well as more efficient) than the lazy [foldMap](Data-Foldable.html#v:foldMap "Data.Foldable").

length = getSum . foldMap' (const (Sum 1)) sum = getSum . foldMap' Sum product = getProduct . foldMap' Product

[ The actual default definitions employ coercions to optimise out[getSum](Data-Monoid.html#v:getSum "Data.Monoid") and [getProduct](Data-Monoid.html#v:getProduct "Data.Monoid"). ]

List of strict functions

The full list of strict recursive functions in this module is:

Lazy corecursive folds

Common examples of lazy corecursive reduction are functions that map and flatten a structure to a lazy stream of result values, i.e. an iterator over the transformed input elements. In such cases, it is important to choose a Foldable method that is lazy in the tail of the structure, such as [foldr](Data-Foldable.html#v:foldr "Data.Foldable") (or [foldMap](Data-Foldable.html#v:foldMap "Data.Foldable"), if the result Monoid has a lazy [mappend](Data-Monoid.html#v:mappend "Data.Monoid") as with e.g. ByteString Builders).

Conversely, an implementation of [foldr](Data-Foldable.html#v:foldr "Data.Foldable") for a structure that can accommodate a large (and possibly unbounded) number of elements is expected to be lazy in the tail of the input, allowing operators that are lazy in the accumulator to yield intermediate results incrementally. Such folds are right-associative, with the tail of the stream returned as a lazily evaluated component of the result (an element of a tuple or some other non-strict constructor, e.g. the (:) constructor for lists).

The toList function below lazily transforms a Foldable structure to a List. Note that this transformation may be lossy, e.g. for a keyed container (Map, HashMap, …) the output stream holds only the values, not the keys. Lossless transformations to/from lists of (key, value) pairs are typically available in the modules for the specific container types.

toList = foldr (:) []

A more complex example is concatenation of a list of lists expressed as a nested right fold (bypassing (`[++](GHC-List.html#v:-43--43- "GHC.List")`)). We can check that the definition is indeed lazy by folding an infinite list of lists, and taking an initial segment.

>>> myconcat = foldr (\x z -> foldr (:) z x) []** **>>> take 15 $ myconcat $ map (\i -> [0..i]) [0..]** **[0,0,1,0,1,2,0,1,2,3,0,1,2,3,4]

Of course in this case another way to achieve the same result is via a list comprehension:

myconcat xss = [x | xs <- xss, x <- xs]

List of lazy functions

The full list of lazy corecursive functions in this module is:

Short-circuit folds

Examples of short-cicuit reduction include various boolean predicates that test whether some or all the elements of a structure satisfy a given condition. Because these don't necessarily consume the entire list, they typically employ [foldr](Data-Foldable.html#v:foldr "Data.Foldable") with an operator that is conditionally strict in its second argument. Once the termination condition is met the second argument (tail of the input structure) is ignored. No result is returned until that happens.

The key distinguishing feature of these folds is conditional strictness in the second argument, it is sometimes evaluated and sometimes not.

The simplest (degenerate case) of these is [null](Data-Foldable.html#v:null "Data.Foldable"), which determines whether a structure is empty or not. This only needs to look at the first element, and only to the extent of whether it exists or not, and not its value. In this case termination is guaranteed, and infinite input structures are fine. Its default definition is of course in terms of the lazy [foldr](Data-Foldable.html#v:foldr "Data.Foldable"):

null = foldr (_ _ -> False) True

A more general example is [any](Data-Foldable.html#v:any "Data.Foldable"), which applies a predicate to each input element in turn until it finds the first one for which the predicate is true, at which point it returns success. If, in an infinite input stream the predicate is false for all the elements, [any](Data-Foldable.html#v:any "Data.Foldable") will not terminate, but since it runs in constant space, it typically won't run out of memory, it'll just loop forever.

List of short-circuit functions

The full list of short-circuit folds in this module is:

Hybrid folds

The below folds, are neither strict reductions that produce a final answer in constant space, nor lazy corecursions, and so have limited applicability. They do have specialised uses, but are best avoided when in doubt.

[foldr'](Data-Foldable.html#v:foldr-39- "Data.Foldable") :: Foldable t => (a -> b -> b) -> b -> t a -> b [foldl](Data-Foldable.html#v:foldl "Data.Foldable") :: Foldable t => (b -> a -> b) -> b -> t a -> b [foldl1](Data-Foldable.html#v:foldl1 "Data.Foldable") :: Foldable t => (a -> a -> a) -> t a -> a [foldrM](Data-Foldable.html#v:foldrM "Data.Foldable") :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m b

The lazy left-folds (used corecursively) and [foldrM](Data-Foldable.html#v:foldrM "Data.Foldable") (used to sequence actions right-to-left) can be performant in structures whose Foldable instances take advantage of efficient right-to-left iteration to compute lazy left folds outside-in from the rightmost element.

The strict [foldr'](Data-Foldable.html#v:foldr-39- "Data.Foldable") is the least likely to be useful, structures that support efficient sequencing only right-to-left are not common.

Generative Recursion

So far, we have not discussed generative recursion. Unlike recursive reduction or corecursion, instead of processing a sequence of elements already in memory, generative recursion involves producing a possibly unbounded sequence of values from an initial seed value. The canonical example of this is [unfoldr](Data-List.html#v:unfoldr "Data.List") for Lists, with variants available for Vectors and various other structures.

A key issue with lists, when used generatively as iterators, rather than as poor-man's containers (see [1]), is that such iterators tend to consume memory when used more than once. A single traversal of a list-as-iterator will run in constant space, but as soon as the list is retained for reuse, its entire element sequence is stored in memory, and the second traversal reads the copy, rather than regenerates the elements. It is sometimes better to recompute the elements rather than memoise the list.

Memoisation happens because the built-in Haskell list [] is represented as data, either empty or a cons-cell holding the first element and the tail of the list. The Foldable class enables a variant representation of iterators as functions, which take an operator and a starting accumulator and output a summary result.

The fmlist package takes this approach, by representing a list via its [foldMap](Data-Foldable.html#v:foldMap "Data.Foldable") action.

Below we implement an analogous data structure using a representation based on [foldr](Data-Foldable.html#v:foldr "Data.Foldable"). This is an example of Church encoding (named after Alonzo Church, inventor of the lambda calculus).

{-# LANGUAGE RankNTypes #-} newtype FRList a = FR { unFR :: forall b. (a -> b -> b) -> b -> b }

The unFR field of this type is essentially its [foldr](Data-Foldable.html#v:foldr "Data.Foldable") method with the list as its first rather than last argument. Thus we immediately get a Foldable instance (and a [toList](Data-Foldable.html#v:toList "Data.Foldable") function mapping an FRList to a regular list).

instance Foldable FRList where foldr f z l = unFR l f z -- With older versions of @base@, also define sum, product, ... -- to ensure use of the strict 'foldl''. -- sum = foldl' (+) 0 -- ...

We can convert a regular list to an FRList with:

fromList :: [a] -> FRList a fromList as = FRList $ \ f z -> foldr f z as

However, reuse of an FRList obtained in this way will typically memoise the underlying element sequence. Instead, we can define**FRList** terms directly:

-- | Immediately return the initial accumulator nil :: FRList a nil = FRList $ \ _ z -> z {-# INLINE nil #-}

-- | Fold the tail to use as an accumulator with the new initial element cons :: a -> FRList a -> FRList a cons a l = FRList $ \ f z -> f a (unFR l f z) {-# INLINE cons #-}

More crucially, we can also directly define the key building block for generative recursion:

-- | Generative recursion, dual to foldr. unfoldr :: (s -> Maybe (a, s)) -> s -> FRList a unfoldr g s0 = FR generate where generate f z = loop s0 where loop s | Just (a, t) <- g s = f a (loop t) | otherwise = z {-# INLINE unfoldr #-}

Which can, for example, be specialised to number ranges:

-- | Generate a range of consecutive integral values. range :: (Ord a, Integral a) => a -> a -> FRList a range lo hi = unfoldr (\s -> if s > hi then Nothing else Just (s, s+1)) lo {-# INLINE range #-}

The program below, when compiled with optimisation:

main :: IO () main = do let r :: FRList Int r = range 1 10000000 in print (sum r, length r)

produces the expected output with no noticeable garbage-collection, despite reuse of the FRList term r.

(50000005000000,10000000) 52,120 bytes allocated in the heap 3,320 bytes copied during GC 44,376 bytes maximum residency (1 sample(s)) 25,256 bytes maximum slop 3 MiB total memory in use (0 MB lost due to fragmentation)

The Weak Head Normal Form of an FRList is a lambda abstraction not a data value, and reuse does not lead to memoisation. Reuse of the iterator above is somewhat contrived, when computing multiple folds over a common list, you should generally traverse a list only once. The goal is to demonstrate that the separate computations of the [sum](Data-Foldable.html#v:sum "Data.Foldable") and[length](Data-Foldable.html#v:length "Data.Foldable") run efficiently in constant space, despite reuse. This would not be the case with the list [1..10000000].

This is, however, an artificially simple reduction. More typically, there are likely to be some allocations in the inner loop, but the temporary storage used will be garbage-collected as needed, and overall memory utilisation will remain modest and will not scale with the size of the list.

If we go back to built-in lists (i.e. []), but avoid reuse by performing reduction in a single pass, as below:

data PairS a b = P !a !b -- We define a strict pair datatype

main :: IO () main = do let l :: [Int] l = [1..10000000] in print $ average l where sumlen :: PairS Int Int -> Int -> PairS Int Int sumlen (P s l) a = P (s + a) (l + 1)

average is =
    let (P s l) = foldl' sumlen (P 0 0) is
     in (fromIntegral s :: Double) / fromIntegral l

the result is again obtained in constant space:

5000000.5 102,176 bytes allocated in the heap 3,320 bytes copied during GC 44,376 bytes maximum residency (1 sample(s)) 25,256 bytes maximum slop 3 MiB total memory in use (0 MB lost due to fragmentation)

(and, in fact, faster than with FRList by a small factor).

The [] list structure works as an efficient iterator when used just once. When space-leaks via list reuse are not a concern, and/or memoisation is actually desirable, the regular list implementation is likely to be faster. This is not a suggestion to replace all your uses of**[]** with a generative alternative.

The FRList type could be further extended with instances of [Functor](Data-Functor.html#t:Functor "Data.Functor"),[Applicative](Control-Applicative.html#t:Applicative "Control.Applicative"), [Monad](Control-Monad.html#t:Monad "Control.Monad"), [Alternative](Control-Applicative.html#t:Alternative "Control.Applicative"), etc., and could then provide a fully-featured list type, optimised for reuse without space-leaks. If, however, all that's required is space-efficient, re-use friendly iteration, less is perhaps more, and just Foldable may be sufficient.

Avoiding multi-pass folds

In applications where you want to compute a composite function of a structure, which requires more than one aggregate as an input, it is generally best to compute all the aggregates in a single pass, rather than to traverse the same structure repeatedly.

The foldl package implements a robust general framework for dealing with this situation. If you choose to to do it yourself, with a bit of care, the simplest cases are not difficult to handle directly. You just need to accumulate the individual aggregates as strict components of a single data type, and then apply a final transformation to it to extract the composite result. For example, computing an average requires computing both the [sum](Data-Foldable.html#v:sum "Data.Foldable") and the [length](Data-Foldable.html#v:length "Data.Foldable") of a (non-empty) structure and dividing the sum by the length:

import Data.Foldable (foldl')

data PairS a b = P !a !b -- We define a strict pair datatype

-- | Compute sum and length in a single pass, then reduce to the average. average :: (Foldable f, Fractional a) => f a -> a average xs = let sumlen (P s l) a = P (s + a) (l + 1 :: Int) (P s l) = foldl' sumlen (P 0 0) xs in s / fromIntegral l

The above example is somewhat contrived, some structures keep track of their length internally, and can return it in \(\mathcal{O}(1)\) time, so this particular recipe for averages is not always the most efficient. In general, composite aggregate functions of large structures benefit from single-pass reduction. This is especially the case when reuse of a list and memoisation of its elements is thereby avoided,

Defining instances

For many structures reasonably efficient Foldable instances can be derived automatically, by enabling the DeriveFoldable GHC extension. When this works, it is generally not necessary to define a custom instance by hand. Though in some cases one may be able to get slightly faster hand-tuned code, care is required to avoid producing slower code, or code that is not sufficiently lazy, strict or lawful.

The hand-crafted instances can get away with only defining one of [foldr](Data-Foldable.html#v:foldr "Data.Foldable") or[foldMap](Data-Foldable.html#v:foldMap "Data.Foldable"). All the other methods have default definitions in terms of one of these. The default definitions have the expected strictness and the expected asymptotic runtime and space costs, modulo small constant factors. If you choose to hand-tune, benchmarking is advised to see whether you're doing better than the default derived implementations, plus careful tests to ensure that the custom methods are correct.

Below we construct a Foldable instance for a data type representing a (finite) binary tree with depth-first traversal.

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

a suitable instance would be:

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

The Node case is a right fold of the left subtree whose initial value is a right fold of the rest of the tree.

For example, when f is (`:`), all three cases return an immediate value, respectively z or a cons cell holding x or l, with the remainder the structure, if any, encapsulated in a lazy thunk. This meets the expected efficient corecursive behaviour of [foldr](Data-Foldable.html#v:foldr "Data.Foldable").

Alternatively, one could define foldMap:

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

And indeed some efficiency may be gained by directly defining both, avoiding some indirection in the default definitions that express one in terms of the other. If you implement just one, likely [foldr](Data-Foldable.html#v:foldr "Data.Foldable") is the better choice.

A binary tree typically (when balanced, or randomly biased) provides equally efficient access to its left and right subtrees. This makes it possible to define a [foldl](Data-Foldable.html#v:foldl "Data.Foldable") optimised for corecursive folds with operators that are lazy in their first (left) argument.

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

foldMap f Empty = mempty foldMap f (Leaf x) = f x foldMap f (Node l k r) = foldMap f l <> f k <> foldMap f r

foldl f z Empty = z foldl f z (Leaf x) = f z x foldl f z (Node l k r) = foldl f (f (foldl f z l) k) r

Now left-to-right and right-to-left iteration over the structure elements are equally efficient (note the mirror-order output when using [foldl](Data-Foldable.html#v:foldl "Data.Foldable")):

>>> foldr (\e acc -> e : acc) [] (Node (Leaf 1) 2 (Leaf 3))** **[1,2,3] >>> foldl (\acc e -> e : acc) [] (Node (Leaf 1) 2 (Leaf 3))** **[3,2,1]

We can carry this further, and define more non-default methods...

The structure definition actually admits trees that are unbounded on either or both sides. The only fold that can plausibly terminate for a tree unbounded on both left and right is [null](Data-Foldable.html#v:null "Data.Foldable"), when defined as shown below. The default definition in terms of [foldr](Data-Foldable.html#v:foldr "Data.Foldable") diverges if the tree is unbounded on the left. Here we define a variant that avoids travelling down the tree to find the leftmost element and just examines the root node.

null Empty = True null _ = False

This is a sound choice also for finite trees.

In practice, unbounded trees are quite uncommon, and can barely be said to be Foldable. They would typically employ breadth first traversal, and would support only corecursive and short-circuit folds (diverge under strict reduction).

Returning to simpler instances, defined just in terms of [foldr](Data-Foldable.html#v:foldr "Data.Foldable"), it is somewhat surprising that a fairly efficient default implementation of the strict [foldl'](Data-Foldable.html#v:foldl-39- "Data.Foldable") is defined in terms of lazy [foldr](Data-Foldable.html#v:foldr "Data.Foldable") when only the latter is explicitly provided by the instance. It may be instructive to take a look at how this works.

Being strict by being lazy

Sometimes, it is useful for the result of applying [foldr](Data-Foldable.html#v:foldr "Data.Foldable") to be a_function_. This is done by mapping the structure elements to functions with the same argument and result types. The per-element functions are then composed to give the final result.

For example, we can flip the strict left fold [foldl'](Data-Foldable.html#v:foldl-39- "Data.Foldable") by writing:

foldl' f z xs = flippedFoldl' f xs z

with the function flippedFoldl' defined as below, with [seq](Prelude.html#v:seq "Prelude") used to ensure the strictness in the accumulator:

flippedFoldl' f [] z = z flippedFoldl' f (x : xs) z = z seq flippedFoldl' f xs (f z x)

Rewriting to use lambdas, this is:

flippedFoldl' f [] = \ b -> b flippedFoldl' f (x : xs) = \ b -> b seq r (f b x) where r = flippedFoldl' f xs

The above has the form of a right fold, enabling a rewrite to:

flippedFoldl' f = \ xs -> foldr f' id xs where f' x r = \ b -> b seq r (f b x)

We can now unflip this to get [foldl'](Data-Foldable.html#v:foldl-39- "Data.Foldable"):

foldl' f z = \ xs -> foldr f' id xs z -- \ xs -> flippedFoldl' f xs z where f' x r = \ b -> b seq r (f b x)

The function foldr f' id xs applied to z is built corecursively, and its terms are applied to an eagerly evaluated accumulator before further terms are applied to the result. As required, this runs in constant space, and can be optimised to an efficient loop.

(The actual definition of [foldl'](Data-Foldable.html#v:foldl-39- "Data.Foldable") labels the lambdas in the definition of**f'** above as oneShot, which enables further optimisations).

Laws

The type constructor [Endo](Data-Monoid.html#t:Endo "Data.Monoid") from Data.Monoid, associates with each type**b** the **newtype**-encapulated type of functions mapping b to itself. Functions from a type to itself are called endomorphisms, hence the name Endo. The type Endo b is a [Monoid](Data-Monoid.html#t:Monoid "Data.Monoid") under function composition:

newtype Endo b = Endo { appEndo :: b -> b } instance Semigroup Endo b where Endo f <> Endo g = Endo (f . g) instance Monoid Endo b where mempty = Endo id

For every [Monoid](Data-Monoid.html#t:Monoid "Data.Monoid") m, we also have a [Dual](Data-Monoid.html#t:Dual "Data.Monoid") monoid Dual m which combines elements in the opposite order:

newtype Dual m = Dual { getDual :: m } instance Semigroup m => Semigroup Dual m where Dual a <> Dual b = Dual (b <> a) instance Monoid m => Monoid Dual m where mempty = Dual mempty

With the above preliminaries out of the way, [Foldable](Data-Foldable.html#t:Foldable "Data.Foldable") instances are expected to satisfy the following laws:

The [foldr](Data-Foldable.html#v:foldr "Data.Foldable") method must be equivalent in value and strictness to replacing each element a of a [Foldable](Data-Foldable.html#t:Foldable "Data.Foldable") structure with Endo (f a), composing these via [foldMap](Data-Foldable.html#v:foldMap "Data.Foldable") and applying the result to the base case**z**:

foldr f z t = appEndo (foldMap (Endo . f) t ) z

Likewise, the [foldl](Data-Foldable.html#v:foldl "Data.Foldable") method must be equivalent in value and strictness to composing the functions flip f a in reverse order and applying the result to the base case:

foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z

When the elements of the structure are taken from a [Monoid](Data-Monoid.html#t:Monoid "Data.Monoid"), the defintion of [fold](Data-Foldable.html#v:fold "Data.Foldable") must agree with foldMap id:

fold = foldMap id

The [length](Data-Foldable.html#v:length "Data.Foldable") method must agree with a [foldMap](Data-Foldable.html#v:foldMap "Data.Foldable") mapping each element to**Sum 1** (The [Sum](Data-Monoid.html#t:Sum "Data.Monoid") type abstracts numbers as a monoid under addition).

length = getSum . foldMap (Sum . const 1)

sum, product, maximum, and minimum should all be essentially equivalent to foldMap forms, such as

sum = getSum . foldMap' Sum product = getProduct . foldMap' Product

but are generally more efficient when defined more directly as:

sum = foldl' (+) 0 product = foldl' (*) 1

If the [Foldable](Data-Foldable.html#t:Foldable "Data.Foldable") structure has a [Functor](Data-Functor.html#t:Functor "Data.Functor") instance, then for every function f mapping the elements into a [Monoid](Data-Monoid.html#t:Monoid "Data.Monoid"), it should satisfy:

foldMap f = fold . fmap f

which implies that

foldMap f . fmap g = foldMap (f . g)

Notes

Since [Foldable](Data-Foldable.html#t:Foldable "Data.Foldable") does not have [Functor](Data-Functor.html#t:Functor "Data.Functor") as a superclass, it is possible to define [Foldable](Data-Foldable.html#t:Foldable "Data.Foldable") instances for structures that constrain their element types. Therefore, Set can be [Foldable](Data-Foldable.html#t:Foldable "Data.Foldable"), even though sets keep their elements in ascending order. This requires the elements to be comparable, which precludes defining a [Functor](Data-Functor.html#t:Functor "Data.Functor") instance for Set.

The [Foldable](Data-Foldable.html#t:Foldable "Data.Foldable") class makes it possible to use idioms familiar from the List type with container structures that are better suited to the task at hand. This supports use of more appropriate [Foldable](Data-Foldable.html#t:Foldable "Data.Foldable") data types, such as Seq,Set, NonEmpty, etc., without requiring new idioms (see[1] for when not to use lists).

The more general methods of the [Foldable](Data-Foldable.html#t:Foldable "Data.Foldable") class are now exported by thePrelude in place of the original List-specific methods (see theFTP Proposal). The List-specific variants are still available in Data.List.

Surprises can arise from the Foldable instance of the 2-tuple (a,) which now behaves as a 1-element Foldable container in its second slot. In contexts where a specific monomorphic type is expected, and you want to be able to rely on type errors to guide refactoring, it may make sense to define and use less-polymorphic variants of some of the Foldable methods.

Below are two examples showing a definition of a reusable less-polymorphic[sum](Data-Foldable.html#v:sum "Data.Foldable") and a one-off in-line specialisation of [length](Data-Foldable.html#v:length "Data.Foldable"):

{-# LANGUAGE TypeApplications #-}

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

type SlowVector a = [a] slowLength :: SlowVector -> Int slowLength v = length @[] v

In both cases, if the data type to which the function is applied changes to something other than a list, the call-site will no longer compile until appropriate changes are made.

Generally linear-time elem

It is perhaps worth noting that since the [elem](Data-Foldable.html#v:elem "Data.Foldable") function in the Foldable class carries only an [Eq](Data-Eq.html#t:Eq "Data.Eq") constraint on the element type, search for the presence or absence of an element in the structure generally takes \(\mathcal{O}(n)\) time, even for ordered structures like Set that are potentially capable of performing the search faster. (The member function of the Set module carries an [Ord](Data-Ord.html#t:Ord "Data.Ord") constraint, and can perform the search in \(\mathcal{O}(log\ n)\) time).

An alternative to Foldable's [elem](Data-Foldable.html#v:elem "Data.Foldable") method is required in order to abstract potentially faster than linear search over general container structures. This can be achieved by defining an additional type class (e.g.HasMember below). Instances of such a type class (that are also[Foldable](Data-Foldable.html#t:Foldable "Data.Foldable")) can employ the [elem](Data-Foldable.html#v:elem "Data.Foldable") linear search as a last resort, when faster search is not supported.

{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}

import qualified Data.Set as Set

class Eq a => HasMember t a where member :: a -> t a -> Bool

instance Eq a => HasMember [] a where member = elem [...] instance Ord a => HasMember Set.Set a where member = Set.member

The above suggests that [elem](Data-Foldable.html#v:elem "Data.Foldable") may be a misfit in the [Foldable](Data-Foldable.html#t:Foldable "Data.Foldable") class. Alternative design ideas are solicited on GHC's bug tracker via issue#20421.

Note that some structure-specific optimisations may of course be possible directly in the corresponding Foldable instance, e.g. with Set the size of the set is known in advance, without iterating to count the elements, and its [length](Data-Foldable.html#v:length "Data.Foldable") instance takes advantage of this to return the size directly.

See also