lens-family-core-1.2.1: Haskell 98 Lens Families

Safe HaskellSafe
LanguageHaskell98

Lens.Family

Contents

Description

This is the main module for end-users of lens-families-core. If you are not building your own lenses or traversals, but just using functional references made by others, this is the only module you need.

Synopsis

Lenses

This module provides ^. for accessing fields and .~ and %~ for setting and modifying fields. Lenses are composed with . from the Prelude and id is the identity lens.

Lens composition in this library enjoys the following identities.

  • x^.l1.l2 === x^.l1^.l2
  • l1.l2 %~ f === l1 %~ l2 %~ f

The identity lens behaves as follows.

  • x^.id === x
  • id %~ f === f

The & operator, allows for a convenient way to sequence record updating:

record & l1 .~ value1 & l2 .~ value2

Lenses are implemented in van Laarhoven style. Lenses have type Functor f => (b -> f b) -> a -> f a and lens families have type Functor f => (b i -> f (b j)) -> a i -> f (a j).

Keep in mind that lenses and lens families can be used directly for functorial updates. For example, _2 id gives you strength.

_2 id :: Functor f => (a, f b) -> f (a, b)

Here is an example of code that uses the Maybe functor to preserves sharing during update when possible.

-- | 'sharedUpdate' returns the *identical* object if the update doesn't change anything.
-- This is useful for preserving sharing.
sharedUpdate :: Eq b => LensLike' Maybe a b -> (b -> b) -> a -> a
sharedUpdate l f a = fromMaybe a (l f' a)
 where
  f' b | fb == b  = Nothing
       | otherwise = Just fb
   where
    fb = f b

Traversals

^. can be used with traversals to access monoidal fields. The result will be a mconcat of all the fields referenced. The various fooOf functions can be used to access different monoidal summaries of some kinds of values.

^? can be used to access the first value of a traversal. Nothing is returned when the traversal has no references.

^.. can be used with a traversals and will return a list of all fields referenced.

When .~ is used with a traversal, all referenced fields will be set to the same value, and when %~ is used with a traversal, all referenced fields will be modified with the same function.

Like lenses, traversals can be composed with ., and because every lens is automatically a traversal, lenses and traversals can be composed with . yielding a traversal.

Traversals are implemented in van Laarhoven style. Traversals have type Applicative f => (b -> f b) -> a -> f a and traversal families have type Applicative f => (b i -> f (b j)) -> a i -> f (a j).

For stock lenses and traversals, see Lens.Family.Stock.

To build your own lenses and traversals, see Lens.Family.Unchecked.

References:

Documentation

to :: Phantom f => (a -> b) -> LensLike f a a' b b' Source #

to :: (a -> b) -> Getter a a' b b'

to promotes a projection function to a read-only lens called a getter. To demote a lens to a projection function, use the section (^.l) or view l.

>>> (3 :+ 4, "example")^._1.to(abs)
5.0 :+ 0.0

view :: FoldLike b a a' b b' -> a -> b Source #

view :: Getter a a' b b' -> a -> b

Demote a lens or getter to a projection function.

view :: Monoid b => Fold a a' b b' -> a -> b

Returns the monoidal summary of a traversal or a fold.

(^.) :: a -> FoldLike b a a' b b' -> b infixl 8 Source #

(^.) :: a -> Getter a a' b b' -> b

Access the value referenced by a getter or lens.

(^.) :: Monoid b => a -> Fold a a' b b' -> b

Access the monoidal summary referenced by a getter or lens.

folding :: (Foldable g, Phantom f, Applicative f) => (a -> g b) -> LensLike f a a' b b' Source #

folding :: (a -> [b]) -> Fold a a' b b'

folding promotes a "toList" function to a read-only traversal called a fold.

To demote a traversal or fold to a "toList" function use the section (^..l) or toListOf l.

views :: FoldLike r a a' b b' -> (b -> r) -> a -> r Source #

views :: Monoid r => Fold a a' b b' -> (b -> r) -> a -> r

Given a fold or traversal, return the foldMap of all the values using the given function.

views :: Getter a a' b b' -> (b -> r) -> a -> r

views is not particularly useful for getters or lenses, but given a getter or lens, it returns the referenced value passed through the given function.

views l f a = f (view l a)

(^..) :: a -> FoldLike [b] a a' b b' -> [b] infixl 8 Source #

(^..) :: a -> Getter a a' b b' -> [b]

Returns a list of all of the referenced values in order.

(^?) :: a -> FoldLike (First b) a a' b b' -> Maybe b infixl 8 Source #

(^?) :: a -> Fold a a' b b' -> Maybe b

Returns Just the first referenced value. Returns Nothing if there are no referenced values.

toListOf :: FoldLike [b] a a' b b' -> a -> [b] Source #

toListOf :: Fold a a' b b' -> a -> [b]

Returns a list of all of the referenced values in order.

allOf :: FoldLike All a a' b b' -> (b -> Bool) -> a -> Bool Source #

allOf :: Fold a a' b b' -> (b -> Bool) -> a -> Bool

Returns true if all of the referenced values satisfy the given predicate.

anyOf :: FoldLike Any a a' b b' -> (b -> Bool) -> a -> Bool Source #

anyOf :: Fold a a' b b' -> (b -> Bool) -> a -> Bool

Returns true if any of the referenced values satisfy the given predicate.

firstOf :: FoldLike (First b) a a' b b' -> a -> Maybe b Source #

firstOf :: Fold a a' b b' -> a -> Maybe b

Returns Just the first referenced value. Returns Nothing if there are no referenced values. See ^? for an infix version of firstOf

lastOf :: FoldLike (Last b) a a' b b' -> a -> Maybe b Source #

lastOf :: Fold a a' b b' -> a -> Maybe b

Returns Just the last referenced value. Returns Nothing if there are no referenced values.

sumOf :: Num b => FoldLike (Sum b) a a' b b' -> a -> b Source #

sumOf :: Num b => Fold a a' b b' -> a -> b

Returns the sum of all the referenced values.

productOf :: Num b => FoldLike (Product b) a a' b b' -> a -> b Source #

productOf :: Num b => Fold a a' b b' -> a -> b

Returns the product of all the referenced values.

lengthOf :: Num r => FoldLike (Sum r) a a' b b' -> a -> r Source #

lengthOf :: Num r => Fold a a' b b' -> a -> r

Counts the number of references in a traversal or fold for the input.

nullOf :: FoldLike All a a' b b' -> a -> Bool Source #

nullOf :: Fold a a' b b' -> a -> Bool

Returns true if the number of references in the input is zero.

backwards :: LensLike (Backwards f) a a' b b' -> LensLike f a a' b b' Source #

backwards :: Traversal a a' b b' -> Traversal a a' b b'
backwards :: Fold a a' b b' -> Fold a a' b b'

Given a traversal or fold, reverse the order that elements are traversed.

backwards :: Lens a a' b b' -> Lens a a' b b'
backwards :: Getter a a' b b' -> Getter a a' b b'
backwards :: Setter a a' b b' -> Setter a a' b b'

No effect on lenses, getters or setters.

over :: ASetter a a' b b' -> (b -> b') -> a -> a' Source #

Demote a setter to a semantic editor combinator.

(%~) :: ASetter a a' b b' -> (b -> b') -> a -> a' infixr 4 Source #

Modify all referenced fields.

set :: ASetter a a' b b' -> b' -> a -> a' Source #

Set all referenced fields to the given value.

(.~) :: ASetter a a' b b' -> b' -> a -> a' infixr 4 Source #

Set all referenced fields to the given value.

(&) :: a -> (a -> b) -> b infixl 1 Source #

A flipped version of ($).

Pseudo-imperatives

(+~) :: Num b => ASetter' a b -> b -> a -> a infixr 4 Source #

(*~) :: Num b => ASetter' a b -> b -> a -> a infixr 4 Source #

(-~) :: Num b => ASetter' a b -> b -> a -> a infixr 4 Source #

(//~) :: Fractional b => ASetter' a b -> b -> a -> a infixr 4 Source #

(&&~) :: ASetter' a Bool -> Bool -> a -> a infixr 4 Source #

(||~) :: ASetter' a Bool -> Bool -> a -> a infixr 4 Source #

(<>~) :: Monoid o => ASetter' a o -> o -> a -> a infixr 4 Source #

Monoidally append a value to all referenced fields.

Types

type LensLike f a a' b b' = (b -> f b') -> a -> f a' Source #

type LensLike' f a b = (b -> f b) -> a -> f a Source #

type FoldLike r a a' b b' = LensLike (Constant r) a a' b b' Source #

type FoldLike' r a b = LensLike' (Constant r) a b Source #

type ASetter a a' b b' = LensLike Identity a a' b b' Source #

class Functor f => Phantom f Source #

Minimal complete definition

coerce

Instances

Phantom (Const * a) Source # 

Methods

coerce :: Const * a a -> Const * a b

Phantom f => Phantom (Backwards * f) Source # 

Methods

coerce :: Backwards * f a -> Backwards * f b

Phantom (Constant * a) Source # 

Methods

coerce :: Constant * a a -> Constant * a b

Phantom f => Phantom (AlongsideRight f a) Source # 

Methods

coerce :: AlongsideRight f a a -> AlongsideRight f a b

Phantom f => Phantom (AlongsideLeft f a) Source # 

Methods

coerce :: AlongsideLeft f a a -> AlongsideLeft f a b

(Phantom f, Functor g) => Phantom (Compose * * f g) Source # 

Methods

coerce :: Compose * * f g a -> Compose * * f g b

data Constant k a b :: forall k. * -> k -> * #

Constant functor.

Instances

Eq2 (Constant *) 

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Constant * a c -> Constant * b d -> Bool #

Ord2 (Constant *) 

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Constant * a c -> Constant * b d -> Ordering #

Read2 (Constant *) 

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Constant * a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Constant * a b] #

Show2 (Constant *) 

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Constant * a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Constant * a b] -> ShowS #

Bifunctor (Constant *) 

Methods

bimap :: (a -> b) -> (c -> d) -> Constant * a c -> Constant * b d #

first :: (a -> b) -> Constant * a c -> Constant * b c #

second :: (b -> c) -> Constant * a b -> Constant * a c #

Functor (Constant * a) 

Methods

fmap :: (a -> b) -> Constant * a a -> Constant * a b #

(<$) :: a -> Constant * a b -> Constant * a a #

Monoid a => Applicative (Constant * a) 

Methods

pure :: a -> Constant * a a #

(<*>) :: Constant * a (a -> b) -> Constant * a a -> Constant * a b #

(*>) :: Constant * a a -> Constant * a b -> Constant * a b #

(<*) :: Constant * a a -> Constant * a b -> Constant * a a #

Foldable (Constant * a) 

Methods

fold :: Monoid m => Constant * a m -> m #

foldMap :: Monoid m => (a -> m) -> Constant * a a -> m #

foldr :: (a -> b -> b) -> b -> Constant * a a -> b #

foldr' :: (a -> b -> b) -> b -> Constant * a a -> b #

foldl :: (b -> a -> b) -> b -> Constant * a a -> b #

foldl' :: (b -> a -> b) -> b -> Constant * a a -> b #

foldr1 :: (a -> a -> a) -> Constant * a a -> a #

foldl1 :: (a -> a -> a) -> Constant * a a -> a #

toList :: Constant * a a -> [a] #

null :: Constant * a a -> Bool #

length :: Constant * a a -> Int #

elem :: Eq a => a -> Constant * a a -> Bool #

maximum :: Ord a => Constant * a a -> a #

minimum :: Ord a => Constant * a a -> a #

sum :: Num a => Constant * a a -> a #

product :: Num a => Constant * a a -> a #

Traversable (Constant * a) 

Methods

traverse :: Applicative f => (a -> f b) -> Constant * a a -> f (Constant * a b) #

sequenceA :: Applicative f => Constant * a (f a) -> f (Constant * a a) #

mapM :: Monad m => (a -> m b) -> Constant * a a -> m (Constant * a b) #

sequence :: Monad m => Constant * a (m a) -> m (Constant * a a) #

Eq a => Eq1 (Constant * a) 

Methods

liftEq :: (a -> b -> Bool) -> Constant * a a -> Constant * a b -> Bool #

Ord a => Ord1 (Constant * a) 

Methods

liftCompare :: (a -> b -> Ordering) -> Constant * a a -> Constant * a b -> Ordering #

Read a => Read1 (Constant * a) 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Constant * a a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Constant * a a] #

Show a => Show1 (Constant * a) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Constant * a a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Constant * a a] -> ShowS #

Phantom (Constant * a) Source # 

Methods

coerce :: Constant * a a -> Constant * a b

Eq a => Eq (Constant k a b) 

Methods

(==) :: Constant k a b -> Constant k a b -> Bool #

(/=) :: Constant k a b -> Constant k a b -> Bool #

Ord a => Ord (Constant k a b) 

Methods

compare :: Constant k a b -> Constant k a b -> Ordering #

(<) :: Constant k a b -> Constant k a b -> Bool #

(<=) :: Constant k a b -> Constant k a b -> Bool #

(>) :: Constant k a b -> Constant k a b -> Bool #

(>=) :: Constant k a b -> Constant k a b -> Bool #

max :: Constant k a b -> Constant k a b -> Constant k a b #

min :: Constant k a b -> Constant k a b -> Constant k a b #

Read a => Read (Constant k a b) 
Show a => Show (Constant k a b) 

Methods

showsPrec :: Int -> Constant k a b -> ShowS #

show :: Constant k a b -> String #

showList :: [Constant k a b] -> ShowS #

Monoid a => Monoid (Constant k a b) 

Methods

mempty :: Constant k a b #

mappend :: Constant k a b -> Constant k a b -> Constant k a b #

mconcat :: [Constant k a b] -> Constant k a b #

data Identity a :: * -> * #

Identity functor and monad. (a non-strict monad)

Since: 4.8.0.0

Instances

Monad Identity 

Methods

(>>=) :: Identity a -> (a -> Identity b) -> Identity b #

(>>) :: Identity a -> Identity b -> Identity b #

return :: a -> Identity a #

fail :: String -> Identity a #

Functor Identity 

Methods

fmap :: (a -> b) -> Identity a -> Identity b #

(<$) :: a -> Identity b -> Identity a #

MonadFix Identity 

Methods

mfix :: (a -> Identity a) -> Identity a #

Applicative Identity 

Methods

pure :: a -> Identity a #

(<*>) :: Identity (a -> b) -> Identity a -> Identity b #

(*>) :: Identity a -> Identity b -> Identity b #

(<*) :: Identity a -> Identity b -> Identity a #

Foldable Identity 

Methods

fold :: Monoid m => Identity m -> 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 #

toList :: Identity a -> [a] #

null :: Identity a -> Bool #

length :: Identity a -> Int #

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

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

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

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

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

Traversable Identity 

Methods

traverse :: Applicative f => (a -> f b) -> Identity a -> f (Identity b) #

sequenceA :: Applicative f => Identity (f a) -> f (Identity a) #

mapM :: Monad m => (a -> m b) -> Identity a -> m (Identity b) #

sequence :: Monad m => Identity (m a) -> m (Identity a) #

Generic1 Identity 

Associated Types

type Rep1 (Identity :: * -> *) :: * -> * #

Methods

from1 :: Identity a -> Rep1 Identity a #

to1 :: Rep1 Identity a -> Identity a #

MonadZip Identity 

Methods

mzip :: Identity a -> Identity b -> Identity (a, b) #

mzipWith :: (a -> b -> c) -> Identity a -> Identity b -> Identity c #

munzip :: Identity (a, b) -> (Identity a, Identity b) #

Identical Identity Source # 

Methods

extract :: Identity a -> a

Bounded a => Bounded (Identity a) 
Enum a => Enum (Identity a) 
Eq a => Eq (Identity a) 

Methods

(==) :: Identity a -> Identity a -> Bool #

(/=) :: Identity a -> Identity a -> Bool #

Floating a => Floating (Identity a) 
Fractional a => Fractional (Identity a) 
Integral a => Integral (Identity a) 
Data a => Data (Identity a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Identity a -> c (Identity a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Identity a) #

toConstr :: Identity a -> Constr #

dataTypeOf :: Identity a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Identity a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Identity a)) #

