groups-0.5.2: Groups
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Group

Synopsis

Documentation

class Monoid m => Group m where Source #

A Group is a Monoid plus a function, invert, such that:

a <> invert a == mempty
invert a <> a == mempty

Minimal complete definition

invert

Methods

invert :: m -> m Source #

(~~) :: m -> m -> m infixl 7 Source #

Group subtraction: x ~~ y == x <> invert y

pow :: Integral x => m -> x -> m Source #

pow a n == a <> a <> ... <> a
 (n lots of a)

If n is negative, the result is inverted.

Instances

Instances details
Group () Source # 
Instance details

Defined in Data.Group

Methods

invert :: () -> () Source #

(~~) :: () -> () -> () Source #

pow :: Integral x => () -> x -> () Source #

Group a => Group (Identity a) Source #

Identity lifts groups pointwise (at only one point).

Instance details

Defined in Data.Group

Methods

invert :: Identity a -> Identity a Source #

(~~) :: Identity a -> Identity a -> Identity a Source #

pow :: Integral x => Identity a -> x -> Identity a Source #

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

Defined in Data.Group

Methods

invert :: Dual a -> Dual a Source #

(~~) :: Dual a -> Dual a -> Dual a Source #

pow :: Integral x => Dual a -> x -> Dual a Source #

Num a => Group (Sum a) Source # 
Instance details

Defined in Data.Group

Methods

invert :: Sum a -> Sum a Source #

(~~) :: Sum a -> Sum a -> Sum a Source #

pow :: Integral x => Sum a -> x -> Sum a Source #

Fractional a => Group (Product a) Source # 
Instance details

Defined in Data.Group

Methods

invert :: Product a -> Product a Source #

(~~) :: Product a -> Product a -> Product a Source #

pow :: Integral x => Product a -> x -> Product a Source #

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

Defined in Data.Group

Methods

invert :: Down a -> Down a Source #

(~~) :: Down a -> Down a -> Down a Source #

pow :: Integral x => Down a -> x -> Down a Source #

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

Defined in Data.Group

Methods

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

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

pow :: Integral x => (a -> b) -> x -> a -> b Source #

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

Defined in Data.Group

Methods

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

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

pow :: Integral x => (a, b) -> x -> (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 #

(~~) :: Op a b -> Op a b -> Op a b Source #

pow :: Integral x => Op a b -> x -> Op a b Source #

Group (Proxy x) Source #

Trivial group, Functor style.

Instance details

Defined in Data.Group

Methods

invert :: Proxy x -> Proxy x Source #

(~~) :: Proxy x -> Proxy x -> Proxy x Source #

pow :: Integral x0 => Proxy x -> x0 -> Proxy x 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 #

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

pow :: Integral x => (a, b, c) -> x -> (a, b, c) Source #

Group a => Group (Const a x) Source #

Const lifts groups into a functor.

Instance details

Defined in Data.Group

Methods

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

(~~) :: Const a x -> Const a x -> Const a x Source #

pow :: Integral x0 => Const a x -> x0 -> Const a x Source #

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

Product of groups, Functor style.

Instance details

Defined in Data.Group

Methods

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

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

pow :: Integral x => (f :*: g) a -> x -> (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 #

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

pow :: Integral x => (a, b, c, d) -> x -> (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 #

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

pow :: Integral x => (f :.: g) a -> x -> (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 #

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

pow :: Integral x => (a, b, c, d, e) -> x -> (a, b, c, d, e) Source #

class Group g => Abelian g Source #

An Abelian group is a Group that follows the rule:

a <> b == b <> a

Instances

Instances details
Abelian () Source # 
Instance details

Defined in Data.Group

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

Defined in Data.Group

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

Defined in Data.Group

Num a => Abelian (Sum a) Source # 
Instance details

Defined in Data.Group

Fractional a => Abelian (Product a) Source # 
Instance details

Defined in Data.Group

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

Defined in Data.Group

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

Defined in Data.Group

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

Defined in Data.Group

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

Defined in Data.Group

Abelian (Proxy x) Source # 
Instance details

Defined in Data.Group

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

Defined in Data.Group

Abelian a => Abelian (Const a x) Source # 
Instance details

Defined in Data.Group

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

Defined in Data.Group

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

Defined in Data.Group

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

Defined in Data.Group

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

Defined in Data.Group

class Group a => Cyclic a where Source #

A Group G is Cyclic if there exists an element x of G such that for all y in G, there exists an n, such that

y = pow x n

Methods

generator :: a Source #

The generator of the Cyclic group.

Instances

Instances details
Cyclic () Source # 
Instance details

Defined in Data.Group

Methods

generator :: () Source #

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

Defined in Data.Group

Integral a => Cyclic (Sum a) Source # 
Instance details

Defined in Data.Group

Methods

generator :: Sum a Source #

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

Defined in Data.Group

Methods

generator :: Down a Source #

Cyclic (Proxy x) Source # 
Instance details

Defined in Data.Group

Methods

generator :: Proxy x Source #

Cyclic a => Cyclic (Const a x) Source # 
Instance details

Defined in Data.Group

Methods

generator :: Const a x Source #

generated :: Cyclic a => [a] Source #

Generate all elements of a Cyclic group using its generator.

Note: Fuses, does not terminate even for finite groups.

generated' :: (Eq a, Cyclic a) => [a] Source #

Lazily generate all elements of a Cyclic group using its generator.

Note: Fuses, terminates if the underlying group is finite.