group-theory-0.1.0.0: The theory of groups
Copyright(c) 2020 Emily Pillmore
LicenseBSD-style
MaintainerEmily Pillmore <emilypi@cohomolo.gy>, Reed Mullanix <reedmullanix@gmail.com>
Stabilitystable
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell2010

Data.Group

Description

This module contains definitions for Group and AbelianGroup, along with the relevant combinators.

Synopsis

Groups

class Monoid a => Group a where Source #

The typeclass of groups (types with an associative binary operation that has an identity, and all inverses, i.e. a Monoid with all inverses), representing the structural symmetries of a mathematical object.

Instances should satisfy the following:

Right identity
x <> mempty = x
Left identity
mempty <> x = x
Associativity
x <> (y <> z) = (x <> y) <> z
Concatenation
mconcat = foldr (<>) mempty
Right inverses
x <> invert x = mempty
Left inverses
invert x <> x = mempty

Some types can be viewed as a group 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 Group, e.g. Sum and Product. Often in practice such differences between addition and multiplication-like operations matter (e.g. when defining rings), and so, classes "additive" (the underlying operation is addition-like) and "multiplicative" group classes are provided in vis AdditiveGroup and MultiplicativeGroup.

Categorically, Groups may be viewed single-object groupoids.

Minimal complete definition

invert | minus

Methods

invert :: a -> a Source #

gtimes :: Integral n => n -> a -> a Source #

Similar to stimes from Semigroup, but handles negative powers by using invert appropriately.

Examples:

Expand
>>> gtimes 2 (Sum 3)
Sum {getSum = 6}
>>> gtimes (-3) (Sum 3)
Sum {getSum = -9}

minus :: a -> a -> a Source #

Group subtraction.

This function denotes principled Group subtraction, where a minus b translates into a <> (invert b). This is because subtraction as an operator is non-associative, but the operation described in terms of addition and inversion is.

Instances

Instances details
Group Ordering Source # 
Instance details

Defined in Data.Group

Group () Source # 
Instance details

Defined in Data.Group

Methods

invert :: () -> () Source #

gtimes :: Integral n => n -> () -> () Source #

minus :: () -> () -> () Source #

Group All Source # 
Instance details

Defined in Data.Group

Methods

invert :: All -> All Source #

gtimes :: Integral n => n -> All -> All Source #

minus :: All -> All -> All Source #

Group Any Source # 
Instance details

Defined in Data.Group

Methods

invert :: Any -> Any Source #

gtimes :: Integral n => n -> Any -> Any Source #

minus :: Any -> Any -> Any Source #

Group (Predicate a) Source # 
Instance details

Defined in Data.Group

Group (Comparison a) Source # 
Instance details

Defined in Data.Group

Group (Equivalence a) Source # 
Instance details

Defined in Data.Group

Group a => Group (Identity a) Source # 
Instance details

Defined in Data.Group

Group a => Group (Dual a) Source # 
Instance details

Defined in Data.Group

Methods

invert :: Dual a -> Dual a Source #

gtimes :: Integral n => n -> Dual a -> Dual a Source #

minus :: Dual a -> Dual a -> Dual a Source #

Group a => Group (Endo a) Source # 
Instance details

Defined in Data.Group

Methods

invert :: Endo a -> Endo a Source #

gtimes :: Integral n => n -> Endo a -> Endo a Source #

minus :: Endo a -> Endo a -> Endo a Source #

Group (Sum Int) Source # 
Instance details

Defined in Data.Group

Methods

invert :: Sum Int -> Sum Int Source #

gtimes :: Integral n => n -> Sum Int -> Sum Int Source #

minus :: Sum Int -> Sum Int -> Sum Int Source #

Group (Sum Int8) Source # 
Instance details

Defined in Data.Group

Group (Sum Int16) Source # 
Instance details

Defined in Data.Group

Group (Sum Int32) Source # 
Instance details

Defined in Data.Group

Group (Sum Int64) Source # 
Instance details

Defined in Data.Group

Group (Sum Integer) Source # 
Instance details

Defined in Data.Group

Group (Sum (Ratio Int)) Source # 
Instance details

Defined in Data.Group

Group (Sum (Ratio Int8)) Source # 
Instance details

