semigroups-0.17.0.1: Anything that associates

Copyright(C) 2011-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell98

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.

The use of (<>) in this module conflicts with an operator with the same name that is being exported by Data.Monoid. However, this package re-exports (most of) the contents of Data.Monoid, so to use semigroups and monoids in the same package just

import Data.Semigroup

Synopsis

Documentation

class Semigroup a where Source

Minimal complete definition

Nothing

Methods

(<>) :: a -> a -> a infixr 6 Source

An associative operation.

(a <> b) <> c = a <> (b <> c)

If a is also a Monoid we further require

(<>) = mappend

sconcat :: NonEmpty a -> a Source

Reduce a non-empty list with <>

The default definition should be sufficient, but this can be overridden for efficiency.

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

Repeat a value n times.

Given that this works on a Semigroup it is allowed to fail if you request 0 or fewer repetitions, and the default definition will do so.

By making this a member of the class, idempotent semigroups and monoids can upgrade this to execute in O(1) by picking stimes = stimesIdempotent or stimes = stimesIdempotentMonoid respectively.

Since: 0.17

Instances

Semigroup Ordering Source 
Semigroup () Source 
Semigroup Void Source 
Semigroup All Source 
Semigroup Any Source 
Semigroup ByteString Source 
Semigroup ByteString Source 
Semigroup Builder Source 
Semigroup ShortByteString Source 
Semigroup IntSet Source 
Semigroup Text Source 
Semigroup Text Source 
Semigroup Builder Source 
Semigroup [a] Source 
Semigroup a => Semigroup (Dual a) Source 
Semigroup (Endo a) Source 
Num a => Semigroup (Sum a) Source 
Num a => Semigroup (Product a) Source 
Semigroup (First a) Source 
Semigroup (Last a) Source 
Semigroup a => Semigroup (Maybe a) Source 
Semigroup (IntMap v) Source 
Ord a => Semigroup (Set a) Source 
Semigroup (Seq a) Source 
Semigroup (NonEmpty a) Source 
(Hashable a, Eq a) => Semigroup (HashSet a) Source 
Semigroup a => Semigroup (Option a) Source 
Monoid m => Semigroup (WrappedMonoid m) Source 
Semigroup (Last a) Source 
Semigroup (First a) Source 
Ord a => Semigroup (Max a) Source 
Ord a => Semigroup (Min a) Source 
Semigroup b => Semigroup (a -> b) Source 
Semigroup (Either a b) Source 
(Semigroup a, Semigroup b) => Semigroup (a, b) Source 
Semigroup a => Semigroup (Const a b) Source 
Semigroup (Proxy k s) Source 
Ord k => Semigroup (Map k v) Source 
(Hashable k, Eq k) => Semigroup (HashMap k a) Source 
(Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c) Source 
Alternative f => Semigroup (Alt * f a) Source 
Semigroup a => Semigroup (Tagged k s a) Source 
(Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d) Source 
(Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e) Source 

stimesMonoid :: (Integral b, Monoid a) => b -> a -> a Source

This is a valid definition of stimes for a Monoid.

Unlike the default definition of stimes, it is defined for 0 and so it should be preferred where possible.

stimesIdempotent :: Integral b => b -> a -> a Source

This is a valid definition of stimes for an idempotent Semigroup.

When x <> x = x, this definition should be preferred, because it works in O(1) rather than O(log n).

stimesIdempotentMonoid :: (Integral b, Monoid a) => b -> a -> a Source

This is a valid definition of stimes for an idempotent Monoid.

When mappend x x = x, this definition should be preferred, because it works in O(1) rather than O(log n)

mtimesDefault :: (Integral b, Monoid a) => b -> a -> a Source

Repeat a value n times.

mtimesDefault n a = a <> a <> ... <> a  -- using <> (n-1) times

Implemented using stimes and mempty.

This is a suitable definition for an mtimes member of Monoid.

Since: 0.17

Semigroups

newtype Min a Source

Constructors

Min 

Fields

getMin :: a
 

Instances

