| Safe Haskell | Safe | 
|---|---|
| Language | Haskell98 | 
Data.Monoid.Compat
Synopsis
- class Semigroup a => Monoid a where
- newtype First a = First {}
- newtype Last a = Last {}
- newtype Ap (f :: k -> Type) (a :: k) :: forall k. (k -> Type) -> k -> Type = Ap {- getAp :: f a
 
- newtype Dual a = Dual {- getDual :: a
 
- newtype Endo a = Endo {- appEndo :: a -> a
 
- newtype All = All {}
- newtype Any = Any {}
- newtype Sum a = Sum {- getSum :: a
 
- newtype Product a = Product {- getProduct :: a
 
- newtype Alt (f :: k -> Type) (a :: k) :: forall k. (k -> Type) -> k -> Type = Alt {- getAlt :: f a
 
- (<>) :: Semigroup a => a -> a -> a
Documentation
class Semigroup a => Monoid a where #
The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:
- x - <>- mempty= x
- mempty- <>x = x
- x(- <>(y- <>z) = (x- <>y)- <>z- Semigrouplaw)
- 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
Methods
Identity of mappend
An associative operation
NOTE: This method is redundant and has the default
 implementation mappend = '(<>)'
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.
Instances
| Monoid Ordering | Since: base-2.1 | 
| Monoid () | Since: base-2.1 | 
| Monoid All | Since: base-2.1 | 
| Monoid Any | Since: base-2.1 | 
| Monoid [a] | Since: base-2.1 | 
| Semigroup a => Monoid (Maybe a) | Lift a semigroup into  Since 4.11.0: constraint on inner  Since: base-2.1 | 
| Monoid a => Monoid (IO a) | Since: base-4.9.0.0 | 
| Monoid (Predicate a) | |
| Monoid (Comparison a) | |
| Defined in Data.Functor.Contravariant Methods mempty :: Comparison a # mappend :: Comparison a -> Comparison a -> Comparison a # mconcat :: [Comparison a] -> Comparison a # | |
| Monoid (Equivalence a) | |
| Defined in Data.Functor.Contravariant Methods mempty :: Equivalence a # mappend :: Equivalence a -> Equivalence a -> Equivalence a # mconcat :: [Equivalence a] -> Equivalence a # | |
| (Ord a, Bounded a) => Monoid (Min a) | Since: base-4.9.0.0 | 
| (Ord a, Bounded a) => Monoid (Max a) | Since: base-4.9.0.0 | 
| Monoid m => Monoid (WrappedMonoid m) | Since: base-4.9.0.0 | 
| Defined in Data.Semigroup Methods mempty :: WrappedMonoid m # mappend :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m # mconcat :: [WrappedMonoid m] -> WrappedMonoid m # | |
| Semigroup a => Monoid (Option a) | Since: base-4.9.0.0 | 
| Monoid a => Monoid (Identity a) | Since: base-4.9.0.0 | 
| Monoid (First a) | Since: base-2.1 | 
| Monoid (Last a) | Since: base-2.1 | 
| Monoid a => Monoid (Dual a) | Since: base-2.1 | 
| Monoid (Endo a) | Since: base-2.1 | 
| Num a => Monoid (Sum a) | Since: base-2.1 | 
| Num a => Monoid (Product a) | Since: base-2.1 | 
| Monoid b => Monoid (a -> b) | Since: base-2.1 | 
| (Monoid a, Monoid b) => Monoid (a, b) | Since: base-2.1 | 
| Monoid a => Monoid (Op a b) | |
| Monoid (Proxy s) | Since: base-4.7.0.0 | 
| (Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) | Since: base-2.1 | 
| Monoid a => Monoid (Const a b) | Since: base-4.9.0.0 | 
| (Applicative f, Monoid a) => Monoid (Ap f a) | Since: base-4.12.0.0 | 
| Alternative f => Monoid (Alt f a) | Since: base-4.8.0.0 | 
| (Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) | Since: base-2.1 | 
| (Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) | Since: base-2.1 | 
Maybe monoid returning the leftmost non-Nothing value.
First aAlt Maybe a
>>>getFirst (First (Just "hello") <> First Nothing <> First (Just "world"))Just "hello"
Use of this type is discouraged. Note the following equivalence:
Data.Monoid.First x === Maybe (Data.Semigroup.First x)
In addition to being equivalent in the structural sense, the two
 also have Monoid instances that behave the same. This type will
 be marked deprecated in GHC 8.8, and removed in GHC 8.10.
 Users are advised to use the variant from Data.Semigroup and wrap
 it in Maybe.
Instances
| Monad First | Since: base-4.8.0.0 | 
| Functor First | Since: base-4.8.0.0 | 
| Applicative First | Since: base-4.8.0.0 | 
| Foldable First | Since: base-4.8.0.0 | 
| Defined in Data.Foldable Methods fold :: Monoid m => First m -> m # foldMap :: Monoid m => (a -> m) -> First a -> m # foldr :: (a -> b -> b) -> b -> First a -> b # foldr' :: (a -> b -> b) -> b -> First a -> b # foldl :: (b -> a -> b) -> b -> First a -> b # foldl' :: (b -> a -> b) -> b -> First a -> b # foldr1 :: (a -> a -> a) -> First a -> a # foldl1 :: (a -> a -> a) -> First a -> a # elem :: Eq a => a -> First a -> Bool # maximum :: Ord a => First a -> a # minimum :: Ord a => First a -> a # | |
| Traversable First | Since: base-4.8.0.0 | 
| Eq a => Eq (First a) | Since: base-2.1 | 
| Ord a => Ord (First a) | Since: base-2.1 | 
| Read a => Read (First a) | Since: base-2.1 | 
| Show a => Show (First a) | Since: base-2.1 | 
| Generic (First a) | |
| Semigroup (First a) | Since: base-4.9.0.0 | 
| Monoid (First a) | Since: base-2.1 | 
| Generic1 First | |
| type Rep (First a) | Since: base-4.7.0.0 | 
| Defined in Data.Monoid | |
| type Rep1 First | Since: base-4.7.0.0 | 
| Defined in Data.Monoid | |
Maybe monoid returning the rightmost non-Nothing value.
Last aDual (First a)Dual (Alt Maybe a)
>>>getLast (Last (Just "hello") <> Last Nothing <> Last (Just "world"))Just "world"
Use of this type is discouraged. Note the following equivalence:
Data.Monoid.Last x === Maybe (Data.Semigroup.Last x)
In addition to being equivalent in the structural sense, the two
 also have Monoid instances that behave the same. This type will
 be marked deprecated in GHC 8.8, and removed in GHC 8.10.
 Users are advised to use the variant from Data.Semigroup and wrap
 it in Maybe.
Instances
| Monad Last | Since: base-4.8.0.0 | 
| Functor Last | Since: base-4.8.0.0 | 
| Applicative Last | Since: base-4.8.0.0 | 
| Foldable Last | Since: base-4.8.0.0 | 
| Defined in Data.Foldable Methods fold :: Monoid m => Last m -> m # foldMap :: Monoid m => (a -> m) -> Last a -> m # foldr :: (a -> b -> b) -> b -> Last a -> b # foldr' :: (a -> b -> b) -> b -> Last a -> b # foldl :: (b -> a -> b) -> b -> Last a -> b # foldl' :: (b -> a -> b) -> b -> Last a -> b # foldr1 :: (a -> a -> a) -> Last a -> a # foldl1 :: (a -> a -> a) -> Last a -> a # elem :: Eq a => a -> Last a -> Bool # maximum :: Ord a => Last a -> a # | |
| Traversable Last | Since: base-4.8.0.0 | 
| Eq a => Eq (Last a) | Since: base-2.1 | 
| Ord a => Ord (Last a) | Since: base-2.1 | 
| Read a => Read (Last a) | Since: base-2.1 | 
| Show a => Show (Last a) | Since: base-2.1 | 
| Generic (Last a) | |
| Semigroup (Last a) | Since: base-4.9.0.0 | 
| Monoid (Last a) | Since: base-2.1 | 
| Generic1 Last | |
| type Rep (Last a) | Since: base-4.7.0.0 | 
| Defined in Data.Monoid | |
| type Rep1 Last | Since: base-4.7.0.0 | 
| Defined in Data.Monoid | |
newtype Ap (f :: k -> Type) (a :: k) :: forall k. (k -> Type) -> k -> Type #
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) | |
| Monad f => Monad (Ap f) | Since: base-4.12.0.0 | 
| Functor f => Functor (Ap f) | Since: base-4.12.0.0 | 
| MonadFail f => MonadFail (Ap f) | Since: base-4.12.0.0 | 
| Defined in Data.Monoid | |
| Applicative f => Applicative (Ap f) | Since: base-4.12.0.0 | 
| Foldable f => Foldable (Ap f) | Since: base-4.12.0.0 | 
| Defined in Data.Foldable Methods fold :: Monoid m => Ap f m -> m # foldMap :: Monoid m => (a -> m) -> Ap f a -> m # foldr :: (a -> b -> b) -> b -> Ap f a -> b # foldr' :: (a -> b -> b) -> b -> Ap f a -> b # foldl :: (b -> a -> b) -> b -> Ap f a -> b # foldl' :: (b -> a -> b) -> b -> Ap f a -> b # foldr1 :: (a -> a -> a) -> Ap f a -> a # foldl1 :: (a -> a -> a) -> Ap f a -> a # elem :: Eq a => a -> Ap f a -> Bool # maximum :: Ord a => Ap f a -> a # | |
| Traversable f => Traversable (Ap f) | Since: base-4.12.0.0 | 
| Alternative f => Alternative (Ap f) | Since: base-4.12.0.0 | 
| MonadPlus f => MonadPlus (Ap f) | Since: base-4.12.0.0 | 
| (Applicative f, Bounded a) => Bounded (Ap f a) | Since: base-4.12.0.0 | 
| Enum (f a) => Enum (Ap f a) | Since: base-4.12.0.0 | 
| Defined in Data.Monoid | |
| Eq (f a) => Eq (Ap f a) | Since: base-4.12.0.0 | 
| (Applicative f, Num a) => Num (Ap f a) | Since: base-4.12.0.0 | 
| Ord (f a) => Ord (Ap f a) | Since: base-4.12.0.0 | 
| Read (f a) => Read (Ap f a) | Since: base-4.12.0.0 | 
| Show (f a) => Show (Ap f a) | Since: base-4.12.0.0 | 
| Generic (Ap f a) | |
| (Applicative f, Semigroup a) => Semigroup (Ap f a) | Since: base-4.12.0.0 | 
| (Applicative f, Monoid a) => Monoid (Ap f a) | Since: base-4.12.0.0 | 
| type Rep1 (Ap f :: k -> Type) | Since: base-4.12.0.0 | 
| Defined in Data.Monoid | |
| type Rep (Ap f a) | Since: base-4.12.0.0 | 
| Defined in Data.Monoid | |
The dual of a Monoid, obtained by swapping the arguments of mappend.
>>>getDual (mappend (Dual "Hello") (Dual "World"))"WorldHello"
Instances
| Monad Dual | Since: base-4.8.0.0 | 
| Functor Dual | Since: base-4.8.0.0 | 
| Applicative Dual | Since: base-4.8.0.0 | 
| Foldable Dual | Since: base-4.8.0.0 | 
| Defined in Data.Foldable Methods fold :: Monoid m => Dual m -> m # foldMap :: Monoid m => (a -> m) -> Dual a -> m # foldr :: (a -> b -> b) -> b -> Dual a -> b # foldr' :: (a -> b -> b) -> b -> Dual a -> b # foldl :: (b -> a -> b) -> b -> Dual a -> b # foldl' :: (b -> a -> b) -> b -> Dual a -> b # foldr1 :: (a -> a -> a) -> Dual a -> a # foldl1 :: (a -> a -> a) -> Dual a -> a # elem :: Eq a => a -> Dual a -> Bool # maximum :: Ord a => Dual a -> a # | |
| Traversable Dual | Since: base-4.8.0.0 | 
| Bounded a => Bounded (Dual a) | Since: base-2.1 | 
| Eq a => Eq (Dual a) | Since: base-2.1 | 
| Ord a => Ord (Dual a) | Since: base-2.1 | 
| Read a => Read (Dual a) | Since: base-2.1 | 
| Show a => Show (Dual a) | Since: base-2.1 | 
| Generic (Dual a) | |
| Semigroup a => Semigroup (Dual a) | Since: base-4.9.0.0 | 
| Monoid a => Monoid (Dual a) | Since: base-2.1 | 
| Generic1 Dual | |
| type Rep (Dual a) | Since: base-4.7.0.0 | 
| Defined in Data.Semigroup.Internal | |
| type Rep1 Dual | 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!"
Boolean monoid under conjunction (&&).
>>>getAll (All True <> mempty <> All False)False
>>>getAll (mconcat (map (\x -> All (even x)) [2,4,6,7,8]))False
Boolean monoid under disjunction (||).
>>>getAny (Any True <> mempty <> Any False)True
>>>getAny (mconcat (map (\x -> Any (even x)) [2,4,6,7,8]))True
Monoid under addition.
>>>getSum (Sum 1 <> Sum 2 <> mempty)3
Instances
| Monad Sum | Since: base-4.8.0.0 | 
| Functor Sum | Since: base-4.8.0.0 | 
| Applicative Sum | Since: base-4.8.0.0 | 
| Foldable Sum | Since: base-4.8.0.0 | 
| Defined in Data.Foldable Methods fold :: Monoid m => Sum m -> m # foldMap :: Monoid m => (a -> m) -> Sum a -> m # foldr :: (a -> b -> b) -> b -> Sum a -> b # foldr' :: (a -> b -> b) -> b -> Sum a -> b # foldl :: (b -> a -> b) -> b -> Sum a -> b # foldl' :: (b -> a -> b) -> b -> Sum a -> b # foldr1 :: (a -> a -> a) -> Sum a -> a # foldl1 :: (a -> a -> a) -> Sum a -> a # elem :: Eq a => a -> Sum a -> Bool # maximum :: Ord a => Sum a -> a # | |
| Traversable Sum | Since: base-4.8.0.0 | 
| Bounded a => Bounded (Sum a) | Since: base-2.1 | 
| Eq a => Eq (Sum a) | Since: base-2.1 | 
| Num a => Num (Sum a) | Since: base-4.7.0.0 | 
| Ord a => Ord (Sum a) | Since: base-2.1 | 
| Read a => Read (Sum a) | Since: base-2.1 | 
| Show a => Show (Sum a) | Since: base-2.1 | 
| Generic (Sum a) | |
| Num a => Semigroup (Sum a) | Since: base-4.9.0.0 | 
| Num a => Monoid (Sum a) | Since: base-2.1 | 
| Generic1 Sum | |
| type Rep (Sum a) | Since: base-4.7.0.0 | 
| Defined in Data.Semigroup.Internal | |
| type Rep1 Sum | 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
| Monad Product | Since: base-4.8.0.0 | 
| Functor Product | Since: base-4.8.0.0 | 
| Applicative Product | Since: base-4.8.0.0 | 
| Foldable Product | Since: base-4.8.0.0 | 
| Defined in Data.Foldable Methods fold :: Monoid m => Product m -> m # foldMap :: Monoid m => (a -> m) -> Product a -> m # foldr :: (a -> b -> b) -> b -> Product a -> b # foldr' :: (a -> b -> b) -> b -> Product a -> b # foldl :: (b -> a -> b) -> b -> Product a -> b # foldl' :: (b -> a -> b) -> b -> Product a -> b # foldr1 :: (a -> a -> a) -> Product a -> a # foldl1 :: (a -> a -> a) -> Product a -> a # elem :: Eq a => a -> Product a -> Bool # maximum :: Ord a => Product a -> a # minimum :: Ord a => Product a -> a # | |
| Traversable Product | Since: base-4.8.0.0 | 
| Bounded a => Bounded (Product a) | Since: base-2.1 | 
| Eq a => Eq (Product a) | Since: base-2.1 | 
| Num a => Num (Product a) | Since: base-4.7.0.0 | 
| Defined in Data.Semigroup.Internal | |
| Ord a => Ord (Product a) | Since: base-2.1 | 
| Read a => Read (Product a) | Since: base-2.1 | 
| Show a => Show (Product a) | Since: base-2.1 | 
| Generic (Product a) | |
| Num a => Semigroup (Product a) | Since: base-4.9.0.0 | 
| Num a => Monoid (Product a) | Since: base-2.1 | 
| Generic1 Product | |
| type Rep (Product a) | Since: base-4.7.0.0 | 
| Defined in Data.Semigroup.Internal | |
| type Rep1 Product | Since: base-4.7.0.0 | 
| Defined in Data.Semigroup.Internal | |
newtype Alt (f :: k -> Type) (a :: k) :: forall k. (k -> Type) -> k -> Type #
Monoid under <|>.
Since: base-4.8.0.0
Instances
| Generic1 (Alt f :: k -> Type) | |
| Monad f => Monad (Alt f) | Since: base-4.8.0.0 | 
| Functor f => Functor (Alt f) | Since: base-4.8.0.0 | 
| Applicative f => Applicative (Alt f) | Since: base-4.8.0.0 | 
| Foldable f => Foldable (Alt f) | Since: base-4.12.0.0 | 
| Defined in Data.Foldable Methods fold :: Monoid m => Alt f m -> m # foldMap :: Monoid m => (a -> m) -> Alt f a -> m # foldr :: (a -> b -> b) -> b -> Alt f a -> b # foldr' :: (a -> b -> b) -> b -> Alt f a -> b # foldl :: (b -> a -> b) -> b -> Alt f a -> b # foldl' :: (b -> a -> b) -> b -> Alt f a -> b # foldr1 :: (a -> a -> a) -> Alt f a -> a # foldl1 :: (a -> a -> a) -> Alt f a -> a # elem :: Eq a => a -> Alt f a -> Bool # maximum :: Ord a => Alt f a -> a # minimum :: Ord a => Alt f a -> a # | |
| Traversable f => Traversable (Alt f) | Since: base-4.12.0.0 | 
| Contravariant f => Contravariant (Alt f) | |
| Alternative f => Alternative (Alt f) | Since: base-4.8.0.0 | 
| MonadPlus f => MonadPlus (Alt f) | Since: base-4.8.0.0 | 
| Enum (f a) => Enum (Alt f a) | Since: base-4.8.0.0 | 
| Eq (f a) => Eq (Alt f a) | Since: base-4.8.0.0 | 
| Num (f a) => Num (Alt f a) | Since: base-4.8.0.0 | 
| Ord (f a) => Ord (Alt f a) | Since: base-4.8.0.0 | 
| Defined in Data.Semigroup.Internal | |
| Read (f a) => Read (Alt f a) | Since: base-4.8.0.0 | 
| Show (f a) => Show (Alt f a) | Since: base-4.8.0.0 | 
| Generic (Alt f a) | |
| Alternative f => Semigroup (Alt f a) | Since: base-4.9.0.0 | 
| Alternative f => Monoid (Alt f a) | Since: base-4.8.0.0 | 
| type Rep1 (Alt f :: k -> Type) | Since: base-4.8.0.0 | 
| Defined in Data.Semigroup.Internal | |
| type Rep (Alt f a) | Since: base-4.8.0.0 | 
| Defined in Data.Semigroup.Internal | |