Saturday 25 July 2009

Strong generating sets for graph symmetries

[New release: HaskellForMaths 0.1.6 here]

Previously in this blog, we've been using two functions for finding generators for the group of symmetries of a graph. Both graphAuts2 and graphAuts3 use depth first search to find a transversal generating sequence - the only difference is that graphAuts3 does more pruning of the search tree, and so is faster.

A transversal generating sequence, remember, means this: If our vertices are labelled 1 to n, then we first try to find a symmetry that takes 1 to 2, then another that takes 1 to 3, and so on up to n; then looking only at those that leave 1 fixed, another which takes 2 to 3, then another which takes 2 to 4, and so on; then looking only at those that fix 1 and 2, another which takes 3 to 4, and so on; and so on. So the answer we get always takes the form of a series of levels - first, a set of symmetries taking 1 to some of [2..n], then a set of symmetries fix 1, and take 2 to some of [3..n], and so on.

Okay, so now suppose that we're doing our depth first search. Suppose that we have already found [[1,2],[3,4]], and [[1,3,2]]. Then in fact we don't need to search for a symmetry taking 1 to 4, because the two symmetries we know already generate one. Specifically:

> p [[1,3,2]] * p [[1,2],[3,4]]
[[1,4,3]]

So the point is that, as it happens, it was already possible to take 1 to 4 by repeated application of the symmetries we had already found to take 1 to 2 and 3.

Given a set of group elements, the orbit of a vertex is defined as those vertices that we can send it to by repeated application of the elements:

orbitV gs x = closure [x] [ (.^ g) | g <- gs ]


(This is using the closure algorithm that we defined previously. Recall that v .^ g means the image of v after action by g.)

This idea enables us to write an even faster graphAuts function. As before, we start by looking for symmetries that send 1 to 2, 1 to 3, and so on. However, this time, we don't bother to look for symmetries sending 1 to a vertex which is already in the orbit of the symmetries we have found.

An example will probably make this clearer. First of all, here is the full transversal generating set of symmetries of the cube:

> mapM_ print $ graphAuts3 $ q 3
[[0,1],[2,3],[4,5],[6,7]]
[[0,2,3,1],[4,6,7,5]]
[[0,3],[4,7]]
[[0,4,6,7,3,1],[2,5]]
[[0,5,3],[2,4,7]]
[[0,6,5,3],[1,2,4,7]]
[[0,7],[1,3],[2,5],[4,6]]
[[1,2],[5,6]]
[[1,4,2],[3,5,6]]
[[2,4],[3,5]]

The list consists of three levels: symmetries moving 0 to 1, 2, 3, 4, 5, 6, 7; symmetries fixing 0 and moving 1 to 2, 4; and a symmetry fixing 0 and 1 and moving 2 to 4. The sequence [0,1,2] is called the base for the TGS.

Now, here's what happens if we skip the search for vertices that are already in the orbit, using a new graphAuts function:

> mapM_ print $ graphAuts $ q 3
[[0,1],[2,3],[4,5],[6,7]]
[[0,2,3,1],[4,6,7,5]]
[[0,4,6,7,3,1],[2,5]]
[[1,2],[5,6]]
[[1,4,2],[3,5,6]]
[[2,4],[3,5]]

We still have three levels, with the same base, [0,1,2]. But in the first level, we haven't needed to find as many symmetries. After we found the 0 to 1 and 0 to 2 symmetries, we didn't need to find a 0 to 3 symmetry, because 3 was already in the orbit of the symmetries we had found. Then, after we had found the 0 to 4 symmetry, we didn't need to find the 0 to 5, 6, 7 symmetries.

> orbitV [ p [[0,1],[2,3],[4,5],[6,7]], p [[0,2,3,1],[4,6,7,5]], p [[0,4,6,7,3,1],[2,5]] ] 0
[0,1,2,3,4,5,6,7]

This new graphAuts function (I won't give the code, as it's really only a minor variation on the graphAuts3 function) is faster still, because we're now pruning the search tree even more.

However, it has lost the nice property of the graphAuts2 and graphAuts3 functions, that the returned list was a transversal generating sequence. Recall that a TGS made it particularly easy to work out the order of the group, or list its elements.

However all is not lost. We can easily reconstruct a TGS from the output of the graphAuts function. Consider that first level in the cube symmetries again. In the TGS, we had symmetries taking 0 to 1, 2, 3, 4, 5, 6, 7. The graphAuts function only returned symmetries taking 0 to 1, 2, 4. That was because it turned out that 3, 5, 6, 7 were already in the orbit of 0 under these symmetries. To reconstruct the TGS, what we need to do is, calculate the orbit of 0 under the 0 to 1, 2, 4 symmetries, but this time, keep track of the group elements as we go. For example, the reason 3 is in the orbit is that:

