base-4.16.3.0: Basic libraries
Copyright(c) Andy Gill 2001
(c) Oregon Graduate Institute of Science and Technology 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Monoid

Description

A type a is a Monoid if it provides an associative function (<>) that lets you combine any two values of type a into one, and a neutral element (mempty) such that

a <> mempty == mempty <> a == a

A Monoid is a Semigroup with the added requirement of a neutral element. Thus any Monoid is a Semigroup, but not the other way around.

Examples

Expand

The Sum monoid is defined by the numerical addition operator and `0` as neutral element:

>>> mempty :: Sum Int Sum {getSum = 0} >>> Sum 1 <> Sum 2 <> Sum 3 <> Sum 4 :: Sum Int Sum {getSum = 10} 

We can combine multiple values in a list into a single value using the mconcat function. Note that we have to specify the type here since Int is a monoid under several different operations:

>>> mconcat [1,2,3,4] :: Sum Int Sum {getSum = 10} >>> mconcat [] :: Sum Int Sum {getSum = 0} 

Another valid monoid instance of Int is Product It is defined by multiplication and `1` as neutral element:

>>> Product 1 <> Product 2 <> Product 3 <> Product 4 :: Product Int Product {getProduct = 24} >>> mconcat [1,2,3,4] :: Product Int Product {getProduct = 24} >>> mconcat [] :: Product Int Product {getProduct = 1} 
Synopsis

Monoid typeclass

classSemigroup a => Monoid a whereSource#

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

Right identity
x <>mempty = x
Left identity
mempty<> x = x
Associativity
x <> (y <> z) = (x <> y) <> z (Semigroup law)
Concatenation
mconcat = foldr (<>) 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.

NOTE: Semigroup is a superclass of Monoid since base-4.11.0.0.

Minimal complete definition

mempty

Methods

mempty :: a Source#

Identity of mappend

>>> "Hello world" <> mempty "Hello world" 

mappend :: a -> a -> a Source#

An associative operation

NOTE: This method is redundant and has the default implementation mappend = (<>) since base-4.11.0.0. Should it be implemented manually, since mappend is a synonym for (<>), it is expected that the two functions are defined the same way. In a future GHC release mappend will be removed from Monoid.

mconcat :: [a] -> a Source#

Fold a list using the monoid.

For most types, the default definition for mconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types.

>>> mconcat ["Hello", " ", "Haskell", "!"] "Hello Haskell!" 

Instances

Instances details
MonoidAllSource#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

MonoidAnySource#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

MonoidEventSource#

Since: base-4.4.0.0

Instance details

Defined in GHC.Event.Internal.Types

MonoidLifetimeSource#

mappend takes the longer of two lifetimes.

Since: base-4.8.0.0

Instance details

Defined in GHC.Event.Internal.Types

MonoidOrderingSource#

Since: base-2.1

Instance details

Defined in GHC.Base

Monoid ()Source#

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: () Source#

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

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

FiniteBits a => Monoid (And a)Source#

This constraint is arguably too strong. However, as some types (such as Natural) have undefined complement, this is the only safe choice.

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

mempty :: And a Source#

mappend :: And a -> And a -> And a Source#

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

FiniteBits a => Monoid (Iff a)Source#

This constraint is arguably too strong. However, as some types (such as Natural) have undefined complement, this is the only safe choice.

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

mempty :: Iff a Source#

mappend :: Iff a -> Iff a -> Iff a Source#

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

Bits a => Monoid (Ior a)Source#

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

mempty :: Ior a Source#

mappend :: Ior a -> Ior a -> Ior a Source#

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

Bits a => Monoid (Xor a)Source#

Since: base-4.16

Instance details

Defined in Data.Bits

Methods

mempty :: Xor a Source#

mappend :: Xor a -> Xor a -> Xor a Source#

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

Monoid (Comparison a)Source#

mempty on comparisons always returns EQ. Without newtypes this equals pure (pure EQ).

mempty :: Comparison a mempty = Comparison _ _ -> EQ 
Instance details

Defined in Data.Functor.Contravariant

Monoid (Equivalence a)Source#

mempty on equivalences always returns True. Without newtypes this equals pure (pure True).

mempty :: Equivalence a mempty = Equivalence _ _ -> True 
Instance details

Defined in Data.Functor.Contravariant

Monoid (Predicate a)Source#

mempty on predicates always returns True. Without newtypes this equals pure True.

mempty :: Predicate a mempty = _ -> True 
Instance details

Defined in Data.Functor.Contravariant

Monoid a => Monoid (Identity a)Source#

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Monoid (First a)Source#

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: First a Source#

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

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

Monoid (Last a)Source#

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: Last a Source#

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

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

Monoid a => Monoid (Down a)Source#

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

mempty :: Down a Source#

mappend :: Down a -> Down a -> Down a Source#

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

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

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Max a Source#

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

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

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

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Min a Source#

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

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