gmapT :: (forall b. Data b => b -> b) -> Identity a -> Identity a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Identity a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Identity a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Identity a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Identity a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Identity a -> m (Identity a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Identity a -> m (Identity a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Identity a -> m (Identity a) #

Num a => Num (Identity a) 
Ord a => Ord (Identity a) 

Methods

compare :: Identity a -> Identity a -> Ordering #

(<) :: Identity a -> Identity a -> Bool #

(<=) :: Identity a -> Identity a -> Bool #

(>) :: Identity a -> Identity a -> Bool #

(>=) :: Identity a -> Identity a -> Bool #

max :: Identity a -> Identity a -> Identity a #

min :: Identity a -> Identity a -> Identity a #

Read a => Read (Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Real a => Real (Identity a) 

Methods

toRational :: Identity a -> Rational #

RealFloat a => RealFloat (Identity a) 
RealFrac a => RealFrac (Identity a) 

Methods

properFraction :: Integral b => Identity a -> (b, Identity a) #

truncate :: Integral b => Identity a -> b #

round :: Integral b => Identity a -> b #

ceiling :: Integral b => Identity a -> b #

floor :: Integral b => Identity a -> b #

Show a => Show (Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Methods

showsPrec :: Int -> Identity a -> ShowS #

show :: Identity a -> String #

showList :: [Identity a] -> ShowS #

Ix a => Ix (Identity a) 
IsString a => IsString (Identity a) 

Methods

fromString :: String -> Identity a #

Generic (Identity a) 

Associated Types

type Rep (Identity a) :: * -> * #

Methods

from :: Identity a -> Rep (Identity a) x #

to :: Rep (Identity a) x -> Identity a #

Semigroup a => Semigroup (Identity a) 

Methods

(<>) :: Identity a -> Identity a -> Identity a #

sconcat :: NonEmpty (Identity a) -> Identity a #

stimes :: Integral b => b -> Identity a -> Identity a #

Monoid a => Monoid (Identity a) 

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

Storable a => Storable (Identity a) 

Methods

sizeOf :: Identity a -> Int #

alignment :: Identity a -> Int #

peekElemOff :: Ptr (Identity a) -> Int -> IO (Identity a) #

pokeElemOff :: Ptr (Identity a) -> Int -> Identity a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Identity a) #

pokeByteOff :: Ptr b -> Int -> Identity a -> IO () #

peek :: Ptr (Identity a) -> IO (Identity a) #

poke :: Ptr (Identity a) -> Identity a -> IO () #

Bits a => Bits (Identity a) 
FiniteBits a => FiniteBits (Identity a) 
type Rep1 Identity 
type Rep1 Identity = D1 (MetaData "Identity" "Data.Functor.Identity" "base" True) (C1 (MetaCons "Identity" PrefixI True) (S1 (MetaSel (Just Symbol "runIdentity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep (Identity a) 
type Rep (Identity a) = D1 (MetaData "Identity" "Data.Functor.Identity" "base" True) (C1 (MetaCons "Identity" PrefixI True) (S1 (MetaSel (Just Symbol "runIdentity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

Re-exports

class Functor f => Applicative f #

A functor with application, providing operations to

  • embed pure expressions (pure), and
  • sequence computations and combine their results (<*>).

A minimal complete definition must include implementations of these functions satisfying the following laws:

identity
pure id <*> v = v
composition
pure (.) <*> u <*> v <*> w = u <*> (v <*> w)
homomorphism
pure f <*> pure x = pure (f x)
interchange
u <*> pure y = pure ($ y) <*> u

The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:

As a consequence of these laws, the Functor instance for f will satisfy

If f is also a Monad, it should satisfy

(which implies that pure and <*> satisfy the applicative functor laws).

Minimal complete definition

pure, (<*>)

Instances

Applicative [] 

Methods

pure :: a -> [a] #

(<*>) :: [a -> b] -> [a] -> [b] #

(*>) :: [a] -> [b] -> [b] #

(<*) :: [a] -> [b] -> [a] #

Applicative Maybe 

Methods

pure :: a -> Maybe a #

(<*>) :: Maybe (a -> b) -> Maybe a -> Maybe b #

(*>) :: Maybe a -> Maybe b -> Maybe b #

(<*) :: Maybe a -> Maybe b -> Maybe a #

Applicative IO 

Methods

pure :: a -> IO a #

(<*>) :: IO (a -> b) -> IO a -> IO b #

(*>) :: IO a -> IO b -> IO b #

(<*) :: IO a -> IO b -> IO a #

Applicative U1 

Methods

pure :: a -> U1 a #

(<*>) :: U1 (a -> b) -> U1 a -> U1 b #

(*>) :: U1 a -> U1 b -> U1 b #

(<*) :: U1 a -> U1 b -> U1 a #

Applicative Par1 

Methods

pure :: a -> Par1 a #

(<*>) :: Par1 (a -> b) -> Par1 a -> Par1 b #

(*>) :: Par1 a -> Par1 b -> Par1 b #

(<*) :: Par1 a -> Par1 b -> Par1 a #

Applicative Identity 

Methods

pure :: a -> Identity a #

(<*>) :: Identity (a -> b) -> Identity a -> Identity b #

(*>) :: Identity a -> Identity b -> Identity b #

(<*) :: Identity a -> Identity b -> Identity a #

Applicative Min 

Methods

pure :: a -> Min a #

(<*>) :: Min (a -> b) -> Min a -> Min b #

(*>) :: Min a -> Min b -> Min b #

(<*) :: Min a -> Min b -> Min a #

Applicative Max 

Methods

pure :: a -> Max a #

(<*>) :: Max (a -> b) -> Max a -> Max b #

(*>) :: Max a -> Max b -> Max b #

(<*) :: Max a -> Max b -> Max a #

Applicative First 

Methods

pure :: a -> First a #

(<*>) :: First (a -> b) -> First a -> First b #

(*>) :: First a -> First b -> First b #

(<*) :: First a -> First b -> First a #

Applicative Last 

Methods

pure :: a -> Last a #

(<*>) :: Last (a -> b) -> Last a -> Last b #

(*>) :: Last a -> Last b -> Last b #

(<*) :: Last a -> Last b -> Last a #

Applicative Option 

Methods

pure :: a -> Option a #

(<*>) :: Option (a -> b) -> Option a -> Option b #

(*>) :: Option a -> Option b -> Option b #

(<*) :: Option a -> Option b -> Option a #

Applicative NonEmpty 

Methods

pure :: a -> NonEmpty a #

(<*>) :: NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b #

(*>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

(<*) :: NonEmpty a -> NonEmpty b -> NonEmpty a #

Applicative Complex 

Methods

pure :: a -> Complex a #

(<*>) :: Complex (a -> b) -> Complex a -> Complex b #

(*>) :: Complex a -> Complex b -> Complex b #

(<*) :: Complex a -> Complex b -> Complex a #

Applicative ZipList 

Methods

pure :: a -> ZipList a #

(<*>) :: ZipList (a -> b) -> ZipList a -> ZipList b #

(*>) :: ZipList a -> ZipList b -> ZipList b #

(<*) :: ZipList a -> ZipList b -> ZipList a #

Applicative Dual 

Methods

pure :: a -> Dual a #

(<*>) :: Dual (a -> b) -> Dual a -> Dual b #

(*>) :: Dual a -> Dual b -> Dual b #

(<*) :: Dual a -> Dual b -> Dual a #

Applicative Sum 

Methods

pure :: a -> Sum a #

(<*>) :: Sum (a -> b) -> Sum a -> Sum b #

(*>) :: Sum a -> Sum b -> Sum b #

(<*) :: Sum a -> Sum b -> Sum a #

Applicative Product 

Methods

pure :: a -> Product a #

(<*>) :: Product (a -> b) -> Product a -> Product b #

(*>) :: Product a -> Product b -> Product b #

(<*) :: Product a -> Product b -> Product a #

Applicative First 

Methods

pure :: a -> First a #

(<*>) :: First (a -> b) -> First a -> First b #

(*>) :: First a -> First b -> First b #

(<*) :: First a -> First b -> First a #

Applicative Last 

Methods

pure :: a -> Last a #

(<*>) :: Last (a -> b) -> Last a -> Last b #

(*>) :: Last a -> Last b -> Last b #

(<*) :: Last a -> Last b -> Last a #

Applicative ((->) a) 

Methods

pure :: a -> a -> a #

(<*>) :: (a -> a -> b) -> (a -> a) -> a -> b #

(*>) :: (a -> a) -> (a -> b) -> a -> b #

(<*) :: (a -> a) -> (a -> b) -> a -> a #

Applicative (Either e) 

Methods

pure :: a -> Either e a #

(<*>) :: Either e (a -> b) -> Either e a -> Either e b #

(*>) :: Either e a -> Either e b -> Either e b #

(<*) :: Either e a -> Either e b -> Either e a #

Applicative f => Applicative (Rec1 f) 

Methods

pure :: a -> Rec1 f a #

(<*>) :: Rec1 f (a -> b) -> Rec1 f a -> Rec1 f b #

(*>) :: Rec1 f a -> Rec1 f b -> Rec1 f b #

(<*) :: Rec1 f a -> Rec1 f b -> Rec1 f a #

Monoid a => Applicative ((,) a) 

Methods

pure :: a -> (a, a) #

(<*>) :: (a, a -> b) -> (a, a) -> (a, b) #

(*>) :: (a, a) -> (a, b) -> (a, b) #

(<*) :: (a, a) -> (a, b) -> (a, a) #

Monad m => Applicative (WrappedMonad m) 

Methods

pure :: a -> WrappedMonad m a #

(<*>) :: WrappedMonad m (a -> b) -> WrappedMonad m a -> WrappedMonad m b #

(*>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b #

(<*) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m a #

Arrow a => Applicative (ArrowMonad a) 

Methods

pure :: a -> ArrowMonad a a #

(<*>) :: ArrowMonad a (a -> b) -> ArrowMonad a a -> ArrowMonad a b #

(*>) :: ArrowMonad a a -> ArrowMonad a b -> ArrowMonad a b #

(<*) :: ArrowMonad a a -> ArrowMonad a b -> ArrowMonad a a #

Applicative (Proxy *) 

Methods

pure :: a -> Proxy * a #

(<*>) :: Proxy * (a -> b) -> Proxy * a -> Proxy * b #

(*>) :: Proxy * a -> Proxy * b -> Proxy * b #

(<*) :: Proxy * a -> Proxy * b -> Proxy * a #

(Applicative f, Applicative g) => Applicative ((:*:) f g) 

Methods

pure :: a -> (f :*: g) a #

(<*>) :: (f :*: g) (a -> b) -> (f :*: g) a -> (f :*: g) b #

(*>) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) b #

(<*) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) a #

(Applicative f, Applicative g) => Applicative ((:.:) f g) 

Methods

pure :: a -> (f :.: g) a #

(<*>) :: (f :.: g) (a -> b) -> (f :.: g) a -> (f :.: g) b #

(*>) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) b #

(<*) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) a #

Arrow a => Applicative (WrappedArrow a b) 

Methods

pure :: a -> WrappedArrow a b a #

(<*>) :: WrappedArrow a b (a -> b) -> WrappedArrow a b a -> WrappedArrow a b b #

(*>) :: WrappedArrow a b a -> WrappedArrow a b b -> WrappedArrow a b b #

(<*) :: WrappedArrow a b a -> WrappedArrow a b b -> WrappedArrow a b a #

Monoid m => Applicative (Const * m) 

Methods

pure :: a -> Const * m a #

(<*>) :: Const * m (a -> b) -> Const * m a -> Const * m b #

(*>) :: Const * m a -> Const * m b -> Const * m b #

(<*) :: Const * m a -> Const * m b -> Const * m a #

Applicative f => Applicative (Alt * f) 

Methods

pure :: a -> Alt * f a #

(<*>) :: Alt * f (a -> b) -> Alt * f a -> Alt * f b #

(*>) :: Alt * f a -> Alt * f b -> Alt * f b #

(<*) :: Alt * f a -> Alt * f b -> Alt * f a #

Applicative f => Applicative (Backwards * f)

Apply f-actions in the reverse order.

Methods

pure :: a -> Backwards * f a #

(<*>) :: Backwards * f (a -> b) -> Backwards * f a -> Backwards * f b #

(*>) :: Backwards * f a -> Backwards * f b -> Backwards * f b #

(<*) :: Backwards * f a -> Backwards * f b -> Backwards * f a #

(Monoid w, Applicative m) => Applicative (WriterT w m) 

Methods

pure :: a -> WriterT w m a #

(<*>) :: WriterT w m (a -> b) -> WriterT w m a -> WriterT w m b #

(*>) :: WriterT w m a -> WriterT w m b -> WriterT w m b #

(<*) :: WriterT w m a -> WriterT w m b -> WriterT w m a #

(Functor m, Monad m) => Applicative (StateT s m) 

Methods

pure :: a -> StateT s m a #

(<*>) :: StateT s m (a -> b) -> StateT s m a -> StateT s m b #

(*>) :: StateT s m a -> StateT s m b -> StateT s m b #

(<*) :: StateT s m a -> StateT s m b -> StateT s m a #

(Functor m, Monad m) => Applicative (StateT s m) 

Methods

pure :: a -> StateT s m a #

(<*>) :: StateT s m (a -> b) -> StateT s m a -> StateT s m b #

(*>) :: StateT s m a -> StateT s m b -> StateT s m b #

(<*) :: StateT s m a -> StateT s m b -> StateT s m a #

Monoid a => Applicative (Constant * a) 

Methods

pure :: a -> Constant * a a #

(<*>) :: Constant * a (a -> b) -> Constant * a a -> Constant * a b #

(*>) :: Constant * a a -> Constant * a b -> Constant * a b #

(<*) :: Constant * a a -> Constant * a b -> Constant * a a #

(Monoid c, Monad m) => Applicative (Zooming m c) # 

Methods

pure :: a -> Zooming m c a #

(<*>) :: Zooming m c (a -> b) -> Zooming m c a -> Zooming m c b #

(*>) :: Zooming m c a -> Zooming m c b -> Zooming m c b #

(<*) :: Zooming m c a -> Zooming m c b -> Zooming m c a #

Applicative (IKleeneStore b b') # 

Methods

pure :: a -> IKleeneStore b b' a #

(<*>) :: IKleeneStore b b' (a -> b) -> IKleeneStore b b' a -> IKleeneStore b b' b #

(*>) :: IKleeneStore b b' a -> IKleeneStore b b' b -> IKleeneStore b b' b #

(<*) :: IKleeneStore b b' a -> IKleeneStore b b' b -> IKleeneStore b b' a #

Applicative f => Applicative (M1 i c f) 

Methods

pure :: a -> M1 i c f a #

(<*>) :: M1 i c f (a -> b) -> M1 i c f a -> M1 i c f b #

(*>) :: M1 i c f a -> M1 i c f b -> M1 i c f b #

(<*) :: M1 i c f a -> M1 i c f b -> M1 i c f a #

(Applicative f, Applicative g) => Applicative (Compose * * f g) 

Methods

pure :: a -> Compose * * f g a #

(<*>) :: Compose * * f g (a -> b) -> Compose * * f g a -> Compose * * f g b #

(*>) :: Compose * * f g a -> Compose * * f g b -> Compose * * f g b #

(<*) :: Compose * * f g a -> Compose * * f g b -> Compose * * f g a #

class Foldable t #

Data structures that can be folded.

For example, given a data type

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

a suitable instance would be

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

This is suitable even for abstract types, as the monoid is assumed to satisfy the monoid laws. Alternatively, one could define foldr:

instance Foldable Tree where
   foldr f z Empty = z
   foldr f z (Leaf x) = f x z
   foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l

Foldable instances are expected to satisfy the following laws:

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

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

sum = getSum . foldMap Sum

but may be less defined.

If the type is also a Functor instance, it should satisfy

foldMap f = fold . fmap f

which implies that

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

Minimal complete definition

foldMap | foldr

Instances

Foldable [] 

Methods

fold :: Monoid m => [m] -> 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 #

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

null :: [a] -> Bool #

length :: [a] -> Int #

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

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

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

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

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

Foldable Maybe 

Methods

fold :: Monoid m => Maybe m -> 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 #

toList :: Maybe a -> [a] #

null :: Maybe a -> Bool #

length :: Maybe a -> Int #

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

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

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

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

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

Foldable V1 

Methods

fold :: Monoid m => V1 m -> 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 #

toList :: V1 a -> [a] #

null :: V1 a -> Bool #

length :: V1 a -> Int #

elem :: Eq a => a -> V1 a -> Bool #

maximum :: Ord a => V1 a -> a #

minimum :: Ord a => V1 a -> a #

sum :: Num a => V1 a -> a #

product :: Num a => V1 a -> a #

Foldable U1 

Methods

fold :: Monoid m => U1 m -> 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 #

toList :: U1 a -> [a] #

null :: U1 a -> Bool #

length :: U1 a -> Int #

elem :: Eq a => a -> U1 a -> Bool #

maximum :: Ord a => U1 a -> a #

minimum :: Ord a => U1 a -> a #

sum :: Num a => U1 a -> a #

product :: Num a => U1 a -> a #

Foldable Par1 

Methods

fold :: Monoid m => Par1 m -> 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 #

toList :: Par1 a -> [a] #

null :: Par1 a -> Bool #

length :: Par1 a -> Int #

elem :: Eq a => a -> Par1 a -> Bool #

maximum :: Ord a => Par1 a -> a #

minimum :: Ord a => Par1 a -> a #

sum :: Num a => Par1 a -> a #

product :: Num a => Par1 a -> a #

Foldable Identity 

Methods

fold :: Monoid m => Identity m -> 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 #

toList :: Identity a -> [a] #

null :: Identity a -> Bool #

length :: Identity a -> Int #

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

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

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

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

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

Foldable Min 

Methods

fold :: Monoid m => Min m -> 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 #

toList :: Min a -> [a] #

null :: Min a -> Bool #

length :: Min a -> Int #

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

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

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

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

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

Foldable Max 

Methods

fold :: Monoid m => Max m -> 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 #

toList :: Max a -> [a] #

null :: Max a -> Bool #

length :: Max a -> Int #

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

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

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

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

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

Foldable First 

Methods

fold :: Monoid m => First m -> 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 #

toList :: First a -> [a] #

null :: First a -> Bool #

length :: First a -> Int #

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

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

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

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

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

Foldable Last 

Methods

fold :: Monoid m => Last m -> 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 #

toList :: Last a -> [a] #

null :: Last a -> Bool #

length :: Last a -> Int #

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

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

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

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

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

Foldable Option 

Methods

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

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

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

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

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

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

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

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

toList :: Option a -> [a] #

null :: Option a -> Bool #

length :: Option a -> Int #

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

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

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

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

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

Foldable NonEmpty 

Methods

fold :: Monoid m => NonEmpty m -> 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 #

toList :: NonEmpty a -> [a] #

null :: NonEmpty a -> Bool #

length :: NonEmpty a -> Int #

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

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

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

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

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

Foldable Complex 

Methods

fold :: Monoid m => Complex m -> 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 #

toList :: Complex a -> [a] #

null :: Complex a -> Bool #

length :: Complex a -> Int #

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

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

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

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

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

Foldable ZipList 

Methods

fold :: Monoid m => ZipList m -> 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 #

toList :: ZipList a -> [a] #

null :: ZipList a -> Bool #

length :: ZipList a -> Int #

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

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

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

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

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

Foldable Dual 

Methods

fold :: Monoid m => Dual m -> 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 #

toList :: Dual a -> [a] #

null :: Dual a -> Bool #

length :: Dual a -> Int #

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

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

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

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

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

Foldable Sum 

Methods

fold :: Monoid m => Sum m -> 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 #

toList :: Sum a -> [a] #

null :: Sum a -> Bool #

length :: Sum a -> Int #

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

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

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

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

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

Foldable Product 

Methods

fold :: Monoid m => Product m -> 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 #

toList :: Product a -> [a] #

null :: Product a -> Bool #

length :: Product a -> Int #

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

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

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

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

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

Foldable First 

Methods

fold :: Monoid m => First m -> 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 #

toList :: First a -> [a] #

null :: First a -> Bool #

length :: First a -> Int #

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

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

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

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

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

Foldable Last 

Methods

fold :: Monoid m => Last m -> 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 #

toList :: Last a -> [a] #

null :: Last a -> Bool #

length :: Last a -> Int #

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

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

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

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

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

Foldable IntMap 

Methods

fold :: Monoid m => IntMap m -> 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 #

toList :: IntMap a -> [a] #

null :: IntMap a -> Bool #

length :: IntMap a -> Int #

elem :: Eq a => a -> IntMap a -> Bool #

maximum :: Ord a => IntMap a -> a #

minimum :: Ord a => IntMap a -> a #

sum :: Num a => IntMap a -> a #

product :: Num a => IntMap a -> a #

Foldable Set 

Methods

fold :: Monoid m => Set m -> 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 #

toList :: Set a -> [a] #

null :: Set a -> Bool #

length :: Set a -> Int #

elem :: Eq a => a -> Set a -> Bool #

maximum :: Ord a => Set a -> a #

minimum :: Ord a => Set a -> a #

sum :: Num a => Set a -> a #

product :: Num a => Set a -> a #

Foldable (Either a) 

Methods

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

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

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

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

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

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

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

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

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

null :: Either a a -> Bool #

length :: Either a a -> Int #

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

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

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

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

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

Foldable f => Foldable (Rec1 f) 

Methods

fold :: Monoid m => Rec1 f m -> 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 #

toList :: Rec1 f a -> [a] #

null :: Rec1 f a -> Bool #

length :: Rec1 f a -> Int #

elem :: Eq a => a -> Rec1 f a -> Bool #

maximum :: Ord a => Rec1 f a -> a #

minimum :: Ord a => Rec1 f a -> a #

sum :: Num a => Rec1 f a -> a #

product :: Num a => Rec1 f a -> a #

Foldable (URec Char) 

Methods

fold :: Monoid m => URec Char m -> m #

foldMap :: Monoid m => (a -> m) -> URec Char a -> m #

foldr :: (a -> b -> b) -> b -> URec Char a -> b #

foldr' :: (a -> b -> b) -> b -> URec Char a -> b #

foldl :: (b -> a -> b) -> b -> URec Char a -> b #

foldl' :: (b -> a -> b) -> b -> URec Char a -> b #

foldr1 :: (a -> a -> a) -> URec Char a -> a #

foldl1 :: (a -> a -> a) -> URec Char a -> a #

toList :: URec Char a -> [a] #

null :: URec Char a -> Bool #

length :: URec Char a -> Int #

elem :: Eq a => a -> URec Char a -> Bool #

maximum :: Ord a => URec Char a -> a #

minimum :: Ord a => URec Char a -> a #

sum :: Num a => URec Char a -> a #

product :: Num a => URec Char a -> a #

Foldable (URec Double) 

Methods

fold :: Monoid m => URec Double m -> m #

foldMap :: Monoid m => (a -> m) -> URec Double a -> m #

foldr :: (a -> b -> b) -> b -> URec Double a -> b #

foldr' :: (a -> b -> b) -> b -> URec Double a -> b #

foldl :: (b -> a -> b) -> b -> URec Double a -> b #

foldl' :: (b -> a -> b) -> b -> URec Double a -> b #

foldr1 :: (a -> a -> a) -> URec Double a -> a #

foldl1 :: (a -> a -> a) -> URec Double a -> a #

toList :: URec Double a -> [a] #

null :: URec Double a -> Bool #

length :: URec Double a -> Int #

elem :: Eq a => a -> URec Double a -> Bool #

maximum :: Ord a => URec Double a -> a #

minimum :: Ord a => URec Double a -> a #

sum :: Num a => URec Double a -> a #

product :: Num a => URec Double a -> a #

Foldable (URec Float) 

Methods

fold :: Monoid m => URec Float m -> m #

foldMap :: Monoid m => (a -> m) -> URec Float a -> m #

foldr :: (a -> b -> b) -> b -> URec Float a -> b #

foldr' :: (a -> b -> b) -> b -> URec Float a -> b #

foldl :: (b -> a -> b) -> b -> URec Float a -> b #

foldl' :: (b -> a -> b) -> b -> URec Float a -> b #

foldr1 :: (a -> a -> a) -> URec Float a -> a #

foldl1 :: (a -> a -> a) -> URec Float a -> a #

toList :: URec Float a -> [a] #

null :: URec Float a -> Bool #

length :: URec Float a -> Int #

elem :: Eq a => a -> URec Float a -> Bool #

maximum :: Ord a => URec Float a -> a #

minimum :: Ord a => URec Float a -> a #

sum :: Num a => URec Float a -> a #

product :: Num a => URec Float a -> a #

Foldable (URec Int) 

Methods

fold :: Monoid m => URec Int m -> m #

foldMap :: Monoid m => (a -> m) -> URec Int a -> m #

foldr :: (a -> b -> b) -> b -> URec Int a -> b #

foldr' :: (a -> b -> b) -> b -> URec Int a -> b #

foldl :: (b -> a -> b) -> b -> URec Int a -> b #

foldl' :: (b -> a -> b) -> b -> URec Int a -> b #

foldr1 :: (a -> a -> a) -> URec Int a -> a #

foldl1 :: (a -> a -> a) -> URec Int a -> a #

toList :: URec Int a -> [a] #

null :: URec Int a -> Bool #

length :: URec Int a -> Int #

elem :: Eq a => a -> URec Int a -> Bool #

maximum :: Ord a => URec Int a -> a #

minimum :: Ord a => URec Int a -> a #

sum :: Num a => URec Int a -> a #

product :: Num a => URec Int a -> a #

Foldable (URec Word) 

Methods

fold :: Monoid m => URec Word m -> m #

foldMap :: Monoid m => (a -> m) -> URec Word a -> m #

foldr :: (a -> b -> b) -> b -> URec Word a -> b #

foldr' :: (a -> b -> b) -> b -> URec Word a -> b #

foldl :: (b -> a -> b) -> b -> URec Word a -> b #

foldl' :: (b -> a -> b) -> b -> URec Word a -> b #

foldr1 :: (a -> a -> a) -> URec Word a -> a #

foldl1 :: (a -> a -> a) -> URec Word a -> a #

toList :: URec Word a -> [a] #

null :: URec Word a -> Bool #

length :: URec Word a -> Int #

elem :: Eq a => a -> URec Word a -> Bool #

maximum :: Ord a => URec Word a -> a #

minimum :: Ord a => URec Word a -> a #

sum :: Num a => URec Word a -> a #

product :: Num a => URec Word a -> a #

Foldable (URec (Ptr ())) 

Methods

fold :: Monoid m => URec (Ptr ()) m -> m #

foldMap :: Monoid m => (a -> m) -> URec (Ptr ()) a -> m #

foldr :: (a -> b -> b) -> b -> URec (Ptr ()) a -> b #

foldr' :: (a -> b -> b) -> b -> URec (Ptr ()) a -> b #

foldl :: (b -> a -> b) -> b -> URec (Ptr ()) a -> b #

foldl' :: (b -> a -> b) -> b -> URec (Ptr ()) a -> b #

foldr1 :: (a -> a -> a) -> URec (Ptr ()) a -> a #

foldl1 :: (a -> a -> a) -> URec (Ptr ()) a -> a #

toList :: URec (Ptr ()) a -> [a] #

null :: URec (Ptr ()) a -> Bool #

length :: URec (Ptr ()) a -> Int #

elem :: Eq a => a -> URec (Ptr ()) a -> Bool #

maximum :: Ord a => URec (Ptr ()) a -> a #

minimum :: Ord a => URec (Ptr ()) a -> a #

sum :: Num a => URec (Ptr ()) a -> a #

product :: Num a => URec (Ptr ()) a -> a #

Foldable ((,) a) 

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Foldable (Array i) 

Methods

fold :: Monoid m => Array i m -> 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 #

toList :: Array i a -> [a] #

null :: Array i a -> Bool #

length :: Array i a -> Int #

elem :: Eq a => a -> Array i a -> Bool #

maximum :: Ord a => Array i a -> a #

minimum :: Ord a => Array i a -> a #

sum :: Num a => Array i a -> a #

product :: Num a => Array i a -> a #

Foldable (Arg a) 

Methods

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

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

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

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

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

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

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

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

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

null :: Arg a a -> Bool #

length :: Arg a a -> Int #

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

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

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

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

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

Foldable (Proxy *) 

Methods

fold :: Monoid m => Proxy * m -> 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 #

toList :: Proxy * a -> [a] #

null :: Proxy * a -> Bool #

length :: Proxy * a -> Int #

elem :: Eq a => a -> Proxy * a -> Bool #

maximum :: Ord a => Proxy * a -> a #

minimum :: Ord a => Proxy * a -> a #

sum :: Num a => Proxy * a -> a #

product :: Num a => Proxy * a -> a #

Foldable (Map k) 

Methods

fold :: Monoid m => Map k m -> 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 #

toList :: Map k a -> [a] #

null :: Map k a -> Bool #

length :: Map k a -> Int #

elem :: Eq a => a -> Map k a -> Bool #

maximum :: Ord a => Map k a -> a #

minimum :: Ord a => Map k a -> a #

sum :: Num a => Map k a -> a #

product :: Num a => Map k a -> a #

Foldable (K1 i c) 

Methods

fold :: Monoid m => K1 i c m -> 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 #

toList :: K1 i c a -> [a] #

null :: K1 i c a -> Bool #

length :: K1 i c a -> Int #

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 #

sum :: Num a => K1 i c a -> a #

product :: Num a => K1 i c a -> a #

(Foldable f, Foldable g) => Foldable ((:+:) f g) 

Methods

fold :: Monoid m => (f :+: g) m -> 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] #

null :: (f :+: g) a -> Bool #

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 #

sum :: Num a => (f :+: g) a -> a #

product :: Num a => (f :+: g) a -> a #

(Foldable f, Foldable g) => Foldable ((:*:) f g) 

Methods

fold :: Monoid m => (f :*: g) m -> 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] #

null :: (f :*: g) a -> Bool #

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 #

sum :: Num a => (f :*: g) a -> a #

product :: Num a => (f :*: g) a -> a #

(Foldable f, Foldable g) => Foldable ((:.:) f g) 

Methods

fold :: Monoid m => (f :.: g) m -> 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] #

null :: (f :.: g) a -> Bool #

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 #

sum :: Num a => (f :.: g) a -> a #

product :: Num a => (f :.: g) a -> a #

Foldable (Const * m) 

Methods

fold :: Monoid m => Const * m m -> m #

foldMap :: Monoid m => (a -> m) -> Const * m a -> m #

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 #

toList :: Const * m a -> [a] #

null :: Const * m a -> Bool #

length :: Const * m a -> Int #

elem :: Eq a => a -> Const * m a -> Bool #

maximum :: Ord a => Const * m a -> a #

minimum :: Ord a => Const * m a -> a #

sum :: Num a => Const * m a -> a #

product :: Num a => Const * m a -> a #

Foldable f => Foldable (Backwards * f)

Derived instance.

Methods

fold :: Monoid m => Backwards * f m -> m #

foldMap :: Monoid m => (a -> m) -> Backwards * f a -> m #

foldr :: (a -> b -> b) -> b -> Backwards * f a -> b #

foldr' :: (a -> b -> b) -> b -> Backwards * f a -> b #

foldl :: (b -> a -> b) -> b -> Backwards * f a -> b #

foldl' :: (b -> a -> b) -> b -> Backwards * f a -> b #

foldr1 :: (a -> a -> a) -> Backwards * f a -> a #

foldl1 :: (a -> a -> a) -> Backwards * f a -> a #

toList :: Backwards * f a -> [a] #

null :: Backwards * f a -> Bool #

length :: Backwards * f a -> Int #

elem :: Eq a => a -> Backwards * f a -> Bool #

maximum :: Ord a => Backwards * f a -> a #

minimum :: Ord a => Backwards * f a -> a #

sum :: Num a => Backwards * f a -> a #

product :: Num a => Backwards * f a -> a #

Foldable f => Foldable (WriterT w f) 

Methods

fold :: Monoid m => WriterT w f m -> 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 #

sum :: Num a => WriterT w f a -> a #

product :: Num a => WriterT w f a -> a #

Foldable (Constant * a) 

Methods

fold :: Monoid m => Constant * a m -> m #

foldMap :: Monoid m => (a -> m) -> Constant * a a -> m #

foldr :: (a -> b -> b) -> b -> Constant * a a -> b #

foldr' :: (a -> b -> b) -> b -> Constant * a a -> b #

foldl :: (b -> a -> b) -> b -> Constant * a a -> b #

foldl' :: (b -> a -> b) -> b -> Constant * a a -> b #

foldr1 :: (a -> a -> a) -> Constant * a a -> a #

foldl1 :: (a -> a -> a) -> Constant * a a -> a #

toList :: Constant * a a -> [a] #

null :: Constant * a a -> Bool #

length :: Constant * a a -> Int #

elem :: Eq a => a -> Constant * a a -> Bool #

maximum :: Ord a => Constant * a a -> a #

minimum :: Ord a => Constant * a a -> a #

sum :: Num a => Constant * a a -> a #

product :: Num a => Constant * a a -> a #

Foldable f => Foldable (M1 i c f) 

Methods

fold :: Monoid m => M1 i c f m -> 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 #

toList :: M1 i c f a -> [a] #

null :: M1 i c f a -> Bool #

length :: M1 i c f a -> Int #

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 #

sum :: Num a => M1 i c f a -> a #

product :: Num a => M1 i c f a -> a #

(Foldable f, Foldable g) => Foldable (Compose * * f g) 

Methods

fold :: Monoid m => Compose * * f g m -> 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 #

sum :: Num a => Compose * * f g a -> a #

product :: Num a => Compose * * f g a -> a #

class Monoid a #

The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:

  • mappend mempty x = x
  • mappend x mempty = x
  • mappend x (mappend y z) = mappend (mappend x y) z
  • mconcat = foldr mappend mempty

The method names refer to the monoid of lists under concatenation, but there are many other instances.

Some types can be viewed as a monoid in more than one way, e.g. both addition and multiplication on numbers. In such cases we often define newtypes and make those instances of Monoid, e.g. Sum and Product.

Minimal complete definition

mempty, mappend

Instances

Monoid Ordering 
Monoid () 

Methods

mempty :: () #

mappend :: () -> () -> () #

mconcat :: [()] -> () #

Monoid All 

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Monoid Any 

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Monoid IntSet 
Monoid [a] 

Methods

mempty :: [a] #

mappend :: [a] -> [a] -> [a] #

mconcat :: [[a]] -> [a] #

Monoid a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S." Since there is no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

Monoid a => Monoid (IO a) 

Methods

mempty :: IO a #

mappend :: IO a -> IO a -> IO a #

mconcat :: [IO a] -> IO a #

Ord a => Monoid (Max a) 

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

Ord a => Monoid (Min a) 

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

Monoid a => Monoid (Identity a) 

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

(Ord a, Bounded a) => Monoid (Min a) 

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

(Ord a, Bounded a) => Monoid (Max a) 

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

Monoid m => Monoid (WrappedMonoid m) 
Semigroup a => Monoid (Option a) 

Methods

mempty :: Option a #

mappend :: Option a -> Option a -> Option a #

mconcat :: [Option a] -> Option a #

Monoid a => Monoid (Dual a) 

Methods

mempty :: Dual a #

mappend :: Dual a -> Dual a -> Dual a #

mconcat :: [Dual a] -> Dual a #

Monoid (Endo a) 

Methods

mempty :: Endo a #

mappend :: Endo a -> Endo a -> Endo a #

mconcat :: [Endo a] -> Endo a #

Num a => Monoid (Sum a) 

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

Num a => Monoid (Product a) 

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

Monoid (First a) 

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

mconcat :: [First a] -> First a #

Monoid (Last a) 

Methods

mempty :: Last a #

mappend :: Last a -> Last a -> Last a #

mconcat :: [Last a] -> Last a #

Monoid (IntMap a) 

Methods

mempty :: IntMap a #

mappend :: IntMap a -> IntMap a -> IntMap a #

mconcat :: [IntMap a] -> IntMap a #

Ord a => Monoid (Set a) 

Methods

mempty :: Set a #

mappend :: Set a -> Set a -> Set a #

mconcat :: [Set a] -> Set a #

Monoid b => Monoid (a -> b) 

Methods

mempty :: a -> b #

mappend :: (a -> b) -> (a -> b) -> a -> b #

mconcat :: [a -> b] -> a -> b #

(Monoid a, Monoid b) => Monoid (a, b) 

Methods

mempty :: (a, b) #

mappend :: (a, b) -> (a, b) -> (a, b) #

mconcat :: [(a, b)] -> (a, b) #

Monoid (Proxy k s) 

Methods

mempty :: Proxy k s #

mappend :: Proxy k s -> Proxy k s -> Proxy k s #

mconcat :: [Proxy k s] -> Proxy k s #

Ord k => Monoid (Map k v) 

Methods

mempty :: Map k v #

mappend :: Map k v -> Map k v -> Map k v #

mconcat :: [Map k v] -> Map k v #

(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) 

Methods

mempty :: (a, b, c) #

mappend :: (a, b, c) -> (a, b, c) -> (a, b, c) #

mconcat :: [(a, b, c)] -> (a, b, c) #

Monoid a => Monoid (Const k a b) 

Methods

mempty :: Const k a b #

mappend :: Const k a b -> Const k a b -> Const k a b #

mconcat :: [Const k a b] -> Const k a b #

Alternative f => Monoid (Alt * f a) 

Methods

mempty :: Alt * f a #

mappend :: Alt * f a -> Alt * f a -> Alt * f a #

mconcat :: [Alt * f a] -> Alt * f a #

Monoid a => Monoid (Constant k a b) 

Methods

mempty :: Constant k a b #

mappend :: Constant k a b -> Constant k a b -> Constant k a b #

mconcat :: [Constant k a b] -> Constant k a b #

(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) 

Methods

mempty :: (a, b, c, d) #

mappend :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

mconcat :: [(a, b, c, d)] -> (a, b, c, d) #

(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) 

Methods

mempty :: (a, b, c, d, e) #

mappend :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e) #

data Backwards k f a :: forall k. (k -> *) -> k -> * #

The same functor, but with an Applicative instance that performs actions in the reverse order.

Instances

Functor f => Functor (Backwards * f)

Derived instance.

Methods

fmap :: (a -> b) -> Backwards * f a -> Backwards * f b #

(<$) :: a -> Backwards * f b -> Backwards * f a #

Applicative f => Applicative (Backwards * f)

Apply f-actions in the reverse order.

Methods

pure :: a -> Backwards * f a #

(<*>) :: Backwards * f (a -> b) -> Backwards * f a -> Backwards * f b #

(*>) :: Backwards * f a -> Backwards * f b -> Backwards * f b #

(<*) :: Backwards * f a -> Backwards * f b -> Backwards * f a #

Foldable f => Foldable (Backwards * f)

Derived instance.

Methods

fold :: Monoid m => Backwards * f m -> m #

foldMap :: Monoid m => (a -> m) -> Backwards * f a -> m #

foldr :: (a -> b -> b) -> b -> Backwards * f a -> b #

foldr' :: (a -> b -> b) -> b -> Backwards * f a -> b #

foldl :: (b -> a -> b) -> b -> Backwards * f a -> b #

foldl' :: (b -> a -> b) -> b -> Backwards * f a -> b #

foldr1 :: (a -> a -> a) -> Backwards * f a -> a #

foldl1 :: (a -> a -> a) -> Backwards * f a -> a #

toList :: Backwards * f a -> [a] #

null :: Backwards * f a -> Bool #

length :: Backwards * f a -> Int #

elem :: Eq a => a -> Backwards * f a -> Bool #

maximum :: Ord a => Backwards * f a -> a #

minimum :: Ord a => Backwards * f a -> a #

sum :: Num a => Backwards * f a -> a #

product :: Num a => Backwards * f a -> a #

Traversable f => Traversable (Backwards * f)

Derived instance.

Methods

traverse :: Applicative f => (a -> f b) -> Backwards * f a -> f (Backwards * f b) #

sequenceA :: Applicative f => Backwards * f (f a) -> f (Backwards * f a) #

mapM :: Monad m => (a -> m b) -> Backwards * f a -> m (Backwards * f b) #

sequence :: Monad m => Backwards * f (m a) -> m (Backwards * f a) #

Eq1 f => Eq1 (Backwards * f) 

Methods

liftEq :: (a -> b -> Bool) -> Backwards * f a -> Backwards * f b -> Bool #

Ord1 f => Ord1 (Backwards * f) 

Methods

liftCompare :: (a -> b -> Ordering) -> Backwards * f a -> Backwards * f b -> Ordering #

Read1 f => Read1 (Backwards * f) 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Backwards * f a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Backwards * f a] #

Show1 f => Show1 (Backwards * f) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Backwards * f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Backwards * f a] -> ShowS #

Alternative f => Alternative (Backwards * f)

Try alternatives in the same order as f.

Methods

empty :: Backwards * f a #

(<|>) :: Backwards * f a -> Backwards * f a -> Backwards * f a #

some :: Backwards * f a -> Backwards * f [a] #

many :: Backwards * f a -> Backwards * f [a] #

Phantom f => Phantom (Backwards * f) Source # 

Methods

coerce :: Backwards * f a -> Backwards * f b

Identical f => Identical (Backwards * f) Source # 

Methods

extract :: Backwards * f a -> a

(Eq1 f, Eq a) => Eq (Backwards * f a) 

Methods

(==) :: Backwards * f a -> Backwards * f a -> Bool #

(/=) :: Backwards * f a -> Backwards * f a -> Bool #

(Ord1 f, Ord a) => Ord (Backwards * f a) 

Methods

compare :: Backwards * f a -> Backwards * f a -> Ordering #

(<) :: Backwards * f a -> Backwards * f a -> Bool #

(<=) :: Backwards * f a -> Backwards * f a -> Bool #

(>) :: Backwards * f a -> Backwards * f a -> Bool #

(>=) :: Backwards * f a -> Backwards * f a -> Bool #

max :: Backwards * f a -> Backwards * f a -> Backwards * f a #

min :: Backwards * f a -> Backwards * f a -> Backwards * f a #

(Read1 f, Read a) => Read (Backwards * f a) 
(Show1 f, Show a) => Show (Backwards * f a) 

Methods

showsPrec :: Int -> Backwards * f a -> ShowS #

show :: Backwards * f a -> String #

showList :: [Backwards * f a] -> ShowS #

data All :: * #

Boolean monoid under conjunction (&&).

Instances

Bounded All 

Methods

minBound :: All #

maxBound :: All #

Eq All 

Methods

(==) :: All -> All -> Bool #

(/=) :: All -> All -> Bool #

Ord All 

Methods

compare :: All -> All -> Ordering #

(<) :: All -> All -> Bool #

(<=) :: All -> All -> Bool #

(>) :: All -> All -> Bool #

(>=) :: All -> All -> Bool #

max :: All -> All -> All #

min :: All -> All -> All #

Read All 
Show All 

Methods

showsPrec :: Int -> All -> ShowS #

show :: All -> String #

showList :: [All] -> ShowS #

Generic All 

Associated Types

type Rep All :: * -> * #

Methods

from :: All -> Rep All x #

to :: Rep All x -> All #

Semigroup All 

Methods

(<>) :: All -> All -> All #

sconcat :: NonEmpty All -> All #

stimes :: Integral b => b -> All -> All #

Monoid All 

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

type Rep All 
type Rep All = D1 (MetaData "All" "Data.Monoid" "base" True) (C1 (MetaCons "All" PrefixI True) (S1 (MetaSel (Just Symbol "getAll") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))

data Any :: * #

Boolean monoid under disjunction (||).

Instances

Bounded Any 

Methods

minBound :: Any #

maxBound :: Any #

Eq Any 

Methods

(==) :: Any -> Any -> Bool #

(/=) :: Any -> Any -> Bool #

Ord Any 

Methods

compare :: Any -> Any -> Ordering #

(<) :: Any -> Any -> Bool #

(<=) :: Any -> Any -> Bool #

(>) :: Any -> Any -> Bool #

(>=) :: Any -> Any -> Bool #

max :: Any -> Any -> Any #

min :: Any -> Any -> Any #

Read Any 
Show Any 

Methods

showsPrec :: Int -> Any -> ShowS #

show :: Any -> String #

showList :: [Any] -> ShowS #

Generic Any 

Associated Types

type Rep Any :: * -> * #

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Semigroup Any 

Methods

(<>) :: Any -> Any -> Any #

sconcat :: NonEmpty Any -> Any #

stimes :: Integral b => b -> Any -> Any #

Monoid Any 

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

type Rep Any 
type Rep Any = D1 (MetaData "Any" "Data.Monoid" "base" True) (C1 (MetaCons "Any" PrefixI True) (S1 (MetaSel (Just Symbol "getAny") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))

data First a :: * -> * #

Maybe monoid returning the leftmost non-Nothing value.

First a is isomorphic to Alt Maybe a, but precedes it historically.

Instances

Monad First 

Methods

(>>=) :: First a -> (a -> First b) -> First b #

(>>) :: First a -> First b -> First b #

return :: a -> First a #

fail :: String -> First a #

Functor First 

Methods

fmap :: (a -> b) -> First a -> First b #

(<$) :: a -> First b -> First a #

Applicative First 

Methods

pure :: a -> First a #

(<*>) :: First (a -> b) -> First a -> First b #

(*>) :: First a -> First b -> First b #

(<*) :: First a -> First b -> First a #

Foldable First 

Methods

fold :: Monoid m => First m -> 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 #

toList :: First a -> [a] #

null :: First a -> Bool #

length :: First a -> Int #

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

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

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

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

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

Generic1 First 

Associated Types

type Rep1 (First :: * -> *) :: * -> * #

Methods

from1 :: First a -> Rep1 First a #

to1 :: Rep1 First a -> First a #

Eq a => Eq (First a) 

Methods

(==) :: First a -> First a -> Bool #

(/=) :: First a -> First a -> Bool #

Ord a => Ord (First a) 

Methods

compare :: First a -> First a -> Ordering #

(<) :: First a -> First a -> Bool #

(<=) :: First a -> First a -> Bool #

(>) :: First a -> First a -> Bool #

(>=) :: First a -> First a -> Bool #

max :: First a -> First a -> First a #

min :: First a -> First a -> First a #

Read a => Read (First a) 
Show a => Show (First a) 

Methods

showsPrec :: Int -> First a -> ShowS #

show :: First a -> String #

showList :: [First a] -> ShowS #

Generic (First a) 

Associated Types

type Rep (First a) :: * -> * #

Methods

from :: First a -> Rep (First a) x #

to :: Rep (First a) x -> First a #

Semigroup (First a) 

Methods

(<>) :: First a -> First a -> First a #

sconcat :: NonEmpty (First a) -> First a #

stimes :: Integral b => b -> First a -> First a #

Monoid (First a) 

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

mconcat :: [First a] -> First a #

type Rep1 First 
type Rep1 First = D1 (MetaData "First" "Data.Monoid" "base" True) (C1 (MetaCons "First" PrefixI True) (S1 (MetaSel (Just Symbol "getFirst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Maybe)))
type Rep (First a) 
type Rep (First a) = D1 (MetaData "First" "Data.Monoid" "base" True) (C1 (MetaCons "First" PrefixI True) (S1 (MetaSel (Just Symbol "getFirst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe a))))

data Last a :: * -> * #

Maybe monoid returning the rightmost non-Nothing value.

Last a is isomorphic to Dual (First a), and thus to Dual (Alt Maybe a)

Instances

Monad Last 

Methods

(>>=) :: Last a -> (a -> Last b) -> Last b #

(>>) :: Last a -> Last b -> Last b #

return :: a -> Last a #

fail :: String -> Last a #

Functor Last 

Methods

fmap :: (a -> b) -> Last a -> Last b #

(<$) :: a -> Last b -> Last a #

Applicative Last 

Methods

pure :: a -> Last a #

(<*>) :: Last (a -> b) -> Last a -> Last b #

(*>) :: Last a -> Last b -> Last b #

(<*) :: Last a -> Last b -> Last a #

Foldable Last 

Methods

fold :: Monoid m => Last m -> 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 #

toList :: Last a -> [a] #

null :: Last a -> Bool #

length :: Last a -> Int #

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

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

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

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

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

Generic1 Last 

Associated Types

type Rep1 (Last :: * -> *) :: * -> * #

Methods

from1 :: Last a -> Rep1 Last a #

to1 :: Rep1 Last a -> Last a #

Eq a => Eq (Last a) 

Methods

(==) :: Last a -> Last a -> Bool #

(/=) :: Last a -> Last a -> Bool #

Ord a => Ord (Last a) 

Methods

compare :: Last a -> Last a -> Ordering #

(<) :: Last a -> Last a -> Bool #

(<=) :: Last a -> Last a -> Bool #

(>) :: Last a -> Last a -> Bool #

(>=) :: Last a -> Last a -> Bool #

max :: Last a -> Last a -> Last a #

min :: Last a -> Last a -> Last a #

Read a => Read (Last a) 
Show a => Show (Last a) 

Methods

showsPrec :: Int -> Last a -> ShowS #

show :: Last a -> String #

showList :: [Last a] -> ShowS #

Generic (Last a) 

Associated Types

type Rep (Last a) :: * -> * #

Methods

from :: Last a -> Rep (Last a) x #

to :: Rep (Last a) x -> Last a #

Semigroup (Last a) 

Methods

(<>) :: Last a -> Last a -> Last a #

sconcat :: NonEmpty (Last a) -> Last a #

stimes :: Integral b => b -> Last a -> Last a #

Monoid (Last a) 

Methods

mempty :: Last a #

mappend :: Last a -> Last a -> Last a #

mconcat :: [Last a] -> Last a #

type Rep1 Last 
type Rep1 Last = D1 (MetaData "Last" "Data.Monoid" "base" True) (C1 (MetaCons "Last" PrefixI True) (S1 (MetaSel (Just Symbol "getLast") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Maybe)))
type Rep (Last a) 
type Rep (Last a) = D1 (MetaData "Last" "Data.Monoid" "base" True) (C1 (MetaCons "Last" PrefixI True) (S1 (MetaSel (Just Symbol "getLast") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe a))))

data Sum a :: * -> * #

Monoid under addition.

Instances

Monad Sum 

Methods

(>>=) :: Sum a -> (a -> Sum b) -> Sum b #

(>>) :: Sum a -> Sum b -> Sum b #

return :: a -> Sum a #

fail :: String -> Sum a #

Functor Sum 

Methods

fmap :: (a -> b) -> Sum a -> Sum b #

(<$) :: a -> Sum b -> Sum a #

Applicative Sum 

Methods

pure :: a -> Sum a #

(<*>) :: Sum (a -> b) -> Sum a -> Sum b #

(*>) :: Sum a -> Sum b -> Sum b #

(<*) :: Sum a -> Sum b -> Sum a #

Foldable Sum 

Methods

fold :: Monoid m => Sum m -> 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 #

toList :: Sum a -> [a] #

null :: Sum a -> Bool #

length :: Sum a -> Int #

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

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

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

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

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

Generic1 Sum 

Associated Types

type Rep1 (Sum :: * -> *) :: * -> * #

Methods

from1 :: Sum a -> Rep1 Sum a #

to1 :: Rep1 Sum a -> Sum a #

Bounded a => Bounded (Sum a) 

Methods

minBound :: Sum a #

maxBound :: Sum a #

Eq a => Eq (Sum a) 

Methods

(==) :: Sum a -> Sum a -> Bool #

(/=) :: Sum a -> Sum a -> Bool #

Num a => Num (Sum a) 

Methods

(+) :: Sum a -> Sum a -> Sum a #

(-) :: Sum a -> Sum a -> Sum a #

(*) :: Sum a -> Sum a -> Sum a #

negate :: Sum a -> Sum a #

abs :: Sum a -> Sum a #

signum :: Sum a -> Sum a #

fromInteger :: Integer -> Sum a #

Ord a => Ord (Sum a) 

Methods

compare :: Sum a -> Sum a -> Ordering #

(<) :: Sum a -> Sum a -> Bool #

(<=) :: Sum a -> Sum a -> Bool #

(>) :: Sum a -> Sum a -> Bool #

(>=) :: Sum a -> Sum a -> Bool #

max :: Sum a -> Sum a -> Sum a #

min :: Sum a -> Sum a -> Sum a #

Read a => Read (Sum a) 
Show a => Show (Sum a) 

Methods

showsPrec :: Int -> Sum a -> ShowS #

show :: Sum a -> String #

showList :: [Sum a] -> ShowS #

Generic (Sum a) 

Associated Types

type Rep (Sum a) :: * -> * #

Methods

from :: Sum a -> Rep (Sum a) x #

to :: Rep (Sum a) x -> Sum a #

Num a => Semigroup (Sum a) 

Methods

(<>) :: Sum a -> Sum a -> Sum a #

sconcat :: NonEmpty (Sum a) -> Sum a #

stimes :: Integral b => b -> Sum a -> Sum a #

Num a => Monoid (Sum a) 

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

type Rep1 Sum 
type Rep1 Sum = D1 (MetaData "Sum" "Data.Monoid" "base" True) (C1 (MetaCons "Sum" PrefixI True) (S1 (MetaSel (Just Symbol "getSum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep (Sum a) 
type Rep (Sum a) = D1 (MetaData "Sum" "Data.Monoid" "base" True) (C1 (MetaCons "Sum" PrefixI True) (S1 (MetaSel (Just Symbol "getSum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

data Product a :: * -> * #

Monoid under multiplication.

Instances

Monad Product 

Methods

(>>=) :: Product a -> (a -> Product b) -> Product b #

(>>) :: Product a -> Product b -> Product b #

return :: a -> Product a #

fail :: String -> Product a #

Functor Product 

Methods

fmap :: (a -> b) -> Product a -> Product b #

(<$) :: a -> Product b -> Product a #

Applicative Product 

Methods

pure :: a -> Product a #

(<*>) :: Product (a -> b) -> Product a -> Product b #

(*>) :: Product a -> Product b -> Product b #

(<*) :: Product a -> Product b -> Product a #

Foldable Product 

Methods

fold :: Monoid m => Product m -> 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 #

toList :: Product a -> [a] #

null :: Product a -> Bool #

length :: Product a -> Int #

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

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

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

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

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

Generic1 Product 

Associated Types

type Rep1 (Product :: * -> *) :: * -> * #

Methods

from1 :: Product a -> Rep1 Product a #

to1 :: Rep1 Product a -> Product a #

Bounded a => Bounded (Product a) 
Eq a => Eq (Product a) 

Methods

(==) :: Product a -> Product a -> Bool #

(/=) :: Product a -> Product a -> Bool #

Num a => Num (Product a) 

Methods

(+) :: Product a -> Product a -> Product a #

(-) :: Product a -> Product a -> Product a #

(*) :: Product a -> Product a -> Product a #

negate :: Product a -> Product a #

abs :: Product a -> Product a #

signum :: Product a -> Product a #

fromInteger :: Integer -> Product a #

Ord a => Ord (Product a) 

Methods

compare :: Product a -> Product a -> Ordering #

(<) :: Product a -> Product a -> Bool #

(<=) :: Product a -> Product a -> Bool #

(>) :: Product a -> Product a -> Bool #

(>=) :: Product a -> Product a -> Bool #

max :: Product a -> Product a -> Product a #

min :: Product a -> Product a -> Product a #

Read a => Read (Product a) 
Show a => Show (Product a) 

Methods

showsPrec :: Int -> Product a -> ShowS #

show :: Product a -> String #

showList :: [Product a] -> ShowS #

Generic (Product a) 

Associated Types

type Rep (Product a) :: * -> * #

Methods

from :: Product a -> Rep (Product a) x #

to :: Rep (Product a) x -> Product a #

Num a => Semigroup (Product a) 

Methods

(<>) :: Product a -> Product a -> Product a #

sconcat :: NonEmpty (Product a) -> Product a #

stimes :: Integral b => b -> Product a -> Product a #

Num a => Monoid (Product a) 

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

type Rep1 Product 
type Rep1 Product = D1 (MetaData "Product" "Data.Monoid" "base" True) (C1 (MetaCons "Product" PrefixI True) (S1 (MetaSel (Just Symbol "getProduct") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep (Product a) 
type Rep (Product a) = D1 (MetaData "Product" "Data.Monoid" "base" True) (C1 (MetaCons "Product" PrefixI True) (S1 (MetaSel (Just Symbol "getProduct") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))