HaskellForMaths-0.4.8: Combinatorics, group theory, commutative algebra, non-commutative algebra

Safe HaskellNone
LanguageHaskell98

Math.Algebra.Group.PermutationGroup

Description

A module for doing arithmetic in permutation groups.

Group elements are represented as permutations of underlying sets, and are entered and displayed using a Haskell-friendly version of cycle notation. For example, the permutation (1 2 3)(4 5) would be entered as p [[1,2,3],[4,5]], and displayed as [[1,2,3],[4,5]]. Permutations can be defined over arbitrary underlying sets (types), not just the integers.

If g and h are group elements, then the expressions g*h and g^-1 calculate product and inverse respectively.

Synopsis

Documentation

rotateL :: [a] -> [a] Source

newtype Permutation a Source

A type for permutations, considered as functions or actions which can be performed on an underlying set.

Constructors

P (Map a a) 

Instances

(Eq k, Num k) => HopfAlgebra k (Permutation Int) 
(Eq k, Num k) => Bialgebra k (Permutation Int) 
(Eq k, Num k) => Coalgebra k (Permutation Int) 
(Eq k, Num k) => Algebra k (Permutation Int) 
(Eq k, Num k) => Module k (Permutation Int) Int 
(Eq k, Num k) => Module k (Permutation Int) [Int] 
Eq a => Eq (Permutation a) 
Ord a => Num (Permutation a)

The Num instance is what enables us to write g*h for the product of group elements and 1 for the group identity. Unfortunately we can't of course give sensible definitions for the other functions declared in the Num typeclass.

Ord a => Ord (Permutation a) 
(Ord a, Show a) => Show (Permutation a) 
Ord a => HasInverses (Permutation a)

The HasInverses instance is what enables us to write g^-1 for the inverse of a group element.

HasInverses (GroupAlgebra Q)

Note that the inverse of a group algebra element can only be efficiently calculated if the group generated by the non-zero terms is very small (eg <100 elements).

fmapP :: Ord a => (t -> a) -> Permutation t -> Permutation a Source

p :: Ord a => [[a]] -> Permutation a Source

Construct a permutation from a list of cycles. For example, p [[1,2,3],[4,5]] returns the permutation that sends 1 to 2, 2 to 3, 3 to 1, 4 to 5, 5 to 4.

fromPairs :: Ord a => [(a, a)] -> Permutation a Source

fromPairs' :: Ord a => [(a, a)] -> Permutation a Source

toPairs :: Permutation a -> [(a, a)] Source

fromList :: Ord a => [a] -> Permutation a Source

supp :: Permutation a -> [a] Source

(.^) :: Ord a => a -> Permutation a -> a Source

x .^ g returns the image of a vertex or point x under the action of the permutation g. For example, 1 .^ p [[1,2,3]] returns 2. The dot is meant to be a mnemonic for point or vertex.

(-^) :: Ord a => [a] -> Permutation a -> [a] Source

b -^ g returns the image of an edge or block b under the action of the permutation g. For example, [1,2] -^ p [[1,4],[2,3]] returns [3,4]. The dash is meant to be a mnemonic for edge or line or block.

fromCycles :: Ord a => [[a]] -> Permutation a Source

toCycles :: Ord a => Permutation a -> [[a]] Source

cycleOf :: Ord a => Permutation a -> a -> [a] Source

sign :: (Ord a1, Num a) => Permutation a1 -> a Source

(~^) :: Ord a => Permutation a -> Permutation a -> Permutation a infix 8 Source

g ~^ h returns the conjugate of g by h, that is, h^-1*g*h. The tilde is meant to a mnemonic, because conjugacy is an equivalence relation.

comm :: (HasInverses a, Num a) => a -> a -> a Source

closureS :: Ord a => [a] -> [a -> a] -> Set a Source

closure :: Ord a => [a] -> [a -> a] -> [a] Source

orbit :: Ord a => (a -> t -> a) -> a -> [t] -> [a] Source

(.^^) :: Ord a => a -> [Permutation a] -> [a] Source

x .^^ gs returns the orbit of the point or vertex x under the action of the gs

orbitP :: Ord a => [Permutation a] -> a -> [a] Source

orbitV :: Ord a => [Permutation a] -> a -> [a] Source

(-^^) :: Ord a => [a] -> [Permutation a] -> [[a]] Source

b -^^ gs returns the orbit of the block or edge b under the action of the gs

orbitB :: Ord a => [Permutation a] -> [a] -> [[a]] Source

orbitE :: Ord a => [Permutation a] -> [a] -> [[a]] Source

action :: Ord a => [a] -> (a -> a) -> Permutation a Source

orbits :: Ord a => [Permutation a] -> [[a]] Source