Defined in Data.Group

Group (Sum (Ratio Int16)) Source # 
Instance details

Defined in Data.Group

Group (Sum (Ratio Int32)) Source # 
Instance details

Defined in Data.Group

Group (Sum (Ratio Int64)) Source # 
Instance details

Defined in Data.Group

Group (Sum (Ratio Word)) Source # 
Instance details

Defined in Data.Group

Group (Sum (Ratio Word8)) Source # 
Instance details

Defined in Data.Group

Group (Sum (Ratio Word16)) Source # 
Instance details

Defined in Data.Group

Group (Sum (Ratio Word32)) Source # 
Instance details

Defined in Data.Group

Group (Sum (Ratio Word64)) Source # 
Instance details

Defined in Data.Group

Group (Sum Rational) Source # 
Instance details

Defined in Data.Group

Group (Sum Word) Source # 
Instance details

Defined in Data.Group

Group (Sum Word8) Source # 
Instance details

Defined in Data.Group

Group (Sum Word16) Source # 
Instance details

Defined in Data.Group

Group (Sum Word32) Source # 
Instance details

Defined in Data.Group

Group (Sum Word64) Source # 
Instance details

Defined in Data.Group

Group (Product (Ratio Int)) Source # 
Instance details

Defined in Data.Group

Group (Product (Ratio Int8)) Source # 
Instance details

Defined in Data.Group

Group (Product (Ratio Int16)) Source # 
Instance details

Defined in Data.Group

Group (Product (Ratio Int32)) Source # 
Instance details

Defined in Data.Group

Group (Product (Ratio Int64)) Source # 
Instance details

Defined in Data.Group

Group (Product (Ratio Natural)) Source # 
Instance details

Defined in Data.Group

Group (Product (Ratio Word)) Source # 
Instance details

Defined in Data.Group

Group (Product (Ratio Word8)) Source # 
Instance details

Defined in Data.Group

Group (Product (Ratio Word16)) Source # 
Instance details

Defined in Data.Group

Group (Product (Ratio Word32)) Source # 
Instance details

Defined in Data.Group

Group (Product (Ratio Word64)) Source # 
Instance details

Defined in Data.Group

Group (Product Rational) Source # 
Instance details

Defined in Data.Group

Group a => Group (Down a) Source # 
Instance details

Defined in Data.Group

Methods

invert :: Down a -> Down a Source #

gtimes :: Integral n => n -> Down a -> Down a Source #

minus :: Down a -> Down a -> Down a Source #

(Eq g, Group g) => Group (Abelianizer g) Source # 
Instance details

Defined in Data.Group

Ord a => Group (FreeAbelianGroup a) Source # 
Instance details

Defined in Data.Group.Free

Group (FreeGroup a) Source # 
Instance details

Defined in Data.Group.Free

Group (FA a) Source # 
Instance details

Defined in Data.Group.Free.Church

Methods

invert :: FA a -> FA a Source #

gtimes :: Integral n => n -> FA a -> FA a Source #

minus :: FA a -> FA a -> FA a Source #

Group (FG a) Source # 
Instance details

Defined in Data.Group.Free.Church

Methods

invert :: FG a -> FG a Source #

gtimes :: Integral n => n -> FG a -> FG a Source #

minus :: FG a -> FG a -> FG a Source #

Group a => Group (Permutation a) Source # 
Instance details

Defined in Data.Group.Permutation

Group b => Group (a -> b) Source # 
Instance details

Defined in Data.Group

Methods

invert :: (a -> b) -> a -> b Source #

gtimes :: Integral n => n -> (a -> b) -> a -> b Source #

minus :: (a -> b) -> (a -> b) -> a -> b Source #

(Group a, Group b) => Group (a, b) Source # 
Instance details

Defined in Data.Group

Methods

invert :: (a, b) -> (a, b) Source #

gtimes :: Integral n => n -> (a, b) -> (a, b) Source #

minus :: (a, b) -> (a, b) -> (a, b) Source #

Group a => Group (Op a b) Source # 
Instance details

Defined in Data.Group

Methods

invert :: Op a b -> Op a b Source #

gtimes :: Integral n => n -> Op a b -> Op a b Source #

minus :: Op a b -> Op a b -> Op a b Source #

