Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
This module provides efficient and streaming left folds that you can combine
using
Applicative
style.
Import this module qualified to avoid clashing with the Prelude:
>>>
import qualified Control.Foldl as Foldl
Use
fold
to apply a
Fold
to a list:
>>>
Foldl.fold Foldl.sum [1..100]
5050
Fold
s are
Applicative
s, so you can combine them using
Applicative
combinators:
>>>
import Control.Applicative
>>>
let average = (/) <$> Foldl.sum <*> Foldl.genericLength
… or you can use
do
notation if you enable the
ApplicativeDo
language
extension:
>>>
:set -XApplicativeDo
>>>
let average = do total <- Foldl.sum; count <- Foldl.genericLength; return (total / count)
… or you can use the fact that the
Fold
type implements
Num
to do this:
>>>
let average = Foldl.sum / Foldl.genericLength
These combined folds will still traverse the list only once, streaming efficiently over the list in constant space without space leaks:
>>>
Foldl.fold average [1..10000000]
5000000.5>>>
Foldl.fold ((,) <$> Foldl.minimum <*> Foldl.maximum) [1..10000000]
(Just 1,Just 10000000)
You might want to try enabling the
-flate-dmd-anal
flag when compiling
executables that use this library to further improve performance.
Synopsis
- data Fold a b = forall x. Fold (x -> a -> x) x (x -> b)
- data FoldM m a b = forall x. FoldM (x -> a -> m x) (m x) (x -> m b)
- fold :: Foldable f => Fold a b -> f a -> b
- foldM :: ( Foldable f, Monad m) => FoldM m a b -> f a -> m b
- scan :: Fold a b -> [a] -> [b]
- prescan :: Traversable t => Fold a b -> t a -> t b
- postscan :: Traversable t => Fold a b -> t a -> t b
- mconcat :: Monoid a => Fold a a
- foldMap :: Monoid w => (a -> w) -> (w -> b) -> Fold a b
- head :: Fold a ( Maybe a)
- last :: Fold a ( Maybe a)
- lastDef :: a -> Fold a a
- lastN :: Int -> Fold a [a]
- null :: Fold a Bool
- length :: Fold a Int
- and :: Fold Bool Bool
- or :: Fold Bool Bool
- all :: (a -> Bool ) -> Fold a Bool
- any :: (a -> Bool ) -> Fold a Bool
- sum :: Num a => Fold a a
- product :: Num a => Fold a a
- mean :: Fractional a => Fold a a
- variance :: Fractional a => Fold a a
- std :: Floating a => Fold a a
- maximum :: Ord a => Fold a ( Maybe a)
- maximumBy :: (a -> a -> Ordering ) -> Fold a ( Maybe a)
- minimum :: Ord a => Fold a ( Maybe a)
- minimumBy :: (a -> a -> Ordering ) -> Fold a ( Maybe a)
- elem :: Eq a => a -> Fold a Bool
- notElem :: Eq a => a -> Fold a Bool
- find :: (a -> Bool ) -> Fold a ( Maybe a)
- index :: Int -> Fold a ( Maybe a)
- lookup :: Eq a => a -> Fold (a, b) ( Maybe b)
- elemIndex :: Eq a => a -> Fold a ( Maybe Int )
- findIndex :: (a -> Bool ) -> Fold a ( Maybe Int )
- random :: FoldM IO a ( Maybe a)
- randomN :: Vector v a => Int -> FoldM IO a ( Maybe (v a))
- mapM_ :: Monad m => (a -> m ()) -> FoldM m a ()
- sink :: ( Monoid w, Monad m) => (a -> m w) -> FoldM m a w
- genericLength :: Num b => Fold a b
- genericIndex :: Integral i => i -> Fold a ( Maybe a)
- list :: Fold a [a]
- revList :: Fold a [a]
- nub :: Ord a => Fold a [a]
- eqNub :: Eq a => Fold a [a]
- set :: Ord a => Fold a ( Set a)
- hashSet :: ( Eq a, Hashable a) => Fold a ( HashSet a)
- map :: Ord a => Fold (a, b) ( Map a b)
- foldByKeyMap :: forall k a b. Ord k => Fold a b -> Fold (k, a) ( Map k b)
- hashMap :: ( Eq a, Hashable a) => Fold (a, b) ( HashMap a b)
- foldByKeyHashMap :: forall k a b. ( Hashable k, Eq k) => Fold a b -> Fold (k, a) ( HashMap k b)
- vector :: Vector v a => Fold a (v a)
- vectorM :: ( PrimMonad m, Vector v a) => FoldM m a (v a)
- purely :: ( forall x. (x -> a -> x) -> x -> (x -> b) -> r) -> Fold a b -> r
- purely_ :: ( forall x. (x -> a -> x) -> x -> x) -> Fold a b -> b
- impurely :: ( forall x. (x -> a -> m x) -> m x -> (x -> m b) -> r) -> FoldM m a b -> r
- impurely_ :: Monad m => ( forall x. (x -> a -> m x) -> m x -> m x) -> FoldM m a b -> m b
- generalize :: Monad m => Fold a b -> FoldM m a b
- simplify :: FoldM Identity a b -> Fold a b
- hoists :: ( forall x. m x -> n x) -> FoldM m a b -> FoldM n a b
- duplicateM :: Applicative m => FoldM m a b -> FoldM m a ( FoldM m a b)
- _Fold1 :: (a -> a -> a) -> Fold a ( Maybe a)
- premap :: (a -> b) -> Fold b r -> Fold a r
- premapM :: Monad m => (a -> m b) -> FoldM m b r -> FoldM m a r
- prefilter :: (a -> Bool ) -> Fold a r -> Fold a r
- prefilterM :: Monad m => (a -> m Bool ) -> FoldM m a r -> FoldM m a r
- predropWhile :: (a -> Bool ) -> Fold a r -> Fold a r
- drop :: Natural -> Fold a b -> Fold a b
- dropM :: Monad m => Natural -> FoldM m a b -> FoldM m a b
- type Handler a b = forall x. (b -> Const ( Dual ( Endo x)) b) -> a -> Const ( Dual ( Endo x)) a
- handles :: Handler a b -> Fold b r -> Fold a r
- foldOver :: Handler s a -> Fold a b -> s -> b
-
newtype
EndoM
m a =
EndoM
{
- appEndoM :: a -> m a
- type HandlerM m a b = forall x. (b -> Const ( Dual ( EndoM m x)) b) -> a -> Const ( Dual ( EndoM m x)) a
- handlesM :: HandlerM m a b -> FoldM m b r -> FoldM m a r
- foldOverM :: Monad m => HandlerM m s a -> FoldM m a b -> s -> m b
- folded :: ( Contravariant f, Applicative f, Foldable t) => (a -> f a) -> t a -> f (t a)
- filtered :: Monoid m => (a -> Bool ) -> (a -> m) -> a -> m
- groupBy :: Ord g => (a -> g) -> Fold a r -> Fold a ( Map g r)
- either :: Fold a1 b1 -> Fold a2 b2 -> Fold ( Either a1 a2) (b1, b2)
- eitherM :: Monad m => FoldM m a1 b1 -> FoldM m a2 b2 -> FoldM m ( Either a1 a2) (b1, b2)
- nest :: Applicative f => Fold a b -> Fold (f a) (f b)
- data RealWorld
- class Monad m => PrimMonad (m :: Type -> Type )
- class Foldable (t :: Type -> Type )
- type family Mutable (v :: Type -> Type ) = (mv :: Type -> Type -> Type ) | mv -> v
- class MVector ( Mutable v) a => Vector (v :: Type -> Type ) a
Fold Types
Efficient representation of a left fold that preserves the fold's step function, initial accumulator, and extraction function
This allows the
Applicative
instance to assemble derived folds that
traverse the container only once
A '
Fold
a b' processes elements of type
a
and results in a
value of type
b
.
forall x. Fold (x -> a -> x) x (x -> b) |
|
Instances
Like
Fold
, but monadic.
A '
FoldM
m a b' processes elements of type
a
and
results in a monadic value of type
m b
.
forall x. FoldM (x -> a -> m x) (m x) (x -> m b) |
|
Instances
Functor m => Profunctor ( FoldM m) Source # | |
Defined in Control.Foldl dimap :: (a -> b) -> (c -> d) -> FoldM m b c -> FoldM m a d Source # lmap :: (a -> b) -> FoldM m b c -> FoldM m a c Source # rmap :: (b -> c) -> FoldM m a b -> FoldM m a c Source # (#.) :: forall a b c q. Coercible c b => q b c -> FoldM m a b -> FoldM m a c Source # (.#) :: forall a b c q. Coercible b a => FoldM m b c -> q a b -> FoldM m a c Source # |
|
Functor m => Functor ( FoldM m a) Source # | |
Applicative m => Applicative ( FoldM m a) Source # | |
Defined in Control.Foldl pure :: a0 -> FoldM m a a0 Source # (<*>) :: FoldM m a (a0 -> b) -> FoldM m a a0 -> FoldM m a b Source # liftA2 :: (a0 -> b -> c) -> FoldM m a a0 -> FoldM m a b -> FoldM m a c Source # (*>) :: FoldM m a a0 -> FoldM m a b -> FoldM m a b Source # (<*) :: FoldM m a a0 -> FoldM m a b -> FoldM m a a0 Source # |
|
Monad m => Extend ( FoldM m a) Source # | |
( Monad m, Floating b) => Floating ( FoldM m a b) Source # | |
Defined in Control.Foldl exp :: FoldM m a b -> FoldM m a b Source # log :: FoldM m a b -> FoldM m a b Source # sqrt :: FoldM m a b -> FoldM m a b Source # (**) :: FoldM m a b -> FoldM m a b -> FoldM m a b Source # logBase :: FoldM m a b -> FoldM m a b -> FoldM m a b Source # sin :: FoldM m a b -> FoldM m a b Source # cos :: FoldM m a b -> FoldM m a b Source # tan :: FoldM m a b -> FoldM m a b Source # asin :: FoldM m a b -> FoldM m a b Source # acos :: FoldM m a b -> FoldM m a b Source # atan :: FoldM m a b -> FoldM m a b Source # sinh :: FoldM m a b -> FoldM m a b Source # cosh :: FoldM m a b -> FoldM m a b Source # tanh :: FoldM m a b -> FoldM m a b Source # asinh :: FoldM m a b -> FoldM m a b Source # acosh :: FoldM m a b -> FoldM m a b Source # atanh :: FoldM m a b -> FoldM m a b Source # log1p :: FoldM m a b -> FoldM m a b Source # expm1 :: FoldM m a b -> FoldM m a b Source # |
|
( Monad m, Fractional b) => Fractional ( FoldM m a b) Source # | |
( Monad m, Num b) => Num ( FoldM m a b) Source # | |
Defined in Control.Foldl (+) :: FoldM m a b -> FoldM m a b -> FoldM m a b Source # (-) :: FoldM m a b -> FoldM m a b -> FoldM m a b Source # (*) :: FoldM m a b -> FoldM m a b -> FoldM m a b Source # negate :: FoldM m a b -> FoldM m a b Source # abs :: FoldM m a b -> FoldM m a b Source # signum :: FoldM m a b -> FoldM m a b Source # fromInteger :: Integer -> FoldM m a b Source # |
|
( Semigroup b, Monad m) => Semigroup ( FoldM m a b) Source # | |
( Monoid b, Monad m) => Monoid ( FoldM m a b) Source # | |
Folding
scan :: Fold a b -> [a] -> [b] Source #
Convert a strict left
Fold
into a scan
>>>
Foldl.scan Foldl.length [1..5]
[0,1,2,3,4,5]
prescan :: Traversable t => Fold a b -> t a -> t b Source #
Convert a
Fold
into a prescan for any
Traversable
type
"Prescan" means that the last element of the scan is not included
>>>
Foldl.prescan Foldl.length [1..5]
[0,1,2,3,4]
postscan :: Traversable t => Fold a b -> t a -> t b Source #
Convert a
Fold
into a postscan for any
Traversable
type
"Postscan" means that the first element of the scan is not included
>>>
Foldl.postscan Foldl.length [1..5]
[1,2,3,4,5]
Folds
head :: Fold a ( Maybe a) Source #
Get the first element of a container or return
Nothing
if the container is
empty
last :: Fold a ( Maybe a) Source #
Get the last element of a container or return
Nothing
if the container is
empty
lastDef :: a -> Fold a a Source #
Get the last element of a container or return a default value if the container is empty
mean :: Fractional a => Fold a a Source #
Compute a numerically stable arithmetic mean of all elements
variance :: Fractional a => Fold a a Source #
Compute a numerically stable (population) variance over all elements
std :: Floating a => Fold a a Source #
Compute a numerically stable (population) standard deviation over all elements
maximumBy :: (a -> a -> Ordering ) -> Fold a ( Maybe a) Source #
Computes the maximum element with respect to the given comparison function
minimumBy :: (a -> a -> Ordering ) -> Fold a ( Maybe a) Source #
Computes the minimum element with respect to the given comparison function
find :: (a -> Bool ) -> Fold a ( Maybe a) Source #
(find predicate)
returns the first element that satisfies the predicate or
Nothing
if no element satisfies the predicate
index :: Int -> Fold a ( Maybe a) Source #
(index n)
returns the
n
th element of the container, or
Nothing
if the
container has an insufficient number of elements
lookup :: Eq a => a -> Fold (a, b) ( Maybe b) Source #
(lookup a)
returns the element paired with the first matching item, or
Nothing
if none matches
elemIndex :: Eq a => a -> Fold a ( Maybe Int ) Source #
(elemIndex a)
returns the index of the first element that equals
a
, or
Nothing
if no element matches
findIndex :: (a -> Bool ) -> Fold a ( Maybe Int ) Source #
(findIndex predicate)
returns the index of the first element that
satisfies the predicate, or
Nothing
if no element satisfies the predicate
randomN :: Vector v a => Int -> FoldM IO a ( Maybe (v a)) Source #
Pick several random elements, using reservoir sampling
mapM_ :: Monad m => (a -> m ()) -> FoldM m a () Source #
Converts an effectful function to a fold. Specialized version of
sink
.
sink :: ( Monoid w, Monad m) => (a -> m w) -> FoldM m a w Source #
Converts an effectful function to a fold
sink (f <> g) = sink f <> sink g -- if `(<>)` is commutative sink mempty = mempty
Generic Folds
genericLength :: Num b => Fold a b Source #
Container folds
nub :: Ord a => Fold a [a] Source #
O(n log n) . Fold values into a list with duplicates removed, while preserving their first occurrences
eqNub :: Eq a => Fold a [a] Source #
O(n^2) . Fold values into a list with duplicates removed, while preserving their first occurrences
foldByKeyHashMap :: forall k a b. ( Hashable k, Eq k) => Fold a b -> Fold (k, a) ( HashMap k b) Source #
vectorM :: ( PrimMonad m, Vector v a) => FoldM m a (v a) Source #
Fold all values into a vector
This is more efficient than
vector
but is impure
Utilities
purely
and
impurely
allow you to write folds compatible with the
foldl
library without incurring a
foldl
dependency. Write your fold to accept
three parameters corresponding to the step function, initial
accumulator, and extraction function and then users can upgrade your
function to accept a
Fold
or
FoldM
using the
purely
or
impurely
combinators.
For example, the
pipes
library implements
fold
and
foldM
functions in
Pipes.Prelude
with the following type:
Pipes.Prelude.fold :: Monad m -> (x -> a -> x) -> x -> (x -> b) -> Producer a m () -> m b Pipes.Prelude.foldM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Producer a m () -> m b
Both
fold
and
foldM
is set up so that you can wrap them with either
purely
or
impurely
to accept a
Fold
or
FoldM
, respectively:
purely Pipes.Prelude.fold :: Monad m => Fold a b -> Producer a m () -> m b impurely Pipes.Prelude.foldM :: Monad m => FoldM m a b -> Producer a m () -> m b
Other streaming libraries supporting
purely
and
impurely
include
io-streams
and
streaming
.
So for example we have:
purely System.IO.Streams.fold_ :: Fold a b -> Streams.InputStream a -> IO b impurely System.IO.Streams.foldM_ :: FoldM IO a b -> Streams.InputStream a -> IO b
The
monotraversable
package makes it convenient to apply a
Fold
or
FoldM
to pure containers that do not allow
a general
Foldable
instance, like unboxed vectors:
purely ofoldlUnwrap :: MonoFoldable mono => Fold (Element mono) b -> mono -> b impurely ofoldMUnwrap :: MonoFoldable mono => FoldM m (Element mono) b -> mono -> m b
purely :: ( forall x. (x -> a -> x) -> x -> (x -> b) -> r) -> Fold a b -> r Source #
Upgrade a fold to accept the
Fold
type
purely_ :: ( forall x. (x -> a -> x) -> x -> x) -> Fold a b -> b Source #
Upgrade a more traditional fold to accept the
Fold
type
impurely :: ( forall x. (x -> a -> m x) -> m x -> (x -> m b) -> r) -> FoldM m a b -> r Source #
Upgrade a monadic fold to accept the
FoldM
type
impurely_ :: Monad m => ( forall x. (x -> a -> m x) -> m x -> m x) -> FoldM m a b -> m b Source #
Upgrade a more traditional monadic fold to accept the
FoldM
type
duplicateM :: Applicative m => FoldM m a b -> FoldM m a ( FoldM m a b) Source #
premap :: (a -> b) -> Fold b r -> Fold a r Source #
(premap f folder)
returns a new
Fold
where f is applied at each step
fold (premap f folder) list = fold folder (List.map f list)
>>>
fold (premap Sum Foldl.mconcat) [1..10]
Sum {getSum = 55}
>>>
fold Foldl.mconcat (List.map Sum [1..10])
Sum {getSum = 55}
premap id = id premap (f . g) = premap g . premap f
premap k (pure r) = pure r premap k (f <*> x) = premap k f <*> premap k x
premapM :: Monad m => (a -> m b) -> FoldM m b r -> FoldM m a r Source #
(premapM f folder)
returns a new
FoldM
where f is applied to each input
element
premapM return = id premapM (f <=< g) = premap g . premap f
premapM k (pure r) = pure r premapM k (f <*> x) = premapM k f <*> premapM k x
prefilter :: (a -> Bool ) -> Fold a r -> Fold a r Source #
(prefilter f folder)
returns a new
Fold
where the folder's input is used
only when the input satisfies a predicate f
This can also be done with
handles
(
handles (filtered f)
) but
prefilter
does not need you to depend on a lens library.
fold (prefilter p folder) list = fold folder (filter p list)
>>>
fold (prefilter (>5) Control.Foldl.sum) [1..10]
40
>>>
fold Control.Foldl.sum (filter (>5) [1..10])
40
prefilterM :: Monad m => (a -> m Bool ) -> FoldM m a r -> FoldM m a r Source #
(prefilterM f folder)
returns a new
FoldM
where the folder's input is used
only when the input satisfies a monadic predicate f.
predropWhile :: (a -> Bool ) -> Fold a r -> Fold a r Source #
Transforms a
Fold
into one which ignores elements
until they stop satisfying a predicate
fold (predropWhile p folder) list = fold folder (dropWhile p list)
>>>
fold (predropWhile (>5) Control.Foldl.sum) [10,9,5,9]
14
drop :: Natural -> Fold a b -> Fold a b Source #
(drop n folder)
returns a new
Fold
that ignores the first
n
inputs but
otherwise behaves the same as the original fold.
fold (drop n folder) list = fold folder (Data.List.genericDrop n list)
>>>
Foldl.fold (Foldl.drop 3 Foldl.sum) [10, 20, 30, 1, 2, 3]
6
>>>
Foldl.fold (Foldl.drop 10 Foldl.sum) [10, 20, 30, 1, 2, 3]
0
dropM :: Monad m => Natural -> FoldM m a b -> FoldM m a b Source #
(dropM n folder)
returns a new
FoldM
that ignores the first
n
inputs but
otherwise behaves the same as the original fold.
foldM (dropM n folder) list = foldM folder (Data.List.genericDrop n list)
>>>
Foldl.foldM (Foldl.dropM 3 (Foldl.generalize Foldl.sum)) [10, 20, 30, 1, 2, 3]
6
>>>
Foldl.foldM (Foldl.dropM 10 (Foldl.generalize Foldl.sum)) [10, 20, 30, 1, 2, 3]
0
type Handler a b = forall x. (b -> Const ( Dual ( Endo x)) b) -> a -> Const ( Dual ( Endo x)) a Source #
handles :: Handler a b -> Fold b r -> Fold a r Source #
(handles t folder)
transforms the input of a
Fold
using a lens,
traversal, or prism:
handles _1 :: Fold a r -> Fold (a, b) r handles _Left :: Fold a r -> Fold (Either a b) r handles traverse :: Traversable t => Fold a r -> Fold (t a) r handles folded :: Foldable t => Fold a r -> Fold (t a) r
>>>
fold (handles traverse sum) [[1..5],[6..10]]
55
>>>
fold (handles (traverse.traverse) sum) [[Nothing, Just 2, Just 7],[Just 13, Nothing, Just 20]]
42
>>>
fold (handles (filtered even) sum) [1..10]
30
>>>
fold (handles _2 Foldl.mconcat) [(1,"Hello "),(2,"World"),(3,"!")]
"Hello World!"
handles id = id handles (f . g) = handles f . handles g
handles t (pure r) = pure r handles t (f <*> x) = handles t f <*> handles t x
foldOver :: Handler s a -> Fold a b -> s -> b Source #
(foldOver f folder xs)
folds all values from a Lens, Traversal, Prism or Fold with the given folder
>>>
foldOver (_Just . both) Foldl.sum (Just (2, 3))
5
>>>
foldOver (_Just . both) Foldl.sum Nothing
0
Foldl.foldOver f folder xs == Foldl.fold folder (xs^..f)
Foldl.foldOver (folded.f) folder == Foldl.fold (handles f folder)
Foldl.foldOver folded == Foldl.fold
instance Monad m => Monoid (EndoM m a) where mempty = EndoM return mappend (EndoM f) (EndoM g) = EndoM (f <=< g)
type HandlerM m a b = forall x. (b -> Const ( Dual ( EndoM m x)) b) -> a -> Const ( Dual ( EndoM m x)) a Source #
handlesM :: HandlerM m a b -> FoldM m b r -> FoldM m a r Source #
(handlesM t folder)
transforms the input of a
FoldM
using a lens,
traversal, or prism:
handlesM _1 :: FoldM m a r -> FoldM (a, b) r handlesM _Left :: FoldM m a r -> FoldM (Either a b) r handlesM traverse :: Traversable t => FoldM m a r -> FoldM m (t a) r handlesM folded :: Foldable t => FoldM m a r -> FoldM m (t a) r
handlesM
obeys these laws:
handlesM id = id handlesM (f . g) = handlesM f . handlesM g
handlesM t (pure r) = pure r handlesM t (f <*> x) = handlesM t f <*> handlesM t x
foldOverM :: Monad m => HandlerM m s a -> FoldM m a b -> s -> m b Source #
(foldOverM f folder xs)
folds all values from a Lens, Traversal, Prism or Fold monadically with the given folder
Foldl.foldOverM (folded.f) folder == Foldl.foldM (handlesM f folder)
Foldl.foldOverM folded == Foldl.foldM
folded :: ( Contravariant f, Applicative f, Foldable t) => (a -> f a) -> t a -> f (t a) Source #
folded :: Foldable t => Fold (t a) a handles folded :: Foldable t => Fold a r -> Fold (t a) r
filtered :: Monoid m => (a -> Bool ) -> (a -> m) -> a -> m Source #
>>>
fold (handles (filtered even) sum) [1..10]
30
>>>
foldM (handlesM (filtered even) (Foldl.mapM_ print)) [1..10]
2 4 6 8 10
groupBy :: Ord g => (a -> g) -> Fold a r -> Fold a ( Map g r) Source #
Perform a
Fold
while grouping the data according to a specified group
projection function. Returns the folded result grouped as a map keyed by the
group.
either :: Fold a1 b1 -> Fold a2 b2 -> Fold ( Either a1 a2) (b1, b2) Source #
Combine two folds into a fold over inputs for either of them.
eitherM :: Monad m => FoldM m a1 b1 -> FoldM m a2 b2 -> FoldM m ( Either a1 a2) (b1, b2) Source #
Combine two monadic folds into a fold over inputs for either of them.
Re-exports
Control.Monad.Primitive
re-exports the
PrimMonad
type class
Data.Foldable
re-exports the
Foldable
type class
Data.Vector.Generic
re-exports the
Vector
type class
RealWorld
is deeply magical. It is
primitive
, but it is not
unlifted
(hence
ptrArg
). We never manipulate values of type
RealWorld
; it's only used in the type system, to parameterise
State#
.
class Monad m => PrimMonad (m :: Type -> Type ) Source #
Class of monads which can perform primitive state-transformer actions.
Instances
PrimMonad IO | |
PrimMonad ( ST s) | |
PrimMonad ( ST s) | |
PrimMonad m => PrimMonad ( ListT m) | |
PrimMonad m => PrimMonad ( MaybeT m) | |
PrimMonad m => PrimMonad ( IdentityT m) | |
( Error e, PrimMonad m) => PrimMonad ( ErrorT e m) | |
PrimMonad m => PrimMonad ( ExceptT e m) | |
PrimMonad m => PrimMonad ( ReaderT r m) | |
PrimMonad m => PrimMonad ( StateT s m) | |
PrimMonad m => PrimMonad ( StateT s m) | |
( Monoid w, PrimMonad m) => PrimMonad ( WriterT w m) | |
( Monoid w, PrimMonad m) => PrimMonad ( WriterT w m) | |
( Monoid w, PrimMonad m) => PrimMonad ( AccumT w m) |
Since: primitive-0.6.3.0 |
( Monoid w, PrimMonad m) => PrimMonad ( WriterT w m) | |
PrimMonad m => PrimMonad ( SelectT r m) | |
PrimMonad m => PrimMonad ( ContT r m) |
Since: primitive-0.6.3.0 |
( Monoid w, PrimMonad m) => PrimMonad ( RWST r w s m) | |
( Monoid w, PrimMonad m) => PrimMonad ( RWST r w s m) | |
( Monoid w, PrimMonad m) => PrimMonad ( RWST r w s m) | |
class Foldable (t :: Type -> Type ) Source #
Data structures that can be folded.
For example, given a data type
data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
a suitable instance would be
instance Foldable Tree where foldMap f Empty = mempty foldMap f (Leaf x) = f x foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r
This is suitable even for abstract types, as the monoid is assumed
to satisfy the monoid laws. Alternatively, one could define
foldr
:
instance Foldable Tree where foldr f z Empty = z foldr f z (Leaf x) = f x z foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l
Foldable
instances are expected to satisfy the following laws:
foldr f z t = appEndo (foldMap (Endo . f) t ) z
foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
fold = foldMap id
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
but may be less defined.
If the type is also a
Functor
instance, it should satisfy
foldMap f = fold . fmap f
which implies that
foldMap f . fmap g = foldMap (f . g)
Instances
Foldable [] |
Since: base-2.1 |
Defined in Data.Foldable fold :: 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 # elem :: Eq a => a -> [a] -> Bool Source # maximum :: Ord a => [a] -> a Source # minimum :: Ord a => [a] -> a Source # |
|
Foldable Maybe |
Since: base-2.1 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable Par1 |
Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable Complex |
Since: base-4.9.0.0 |
Defined in Data.Complex fold :: 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 # |
|
Foldable Min |
Since: base-4.9.0.0 |
Defined in Data.Semigroup fold :: 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 # |
|
Foldable Max |
Since: base-4.9.0.0 |
Defined in Data.Semigroup fold :: 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 # |
|
Foldable First |
Since: base-4.9.0.0 |
Defined in Data.Semigroup fold :: 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 # |
|
Foldable Last |
Since: base-4.9.0.0 |
Defined in Data.Semigroup fold :: 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 # |
|
Foldable Option |
Since: base-4.9.0.0 |
Defined in Data.Semigroup fold :: Monoid m => Option m -> m Source # foldMap :: Monoid m => (a -> m) -> Option a -> m Source # foldMap' :: Monoid m => (a -> m) -> Option a -> m Source # foldr :: (a -> b -> b) -> b -> Option a -> b Source # foldr' :: (a -> b -> b) -> b -> Option a -> b Source # foldl :: (b -> a -> b) -> b -> Option a -> b Source # foldl' :: (b -> a -> b) -> b -> Option a -> b Source # foldr1 :: (a -> a -> a) -> Option a -> a Source # foldl1 :: (a -> a -> a) -> Option a -> a Source # toList :: Option a -> [a] Source # null :: Option a -> Bool Source # length :: Option a -> Int Source # elem :: Eq a => a -> Option a -> Bool Source # maximum :: Ord a => Option a -> a Source # minimum :: Ord a => Option a -> a Source # |
|
Foldable ZipList |
Since: base-4.9.0.0 |
Defined in Control.Applicative fold :: 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 # |
|
Foldable Identity |
Since: base-4.8.0.0 |
Defined in Data.Functor.Identity fold :: 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 # |
|
Foldable First |
Since: base-4.8.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable Last |
Since: base-4.8.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable Dual |
Since: base-4.8.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable Sum |
Since: base-4.8.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable Product |
Since: base-4.8.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable Down |
Since: base-4.12.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable NonEmpty |
Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable IntMap |
Folds in order of increasing key. |
Defined in Data.IntMap.Internal fold :: Monoid m => IntMap m -> m Source # foldMap :: Monoid m => (a -> m) -> IntMap a -> m Source # foldMap' :: Monoid m => (a -> m) -> IntMap a -> m Source # foldr :: (a -> b -> b) -> b -> IntMap a -> b Source # foldr' :: (a -> b -> b) -> b -> IntMap a -> b Source # foldl :: (b -> a -> b) -> b -> IntMap a -> b Source # foldl' :: (b -> a -> b) -> b -> IntMap a -> b Source # foldr1 :: (a -> a -> a) -> IntMap a -> a Source # foldl1 :: (a -> a -> a) -> IntMap a -> a Source # toList :: IntMap a -> [a] Source # null :: IntMap a -> Bool Source # length :: IntMap a -> Int Source # elem :: Eq a => a -> IntMap a -> Bool Source # maximum :: Ord a => IntMap a -> a Source # minimum :: Ord a => IntMap a -> a Source # |
|
Foldable Tree | |
Defined in Data.Tree fold :: Monoid m => Tree m -> m Source # foldMap :: Monoid m => (a -> m) -> Tree a -> m Source # foldMap' :: Monoid m => (a -> m) -> Tree a -> m Source # foldr :: (a -> b -> b) -> b -> Tree a -> b Source # foldr' :: (a -> b -> b) -> b -> Tree a -> b Source # foldl :: (b -> a -> b) -> b -> Tree a -> b Source # foldl' :: (b -> a -> b) -> b -> Tree a -> b Source # foldr1 :: (a -> a -> a) -> Tree a -> a Source # foldl1 :: (a -> a -> a) -> Tree a -> a Source # toList :: Tree a -> [a] Source # null :: Tree a -> Bool Source # length :: Tree a -> Int Source # elem :: Eq a => a -> Tree a -> Bool Source # maximum :: Ord a => Tree a -> a Source # minimum :: Ord a => Tree a -> a Source # |
|
Foldable Seq | |
Defined in Data.Sequence.Internal fold :: Monoid m => Seq m -> m Source # foldMap :: Monoid m => (a -> m) -> Seq a -> m Source # foldMap' :: Monoid m => (a -> m) -> Seq a -> m Source # foldr :: (a -> b -> b) -> b -> Seq a -> b Source # foldr' :: (a -> b -> b) -> b -> Seq a -> b Source # foldl :: (b -> a -> b) -> b -> Seq a -> b Source # foldl' :: (b -> a -> b) -> b -> Seq a -> b Source # foldr1 :: (a -> a -> a) -> Seq a -> a Source # foldl1 :: (a -> a -> a) -> Seq a -> a Source # toList :: Seq a -> [a] Source # null :: Seq a -> Bool Source # length :: Seq a -> Int Source # elem :: Eq a => a -> Seq a -> Bool Source # maximum :: Ord a => Seq a -> a Source # minimum :: Ord a => Seq a -> a Source # |
|
Foldable FingerTree | |
Defined in Data.Sequence.Internal fold :: Monoid m => FingerTree m -> m Source # foldMap :: Monoid m => (a -> m) -> FingerTree a -> m Source # foldMap' :: Monoid m => (a -> m) -> FingerTree a -> m Source # foldr :: (a -> b -> b) -> b -> FingerTree a -> b Source # foldr' :: (a -> b -> b) -> b -> FingerTree a -> b Source # foldl :: (b -> a -> b) -> b -> FingerTree a -> b Source # foldl' :: (b -> a -> b) -> b -> FingerTree a -> b Source # foldr1 :: (a -> a -> a) -> FingerTree a -> a Source # foldl1 :: (a -> a -> a) -> FingerTree a -> a Source # toList :: FingerTree a -> [a] Source # null :: FingerTree a -> Bool Source # length :: FingerTree a -> Int Source # elem :: Eq a => a -> FingerTree a -> Bool Source # maximum :: Ord a => FingerTree a -> a Source # minimum :: Ord a => FingerTree a -> a Source # sum :: Num a => FingerTree a -> a Source # product :: Num a => FingerTree a -> a Source # |
|
Foldable Digit | |
Defined in Data.Sequence.Internal fold :: Monoid m => Digit m -> m Source # foldMap :: Monoid m => (a -> m) -> Digit a -> m Source # foldMap' :: Monoid m => (a -> m) -> Digit a -> m Source # foldr :: (a -> b -> b) -> b -> Digit a -> b Source # foldr' :: (a -> b -> b) -> b -> Digit a -> b Source # foldl :: (b -> a -> b) -> b -> Digit a -> b Source # foldl' :: (b -> a -> b) -> b -> Digit a -> b Source # foldr1 :: (a -> a -> a) -> Digit a -> a Source # foldl1 :: (a -> a -> a) -> Digit a -> a Source # toList :: Digit a -> [a] Source # null :: Digit a -> Bool Source # length :: Digit a -> Int Source # elem :: Eq a => a -> Digit a -> Bool Source # maximum :: Ord a => Digit a -> a Source # minimum :: Ord a => Digit a -> a Source # |
|
Foldable Node | |
Defined in Data.Sequence.Internal fold :: Monoid m => Node m -> m Source # foldMap :: Monoid m => (a -> m) -> Node a -> m Source # foldMap' :: Monoid m => (a -> m) -> Node a -> m Source # foldr :: (a -> b -> b) -> b -> Node a -> b Source # foldr' :: (a -> b -> b) -> b -> Node a -> b Source # foldl :: (b -> a -> b) -> b -> Node a -> b Source # foldl' :: (b -> a -> b) -> b -> Node a -> b Source # foldr1 :: (a -> a -> a) -> Node a -> a Source # foldl1 :: (a -> a -> a) -> Node a -> a Source # toList :: Node a -> [a] Source # null :: Node a -> Bool Source # length :: Node a -> Int Source # elem :: Eq a => a -> Node a -> Bool Source # maximum :: Ord a => Node a -> a Source # minimum :: Ord a => Node a -> a Source # |
|
Foldable Elem | |
Defined in Data.Sequence.Internal fold :: Monoid m => Elem m -> m Source # foldMap :: Monoid m => (a -> m) -> Elem a -> m Source # foldMap' :: Monoid m => (a -> m) -> Elem a -> m Source # foldr :: (a -> b -> b) -> b -> Elem a -> b Source # foldr' :: (a -> b -> b) -> b -> Elem a -> b Source # foldl :: (b -> a -> b) -> b -> Elem a -> b Source # foldl' :: (b -> a -> b) -> b -> Elem a -> b Source # foldr1 :: (a -> a -> a) -> Elem a -> a Source # foldl1 :: (a -> a -> a) -> Elem a -> a Source # toList :: Elem a -> [a] Source # null :: Elem a -> Bool Source # length :: Elem a -> Int Source # elem :: Eq a => a -> Elem a -> Bool Source # maximum :: Ord a => Elem a -> a Source # minimum :: Ord a => Elem a -> a Source # |
|
Foldable ViewL | |
Defined in Data.Sequence.Internal fold :: Monoid m => ViewL m -> m Source # foldMap :: Monoid m => (a -> m) -> ViewL a -> m Source # foldMap' :: Monoid m => (a -> m) -> ViewL a -> m Source # foldr :: (a -> b -> b) -> b -> ViewL a -> b Source # foldr' :: (a -> b -> b) -> b -> ViewL a -> b Source # foldl :: (b -> a -> b) -> b -> ViewL a -> b Source # foldl' :: (b -> a -> b) -> b -> ViewL a -> b Source # foldr1 :: (a -> a -> a) -> ViewL a -> a Source # foldl1 :: (a -> a -> a) -> ViewL a -> a Source # toList :: ViewL a -> [a] Source # null :: ViewL a -> Bool Source # length :: ViewL a -> Int Source # elem :: Eq a => a -> ViewL a -> Bool Source # maximum :: Ord a => ViewL a -> a Source # minimum :: Ord a => ViewL a -> a Source # |
|
Foldable ViewR | |
Defined in Data.Sequence.Internal fold :: Monoid m => ViewR m -> m Source # foldMap :: Monoid m => (a -> m) -> ViewR a -> m Source # foldMap' :: Monoid m => (a -> m) -> ViewR a -> m Source # foldr :: (a -> b -> b) -> b -> ViewR a -> b Source # foldr' :: (a -> b -> b) -> b -> ViewR a -> b Source # foldl :: (b -> a -> b) -> b -> ViewR a -> b Source # foldl' :: (b -> a -> b) -> b -> ViewR a -> b Source # foldr1 :: (a -> a -> a) -> ViewR a -> a Source # foldl1 :: (a -> a -> a) -> ViewR a -> a Source # toList :: ViewR a -> [a] Source # null :: ViewR a -> Bool Source # length :: ViewR a -> Int Source # elem :: Eq a => a -> ViewR a -> Bool Source # maximum :: Ord a => ViewR a -> a Source # minimum :: Ord a => ViewR a -> a Source # |
|
Foldable Set |
Folds in order of increasing key. |
Defined in Data.Set.Internal fold :: Monoid m => Set m -> m Source # foldMap :: Monoid m => (a -> m) -> Set a -> m Source # foldMap' :: Monoid m => (a -> m) -> Set a -> m Source # foldr :: (a -> b -> b) -> b -> Set a -> b Source # foldr' :: (a -> b -> b) -> b -> Set a -> b Source # foldl :: (b -> a -> b) -> b -> Set a -> b Source # foldl' :: (b -> a -> b) -> b -> Set a -> b Source # foldr1 :: (a -> a -> a) -> Set a -> a Source # foldl1 :: (a -> a -> a) -> Set a -> a Source # toList :: Set a -> [a] Source # null :: Set a -> Bool Source # length :: Set a -> Int Source # elem :: Eq a => a -> Set a -> Bool Source # maximum :: Ord a => Set a -> a Source # minimum :: Ord a => Set a -> a Source # |
|
Foldable Hashed | |
Defined in Data.Hashable.Class fold :: Monoid m => Hashed m -> m Source # foldMap :: Monoid m => (a -> m) -> Hashed a -> m Source # foldMap' :: Monoid m => (a -> m) -> Hashed a -> m Source # foldr :: (a -> b -> b) -> b -> Hashed a -> b Source # foldr' :: (a -> b -> b) -> b -> Hashed a -> b Source # foldl :: (b -> a -> b) -> b -> Hashed a -> b Source # foldl' :: (b -> a -> b) -> b -> Hashed a -> b Source # foldr1 :: (a -> a -> a) -> Hashed a -> a Source # foldl1 :: (a -> a -> a) -> Hashed a -> a Source # toList :: Hashed a -> [a] Source # null :: Hashed a -> Bool Source # length :: Hashed a -> Int Source # elem :: Eq a => a -> Hashed a -> Bool Source # maximum :: Ord a => Hashed a -> a Source # minimum :: Ord a => Hashed a -> a Source # |
|
Foldable HashSet | |
Defined in Data.HashSet.Internal fold :: Monoid m => HashSet m -> m Source # foldMap :: Monoid m => (a -> m) -> HashSet a -> m Source # foldMap' :: Monoid m => (a -> m) -> HashSet a -> m Source # foldr :: (a -> b -> b) -> b -> HashSet a -> b Source # foldr' :: (a -> b -> b) -> b -> HashSet a -> b Source # foldl :: (b -> a -> b) -> b -> HashSet a -> b Source # foldl' :: (b -> a -> b) -> b -> HashSet a -> b Source # foldr1 :: (a -> a -> a) -> HashSet a -> a Source # foldl1 :: (a -> a -> a) -> HashSet a -> a Source # toList :: HashSet a -> [a] Source # null :: HashSet a -> Bool Source # length :: HashSet a -> Int Source # elem :: Eq a => a -> HashSet a -> Bool Source # maximum :: Ord a => HashSet a -> a Source # minimum :: Ord a => HashSet a -> a Source # |
|
Foldable ( Either a) |
Since: base-4.7.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable ( V1 :: Type -> Type ) |
Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: 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 # 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 # |
|
Foldable ( U1 :: Type -> Type ) |
Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: 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 # 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 # |
|
Foldable ( UAddr :: Type -> Type ) |
Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable ( UChar :: Type -> Type ) |
Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable ( UDouble :: Type -> Type ) |
Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable ( UFloat :: Type -> Type ) |
Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable ( UInt :: Type -> Type ) |
Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable ( UWord :: Type -> Type ) |
Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable ( (,) a) |
Since: base-4.7.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable ( Array i) |
Since: base-4.8.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable ( Arg a) |
Since: base-4.9.0.0 |
Defined in Data.Semigroup fold :: 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 # |
|
Foldable ( Proxy :: Type -> Type ) |
Since: base-4.7.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable ( Map k) |
Folds in order of increasing key. |
Defined in Data.Map.Internal fold :: Monoid m => Map k m -> m Source # foldMap :: Monoid m => (a -> m) -> Map k a -> m Source # foldMap' :: Monoid m => (a -> m) -> Map k a -> m Source # foldr :: (a -> b -> b) -> b -> Map k a -> b Source # foldr' :: (a -> b -> b) -> b -> Map k a -> b Source # foldl :: (b -> a -> b) -> b -> Map k a -> b Source # foldl' :: (b -> a -> b) -> b -> Map k a -> b Source # foldr1 :: (a -> a -> a) -> Map k a -> a Source # foldl1 :: (a -> a -> a) -> Map k a -> a Source # toList :: Map k a -> [a] Source # null :: Map k a -> Bool Source # length :: Map k a -> Int Source # elem :: Eq a => a -> Map k a -> Bool Source # maximum :: Ord a => Map k a -> a Source # minimum :: Ord a => Map k a -> a Source # |
|
Foldable f => Foldable ( ListT f) | |
Defined in Control.Monad.Trans.List fold :: Monoid m => ListT f m -> m Source # foldMap :: Monoid m => (a -> m) -> ListT f a -> m Source # foldMap' :: Monoid m => (a -> m) -> ListT f a -> m Source # foldr :: (a -> b -> b) -> b -> ListT f a -> b Source # foldr' :: (a -> b -> b) -> b -> ListT f a -> b Source # foldl :: (b -> a -> b) -> b -> ListT f a -> b Source # foldl' :: (b -> a -> b) -> b -> ListT f a -> b Source # foldr1 :: (a -> a -> a) -> ListT f a -> a Source # foldl1 :: (a -> a -> a) -> ListT f a -> a Source # toList :: ListT f a -> [a] Source # null :: ListT f a -> Bool Source # length :: ListT f a -> Int Source # elem :: Eq a => a -> ListT f a -> Bool Source # maximum :: Ord a => ListT f a -> a Source # minimum :: Ord a => ListT f a -> a Source # |
|
Foldable f => Foldable ( Lift f) | |
Defined in Control.Applicative.Lift fold :: Monoid m => Lift f m -> m Source # foldMap :: Monoid m => (a -> m) -> Lift f a -> m Source # foldMap' :: Monoid m => (a -> m) -> Lift f a -> m Source # foldr :: (a -> b -> b) -> b -> Lift f a -> b Source # foldr' :: (a -> b -> b) -> b -> Lift f a -> b Source # foldl :: (b -> a -> b) -> b -> Lift f a -> b Source # foldl' :: (b -> a -> b) -> b -> Lift f a -> b Source # foldr1 :: (a -> a -> a) -> Lift f a -> a Source # foldl1 :: (a -> a -> a) -> Lift f a -> a Source # toList :: Lift f a -> [a] Source # null :: Lift f a -> Bool Source # length :: Lift f a -> Int Source # elem :: Eq a => a -> Lift f a -> Bool Source # maximum :: Ord a => Lift f a -> a Source # minimum :: Ord a => Lift f a -> a Source # |
|
Foldable f => Foldable ( MaybeT f) | |
Defined in Control.Monad.Trans.Maybe fold :: Monoid m => MaybeT f m -> m Source # foldMap :: Monoid m => (a -> m) -> MaybeT f a -> m Source # foldMap' :: Monoid m => (a -> m) -> MaybeT f a -> m Source # foldr :: (a -> b -> b) -> b -> MaybeT f a -> b Source # foldr' :: (a -> b -> b) -> b -> MaybeT f a -> b Source # foldl :: (b -> a -> b) -> b -> MaybeT f a -> b Source # foldl' :: (b -> a -> b) -> b -> MaybeT f a -> b Source # foldr1 :: (a -> a -> a) -> MaybeT f a -> a Source # foldl1 :: (a -> a -> a) -> MaybeT f a -> a Source # toList :: MaybeT f a -> [a] Source # null :: MaybeT f a -> Bool Source # length :: MaybeT f a -> Int Source # elem :: Eq a => a -> MaybeT f a -> Bool Source # maximum :: Ord a => MaybeT f a -> a Source # minimum :: Ord a => MaybeT f a -> a Source # |
|
Foldable ( HashMap k) | |
Defined in Data.HashMap.Internal fold :: Monoid m => HashMap k m -> m Source # foldMap :: Monoid m => (a -> m) -> HashMap k a -> m Source # foldMap' :: Monoid m => (a -> m) -> HashMap k a -> m Source # foldr :: (a -> b -> b) -> b -> HashMap k a -> b Source # foldr' :: (a -> b -> b) -> b -> HashMap k a -> b Source # foldl :: (b -> a -> b) -> b -> HashMap k a -> b Source # foldl' :: (b -> a -> b) -> b -> HashMap k a -> b Source # foldr1 :: (a -> a -> a) -> HashMap k a -> a Source # foldl1 :: (a -> a -> a) -> HashMap k a -> a Source # toList :: HashMap k a -> [a] Source # null :: HashMap k a -> Bool Source # length :: HashMap k a -> Int Source # elem :: Eq a => a -> HashMap k a -> Bool Source # maximum :: Ord a => HashMap k a -> a Source # minimum :: Ord a => HashMap k a -> a Source # |
|
Foldable f => Foldable ( Rec1 f) |
Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable ( Const m :: Type -> Type ) |
Since: base-4.7.0.0 |
Defined in Data.Functor.Const fold :: 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 # |
|
Foldable f => Foldable ( Ap f) |
Since: base-4.12.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Foldable f => Foldable ( Alt f) |
Since: base-4.12.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
Bifoldable p => Foldable ( Join p) | |
Defined in Data.Bifunctor.Join fold :: Monoid m => Join p m -> m Source # foldMap :: Monoid m => (a -> m) -> Join p a -> m Source # foldMap' :: Monoid m => (a -> m) -> Join p a -> m Source # foldr :: (a -> b -> b) -> b -> Join p a -> b Source # foldr' :: (a -> b -> b) -> b -> Join p a -> b Source # foldl :: (b -> a -> b) -> b -> Join p a -> b Source # foldl' :: (b -> a -> b) -> b -> Join p a -> b Source # foldr1 :: (a -> a -> a) -> Join p a -> a Source # foldl1 :: (a -> a -> a) -> Join p a -> a Source # toList :: Join p a -> [a] Source # null :: Join p a -> Bool Source # length :: Join p a -> Int Source # elem :: Eq a => a -> Join p a -> Bool Source # maximum :: Ord a => Join p a -> a Source # minimum :: Ord a => Join p a -> a Source # |
|
Foldable f => Foldable ( IdentityT f) | |
Defined in Control.Monad.Trans.Identity fold :: Monoid m => IdentityT f m -> m Source # foldMap :: Monoid m => (a -> m) -> IdentityT f a -> m Source # foldMap' :: Monoid m => (a -> m) -> IdentityT f a -> m Source # foldr :: (a -> b -> b) -> b -> IdentityT f a -> b Source # foldr' :: (a -> b -> b) -> b -> IdentityT f a -> b Source # foldl :: (b -> a -> b) -> b -> IdentityT f a -> b Source # foldl' :: (b -> a -> b) -> b -> IdentityT f a -> b Source # foldr1 :: (a -> a -> a) -> IdentityT f a -> a Source # foldl1 :: (a -> a -> a) -> IdentityT f a -> a Source # toList :: IdentityT f a -> [a] Source # null :: IdentityT f a -> Bool Source # length :: IdentityT f a -> Int Source # elem :: Eq a => a -> IdentityT f a -> Bool Source # maximum :: Ord a => IdentityT f a -> a Source # minimum :: Ord a => IdentityT f a -> a Source # |
|
Foldable f => Foldable ( ErrorT e f) | |
Defined in Control.Monad.Trans.Error fold :: Monoid m => ErrorT e f m -> m Source # foldMap :: Monoid m => (a -> m) -> ErrorT e f a -> m Source # foldMap' :: Monoid m => (a -> m) -> ErrorT e f a -> m Source # foldr :: (a -> b -> b) -> b -> ErrorT e f a -> b Source # foldr' :: (a -> b -> b) -> b -> ErrorT e f a -> b Source # foldl :: (b -> a -> b) -> b -> ErrorT e f a -> b Source # foldl' :: (b -> a -> b) -> b -> ErrorT e f a -> b Source # foldr1 :: (a -> a -> a) -> ErrorT e f a -> a Source # foldl1 :: (a -> a -> a) -> ErrorT e f a -> a Source # toList :: ErrorT e f a -> [a] Source # null :: ErrorT e f a -> Bool Source # length :: ErrorT e f a -> Int Source # elem :: Eq a => a -> ErrorT e f a -> Bool Source # maximum :: Ord a => ErrorT e f a -> a Source # minimum :: Ord a => ErrorT e f a -> a Source # |
|
Foldable f => Foldable ( ExceptT e f) | |
Defined in Control.Monad.Trans.Except fold :: Monoid m => ExceptT e f m -> m Source # foldMap :: Monoid m => (a -> m) -> ExceptT e f a -> m Source # foldMap' :: Monoid m => (a -> m) -> ExceptT e f a -> m Source # foldr :: (a -> b -> b) -> b -> ExceptT e f a -> b Source # foldr' :: (a -> b -> b) -> b -> ExceptT e f a -> b Source # foldl :: (b -> a -> b) -> b -> ExceptT e f a -> b Source # foldl' :: (b -> a -> b) -> b -> ExceptT e f a -> b Source # foldr1 :: (a -> a -> a) -> ExceptT e f a -> a Source # foldl1 :: (a -> a -> a) -> ExceptT e f a -> a Source # toList :: ExceptT e f a -> [a] Source # null :: ExceptT e f a -> Bool Source # length :: ExceptT e f a -> Int Source # elem :: Eq a => a -> ExceptT e f a -> Bool Source # maximum :: Ord a => ExceptT e f a -> a Source # minimum :: Ord a => ExceptT e f a -> a Source # |
|
Foldable f => Foldable ( WriterT w f) | |
Defined in Control.Monad.Trans.Writer.Lazy fold :: Monoid m => WriterT w f m -> m Source # foldMap :: Monoid m => (a -> m) -> WriterT w f a -> m Source # foldMap' :: Monoid m => (a -> m) -> WriterT w f a -> m Source # foldr :: (a -> b -> b) -> b -> WriterT w f a -> b Source # foldr' :: (a -> b -> b) -> b -> WriterT w f a -> b Source # foldl :: (b -> a -> b) -> b -> WriterT w f a -> b Source # foldl' :: (b -> a -> b) -> b -> WriterT w f a -> b Source # foldr1 :: (a -> a -> a) -> WriterT w f a -> a Source # foldl1 :: (a -> a -> a) -> WriterT w f a -> a Source # toList :: WriterT w f a -> [a] Source # null :: WriterT w f a -> Bool Source # length :: WriterT w f a -> Int Source # elem :: Eq a => a -> WriterT w f a -> Bool Source # maximum :: Ord a => WriterT w f a -> a Source # minimum :: Ord a => WriterT w f a -> a Source # |
|
Foldable f => Foldable ( WriterT w f) | |
Defined in Control.Monad.Trans.Writer.Strict fold :: Monoid m => WriterT w f m -> m Source # foldMap :: Monoid m => (a -> m) -> WriterT w f a -> m Source # foldMap' :: Monoid m => (a -> m) -> WriterT w f a -> m Source # foldr :: (a -> b -> b) -> b -> WriterT w f a -> b Source # foldr' :: (a -> b -> b) -> b -> WriterT w f a -> b Source # foldl :: (b -> a -> b) -> b -> WriterT w f a -> b Source # foldl' :: (b -> a -> b) -> b -> WriterT w f a -> b Source # foldr1 :: (a -> a -> a) -> WriterT w f a -> a Source # foldl1 :: (a -> a -> a) -> WriterT w f a -> a Source # toList :: WriterT w f a -> [a] Source # null :: WriterT w f a -> Bool Source # length :: WriterT w f a -> Int Source # elem :: Eq a => a -> WriterT w f a -> Bool Source # maximum :: Ord a => WriterT w f a -> a Source # minimum :: Ord a => WriterT w f a -> a Source # |
|
Foldable ( Tagged s) | |
Defined in Data.Tagged fold :: Monoid m => Tagged s m -> m Source # foldMap :: Monoid m => (a -> m) -> Tagged s a -> m Source # foldMap' :: Monoid m => (a -> m) -> Tagged s a -> m Source # foldr :: (a -> b -> b) -> b -> Tagged s a -> b Source # foldr' :: (a -> b -> b) -> b -> Tagged s a -> b Source # foldl :: (b -> a -> b) -> b -> Tagged s a -> b Source # foldl' :: (b -> a -> b) -> b -> Tagged s a -> b Source # foldr1 :: (a -> a -> a) -> Tagged s a -> a Source # foldl1 :: (a -> a -> a) -> Tagged s a -> a Source # toList :: Tagged s a -> [a] Source # null :: Tagged s a -> Bool Source # length :: Tagged s a -> Int Source # elem :: Eq a => a -> Tagged s a -> Bool Source # maximum :: Ord a => Tagged s a -> a Source # minimum :: Ord a => Tagged s a -> a Source # |
|
Foldable f => Foldable ( Reverse f) |
Fold from right to left. |
Defined in Data.Functor.Reverse fold :: Monoid m => Reverse f m -> m Source # foldMap :: Monoid m => (a -> m) -> Reverse f a -> m Source # foldMap' :: Monoid m => (a -> m) -> Reverse f a -> m Source # foldr :: (a -> b -> b) -> b -> Reverse f a -> b Source # foldr' :: (a -> b -> b) -> b -> Reverse f a -> b Source # foldl :: (b -> a -> b) -> b -> Reverse f a -> b Source # foldl' :: (b -> a -> b) -> b -> Reverse f a -> b Source # foldr1 :: (a -> a -> a) -> Reverse f a -> a Source # foldl1 :: (a -> a -> a) -> Reverse f a -> a Source # toList :: Reverse f a -> [a] Source # null :: Reverse f a -> Bool Source # length :: Reverse f a -> Int Source # elem :: Eq a => a -> Reverse f a -> Bool Source # maximum :: Ord a => Reverse f a -> a Source # minimum :: Ord a => Reverse f a -> a Source # |
|
Foldable f => Foldable ( Backwards f) |
Derived instance. |
Defined in Control.Applicative.Backwards fold :: Monoid m => Backwards f m -> m Source # foldMap :: Monoid m => (a -> m) -> Backwards f a -> m Source # foldMap' :: Monoid m => (a -> m) -> Backwards f a -> m Source # foldr :: (a -> b -> b) -> b -> Backwards f a -> b Source # foldr' :: (a -> b -> b) -> b -> Backwards f a -> b Source # foldl :: (b -> a -> b) -> b -> Backwards f a -> b Source # foldl' :: (b -> a -> b) -> b -> Backwards f a -> b Source # foldr1 :: (a -> a -> a) -> Backwards f a -> a Source # foldl1 :: (a -> a -> a) -> Backwards f a -> a Source # toList :: Backwards f a -> [a] Source # null :: Backwards f a -> Bool Source # length :: Backwards f a -> Int Source # elem :: Eq a => a -> Backwards f a -> Bool Source # maximum :: Ord a => Backwards f a -> a Source # minimum :: Ord a => Backwards f a -> a Source # |
|
Foldable ( K1 i c :: Type -> Type ) |
Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
( Foldable f, Foldable g) => Foldable (f :+: g) |
Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
( Foldable f, Foldable g) => Foldable (f :*: g) |
Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
( 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 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 # |
|
( 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 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 # |
|
Foldable ( Forget r a :: Type -> Type ) | |
Defined in Data.Profunctor.Types fold :: Monoid m => Forget r a m -> m Source # foldMap :: Monoid m => (a0 -> m) -> Forget r a a0 -> m Source # foldMap' :: Monoid m => (a0 -> m) -> Forget r a a0 -> m Source # foldr :: (a0 -> b -> b) -> b -> Forget r a a0 -> b Source # foldr' :: (a0 -> b -> b) -> b -> Forget r a a0 -> b Source # foldl :: (b -> a0 -> b) -> b -> Forget r a a0 -> b Source # foldl' :: (b -> a0 -> b) -> b -> Forget r a a0 -> b Source # foldr1 :: (a0 -> a0 -> a0) -> Forget r a a0 -> a0 Source # foldl1 :: (a0 -> a0 -> a0) -> Forget r a a0 -> a0 Source # toList :: Forget r a a0 -> [a0] Source # null :: Forget r a a0 -> Bool Source # length :: Forget r a a0 -> Int Source # elem :: Eq a0 => a0 -> Forget r a a0 -> Bool Source # maximum :: Ord a0 => Forget r a a0 -> a0 Source # minimum :: Ord a0 => Forget r a a0 -> a0 Source # |
|
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 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 # |
|
( Foldable f, Foldable g) => Foldable (f :.: g) |
Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: 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 # |
|
( 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 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 # |
|
Bifoldable p => Foldable ( WrappedBifunctor p a) | |
Defined in Data.Bifunctor.Wrapped fold :: Monoid m => WrappedBifunctor p a m -> m Source # foldMap :: Monoid m => (a0 -> m) -> WrappedBifunctor p a a0 -> m Source # foldMap' :: Monoid m => (a0 -> m) -> WrappedBifunctor p a a0 -> m Source # foldr :: (a0 -> b -> b) -> b -> WrappedBifunctor p a a0 -> b Source # foldr' :: (a0 -> b -> b) -> b -> WrappedBifunctor p a a0 -> b Source # foldl :: (b -> a0 -> b) -> b -> WrappedBifunctor p a a0 -> b Source # foldl' :: (b -> a0 -> b) -> b -> WrappedBifunctor p a a0 -> b Source # foldr1 :: (a0 -> a0 -> a0) -> WrappedBifunctor p a a0 -> a0 Source # foldl1 :: (a0 -> a0 -> a0) -> WrappedBifunctor p a a0 -> a0 Source # toList :: WrappedBifunctor p a a0 -> [a0] Source # null :: WrappedBifunctor p a a0 -> Bool Source # length :: WrappedBifunctor p a a0 -> Int Source # elem :: Eq a0 => a0 -> WrappedBifunctor p a a0 -> Bool Source # maximum :: Ord a0 => WrappedBifunctor p a a0 -> a0 Source # minimum :: Ord a0 => WrappedBifunctor p a a0 -> a0 Source # sum :: Num a0 => WrappedBifunctor p a a0 -> a0 Source # product :: Num a0 => WrappedBifunctor p a a0 -> a0 Source # |
|
Foldable g => Foldable ( Joker g a) | |
Defined in Data.Bifunctor.Joker fold :: Monoid m => Joker g a m -> m Source # foldMap :: Monoid m => (a0 -> m) -> Joker g a a0 -> m Source # foldMap' :: Monoid m => (a0 -> m) -> Joker g a a0 -> m Source # foldr :: (a0 -> b -> b) -> b -> Joker g a a0 -> b Source # foldr' :: (a0 -> b -> b) -> b -> Joker g a a0 -> b Source # foldl :: (b -> a0 -> b) -> b -> Joker g a a0 -> b Source # foldl' :: (b -> a0 -> b) -> b -> Joker g a a0 -> b Source # foldr1 :: (a0 -> a0 -> a0) -> Joker g a a0 -> a0 Source # foldl1 :: (a0 -> a0 -> a0) -> Joker g a a0 -> a0 Source # toList :: Joker g a a0 -> [a0] Source # null :: Joker g a a0 -> Bool Source # length :: Joker g a a0 -> Int Source # elem :: Eq a0 => a0 -> Joker g a a0 -> Bool Source # maximum :: Ord a0 => Joker g a a0 -> a0 Source # minimum :: Ord a0 => Joker g a a0 -> a0 Source # |
|
Bifoldable p => Foldable ( Flip p a) | |
Defined in Data.Bifunctor.Flip fold :: Monoid m => Flip p a m -> m Source # foldMap :: Monoid m => (a0 -> m) -> Flip p a a0 -> m Source # foldMap' :: Monoid m => (a0 -> m) -> Flip p a a0 -> m Source # foldr :: (a0 -> b -> b) -> b -> Flip p a a0 -> b Source # foldr' :: (a0 -> b -> b) -> b -> Flip p a a0 -> b Source # foldl :: (b -> a0 -> b) -> b -> Flip p a a0 -> b Source # foldl' :: (b -> a0 -> b) -> b -> Flip p a a0 -> b Source # foldr1 :: (a0 -> a0 -> a0) -> Flip p a a0 -> a0 Source # foldl1 :: (a0 -> a0 -> a0) -> Flip p a a0 -> a0 Source # toList :: Flip p a a0 -> [a0] Source # null :: Flip p a a0 -> Bool Source # length :: Flip p a a0 -> Int Source # elem :: Eq a0 => a0 -> Flip p a a0 -> Bool Source # maximum :: Ord a0 => Flip p a a0 -> a0 Source # minimum :: Ord a0 => Flip p a a0 -> a0 Source # |
|
Foldable ( Clown f a :: Type -> Type ) | |
Defined in Data.Bifunctor.Clown fold :: Monoid m => Clown f a m -> m Source # foldMap :: Monoid m => (a0 -> m) -> Clown f a a0 -> m Source # foldMap' :: Monoid m => (a0 -> m) -> Clown f a a0 -> m Source # foldr :: (a0 -> b -> b) -> b -> Clown f a a0 -> b Source # foldr' :: (a0 -> b -> b) -> b -> Clown f a a0 -> b Source # foldl :: (b -> a0 -> b) -> b -> Clown f a a0 -> b Source # foldl' :: (b -> a0 -> b) -> b -> Clown f a a0 -> b Source # foldr1 :: (a0 -> a0 -> a0) -> Clown f a a0 -> a0 Source # foldl1 :: (a0 -> a0 -> a0) -> Clown f a a0 -> a0 Source # toList :: Clown f a a0 -> [a0] Source # null :: Clown f a a0 -> Bool Source # length :: Clown f a a0 -> Int Source # elem :: Eq a0 => a0 -> Clown f a a0 -> Bool Source # maximum :: Ord a0 => Clown f a a0 -> a0 Source # minimum :: Ord a0 => Clown f a a0 -> a0 Source # |
|
( Foldable (f a), Foldable (g a)) => Foldable ( Sum f g a) | |
Defined in Data.Bifunctor.Sum fold :: Monoid m => Sum f g a m -> m Source # foldMap :: Monoid m => (a0 -> m) -> Sum f g a a0 -> m Source # foldMap' :: Monoid m => (a0 -> m) -> Sum f g a a0 -> m Source # foldr :: (a0 -> b -> b) -> b -> Sum f g a a0 -> b Source # foldr' :: (a0 -> b -> b) -> b -> Sum f g a a0 -> b Source # foldl :: (b -> a0 -> b) -> b -> Sum f g a a0 -> b Source # foldl' :: (b -> a0 -> b) -> b -> Sum f g a a0 -> b Source # foldr1 :: (a0 -> a0 -> a0) -> Sum f g a a0 -> a0 Source # foldl1 :: (a0 -> a0 -> a0) -> Sum f g a a0 -> a0 Source # toList :: Sum f g a a0 -> [a0] Source # null :: Sum f g a a0 -> Bool Source # length :: Sum f g a a0 -> Int Source # elem :: Eq a0 => a0 -> Sum f g a a0 -> Bool Source # maximum :: Ord a0 => Sum f g a a0 -> a0 Source # minimum :: Ord a0 => Sum f g a a0 -> a0 Source # |
|
( Foldable (f a), Foldable (g a)) => Foldable ( Product f g a) | |
Defined in Data.Bifunctor.Product fold :: Monoid m => Product f g a m -> m Source # foldMap :: Monoid m => (a0 -> m) -> Product f g a a0 -> m Source # foldMap' :: Monoid m => (a0 -> m) -> Product f g a a0 -> m Source # foldr :: (a0 -> b -> b) -> b -> Product f g a a0 -> b Source # foldr' :: (a0 -> b -> b) -> b -> Product f g a a0 -> b Source # foldl :: (b -> a0 -> b) -> b -> Product f g a a0 -> b Source # foldl' :: (b -> a0 -> b) -> b -> Product f g a a0 -> b Source # foldr1 :: (a0 -> a0 -> a0) -> Product f g a a0 -> a0 Source # foldl1 :: (a0 -> a0 -> a0) -> Product f g a a0 -> a0 Source # toList :: Product f g a a0 -> [a0] Source # null :: Product f g a a0 -> Bool Source # length :: Product f g a a0 -> Int Source # elem :: Eq a0 => a0 -> Product f g a a0 -> Bool Source # maximum :: Ord a0 => Product f g a a0 -> a0 Source # minimum :: Ord a0 => Product f g a a0 -> a0 Source # |
|
( Foldable f, Bifoldable p) => Foldable ( Tannen f p a) | |
Defined in Data.Bifunctor.Tannen fold :: Monoid m => Tannen f p a m -> m Source # foldMap :: Monoid m => (a0 -> m) -> Tannen f p a a0 -> m Source # foldMap' :: Monoid m => (a0 -> m) -> Tannen f p a a0 -> m Source # foldr :: (a0 -> b -> b) -> b -> Tannen f p a a0 -> b Source # foldr' :: (a0 -> b -> b) -> b -> Tannen f p a a0 -> b Source # foldl :: (b -> a0 -> b) -> b -> Tannen f p a a0 -> b Source # foldl' :: (b -> a0 -> b) -> b -> Tannen f p a a0 -> b Source # foldr1 :: (a0 -> a0 -> a0) -> Tannen f p a a0 -> a0 Source # foldl1 :: (a0 -> a0 -> a0) -> Tannen f p a a0 -> a0 Source # toList :: Tannen f p a a0 -> [a0] Source # null :: Tannen f p a a0 -> Bool Source # length :: Tannen f p a a0 -> Int Source # elem :: Eq a0 => a0 -> Tannen f p a a0 -> Bool Source # maximum :: Ord a0 => Tannen f p a a0 -> a0 Source # minimum :: Ord a0 => Tannen f p a a0 -> a0 Source # |
|
( Bifoldable p, Foldable g) => Foldable ( Biff p f g a) | |
Defined in Data.Bifunctor.Biff fold :: Monoid m => Biff p f g a m -> m Source # foldMap :: Monoid m => (a0 -> m) -> Biff p f g a a0 -> m Source # foldMap' :: Monoid m => (a0 -> m) -> Biff p f g a a0 -> m Source # foldr :: (a0 -> b -> b) -> b -> Biff p f g a a0 -> b Source # foldr' :: (a0 -> b -> b) -> b -> Biff p f g a a0 -> b Source # foldl :: (b -> a0 -> b) -> b -> Biff p f g a a0 -> b Source # foldl' :: (b -> a0 -> b) -> b -> Biff p f g a a0 -> b Source # foldr1 :: (a0 -> a0 -> a0) -> Biff p f g a a0 -> a0 Source # foldl1 :: (a0 -> a0 -> a0) -> Biff p f g a a0 -> a0 Source # toList :: Biff p f g a a0 -> [a0] Source # null :: Biff p f g a a0 -> Bool Source # length :: Biff p f g a a0 -> Int Source # elem :: Eq a0 => a0 -> Biff p f g a a0 -> Bool Source # maximum :: Ord a0 => Biff p f g a a0 -> a0 Source # minimum :: Ord a0 => Biff p f g a a0 -> a0 Source # |
type family Mutable (v :: Type -> Type ) = (mv :: Type -> Type -> Type ) | mv -> v Source #
Mutable v s a
is the mutable version of the pure vector type
v a
with
the state token
s
. It is injective on GHC 8 and newer.
class MVector ( Mutable v) a => Vector (v :: Type -> Type ) a Source #
Class of immutable vectors. Every immutable vector is associated with its
mutable version through the
Mutable
type family. Methods of this class
should not be used directly. Instead,
Data.Vector.Generic
and other
Data.Vector modules provide safe and fusible wrappers.
Minimum complete implementation: