| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Precursor.Algebra.Monoid
- class Monoid a where
- mempty :: Monoid a => a
- mappend :: Monoid a => a -> a -> a
- newtype Dual a :: * -> * = Dual {
- getDual :: a
- newtype Endo a :: * -> * = Endo {
- appEndo :: a -> a
- newtype Sum a = Sum {
- getSum :: a
- newtype Product a = Product {
- getProduct :: a
- newtype Option a :: * -> * = Option {}
- option :: b -> (a -> b) -> Option a -> b
Monoid typeclass
The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:
mappend mempty x = x
mappend x mempty = x
mappend x (mappend y z) = mappend (mappend x y) z
mconcat =
foldrmappend 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.
Instances
| Monoid Ordering | |
| Monoid () | |
| Monoid All | |
| Monoid Any | |
| Monoid ByteString | |
| Monoid ByteString | |
| Monoid IntSet | |
| Monoid Doc | |
| Monoid Builder | |
| Monoid [a] | |
| Monoid a => Monoid (Maybe a) | Lift a semigroup into |
| Monoid a => Monoid (IO a) | |
| Ord a => Monoid (Max a) | |
| Ord a => Monoid (Min a) | |
| Monoid a => Monoid (Identity a) | |
| (Ord a, Bounded a) => Monoid (Min a) | |
| (Ord a, Bounded a) => Monoid (Max a) | |
| Monoid m => Monoid (WrappedMonoid m) | |
| Semigroup a => Monoid (Option a) | |
| Monoid a => Monoid (Dual a) | |
| Monoid (Endo a) | |
| Num a => Monoid (Sum a) | |
| Num a => Monoid (Product a) | |
| Monoid (First a) | |
| Monoid (Last a) | |
| Monoid (IntMap a) | |
| Monoid (Seq a) | |
| Ord a => Monoid (Set a) | |
| Monoid (Doc a) | |
| Semiring a => Monoid (Product a) # | |
| Semiring a => Monoid (Sum a) # | |
| Monoid b => Monoid (a -> b) | |
| (Monoid a, Monoid b) => Monoid (a, b) | |
| Monoid (Proxy k s) | |
| Ord k => Monoid (Map k v) | |
| (Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) | |
| Monoid a => Monoid (Const k a b) | |
| Alternative f => Monoid (Alt * f a) | |
| (Semigroup a, Monoid a) => Monoid (Tagged k s a) | |
| (Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) | |
| (Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) | |
Instances
| Monad Dual | |
| Functor Dual | |
| MonadFix Dual | |
| Applicative Dual | |
| Foldable Dual | |
| Traversable Dual | |
| Generic1 Dual | |
| Bounded a => Bounded (Dual a) | |
| Eq a => Eq (Dual a) | |
| Ord a => Ord (Dual a) | |
| Read a => Read (Dual a) | |
| Show a => Show (Dual a) | |
| Generic (Dual a) | |
| Semigroup a => Semigroup (Dual a) | |
| Monoid a => Monoid (Dual a) | |
| type Rep1 Dual | |
| type Rep (Dual a) | |
The monoid of endomorphisms under composition.
Semiring wrappers
Monoid under addition.
Instances
| Monad Sum Source # | |
| Functor Sum Source # | |
| Applicative Sum Source # | |
| Generic1 Sum Source # | |
| Bounded a => Bounded (Sum a) Source # | |
| Eq a => Eq (Sum a) Source # | |
| Ord a => Ord (Sum a) Source # | |
| Generic (Sum a) Source # | |
| Semiring a => Semigroup (Sum a) Source # | |
| Semiring a => Monoid (Sum a) Source # | |
| TextShow a => TextShow (Sum a) Source # | |
| Num a => Num (Sum a) Source # | |
| type Rep1 Sum Source # | |
| type Rep (Sum a) Source # | |
Monoid under multiplication.
Constructors
| Product | |
Fields
| |
Instances
| Monad Product Source # | |
| Functor Product Source # | |
| Applicative Product Source # | |
| Generic1 Product Source # | |
| Bounded a => Bounded (Product a) Source # | |
| Eq a => Eq (Product a) Source # | |
| Ord a => Ord (Product a) Source # | |
| Generic (Product a) Source # | |
| Semiring a => Semigroup (Product a) Source # | |
| Semiring a => Monoid (Product a) Source # | |
| TextShow a => TextShow (Product a) Source # | |
| Num a => Num (Product a) Source # | |
| type Rep1 Product Source # | |
| type Rep (Product a) Source # | |
A better monoid for Maybe
Option is effectively Maybe with a better instance of
Monoid, built off of an underlying Semigroup instead of an
underlying Monoid.
Ideally, this type would not exist at all and we would just fix the
Monoid instance of Maybe
Instances
| Monad Option | |
| Functor Option | |
| MonadFix Option | |
| Applicative Option | |
| Foldable Option | |
| Traversable Option | |
| Generic1 Option | |
| Alternative Option | |
| MonadPlus Option | |
| Eq a => Eq (Option a) | |
| Data a => Data (Option a) | |
| Ord a => Ord (Option a) | |
| Read a => Read (Option a) | |
| Show a => Show (Option a) | |
| Generic (Option a) | |
| Semigroup a => Semigroup (Option a) | |
| Semigroup a => Monoid (Option a) | |
| type Rep1 Option | |
| type Rep (Option a) | |