> p [[0,2,3,1],[4,6,7,5]] * p [[0,1],[2,3],[4,5],[6,7]]
[[0,3],[4,7]]

Here's the code. We find the base "bs" by looking at the minimum supports (the least vertex that is moved) of the inputs. We then sort the inputs into levels, using this base. Finally, for each level, we use a modified version of the closure algorithm, that tracks not only where we've got to in the orbit, but also how we got there.

tgsFromSgs sgs = concatMap transversal bs where
bs = toListSet $ map minsupp sgs
transversal b = closure b $ filter ( (b <=) . minsupp ) sgs
closure b gs = closure' M.empty (M.fromList [(b, 1)]) where
closure' interior boundary
| M.null boundary = filter (/=1) $ M.elems interior
| otherwise =
let interior' = M.union interior boundary
boundary' = M.fromList [(x .^ g, h*g) | (x,h) <- M.toList boundary, g <- gs] M.\\ interior'
in closure' interior' boundary'

A set of generators from which we can reconstruct a TGS in this way is called a strong generating set, or SGS. (Strictly speaking, an SGS is relative to a base - we've been using the base that is implied by the Ord instance and the minimum supports of the elements.)

In practice, we prefer to work with SGS than TGS, because they're shorter. Since you can so easily reconstruct a TGS from them, they're just as useful.

I should admit that I'm sidestepping a few subtleties here. The take-home message is:
  • A strong generating set is a set of generators for a group of a particularly useful form
  • The graphAuts function gives us a strong generating set by construction
That means that for symmetries of graphs, we are doing pretty well. We have an efficient algorithm (graphAuts) for finding a strong generating set for the symmetry group.

However, what we would like is, given just any set of generators for a group, to be able to construct a strong generating set. For that, we will need the Schreier-Sims algorithm. Next time, I'll show why this would be so useful, by looking at Rubik's cube.

Monday 20 July 2009

Faster graph symmetries using distance partitions

Up to now, we've been using the graphAuts2 function to find us a generating set (in fact a transversal generating sequence) for the symmetries of a graph. Unfortunately, graphAuts2 simply isn't fast enough for some of the larger graphs we would like to investigate. (I'll give an example at the end.) This week therefore, we're going to look at a more efficient way to find graph automorphisms, based on distance partitions.

Given a graph, the distance between vertices x and y is defined as the length of the shortest path between them - that is, the number of edges on the path. For example, in the cube shown below, the distance between the 0 and 7 vertices is 3. There are several routes, but each route involves passing along at least 3 edges. In HaskellForMaths, we can use the "distance" function to find this out:

> :load Math.Combinatorics.GraphAuts
> distance (q 3) 0 7
3

In the picture, we see that the vertices fall into four levels, depending on whether their distance from 0 is 0, 1, 2, or 3. Thus, distance from a given vertex can be used to partition the vertices in a graph. This is called the distance partition:

> distancePartition (q 3) 0
[[0],[1,2,4],[3,5,6],[7]]

(The implementation of distancePartition is a variant on the closure algorithm that we have seen a couple of times before, and is left as an exercise.)

Okay, so how do distance partitions help us with finding graph symmetries?

Well, recall that the way graphAuts2 works is, using depth-first search, try to find a symmetry that sends 0 to 1, another that sends 0 to 2, another that sends 0 to 3, and so on, then looking only at those that fix 0, another that sends 1 to 2, another that sends 1 to 3, and so on, then looking only at those that fix 0 and 1, another that sends 2 to 3, another that sends 2 to 4, and so on, and so on.

Well, the first step is to realise that graph symmetries must preserve distance. That is, if g is a symmetry, then we must have: distance x y = distance (x .^ g) (y .^ g). So, suppose that we are looking for a graph symmetry that sends 0 to 1, and we're wondering where to send x. Well, we need only consider those y such that distance 0 x = distance 1 y.

In terms of distance partitions, this means that, once we have decided to map 0 to 1, then we must map each cell in the distance partition of 0 to the corresponding cell in the distance partition of 1.

> distancePartition (q 3) 0
[[0],[1,2,4],[3,5,6],[7]]
> distancePartition (q 3) 1
[[1],[0,3,5],[2,4,7],[6]]

Specifically, we must map {1,2,4} to {0,3,5} (though not necessarily in that order), and {3,5,6} to {2,4,7}, and 7 to 6.

This is already going to cut down our search space considerably, perhaps especially on graphs with many vertices. However, we can go further.

Suppose now that we are looking for symmetries that send 0 to 0 and 1 to 1. Because they send 0 to 0, they must preserve the cells in the distance partition from 0. So they must send {1,2,4} to {1,2,4} (but not necessarily in that order), {3,5,6} to {3,5,6}, and 7 to 7. Also, because they send 1 to 1, they must preserve the cells in the distance partition from 1. So they must send {0,3,5} to {0,3,5}, {2,4,7} to {2,4,7}, and 6 to 6.

I think of this a being a bit like triangulation. Suppose we're wondering where to send 2 to. Well, looking at the distance partition from 0, we see that it must go to one of {1,2,4}. On the other hand, looking at the distance partition from 1, we see that it must go to one of {2,4,7}. So that actually narrows it down to {2,4}. (Yes, I know, in this case we could already see that, but you get the idea.) If we take another fix from a third point, that will narrow it down even further, and so on.

So the idea of our new graphAuts3 function will be as follows.
  • We will still start by trying to send 0 to 1, 2, 3, 4, 5, 6, 7, and finally 0.
  • If we're trying to send 0 to x, then when we come to wonder where to send 1, we'll consider only those y with distance x y = distance 0 1. In terms of the distance partition, this means that if 1 falls into cell d of the distance partition from 0, then y must fall into cell d of the distance partition from x.
  • As we successively decide where to send 1, 2, etc, we will "refine" the cells of the partition by triangulation with the new point.
The code for refining partitions is very simple:

refine p1 p2 = concat [ [c1 `intersect` c2 | c2 <- p2] | c1 <- p1]

For example:

> distancePartition (q 3) 0 `refine` distancePartition (q 3) 1
[[],[0],[],[],[1],[],[2,4],[],[],[3,5],[],[6],[],[],[7],[]]

We get quite a few empty lists in the refinement - they're a necessary evil, but we will remove them as we go along.

Okay, so here's our graphAuts3 function:

graphAuts3 g@(G vs es) = graphAuts' [] [vs] where
graphAuts' us ((x:ys):pt) =
let px = refine (ys : pt) (dps M.! x)
p y = refine ((x : L.delete y ys) : pt) (dps M.! y)
uus = zip us us
p' = L.sort $ filter (not . null) $ px
in concat [take 1 $ dfs ((x,y):uus) px (p y) | y <- ys]
++ graphAuts' (x:us) p'
graphAuts' us ([]:pt) = graphAuts' us pt
graphAuts' _ [] = []
dfs xys p1 p2
| map length p1 /= map length p2 = []
| otherwise =
let p1' = filter (not . null) p1
p2' = filter (not . null) p2
in if all isSingleton p1'
then let xys' = xys ++ zip (concat p1') (concat p2')
in if isCompatible xys' then [fromPairs' xys'] else []
else let (x:xs):p1'' = p1'
ys:p2'' = p2'
in concat [dfs ((x,y):xys)
(refine (xs : p1'') (dps M.! x))
(refine ((L.delete y ys):p2'') (dps M.! y))
| y <- ys]
isCompatible xys = and [([x,x'] `S.member` es') == (L.sort [y,y'] `S.member` es') | (x,y) <- xys, (x',y') <- xys, x < x']
dps = M.fromList [(v, distancePartition g v) | v <- vs]
es' = S.fromList es

It looks complicated (and perhaps I could tidy it up a little), but what it's doing is really fairly straightforward. Basically, we're still doing depth first search, in levels, as before. However, we're now maintaining two partitions as we go, the source partition p1 and the target partition p2, and we're constrained to map cells in the source partition to the corresponding cells in the target partition. If we ever find that the "shape" (map length) of the source and target partitions are different, then we know we have gone wrong and need to backtrack. Having satisfied ourselves that the shapes are the same, we can remove those pesky empty lists. Finally, as soon as we find that every cell is a singleton, then we can can shortcut any further search - although we still need to check that the implied mapping is a valid symmetry, to avoid false positives.

Okay, so how about a brief demonstration of its power. Time for a confession - on most of the smallish graphs that we've considered so far, graphAuts3 is actually slightly slower than graphAuts2. However, it's not too difficult to find larger graphs where it wins out.

The Kneser graphs are defined as follows:

kneser n k | 2*k <= n = graph (vs,es) where
vs = combinationsOf k [1..n]
es = [ [v1,v2] | [v1,v2] <- combinationsOf 2 vs, disjoint v1 v2]

So the Kneser graph has as vertices the k-subsets of [1..n], with edges joining subsets which are disjoint.

We've already met one of them - the Petersen graph is kneser 5 2. Kneser 7 3 is shown below - it has 35 vertices and 70 edges:

So here's an experiment you can try at home. Compare the running times of graphAuts2 and graphAuts3 on kneser 7 3. On my laptop, graphAuts3 manages to find a transversal generating set of 49 symmetries in less than a second. On the other hand, graphAuts2 had only managed to find 1 symmetry after 10 minutes, at which point I gave up.

Incidentally:

> orderTGS $ graphAuts3 $ kneser 7 3
5040

... which is 7 factorial. That's because the action of S 7 on [1..7] induces an action on kneser 7 3, and it turns out that every symmetry of kneser 7 3 arises from an underlying permutation of [1..7].

Anyway, with graphAuts3, and the orderTGS function from last time (for calculating the number of symmetries, given a transversal generating sequence), we are beginning to have the tools to investigate some larger graphs. However, there is another improvement we can make, which will lead us to strong generating sets and the Schreier-Sims algorithm - next time.

Wednesday 15 July 2009

Counting symmetries using transversals

Previously, we've been using the HaskellForMaths library's graphAuts2 function to find a generating set for the symmetries of a graph. The generating set returned by graphAuts2 has a particularly useful form, which I want to explore this week. Let's just remind ourselves how it works.

> :load Math.Combinatorics.GraphAuts
> mapM_ print $ graphAuts2 $ q 3
[[0,1],[2,3],[4,5],[6,7]]
[[0,2,3,1],[4,6,7,5]]
[[0,3],[4,7]]
[[0,4,6,7,3,1],[2,5]]
[[0,5,3],[2,4,7]]
[[0,6,5,3],[1,2,4,7]]
[[0,7],[1,3],[2,5],[4,6]]
[[1,2],[5,6]]
[[1,4,2],[3,5,6]]
[[2,4],[3,5]]
What graphAuts2 does is, it tries to find a symmetry which sends 0 to 1, another which sends 0 to 2, another which sends 0 to 3, and so on, then looking only at symmetries which leave 0 where it is, another which sends 1 to 2, another which sends 1 to 3, and so on, then leaving 0 and 1 where they are, another which sends 2 to 3, another which sends 2 to 4, and so on, and so on. Most of the time, it won't find all the symmetries it's looking for - as in this case.

Now, a few weeks back I set a puzzle: Given just the list returned by graphAuts2, how can I instantly tell how many symmetries there are in total?

Well, think of it like this.

First of all, I'm trying to find all the different places that I can move the 0 vertex to. Hopefully it's obvious that I can move the 0 vertex to any of the eight vertices. The first seven elements returned by graphAuts2 are symmetries which move 0 to 1,2,3,4,5,6,7 respectively - plus of course I can always just leave the cube as it is and leave 0 at 0.

Now, suppose that I have decided to leave 0 where it is. Next, I try to find all the different places that I can move 1 to, but leaving 0 where it is. If you look at the picture, I hope you can see that having fixed 0, our only choices for 1 are 1, 2, and 4. The next two elements returned by graphAuts2 are symmetries which move 1 to 2 and 4 respectively - plus of course, the identity element leaves the cube as it is, so leaves 0 at 0 and 1 at 1.

Now, suppose that I have decided to leave 0 and 1 where they are. Next I try to find all the different places that I can move 2 to. If you look at the picture, you'll see that if we fix 0 and 1, our only choices for 2 are 2 and 4. The identity leaves 2 where it is, and the last element returned by graphAuts2 moves 2 to 4.

Now, suppose that we decide to leave 0, 1 and 2 where they are. Next I try to find all the different places I can move 3 to. graphAuts2 didn't return any more elements. What it is telling us is that once I have decided to fix 0, 1, and 2, I have no choice but to fix 3 and all the other vertices too.

Okay, so how many symmetries are there in total? Well, I had 8 choices for the first vertex, then 3 choices for the second vertex, then 2 choices for the third vertex, then no more choices. So that gives us 8*3*2 = 48. Let's just check:

> length $ elts $ graphAuts2 $ q 3
48

We can write code to do this for us.

orderTGS tgs =
let transversals = map (1:) $ L.groupBy (\g h -> minsupp g == minsupp h) tgs
in product $ map L.genericLength transversals

This code needs a bit of explaining:
  • The order of a group means the number of elements. That's what we're trying to calculate.
  • TGS stands for transversal generating set. This is my name for a generating set of the type returned by graphAuts2. (I'll explain the name in a little bit.)
  • Given a TGS, the first thing we need to do is group the elements into levels based on what I call the minimum support - the least vertex that they move. In the case of the cube, we have three levels - seven elements that move 0, two elements that fix 0 and move 1, and one element that fixes 0 and 1 but moves 2
  • Next we add the identity element (called 1) to each level, to show that we can also just leave the vertex where it is
  • Finally, to calculate the order, we multiply the number of elements in each level.

> orderTGS $ graphAuts2 $ q 3
48

Let's think a little more about how this works. What are transversals, and what's so special about "transversal generating sets"? Well, consider the following picture:



On the left, the 48 dots represent the 48 symmetries of the cube. The eight columns divide the elements according to whether they send 0 to 0, 1, 2, 3, 4, 5, 6, or 7. The red dot in the top left is the identity, which sends 0 to 0. Then graphAuts2 finds us one dot (the blue one) in each column. So we have a representative from each column. This set of representatives is called a transversal.

Next, on the right, we confine our attention to only the first column, the elements that send 0 to 0. The three blocks divide the elements by whether they send 1 to 1, 2, or 4. The red dot in the top block is again the identity. Then graphAuts2 finds us a blue dot in each of the other two blocks. So we have another transversal.

Finally (not shown), we divide the top left block by whether the elements send 2 to 2 or 4. In this case we have just two divisions, consisting of a single element each - the identity, and the last element found by graphAuts2. Taken together, these two elements constitute our third transversal.

So a transversal generating set - it should really be called a transversal generating sequence, because the order matters - is a sequence of transversals (but omitting the identity), starting at the outermost layer and going successively inwards, that generates the group.

And now it should be totally clear why this method of calculating the order of the group works. The only thing which perhaps isn't clear is, how do we know that there are the same number of elements in each column, and in each block, at each stage? (This is clearly required, if the method is to work.) Well, the answer is simply that multiplication by the blue dot in any column gives a one-to-one correspondence between the elements in the left hand column and the elements in that column, so the number of elements must be the same.

As this last remark perhaps suggests, we can also use these transversals to list the elements of a group:

eltsTGS tgs =
let transversals = map (1:) $ L.groupBy (\g h -> minsupp g == minsupp h) tgs
in map product $ sequence transversals

So once again, we construct some transversals by grouping the TGS into levels, and then adding the identity to each level. Then what the last line is saying is, to get an element of the group, just pick an element from each of the transversals (levels), and multiply them together. To get all the elements of the group, consider all possible such choices.

The reason that transversal generating sets and the orderTGS function are important, is that they are the first step towards being able to work with large or very large groups. Previously, if we wanted to know how many elements there are in a group, we would have had to use the "elts" function to generate them all, and then count them. This is okay for small groups, but for graphs with thousands or millions of symmetries, it is not going to be practical. With the orderTGS function, we will be able to find out how many symmetries a graph has, even if it is in the thousands or millions, so long as we can find a TGS.

Our next stumbling block is that the graphAuts2 function itself is not efficient enough to handle these larger graphs. So next time, we'll look at a more efficient way to find a TGS for a graph. After that, we'll look at something called a strong generating set, and an algorithm called the Schreier-Sims algorithm, that can always find us a strong generating set, given only some generators for the group.

Wednesday 8 July 2009

Conjugacy classes, part 2

Last time we saw that the symmetries of a graph can be divided into conjugacy classes, where the elements of each class are somehow the same symmetry, just viewed from a different angle. This time we're going to look at the conjugacy classes of symmetries of a few simple graphs, to get more of a feel for how this works.

Let's start with the graph of the cube, otherwise known (in graph theory) as q 3. q n has as vertices all points in {0,1}n, with edges between pairs of vertices which differ in only one position:

q' k = graph (vs,es) where
vs = sequence $ replicate k [0,1]
es = [ [u,v] | [u,v] <- combinationsOf 2 vs, hammingDistance u v == 1 ]
hammingDistance as bs = length $ filter id $ zipWith (/=) as bs

For example:

> :load Math.Combinatorics.GraphAuts
> q' 3
G [[0,0,0],[0,0,1],[0,1,0],[0,1,1],[1,0,0],[1,0,1],[1,1,0],[1,1,1]]
[[[0,0,0],[0,0,1]],[[0,0,0],[0,1,0]],[[0,0,0],[1,0,0]],[[0,0,1],[0,1,1]],
[[0,0,1],[1,0,1]],[[0,1,0],[0,1,1]],[[0,1,0],[1,1,0]],[[0,1,1],[1,1,1]],
[[1,0,0],[1,0,1]],[[1,0,0],[1,1,0]],[[1,0,1],[1,1,1]],[[1,1,0],[1,1,1]]]

However, this is a bit hard to read, a jumble of 0s, 1s and square brackets, so we normally work over integers instead, by considering the sequences of 0s and 1s as the bits in the binary representation of a number:

> q 3
G [0,1,2,3,4,5,6,7]
[[0,1],[0,2],[0,4],[1,3],[1,5],[2,3],[2,6],[3,7],[4,5],[4,6],[5,7],[6,7]]


Okay, so we would like to investigate the symmetries of the cube, and as we saw last time, what we're really interested in is just the different classes of symmetry, rather than listing every single symmetry.

> mapM_ print $ conjClassReps $ graphAuts2 $ q 3
([],1)
([[0,1],[2,3],[4,5],[6,7]],3)
([[0,1],[2,5],[3,4],[6,7]],6)
([[0,1,3,2],[4,5,7,6]],6)
([[0,1,3,7,6,4],[2,5]],8)
([[0,3],[1,2],[4,7],[5,6]],3)
([[0,3,6,5],[1,2,7,4]],6)
([[0,3,6],[1,7,4]],8)
([[0,3],[4,7]],6)
([[0,7],[1,6],[2,5],[3,4]],1)

What we need to do is look at the representatives of each class, and try to understand what they are doing, so as to be able to give a textual description:
  • [] is the identity permutation, which leaves everything where it is
  • [[0,1],[2,3],[4,5],[6,7]] is a reflection in a plane midway between opposing faces. There are three such elements, because there are three pairs of opposing faces.
  • [[0,1],[2,5],[3,4],[6,7]] is a 180 degree rotation about an axis joining the midpoints of opposite edges. There are six elements, because there are six pairs of opposite edges.
  • [[0,1,3,2],[4,5,7,6]] is a 90 degree rotation about an axis through the centres of opposing faces. There are six faces (or three pairs of faces, with clockwise and anti-clockwise turns).
  • [[0,1,3,7,6,4],[2,5]] - this is an interesting one. There is a 6-cycle, so there's some sort of 60 degree rotation going on. But there is also a 2-cycle, so some sort of reflection or 180 degree rotation. If you think about it, you'll see that what is happening is that you're holding the cube by opposite corners (2 and 5 here), and spinning it by 60 degrees - but at the same time, reflecting it in the plane midway between.
  • Exercise: Finish off the list

Previously we saw that the automorphism group of the complete graph k n is the symmetric group S n.

The conjugacy classes of S n are particularly easy to understand. Let's look at an example:

> mapM_ print $ conjClassReps $ _S 5
([],1)
([[1,2]],10)
([[1,2],[3,4]],15)
([[1,2],[3,4,5]],20)
([[1,2,3]],20)
([[1,2,3,4]],30)
([[1,2,3,4,5]],24)

k 5 doesn't have an obvious spatial interpretation (unlike the pentagon and the cube that we have considered previously), so we're going to need a more abstract description of the classes.

Let's have a look at one of the classes:
> conjClass (_S 5) (p [[1,2]])
[[[1,2]],[[1,3]],[[1,4]],[[1,5]],[[2,3]],[[2,4]],[[2,5]],[[3,4]],[[3,5]],[[4,5]]]

There might be a slight surprise here. Surely [[1,2]] and [[1,3]] don't belong in the same class, you might think, because 1 and 2 are next to each other, and 1 and 3 aren't. Or to take another example, we have [[1,2,3,4,5]], and [[1,3,5,2,4]] in the same class - surely that can't be right - we saw when looking at c 5 that one is a 1/5 rotation, and the other is a 2/5 rotation.

Well, the first thing to point out is that we can be misled by the spatial representation of a graph. In the picture of k 5, it might look like the relationship between 1 and 2 is not the same as the relationship between 1 and 3. However, from the point of the view of the graph, it is. An alien who saw in graph space rather than in 2-d or 3-d space wouldn't be able to tell a difference.

Another thing to emphasize is that conjugacy classes are relative to the group you're working in. For example, the elements [[1,2,3,4,5]] and [[1,3,5,2,4]] occur in both S 5 and D 10 (the symmetry group of c 5). In S 5, they are in the same conjugacy class, but in D 10, they are not. Specifically, we have:

> p [[1,2,3,4,5]] ~^ p [[2,3,5,4]]
[[1,3,5,2,4]]

[[2,3,5,4]] is an element of S 5, so [[1,2,3,4,5]] and [[1,3,5,2,4]] are conjugate in S 5. However, [[2,3,5,4]] is not an element of D 10, so they are not conjugate in D 10.

We can translate this back to our intuition about conjugate elements "looking the same but from a different angle". We have our alien who sees in graph space. When our alien is sitting in the graph space k 5, then [[2,3,5,4]], being a symmetry of the graph, is a transformation that moves the graph to a different angle. On the other hand, in the graph space c 5, [[2,3,5,4]] is not a symmetry - instead of moving the graph to a different angle, it just crumples the graph up.

Let's look a little more closely at that conjugation operation again:

> p [[1,2,3,4,5]] ~^ p [[2,3,5,4]]
[[1,3,5,2,4]]

Let's compare where we started - [[1,2,3,4,5]] - with where we ended - [[1,3,5,2,4]] - what has changed? Well, the 2 turned into a 3, the 3 turned into a 5, the 5 turned into a 4, and the 4 turned into a 2. So conjugating by [[2,3,5,4]] has the same effect as actually applying [[2,3,5,4]] to each of the numbers in the cycle notation for [[1,2,3,4,5]].

Why is this? Well, remember that:

g ~^ h = h^-1 * g * h

So if h is [[2,3,5,4]], what this says is:
  • First, undo [[2,3,5,4]]. That is, put 3 into the 2 position, 5 into the 3 position, and so on.
  • Next, do g. But if g says to do something to 2, we'll actually be doing it to 3, which is in the 2 position, and so on.
  • Finally, do [[2,3,5,4]]. So put whatever's in the 2 position back into the 3 position, put what's in the 3 position back in the 5 position, and so on.
For example, if g = [[1,2,3,4,5]], then the overall effect on 3 is: put into the 2 position (h^-1), then put into the 3 position (g), then put into the 5 position (h). Notice the way that 3 gets off the merry-go-round at one point, but gets on again at a different point, because someone rearranged the chairs in the middle.

Well anyway, I'm sure if you think about it hard enough, you'll get it.

Getting back to the conjugacy classes of S n, it turns out that a conjugacy class in S n just consists of all elements having the same "cycle shape". For example, the class of [[1,2]] consists of all elements having a single 2-cycle. The class of [[1,2],[3,4]] consists of all elements having two 2-cycles. The class of [[1,2],[3,4,5]] consists of all elements having a 2-cycle and a 3-cycle.

The reason for this should now be obvious. To get from [[1,2],[3,4,5]] to [[a,b],[c,d,e]], you just need to find the permutation that sends 1 to a, 2 to b, 3 to c, 4 to d, and 5 to e. Since S 5 contains all permutations of [1..5], this permutation must be among them.

Hope that all made sense.

Friday 3 July 2009

Conjugacy classes, part 1

(New release: HaskellForMaths 0.1.5 is available here, or here.)

Over the last few weeks, we've been looking at the HaskellForMaths code for specifying graphs, and then finding generators for their automorphism groups. However, in our hurry, we haven't really stopped to take a good look at those automorphisms (symmetries) themselves.

For example, consider our old favourite, the pentagon c 5.

> :load Math.Combinatorics.GraphAuts
> mapM_ print $ elts $ graphAuts2 $ c 5
[]
[[1,2],[3,5]]
[[1,2,3,4,5]]
[[1,3,5,2,4]]
[[1,3],[4,5]]
[[1,4],[2,3]]
[[1,4,2,5,3]]
[[1,5,4,3,2]]
[[1,5],[2,4]]
[[2,5],[3,4]]

We can divide the symmetries of c 5 into four different classes:
  • The identity permutation, [] or 1, which leaves c 5 as it is
  • Five reflections, which reflect everything in the axis joining a vertex and the midpoint of the opposite edge. For example, [[2,5],[3,4]] is the reflection in the vertical axis.
  • Two 1/5 rotations [[1,2,3,4,5]] and [[1,5,4,3,2]]
  • Two 2/5 rotations [[1,3,5,2,4]] and [[1,4,2,5,3]]
Within each of these four classes, the symmetries are in some sense the same symmetry, just viewed from a different angle. What I see as the reflection in the vertical axis looks just like the reflection in one of the diagonal axes to someone sitting at a different chair around the table. What I see as the clockwise 1/5 rotation looks like an anti-clockwise 1/5 rotation to someone looking from behind the glass.

So the intuition we're trying to capture is that among the symmetries of a given graph, there are several different classes, but within each class, the symmetries are somehow the same, just viewed from a different angle. In group theory, these are called conjugacy classes, and that's what I want to explore this week.

Let's look at an example in more detail. What does it mean to say that the reflection [[2,5],[3,4]] in the vertical axis, and the reflection [[1,2],[3,5]] in the 36 degree axis are somehow the same. Well I think of it like this.

Suppose that I'm sitting at the bottom of the table (between the 3 and the 4), with a camera, and I take a short movie of the [[2,5],[3,4]] reflection as it takes place. Now, suppose that instead, I go and sit between the 1 and the 2, and then take a movie of the [[1,2],[3,5]] reflection. The two movies are both going to look like reflection in the vertical axis - because from the camera viewpoint, that's what they both were.

Next, suppose that instead of me moving to another chair to get my view, we move the table back round to me. So I rotate the table (and the graph) by a 2/5 clockwise turn, so that the 1 and 2 are either side of me. Then I perform the [[2,5],[3,4]] reflection in the vertical axis, and take my movie of it. Then I move the table back by a 2/5 anti-clockwise turn. So I still get a movie of a reflection in the vertical axis. But the overall effect on the graph is actually the [[1,2],[3,5]] reflection.

Now, the key point is that when I moved the table at the beginning, I was doing a graph symmetry (2/5 clockwise turn). And when I moved the table back again at the end, I was just undoing the symmetry.

We will say that symmetries g1 and g2 are somehow the same if there is a symmetry h such that:
doing h, then doing g1, then undoing h is the same as doing g2.
In our example:
doing [[1,3,5,2,4]], then [[2,5],[3,4]], then undoing [[1,3,5,2,4]] is the same as doing [[1,2],[3,5]].

Or, in the language of group theory, we will say that g1 and g2 are conjugate if there is an h such that:
h * g1 * h^-1 = g2
In our example:
> p [[1,3,5,2,4]] * p [[2,5],[3,4]] * p [[1,3,5,2,4]] ^-1 == p [[1,2],[3,5]]
True

In HaskellForMaths, the conjugate of g by h is defined as follows:
g ~^ h = h^-1 * g * h
(Note that we now put the h^-1 in front and the h behind the g, as is customary in the literature. Clearly this makes no real difference to what's going on.)

Conjugacy is an equivalence relation. That is:
  • It is reflexive - g is conjugate to itself (taking h = 1)
  • It is symmetric - if g1 is conjugate to g2 then g2 is conjugate to g1 (replacing h by h^-1)
  • It is transitive - if g1 is conjugate to g2 (by h), and g2 is conjugate to g3 (by k), then g1 is conjugate to g3 (by h*k)
Perhaps at this point, it's worth mentioning the mnemonic for some of these symbolic operators we've seen. Suppose that we have a vertex v, and edge e, and permutations g and h. Then:
  • v .^ g means the image of the vertex v when acted on by g. The dot is meant to represent a vertex.
  • e -^ g means the image of the edge e when acted on by g. The dash is meant to represent an edge.
  • g ~^ h means the conjugate of g by h. The tilde is meant to remind you of conjugacy because tilde is the customary symbol for an equivalence relation.
Next, we would like to be able to find the conjugacy classes of a group. To do this, we first introduce a very useful auxiliary function:
import qualified Data.Set as S

closure xs fs = closure' S.empty (S.fromList xs) where
closure' interior boundary
| S.null boundary = S.toList interior
| otherwise =
let interior' = S.union interior boundary
boundary' = S.fromList [f x | x <- S.toList boundary, f <- fs] S.\\ interior'
in closure' interior' boundary'
What closure is doing is, starting with a set xs, it is repeatedly growing the set by adding new elements f x, by applying the functions fs - until we get to the point where the set is closed, meaning that for every x in the set, f x is also already in the set.

We've already been using this. The "elts" function that we've been using to list all elements of the group generated by gs, can be defined as follows:

elts gs = closure [1] [ *g | g <- gs]


It is now straightforward to calculate the conjugacy class of an element h in the group generated by gs:

conjClass gs h = closure [h] [ ~^ g | g <- gs]

For example:

> conjClass (graphAuts2 $ c 5) (p [[1,2,3,4,5]])
[[[1,2,3,4,5]],[[1,5,4,3,2]]]

Now, given a group of graph automorphisms, what we would like to do is find all the conjugacy classes, so that we can understand the different types of symmetry that the graph has. However, we don't really need to list all the elements of each conjugacy class - it will be sufficient to have a single representative of each class, and perhaps also to know how many elements are in that class.

conjClassReps gs = conjClassReps' (elts gs) where
conjClassReps' (h:hs) =
let cc = conjClass gs h in (h, length cc) : conjClassReps' (hs \\ cc)
conjClassReps' [] = []

Okay, so let's test it out.

> mapM_ print $ conjClassReps $ graphAuts2 $ c 5
([],1)
([[1,2],[3,5]],5)
([[1,2,3,4,5]],2)
([[1,3,5,2,4]],2)

These are the four classes that we identified at the beginning.

To summarise, conjugacy classes give us a way to investigate the different types of symmetries that a graph has. (Later on, we'll use groups and conjugacy classes to study the symmetries of other objects besides graphs.)

That's it for now. Next time, we'll look at a few more examples.

Exercise: Investigate the conjugacy classes of symmetries of the cube, q 3. Describe the different classes.
Hint: Start by typing:
> mapM_ print $ conjClassReps $ graphAuts2 $ q 3

Followers