Cabal-1.24.0.0: A framework for packaging Haskell software

Safe HaskellSafe
LanguageHaskell98

Distribution.Compat.Semigroup

Description

Compatibility layer for Data.Semigroup

Synopsis

Documentation

class Semigroup a where Source

Methods

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

Instances

Semigroup Ordering Source 
Semigroup () Source 
Semigroup All Source 
Semigroup Any Source 
Semigroup CDialect Source 
Semigroup BuildInfo Source 
Semigroup BenchmarkInterface Source 
Semigroup Benchmark Source 
Semigroup TestSuiteInterface Source 
Semigroup TestSuite Source 
Semigroup Executable Source 
Semigroup Library Source 
Semigroup ModuleRenaming Source 
Semigroup SetupBuildInfo Source 
Semigroup BenchmarkFlags Source 
Semigroup TestFlags Source 
Semigroup TestShowDetails Source 
Semigroup ReplFlags Source 
Semigroup BuildFlags Source 
Semigroup CleanFlags Source 
Semigroup HaddockFlags Source 
Semigroup HscolourFlags Source 
Semigroup RegisterFlags Source 
Semigroup SDistFlags Source 
Semigroup InstallFlags Source 
Semigroup CopyFlags Source 
Semigroup ConfigFlags Source 
Semigroup AllowNewer Source 
Semigroup GlobalFlags Source 
Semigroup GhcOptions Source 
Semigroup [a] Source 
Semigroup a => Semigroup (Dual a) Source 
Semigroup a => Semigroup (Maybe a) Source 
Semigroup (Condition a) Source 
Semigroup dir => Semigroup (InstallDirs dir) Source 
Ord a => Semigroup (NubListR a) Source 
Ord a => Semigroup (NubList a) Source 
HasUnitId a => Semigroup (PackageIndex a) Source 
Semigroup (Flag a) Source 
Semigroup b => Semigroup (a -> b) Source 
Semigroup (Either a b) Source 
(Semigroup a, Semigroup b) => Semigroup (a, b) Source 
(Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c) 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 

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 IntSet 
Monoid Doc 
Monoid CDialect 
Monoid BuildInfo 
Monoid BenchmarkInterface 
Monoid Benchmark 
Monoid TestSuiteInterface 
Monoid TestSuite 
Monoid Executable 
Monoid Library 
Monoid ModuleRenaming 
Monoid SetupBuildInfo 
Monoid BenchmarkFlags 
Monoid TestFlags 
Monoid TestShowDetails 
Monoid ReplFlags 
Monoid BuildFlags 
Monoid CleanFlags 
Monoid HaddockFlags 
Monoid HscolourFlags 
Monoid RegisterFlags 
Monoid SDistFlags 
Monoid InstallFlags 
Monoid CopyFlags 
Monoid ConfigFlags 
Monoid AllowNewer 
Monoid GlobalFlags 
Monoid GhcOptions 
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) 
Monoid (Condition a) 
(Semigroup dir, Monoid dir) => Monoid (InstallDirs dir) 
Ord a => Monoid (NubListR a) 
Ord a => Monoid (NubList a)

Monoid operations on NubLists. For a valid Monoid instance we need to satistfy the required monoid laws; identity, associativity and closure.

Identity : by inspection: mempty mappend NubList xs == NubList xs mappend mempty

Associativity : by inspection: (NubList xs mappend NubList ys) mappend NubList zs == NubList xs mappend (NubList ys mappend NubList zs)

Closure : appending two lists of type a and removing duplicates obviously does not change the type.

HasUnitId a => Monoid (PackageIndex a) 
Monoid (Flag 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) 
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) 
Alternative f => Monoid (Alt * f 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 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 Source 
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 Source 
type Rep Any = D1 D1Any (C1 C1_0Any (S1 S1_0_0Any (Rec0 Bool)))