| Portability | portable | 
|---|---|
| Stability | provisional | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
Data.Semigroup
Contents
Description
In mathematics, a semigroup is an algebraic structure consisting of a set together with an associative binary operation. A semigroup generalizes a monoid in that there might not exist an identity element. It also (originally) generalized a group (a monoid with all inverses) to a type where every element did not have to have an inverse, thus the name semigroup.
- class  Semigroup a  where
- (<>) :: a -> a -> a
 - sconcat :: NonEmpty a -> a
 - replicate1p :: Whole n => n -> a -> a
 
 - newtype  Min a = Min {
- getMin :: a
 
 - newtype  Max a = Max {
- getMax :: a
 
 - newtype  First a = First {
- getFirst :: a
 
 - newtype  Last a = Last {
- getLast :: a
 
 - newtype  WrappedMonoid m = WrapMonoid {
- unwrapMonoid :: m
 
 - 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 Option a = Option {}
 - option :: b -> (a -> b) -> Option a -> b
 - diff :: Semigroup m => m -> Endo m
 - cycle1 :: Semigroup m => m -> m
 
Documentation
Methods
An associative operation.
(a <> b) <> c = a <> (b <> c)
sconcat :: NonEmpty a -> aSource
Reduce a non-empty list with <>
The default definition should be sufficient, but this can be overridden for efficiency.
replicate1p :: Whole n => n -> a -> aSource
Repeat a value (n + 1) times.
replicate1p n a = a <> a <> ... n + 1 times <> a
The default definition uses peasant multiplication, exploiting associativity to only
 require O(log n) uses of <>.
Instances
| Semigroup () | |
| Semigroup All | |
| Semigroup Any | |
| Semigroup IntSet | |
| Semigroup [a] | |
| Semigroup a => Semigroup (Dual a) | |
| Semigroup (Endo a) | |
| Num a => Semigroup (Sum a) | |
| Num a => Semigroup (Product a) | |
| Semigroup (First a) | |
| Semigroup (Last a) | |
| Semigroup a => Semigroup (Maybe a) | |
| Semigroup (Seq a) | |
| Semigroup (IntMap v) | |
| Ord a => Semigroup (Set a) | |
| Semigroup (NonEmpty a) | |
| Semigroup a => Semigroup (Option a) | |
| Monoid m => Semigroup (WrappedMonoid m) | |
| Semigroup (Last a) | |
| Semigroup (First a) | |
| Ord a => Semigroup (Max a) | |
| Ord a => Semigroup (Min a) | |
| Semigroup b => Semigroup (a -> b) | |
| Semigroup (Either a b) | |
| (Semigroup a, Semigroup b) => Semigroup (a, b) | |
| Ord k => Semigroup (Map k v) | |
| (Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c) | |
| (Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d) | |
| (Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e) | 
Semigroups
newtype WrappedMonoid m Source
Provide a Semigroup for an arbitrary Monoid.
Constructors
| WrapMonoid | |
Fields 
  | |
Instances
| Typeable1 WrappedMonoid | |
| Bounded m => Bounded (WrappedMonoid m) | |
| Eq m => Eq (WrappedMonoid m) | |
| Data m => Data (WrappedMonoid m) | |
| Ord m => Ord (WrappedMonoid m) | |
| Read m => Read (WrappedMonoid m) | |
| Show m => Show (WrappedMonoid m) | |
| Monoid m => Monoid (WrappedMonoid m) | |
| Monoid m => Semigroup (WrappedMonoid m) | 
Monoids from Data.Monoid
newtype Endo a
The monoid of endomorphisms under composition.
newtype All
Boolean monoid under conjunction.
newtype Any
Boolean monoid under disjunction.
newtype Sum a
Monoid under addition.
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 intance of Maybe
Instances
| Monad Option | |
| Functor Option | |
| Typeable1 Option | |
| MonadFix Option | |
| MonadPlus Option | |
| Applicative Option | |
| Foldable Option | |
| Traversable Option | |
| Alternative 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) | |
| Semigroup a => Monoid (Option a) | |
| Semigroup a => Semigroup (Option a) |