Monad Min Source 
Functor Min Source 
MonadFix Min Source 
Applicative Min Source 
Foldable Min Source 
Traversable Min Source 
Generic1 Min Source 
Bounded a => Bounded (Min a) Source 
Enum a => Enum (Min a) Source 
Eq a => Eq (Min a) Source 
Data a => Data (Min a) Source 
Num a => Num (Min a) Source 
Ord a => Ord (Min a) Source 
Read a => Read (Min a) Source 
Show a => Show (Min a) Source 
Generic (Min a) Source 
(Ord a, Bounded a) => Monoid (Min a) Source 
NFData a => NFData (Min a) Source 
Hashable a => Hashable (Min a) Source 
Ord a => Semigroup (Min a) Source 
type Rep1 Min Source 
type Rep (Min a) Source 

newtype Max a Source

Constructors

Max 

Fields

getMax :: a
 

Instances

Monad Max Source 
Functor Max Source 
MonadFix Max Source 
Applicative Max Source 
Foldable Max Source 
Traversable Max Source 
Generic1 Max Source 
Bounded a => Bounded (Max a) Source 
Enum a => Enum (Max a) Source 
Eq a => Eq (Max a) Source 
Data a => Data (Max a) Source 
Num a => Num (Max a) Source 
Ord a => Ord (Max a) Source 
Read a => Read (Max a) Source 
Show a => Show (Max a) Source 
Generic (Max a) Source 
(Ord a, Bounded a) => Monoid (Max a) Source 
NFData a => NFData (Max a) Source 
Hashable a => Hashable (Max a) Source 
Ord a => Semigroup (Max a) Source 
type Rep1 Max Source 
type Rep (Max a) Source 

newtype First a Source

Use Option (First a) to get the behavior of First from Data.Monoid.

Constructors

First 

Fields

getFirst :: a
 

newtype Last a Source

Use Option (Last a) to get the behavior of Last from Data.Monoid

Constructors

Last 

Fields

getLast :: a
 

Re-exported monoids from Data.Monoid

class Monoid a where

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 = foldr mappend 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.

Minimal complete definition

mempty, mappend

Methods

mempty :: a

Identity of mappend

mappend :: a -> a -> a

An associative operation

mconcat :: [a] -> a

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 
Monoid () 
Monoid All 
Monoid Any 
Monoid ByteString 
Monoid ByteString 
Monoid Builder 
Monoid ShortByteString 
Monoid IntSet 
Monoid Builder 
Monoid [a] 
Ord a => Monoid (Max a) 
Ord a => Monoid (Min 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 a => Monoid (Maybe a)

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 there is no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Monoid (IntMap a) 
Ord a => Monoid (Set a) 
Monoid (Seq a) 
(Hashable a, Eq a) => Monoid (HashSet a) 
Semigroup a => Monoid (Option a) 
Monoid m => Monoid (WrappedMonoid m) 
(Ord a, Bounded a) => Monoid (Max a) 
(Ord a, Bounded a) => Monoid (Min a) 
Monoid b => Monoid (a -> b) 
(Monoid a, Monoid b) => Monoid (a, b) 
Monoid a => Monoid (Const a b) 
Monoid (Proxy k s) 
Ord k => Monoid (Map k v) 
(Eq k, Hashable k) => Monoid (HashMap k v) 
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) 
Alternative f => Monoid (Alt * f 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) 

newtype Dual a :: * -> *

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

Constructors

Dual 

Fields

getDual :: a
 

Instances

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) 
Monoid a => Monoid (Dual a) 
NFData a => NFData (Dual a)

Since: 1.4.0.0

Semigroup a => Semigroup (Dual a) 
type Rep1 Dual = D1 D1Dual (C1 C1_0Dual (S1 S1_0_0Dual Par1)) 
type Rep (Dual a) = D1 D1Dual (C1 C1_0Dual (S1 S1_0_0Dual (Rec0 a))) 

newtype Endo a :: * -> *

The monoid of endomorphisms under composition.

Constructors

Endo 

Fields

appEndo :: a -> a
 

Instances

Generic (Endo a) 
Monoid (Endo a) 
Semigroup (Endo a) 
type Rep (Endo a) = D1 D1Endo (C1 C1_0Endo (S1 S1_0_0Endo (Rec0 (a -> a)))) 

