combinat-0.2.8.1: Generate and manipulate various combinatorial objects.

Safe HaskellNone
LanguageHaskell2010

Math.Combinat.Groups.Free

Contents

Description

Words in free groups (and free powers of cyclic groups).

This module is not re-exported by Math.Combinat

Synopsis

Words

data Generator idx Source

A generator of a (free) group, indexed by which "copy" of the group we are dealing with.

Constructors

Gen !idx 
Inv !idx 

Instances

Functor Generator Source 
Eq idx => Eq (Generator idx) Source 
Ord idx => Ord (Generator idx) Source 
Read idx => Read (Generator idx) Source 
Show idx => Show (Generator idx) Source 

genIdx :: Generator idx -> idx Source

The index of a generator

genSign :: Generator idx -> Sign Source

The sign of the (exponent of the) generator (that is, the generator is Plus, the inverse is Minus)

absGen :: Generator idx -> Generator idx Source

keep the index, but return always the Gen one.

type Word idx = [Generator idx] Source

A word, describing (non-uniquely) an element of a group. The identity element is represented (among others) by the empty word.

showGen :: Generator Int -> Char Source

Generators are shown as small letters: a, b, c, ... and their inverses are shown as capital letters, so A=a^-1, B=b^-1, etc.

inverseGen :: Generator a -> Generator a Source

The inverse of a generator

inverseWord :: Word a -> Word a Source

The inverse of a word

allWords Source

Arguments

:: Int

g = number of generators

-> Int

n = length of the word

-> [Word Int] 

Lists all words of the given length (total number will be (2g)^n). The numbering of the generators is [1..g].

allWordsNoInv Source

Arguments

:: Int

g = number of generators

-> Int

n = length of the word

-> [Word Int] 

Lists all words of the given length which do not contain inverse generators (total number will be g^n). The numbering of the generators is [1..g].

Random words

randomGenerator Source

Arguments

:: RandomGen g 
=> Int

g = number of generators

-> g 
-> (Generator Int, g) 

A random group generator (or its inverse) between 1 and g

randomGeneratorNoInv Source

Arguments

:: RandomGen g 
=> Int

g = number of generators

-> g 
-> (Generator Int, g) 

A random group generator (but never its inverse) between 1 and g

randomWord Source

Arguments

:: RandomGen g 
=> Int

g = number of generators

-> Int

n = length of the word

-> g 
-> (Word Int, g) 

A random word of length n using g generators (or their inverses)

randomWordNoInv Source

Arguments

:: RandomGen g 
=> Int

g = number of generators

-> Int

n = length of the word

-> g 
-> (Word Int, g) 

A random word of length n using g generators (but not their inverses)

The free group on g generators

multiplyFree :: Eq idx => Word idx -> Word idx -> Word idx Source

Multiplication of the free group (returns the reduced result). It is true for any two words w1 and w2 that

multiplyFree (reduceWordFree w1) (reduceWord w2) = multiplyFree w1 w2

equivalentFree :: Eq idx => Word idx -> Word idx -> Bool Source

Decides whether two words represent the same group element in the free group

reduceWordFree :: Eq idx => Word idx -> Word idx Source

Reduces a word in a free group by repeatedly removing x*x^(-1) and x^(-1)*x pairs. The set of reduced words forms the free group; the multiplication is obtained by concatenation followed by reduction.

reduceWordFreeNaive :: Eq idx => Word idx -> Word idx Source

Naive (but canonical) reduction algorithm for the free groups

countIdentityWordsFree Source

Arguments

:: Int

g = number of generators in the free group

-> Int

n = length of the unreduced word

-> Integer 

Counts the number of words of length n which reduce to the identity element.

Generating function is Gf_g(u) = \frac {2g-1} { g-1 + g \sqrt{ 1 - (8g-4)u^2 } }

countWordReductionsFree Source

Arguments

:: Int

g = number of generators in the free group

-> Int

n = length of the unreduced word

-> Int

k = length of the reduced word

-> Integer 

Counts the number of words of length n whose reduced form has length k (clearly n and k must have the same parity for this to be nonzero):

countWordReductionsFree g n k == sum [ 1 | w <- allWords g n, k == length (reduceWordFree w) ]