Group a => Group (Proxy a) Source # 
Instance details

Defined in Data.Group

Methods

invert :: Proxy a -> Proxy a Source #

gtimes :: Integral n => n -> Proxy a -> Proxy a Source #

minus :: Proxy a -> Proxy a -> Proxy a Source #

(Group a, Group b, Group c) => Group (a, b, c) Source # 
Instance details

Defined in Data.Group

Methods

invert :: (a, b, c) -> (a, b, c) Source #

gtimes :: Integral n => n -> (a, b, c) -> (a, b, c) Source #

minus :: (a, b, c) -> (a, b, c) -> (a, b, c) Source #

Group a => Group (Const a b) Source # 
Instance details

Defined in Data.Group

Methods

invert :: Const a b -> Const a b Source #

gtimes :: Integral n => n -> Const a b -> Const a b Source #

minus :: Const a b -> Const a b -> Const a b Source #

(Group (f a), Group (g a)) => Group ((f :*: g) a) Source # 
Instance details

Defined in Data.Group

Methods

invert :: (f :*: g) a -> (f :*: g) a Source #

gtimes :: Integral n => n -> (f :*: g) a -> (f :*: g) a Source #

minus :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a Source #

(Group a, Group b, Group c, Group d) => Group (a, b, c, d) Source # 
Instance details

Defined in Data.Group

Methods

invert :: (a, b, c, d) -> (a, b, c, d) Source #

gtimes :: Integral n => n -> (a, b, c, d) -> (a, b, c, d) Source #

minus :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source #

Group (f (g a)) => Group ((f :.: g) a) Source # 
Instance details

Defined in Data.Group

Methods

invert :: (f :.: g) a -> (f :.: g) a Source #

gtimes :: Integral n => n -> (f :.: g) a -> (f :.: g) a Source #

minus :: (f :.: g) a -> (f :.: g) a -> (f :.: g) a Source #

(Group a, Group b, Group c, Group d, Group e) => Group (a, b, c, d, e) Source # 
Instance details

Defined in Data.Group

Methods

invert :: (a, b, c, d, e) -> (a, b, c, d, e) Source #

gtimes :: Integral n => n -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

minus :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

Group combinators

(><) :: Group a => a -> a -> a infixr 6 Source #

Apply (<>), commuting its arguments. When the group is abelian, a <> b is identically b <> a.

Conjugation

conjugate :: Group a => a -> a -> a Source #

Conjugate an element of a group by another element. When the group is abelian, conjugation is the identity.

Symbolically, this is \( (g,a) \mapsto gag^{-1} \).

Examples:

>>> let x = Sum (3 :: Int)
>>> conjugate x x
Sum {getSum = 3}
>>> let x = All True
>>> conjugate (All False) x
All {getAll = False}

unconjugate :: Group a => a -> a -> a Source #

Apply an inverse conjugate to a conjugated element.

unconjugate . conjugate = id
conjugate . unconjugate = id

Examples:

>>> let x = Sum (3 :: Int)
>>> unconjugate x (conjugate x x)
Sum {getSum = 3}

pattern Conjugate :: Group a => (a, a) -> (a, a) Source #

Bidirectional pattern for conjugation by a group element

Note: When the underlying Group is abelian, this pattern is the identity.

Order

data Order Source #

The order of a group element.

The order of a group element can either be infinite, as in the case of All False, or finite, as in the case of All True.

Constructors

Infinite 
Finite !Natural 

Instances

Instances details
Eq Order Source # 
Instance details

Defined in Data.Group

Methods

(==) :: Order -> Order -> Bool #

(/=) :: Order -> Order -> Bool #

Show Order Source # 
Instance details

Defined in Data.Group

Methods

showsPrec :: Int -> Order -> ShowS #

show :: Order -> String #

showList :: [Order] -> ShowS #

pattern Infinitary :: (Eq g, Group g) => g Source #

Unidirectional pattern synonym for the infinite order of a group element.

pattern Finitary :: (Eq g, Group g) => Natural -> g Source #

Unidirectional pattern synonym for the finite order of a group element.

order :: (Eq g, Group g) => g -> Order Source #

Calculate the exponent of a particular element in a group.

