Copyright | (c) 2018-2023 Kowainik |
---|---|
License | MIT |
Maintainer | Kowainik <xrom.xkov@gmail.com> |
Stability | Stable |
Portability | Portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Reexports Data.Foldable and Data.Traversable.
Synopsis
- class Foldable (t :: Type -> Type) where
- concat :: Foldable t => t [a] -> [a]
- and :: Foldable t => t Bool -> Bool
- or :: Foldable t => t Bool -> Bool
- any :: Foldable t => (a -> Bool) -> t a -> Bool
- all :: Foldable t => (a -> Bool) -> t a -> Bool
- concatMap :: Foldable t => (a -> [b]) -> t a -> [b]
- foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
- traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f ()
- for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f ()
- mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m ()
- sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f ()
- sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
- asum :: (Foldable t, Alternative f) => t (f a) -> f a
- find :: Foldable t => (a -> Bool) -> t a -> Maybe a
- class (Functor t, Foldable t) => Traversable (t :: Type -> Type) where
- traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
- sequenceA :: Applicative f => t (f a) -> f (t a)
- mapM :: Monad m => (a -> m b) -> t a -> m (t b)
- sequence :: Monad m => t (m a) -> m (t a)
- forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
- mapAccumL :: Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b)
- mapAccumR :: Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b)
- class Bifoldable (p :: Type -> Type -> Type) where
- bifoldr' :: Bifoldable t => (a -> c -> c) -> (b -> c -> c) -> c -> t a b -> c
- bifoldrM :: (Bifoldable t, Monad m) => (a -> c -> m c) -> (b -> c -> m c) -> c -> t a b -> m c
- bifoldl' :: Bifoldable t => (a -> b -> a) -> (a -> c -> a) -> a -> t b c -> a
- bifoldlM :: (Bifoldable t, Monad m) => (a -> b -> m a) -> (a -> c -> m a) -> a -> t b c -> m a
- bitraverse_ :: (Bifoldable t, Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f ()
- bifor_ :: (Bifoldable t, Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f ()
- bisequence_ :: (Bifoldable t, Applicative f) => t (f a) (f b) -> f ()
- biasum :: (Bifoldable t, Alternative f) => t (f a) (f a) -> f a
- biList :: Bifoldable t => t a a -> [a]
- binull :: Bifoldable t => t a b -> Bool
- bilength :: Bifoldable t => t a b -> Int
- bielem :: (Bifoldable t, Eq a) => a -> t a a -> Bool
- biand :: Bifoldable t => t Bool Bool -> Bool
- bior :: Bifoldable t => t Bool Bool -> Bool
- biany :: Bifoldable t => (a -> Bool) -> (b -> Bool) -> t a b -> Bool
- biall :: Bifoldable t => (a -> Bool) -> (b -> Bool) -> t a b -> Bool
- bifind :: Bifoldable t => (a -> Bool) -> t a a -> Maybe a
- class (Bifunctor t, Bifoldable t) => Bitraversable (t :: Type -> Type -> Type) where
- bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> t a b -> f (t c d)
- bifor :: (Bitraversable t, Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f (t c d)
- bisequence :: (Bitraversable t, Applicative f) => t (f a) (f b) -> f (t a b)
- bimapDefault :: Bitraversable t => (a -> b) -> (c -> d) -> t a c -> t b d
- bifoldMapDefault :: (Bitraversable t, Monoid m) => (a -> m) -> (b -> m) -> t a b -> m
Foldable
reexports
class Foldable (t :: Type -> Type) where #
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 of Data.Foldable.
For the class laws see the Laws section of Data.Foldable.
fold :: Monoid m => t m -> m #
Given a structure with elements whose type is a Monoid
, combine them
via the monoid's (
operator. This fold is right-associative and
lazy in the accumulator. When you need a strict left-associative fold,
use <>
)foldMap'
instead, with id
as the map.
Examples
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
(
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 #
Map each element of the structure into a monoid, and combine the
results with (
. This fold is right-associative and lazy in the
accumulator. For strict left-associative folds consider <>
)foldMap'
instead.
Examples
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 (
is lazy in its second argument, <>
)foldMap
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 #
A left-associative variant of foldMap
that is strict in the
accumulator. Use this method for strict reduction when partial
results are merged via (
.<>
)
Examples
Define a Monoid
over finite bit strings under xor
. Use it to
strictly compute the xor
of a list of 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 #
Right-associative fold of a structure, lazy in the accumulator.
In the case of lists, foldr
, when applied to a binary operator, a
starting value (typically the right-identity of the operator), and a
list, reduces the list using the binary operator, from right to left:
foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)
Note that since the head of the resulting expression is produced by an
application of the operator to the first element of the list, given an
operator lazy in its right argument, foldr
can produce a terminating
expression from an unbounded list.
For a general Foldable
structure this should be semantically identical
to,
foldr f z =foldr
f z .toList
Examples
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
to infinite structures usually doesn't terminate.
It may still terminate under one of the following conditions:
- the folding function is short-circuiting
- the folding function is lazy on its second argument
Short-circuiting
(
short-circuits on ||
)True
values, so the following terminates
because there is a True
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
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
, but []
is more clear):
>>>
take 5 $ foldr (\i acc -> i : fmap (+3) acc) [] (repeat 1)
[1,4,7,10,13]
foldl' :: (b -> a -> b) -> b -> t a -> b #
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
).
For a general Foldable
structure this should be semantically identical
to,
foldl' f z =foldl'
f z .toList
Since: base-4.6.0.0
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
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
is the identity:
>>>
toList [1, 2, 3]
[1,2,3]
Since: base-4.8.0.0
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
Basic usage:
>>>
null []
True
>>>
null [1]
False
null
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
Returns the size/length of a finite structure as an 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
Basic usage:
>>>
length []
0
>>>
length ['a', 'b', 'c']
3>>>
length [1..]
* Hangs forever *
Since: base-4.8.0.0
Instances
Foldable ZipList | Since: base-4.9.0.0 |
Defined in Control.Applicative fold :: Monoid m => ZipList m -> m # foldMap :: Monoid m => (a -> m) -> ZipList a -> m # foldMap' :: Monoid m => (a -> m) -> ZipList a -> m # foldr :: (a -> b -> b) -> b -> ZipList a -> b # foldr' :: (a -> b -> b) -> b -> ZipList a -> b # foldl :: (b -> a -> b) -> b -> ZipList a -> b # foldl' :: (b -> a -> b) -> b -> ZipList a -> b # foldr1 :: (a -> a -> a) -> ZipList a -> a # foldl1 :: (a -> a -> a) -> ZipList a -> a # elem :: Eq a => a -> ZipList a -> Bool # maximum :: Ord a => ZipList a -> a # minimum :: Ord a => ZipList a -> a # | |
Foldable Complex | Since: base-4.9.0.0 |
Defined in Data.Complex fold :: Monoid m => Complex m -> m # foldMap :: Monoid m => (a -> m) -> Complex a -> m # foldMap' :: Monoid m => (a -> m) -> Complex a -> m # foldr :: (a -> b -> b) -> b -> Complex a -> b # foldr' :: (a -> b -> b) -> b -> Complex a -> b # foldl :: (b -> a -> b) -> b -> Complex a -> b # foldl' :: (b -> a -> b) -> b -> Complex a -> b # foldr1 :: (a -> a -> a) -> Complex a -> a # foldl1 :: (a -> a -> a) -> Complex a -> a # elem :: Eq a => a -> Complex a -> Bool # maximum :: Ord a => Complex a -> a # minimum :: Ord a => Complex a -> a # | |
Foldable Identity | Since: base-4.8.0.0 |
Defined in Data.Functor.Identity fold :: Monoid m => Identity m -> m # foldMap :: Monoid m => (a -> m) -> Identity a -> m # foldMap' :: Monoid m => (a -> m) -> Identity a -> m # foldr :: (a -> b -> b) -> b -> Identity a -> b # foldr' :: (a -> b -> b) -> b -> Identity a -> b # foldl :: (b -> a -> b) -> b -> Identity a -> b # foldl' :: (b -> a -> b) -> b -> Identity a -> b # foldr1 :: (a -> a -> a) -> Identity a -> a # foldl1 :: (a -> a -> a) -> Identity a -> a # elem :: Eq a => a -> Identity a -> Bool # maximum :: Ord a => Identity a -> a # minimum :: Ord a => Identity a -> a # | |
Foldable First | Since: base-4.8.0.0 |
Defined in Data.Foldable fold :: Monoid m => First m -> m # foldMap :: Monoid m => (a -> m) -> First a -> m # foldMap' :: Monoid m => (a -> m) -> First a -> m # foldr :: (a -> b -> b) -> b -> First a -> b # foldr' :: (a -> b -> b) -> b -> First a -> b # foldl :: (b -> a -> b) -> b -> First a -> b # foldl' :: (b -> a -> b) -> b -> First a -> b # foldr1 :: (a -> a -> a) -> First a -> a # foldl1 :: (a -> a -> a) -> First a -> a # elem :: Eq a => a -> First a -> Bool # maximum :: Ord a => First a -> a # minimum :: Ord a => First a -> a # | |
Foldable Last | Since: base-4.8.0.0 |
Defined in Data.Foldable fold :: Monoid m => Last m -> m # foldMap :: Monoid m => (a -> m) -> Last a -> m # foldMap' :: Monoid m => (a -> m) -> Last a -> m # foldr :: (a -> b -> b) -> b -> Last a -> b # foldr' :: (a -> b -> b) -> b -> Last a -> b # foldl :: (b -> a -> b) -> b -> Last a -> b # foldl' :: (b -> a -> b) -> b -> Last a -> b # foldr1 :: (a -> a -> a) -> Last a -> a # foldl1 :: (a -> a -> a) -> Last a -> a # elem :: Eq a => a -> Last a -> Bool # maximum :: Ord a => Last a -> a # | |
Foldable Down | Since: base-4.12.0.0 |
Defined in Data.Foldable fold :: Monoid m => Down m -> m # foldMap :: Monoid m => (a -> m) -> Down a -> m # foldMap' :: Monoid m => (a -> m) -> Down a -> m # foldr :: (a -> b -> b) -> b -> Down a -> b # foldr' :: (a -> b -> b) -> b -> Down a -> b # foldl :: (b -> a -> b) -> b -> Down a -> b # foldl' :: (b -> a -> b) -> b -> Down a -> b # foldr1 :: (a -> a -> a) -> Down a -> a # foldl1 :: (a -> a -> a) -> Down a -> a # elem :: Eq a => a -> Down a -> Bool # maximum :: Ord a => Down a -> a # | |
Foldable First | Since: base-4.9.0.0 |
Defined in Data.Semigroup fold :: Monoid m => First m -> m # foldMap :: Monoid m => (a -> m) -> First a -> m # foldMap' :: Monoid m => (a -> m) -> First a -> m # foldr :: (a -> b -> b) -> b -> First a -> b # foldr' :: (a -> b -> b) -> b -> First a -> b # foldl :: (b -> a -> b) -> b -> First a -> b # foldl' :: (b -> a -> b) -> b -> First a -> b # foldr1 :: (a -> a -> a) -> First a -> a # foldl1 :: (a -> a -> a) -> First a -> a # elem :: Eq a => a -> First a -> Bool # maximum :: Ord a => First a -> a # minimum :: Ord a => First a -> a # | |
Foldable Last | Since: base-4.9.0.0 |
Defined in Data.Semigroup fold :: Monoid m => Last m -> m # foldMap :: Monoid m => (a -> m) -> Last a -> m # foldMap' :: Monoid m => (a -> m) -> Last a -> m # foldr :: (a -> b -> b) -> b -> Last a -> b # foldr' :: (a -> b -> b) -> b -> Last a -> b # foldl :: (b -> a -> b) -> b -> Last a -> b # foldl' :: (b -> a -> b) -> b -> Last a -> b # foldr1 :: (a -> a -> a) -> Last a -> a # foldl1 :: (a -> a -> a) -> Last a -> a # elem :: Eq a => a -> Last a -> Bool # maximum :: Ord a => Last a -> a # | |
Foldable Max | Since: base-4.9.0.0 |
Defined in Data.Semigroup fold :: Monoid m => Max m -> m # foldMap :: Monoid m => (a -> m) -> Max a -> m # foldMap' :: Monoid m => (a -> m) -> Max a -> m # foldr :: (a -> b -> b) -> b -> Max a -> b # foldr' :: (a -> b -> b) -> b -> Max a -> b # foldl :: (b -> a -> b) -> b -> Max a -> b # foldl' :: (b -> a -> b) -> b -> Max a -> b # foldr1 :: (a -> a -> a) -> Max a -> a # foldl1 :: (a -> a -> a) -> Max a -> a # elem :: Eq a => a -> Max a -> Bool # maximum :: Ord a => Max a -> a # | |
Foldable Min | Since: base-4.9.0.0 |
Defined in Data.Semigroup fold :: Monoid m => Min m -> m # foldMap :: Monoid m => (a -> m) -> Min a -> m # foldMap' :: Monoid m => (a -> m) -> Min a -> m # foldr :: (a -> b -> b) -> b -> Min a -> b # foldr' :: (a -> b -> b) -> b -> Min a -> b # foldl :: (b -> a -> b) -> b -> Min a -> b # foldl' :: (b -> a -> b) -> b -> Min a -> b # foldr1 :: (a -> a -> a) -> Min a -> a # foldl1 :: (a -> a -> a) -> Min a -> a # elem :: Eq a => a -> Min a -> Bool # maximum :: Ord a => Min a -> a # | |
Foldable Dual | Since: base-4.8.0.0 |
Defined in Data.Foldable fold :: Monoid m => Dual m -> m # foldMap :: Monoid m => (a -> m) -> Dual a -> m # foldMap' :: Monoid m => (a -> m) -> Dual a -> m # foldr :: (a -> b -> b) -> b -> Dual a -> b # foldr' :: (a -> b -> b) -> b -> Dual a -> b # foldl :: (b -> a -> b) -> b -> Dual a -> b # foldl' :: (b -> a -> b) -> b -> Dual a -> b # foldr1 :: (a -> a -> a) -> Dual a -> a # foldl1 :: (a -> a -> a) -> Dual a -> a # elem :: Eq a => a -> Dual a -> Bool # maximum :: Ord a => Dual a -> a # | |
Foldable Product | Since: base-4.8.0.0 |
Defined in Data.Foldable fold :: Monoid m => Product m -> m # foldMap :: Monoid m => (a -> m) -> Product a -> m # foldMap' :: Monoid m => (a -> m) -> Product a -> m # foldr :: (a -> b -> b) -> b -> Product a -> b # foldr' :: (a -> b -> b) -> b -> Product a -> b # foldl :: (b -> a -> b) -> b -> Product a -> b # foldl' :: (b -> a -> b) -> b -> Product a -> b # foldr1 :: (a -> a -> a) -> Product a -> a # foldl1 :: (a -> a -> a) -> Product a -> a # elem :: Eq a => a -> Product a -> Bool # maximum :: Ord a => Product a -> a # minimum :: Ord a => Product a -> a # | |
Foldable Sum | Since: base-4.8.0.0 |
Defined in Data.Foldable fold :: Monoid m => Sum m -> m # foldMap :: Monoid m => (a -> m) -> Sum a -> m # foldMap' :: Monoid m => (a -> m) -> Sum a -> m # foldr :: (a -> b -> b) -> b -> Sum a -> b # foldr' :: (a -> b -> b) -> b -> Sum a -> b # foldl :: (b -> a -> b) -> b -> Sum a -> b # foldl' :: (b -> a -> b) -> b -> Sum a -> b # foldr1 :: (a -> a -> a) -> Sum a -> a # foldl1 :: (a -> a -> a) -> Sum a -> a # elem :: Eq a => a -> Sum a -> Bool # maximum :: Ord a => Sum a -> a # | |
Foldable NonEmpty | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => NonEmpty m -> m # foldMap :: Monoid m => (a -> m) -> NonEmpty a -> m # foldMap' :: Monoid m => (a -> m) -> NonEmpty a -> m # foldr :: (a -> b -> b) -> b -> NonEmpty a -> b # foldr' :: (a -> b -> b) -> b -> NonEmpty a -> b # foldl :: (b -> a -> b) -> b -> NonEmpty a -> b # foldl' :: (b -> a -> b) -> b -> NonEmpty a -> b # foldr1 :: (a -> a -> a) -> NonEmpty a -> a # foldl1 :: (a -> a -> a) -> NonEmpty a -> a # elem :: Eq a => a -> NonEmpty a -> Bool # maximum :: Ord a => NonEmpty a -> a # minimum :: Ord a => NonEmpty a -> a # | |
Foldable Par1 | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => Par1 m -> m # foldMap :: Monoid m => (a -> m) -> Par1 a -> m # foldMap' :: Monoid m => (a -> m) -> Par1 a -> m # foldr :: (a -> b -> b) -> b -> Par1 a -> b # foldr' :: (a -> b -> b) -> b -> Par1 a -> b # foldl :: (b -> a -> b) -> b -> Par1 a -> b # foldl' :: (b -> a -> b) -> b -> Par1 a -> b # foldr1 :: (a -> a -> a) -> Par1 a -> a # foldl1 :: (a -> a -> a) -> Par1 a -> a # elem :: Eq a => a -> Par1 a -> Bool # maximum :: Ord a => Par1 a -> a # | |
Foldable IntMap | Folds in order of increasing key. |
Defined in Data.IntMap.Internal fold :: Monoid m => IntMap m -> m # foldMap :: Monoid m => (a -> m) -> IntMap a -> m # foldMap' :: Monoid m => (a -> m) -> IntMap a -> m # foldr :: (a -> b -> b) -> b -> IntMap a -> b # foldr' :: (a -> b -> b) -> b -> IntMap a -> b # foldl :: (b -> a -> b) -> b -> IntMap a -> b # foldl' :: (b -> a -> b) -> b -> IntMap a -> b # foldr1 :: (a -> a -> a) -> IntMap a -> a # foldl1 :: (a -> a -> a) -> IntMap a -> a # elem :: Eq a => a -> IntMap a -> Bool # maximum :: Ord a => IntMap a -> a # minimum :: Ord a => IntMap a -> a # | |
Foldable Digit | |
Defined in Data.Sequence.Internal fold :: Monoid m => Digit m -> m # foldMap :: Monoid m => (a -> m) -> Digit a -> m # foldMap' :: Monoid m => (a -> m) -> Digit a -> m # foldr :: (a -> b -> b) -> b -> Digit a -> b # foldr' :: (a -> b -> b) -> b -> Digit a -> b # foldl :: (b -> a -> b) -> b -> Digit a -> b # foldl' :: (b -> a -> b) -> b -> Digit a -> b # foldr1 :: (a -> a -> a) -> Digit a -> a # foldl1 :: (a -> a -> a) -> Digit a -> a # elem :: Eq a => a -> Digit a -> Bool # maximum :: Ord a => Digit a -> a # minimum :: Ord a => Digit a -> a # | |
Foldable Elem | |
Defined in Data.Sequence.Internal fold :: Monoid m => Elem m -> m # foldMap :: Monoid m => (a -> m) -> Elem a -> m # foldMap' :: Monoid m => (a -> m) -> Elem a -> m # foldr :: (a -> b -> b) -> b -> Elem a -> b # foldr' :: (a -> b -> b) -> b -> Elem a -> b # foldl :: (b -> a -> b) -> b -> Elem a -> b # foldl' :: (b -> a -> b) -> b -> Elem a -> b # foldr1 :: (a -> a -> a) -> Elem a -> a # foldl1 :: (a -> a -> a) -> Elem a -> a # elem :: Eq a => a -> Elem a -> Bool # maximum :: Ord a => Elem a -> a # | |
Foldable FingerTree | |
Defined in Data.Sequence.Internal fold :: Monoid m => FingerTree m -> m # foldMap :: Monoid m => (a -> m) -> FingerTree a -> m # foldMap' :: Monoid m => (a -> m) -> FingerTree a -> m # foldr :: (a -> b -> b) -> b -> FingerTree a -> b # foldr' :: (a -> b -> b) -> b -> FingerTree a -> b # foldl :: (b -> a -> b) -> b -> FingerTree a -> b # foldl' :: (b -> a -> b) -> b -> FingerTree a -> b # foldr1 :: (a -> a -> a) -> FingerTree a -> a # foldl1 :: (a -> a -> a) -> FingerTree a -> a # toList :: FingerTree a -> [a] # null :: FingerTree a -> Bool # length :: FingerTree a -> Int # elem :: Eq a => a -> FingerTree a -> Bool # maximum :: Ord a => FingerTree a -> a # minimum :: Ord a => FingerTree a -> a # sum :: Num a => FingerTree a -> a # product :: Num a => FingerTree a -> a # | |
Foldable Node | |
Defined in Data.Sequence.Internal fold :: Monoid m => Node m -> m # foldMap :: Monoid m => (a -> m) -> Node a -> m # foldMap' :: Monoid m => (a -> m) -> Node a -> m # foldr :: (a -> b -> b) -> b -> Node a -> b # foldr' :: (a -> b -> b) -> b -> Node a -> b # foldl :: (b -> a -> b) -> b -> Node a -> b # foldl' :: (b -> a -> b) -> b -> Node a -> b # foldr1 :: (a -> a -> a) -> Node a -> a # foldl1 :: (a -> a -> a) -> Node a -> a # elem :: Eq a => a -> Node a -> Bool # maximum :: Ord a => Node a -> a # | |
Foldable Seq | |
Defined in Data.Sequence.Internal fold :: Monoid m => Seq m -> m # foldMap :: Monoid m => (a -> m) -> Seq a -> m # foldMap' :: Monoid m => (a -> m) -> Seq a -> m # foldr :: (a -> b -> b) -> b -> Seq a -> b # foldr' :: (a -> b -> b) -> b -> Seq a -> b # foldl :: (b -> a -> b) -> b -> Seq a -> b # foldl' :: (b -> a -> b) -> b -> Seq a -> b # foldr1 :: (a -> a -> a) -> Seq a -> a # foldl1 :: (a -> a -> a) -> Seq a -> a # elem :: Eq a => a -> Seq a -> Bool # maximum :: Ord a => Seq a -> a # | |
Foldable ViewL | |
Defined in Data.Sequence.Internal fold :: Monoid m => ViewL m -> m # foldMap :: Monoid m => (a -> m) -> ViewL a -> m # foldMap' :: Monoid m => (a -> m) -> ViewL a -> m # foldr :: (a -> b -> b) -> b -> ViewL a -> b # foldr' :: (a -> b -> b) -> b -> ViewL a -> b # foldl :: (b -> a -> b) -> b -> ViewL a -> b # foldl' :: (b -> a -> b) -> b -> ViewL a -> b # foldr1 :: (a -> a -> a) -> ViewL a -> a # foldl1 :: (a -> a -> a) -> ViewL a -> a # elem :: Eq a => a -> ViewL a -> Bool # maximum :: Ord a => ViewL a -> a # minimum :: Ord a => ViewL a -> a # | |
Foldable ViewR | |
Defined in Data.Sequence.Internal fold :: Monoid m => ViewR m -> m # foldMap :: Monoid m => (a -> m) -> ViewR a -> m # foldMap' :: Monoid m => (a -> m) -> ViewR a -> m # foldr :: (a -> b -> b) -> b -> ViewR a -> b # foldr' :: (a -> b -> b) -> b -> ViewR a -> b # foldl :: (b -> a -> b) -> b -> ViewR a -> b # foldl' :: (b -> a -> b) -> b -> ViewR a -> b # foldr1 :: (a -> a -> a) -> ViewR a -> a # foldl1 :: (a -> a -> a) -> ViewR a -> a # elem :: Eq a => a -> ViewR a -> Bool # maximum :: Ord a => ViewR a -> a # minimum :: Ord a => ViewR a -> a # | |
Foldable Set | Folds in order of increasing key. |
Defined in Data.Set.Internal fold :: Monoid m => Set m -> m # foldMap :: Monoid m => (a -> m) -> Set a -> m # foldMap' :: Monoid m => (a -> m) -> Set a -> m # foldr :: (a -> b -> b) -> b -> Set a -> b # foldr' :: (a -> b -> b) -> b -> Set a -> b # foldl :: (b -> a -> b) -> b -> Set a -> b # foldl' :: (b -> a -> b) -> b -> Set a -> b # foldr1 :: (a -> a -> a) -> Set a -> a # foldl1 :: (a -> a -> a) -> Set a -> a # elem :: Eq a => a -> Set a -> Bool # maximum :: Ord a => Set a -> a # | |
Foldable Tree | Folds in preorder |
Defined in Data.Tree fold :: Monoid m => Tree m -> m # foldMap :: Monoid m => (a -> m) -> Tree a -> m # foldMap' :: Monoid m => (a -> m) -> Tree a -> m # foldr :: (a -> b -> b) -> b -> Tree a -> b # foldr' :: (a -> b -> b) -> b -> Tree a -> b # foldl :: (b -> a -> b) -> b -> Tree a -> b # foldl' :: (b -> a -> b) -> b -> Tree a -> b # foldr1 :: (a -> a -> a) -> Tree a -> a # foldl1 :: (a -> a -> a) -> Tree a -> a # elem :: Eq a => a -> Tree a -> Bool # maximum :: Ord a => Tree a -> a # | |
Foldable Hashed | |
Defined in Data.Hashable.Class fold :: Monoid m => Hashed m -> m # foldMap :: Monoid m => (a -> m) -> Hashed a -> m # foldMap' :: Monoid m => (a -> m) -> Hashed a -> m # foldr :: (a -> b -> b) -> b -> Hashed a -> b # foldr' :: (a -> b -> b) -> b -> Hashed a -> b # foldl :: (b -> a -> b) -> b -> Hashed a -> b # foldl' :: (b -> a -> b) -> b -> Hashed a -> b # foldr1 :: (a -> a -> a) -> Hashed a -> a # foldl1 :: (a -> a -> a) -> Hashed a -> a # elem :: Eq a => a -> Hashed a -> Bool # maximum :: Ord a => Hashed a -> a # minimum :: Ord a => Hashed a -> a # | |
Foldable HashSet | |
Defined in Data.HashSet.Internal fold :: Monoid m => HashSet m -> m # foldMap :: Monoid m => (a -> m) -> HashSet a -> m # foldMap' :: Monoid m => (a -> m) -> HashSet a -> m # foldr :: (a -> b -> b) -> b -> HashSet a -> b # foldr' :: (a -> b -> b) -> b -> HashSet a -> b # foldl :: (b -> a -> b) -> b -> HashSet a -> b # foldl' :: (b -> a -> b) -> b -> HashSet a -> b # foldr1 :: (a -> a -> a) -> HashSet a -> a # foldl1 :: (a -> a -> a) -> HashSet a -> a # elem :: Eq a => a -> HashSet a -> Bool # maximum :: Ord a => HashSet a -> a # minimum :: Ord a => HashSet a -> a # | |
Foldable Maybe | Since: base-2.1 |
Defined in Data.Foldable fold :: Monoid m => Maybe m -> m # foldMap :: Monoid m => (a -> m) -> Maybe a -> m # foldMap' :: Monoid m => (a -> m) -> Maybe a -> m # foldr :: (a -> b -> b) -> b -> Maybe a -> b # foldr' :: (a -> b -> b) -> b -> Maybe a -> b # foldl :: (b -> a -> b) -> b -> Maybe a -> b # foldl' :: (b -> a -> b) -> b -> Maybe a -> b # foldr1 :: (a -> a -> a) -> Maybe a -> a # foldl1 :: (a -> a -> a) -> Maybe a -> a # elem :: Eq a => a -> Maybe a -> Bool # maximum :: Ord a => Maybe a -> a # minimum :: Ord a => Maybe a -> a # | |
Foldable Solo | Since: base-4.15 |
Defined in Data.Foldable fold :: Monoid m => Solo m -> m # foldMap :: Monoid m => (a -> m) -> Solo a -> m # foldMap' :: Monoid m => (a -> m) -> Solo a -> m # foldr :: (a -> b -> b) -> b -> Solo a -> b # foldr' :: (a -> b -> b) -> b -> Solo a -> b # foldl :: (b -> a -> b) -> b -> Solo a -> b # foldl' :: (b -> a -> b) -> b -> Solo a -> b # foldr1 :: (a -> a -> a) -> Solo a -> a # foldl1 :: (a -> a -> a) -> Solo a -> a # elem :: Eq a => a -> Solo a -> Bool # maximum :: Ord a => Solo a -> a # | |
Foldable List | Since: base-2.1 |
Defined in Data.Foldable fold :: Monoid m => [m] -> m # foldMap :: Monoid m => (a -> m) -> [a] -> m # foldMap' :: Monoid m => (a -> m) -> [a] -> m # foldr :: (a -> b -> b) -> b -> [a] -> b # foldr' :: (a -> b -> b) -> b -> [a] -> b # foldl :: (b -> a -> b) -> b -> [a] -> b # foldl' :: (b -> a -> b) -> b -> [a] -> b # foldr1 :: (a -> a -> a) -> [a] -> a # foldl1 :: (a -> a -> a) -> [a] -> a # elem :: Eq a => a -> [a] -> Bool # maximum :: Ord a => [a] -> a # | |
Foldable (Either a) | Since: base-4.7.0.0 |
Defined in Data.Foldable fold :: Monoid m => Either a m -> m # foldMap :: Monoid m => (a0 -> m) -> Either a a0 -> m # foldMap' :: Monoid m => (a0 -> m) -> Either a a0 -> m # foldr :: (a0 -> b -> b) -> b -> Either a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> Either a a0 -> b # foldl :: (b -> a0 -> b) -> b -> Either a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> Either a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 # toList :: Either a a0 -> [a0] # length :: Either a a0 -> Int # elem :: Eq a0 => a0 -> Either a a0 -> Bool # maximum :: Ord a0 => Either a a0 -> a0 # minimum :: Ord a0 => Either a a0 -> a0 # | |
Foldable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Data.Foldable fold :: Monoid m => Proxy m -> m # foldMap :: Monoid m => (a -> m) -> Proxy a -> m # foldMap' :: Monoid m => (a -> m) -> Proxy a -> m # foldr :: (a -> b -> b) -> b -> Proxy a -> b # foldr' :: (a -> b -> b) -> b -> Proxy a -> b # foldl :: (b -> a -> b) -> b -> Proxy a -> b # foldl' :: (b -> a -> b) -> b -> Proxy a -> b # foldr1 :: (a -> a -> a) -> Proxy a -> a # foldl1 :: (a -> a -> a) -> Proxy a -> a # elem :: Eq a => a -> Proxy a -> Bool # maximum :: Ord a => Proxy a -> a # minimum :: Ord a => Proxy a -> a # | |
Foldable (Arg a) | Since: base-4.9.0.0 |
Defined in Data.Semigroup fold :: Monoid m => Arg a m -> m # foldMap :: Monoid m => (a0 -> m) -> Arg a a0 -> m # foldMap' :: Monoid m => (a0 -> m) -> Arg a a0 -> m # foldr :: (a0 -> b -> b) -> b -> Arg a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> Arg a a0 -> b # foldl :: (b -> a0 -> b) -> b -> Arg a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> Arg a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> Arg a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> Arg a a0 -> a0 # elem :: Eq a0 => a0 -> Arg a a0 -> Bool # maximum :: Ord a0 => Arg a a0 -> a0 # minimum :: Ord a0 => Arg a a0 -> a0 # | |
Foldable (Array i) | Since: base-4.8.0.0 |
Defined in Data.Foldable fold :: Monoid m => Array i m -> m # foldMap :: Monoid m => (a -> m) -> Array i a -> m # foldMap' :: Monoid m => (a -> m) -> Array i a -> m # foldr :: (a -> b -> b) -> b -> Array i a -> b # foldr' :: (a -> b -> b) -> b -> Array i a -> b # foldl :: (b -> a -> b) -> b -> Array i a -> b # foldl' :: (b -> a -> b) -> b -> Array i a -> b # foldr1 :: (a -> a -> a) -> Array i a -> a # foldl1 :: (a -> a -> a) -> Array i a -> a # elem :: Eq a => a -> Array i a -> Bool # maximum :: Ord a => Array i a -> a # minimum :: Ord a => Array i a -> a # | |
Foldable (U1 :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => U1 m -> m # foldMap :: Monoid m => (a -> m) -> U1 a -> m # foldMap' :: Monoid m => (a -> m) -> U1 a -> m # foldr :: (a -> b -> b) -> b -> U1 a -> b # foldr' :: (a -> b -> b) -> b -> U1 a -> b # foldl :: (b -> a -> b) -> b -> U1 a -> b # foldl' :: (b -> a -> b) -> b -> U1 a -> b # foldr1 :: (a -> a -> a) -> U1 a -> a # foldl1 :: (a -> a -> a) -> U1 a -> a # elem :: Eq a => a -> U1 a -> Bool # maximum :: Ord a => U1 a -> a # | |
Foldable (UAddr :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UAddr m -> m # foldMap :: Monoid m => (a -> m) -> UAddr a -> m # foldMap' :: Monoid m => (a -> m) -> UAddr a -> m # foldr :: (a -> b -> b) -> b -> UAddr a -> b # foldr' :: (a -> b -> b) -> b -> UAddr a -> b # foldl :: (b -> a -> b) -> b -> UAddr a -> b # foldl' :: (b -> a -> b) -> b -> UAddr a -> b # foldr1 :: (a -> a -> a) -> UAddr a -> a # foldl1 :: (a -> a -> a) -> UAddr a -> a # elem :: Eq a => a -> UAddr a -> Bool # maximum :: Ord a => UAddr a -> a # minimum :: Ord a => UAddr a -> a # | |
Foldable (UChar :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UChar m -> m # foldMap :: Monoid m => (a -> m) -> UChar a -> m # foldMap' :: Monoid m => (a -> m) -> UChar a -> m # foldr :: (a -> b -> b) -> b -> UChar a -> b # foldr' :: (a -> b -> b) -> b -> UChar a -> b # foldl :: (b -> a -> b) -> b -> UChar a -> b # foldl' :: (b -> a -> b) -> b -> UChar a -> b # foldr1 :: (a -> a -> a) -> UChar a -> a # foldl1 :: (a -> a -> a) -> UChar a -> a # elem :: Eq a => a -> UChar a -> Bool # maximum :: Ord a => UChar a -> a # minimum :: Ord a => UChar a -> a # | |
Foldable (UDouble :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UDouble m -> m # foldMap :: Monoid m => (a -> m) -> UDouble a -> m # foldMap' :: Monoid m => (a -> m) -> UDouble a -> m # foldr :: (a -> b -> b) -> b -> UDouble a -> b # foldr' :: (a -> b -> b) -> b -> UDouble a -> b # foldl :: (b -> a -> b) -> b -> UDouble a -> b # foldl' :: (b -> a -> b) -> b -> UDouble a -> b # foldr1 :: (a -> a -> a) -> UDouble a -> a # foldl1 :: (a -> a -> a) -> UDouble a -> a # elem :: Eq a => a -> UDouble a -> Bool # maximum :: Ord a => UDouble a -> a # minimum :: Ord a => UDouble a -> a # | |
Foldable (UFloat :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UFloat m -> m # foldMap :: Monoid m => (a -> m) -> UFloat a -> m # foldMap' :: Monoid m => (a -> m) -> UFloat a -> m # foldr :: (a -> b -> b) -> b -> UFloat a -> b # foldr' :: (a -> b -> b) -> b -> UFloat a -> b # foldl :: (b -> a -> b) -> b -> UFloat a -> b # foldl' :: (b -> a -> b) -> b -> UFloat a -> b # foldr1 :: (a -> a -> a) -> UFloat a -> a # foldl1 :: (a -> a -> a) -> UFloat a -> a # elem :: Eq a => a -> UFloat a -> Bool # maximum :: Ord a => UFloat a -> a # minimum :: Ord a => UFloat a -> a # | |
Foldable (UInt :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UInt m -> m # foldMap :: Monoid m => (a -> m) -> UInt a -> m # foldMap' :: Monoid m => (a -> m) -> UInt a -> m # foldr :: (a -> b -> b) -> b -> UInt a -> b # foldr' :: (a -> b -> b) -> b -> UInt a -> b # foldl :: (b -> a -> b) -> b -> UInt a -> b # foldl' :: (b -> a -> b) -> b -> UInt a -> b # foldr1 :: (a -> a -> a) -> UInt a -> a # foldl1 :: (a -> a -> a) -> UInt a -> a # elem :: Eq a => a -> UInt a -> Bool # maximum :: Ord a => UInt a -> a # | |
Foldable (UWord :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => UWord m -> m # foldMap :: Monoid m => (a -> m) -> UWord a -> m # foldMap' :: Monoid m => (a -> m) -> UWord a -> m # foldr :: (a -> b -> b) -> b -> UWord a -> b # foldr' :: (a -> b -> b) -> b -> UWord a -> b # foldl :: (b -> a -> b) -> b -> UWord a -> b # foldl' :: (b -> a -> b) -> b -> UWord a -> b # foldr1 :: (a -> a -> a) -> UWord a -> a # foldl1 :: (a -> a -> a) -> UWord a -> a # elem :: Eq a => a -> UWord a -> Bool # maximum :: Ord a => UWord a -> a # minimum :: Ord a => UWord a -> a # | |
Foldable (V1 :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => V1 m -> m # foldMap :: Monoid m => (a -> m) -> V1 a -> m # foldMap' :: Monoid m => (a -> m) -> V1 a -> m # foldr :: (a -> b -> b) -> b -> V1 a -> b # foldr' :: (a -> b -> b) -> b -> V1 a -> b # foldl :: (b -> a -> b) -> b -> V1 a -> b # foldl' :: (b -> a -> b) -> b -> V1 a -> b # foldr1 :: (a -> a -> a) -> V1 a -> a # foldl1 :: (a -> a -> a) -> V1 a -> a # elem :: Eq a => a -> V1 a -> Bool # maximum :: Ord a => V1 a -> a # | |
Foldable (Map k) | Folds in order of increasing key. |
Defined in Data.Map.Internal fold :: Monoid m => Map k m -> m # foldMap :: Monoid m => (a -> m) -> Map k a -> m # foldMap' :: Monoid m => (a -> m) -> Map k a -> m # foldr :: (a -> b -> b) -> b -> Map k a -> b # foldr' :: (a -> b -> b) -> b -> Map k a -> b # foldl :: (b -> a -> b) -> b -> Map k a -> b # foldl' :: (b -> a -> b) -> b -> Map k a -> b # foldr1 :: (a -> a -> a) -> Map k a -> a # foldl1 :: (a -> a -> a) -> Map k a -> a # elem :: Eq a => a -> Map k a -> Bool # maximum :: Ord a => Map k a -> a # minimum :: Ord a => Map k a -> a # | |
Foldable (HashMap k) | |
Defined in Data.HashMap.Internal fold :: Monoid m => HashMap k m -> m # foldMap :: Monoid m => (a -> m) -> HashMap k a -> m # foldMap' :: Monoid m => (a -> m) -> HashMap k a -> m # foldr :: (a -> b -> b) -> b -> HashMap k a -> b # foldr' :: (a -> b -> b) -> b -> HashMap k a -> b # foldl :: (b -> a -> b) -> b -> HashMap k a -> b # foldl' :: (b -> a -> b) -> b -> HashMap k a -> b # foldr1 :: (a -> a -> a) -> HashMap k a -> a # foldl1 :: (a -> a -> a) -> HashMap k a -> a # toList :: HashMap k a -> [a] # length :: HashMap k a -> Int # elem :: Eq a => a -> HashMap k a -> Bool # maximum :: Ord a => HashMap k a -> a # minimum :: Ord a => HashMap k a -> a # | |
Foldable f => Foldable (MaybeT f) | |
Defined in Control.Monad.Trans.Maybe fold :: Monoid m => MaybeT f m -> m # foldMap :: Monoid m => (a -> m) -> MaybeT f a -> m # foldMap' :: Monoid m => (a -> m) -> MaybeT f a -> m # foldr :: (a -> b -> b) -> b -> MaybeT f a -> b # foldr' :: (a -> b -> b) -> b -> MaybeT f a -> b # foldl :: (b -> a -> b) -> b -> MaybeT f a -> b # foldl' :: (b -> a -> b) -> b -> MaybeT f a -> b # foldr1 :: (a -> a -> a) -> MaybeT f a -> a # foldl1 :: (a -> a -> a) -> MaybeT f a -> a # elem :: Eq a => a -> MaybeT f a -> Bool # maximum :: Ord a => MaybeT f a -> a # minimum :: Ord a => MaybeT f a -> a # | |
Foldable ((,) a) | Since: base-4.7.0.0 |
Defined in Data.Foldable fold :: Monoid m => (a, m) -> m # foldMap :: Monoid m => (a0 -> m) -> (a, a0) -> m # foldMap' :: Monoid m => (a0 -> m) -> (a, a0) -> m # foldr :: (a0 -> b -> b) -> b -> (a, a0) -> b # foldr' :: (a0 -> b -> b) -> b -> (a, a0) -> b # foldl :: (b -> a0 -> b) -> b -> (a, a0) -> b # foldl' :: (b -> a0 -> b) -> b -> (a, a0) -> b # foldr1 :: (a0 -> a0 -> a0) -> (a, a0) -> a0 # foldl1 :: (a0 -> a0 -> a0) -> (a, a0) -> a0 # elem :: Eq a0 => a0 -> (a, a0) -> Bool # maximum :: Ord a0 => (a, a0) -> a0 # minimum :: Ord a0 => (a, a0) -> a0 # | |
Foldable (Const m :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Data.Functor.Const fold :: Monoid m0 => Const m m0 -> m0 # foldMap :: Monoid m0 => (a -> m0) -> Const m a -> m0 # foldMap' :: Monoid m0 => (a -> m0) -> Const m a -> m0 # foldr :: (a -> b -> b) -> b -> Const m a -> b # foldr' :: (a -> b -> b) -> b -> Const m a -> b # foldl :: (b -> a -> b) -> b -> Const m a -> b # foldl' :: (b -> a -> b) -> b -> Const m a -> b # foldr1 :: (a -> a -> a) -> Const m a -> a # foldl1 :: (a -> a -> a) -> Const m a -> a # elem :: Eq a => a -> Const m a -> Bool # maximum :: Ord a => Const m a -> a # minimum :: Ord a => Const m a -> a # | |
Foldable f => Foldable (Ap f) | Since: base-4.12.0.0 |
Defined in Data.Foldable fold :: Monoid m => Ap f m -> m # foldMap :: Monoid m => (a -> m) -> Ap f a -> m # foldMap' :: Monoid m => (a -> m) -> Ap f a -> m # foldr :: (a -> b -> b) -> b -> Ap f a -> b # foldr' :: (a -> b -> b) -> b -> Ap f a -> b # foldl :: (b -> a -> b) -> b -> Ap f a -> b # foldl' :: (b -> a -> b) -> b -> Ap f a -> b # foldr1 :: (a -> a -> a) -> Ap f a -> a # foldl1 :: (a -> a -> a) -> Ap f a -> a # elem :: Eq a => a -> Ap f a -> Bool # maximum :: Ord a => Ap f a -> a # | |
Foldable f => Foldable (Alt f) | Since: base-4.12.0.0 |
Defined in Data.Foldable fold :: Monoid m => Alt f m -> m # foldMap :: Monoid m => (a -> m) -> Alt f a -> m # foldMap' :: Monoid m => (a -> m) -> Alt f a -> m # foldr :: (a -> b -> b) -> b -> Alt f a -> b # foldr' :: (a -> b -> b) -> b -> Alt f a -> b # foldl :: (b -> a -> b) -> b -> Alt f a -> b # foldl' :: (b -> a -> b) -> b -> Alt f a -> b # foldr1 :: (a -> a -> a) -> Alt f a -> a # foldl1 :: (a -> a -> a) -> Alt f a -> a # elem :: Eq a => a -> Alt f a -> Bool # maximum :: Ord a => Alt f a -> a # minimum :: Ord a => Alt f a -> a # | |
Foldable f => Foldable (Rec1 f) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => Rec1 f m -> m # foldMap :: Monoid m => (a -> m) -> Rec1 f a -> m # foldMap' :: Monoid m => (a -> m) -> Rec1 f a -> m # foldr :: (a -> b -> b) -> b -> Rec1 f a -> b # foldr' :: (a -> b -> b) -> b -> Rec1 f a -> b # foldl :: (b -> a -> b) -> b -> Rec1 f a -> b # foldl' :: (b -> a -> b) -> b -> Rec1 f a -> b # foldr1 :: (a -> a -> a) -> Rec1 f a -> a # foldl1 :: (a -> a -> a) -> Rec1 f a -> a # elem :: Eq a => a -> Rec1 f a -> Bool # maximum :: Ord a => Rec1 f a -> a # minimum :: Ord a => Rec1 f a -> a # | |
Foldable f => Foldable (ExceptT e f) | |
Defined in Control.Monad.Trans.Except fold :: Monoid m => ExceptT e f m -> m # foldMap :: Monoid m => (a -> m) -> ExceptT e f a -> m # foldMap' :: Monoid m => (a -> m) -> ExceptT e f a -> m # foldr :: (a -> b -> b) -> b -> ExceptT e f a -> b # foldr' :: (a -> b -> b) -> b -> ExceptT e f a -> b # foldl :: (b -> a -> b) -> b -> ExceptT e f a -> b # foldl' :: (b -> a -> b) -> b -> ExceptT e f a -> b # foldr1 :: (a -> a -> a) -> ExceptT e f a -> a # foldl1 :: (a -> a -> a) -> ExceptT e f a -> a # toList :: ExceptT e f a -> [a] # null :: ExceptT e f a -> Bool # length :: ExceptT e f a -> Int # elem :: Eq a => a -> ExceptT e f a -> Bool # maximum :: Ord a => ExceptT e f a -> a # minimum :: Ord a => ExceptT e f a -> a # | |
Foldable f => Foldable (IdentityT f) | |
Defined in Control.Monad.Trans.Identity fold :: Monoid m => IdentityT f m -> m # foldMap :: Monoid m => (a -> m) -> IdentityT f a -> m # foldMap' :: Monoid m => (a -> m) -> IdentityT f a -> m # foldr :: (a -> b -> b) -> b -> IdentityT f a -> b # foldr' :: (a -> b -> b) -> b -> IdentityT f a -> b # foldl :: (b -> a -> b) -> b -> IdentityT f a -> b # foldl' :: (b -> a -> b) -> b -> IdentityT f a -> b # foldr1 :: (a -> a -> a) -> IdentityT f a -> a # foldl1 :: (a -> a -> a) -> IdentityT f a -> a # toList :: IdentityT f a -> [a] # null :: IdentityT f a -> Bool # length :: IdentityT f a -> Int # elem :: Eq a => a -> IdentityT f a -> Bool # maximum :: Ord a => IdentityT f a -> a # minimum :: Ord a => IdentityT f a -> a # | |
Foldable f => Foldable (WriterT w f) | |
Defined in Control.Monad.Trans.Writer.Lazy fold :: Monoid m => WriterT w f m -> m # foldMap :: Monoid m => (a -> m) -> WriterT w f a -> m # foldMap' :: Monoid m => (a -> m) -> WriterT w f a -> m # foldr :: (a -> b -> b) -> b -> WriterT w f a -> b # foldr' :: (a -> b -> b) -> b -> WriterT w f a -> b # foldl :: (b -> a -> b) -> b -> WriterT w f a -> b # foldl' :: (b -> a -> b) -> b -> WriterT w f a -> b # foldr1 :: (a -> a -> a) -> WriterT w f a -> a # foldl1 :: (a -> a -> a) -> WriterT w f a -> a # toList :: WriterT w f a -> [a] # null :: WriterT w f a -> Bool # length :: WriterT w f a -> Int # elem :: Eq a => a -> WriterT w f a -> Bool # maximum :: Ord a => WriterT w f a -> a # minimum :: Ord a => WriterT w f a -> a # | |
Foldable f => Foldable (WriterT w f) | |
Defined in Control.Monad.Trans.Writer.Strict fold :: Monoid m => WriterT w f m -> m # foldMap :: Monoid m => (a -> m) -> WriterT w f a -> m # foldMap' :: Monoid m => (a -> m) -> WriterT w f a -> m # foldr :: (a -> b -> b) -> b -> WriterT w f a -> b # foldr' :: (a -> b -> b) -> b -> WriterT w f a -> b # foldl :: (b -> a -> b) -> b -> WriterT w f a -> b # foldl' :: (b -> a -> b) -> b -> WriterT w f a -> b # foldr1 :: (a -> a -> a) -> WriterT w f a -> a # foldl1 :: (a -> a -> a) -> WriterT w f a -> a # toList :: WriterT w f a -> [a] # null :: WriterT w f a -> Bool # length :: WriterT w f a -> Int # elem :: Eq a => a -> WriterT w f a -> Bool # maximum :: Ord a => WriterT w f a -> a # minimum :: Ord a => WriterT w f a -> a # | |
(Foldable f, Foldable g) => Foldable (Product f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Product fold :: Monoid m => Product f g m -> m # foldMap :: Monoid m => (a -> m) -> Product f g a -> m # foldMap' :: Monoid m => (a -> m) -> Product f g a -> m # foldr :: (a -> b -> b) -> b -> Product f g a -> b # foldr' :: (a -> b -> b) -> b -> Product f g a -> b # foldl :: (b -> a -> b) -> b -> Product f g a -> b # foldl' :: (b -> a -> b) -> b -> Product f g a -> b # foldr1 :: (a -> a -> a) -> Product f g a -> a # foldl1 :: (a -> a -> a) -> Product f g a -> a # toList :: Product f g a -> [a] # null :: Product f g a -> Bool # length :: Product f g a -> Int # elem :: Eq a => a -> Product f g a -> Bool # maximum :: Ord a => Product f g a -> a # minimum :: Ord a => Product f g a -> a # | |
(Foldable f, Foldable g) => Foldable (Sum f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Sum fold :: Monoid m => Sum f g m -> m # foldMap :: Monoid m => (a -> m) -> Sum f g a -> m # foldMap' :: Monoid m => (a -> m) -> Sum f g a -> m # foldr :: (a -> b -> b) -> b -> Sum f g a -> b # foldr' :: (a -> b -> b) -> b -> Sum f g a -> b # foldl :: (b -> a -> b) -> b -> Sum f g a -> b # foldl' :: (b -> a -> b) -> b -> Sum f g a -> b # foldr1 :: (a -> a -> a) -> Sum f g a -> a # foldl1 :: (a -> a -> a) -> Sum f g a -> a # elem :: Eq a => a -> Sum f g a -> Bool # maximum :: Ord a => Sum f g a -> a # minimum :: Ord a => Sum f g a -> a # | |
(Foldable f, Foldable g) => Foldable (f :*: g) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => (f :*: g) m -> m # foldMap :: Monoid m => (a -> m) -> (f :*: g) a -> m # foldMap' :: Monoid m => (a -> m) -> (f :*: g) a -> m # foldr :: (a -> b -> b) -> b -> (f :*: g) a -> b # foldr' :: (a -> b -> b) -> b -> (f :*: g) a -> b # foldl :: (b -> a -> b) -> b -> (f :*: g) a -> b # foldl' :: (b -> a -> b) -> b -> (f :*: g) a -> b # foldr1 :: (a -> a -> a) -> (f :*: g) a -> a # foldl1 :: (a -> a -> a) -> (f :*: g) a -> a # toList :: (f :*: g) a -> [a] # length :: (f :*: g) a -> Int # elem :: Eq a => a -> (f :*: g) a -> Bool # maximum :: Ord a => (f :*: g) a -> a # minimum :: Ord a => (f :*: g) a -> a # | |
(Foldable f, Foldable g) => Foldable (f :+: g) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => (f :+: g) m -> m # foldMap :: Monoid m => (a -> m) -> (f :+: g) a -> m # foldMap' :: Monoid m => (a -> m) -> (f :+: g) a -> m # foldr :: (a -> b -> b) -> b -> (f :+: g) a -> b # foldr' :: (a -> b -> b) -> b -> (f :+: g) a -> b # foldl :: (b -> a -> b) -> b -> (f :+: g) a -> b # foldl' :: (b -> a -> b) -> b -> (f :+: g) a -> b # foldr1 :: (a -> a -> a) -> (f :+: g) a -> a # foldl1 :: (a -> a -> a) -> (f :+: g) a -> a # toList :: (f :+: g) a -> [a] # length :: (f :+: g) a -> Int # elem :: Eq a => a -> (f :+: g) a -> Bool # maximum :: Ord a => (f :+: g) a -> a # minimum :: Ord a => (f :+: g) a -> a # | |
Foldable (K1 i c :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => K1 i c m -> m # foldMap :: Monoid m => (a -> m) -> K1 i c a -> m # foldMap' :: Monoid m => (a -> m) -> K1 i c a -> m # foldr :: (a -> b -> b) -> b -> K1 i c a -> b # foldr' :: (a -> b -> b) -> b -> K1 i c a -> b # foldl :: (b -> a -> b) -> b -> K1 i c a -> b # foldl' :: (b -> a -> b) -> b -> K1 i c a -> b # foldr1 :: (a -> a -> a) -> K1 i c a -> a # foldl1 :: (a -> a -> a) -> K1 i c a -> a # elem :: Eq a => a -> K1 i c a -> Bool # maximum :: Ord a => K1 i c a -> a # minimum :: Ord a => K1 i c a -> a # | |
(Foldable f, Foldable g) => Foldable (Compose f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose fold :: Monoid m => Compose f g m -> m # foldMap :: Monoid m => (a -> m) -> Compose f g a -> m # foldMap' :: Monoid m => (a -> m) -> Compose f g a -> m # foldr :: (a -> b -> b) -> b -> Compose f g a -> b # foldr' :: (a -> b -> b) -> b -> Compose f g a -> b # foldl :: (b -> a -> b) -> b -> Compose f g a -> b # foldl' :: (b -> a -> b) -> b -> Compose f g a -> b # foldr1 :: (a -> a -> a) -> Compose f g a -> a # foldl1 :: (a -> a -> a) -> Compose f g a -> a # toList :: Compose f g a -> [a] # null :: Compose f g a -> Bool # length :: Compose f g a -> Int # elem :: Eq a => a -> Compose f g a -> Bool # maximum :: Ord a => Compose f g a -> a # minimum :: Ord a => Compose f g a -> a # | |
(Foldable f, Foldable g) => Foldable (f :.: g) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => (f :.: g) m -> m # foldMap :: Monoid m => (a -> m) -> (f :.: g) a -> m # foldMap' :: Monoid m => (a -> m) -> (f :.: g) a -> m # foldr :: (a -> b -> b) -> b -> (f :.: g) a -> b # foldr' :: (a -> b -> b) -> b -> (f :.: g) a -> b # foldl :: (b -> a -> b) -> b -> (f :.: g) a -> b # foldl' :: (b -> a -> b) -> b -> (f :.: g) a -> b # foldr1 :: (a -> a -> a) -> (f :.: g) a -> a # foldl1 :: (a -> a -> a) -> (f :.: g) a -> a # toList :: (f :.: g) a -> [a] # length :: (f :.: g) a -> Int # elem :: Eq a => a -> (f :.: g) a -> Bool # maximum :: Ord a => (f :.: g) a -> a # minimum :: Ord a => (f :.: g) a -> a # | |
Foldable f => Foldable (M1 i c f) | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => M1 i c f m -> m # foldMap :: Monoid m => (a -> m) -> M1 i c f a -> m # foldMap' :: Monoid m => (a -> m) -> M1 i c f a -> m # foldr :: (a -> b -> b) -> b -> M1 i c f a -> b # foldr' :: (a -> b -> b) -> b -> M1 i c f a -> b # foldl :: (b -> a -> b) -> b -> M1 i c f a -> b # foldl' :: (b -> a -> b) -> b -> M1 i c f a -> b # foldr1 :: (a -> a -> a) -> M1 i c f a -> a # foldl1 :: (a -> a -> a) -> M1 i c f a -> a # elem :: Eq a => a -> M1 i c f a -> Bool # maximum :: Ord a => M1 i c f a -> a # minimum :: Ord a => M1 i c f a -> a # |
concat :: Foldable t => t [a] -> [a] #
The concatenation of all the elements of a container of lists.
Examples
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]
and :: Foldable t => t Bool -> Bool #
and
returns the conjunction of a container of Bools. For the
result to be True
, the container must be finite; False
, however,
results from a False
value finitely far from the left end.
Examples
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 #
or
returns the disjunction of a container of Bools. For the
result to be False
, the container must be finite; True
, however,
results from a True
value finitely far from the left end.
Examples
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 #
Determines whether any element of the structure satisfies the predicate.
Examples
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 #
Determines whether all elements of the structure satisfy the predicate.
Examples
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 *
concatMap :: Foldable t => (a -> [b]) -> t a -> [b] #
Map a function over all the elements of a container and concatenate the resulting lists.
Examples
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]
foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b #
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 (
short-circuits (as with, e.g.,
>>=
)mzero
in a MonadPlus
), 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
instead.
If the monadic effects don't short-circuit, the outermost application of
f
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
Basic usage:
>>>
let f a e = do { print e ; return $ e : a }
>>>
foldlM f [] [0..3]
0 1 2 3 [3,2,1,0]
traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f () #
Map each element of a structure to an Applicative
action, evaluate these
actions from left to right, and ignore the results. For a version that
doesn't ignore the results see traverse
.
traverse_
is just like mapM_
, but generalised to Applicative
actions.
Examples
Basic usage:
>>>
traverse_ print ["Hello", "world", "!"]
"Hello" "world" "!"
for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f () #
for_
is traverse_
with its arguments flipped. For a version
that doesn't ignore the results see for
. This
is forM_
generalised to Applicative
actions.
for_
is just like forM_
, but generalised to Applicative
actions.
Examples
Basic usage:
>>>
for_ [1..4] print
1 2 3 4
sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f () #
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
.
sequenceA_
is just like sequence_
, but generalised to Applicative
actions.
Examples
Basic usage:
>>>
sequenceA_ [print "Hello", print "world", print "!"]
"Hello" "world" "!"
sequence_ :: (Foldable t, Monad m) => t (m a) -> m () #
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
.
sequence_
is just like sequenceA_
, but specialised to monadic
actions.
asum :: (Foldable t, Alternative f) => t (f a) -> f a #
The sum of a collection of actions using (<|>)
, generalizing concat
.
asum
is just like msum
, but generalised to Alternative
.
Examples
Basic usage:
>>>
asum [Just "Hello", Nothing, Just "World"]
Just "Hello"
class (Functor t, Foldable t) => Traversable (t :: Type -> Type) where #
Functors representing data structures that can be transformed to
structures of the same shape by performing an Applicative
(or,
therefore, Monad
) action on each element from left to right.
A more detailed description of what same shape means, the various methods, how traversals are constructed, and example advanced use-cases can be found in the Overview section of Data.Traversable.
For the class laws see the Laws section of Data.Traversable.
traverse :: Applicative f => (a -> f b) -> t a -> f (t b) #
Map each element of a structure to an action, evaluate these actions
from left to right, and collect the results. For a version that ignores
the results see traverse_
.
Examples
Basic usage:
In the first two examples we show each evaluated action mapping to the output structure.
>>>
traverse Just [1,2,3,4]
Just [1,2,3,4]
>>>
traverse id [Right 1, Right 2, Right 3, Right 4]
Right [1,2,3,4]
In the next examples, we show that Nothing
and Left
values short
circuit the created structure.
>>>
traverse (const Nothing) [1,2,3,4]
Nothing
>>>
traverse (\x -> if odd x then Just x else Nothing) [1,2,3,4]
Nothing
>>>
traverse id [Right 1, Right 2, Right 3, Right 4, Left 0]
Left 0
sequenceA :: Applicative f => t (f a) -> f (t a) #
Evaluate each action in the structure from left to right, and
collect the results. For a version that ignores the results
see sequenceA_
.
Examples
Basic usage:
For the first two examples we show sequenceA fully evaluating a a structure and collecting the results.
>>>
sequenceA [Just 1, Just 2, Just 3]
Just [1,2,3]
>>>
sequenceA [Right 1, Right 2, Right 3]
Right [1,2,3]
The next two example show Nothing
and Just
will short circuit
the resulting structure if present in the input. For more context,
check the Traversable
instances for Either
and Maybe
.
>>>
sequenceA [Just 1, Just 2, Just 3, Nothing]
Nothing
>>>
sequenceA [Right 1, Right 2, Right 3, Left 4]
Left 4
mapM :: Monad m => (a -> m b) -> t a -> m (t b) #
Map each element of a structure to a monadic action, evaluate
these actions from left to right, and collect the results. For
a version that ignores the results see mapM_
.
Examples
sequence :: Monad m => t (m a) -> m (t a) #
Evaluate each monadic action in the structure from left to
right, and collect the results. For a version that ignores the
results see sequence_
.
Examples
Basic usage:
The first two examples are instances where the input and
and output of sequence
are isomorphic.
>>>
sequence $ Right [1,2,3,4]
[Right 1,Right 2,Right 3,Right 4]
>>>
sequence $ [Right 1,Right 2,Right 3,Right 4]
Right [1,2,3,4]
The following examples demonstrate short circuit behavior
for sequence
.
>>>
sequence $ Left [1,2,3,4]
Left [1,2,3,4]
>>>
sequence $ [Left 0, Right 1,Right 2,Right 3,Right 4]
Left 0
Instances
forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) #
mapAccumL :: Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b) #
The mapAccumL
function behaves like a combination of fmap
and foldl
; it applies a function to each element of a structure,
passing an accumulating parameter from left to right, and returning
a final value of this accumulator together with the new structure.
Examples
Basic usage:
>>>
mapAccumL (\a b -> (a + b, a)) 0 [1..10]
(55,[0,1,3,6,10,15,21,28,36,45])
>>>
mapAccumL (\a b -> (a <> show b, a)) "0" [1..5]
("012345",["0","01","012","0123","01234"])
mapAccumR :: Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b) #
The mapAccumR
function behaves like a combination of fmap
and foldr
; it applies a function to each element of a structure,
passing an accumulating parameter from right to left, and returning
a final value of this accumulator together with the new structure.
Examples
Basic usage:
>>>
mapAccumR (\a b -> (a + b, a)) 0 [1..10]
(55,[54,52,49,45,40,34,27,19,10,0])
>>>
mapAccumR (\a b -> (a <> show b, a)) "0" [1..5]
("054321",["05432","0543","054","05","0"])
Bi
reexports
class Bifoldable (p :: Type -> Type -> Type) where #
Bifoldable
identifies foldable structures with two different varieties
of elements (as opposed to Foldable
, which has one variety of element).
Common examples are Either
and (,)
:
instance Bifoldable Either where bifoldMap f _ (Left a) = f a bifoldMap _ g (Right b) = g b instance Bifoldable (,) where bifoldr f g z (a, b) = f a (g b z)
Some examples below also use the following BiList to showcase empty
Bifoldable behaviors when relevant (Either
and (,)
containing always exactly
resp. 1 and 2 elements):
data BiList a b = BiList [a] [b] instance Bifoldable BiList where bifoldr f g z (BiList as bs) = foldr f (foldr g z bs) as
A minimal Bifoldable
definition consists of either bifoldMap
or
bifoldr
. When defining more than this minimal set, one should ensure
that the following identities hold:
bifold
≡bifoldMap
id
id
bifoldMap
f g ≡bifoldr
(mappend
. f) (mappend
. g)mempty
bifoldr
f g z t ≡appEndo
(bifoldMap
(Endo . f) (Endo . g) t) z
If the type is also a Bifunctor
instance, it should satisfy:
bifoldMap
f g ≡bifold
.bimap
f g
which implies that
bifoldMap
f g .bimap
h i ≡bifoldMap
(f . h) (g . i)
Since: base-4.10.0.0
bifold :: Monoid m => p m m -> m #
Combines the elements of a structure using a monoid.
bifold
≡bifoldMap
id
id
Examples
Basic usage:
>>>
bifold (Right [1, 2, 3])
[1,2,3]
>>>
bifold (Left [5, 6])
[5,6]
>>>
bifold ([1, 2, 3], [4, 5])
[1,2,3,4,5]
>>>
bifold (Product 6, Product 7)
Product {getProduct = 42}
>>>
bifold (Sum 6, Sum 7)
Sum {getSum = 13}
Since: base-4.10.0.0
bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> p a b -> m #
Combines the elements of a structure, given ways of mapping them to a common monoid.
bifoldMap
f g ≡bifoldr
(mappend
. f) (mappend
. g)mempty
Examples
Basic usage:
>>>
bifoldMap (take 3) (fmap digitToInt) ([1..], "89")
[1,2,3,8,9]
>>>
bifoldMap (take 3) (fmap digitToInt) (Left [1..])
[1,2,3]
>>>
bifoldMap (take 3) (fmap digitToInt) (Right "89")
[8,9]
Since: base-4.10.0.0
bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> p a b -> c #
Combines the elements of a structure in a right associative manner.
Given a hypothetical function toEitherList :: p a b -> [Either a b]
yielding a list of all elements of a structure in order, the following
would hold:
bifoldr
f g z ≡foldr
(either
f g) z . toEitherList
Examples
Basic usage:
> bifoldr (+) (*) 3 (5, 7) 26 -- 5 + (7 * 3) > bifoldr (+) (*) 3 (7, 5) 22 -- 7 + (5 * 3) > bifoldr (+) (*) 3 (Right 5) 15 -- 5 * 3 > bifoldr (+) (*) 3 (Left 5) 8 -- 5 + 3
Since: base-4.10.0.0
bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> p a b -> c #
Combines the elements of a structure in a left associative manner. Given
a hypothetical function toEitherList :: p a b -> [Either a b]
yielding a
list of all elements of a structure in order, the following would hold:
bifoldl
f g z ≡foldl
(acc ->either
(f acc) (g acc)) z . toEitherList
Note that if you want an efficient left-fold, you probably want to use
bifoldl'
instead of bifoldl
. The reason is that the latter does not
force the "inner" results, resulting in a thunk chain which then must be
evaluated from the outside-in.
Examples
Basic usage:
> bifoldl (+) (*) 3 (5, 7) 56 -- (5 + 3) * 7 > bifoldl (+) (*) 3 (7, 5) 50 -- (7 + 3) * 5 > bifoldl (+) (*) 3 (Right 5) 15 -- 5 * 3 > bifoldl (+) (*) 3 (Left 5) 8 -- 5 + 3
Since: base-4.10.0.0
Instances
Bifoldable Either | Since: base-4.10.0.0 |
Bifoldable Arg | Since: base-4.10.0.0 |
Bifoldable Map | Since: containers-0.6.3.1 |
Bifoldable HashMap | Since: unordered-containers-0.2.11 |
Bifoldable (,) | Since: base-4.10.0.0 |
Bifoldable (Const :: Type -> Type -> Type) | Since: base-4.10.0.0 |
Bifoldable ((,,) x) | Since: base-4.10.0.0 |
Bifoldable (K1 i :: Type -> Type -> Type) | Since: base-4.10.0.0 |
Bifoldable ((,,,) x y) | Since: base-4.10.0.0 |
Bifoldable ((,,,,) x y z) | Since: base-4.10.0.0 |
Bifoldable ((,,,,,) x y z w) | Since: base-4.10.0.0 |
Bifoldable ((,,,,,,) x y z w v) | Since: base-4.10.0.0 |
Defined in Data.Bifoldable |
bifoldr' :: Bifoldable t => (a -> c -> c) -> (b -> c -> c) -> c -> t a b -> c #
As bifoldr
, but strict in the result of the reduction functions at each
step.
Since: base-4.10.0.0
bifoldrM :: (Bifoldable t, Monad m) => (a -> c -> m c) -> (b -> c -> m c) -> c -> t a b -> m c #
Right associative monadic bifold over a structure.
Since: base-4.10.0.0
bifoldl' :: Bifoldable t => (a -> b -> a) -> (a -> c -> a) -> a -> t b c -> a #
As bifoldl
, but strict in the result of the reduction functions at each
step.
This ensures that each step of the bifold 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, monolithic result (e.g., bilength
).
Since: base-4.10.0.0
bifoldlM :: (Bifoldable t, Monad m) => (a -> b -> m a) -> (a -> c -> m a) -> a -> t b c -> m a #
Left associative monadic bifold over a structure.
Examples
Basic usage:
>>>
bifoldlM (\a b -> print b >> pure a) (\a c -> print (show c) >> pure a) 42 ("Hello", True)
"Hello" "True" 42
>>>
bifoldlM (\a b -> print b >> pure a) (\a c -> print (show c) >> pure a) 42 (Right True)
"True" 42
>>>
bifoldlM (\a b -> print b >> pure a) (\a c -> print (show c) >> pure a) 42 (Left "Hello")
"Hello" 42
Since: base-4.10.0.0
bitraverse_ :: (Bifoldable t, Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f () #
Map each element of a structure using one of two actions, evaluate these
actions from left to right, and ignore the results. For a version that
doesn't ignore the results, see bitraverse
.
Examples
Basic usage:
>>>
bitraverse_ print (print . show) ("Hello", True)
"Hello" "True"
>>>
bitraverse_ print (print . show) (Right True)
"True"
>>>
bitraverse_ print (print . show) (Left "Hello")
"Hello"
Since: base-4.10.0.0
bifor_ :: (Bifoldable t, Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f () #
As bitraverse_
, but with the structure as the primary argument. For a
version that doesn't ignore the results, see bifor
.
Examples
Basic usage:
>>>
bifor_ ("Hello", True) print (print . show)
"Hello" "True"
>>>
bifor_ (Right True) print (print . show)
"True"
>>>
bifor_ (Left "Hello") print (print . show)
"Hello"
Since: base-4.10.0.0
bisequence_ :: (Bifoldable t, Applicative f) => t (f a) (f b) -> f () #
Evaluate each action in the structure from left to right, and ignore the
results. For a version that doesn't ignore the results, see
bisequence
.
Examples
Basic usage:
>>>
bisequence_ (print "Hello", print "World")
"Hello" "World"
>>>
bisequence_ (Left (print "Hello"))
"Hello"
>>>
bisequence_ (Right (print "World"))
"World"
Since: base-4.10.0.0
biasum :: (Bifoldable t, Alternative f) => t (f a) (f a) -> f a #
The sum of a collection of actions, generalizing biconcat
.
Examples
Basic usage:
>>>
biasum (Nothing, Nothing)
Nothing
>>>
biasum (Nothing, Just 42)
Just 42
>>>
biasum (Just 18, Nothing)
Just 18
>>>
biasum (Just 18, Just 42)
Just 18
Since: base-4.10.0.0
biList :: Bifoldable t => t a a -> [a] #
Collects the list of elements of a structure, from left to right.
Examples
Basic usage:
>>>
biList (18, 42)
[18,42]
>>>
biList (Left 18)
[18]
Since: base-4.10.0.0
binull :: Bifoldable t => t a b -> Bool #
Test whether the structure is empty.
Examples
Basic usage:
>>>
binull (18, 42)
False
>>>
binull (Right 42)
False
>>>
binull (BiList [] [])
True
Since: base-4.10.0.0
bilength :: Bifoldable t => t a b -> Int #
Returns the size/length of a finite structure as an Int
.
Examples
Basic usage:
>>>
bilength (True, 42)
2
>>>
bilength (Right 42)
1
>>>
bilength (BiList [1,2,3] [4,5])
5
>>>
bilength (BiList [] [])
0
On infinite structures, this function hangs:
> bilength (BiList [1..] []) * Hangs forever *
Since: base-4.10.0.0
bielem :: (Bifoldable t, Eq a) => a -> t a a -> Bool #
Does the element occur in the structure?
Examples
Basic usage:
>>>
bielem 42 (17, 42)
True
>>>
bielem 42 (17, 43)
False
>>>
bielem 42 (Left 42)
True
>>>
bielem 42 (Right 13)
False
>>>
bielem 42 (BiList [1..5] [1..100])
True
>>>
bielem 42 (BiList [1..5] [1..41])
False
Since: base-4.10.0.0
biand :: Bifoldable t => t Bool Bool -> Bool #
biand
returns the conjunction of a container of Bools. For the
result to be True
, the container must be finite; False
, however,
results from a False
value finitely far from the left end.
Examples
Basic usage:
>>>
biand (True, False)
False
>>>
biand (True, True)
True
>>>
biand (Left True)
True
Empty structures yield True
:
>>>
biand (BiList [] [])
True
A False
value finitely far from the left end yields False
(short circuit):
>>>
biand (BiList [True, True, False, True] (repeat True))
False
A False
value infinitely far from the left end hangs:
> biand (BiList (repeat True) [False]) * Hangs forever *
An infinitely True
value hangs:
> biand (BiList (repeat True) []) * Hangs forever *
Since: base-4.10.0.0
bior :: Bifoldable t => t Bool Bool -> Bool #
bior
returns the disjunction of a container of Bools. For the
result to be False
, the container must be finite; True
, however,
results from a True
value finitely far from the left end.
Examples
Basic usage:
>>>
bior (True, False)
True
>>>
bior (False, False)
False
>>>
bior (Left True)
True
Empty structures yield False
:
>>>
bior (BiList [] [])
False
A True
value finitely far from the left end yields True
(short circuit):
>>>
bior (BiList [False, False, True, False] (repeat False))
True
A True
value infinitely far from the left end hangs:
> bior (BiList (repeat False) [True]) * Hangs forever *
An infinitely False
value hangs:
> bior (BiList (repeat False) []) * Hangs forever *
Since: base-4.10.0.0
biany :: Bifoldable t => (a -> Bool) -> (b -> Bool) -> t a b -> Bool #
Determines whether any element of the structure satisfies its appropriate
predicate argument. Empty structures yield False
.
Examples
Basic usage:
>>>
biany even isDigit (27, 't')
False
>>>
biany even isDigit (27, '8')
True
>>>
biany even isDigit (26, 't')
True
>>>
biany even isDigit (Left 27)
False
>>>
biany even isDigit (Left 26)
True
>>>
biany even isDigit (BiList [27, 53] ['t', '8'])
True
Empty structures yield False
:
>>>
biany even isDigit (BiList [] [])
False
Since: base-4.10.0.0
biall :: Bifoldable t => (a -> Bool) -> (b -> Bool) -> t a b -> Bool #
Determines whether all elements of the structure satisfy their appropriate
predicate argument. Empty structures yield True
.
Examples
Basic usage:
>>>
biall even isDigit (27, 't')
False
>>>
biall even isDigit (26, '8')
True
>>>
biall even isDigit (Left 27)
False
>>>
biall even isDigit (Left 26)
True
>>>
biall even isDigit (BiList [26, 52] ['3', '8'])
True
Empty structures yield True
:
>>>
biall even isDigit (BiList [] [])
True
Since: base-4.10.0.0
bifind :: Bifoldable t => (a -> Bool) -> t a a -> Maybe a #
The bifind
function takes a predicate and a structure and returns
the leftmost element of the structure matching the predicate, or
Nothing
if there is no such element.
Examples
Basic usage:
>>>
bifind even (27, 53)
Nothing
>>>
bifind even (27, 52)
Just 52
>>>
bifind even (26, 52)
Just 26
Empty structures always yield Nothing
:
>>>
bifind even (BiList [] [])
Nothing
Since: base-4.10.0.0
class (Bifunctor t, Bifoldable t) => Bitraversable (t :: Type -> Type -> Type) where #
Bitraversable
identifies bifunctorial data structures whose elements can
be traversed in order, performing Applicative
or Monad
actions at each
element, and collecting a result structure with the same shape.
As opposed to Traversable
data structures, which have one variety of
element on which an action can be performed, Bitraversable
data structures
have two such varieties of elements.
A definition of bitraverse
must satisfy the following laws:
- Naturality
for every applicative transformationbitraverse
(t . f) (t . g) ≡ t .bitraverse
f gt
- Identity
bitraverse
Identity
Identity
≡Identity
- Composition
Compose
.fmap
(bitraverse
g1 g2) .bitraverse
f1 f2 ≡bitraverse
(Compose
.fmap
g1 . f1) (Compose
.fmap
g2 . f2)
where an applicative transformation is a function
t :: (Applicative
f,Applicative
g) => f a -> g a
preserving the Applicative
operations:
t (pure
x) =pure
x t (f<*>
x) = t f<*>
t x
and the identity functor Identity
and composition functors
Compose
are from Data.Functor.Identity and
Data.Functor.Compose.
Some simple examples are Either
and (,)
:
instance Bitraversable Either where bitraverse f _ (Left x) = Left <$> f x bitraverse _ g (Right y) = Right <$> g y instance Bitraversable (,) where bitraverse f g (x, y) = (,) <$> f x <*> g y
Bitraversable
relates to its superclasses in the following ways:
bimap
f g ≡runIdentity
.bitraverse
(Identity
. f) (Identity
. g)bifoldMap
f g =getConst
.bitraverse
(Const
. f) (Const
. g)
These are available as bimapDefault
and bifoldMapDefault
respectively.
Since: base-4.10.0.0
bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> t a b -> f (t c d) #
Evaluates the relevant functions at each element in the structure, running the action, and builds a new structure with the same shape, using the results produced from sequencing the actions.
bitraverse
f g ≡bisequenceA
.bimap
f g
For a version that ignores the results, see bitraverse_
.
Examples
Basic usage:
>>>
bitraverse listToMaybe (find odd) (Left [])
Nothing
>>>
bitraverse listToMaybe (find odd) (Left [1, 2, 3])
Just (Left 1)
>>>
bitraverse listToMaybe (find odd) (Right [4, 5])
Just (Right 5)
>>>
bitraverse listToMaybe (find odd) ([1, 2, 3], [4, 5])
Just (1,5)
>>>
bitraverse listToMaybe (find odd) ([], [4, 5])
Nothing
Since: base-4.10.0.0
Instances
Bitraversable Either | Since: base-4.10.0.0 |
Defined in Data.Bitraversable bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Either a b -> f (Either c d) # | |
Bitraversable Arg | Since: base-4.10.0.0 |
Defined in Data.Semigroup bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Arg a b -> f (Arg c d) # | |
Bitraversable (,) | Since: base-4.10.0.0 |
Defined in Data.Bitraversable bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (a, b) -> f (c, d) # | |
Bitraversable (Const :: Type -> Type -> Type) | Since: base-4.10.0.0 |
Defined in Data.Bitraversable bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Const a b -> f (Const c d) # | |
Bitraversable ((,,) x) | Since: base-4.10.0.0 |
Defined in Data.Bitraversable bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (x, a, b) -> f (x, c, d) # | |
Bitraversable (K1 i :: Type -> Type -> Type) | Since: base-4.10.0.0 |
Defined in Data.Bitraversable bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> K1 i a b -> f (K1 i c d) # | |
Bitraversable ((,,,) x y) | Since: base-4.10.0.0 |
Defined in Data.Bitraversable bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (x, y, a, b) -> f (x, y, c, d) # | |
Bitraversable ((,,,,) x y z) | Since: base-4.10.0.0 |
Defined in Data.Bitraversable bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (x, y, z, a, b) -> f (x, y, z, c, d) # | |
Bitraversable ((,,,,,) x y z w) | Since: base-4.10.0.0 |
Defined in Data.Bitraversable bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (x, y, z, w, a, b) -> f (x, y, z, w, c, d) # | |
Bitraversable ((,,,,,,) x y z w v) | Since: base-4.10.0.0 |
Defined in Data.Bitraversable bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> (x, y, z, w, v, a, b) -> f (x, y, z, w, v, c, d) # |
bifor :: (Bitraversable t, Applicative f) => t a b -> (a -> f c) -> (b -> f d) -> f (t c d) #
bifor
is bitraverse
with the structure as the first argument. For a
version that ignores the results, see bifor_
.
Examples
Basic usage:
>>>
bifor (Left []) listToMaybe (find even)
Nothing
>>>
bifor (Left [1, 2, 3]) listToMaybe (find even)
Just (Left 1)
>>>
bifor (Right [4, 5]) listToMaybe (find even)
Just (Right 4)
>>>
bifor ([1, 2, 3], [4, 5]) listToMaybe (find even)
Just (1,4)
>>>
bifor ([], [4, 5]) listToMaybe (find even)
Nothing
Since: base-4.10.0.0
bisequence :: (Bitraversable t, Applicative f) => t (f a) (f b) -> f (t a b) #
Sequences all the actions in a structure, building a new structure with
the same shape using the results of the actions. For a version that ignores
the results, see bisequence_
.
bisequence
≡bitraverse
id
id
Examples
Basic usage:
>>>
bisequence (Just 4, Nothing)
Nothing
>>>
bisequence (Just 4, Just 5)
Just (4,5)
>>>
bisequence ([1, 2, 3], [4, 5])
[(1,4),(1,5),(2,4),(2,5),(3,4),(3,5)]
Since: base-4.10.0.0
bimapDefault :: Bitraversable t => (a -> b) -> (c -> d) -> t a c -> t b d #
A default definition of bimap
in terms of the Bitraversable
operations.
bimapDefault
f g ≡runIdentity
.bitraverse
(Identity
. f) (Identity
. g)
Since: base-4.10.0.0
bifoldMapDefault :: (Bitraversable t, Monoid m) => (a -> m) -> (b -> m) -> t a b -> m #
A default definition of bifoldMap
in terms of the Bitraversable
operations.
bifoldMapDefault
f g ≡getConst
.bitraverse
(Const
. f) (Const
. g)
Since: base-4.10.0.0