newtype All :: *

Boolean monoid under conjunction (&&).

Constructors

All 

Fields

getAll :: Bool
 

Instances

Bounded All 
Eq All 
Ord All 
Read All 
Show All 
Generic All 
Monoid All 
NFData All

Since: 1.4.0.0

Semigroup All 
type Rep All = D1 D1All (C1 C1_0All (S1 S1_0_0All (Rec0 Bool))) 

newtype Any :: *

Boolean monoid under disjunction (||).

Constructors

Any 

Fields

getAny :: Bool
 

Instances

Bounded Any 
Eq Any 
Ord Any 
Read Any 
Show Any 
Generic Any 
Monoid Any 
NFData Any

Since: 1.4.0.0

Semigroup Any 
type Rep Any = D1 D1Any (C1 C1_0Any (S1 S1_0_0Any (Rec0 Bool))) 

newtype Sum a :: * -> *

Monoid under addition.

Constructors

Sum 

Fields

getSum :: a
 

Instances

Generic1 Sum 
Bounded a => Bounded (Sum a) 
Eq a => Eq (Sum a) 
Num a => Num (Sum a) 
Ord a => Ord (Sum a) 
Read a => Read (Sum a) 
Show a => Show (Sum a) 
Generic (Sum a) 
Num a => Monoid (Sum a) 
NFData a => NFData (Sum a)

Since: 1.4.0.0

Num a => Semigroup (Sum a) 
type Rep1 Sum = D1 D1Sum (C1 C1_0Sum (S1 S1_0_0Sum Par1)) 
type Rep (Sum a) = D1 D1Sum (C1 C1_0Sum (S1 S1_0_0Sum (Rec0 a))) 

newtype Product a :: * -> *

Monoid under multiplication.

Constructors

Product 

Fields

getProduct :: a
 

Instances

Generic1 Product 
Bounded a => Bounded (Product a) 
Eq a => Eq (Product a) 
Num a => Num (Product a) 
Ord a => Ord (Product a) 
Read a => Read (Product a) 
Show a => Show (Product a) 
Generic (Product a) 
Num a => Monoid (Product a) 
NFData a => NFData (Product a)

Since: 1.4.0.0

Num a => Semigroup (Product a) 
type Rep1 Product = D1 D1Product (C1 C1_0Product (S1 S1_0_0Product Par1)) 
type Rep (Product a) = D1 D1Product (C1 C1_0Product (S1 S1_0_0Product (Rec0 a))) 

A better monoid for Maybe

newtype Option a Source

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

Constructors

Option 

Fields

getOption :: Maybe a
 

option :: b -> (a -> b) -> Option a -> b Source

Fold an Option case-wise, just like maybe.

Difference lists of a semigroup

diff :: Semigroup m => m -> Endo m Source

This lets you use a difference list of a Semigroup as a Monoid.

cycle1 :: Semigroup m => m -> m Source

A generalization of cycle to an arbitrary Semigroup. May fail to terminate for some values in some semigroups.

ArgMin, ArgMax

data Arg a b Source

Arg isn't itself a Semigroup in its own right, but it can be placed inside Min and Max to compute an arg min or arg max.

Constructors

Arg a b 

Instances

Bifunctor Arg Source 
Functor (Arg a) Source 
Foldable (Arg a) Source 
Traversable (Arg a) Source 
Generic1 (Arg a) Source 
Eq a => Eq (Arg a b) Source 
(Data a, Data b) => Data (Arg a b) Source 
Ord a => Ord (Arg a b) Source 
(Read a, Read b) => Read (Arg a b) Source 
(Show a, Show b) => Show (Arg a b) Source 
Generic (Arg a b) Source 
(NFData a, NFData b) => NFData (Arg a b) Source 
(Hashable a, Hashable b) => Hashable (Arg a b) Source 
type Rep1 (Arg a) Source 
type Rep (Arg a b) Source 

type ArgMin a b = Min (Arg a b) Source

type ArgMax a b = Max (Arg a b) Source