Warning: If order expects a FiniteGroup, this is gauranteed to terminate. However, this is not true of groups in general. This will spin forever if you give it something like non-zero Sum Integer.

Examples:

>>> order @(Sum Word8) 3
Finite 255
>>> order (Any False)
Finite 1
>>> order (All False)
Infinite

Abelianization

data Abelianizer a Source #

Quotient a pair of group elements by their commutator.

The of the quotient \( G / [G,G] \) forms an abelian group, and Abelianizer forms a functor from the category of groups to the category of Abelian groups. This functor is left adjoint to the inclusion functor \( Ab \rightarrow Grp \), forming a monad in \( Grp \).

Constructors

Quot 
Commuted a 

Instances

Instances details
Monad Abelianizer Source # 
Instance details

Defined in Data.Group

Methods

(>>=) :: Abelianizer a -> (a -> Abelianizer b) -> Abelianizer b #

(>>) :: Abelianizer a -> Abelianizer b -> Abelianizer b #

return :: a -> Abelianizer a #

Functor Abelianizer Source # 
Instance details

Defined in Data.Group

Methods

fmap :: (a -> b) -> Abelianizer a -> Abelianizer b #

(<$) :: a -> Abelianizer b -> Abelianizer a #

Applicative Abelianizer Source # 
Instance details

Defined in Data.Group

Methods

pure :: a -> Abelianizer a #

(<*>) :: Abelianizer (a -> b) -> Abelianizer a -> Abelianizer b #

liftA2 :: (a -> b -> c) -> Abelianizer a -> Abelianizer b -> Abelianizer c #

(*>) :: Abelianizer a -> Abelianizer b -> Abelianizer b #

(<*) :: Abelianizer a -> Abelianizer b -> Abelianizer a #

Foldable Abelianizer Source # 
Instance details

Defined in Data.Group

Methods

fold :: Monoid m => Abelianizer m -> m #

foldMap :: Monoid m => (a -> m) -> Abelianizer a -> m #

foldMap' :: Monoid m => (a -> m) -> Abelianizer a -> m #

foldr :: (a -> b -> b) -> b -> Abelianizer a -> b #

foldr' :: (a -> b -> b) -> b -> Abelianizer a -> b #

foldl :: (b -> a -> b) -> b -> Abelianizer a -> b #

foldl' :: (b -> a -> b) -> b -> Abelianizer a -> b #

foldr1 :: (a -> a -> a) -> Abelianizer a -> a #

foldl1 :: (a -> a -> a) -> Abelianizer a -> a #

toList :: Abelianizer a -> [a] #

null :: Abelianizer a -> Bool #

length :: Abelianizer a -> Int #

elem :: Eq a => a -> Abelianizer a -> Bool #

maximum :: Ord a => Abelianizer a -> a #

minimum :: Ord a => Abelianizer a -> a #

sum :: Num a => Abelianizer a -> a #

product :: Num a => Abelianizer a -> a #

Traversable Abelianizer Source # 
Instance details

Defined in Data.Group

Methods

traverse :: Applicative f => (a -> f b) -> Abelianizer a -> f (Abelianizer b) #

sequenceA :: Applicative f => Abelianizer (f a) -> f (Abelianizer a) #

mapM :: Monad m => (a -> m b) -> Abelianizer a -> m (Abelianizer b) #

sequence :: Monad m => Abelianizer (m a) -> m (Abelianizer a) #

GroupFoldable Abelianizer Source # 
Instance details

Defined in Data.Group.Foldable

Methods

goldMap :: Group g => (a -> g) -> Abelianizer a -> g Source #

toFG :: Abelianizer a -> FG a Source #

Eq a => Eq (Abelianizer a) Source # 
Instance details

Defined in Data.Group

Show a => Show (Abelianizer a) Source # 
Instance details

Defined in Data.Group

Semigroup g => Semigroup (Abelianizer g) Source # 
Instance details

Defined in Data.Group

Monoid g => Monoid (Abelianizer g) Source # 
Instance details

Defined in Data.Group

(Eq a, AbelianGroup a) => AbelianGroup (Abelianizer a) Source # 
Instance details

Defined in Data.Group

(Eq g, Group g) => Group (Abelianizer g) Source # 
Instance details

Defined in Data.Group