Monoid m => Monoid (WrappedMonoid m)Source#

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Monoid a => Monoid (Dual a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Dual a Source#

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

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

Monoid (Endo a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Endo a Source#

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

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

Num a => Monoid (Product a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Num a => Monoid (Sum a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Sum a Source#

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

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

Monoid p => Monoid (Par1 p)Source#

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: Par1 p Source#

mappend :: Par1 p -> Par1 p -> Par1 p Source#

mconcat :: [Par1 p] -> Par1 p Source#

Monoid a => Monoid (IO a)Source#

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

mempty :: IO a Source#

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

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

Semigroup a => Monoid (Maybe a)Source#

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 4.11.0: constraint on inner a value generalised from Monoid to Semigroup.

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: Maybe a Source#

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

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

Monoid a => Monoid (a)Source#

Since: base-4.15

Instance details

Defined in GHC.Base

Methods

mempty :: (a) Source#

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

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

Monoid [a]Source#

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: [a] Source#

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

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

Monoid a => Monoid (Op a b)Source#

mempty @(Op a b) without newtypes is mempty @(b->a) = _ -> mempty.

mempty :: Op a b mempty = Op _ -> mempty 
Instance details

Defined in Data.Functor.Contravariant

Methods

mempty :: Op a b Source#

mappend :: Op a b -> Op a b -> Op a b Source#

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

Monoid (Proxy s)Source#

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s Source#

mappend :: Proxy s -> Proxy s -> Proxy s Source#

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

Monoid (U1 p)Source#

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: U1 p Source#

mappend :: U1 p -> U1 p -> U1 p Source#

mconcat :: [U1 p] -> U1 p Source#

Monoid a => Monoid (ST s a)Source#

Since: base-4.11.0.0

Instance details

Defined in GHC.ST

Methods

mempty :: ST s a Source#

mappend :: ST s a -> ST s a -> ST s a Source#

mconcat :: [ST s a] -> ST s a Source#

Monoid b => Monoid (a -> b)Source#

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: a -> b Source#

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

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

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

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b) Source#

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

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

Monoid a => Monoid (Const a b)Source#

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

mempty :: Const a b Source#

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

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

(Applicative f, Monoid a) => Monoid (Ap f a)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

mempty :: Ap f a Source#

mappend :: Ap f a -> Ap f a -> Ap f a Source#

mconcat :: [Ap f a] -> Ap f a Source#

Alternative f => Monoid (Alt f a)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Alt f a Source#

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

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

Monoid (f p) => Monoid (Rec1 f p)Source#

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: Rec1 f p Source#

mappend :: Rec1 f p -> Rec1 f p -> Rec1 f p Source#

mconcat :: [Rec1 f p] -> Rec1 f p Source#

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

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

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

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

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

(Monoid (f a), Monoid (g a)) => Monoid (Product f g a)Source#

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Product

Methods

mempty :: Product f g a Source#

mappend :: Product f g a -> Product f g a -> Product f g a Source#

mconcat :: [Product f g a] -> Product f g a Source#

(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p)Source#

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: (f :*: g) p Source#

mappend :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p Source#

mconcat :: [(f :*: g) p] -> (f :*: g) p Source#

Monoid c => Monoid (K1 i c p)Source#

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: K1 i c p Source#

mappend :: K1 i c p -> K1 i c p -> K1 i c p Source#

mconcat :: [K1 i c p] -> K1 i c p Source#

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

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

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

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

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

Monoid (f (g a)) => Monoid (Compose f g a)Source#

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Compose

Methods

mempty :: Compose f g a Source#

mappend :: Compose f g a -> Compose f g a -> Compose f g a Source#

mconcat :: [Compose f g a] -> Compose f g a Source#

Monoid (f (g p)) => Monoid ((f :.: g) p)Source#

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: (f :.: g) p Source#

mappend :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p Source#

mconcat :: [(f :.: g) p] -> (f :.: g) p Source#

Monoid (f p) => Monoid (M1 i c f p)Source#

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: M1 i c f p Source#

mappend :: M1 i c f p -> M1 i c f p -> M1 i c f p Source#

mconcat :: [M1 i c f p] -> M1 i c f p Source#

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

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

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

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

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

(<>) :: Semigroup a => a -> a -> a infixr 6Source#

An associative operation.

>>> [1,2,3] <> [4,5,6] [1,2,3,4,5,6] 

newtypeDual a Source#

The dual of a Monoid, obtained by swapping the arguments of mappend.

>>> getDual (mappend (Dual "Hello") (Dual "World")) "WorldHello" 

Constructors

Dual 

Fields

Instances

Instances details
MonadFixDualSource#

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Dual a) -> Dual a Source#

MonadZipDualSource#

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Zip

Methods

mzip :: Dual a -> Dual b -> Dual (a, b) Source#

mzipWith :: (a -> b -> c) -> Dual a -> Dual b -> Dual c Source#

munzip :: Dual (a, b) -> (Dual a, Dual b) Source#

FoldableDualSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

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 -> BoolSource#

length :: Dual a -> IntSource#

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

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

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

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

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

TraversableDualSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

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

sequenceA :: Applicative f => Dual (f a) -> f (Dual a) Source#

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

sequence :: Monad m => Dual (m a) -> m (Dual a) Source#

ApplicativeDualSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

pure :: a -> Dual a Source#

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

liftA2 :: (a -> b -> c) -> Dual a -> Dual b -> Dual c Source#

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

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

FunctorDualSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Dual a -> Dual b Source#

(<$) :: a -> Dual b -> Dual a Source#

MonadDualSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(>>=) :: Dual a -> (a -> Dual b) -> Dual b Source#

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

return :: a -> Dual a Source#

Data a => Data (Dual a)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstr :: Dual a -> ConstrSource#

dataTypeOf :: Dual a -> DataTypeSource#

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

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

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

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

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

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

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

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

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

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

Monoid a => Monoid (Dual a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Dual a Source#

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

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

Semigroup a => Semigroup (Dual a)Source#

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Dual a -> Dual a -> Dual a Source#

sconcat :: NonEmpty (Dual a) -> Dual a Source#

stimes :: Integral b => b -> Dual a -> Dual a Source#

Bounded a => Bounded (Dual a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Generic (Dual a)Source# 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

typeRep (Dual a) :: Type -> TypeSource#

Methods

from :: Dual a -> Rep (Dual a) x Source#

to :: Rep (Dual a) x -> Dual a Source#

Read a => Read (Dual a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show a => Show (Dual a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Eq a => Eq (Dual a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

(==) :: Dual a -> Dual a -> BoolSource#

(/=) :: Dual a -> Dual a -> BoolSource#

Ord a => Ord (Dual a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Dual a -> Dual a -> OrderingSource#

(<) :: Dual a -> Dual a -> BoolSource#

(<=) :: Dual a -> Dual a -> BoolSource#

(>) :: Dual a -> Dual a -> BoolSource#

(>=) :: Dual a -> Dual a -> BoolSource#

max :: Dual a -> Dual a -> Dual a Source#

min :: Dual a -> Dual a -> Dual a Source#

Generic1DualSource# 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

typeRep1Dual :: k -> TypeSource#

Methods

from1 :: forall (a :: k). Dual a -> Rep1Dual a Source#

to1 :: forall (a :: k). Rep1Dual a -> Dual a Source#

typeRep (Dual a)Source#

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

typeRep (Dual a) = D1 ('MetaData "Dual" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Dual" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDual") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
typeRep1DualSource#

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

typeRep1Dual = D1 ('MetaData "Dual" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Dual" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDual") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

newtypeEndo a Source#

The monoid of endomorphisms under composition.

>>> let computation = Endo ("Hello, " ++) <> Endo (++ "!") >>> appEndo computation "Haskell" "Hello, Haskell!" 

Constructors

Endo 

Fields

Instances

Instances details
Monoid (Endo a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Endo a Source#

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

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

Semigroup (Endo a)Source#

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Endo a -> Endo a -> Endo a Source#

sconcat :: NonEmpty (Endo a) -> Endo a Source#

stimes :: Integral b => b -> Endo a -> Endo a Source#

Generic (Endo a)Source# 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

typeRep (Endo a) :: Type -> TypeSource#

Methods

from :: Endo a -> Rep (Endo a) x Source#

to :: Rep (Endo a) x -> Endo a Source#

typeRep (Endo a)Source#

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

typeRep (Endo a) = D1 ('MetaData "Endo" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Endo" 'PrefixI 'True) (S1 ('MetaSel ('Just "appEndo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a -> a))))

Bool wrappers

newtypeAllSource#

Boolean monoid under conjunction (&&).

>>> getAll (All True <> mempty <> All False) False 
>>> getAll (mconcat (map (\x -> All (even x)) [2,4,6,7,8])) False 

Constructors

All 

Fields

Instances

Instances details
DataAllSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> All -> c AllSource#

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

toConstr :: All -> ConstrSource#

dataTypeOf :: All -> DataTypeSource#

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c All) Source#

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c All) Source#

gmapT :: (forall b. Data b => b -> b) -> All -> AllSource#

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> All -> r Source#

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> All -> r Source#

gmapQ :: (forall d. Data d => d -> u) -> All -> [u] Source#

gmapQi :: Int -> (forall d. Data d => d -> u) -> All -> u Source#

gmapM :: Monad m => (forall d. Data d => d -> m d) -> All -> m AllSource#

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> All -> m AllSource#

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> All -> m AllSource#

MonoidAllSource#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

SemigroupAllSource#

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

BoundedAllSource#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

GenericAllSource# 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

typeRepAll :: Type -> TypeSource#

Methods

from :: All -> RepAll x Source#

to :: RepAll x -> AllSource#

ReadAllSource#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

ShowAllSource#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

EqAllSource#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

(==) :: All -> All -> BoolSource#

(/=) :: All -> All -> BoolSource#

OrdAllSource#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

typeRepAllSource#

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

typeRepAll = D1 ('MetaData "All" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "All" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAll") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0Bool)))

newtypeAnySource#

Boolean monoid under disjunction (||).

>>> getAny (Any True <> mempty <> Any False) True 
>>> getAny (mconcat (map (\x -> Any (even x)) [2,4,6,7,8])) True 

Constructors

Any 

Fields

Instances

Instances details
DataAnySource#

Since: base-4.8.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Any -> c AnySource#

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

toConstr :: Any -> ConstrSource#

dataTypeOf :: Any -> DataTypeSource#

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Any) Source#

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Any) Source#

gmapT :: (forall b. Data b => b -> b) -> Any -> AnySource#

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Any -> r Source#

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Any -> r Source#

gmapQ :: (forall d. Data d => d -> u) -> Any -> [u] Source#

gmapQi :: Int -> (forall d. Data d => d -> u) -> Any -> u Source#

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Any -> m AnySource#

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Any -> m AnySource#

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Any -> m AnySource#

MonoidAnySource#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

SemigroupAnySource#

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

BoundedAnySource#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

GenericAnySource# 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

typeRepAny :: Type -> TypeSource#

Methods

from :: Any -> RepAny x Source#

to :: RepAny x -> AnySource#

ReadAnySource#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

ShowAnySource#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

EqAnySource#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

(==) :: Any -> Any -> BoolSource#

(/=) :: Any -> Any -> BoolSource#

OrdAnySource#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

typeRepAnySource#

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

typeRepAny = D1 ('MetaData "Any" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Any" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAny") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0Bool)))

Num wrappers

newtypeSum a Source#

Monoid under addition.

>>> getSum (Sum 1 <> Sum 2 <> mempty) 3 

Constructors

Sum 

Fields

Instances

Instances details
MonadFixSumSource#

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Sum a) -> Sum a Source#

MonadZipSumSource#

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Zip

Methods

mzip :: Sum a -> Sum b -> Sum (a, b) Source#

mzipWith :: (a -> b -> c) -> Sum a -> Sum b -> Sum c Source#

munzip :: Sum (a, b) -> (Sum a, Sum b) Source#

FoldableSumSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

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 -> BoolSource#

length :: Sum a -> IntSource#

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

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

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

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

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

TraversableSumSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

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

sequenceA :: Applicative f => Sum (f a) -> f (Sum a) Source#

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

sequence :: Monad m => Sum (m a) -> m (Sum a) Source#

ApplicativeSumSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

pure :: a -> Sum a Source#

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

liftA2 :: (a -> b -> c) -> Sum a -> Sum b -> Sum c Source#

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

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

FunctorSumSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Sum a -> Sum b Source#

(<$) :: a -> Sum b -> Sum a Source#

MonadSumSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(>>=) :: Sum a -> (a -> Sum b) -> Sum b Source#

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

return :: a -> Sum a Source#

Data a => Data (Sum a)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstr :: Sum a -> ConstrSource#

dataTypeOf :: Sum a -> DataTypeSource#

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

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

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

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

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

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

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

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

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

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

Num a => Monoid (Sum a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Sum a Source#

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

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

Num a => Semigroup (Sum a)Source#

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Sum a -> Sum a -> Sum a Source#

sconcat :: NonEmpty (Sum a) -> Sum a Source#

stimes :: Integral b => b -> Sum a -> Sum a Source#

Bounded a => Bounded (Sum a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Generic (Sum a)Source# 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

typeRep (Sum a) :: Type -> TypeSource#

Methods

from :: Sum a -> Rep (Sum a) x Source#

to :: Rep (Sum a) x -> Sum a Source#

Num a => Num (Sum a)Source#

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(+) :: Sum a -> Sum a -> Sum a Source#

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

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

negate :: Sum a -> Sum a Source#

abs :: Sum a -> Sum a Source#

signum :: Sum a -> Sum a Source#

fromInteger :: Integer -> Sum a Source#

Read a => Read (Sum a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show a => Show (Sum a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Eq a => Eq (Sum a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

(==) :: Sum a -> Sum a -> BoolSource#

(/=) :: Sum a -> Sum a -> BoolSource#

Ord a => Ord (Sum a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Sum a -> Sum a -> OrderingSource#

(<) :: Sum a -> Sum a -> BoolSource#

(<=) :: Sum a -> Sum a -> BoolSource#

(>) :: Sum a -> Sum a -> BoolSource#

(>=) :: Sum a -> Sum a -> BoolSource#

max :: Sum a -> Sum a -> Sum a Source#

min :: Sum a -> Sum a -> Sum a Source#

Generic1SumSource# 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

typeRep1Sum :: k -> TypeSource#

Methods

from1 :: forall (a :: k). Sum a -> Rep1Sum a Source#

to1 :: forall (a :: k). Rep1Sum a -> Sum a Source#

typeRep (Sum a)Source#

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

typeRep (Sum a) = D1 ('MetaData "Sum" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Sum" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
typeRep1SumSource#

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

typeRep1Sum = D1 ('MetaData "Sum" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Sum" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

newtypeProduct a Source#

Monoid under multiplication.

>>> getProduct (Product 3 <> Product 4 <> mempty) 12 

Constructors

Product 

Fields

Instances

Instances details
MonadFixProductSource#

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Product a) -> Product a Source#

MonadZipProductSource#

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Zip

Methods

mzip :: Product a -> Product b -> Product (a, b) Source#

mzipWith :: (a -> b -> c) -> Product a -> Product b -> Product c Source#

munzip :: Product (a, b) -> (Product a, Product b) Source#

FoldableProductSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

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 -> BoolSource#

length :: Product a -> IntSource#

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

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

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

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

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

TraversableProductSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

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

sequenceA :: Applicative f => Product (f a) -> f (Product a) Source#

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

sequence :: Monad m => Product (m a) -> m (Product a) Source#

ApplicativeProductSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

pure :: a -> Product a Source#

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

liftA2 :: (a -> b -> c) -> Product a -> Product b -> Product c Source#

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

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

FunctorProductSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Product a -> Product b Source#

(<$) :: a -> Product b -> Product a Source#

MonadProductSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(>>=) :: Product a -> (a -> Product b) -> Product b Source#

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

return :: a -> Product a Source#

Data a => Data (Product a)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstr :: Product a -> ConstrSource#

dataTypeOf :: Product a -> DataTypeSource#

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

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

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

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

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

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

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

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

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

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

Num a => Monoid (Product a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Num a => Semigroup (Product a)Source#

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Bounded a => Bounded (Product a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Generic (Product a)Source# 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

typeRep (Product a) :: Type -> TypeSource#

Methods

from :: Product a -> Rep (Product a) x Source#

to :: Rep (Product a) x -> Product a Source#

Num a => Num (Product a)Source#

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Read a => Read (Product a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show a => Show (Product a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Eq a => Eq (Product a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

(==) :: Product a -> Product a -> BoolSource#

(/=) :: Product a -> Product a -> BoolSource#

Ord a => Ord (Product a)Source#

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Generic1ProductSource# 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

typeRep1Product :: k -> TypeSource#

Methods

from1 :: forall (a :: k). Product a -> Rep1Product a Source#

to1 :: forall (a :: k). Rep1Product a -> Product a Source#

typeRep (Product a)Source#

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

typeRep (Product a) = D1 ('MetaData "Product" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Product" 'PrefixI 'True) (S1 ('MetaSel ('Just "getProduct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
typeRep1ProductSource#

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

typeRep1Product = D1 ('MetaData "Product" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Product" 'PrefixI 'True) (S1 ('MetaSel ('Just "getProduct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Maybe wrappers

To implement find or findLast on any Foldable:

findLast :: Foldable t => (a -> Bool) -> t a -> Maybe a findLast pred = getLast . foldMap (x -> if pred x then Last (Just x) else Last Nothing) 

Much of Maps interface can be implemented with alter. Some of the rest can be implemented with a new alterF function and either First or Last:

alterF :: (Functor f, Ord k) => (Maybe a -> f (Maybe a)) -> k -> Map k a -> f (Map k a) instance Monoid a => Functor ((,) a) -- from Data.Functor
insertLookupWithKey :: Ord k => (k -> v -> v -> v) -> k -> v -> Map k v -> (Maybe v, Map k v) insertLookupWithKey combine key value = Arrow.first getFirst . alterF doChange key where doChange Nothing = (First Nothing, Just value) doChange (Just oldValue) = (First (Just oldValue), Just (combine key value oldValue)) 

newtypeFirst a Source#

Maybe monoid returning the leftmost non-Nothing value.

First a is isomorphic to AltMaybe a, but precedes it historically.

>>> getFirst (First (Just "hello") <> First Nothing <> First (Just "world")) Just "hello" 

Constructors

First 

Fields

Instances

Instances details
MonadFixFirstSource#

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> First a) -> First a Source#

MonadZipFirstSource#

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Zip

Methods

mzip :: First a -> First b -> First (a, b) Source#

mzipWith :: (a -> b -> c) -> First a -> First b -> First c Source#

munzip :: First (a, b) -> (First a, First b) Source#

FoldableFirstSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

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 -> BoolSource#

length :: First a -> IntSource#

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

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

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

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

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

TraversableFirstSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

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

sequenceA :: Applicative f => First (f a) -> f (First a) Source#

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

sequence :: Monad m => First (m a) -> m (First a) Source#

ApplicativeFirstSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Methods

pure :: a -> First a Source#

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

liftA2 :: (a -> b -> c) -> First a -> First b -> First c Source#

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

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

FunctorFirstSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Methods

fmap :: (a -> b) -> First a -> First b Source#

(<$) :: a -> First b -> First a Source#

MonadFirstSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Methods

(>>=) :: First a -> (a -> First b) -> First b Source#

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

return :: a -> First a Source#

Data a => Data (First a)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstr :: First a -> ConstrSource#

dataTypeOf :: First a -> DataTypeSource#

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

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

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

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

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

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

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

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

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

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

Monoid (First a)Source#

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: First a Source#

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

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

Semigroup (First a)Source#

Since: base-4.9.0.0

Instance details

Defined in Data.Monoid

Methods

(<>) :: First a -> First a -> First a Source#

sconcat :: NonEmpty (First a) -> First a Source#

stimes :: Integral b => b -> First a -> First a Source#

Generic (First a)Source# 
Instance details

Defined in Data.Monoid

Associated Types

typeRep (First a) :: Type -> TypeSource#

Methods

from :: First a -> Rep (First a) x Source#

to :: Rep (First a) x -> First a Source#

Read a => Read (First a)Source#

Since: base-2.1

Instance details

Defined in Data.Monoid

Show a => Show (First a)Source#

Since: base-2.1

Instance details

Defined in Data.Monoid

Eq a => Eq (First a)Source#

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

(==) :: First a -> First a -> BoolSource#

(/=) :: First a -> First a -> BoolSource#

Ord a => Ord (First a)Source#

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

compare :: First a -> First a -> OrderingSource#

(<) :: First a -> First a -> BoolSource#

(<=) :: First a -> First a -> BoolSource#

(>) :: First a -> First a -> BoolSource#

(>=) :: First a -> First a -> BoolSource#

max :: First a -> First a -> First a Source#

min :: First a -> First a -> First a Source#

Generic1FirstSource# 
Instance details

Defined in Data.Monoid

Associated Types

typeRep1First :: k -> TypeSource#

Methods

from1 :: forall (a :: k). First a -> Rep1First a Source#

to1 :: forall (a :: k). Rep1First a -> First a Source#

typeRep (First a)Source#

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

typeRep (First a) = D1 ('MetaData "First" "Data.Monoid" "base" 'True) (C1 ('MetaCons "First" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFirst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a))))
typeRep1FirstSource#

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

typeRep1First = D1 ('MetaData "First" "Data.Monoid" "base" 'True) (C1 ('MetaCons "First" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFirst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1Maybe)))

newtypeLast a Source#

Maybe monoid returning the rightmost non-Nothing value.

Last a is isomorphic to Dual (First a), and thus to Dual (AltMaybe a)

>>> getLast (Last (Just "hello") <> Last Nothing <> Last (Just "world")) Just "world" 

Constructors

Last 

Fields

Instances

Instances details
MonadFixLastSource#

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Last a) -> Last a Source#

MonadZipLastSource#

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Zip

Methods

mzip :: Last a -> Last b -> Last (a, b) Source#

mzipWith :: (a -> b -> c) -> Last a -> Last b -> Last c Source#

munzip :: Last (a, b) -> (Last a, Last b) Source#

FoldableLastSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

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 -> BoolSource#

length :: Last a -> IntSource#

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

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

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

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

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

TraversableLastSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

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

sequenceA :: Applicative f => Last (f a) -> f (Last a) Source#

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

sequence :: Monad m => Last (m a) -> m (Last a) Source#

ApplicativeLastSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Methods

pure :: a -> Last a Source#

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

liftA2 :: (a -> b -> c) -> Last a -> Last b -> Last c Source#

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

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

FunctorLastSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Methods

fmap :: (a -> b) -> Last a -> Last b Source#

(<$) :: a -> Last b -> Last a Source#

MonadLastSource#

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Methods

(>>=) :: Last a -> (a -> Last b) -> Last b Source#

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

return :: a -> Last a Source#

Data a => Data (Last a)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstr :: Last a -> ConstrSource#

dataTypeOf :: Last a -> DataTypeSource#

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

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

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

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

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

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

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

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

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

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

Monoid (Last a)Source#

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: Last a Source#

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

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

Semigroup (Last a)Source#

Since: base-4.9.0.0

Instance details

Defined in Data.Monoid

Methods

(<>) :: Last a -> Last a -> Last a Source#

sconcat :: NonEmpty (Last a) -> Last a Source#

stimes :: Integral b => b -> Last a -> Last a Source#

Generic (Last a)Source# 
Instance details

Defined in Data.Monoid

Associated Types

typeRep (Last a) :: Type -> TypeSource#

Methods

from :: Last a -> Rep (Last a) x Source#

to :: Rep (Last a) x -> Last a Source#

Read a => Read (Last a)Source#

Since: base-2.1

Instance details

Defined in Data.Monoid

Show a => Show (Last a)Source#

Since: base-2.1

Instance details

Defined in Data.Monoid

Eq a => Eq (Last a)Source#

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

(==) :: Last a -> Last a -> BoolSource#

(/=) :: Last a -> Last a -> BoolSource#

Ord a => Ord (Last a)Source#

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

compare :: Last a -> Last a -> OrderingSource#

(<) :: Last a -> Last a -> BoolSource#

(<=) :: Last a -> Last a -> BoolSource#

(>) :: Last a -> Last a -> BoolSource#

(>=) :: Last a -> Last a -> BoolSource#

max :: Last a -> Last a -> Last a Source#

min :: Last a -> Last a -> Last a Source#

Generic1LastSource# 
Instance details

Defined in Data.Monoid

Associated Types

typeRep1Last :: k -> TypeSource#

Methods

from1 :: forall (a :: k). Last a -> Rep1Last a Source#

to1 :: forall (a :: k). Rep1Last a -> Last a Source#

typeRep (Last a)Source#

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

typeRep (Last a) = D1 ('MetaData "Last" "Data.Monoid" "base" 'True) (C1 ('MetaCons "Last" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLast") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a))))
typeRep1LastSource#

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

typeRep1Last = D1 ('MetaData "Last" "Data.Monoid" "base" 'True) (C1 ('MetaCons "Last" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLast") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1Maybe)))

Alternative wrapper

newtypeAlt f a Source#

Monoid under <|>.

>>> getAlt (Alt (Just 12) <> Alt (Just 24)) Just 12 
>>> getAlt $ Alt Nothing <> Alt (Just 24) Just 24 

Since: base-4.8.0.0

Constructors

Alt 

Fields

Instances

Instances details
Generic1 (Alt f :: k -> Type)Source# 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

typeRep1 (Alt f) :: k -> TypeSource#

Methods

from1 :: forall (a :: k0). Alt f a -> Rep1 (Alt f) a Source#

to1 :: forall (a :: k0). Rep1 (Alt f) a -> Alt f a Source#

MonadFix f => MonadFix (Alt f)Source#

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Alt f a) -> Alt f a Source#

MonadZip f => MonadZip (Alt f)Source#

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Zip

Methods

mzip :: Alt f a -> Alt f b -> Alt f (a, b) Source#

mzipWith :: (a -> b -> c) -> Alt f a -> Alt f b -> Alt f c Source#

munzip :: Alt f (a, b) -> (Alt f a, Alt f b) Source#

Foldable f => Foldable (Alt f)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Foldable

Methods

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 -> BoolSource#

length :: Alt f a -> IntSource#

elem :: Eq a => a -> Alt f a -> BoolSource#

maximum :: Ord a => Alt f a -> a Source#

minimum :: Ord a => Alt f a -> a Source#

sum :: Num a => Alt f a -> a Source#

product :: Num a => Alt f a -> a Source#

Contravariant f => Contravariant (Alt f)Source# 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Alt f a -> Alt f a' Source#

(>$) :: b -> Alt f b -> Alt f a Source#

Traversable f => Traversable (Alt f)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Alt f a -> f0 (Alt f b) Source#

sequenceA :: Applicative f0 => Alt f (f0 a) -> f0 (Alt f a) Source#

mapM :: Monad m => (a -> m b) -> Alt f a -> m (Alt f b) Source#

sequence :: Monad m => Alt f (m a) -> m (Alt f a) Source#

Alternative f => Alternative (Alt f)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

empty :: Alt f a Source#

(<|>) :: Alt f a -> Alt f a -> Alt f a Source#

some :: Alt f a -> Alt f [a] Source#

many :: Alt f a -> Alt f [a] Source#

Applicative f => Applicative (Alt f)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

pure :: a -> Alt f a Source#

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

liftA2 :: (a -> b -> c) -> Alt f a -> Alt f b -> Alt f c Source#

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

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

Functor f => Functor (Alt f)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Alt f a -> Alt f b Source#

(<$) :: a -> Alt f b -> Alt f a Source#

Monad f => Monad (Alt f)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(>>=) :: Alt f a -> (a -> Alt f b) -> Alt f b Source#

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

return :: a -> Alt f a Source#

MonadPlus f => MonadPlus (Alt f)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

mzero :: Alt f a Source#

mplus :: Alt f a -> Alt f a -> Alt f a Source#

(Data (f a), Data a, Typeable f) => Data (Alt f a)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstr :: Alt f a -> ConstrSource#

dataTypeOf :: Alt f a -> DataTypeSource#

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Alt f a)) Source#

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Alt f a)) Source#

gmapT :: (forall b. Data b => b -> b) -> Alt f a -> Alt f a Source#

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Alt f a -> r Source#

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Alt f a -> r Source#

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> Alt f a -> u Source#

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source#

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source#

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Alt f a -> m (Alt f a) Source#

Alternative f => Monoid (Alt f a)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Alt f a Source#

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

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

Alternative f => Semigroup (Alt f a)Source#

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Alt f a -> Alt f a -> Alt f a Source#

sconcat :: NonEmpty (Alt f a) -> Alt f a Source#

stimes :: Integral b => b -> Alt f a -> Alt f a Source#

Enum (f a) => Enum (Alt f a)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

succ :: Alt f a -> Alt f a Source#

pred :: Alt f a -> Alt f a Source#

toEnum :: Int -> Alt f a Source#

fromEnum :: Alt f a -> IntSource#

enumFrom :: Alt f a -> [Alt f a] Source#

enumFromThen :: Alt f a -> Alt f a -> [Alt f a] Source#

enumFromTo :: Alt f a -> Alt f a -> [Alt f a] Source#

enumFromThenTo :: Alt f a -> Alt f a -> Alt f a -> [Alt f a] Source#

Generic (Alt f a)Source# 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

typeRep (Alt f a) :: Type -> TypeSource#

Methods

from :: Alt f a -> Rep (Alt f a) x Source#

to :: Rep (Alt f a) x -> Alt f a Source#

Num (f a) => Num (Alt f a)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(+) :: Alt f a -> Alt f a -> Alt f a Source#

(-) :: Alt f a -> Alt f a -> Alt f a Source#

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

negate :: Alt f a -> Alt f a Source#

abs :: Alt f a -> Alt f a Source#

signum :: Alt f a -> Alt f a Source#

fromInteger :: Integer -> Alt f a Source#

Read (f a) => Read (Alt f a)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Show (f a) => Show (Alt f a)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Alt f a -> ShowSSource#

show :: Alt f a -> StringSource#

showList :: [Alt f a] -> ShowSSource#

Eq (f a) => Eq (Alt f a)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(==) :: Alt f a -> Alt f a -> BoolSource#

(/=) :: Alt f a -> Alt f a -> BoolSource#

Ord (f a) => Ord (Alt f a)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Alt f a -> Alt f a -> OrderingSource#

(<) :: Alt f a -> Alt f a -> BoolSource#

(<=) :: Alt f a -> Alt f a -> BoolSource#

(>) :: Alt f a -> Alt f a -> BoolSource#

(>=) :: Alt f a -> Alt f a -> BoolSource#

max :: Alt f a -> Alt f a -> Alt f a Source#

min :: Alt f a -> Alt f a -> Alt f a Source#

typeRep1 (Alt f :: k -> Type)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

typeRep1 (Alt f :: k -> Type) = D1 ('MetaData "Alt" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Alt" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAlt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 f)))
typeRep (Alt f a)Source#

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

typeRep (Alt f a) = D1 ('MetaData "Alt" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Alt" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAlt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a))))

Applicative wrapper

newtypeAp f a Source#

This data type witnesses the lifting of a Monoid into an Applicative pointwise.

Since: base-4.12.0.0

Constructors

Ap 

Fields

Instances

Instances details
Generic1 (Ap f :: k -> Type)Source# 
Instance details

Defined in Data.Monoid

Associated Types

typeRep1 (Ap f) :: k -> TypeSource#

Methods

from1 :: forall (a :: k0). Ap f a -> Rep1 (Ap f) a Source#

to1 :: forall (a :: k0). Rep1 (Ap f) a -> Ap f a Source#

MonadFail f => MonadFail (Ap f)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

fail :: String -> Ap f a Source#

MonadFix f => MonadFix (Ap f)Source#

Since: base-4.12.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Ap f a) -> Ap f a Source#

Foldable f => Foldable (Ap f)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Foldable

Methods

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 -> BoolSource#

length :: Ap f a -> IntSource#

elem :: Eq a => a -> Ap f a -> BoolSource#

maximum :: Ord a => Ap f a -> a Source#

minimum :: Ord a => Ap f a -> a Source#

sum :: Num a => Ap f a -> a Source#

product :: Num a => Ap f a -> a Source#

Traversable f => Traversable (Ap f)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Ap f a -> f0 (Ap f b) Source#

sequenceA :: Applicative f0 => Ap f (f0 a) -> f0 (Ap f a) Source#

mapM :: Monad m => (a -> m b) -> Ap f a -> m (Ap f b) Source#

sequence :: Monad m => Ap f (m a) -> m (Ap f a) Source#

Alternative f => Alternative (Ap f)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

empty :: Ap f a Source#

(<|>) :: Ap f a -> Ap f a -> Ap f a Source#

some :: Ap f a -> Ap f [a] Source#

many :: Ap f a -> Ap f [a] Source#

Applicative f => Applicative (Ap f)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

pure :: a -> Ap f a Source#

(<*>) :: Ap f (a -> b) -> Ap f a -> Ap f b Source#

liftA2 :: (a -> b -> c) -> Ap f a -> Ap f b -> Ap f c Source#

(*>) :: Ap f a -> Ap f b -> Ap f b Source#

(<*) :: Ap f a -> Ap f b -> Ap f a Source#

Functor f => Functor (Ap f)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

fmap :: (a -> b) -> Ap f a -> Ap f b Source#

(<$) :: a -> Ap f b -> Ap f a Source#

Monad f => Monad (Ap f)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

(>>=) :: Ap f a -> (a -> Ap f b) -> Ap f b Source#

(>>) :: Ap f a -> Ap f b -> Ap f b Source#

return :: a -> Ap f a Source#

MonadPlus f => MonadPlus (Ap f)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

mzero :: Ap f a Source#

mplus :: Ap f a -> Ap f a -> Ap f a Source#

(Data (f a), Data a, Typeable f) => Data (Ap f a)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstr :: Ap f a -> ConstrSource#

dataTypeOf :: Ap f a -> DataTypeSource#

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ap f a)) Source#

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ap f a)) Source#

gmapT :: (forall b. Data b => b -> b) -> Ap f a -> Ap f a Source#

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ap f a -> r Source#

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ap f a -> r Source#

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ap f a -> u Source#

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) Source#

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) Source#

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ap f a -> m (Ap f a) Source#

(Applicative f, Monoid a) => Monoid (Ap f a)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

mempty :: Ap f a Source#

mappend :: Ap f a -> Ap f a -> Ap f a Source#

mconcat :: [Ap f a] -> Ap f a Source#

(Applicative f, Semigroup a) => Semigroup (Ap f a)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

(<>) :: Ap f a -> Ap f a -> Ap f a Source#

sconcat :: NonEmpty (Ap f a) -> Ap f a Source#

stimes :: Integral b => b -> Ap f a -> Ap f a Source#

(Applicative f, Bounded a) => Bounded (Ap f a)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

minBound :: Ap f a Source#

maxBound :: Ap f a Source#

Enum (f a) => Enum (Ap f a)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

succ :: Ap f a -> Ap f a Source#

pred :: Ap f a -> Ap f a Source#

toEnum :: Int -> Ap f a Source#

fromEnum :: Ap f a -> IntSource#

enumFrom :: Ap f a -> [Ap f a] Source#

enumFromThen :: Ap f a -> Ap f a -> [Ap f a] Source#

enumFromTo :: Ap f a -> Ap f a -> [Ap f a] Source#

enumFromThenTo :: Ap f a -> Ap f a -> Ap f a -> [Ap f a] Source#

Generic (Ap f a)Source# 
Instance details

Defined in Data.Monoid

Associated Types

typeRep (Ap f a) :: Type -> TypeSource#

Methods

from :: Ap f a -> Rep (Ap f a) x Source#

to :: Rep (Ap f a) x -> Ap f a Source#

(Applicative f, Num a) => Num (Ap f a)Source#

Note that even if the underlying Num and Applicative instances are lawful, for most Applicatives, this instance will not be lawful. If you use this instance with the list Applicative, the following customary laws will not hold:

Commutativity:

>>> Ap [10,20] + Ap [1,2] Ap {getAp = [11,12,21,22]} >>> Ap [1,2] + Ap [10,20] Ap {getAp = [11,21,12,22]} 

Additive inverse:

>>> Ap [] + negate (Ap []) Ap {getAp = []} >>> fromInteger 0 :: Ap [] Int Ap {getAp = [0]} 

Distributivity:

>>> Ap [1,2] * (3 + 4) Ap {getAp = [7,14]} >>> (Ap [1,2] * 3) + (Ap [1,2] * 4) Ap {getAp = [7,11,10,14]} 

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

(+) :: Ap f a -> Ap f a -> Ap f a Source#

(-) :: Ap f a -> Ap f a -> Ap f a Source#

(*) :: Ap f a -> Ap f a -> Ap f a Source#

negate :: Ap f a -> Ap f a Source#

abs :: Ap f a -> Ap f a Source#

signum :: Ap f a -> Ap f a Source#

fromInteger :: Integer -> Ap f a Source#

Read (f a) => Read (Ap f a)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Show (f a) => Show (Ap f a)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

showsPrec :: Int -> Ap f a -> ShowSSource#

show :: Ap f a -> StringSource#

showList :: [Ap f a] -> ShowSSource#

Eq (f a) => Eq (Ap f a)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

(==) :: Ap f a -> Ap f a -> BoolSource#

(/=) :: Ap f a -> Ap f a -> BoolSource#

Ord (f a) => Ord (Ap f a)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

compare :: Ap f a -> Ap f a -> OrderingSource#

(<) :: Ap f a -> Ap f a -> BoolSource#

(<=) :: Ap f a -> Ap f a -> BoolSource#

(>) :: Ap f a -> Ap f a -> BoolSource#

(>=) :: Ap f a -> Ap f a -> BoolSource#

max :: Ap f a -> Ap f a -> Ap f a Source#

min :: Ap f a -> Ap f a -> Ap f a Source#

typeRep1 (Ap f :: k -> Type)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

typeRep1 (Ap f :: k -> Type) = D1 ('MetaData "Ap" "Data.Monoid" "base" 'True) (C1 ('MetaCons "Ap" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 f)))
typeRep (Ap f a)Source#

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

typeRep (Ap f a) = D1 ('MetaData "Ap" "Data.Monoid" "base" 'True) (C1 ('MetaCons "Ap" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a))))
close