_C :: Integral a => a -> [Permutation a] Source

_C n returns generators for Cn, the cyclic group of order n

_D :: Integral a => a -> [Permutation a] Source

_D2 :: Integral a => a -> [Permutation a] Source

_S :: Integral a => a -> [Permutation a] Source

_S n returns generators for Sn, the symmetric group on [1..n]

_A :: Integral a => a -> [Permutation a] Source

_A n returns generators for An, the alternating group on [1..n]

dp :: (Ord a, Ord b) => [Permutation a] -> [Permutation b] -> [Permutation (Either a b)] Source

Given generators for groups H and K, acting on sets A and B respectively, return generators for the direct product H*K, acting on the disjoint union A+B (= Either A B)

wr :: (Ord t1, Ord t) => [Permutation t] -> [Permutation t1] -> [Permutation (t, t1)] Source

toSn :: (Ord a, Ord k, Num a, Enum a) => [Permutation k] -> [Permutation a] Source

fromDigits' :: Num a => [a] -> a Source

fromBinary' :: Num a => [a] -> a Source

elts :: (Num a, Ord a) => [a] -> [a] Source

Given generators for a group, return a (sorted) list of all elements of the group. Implemented using a naive closure algorithm, so only suitable for small groups (|G| < 10000)

eltsS :: (Ord a, Num a) => [a] -> Set a Source

order :: (Num a, Ord a) => [a] -> Int Source

Given generators for a group, return the order of the group (the number of elements). Implemented using a naive closure algorithm, so only suitable for small groups (|G| < 10000)

isMember :: (Ord a, Num a) => [a] -> a -> Bool Source

orderTGS :: (Ord a, Num a1) => [Permutation a] -> a1 Source

orderSGS :: Ord a => [Permutation a] -> Integer Source

Given a strong generating set, return the order of the group it generates. Note that the SGS is assumed to be relative to the natural order of the points on which the group acts.

orderBSGS :: Ord a => ([a], [Permutation a]) -> Integer Source

Given a base and strong generating set, return the order of the group it generates.

gens :: (Ord a, Num a) => [a] -> [a] Source

conjClassReps :: (Ord a, Show a) => [Permutation a] -> [(Permutation a, Int)] Source

conjClassReps gs returns conjugacy class representatives and sizes for the group generated by gs. This implementation is only suitable for use with small groups (|G| < 10000).

reduceGens :: (Ord a, Num a) => [a] -> [a] Source

isSubgp :: (Ord a, Num a) => [a] -> [a] -> Bool Source

subgps :: (Ord a, Show a) => [Permutation a] -> [[Permutation a]] Source

Return the subgroups of a group. Only suitable for use on small groups (eg < 100 elts)

centralizer :: (Ord t, Num t) => [t] -> [t] -> [t] Source

centre :: (Ord t, Num t) => [t] -> [t] Source

stabilizer :: Ord a => [Permutation a] -> a -> [Permutation a] Source

ptStab :: Ord a => [Permutation a] -> [a] -> [Permutation a] Source

setStab :: Ord a => [Permutation a] -> [a] -> [Permutation a] Source

(-*-) :: (Ord b, Num b) => [b] -> [b] -> [b] Source

(-*) :: (Ord a, Num a) => [a] -> a -> [a] Source

(*-) :: (Ord a, Num a) => a -> [a] -> [a] Source

isNormal :: (Ord a, Show a) => [Permutation a] -> [Permutation a] -> Bool Source

isNormal gs ks returns True if <ks> is normal in <gs>. Note, it is caller's responsibility to ensure that <ks> is a subgroup of <gs> (ie that each k is in <gs>).

normalSubgps :: (Ord a, Show a) => [Permutation a] -> [[Permutation a]] Source

Return the normal subgroups of a group. Only suitable for use on small groups (eg < 100 elts)

isSimple :: (Show a, Ord a) => [Permutation a] -> Bool Source

cosets :: (Ord t, Num t) => [t] -> [t] -> [[t]] Source

quotientGp :: (Ord a, Show a) => [Permutation a] -> [Permutation a] -> [Permutation Int] Source

quotientGp gs ks returns <gs> / <ks>

(//) :: (Ord a, Show a) => [Permutation a] -> [Permutation a] -> [Permutation Int] Source

Synonym for quotientGp

subgpAction :: (Ord a1, Ord a, Num a1, Enum a1) => [Permutation a] -> [Permutation a] -> [Permutation a1] Source

rrpr :: (Ord a, Num a) => [a] -> a -> Permutation a Source

rrpr' :: (Ord a, Num a) => [a] -> a -> Permutation a Source

permutationMatrix :: (Ord a, Num t) => [a] -> Permutation a -> [[t]] Source