Copyright | (c) Andy Gill 2001 (c) Oregon Graduate Institute of Science and Technology 2001 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | experimental |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
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
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
- classSemigroup a => Monoid a where
- (<>) :: Semigroup a => a -> a -> a
- newtypeDual a = Dual {
- getDual :: a
- newtypeEndo a = Endo {
- appEndo :: a -> a
- newtypeAll = All {}
- newtypeAny = Any {}
- newtypeSum a = Sum {
- getSum :: a
- newtypeProduct a = Product {
- getProduct :: a
- newtypeFirst a = First {}
- newtypeLast a = Last {}
- newtypeAlt f a = Alt {
- getAlt :: f a
- newtypeAp f a = Ap {
- getAp :: f a
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)<>
zSemigroup
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 newtype
s 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
Methods
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
since base-4.11.0.0. Should it be implemented manually, since mappend
= (<>
)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
.
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
MonoidAllSource# | Since: base-2.1 |
MonoidAnySource# | Since: base-2.1 |
MonoidEventSource# | Since: base-4.4.0.0 |
MonoidLifetimeSource# |
Since: base-4.8.0.0 |
MonoidOrderingSource# | Since: base-2.1 |
Monoid ()Source# | Since: base-2.1 |
FiniteBits a => Monoid (And a)Source# | This constraint is arguably too strong. However, as some types (such as Since: base-4.16 |
FiniteBits a => Monoid (Iff a)Source# | This constraint is arguably too strong. However, as some types (such as Since: base-4.16 |
Bits a => Monoid (Ior a)Source# | Since: base-4.16 |
Bits a => Monoid (Xor a)Source# | Since: base-4.16 |
Monoid (Comparison a)Source# |
mempty :: Comparison a mempty = Comparison _ _ -> EQ |
Defined in Data.Functor.Contravariant Methods mempty :: Comparison a Source# mappend :: Comparison a -> Comparison a -> Comparison a Source# mconcat :: [Comparison a] -> Comparison a Source# | |
Monoid (Equivalence a)Source# |
mempty :: Equivalence a mempty = Equivalence _ _ -> True |
Defined in Data.Functor.Contravariant Methods mempty :: Equivalence a Source# mappend :: Equivalence a -> Equivalence a -> Equivalence a Source# mconcat :: [Equivalence a] -> Equivalence a Source# | |
Monoid (Predicate a)Source# |
mempty :: Predicate a mempty = _ -> True |
Monoid a => Monoid (Identity a)Source# | Since: base-4.9.0.0 |
Monoid (First a)Source# | Since: base-2.1 |
Monoid (Last a)Source# | Since: base-2.1 |
Monoid a => Monoid (Down a)Source# | Since: base-4.11.0.0 |
(Ord a, Bounded a) => Monoid (Max a)Source# | Since: base-4.9.0.0 |
(Ord a, Bounded a) => Monoid (Min a)Source# | Since: base-4.9.0.0 |
Monoid m => Monoid (WrappedMonoid m)Source# | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods mempty :: WrappedMonoid m Source# mappend :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m Source# mconcat :: [WrappedMonoid m] -> WrappedMonoid m Source# | |
Monoid a => Monoid (Dual a)Source# | Since: base-2.1 |
Monoid (Endo a)Source# | Since: base-2.1 |
Num a => Monoid (Product a)Source# | Since: base-2.1 |
Num a => Monoid (Sum a)Source# | Since: base-2.1 |
Monoid p => Monoid (Par1 p)Source# | Since: base-4.12.0.0 |
Monoid a => Monoid (IO a)Source# | Since: base-4.9.0.0 |
Semigroup a => Monoid (Maybe a)Source# | Lift a semigroup into Since 4.11.0: constraint on inner Since: base-2.1 |
Monoid a => Monoid (a)Source# | Since: base-4.15 |
Monoid [a]Source# | Since: base-2.1 |
Monoid a => Monoid (Op a b)Source# |
mempty :: Op a b mempty = Op _ -> mempty |
Monoid (Proxy s)Source# | Since: base-4.7.0.0 |
Monoid (U1 p)Source# | Since: base-4.12.0.0 |
Monoid a => Monoid (ST s a)Source# | Since: base-4.11.0.0 |
Monoid b => Monoid (a -> b)Source# | Since: base-2.1 |
(Monoid a, Monoid b) => Monoid (a, b)Source# | Since: base-2.1 |
Monoid a => Monoid (Const a b)Source# | Since: base-4.9.0.0 |
(Applicative f, Monoid a) => Monoid (Ap f a)Source# | Since: base-4.12.0.0 |
Alternative f => Monoid (Alt f a)Source# | Since: base-4.8.0.0 |
Monoid (f p) => Monoid (Rec1 f p)Source# | Since: base-4.12.0.0 |
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c)Source# | Since: base-2.1 |
(Monoid (f a), Monoid (g a)) => Monoid (Product f g a)Source# | Since: base-4.16.0.0 |
(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p)Source# | Since: base-4.12.0.0 |
Monoid c => Monoid (K1 i c p)Source# | Since: base-4.12.0.0 |
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d)Source# | Since: base-2.1 |
Monoid (f (g a)) => Monoid (Compose f g a)Source# | Since: base-4.16.0.0 |
Monoid (f (g p)) => Monoid ((f :.: g) p)Source# | Since: base-4.12.0.0 |
Monoid (f p) => Monoid (M1 i c f p)Source# | Since: base-4.12.0.0 |
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e)Source# | Since: base-2.1 |
(<>) :: Semigroup a => a -> a -> a infixr 6Source#
An associative operation.
>>>
[1,2,3] <> [4,5,6]
[1,2,3,4,5,6]
The dual of a Monoid
, obtained by swapping the arguments of mappend
.
>>>
getDual (mappend (Dual "Hello") (Dual "World"))
"WorldHello"
Instances
MonadFixDualSource# | Since: base-4.8.0.0 |
MonadZipDualSource# | Since: base-4.8.0.0 |
FoldableDualSource# | Since: base-4.8.0.0 |
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# 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# | |
TraversableDualSource# | Since: base-4.8.0.0 |
ApplicativeDualSource# | Since: base-4.8.0.0 |
FunctorDualSource# | Since: base-4.8.0.0 |
MonadDualSource# | Since: base-4.8.0.0 |
Data a => Data (Dual a)Source# | Since: base-4.8.0.0 |
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 |
Semigroup a => Semigroup (Dual a)Source# | Since: base-4.9.0.0 |
Bounded a => Bounded (Dual a)Source# | Since: base-2.1 |
Generic (Dual a)Source# | |
Read a => Read (Dual a)Source# | Since: base-2.1 |
Show a => Show (Dual a)Source# | Since: base-2.1 |
Eq a => Eq (Dual a)Source# | Since: base-2.1 |
Ord a => Ord (Dual a)Source# | Since: base-2.1 |
Defined in Data.Semigroup.Internal | |
Generic1DualSource# | |
typeRep (Dual a)Source# | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
typeRep1DualSource# | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal |
The monoid of endomorphisms under composition.
>>>
let computation = Endo ("Hello, " ++) <> Endo (++ "!")
>>>
appEndo computation "Haskell"
"Hello, Haskell!"
Bool
wrappers
Boolean monoid under conjunction (&&
).
>>>
getAll (All True <> mempty <> All False)
False
>>>
getAll (mconcat (map (\x -> All (even x)) [2,4,6,7,8]))
False
Instances
DataAllSource# | Since: base-4.8.0.0 |
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 |
SemigroupAllSource# | Since: base-4.9.0.0 |
BoundedAllSource# | Since: base-2.1 |
GenericAllSource# | |
ReadAllSource# | Since: base-2.1 |
ShowAllSource# | Since: base-2.1 |
EqAllSource# | Since: base-2.1 |
OrdAllSource# | Since: base-2.1 |
typeRepAllSource# | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal |
Boolean monoid under disjunction (||
).
>>>
getAny (Any True <> mempty <> Any False)
True
>>>
getAny (mconcat (map (\x -> Any (even x)) [2,4,6,7,8]))
True
Instances
DataAnySource# | Since: base-4.8.0.0 |
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 |
SemigroupAnySource# | Since: base-4.9.0.0 |
BoundedAnySource# | Since: base-2.1 |
GenericAnySource# | |
ReadAnySource# | Since: base-2.1 |
ShowAnySource# | Since: base-2.1 |
EqAnySource# | Since: base-2.1 |
OrdAnySource# | Since: base-2.1 |
typeRepAnySource# | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal |
Num
wrappers
Monoid under addition.
>>>
getSum (Sum 1 <> Sum 2 <> mempty)
3
Instances
MonadFixSumSource# | Since: base-4.8.0.0 |
MonadZipSumSource# | Since: base-4.8.0.0 |
FoldableSumSource# | Since: base-4.8.0.0 |
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# elem :: Eq a => a -> Sum a -> BoolSource# maximum :: Ord a => Sum a -> a Source# minimum :: Ord a => Sum a -> a Source# | |
TraversableSumSource# | Since: base-4.8.0.0 |
ApplicativeSumSource# | Since: base-4.8.0.0 |
FunctorSumSource# | Since: base-4.8.0.0 |
MonadSumSource# | Since: base-4.8.0.0 |
Data a => Data (Sum a)Source# | Since: base-4.8.0.0 |
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 |
Num a => Semigroup (Sum a)Source# | Since: base-4.9.0.0 |
Bounded a => Bounded (Sum a)Source# | Since: base-2.1 |
Generic (Sum a)Source# | |
Num a => Num (Sum a)Source# | Since: base-4.7.0.0 |
Read a => Read (Sum a)Source# | Since: base-2.1 |
Show a => Show (Sum a)Source# | Since: base-2.1 |
Eq a => Eq (Sum a)Source# | Since: base-2.1 |
Ord a => Ord (Sum a)Source# | Since: base-2.1 |
Defined in Data.Semigroup.Internal | |
Generic1SumSource# | |
typeRep (Sum a)Source# | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
typeRep1SumSource# | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal |
Monoid under multiplication.
>>>
getProduct (Product 3 <> Product 4 <> mempty)
12
Constructors
Product | |
Fields
|
Instances
MonadFixProductSource# | Since: base-4.8.0.0 |
MonadZipProductSource# | Since: base-4.8.0.0 |
FoldableProductSource# | Since: base-4.8.0.0 |
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# | |
TraversableProductSource# | Since: base-4.8.0.0 |
Defined in Data.Traversable | |
ApplicativeProductSource# | Since: base-4.8.0.0 |
Defined in Data.Semigroup.Internal | |
FunctorProductSource# | Since: base-4.8.0.0 |
MonadProductSource# | Since: base-4.8.0.0 |
Data a => Data (Product a)Source# | Since: base-4.8.0.0 |
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 |
Num a => Semigroup (Product a)Source# | Since: base-4.9.0.0 |
Bounded a => Bounded (Product a)Source# | Since: base-2.1 |
Generic (Product a)Source# | |
Num a => Num (Product a)Source# | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal Methods (+) :: Product a -> Product a -> Product a Source# (-) :: Product a -> Product a -> Product a Source# (*) :: Product a -> Product a -> Product a Source# negate :: Product a -> Product a Source# abs :: Product a -> Product a Source# signum :: Product a -> Product a Source# fromInteger :: Integer -> Product a Source# | |
Read a => Read (Product a)Source# | Since: base-2.1 |
Show a => Show (Product a)Source# | Since: base-2.1 |
Eq a => Eq (Product a)Source# | Since: base-2.1 |
Ord a => Ord (Product a)Source# | Since: base-2.1 |
Defined in Data.Semigroup.Internal | |
Generic1ProductSource# | |
typeRep (Product a)Source# | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal | |
typeRep1ProductSource# | Since: base-4.7.0.0 |
Defined in Data.Semigroup.Internal |
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 Map
s 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))
Maybe monoid returning the leftmost non-Nothing value.
is isomorphic to First
a
, but precedes it historically.Alt
Maybe
a
>>>
getFirst (First (Just "hello") <> First Nothing <> First (Just "world"))
Just "hello"
Instances
MonadFixFirstSource# | Since: base-4.8.0.0 |
MonadZipFirstSource# | Since: base-4.8.0.0 |
FoldableFirstSource# | Since: base-4.8.0.0 |
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# | |
TraversableFirstSource# | Since: base-4.8.0.0 |
ApplicativeFirstSource# | Since: base-4.8.0.0 |
FunctorFirstSource# | Since: base-4.8.0.0 |
MonadFirstSource# | Since: base-4.8.0.0 |
Data a => Data (First a)Source# | Since: base-4.8.0.0 |
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 |
Semigroup (First a)Source# | Since: base-4.9.0.0 |
Generic (First a)Source# | |
Read a => Read (First a)Source# | Since: base-2.1 |
Show a => Show (First a)Source# | Since: base-2.1 |
Eq a => Eq (First a)Source# | Since: base-2.1 |
Ord a => Ord (First a)Source# | Since: base-2.1 |
Generic1FirstSource# | |
typeRep (First a)Source# | Since: base-4.7.0.0 |
Defined in Data.Monoid | |
typeRep1FirstSource# | Since: base-4.7.0.0 |
Defined in Data.Monoid |
Maybe monoid returning the rightmost non-Nothing value.
is isomorphic to Last
a
, and thus to Dual
(First
a)Dual
(Alt
Maybe
a)
>>>
getLast (Last (Just "hello") <> Last Nothing <> Last (Just "world"))
Just "world"
Instances
MonadFixLastSource# | Since: base-4.8.0.0 |
MonadZipLastSource# | Since: base-4.8.0.0 |
FoldableLastSource# | Since: base-4.8.0.0 |
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# 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# | |
TraversableLastSource# | Since: base-4.8.0.0 |
ApplicativeLastSource# | Since: base-4.8.0.0 |
FunctorLastSource# | Since: base-4.8.0.0 |
MonadLastSource# | Since: base-4.8.0.0 |
Data a => Data (Last a)Source# | Since: base-4.8.0.0 |
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 |
Semigroup (Last a)Source# | Since: base-4.9.0.0 |
Generic (Last a)Source# | |
Read a => Read (Last a)Source# | Since: base-2.1 |
Show a => Show (Last a)Source# | Since: base-2.1 |
Eq a => Eq (Last a)Source# | Since: base-2.1 |
Ord a => Ord (Last a)Source# | Since: base-2.1 |
Defined in Data.Monoid | |
Generic1LastSource# | |
typeRep (Last a)Source# | Since: base-4.7.0.0 |
Defined in Data.Monoid | |
typeRep1LastSource# | Since: base-4.7.0.0 |
Defined in Data.Monoid |
Alternative
wrapper
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
Instances
Generic1 (Alt f :: k -> Type)Source# | |
MonadFix f => MonadFix (Alt f)Source# | Since: base-4.8.0.0 |
MonadZip f => MonadZip (Alt f)Source# | Since: base-4.8.0.0 |
Foldable f => Foldable (Alt f)Source# | Since: base-4.12.0.0 |
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# | |
Contravariant f => Contravariant (Alt f)Source# | |
Traversable f => Traversable (Alt f)Source# | Since: base-4.12.0.0 |
Alternative f => Alternative (Alt f)Source# | Since: base-4.8.0.0 |
Applicative f => Applicative (Alt f)Source# | Since: base-4.8.0.0 |
Functor f => Functor (Alt f)Source# | Since: base-4.8.0.0 |
Monad f => Monad (Alt f)Source# | Since: base-4.8.0.0 |
MonadPlus f => MonadPlus (Alt f)Source# | Since: base-4.8.0.0 |
(Data (f a), Data a, Typeable f) => Data (Alt f a)Source# | Since: base-4.8.0.0 |
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 |
Alternative f => Semigroup (Alt f a)Source# | Since: base-4.9.0.0 |
Enum (f a) => Enum (Alt f a)Source# | Since: base-4.8.0.0 |
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# | |
Num (f a) => Num (Alt f a)Source# | Since: base-4.8.0.0 |
Defined in Data.Semigroup.Internal | |
Read (f a) => Read (Alt f a)Source# | Since: base-4.8.0.0 |
Show (f a) => Show (Alt f a)Source# | Since: base-4.8.0.0 |
Eq (f a) => Eq (Alt f a)Source# | Since: base-4.8.0.0 |
Ord (f a) => Ord (Alt f a)Source# | Since: base-4.8.0.0 |
typeRep1 (Alt f :: k -> Type)Source# | Since: base-4.8.0.0 |
Defined in Data.Semigroup.Internal | |
typeRep (Alt f a)Source# | Since: base-4.8.0.0 |
Defined in Data.Semigroup.Internal |
Applicative
wrapper
This data type witnesses the lifting of a Monoid
into an Applicative
pointwise.
Since: base-4.12.0.0
Instances
Generic1 (Ap f :: k -> Type)Source# | |
MonadFail f => MonadFail (Ap f)Source# | Since: base-4.12.0.0 |
MonadFix f => MonadFix (Ap f)Source# | Since: base-4.12.0.0 |
Foldable f => Foldable (Ap f)Source# | Since: base-4.12.0.0 |
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# 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# | |
Traversable f => Traversable (Ap f)Source# | Since: base-4.12.0.0 |
Alternative f => Alternative (Ap f)Source# | Since: base-4.12.0.0 |
Applicative f => Applicative (Ap f)Source# | Since: base-4.12.0.0 |
Functor f => Functor (Ap f)Source# | Since: base-4.12.0.0 |
Monad f => Monad (Ap f)Source# | Since: base-4.12.0.0 |
MonadPlus f => MonadPlus (Ap f)Source# | Since: base-4.12.0.0 |
(Data (f a), Data a, Typeable f) => Data (Ap f a)Source# | Since: base-4.12.0.0 |
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 |
(Applicative f, Semigroup a) => Semigroup (Ap f a)Source# | Since: base-4.12.0.0 |
(Applicative f, Bounded a) => Bounded (Ap f a)Source# | Since: base-4.12.0.0 |
Enum (f a) => Enum (Ap f a)Source# | Since: base-4.12.0.0 |
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# | |
(Applicative f, Num a) => Num (Ap f a)Source# | Note that even if the underlying Commutativity:
Additive inverse:
Distributivity:
Since: base-4.12.0.0 |
Read (f a) => Read (Ap f a)Source# | Since: base-4.12.0.0 |
Show (f a) => Show (Ap f a)Source# | Since: base-4.12.0.0 |
Eq (f a) => Eq (Ap f a)Source# | Since: base-4.12.0.0 |
Ord (f a) => Ord (Ap f a)Source# | Since: base-4.12.0.0 |
Defined in Data.Monoid | |
typeRep1 (Ap f :: k -> Type)Source# | Since: base-4.12.0.0 |
Defined in Data.Monoid | |
typeRep (Ap f a)Source# | Since: base-4.12.0.0 |
Defined in Data.Monoid |