Free powers of cyclic groups

multiplyZ2 :: Eq idx => Word idx -> Word idx -> Word idx Source

Multiplication in free products of Z2's

multiplyZ3 :: Eq idx => Word idx -> Word idx -> Word idx Source

Multiplication in free products of Z3's

multiplyZm :: Eq idx => Int -> Word idx -> Word idx -> Word idx Source

Multiplication in free products of Zm's

equivalentZ2 :: Eq idx => Word idx -> Word idx -> Bool Source

Decides whether two words represent the same group element in free products of Z2

equivalentZ3 :: Eq idx => Word idx -> Word idx -> Bool Source

Decides whether two words represent the same group element in free products of Z3

equivalentZm :: Eq idx => Int -> Word idx -> Word idx -> Bool Source

Decides whether two words represent the same group element in free products of Zm

reduceWordZ2 :: Eq idx => Word idx -> Word idx Source

Reduces a word, where each generator x satisfies the additional relation x^2=1 (that is, free products of Z2's)

reduceWordZ3 :: Eq idx => Word idx -> Word idx Source

Reduces a word, where each generator x satisfies the additional relation x^3=1 (that is, free products of Z3's)

reduceWordZm :: Eq idx => Int -> Word idx -> Word idx Source

Reduces a word, where each generator x satisfies the additional relation x^m=1 (that is, free products of Zm's)

reduceWordZ2Naive :: Eq idx => Word idx -> Word idx Source

Reduces a word, where each generator x satisfies the additional relation x^2=1 (that is, free products of Z2's). Naive (but canonical) algorithm.

reduceWordZ3Naive :: Eq idx => Word idx -> Word idx Source

Reduces a word, where each generator x satisfies the additional relation x^3=1 (that is, free products of Z3's). Naive (but canonical) algorithm.

reduceWordZmNaive :: Eq idx => Int -> Word idx -> Word idx Source

Reduces a word, where each generator x satisfies the additional relation x^m=1 (that is, free products of Zm's). Naive (but canonical) algorithm.

countIdentityWordsZ2 Source

Arguments

:: Int

g = number of generators in the free group

-> Int

n = length of the unreduced word

-> Integer 

Counts the number of words (without inverse generators) of length n which reduce to the identity element, using the relations x^2=1.

Generating function is Gf_g(u) = \frac {2g-2} { g-2 + g \sqrt{ 1 - (4g-4)u^2 } }

The first few g cases:

A000984 = [ countIdentityWordsZ2 2 (2*n) | n<-[0..] ] = [1,2,6,20,70,252,924,3432,12870,48620,184756...]
A089022 = [ countIdentityWordsZ2 3 (2*n) | n<-[0..] ] = [1,3,15,87,543,3543,23823,163719,1143999,8099511,57959535...]
A035610 = [ countIdentityWordsZ2 4 (2*n) | n<-[0..] ] = [1,4,28,232,2092,19864,195352,1970896,20275660,211823800,2240795848...]
A130976 = [ countIdentityWordsZ2 5 (2*n) | n<-[0..] ] = [1,5,45,485,5725,71445,925965,12335685,167817405,2321105525,32536755565...]

countWordReductionsZ2 Source

Arguments

:: Int

g = number of generators in the free group

-> Int

n = length of the unreduced word

-> Int

k = length of the reduced word

-> Integer 

Counts the number of words (without inverse generators) of length n whose reduced form in the product of Z2-s (that is, for each generator x we have x^2=1) has length k (clearly n and k must have the same parity for this to be nonzero):

countWordReductionsZ2 g n k == sum [ 1 | w <- allWordsNoInv g n, k == length (reduceWordZ2 w) ]

countIdentityWordsZ3NoInv Source

Arguments

:: Int

g = number of generators in the free group

-> Int

n = length of the unreduced word

-> Integer 

Counts the number of words (without inverse generators) of length n which reduce to the identity element, using the relations x^3=1.

countIdentityWordsZ3NoInv g n == sum [ 1 | w <- allWordsNoInv g n, 0 == length (reduceWordZ2 w) ]

In mathematica, the formula is: Sum[ g^k * (g-1)^(n-k) * k/n * Binomial[3*n-k-1, n-k] , {k, 1,n} ]