abelianize :: (Eq g, Group g) => g -> g -> Abelianizer g Source #

Quotient a pair of group elements by their commutator.

Ranging over the entire group, this operation constructs the quotient of the group by its commutator sub-group \( G / [G,G] \).

commutate :: Group g => g -> g -> g Source #

Take the commutator of two elements of a group.

pattern Abelianized :: (Eq g, Group g) => g -> (g, g) Source #

A unidirectional pattern synonym for elements of a group modulo commutators which are not the identity.

pattern Quotiented :: (Eq g, Group g) => (g, g) Source #

A unidirectional pattern synonym for elements of a group modulo commutators which are the identity.

Abelian groups

class Group a => AbelianGroup a Source #

Commutative Groups.

Instances of AbelianGroup satisfy the following laws:

Commutativity
x <> y = y <> x

Instances

Instances details
AbelianGroup Ordering Source # 
Instance details

Defined in Data.Group

AbelianGroup () Source # 
Instance details

Defined in Data.Group

AbelianGroup All Source # 
Instance details

Defined in Data.Group

AbelianGroup Any Source # 
Instance details

Defined in Data.Group

AbelianGroup (Predicate a) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Comparison a) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Equivalence a) Source # 
Instance details

Defined in Data.Group

AbelianGroup a => AbelianGroup (Identity a) Source # 
Instance details

Defined in Data.Group

AbelianGroup a => AbelianGroup (Dual a) Source # 
Instance details

Defined in Data.Group

AbelianGroup a => AbelianGroup (Endo a) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum Int) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum Int8) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum Int16) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum Int32) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum Int64) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum Integer) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum (Ratio Int)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum (Ratio Int8)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum (Ratio Int16)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum (Ratio Int32)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum (Ratio Int64)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum (Ratio Integer)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum (Ratio Word)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum (Ratio Word8)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum (Ratio Word16)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum (Ratio Word32)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum (Ratio Word64)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum Word) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum Word8) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum Word16) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum Word32) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Sum Word64) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Product (Ratio Int)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Product (Ratio Int8)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Product (Ratio Int16)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Product (Ratio Int32)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Product (Ratio Int64)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Product (Ratio Integer)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Product (Ratio Natural)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Product (Ratio Word)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Product (Ratio Word8)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Product (Ratio Word16)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Product (Ratio Word32)) Source # 
Instance details

Defined in Data.Group

AbelianGroup (Product (Ratio Word64)) Source # 
Instance details

Defined in Data.Group

AbelianGroup a => AbelianGroup (Down a) Source # 
Instance details

Defined in Data.Group

(Eq a, AbelianGroup a) => AbelianGroup (Abelianizer a) Source # 
Instance details

Defined in Data.Group

AbelianGroup a => AbelianGroup (Permutation a) Source # 
Instance details

Defined in Data.Group.Permutation

AbelianGroup b => AbelianGroup (a -> b) Source # 
Instance details

Defined in Data.Group

(AbelianGroup a, AbelianGroup b) => AbelianGroup (a, b) Source # 
Instance details

Defined in Data.Group

AbelianGroup a => AbelianGroup (Op a b) Source # 
Instance details

Defined in Data.Group

AbelianGroup a => AbelianGroup (Proxy a) Source # 
Instance details

Defined in Data.Group

(AbelianGroup a, AbelianGroup b, AbelianGroup c) => AbelianGroup (a, b, c) Source # 
Instance details

Defined in Data.Group

AbelianGroup a => AbelianGroup (Const a b) Source # 
Instance details

Defined in Data.Group

(AbelianGroup (f a), AbelianGroup (g a)) => AbelianGroup ((f :*: g) a) Source # 
Instance details

Defined in Data.Group

(AbelianGroup a, AbelianGroup b, AbelianGroup c, AbelianGroup d) => AbelianGroup (a, b, c, d) Source # 
Instance details

Defined in Data.Group

AbelianGroup (f (g a)) => AbelianGroup ((f :.: g) a) Source # 
Instance details

Defined in Data.Group

(AbelianGroup a, AbelianGroup b, AbelianGroup c, AbelianGroup d, AbelianGroup e) => AbelianGroup (a, b, c, d, e) Source # 
Instance details

Defined in Data.Group