Saturday 27 June 2009

Direct products revisited

One of the things I talked about last time was the cartesian product of permutation groups. Unfortunately, I got a bit confused, and probably managed to confuse everyone else too. So I thought it might be a good idea to have another go, coming from another angle.

Given two graphs g1 and g2, we can form a graph g1+g2, just by placing them side by side. For example, here's what c 4 + c 5 looks like:

It's important that you see this as a single graph with 9 vertices, rather than as two graphs with four and five vertices. Unlike the graphs we have looked at previously, this graph is not connected.

When we're writing the Haskell code for this sum of two graphs, we need to be careful. What if the vertices in the two graphs are using the same labels. In this case, c4 has vertices [1..4], c 5 has vertices [1..5]. If we're not careful, we might get this graph instead:


We need to take a disjoint union of the vertices, even if in fact they are using the same labels. The way to do this is to use Either.

So, here's the code for the disjoint sum of two graphs:

dsum g1 g2 = graph (vs,es) where
vs = map Left (vertices g1) ++ map Right (vertices g2)
es = (map . map) Left (edges g1) ++ (map . map) Right (edges g2)

And here it is in action:

> dsum (c 4) (c 5)
G [Left 1,Left 2,Left 3,Left 4,Right 1,Right 2,Right 3,Right 4,Right 5]
[[Left 1,Left 2],[Left 1,Left 4],[Left 2,Left 3],[Left 3,Left 4],
[Right 1,Right 2],[Right 1,Right 5],[Right 2,Right 3],[Right 3,Right 4],[Right 4,Right 5]]

Notice how, as required, our new graph has nine vertices.

Now, what are the symmetries of g1+g2 going to look like? Well suppose we already know the symmetry group of g1 - call it H - and the symmetry group of g2 - call it K. Hopefully it's obvious that given any h from H, and k from K - symmetries of g1 and g2 respectively - then doing h to the left hand side and k to the right hand side of g1+g2 will be a symmetry.

So we can think of the symmetry group of g1+g2 as consisting of elements (h,k), where we do h to the left hand side and k to the right hand side. If we do (h1,k1) then (h2,k2), it's the same as doing (h1 then h2, k1 then k2). Or, in group language, (h1,k1)*(h2,k2) = (h1*h2,k1*k2).

Another way to think about this. Normally, if we have two symmetries a and b, it matters what order we do them in. a*b (a then b) isn't necessarily the same as b*a (b then a). However, if a is a symmetry of the left hand side, and b is a symmetry of the right hand side, then the order doesn't matter. a*b = b*a. We say that a and b commute. The reason the order doesn't matter is that a is moving only left hand vertices and edges, and b is moving only right hand vertices and edges.

Because of this, there's no need to write the elements as (h,k), we can just write them as h*k. Then h1*k1 * h2*k2 = h1*h2 * k1*k2 (since we know hs and ks commute).

In this case, the symmetry group of g1+g2 is the direct product of the symmetry group of g1 and the symmetry group of g2. (Last time, I incorrectly called this the cartesian product.) In Haskell:

dp hs ks =
[P $ M.fromList $ map (\(x,x') -> (Left x,Left x')) $ M.toList h' | P h' <- hs] ++
[P $ M.fromList $ map (\(y,y') -> (Right y,Right y')) $ M.toList k' | P k' <- ks]

Recall that in HaskellForMaths, permutations are implemented using Data.Map. What this is saying is that we change all the (x,x') mappings in the permutations in the first group to (Left x, Left x') mappings, and all the (y,y') mappings in the second group to (Right y, Right y') mappings. The construction ensures that the elements of h and the elements of k are acting on disjoint sets, so they will commute with one another. Hopefully you can see that the the group calculated by this function is (isomorphic to) the direct product.
(This function is called "cp" in HaskellForMaths 0.1.3, but I'll change it to "dp" in the next release.)

As expected, we have:

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

> mapM_ print $ graphAuts2 (c 4) `dp` graphAuts2 (c 5)
[[Left 1,Left 2],[Left 3,Left 4]]
[[Left 1,Left 3]]
[[Left 1,Left 4,Left 3,Left 2]]
[[Left 2,Left 4]]
[[Right 1,Right 2],[Right 3,Right 5]]
[[Right 1,Right 3],[Right 4,Right 5]]
[[Right 1,Right 4],[Right 2,Right 3]]
[[Right 1,Right 5,Right 4,Right 3,Right 2]]
[[Right 2,Right 5],[Right 3,Right 4]]

They're the same.

The number of elements in a group is called its order:

order gs = length $ elts gs

(Remember that we always represent a group by a list of generators. "order" calculates how many elements are in the group generated by gs.)

The direct product of H and K consists of all pairs hk or (h,k) from h and k. We're guaranteed that (h1,k1) /= (h2,k2), unless h1=h2 and k1=k2. Hence we will always find
order (hs `dp` ks) == order hs * order ks

So that's the direct product. Now, last time, we were looking at the complete bipartite graphs kb m n. In this graph, any permutation of the left vertices among themselves, together with any permutation of the right vertices among themselves, is a symmetry of the graph.

The set of all permutations of [1..n] is called S n. So what we're saying is that the symmetry group of kb m n contains
_S m `dp` _S n

Hopefully that makes a little more sense now.

Friday 26 June 2009

Some groups and some graphs

(Spoiler alert: Solutions to last week's exercise coming up.)

Previously we looked at the graphAuts1 function, which lists all symmetries of a graph, and the graphAuts2 function, which lists a set of generators for the symmetry group of a graph: that is, a few symmetries, from which all the rest can be generated as products / sequences.

This time we're going to start looking at some particular graphs.

Recall that the complete graph, k n, is the graph on n vertices which has every possible edge.
k n = graph (vs,es) where
vs = [1..n]
es = combinationsOf 2 vs
For example:

> k 5
G [1,2,3,4,5]
[[1,2],[1,3],[1,4],[1,5],[2,3],[2,4],[2,5],[3,4],[3,5],[4,5]]


If we look at the symmetries of this graph:

> mapM_ print $ graphAuts2 $ k 5
[[1,2]]
[[1,3,2]]
[[1,4,3,2]]
[[1,5,4,3,2]]
[[2,3]]
[[2,4,3]]
[[2,5,4,3]]
[[3,4]]
[[3,5,4]]
[[4,5]]

Remember that graphAuts2 tries to find symmetries that take the 1 vertex to the 2, 3, 4, or 5 positions, symmetries that leave 1 where it is and take the 2 vertex to the 3, 4, or 5 positions, symmetries that leave 1 and 2 where they are, and so on. In this case, it seems to have found everything it's looking for.

That's because, for the complete graph, any permutation of the vertices is a symmetry. Recall that a symmetry is a permutation of the vertices that moves edges to edge positions and non-edges to non-edge positions. In the complete graph, every position is an edge position, so there are no non-edges, and every edge moves to an edge position, no matter what we do.

Let's just check. We know that the number of permutations of n objects is n!. The "elts" function lists all the permutations generated by a generating set.

> length $ elts $ graphAuts2 $ k 5
120

So it works (5! = 120). The group of all permutations of [1..n] is called the symmetric group, S n. "graphAuts2" found 10 generators, but in fact we could have generated all the elements from just two generators:
_S n | n >= 3 = [s,t]
| n == 2 = [t]
| n == 1 = []
where s = p [[1..n]]
t = p [[1,2]]
The two generators are an n-cycle s, which cycles all n positions, and a "transposition" t, which just swaps two positions. Let's check that s and t really do generate all permutations:
> _S 5
[[[1,2,3,4,5]],[[1,2]]]
> length $ elts $ _S 5
120
> map (isGraphAut (k 5)) (_S 5)
[True,True]

What about the complete bipartite graphs kb m n? Recall that these consist of m vertices on the left and n on the right, with every left vertex joined to every right vertex by an edge.
kb' m n = graph (vs,es) where
vs = map Left [1..m] ++ map Right [1..n]
es = [ [Left i, Right j] | i <- [1..m], j <- [1..n] ]
For example:
> kb' 2 3
G [Left 1,Left 2,Right 1,Right 2,Right 3]
[[Left 1,Right 1],[Left 1,Right 2],[Left 1,Right 3],[Left 2,Right 1],[Left 2,Right 2],[Left 2,Right 3]]


> mapM_ print $ graphAuts2 $ kb' 2 3
[[Left 1,Left 2]]
[[Right 1,Right 2]]
[[Right 1,Right 3,Right 2]]
[[Right 2,Right 3]]

This is saying that we can take any left vertex to any other left vertex, and any right vertex to any other right vertex. Moreover, we can do the left and right moves independently of one another. However, we can't take a left vertex to a right vertex - unless m = n.

So on the left side, we have the full symmetric group S m acting on the left vertices, and on the right side we have the full symmetric group S n acting on the right vertices - and they are acting independently of one another. This situation is called the cartesian product of the two groups. In the HaskellForMaths library, there is a "cp" function to construct the cartesian product of two groups H and K:
cp :: (Ord a, Ord b) =>
[Permutation a] -> [Permutation b] -> [Permutation (Either a b)]
cp hs ks =
[P $ M.fromList $ map (\(x,x') -> (Left x,Left x')) $ M.toList h | P h <- hs] ++
[P $ M.fromList $ map (\(y,y') -> (Right y,Right y')) $ M.toList k | P k <- ks]
(Recall that permutations are implemented using Data.Map - hopefully you can see what's going on here.)
So hs is a list of generators for a group H acting on a, ks is a list of generators for a group K acting on b. What this function does is create a copy of hs in the left part of an Either a b, and a copy of ks in the right part. Taken together, these generate a group which is isomorphic to the cartesian product of H and K.

For example:
> mapM_ print $ _S 2 `cp` _S 3
[[Left 1,Left 2]]
[[Right 1,Right 2,Right 3]]
[[Right 1,Right 2]]


Exercise:
What is wrong with the following alternative definition of cartesian product of groups?
cp2 :: (Ord a, Ord b, Num a, Num b) =>
[Permutation a] -> [Permutation b] -> [Permutation (a, b)]
cp2 hs ks =
[P $ M.fromList $ map (\(x,x') -> ((x,1),(x',1))) $ M.toList h | P h <- hs] ++
[P $ M.fromList $ map (\(y,y') -> ((1,y),(1,y'))) $ M.toList k | P k <- ks]

(By the way, I hope that the cp and cp2 functions convince you of the beauty of having made our Permutation type polymorphic.)

Anyway, I hope you're beginning to get a feel for how this graph symmetry thing works.
Time to look at some more interesting graphs. This is the Petersen graph:

It's defined as follows:
petersen = graph (vs,es) where
vs = combinationsOf 2 [1..5]
es = [ [v1,v2] | [v1,v2] <- combinationsOf 2 vs, disjoint v1 v2]
The vertices are the 2-subsets of [1..5] (see the labels on the picture), with edges between 2-subsets that are disjoint.

I'll just mention in passing that the 2-subsets of [1..5] have a natural interpretation as the edges of k 5, so that in fact we have:

> petersen == complement (lineGraph' (k 5))
True


Now hopefully you're thinking to yourself "Hmm, from the construction, I wonder whether there is an action of S 5 on the Petersen graph.".

Indeed there is. The action of S 5 on [1..5] induces an action on the 2-subsets of [1..5]. Because the construction is "symmetric" on the 2-subsets (the 2-subsets are all treated the same way), the induced actions are actually symmetries of the Petersen graph.

Here's some code which can be used to calculate the induced action:
action xs f = fromPairs [(x, f x) | x <- xs] 
For example:

> action (combinationsOf 2 [1..5]) (-^ p [[1,2,3,4,5]])
[[[1,2],[2,3],[3,4],[4,5],[1,5]],[[1,3],[2,4],[3,5],[1,4],[2,5]]]

So the 5-cycle [[1,2,3,4,5]], acting on [1..5], induces an action on the 2-subsets of [1..5] which consists of two 5-cycles, for 2-subsets {x,x+1}, and 2-subsets {x,x+2} (mod 5). If you look back at the picture, you'll see that this is an anti-clockwise 2/5 turn. On the other hand:

> action (combinationsOf 2 [1..5]) (-^ p [[1,2]])
[[[1,3],[2,3]],[[1,4],[2,4]],[[1,5],[2,5]]]

If you look at the picture, you'll see that this is a rather more intriguing symmetry of the Petersen graph, which swaps the inner 13,25 edge with the outer 23,15 edge.

(Note: The above code is a slight improvement over the code for this task in v0.1.3, and will be included in the next HaskellForMaths release.)

It turns out that all the symmetries of the Petersen graph are induced by this action of S 5:
> elts (graphAuts2 petersen) == elts [action (combinationsOf 2 [1..5]) (-^ g) | g <- _S 5]
True


That's about it for now. I'll leave you with something to think about.

Exercise:
If you give me a graph g, and show me what "graphAuts2 g" returns, I can tell you at a glance how many symmetries g has. (That is, I can tell you what "length $ elts $ graphAuts2 g" would return, but without running it.) How do I do it?

For example, here's the dodecahedron graph.


> mapM_ print $ graphAuts2 dodecahedron
[[1,2],[3,5],[6,8],[9,15],[10,14],[11,13],[17,20],[18,19]]
[[1,3],[4,5],[6,10],[7,9],[11,15],[12,14],[16,17],[18,20]]
[[1,4],[2,3],[6,12],[7,11],[8,10],[13,15],[16,18],[19,20]]
[[1,5,4,3,2],[6,14,12,10,8],[7,15,13,11,9],[16,20,19,18,17]]
[[1,6,15,20,19,18,11,10,3,2],[4,8,5,7,14,16,13,17,12,9]]
[[1,7,20,18,12,3],[2,6,16,19,11,4],[5,8,15,17,13,10],[9,14]]
[[1,8,3],[4,6,9],[5,7,10],[11,14,16],[12,15,17],[13,20,18]]
[[1,9,6,17,15,18,14,11,5,10],[2,8,7,16,20,19,13,12,4,3]]
[[1,10],[2,3],[4,8],[5,9],[6,11],[7,12],[13,16],[14,17],[15,18],[19,20]]
[[1,11],[2,10],[5,12],[6,18],[7,17],[8,9],[13,14],[15,19]]
[[1,12,9],[2,4,10],[5,11,8],[6,13,17],[7,14,18],[15,19,16]]
[[1,13,6,19,7,18,8,11,2,12],[3,4,5,14,15,20,16,17,9,10]]
[[1,14,20,18,9,3],[2,5,15,19,17,10],[4,6,13,16,11,8],[7,12]]
[[1,15,19,11,3],[2,6,20,18,10],[4,5,14,13,12],[7,16,17,9,8]]
[[1,16,10],[2,7,9],[3,6,17],[4,15,18],[5,20,11],[12,14,19]]
[[1,17,4,7,11],[2,9,3,8,10],[5,16,12,6,18],[13,15,19,14,20]]
[[1,18],[2,11],[3,10],[4,9],[5,17],[6,19],[7,13],[8,12],[14,16],[15,20]]
[[1,19,8,14,17],[2,13,9,5,18],[3,12,10,4,11],[6,20,7,15,16]]
[[1,20,11,2,15,18,3,6,19,10],[4,7,13,9,5,16,12,8,14,17]]
[[2,5],[3,4],[7,15],[8,14],[9,13],[10,12],[16,20],[17,19]]
[[2,6,5],[3,7,14],[4,8,15],[9,20,12],[10,16,13],[11,17,19]]
[[3,8],[4,7],[5,6],[9,10],[11,17],[12,16],[13,20],[14,15]]

I can tell just by looking at that list that there are 120 symmetries in total. How do I do it?

Thursday 18 June 2009

Group generators for graph symmetries

Last time we had a first attempt at a function to find the symmetries of a graph. This time we're going to make a minor improvement. (There is still a major improvement to come, but not this week.)

Our graphAuts1 function from last time listed all the symmetries of a graph. When we come to look at highly symmetric graphs, that is going to be a long list (thousands or even millions long in some cases). But if you do one symmetry of a graph followed by another (say a reflection followed by a rotation), the result is again a symmetry. What if we could find just a few symmetries of the graph, from which all the others could be generated as sequences of actions?

As an example, let's look at the symmetries of a square (or the graph c 4):

There are eight symmetries in all. However, we need just two of them to generate all the rest: the 90 degree clockwise rotation - a; and the reflection in the vertical axis - b. It is easy to see that doing the 180 (respectively 270) degree rotation is the same as doing the 90 degree rotation two (respectively three) times. This is written as a*a, or a^2. Not quite so easy to see is that the reflection in the horizontal axis is the same as doing the 180 degree rotation followed by the reflection in the vertical axis - written a^2 * b. (The starting position, or "do nothing", in the top left is labelled 1, because if you do nothing then do x, or do x then do nothing, that is the same as just doing x - so it acts like a 1: 1*x = x = x*1.)

You can confirm this within GHCi:

> :load Math.Algebra.Group.PermutationGroup
> let a = p [[1,2,3,4]]
> let b = p [[1,2],[3,4]]
> a^2 * b
[[1,4],[2,3]]
> 1 * a
[[1,2,3,4]]

Naturally, if someone gives us a set of permutations, such as [a,b] above, it would be good to be able to list all the elements that they generate. In Math.Algebra.Group.PermutationGroup, the "elts" function does just this:

import qualified Data.List as L
import qualified Data.Set as S

elts gs = elts' S.empty (S.singleton 1) where
elts' interior boundary
| S.null boundary = S.toList interior
| otherwise =
let interior' = S.union interior boundary
boundary' = S.fromList [h * g | h <- S.toList boundary, g <- gs] S.\\ interior'
in elts' interior' boundary'

(This "closure" algorithm turns out to be useful for all sorts of things, so in the library code it's actually factored out into a separate function. However, for the specific problem of listing elements of permutation groups, we will in fact come up with a more efficient algorithm in due course.)

For example, with a and b as before:

> mapM_ print $ elts [a,b]
[]
[[1,2],[3,4]]
[[1,2,3,4]]
[[1,3],[2,4]]
[[1,3]]
[[1,4,3,2]]
[[1,4],[2,3]]
[[2,4]]

You can check that these are the eight symmetries shown in the diagram above.

It's much more convenient to work with a few generators than with hundreds or thousands of elements, so in the HaskellForMaths library we always represent a permutation group as a list of generators.

Okay, so how does this help us with graph symmetries? Well, the idea is that we'll still use depth-first search, but instead of searching for all symmetries, we'll search for just one symmetry that takes 1 to 2, one symmetry that takes 1 to 3, and so on, one symmetry that fixes 1, and takes 2 to 3, one symmetry that fixes 1, and takes 2 to 4, and so on, and so on. The ones that we find will generate all symmetries of the graph.

Here's the code:

graphAuts2 (G vs es) = graphAuts' [] vs where
graphAuts' us (v:vs) =
let uus = zip us us
in concat [take 1 $ dfs ((v,w):uus) vs (v : L.delete w vs) | w <- vs, isCompatible (v,w) uus]
++ graphAuts' (v:us) vs
graphAuts' _ [] = []
dfs xys (x:xs) ys =
concat [dfs ((x,y):xys) xs (L.delete y ys) | y <- ys, isCompatible (x,y) xys]
dfs xys [] [] = [fromPairs xys]
isCompatible (x,y) xys = and [([x',x] `S.member` es') == (L.sort [y,y'] `S.member` es') | (x',y') <- xys]
es' = S.fromList es

The bottom half of this function is just the same as graphAuts1 - it is only the graphAuts' part that is new. (Notice that the "take 1", together with lazy evaluation, means that we're actually searching far less of the tree now.)

Let's try it on our old favourite, the pentagon, c 5:

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

The claim is that these five symmetries generate all the rest. Let's make sure:

> 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]]

These are the same 10 symmetries that we found last time using graphAuts1 (though listed in a different order).

That's it for now.

Exercise:
(I meant to put this in last time, but forgot)
Find the symmetries of the following graphs, and explain your findings:
  • k 5, the complete graph on 5 vertices
  • kb 2 3, the complete bipartite graph on 2 and 3 vertices
  • kb 3 3, the complete bipartite graph on 3 and 3 vertices

Monday 15 June 2009

Graph symmetries

Well, after a couple of false starts, I think I have now succeeded in putting a working release of Haskell for Maths on Hackage - v0.1.3 is here.

So, as promised, we can get back to symmetries of graphs.

First a quick recap:
Graphs are represented as G vs es, where vs is a list of vertices and es is a list of edges, where an edge is a two-element list of vertices. For example, the cyclic graph c 5 (the pentagon - the picture on the left below):

> c 5
G [1,2,3,4,5] [[1,2],[1,5],[2,3],[3,4],[4,5]]

Using cycle notation, we can think of permutations dynamically as acting on the vertices or edges of a graph.

> 2 .^ p [[2,5],[3,4]]
5
> [2,3] -^ p [[2,5],[3,4]]
[4,5]

The "p" function constructs a permutation from a list of cycles. p [[2,5],[3,4]] is the reflection of c 5 in the vertical axis, shown in the middle below, which swaps the 2 and 5 positions, and the 3 and 4 positions. v .^ g represents the action of a permutation g on a vertex v. e -^ g represents the induced action of g on an edge e. (An edge just moves where its two endpoints move.)

We say that the reflection p [[2,5],[3,4]] is a symmetry of the graph, because the graph is the same after as it was before. On the other hand, it should be clear from the picture on the right that the permutation p [[1,2]], which swaps the 1 and 2 positions, is not a symmetry:

> [2,3] -^ p [[1,2]]
[1,3]

It moves the [2,3] edge to [1,3], which was not present as an edge in the original c 5.

Here's the code to test whether a permutation h is a symmetry ("automorphism") of a given graph:
module Math.Combinatorics.GraphAuts where

import qualified Data.Set as S

...

isGraphAut (G vs es) h = all (`S.member` es') [e -^ h | e <- es]
where es' = S.fromList es
(We use Data.Set for efficiency on large graphs.)

Next we would like code to find all symmetries/automorphisms of a graph. Here is a first attempt:
graphAuts1 (G vs es) = dfs [] vs vs where
dfs xys (x:xs) ys =
concat [dfs ((x,y):xys) xs (L.delete y ys) | y <- ys, isCompatible (x,y) xys]
dfs xys [] [] = [fromPairs xys]
isCompatible (x,y) xys =
and [([x',x] `S.member` es') == (L.sort [y,y'] `S.member` es') | (x',y') <- xys]
es' = S.fromList es
We use depth-first search to try build up a list of pairs (x,y), which will represent a permutation which takes each x to the corresponding y. Whenever we add a new pair, we check whether it is compatible with what we have so far - specifically, that whenever {x,x'} is an edge (respectively non-edge) in the graph, then so is {y,y'}, its image after being acted on by the permutation.

We will develop a far more efficient algorithm in due course, but this is sufficient for small graphs. Let's try it out:

> mapM_ print $ graphAuts1 $ c 5
[]
[[2,5],[3,4]]
[[1,2],[3,5]]
[[1,2,3,4,5]]
[[1,3],[4,5]]
[[1,3,5,2,4]]
[[1,4],[2,3]]
[[1,4,2,5,3]]
[[1,5,4,3,2]]
[[1,5],[2,4]]

First, we have the identity permutation, which leaves everything where it is. We also have five permutations like [[2,5],[3,4]], which swap two pairs of positions - these are the five reflections, in the axes joining a vertex to the midpoint of the opposite edge. That leaves four more.
[[1,2,3,4,5]] is the cycle that takes 1 to 2, 2 to 3, 3 to 4, 4 to 5, and 5 to 1. In other words, it's a clockwise 72 degree rotation of the pentagon (except that of course graphs aren't really rigid objects in space - but you get the idea). The other three similar elements are the 144, 216 and 288 degree rotations.

That's it for now. Coming soon: a more efficient algorithm for finding graph automorphisms, and some graphs with interesting automorphism groups.

Friday 12 June 2009

It's on Hackage!

Following numerous requests, I've finally managed to upload Haskell for Maths to Hackage:
http://hackage.haskell.org/package/HaskellForMaths

It's my first experience with Hackage, so I'm bound to have done something wrong - let me know what, and I'll try to fix it.

The fallback option is still to download the zipfile from the Haskell for Maths website.

Thursday 11 June 2009

Permutation groups

Last time, we looked at how graphs are represented in the Haskell for Maths library. What we're heading for is to look at symmetries of graphs. But first, we need to talk about permutation groups.

Given a finite set, a permutation is an arrangement of its elements into a sequence. For example, here are three permutations of the numbers 1 to 5:
[1,2,3,4,5]
[1,5,4,3,2]
[2,1,3,4,5]

Where it gets interesting is if the set we are permuting is the underlying set of some mathematical object - such as the vertex set of a graph. For example, we saw last time that we can label the vertices of the cyclic graph c 5 (the pentagon) with the numbers 1 to 5. In that case, the permutations above correspond to the following diagrams.

The permutation [1,2,3,4,5] - the diagram on the left - can be thought of as the starting position. (So the convention is that we read the numbers clockwise from the top.)
The permutation [1,5,4,3,2] - the diagram in the middle - is a reflection of the starting position in the vertical axis.
The permutation [2,1,3,4,5] - on the right - just swaps the 1 and 2 vertices.

When we write a permutation as a list of vertices, we're taking a static view of it. But we can also take a dynamic view, where we think not about where the vertices end up, but about what we had to do to get them there (from the starting position).

For example, for the reflection [1,5,4,3,2], what we had to do was swap the 2 and 5 vertices, and swap the 3 and 4 vertices. (As a hint of what's to come, we will end up writing this as [[2,5],[3,4]].)

In this view, the permutation is not the end position, but the function or map that we used to get there from the starting position. Hence, in the module Math.Algebra.Group.PermutationGroup, permutations are defined as follows

import qualified Data.Map as M

newtype Permutation a = P (M.Map a a) deriving (Eq,Ord)

Notice that, as for our Graph datatype, although we will often consider permutations as acting on integers, we have left ourselves the option of acting on other things too. Again, this will prove to be extremely useful.

The library provides three ways to construct permutations:


> :load Math.Algebra.Group.PermutationGroup
> fromList [1,5,4,3,2]
[[2,5],[3,4]]
> fromPairs [(1,1),(2,5),(3,4),(4,3),(5,2)]
[[2,5],[3,4]]
> fromCycles [[2,5],[3,4]]
[[2,5],[3,4]]


Notice that permutations are always shown in cycle notation. Once you get used to it, this is the most natural way to think about permutations. For this reason "p" is provided as a shorthand for "fromCycles", as this is how we will most often construct permutations.

Given a permutation, we can ask what is its action on a vertex, or on an edge:

> 2 .^ p [[2,5],[3,4]]
5
> [1,2] -^ p [[2,5],[3,4]]
[1,5]

This says that our reflection sends the vertex 2 to 5, and the edge [1,2] to [1,5].

Finally, if a permutation is something you do, then we can ask what happens if you do g then h, or how to undo g:

> p [[2,5],[3,4]] * p [[2,5],[3,4]]
[]
> p [[2,5],[3,4]] ^-1
[[2,5],[3,4]]

This says that if you do our reflection, and then do it again, you end up back at the starting position; and that if you want to undo our reflection, just do it again.

Exercise: Write implementations of the (.^), (-^), (*), and (^-) operators shown above, and compare with the library implementations.

There's quite a lot more in Math.Algebra.Group.PermutationGroup, which I hope to talk about at some point. But for now, that's all we need. (Although, if you want to keep following, it would be a good idea to play around and make sure you've got the hang of cycle notation.)

Next time, graph symmetries (hopefully).

Sunday 7 June 2009

Simple graphs with Math.Combinatorics.Graph

Hello again.

In this blog I'll be talking about my Haskell for Maths library - the maths behind it, how the code works, and how to use it. I thought we'd begin with something easy, (simple) graphs. Here are a couple of examples:

Well actually, these are really the same graph - the cube. You see, we're not really interested in the spatial arrangement of the vertices and edges, but only in the pattern of connectivity between them. These graphs have the same vertices (the numbers 0 to 7), and you can check that the edges connect the same pairs of vertices.

So a graph is defined as a pair (vs, es) where vs is a set of vertices, labelled by integers, say, and es is a set of edges - where an edge is a set of two vertices. In Haskell:

data Graph a = G [a] [[a]] deriving (Eq,Ord,Show)

For example (jumping ahead a little), the graph shown above is:

> :load Math.Combinatorics.Graph
> 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]]

Although we will often use integers to label the vertices, notice that the Graph data type permits us to use other types. This will turn out to be extremely useful.

Okay, so whenever we define a new type of mathematical object, one of the first things we want to know is if there are any standard families of such objects. Here are a few standard graphs.



(Note that from now on I usually won't label the vertices. When studying graphs, what we're really interested in is the underlying structure of vertices connected by edges. The labels on the vertices are just scaffolding.)

The graph on the left is c 5, the cyclic graph on 5 vertices.

c n = graph (vs,es) where
vs = [1..n]
es = L.insert [1,n] [[i,i+1] | i <- [1..n-1]]

Just a little note about this. For convenience, we insist that the lists of vertices and edges are always in ascending order, and that each edge (list of two vertices) is itself in ascending order. The "graph" constructor checks this for us.

The middle graph above is k 5, the complete graph on 5 vertices, in which every pair of vertices is connected by an edge.

k n = graph (vs,es) where
vs = [1..n]
es = [[i,j] | i <- [1..n-1], j <- [i+1..n]]

The graph on the right is the complete bipartite graph kb 2 3, in which each of two vertices on the left is connected to each of three vertices on the right. Here we have an example where it is useful to be able to use types other than Integer to label our vertices:

kb' m n = graph (vs,es) where
vs = map Left [1..m] ++ map Right [1..n]
es = [ [Left i, Right j] | i <- [1..m], j <- [1..n] ]

kb m n = to1n $ kb' m n

The function "to1n" converts a graph over some other type to a graph over the integers.

> kb' 2 3
G [Left 1,Left 2,Right 1,Right 2,Right 3]
[[Left 1,Right 1],[Left 1,Right 2],[Left 1,Right 3],
[Left 2,Right 1],[Left 2,Right 2],[Left 2,Right 3]]

> kb 2 3
G [1,2,3,4,5] [[1,3],[1,4],[1,5],[2,3],[2,4],[2,5]]

There are a few more standard families of graphs, and some new from old constructions, defined in the Math.Combinatorics.Graph module. See the code for details.

That's about all I've got time for just now. What I'm heading for is to be able to study the symmetries (automorphisms) of graphs. The code is in Math.Combinatorics.GraphAuts, if you want a sneak preview - otherwise you'll just have to wait.

Saturday 6 June 2009

Welcome to Haskell for Maths

Welcome.

I have started this blog so that I can talk about my Haskell for Maths library, which is available at:

http://www.polyomino.f2s.com/haskellformathsv2/HaskellForMathsv2.html

(I will probably put it on Hackage at some point, but I'm having a few problems getting the Cabal toolchain to work properly on Windows.)

Haskell for Maths is a library of Haskell code, mainly in algebra and combinatorics. (An earlier v1 of the code, accessible from that link, also contained some number theory code.)

The core building blocks of the library are the following data structures and algorithms:
  • permutations and the Schreier-Sims algorithm
  • string rewriting and the Knuth-Bendix algorithm
  • multivariate polynomials and the Buchberger algorithm for Groebner bases
  • non-commutative polynomials and Groebner-Shirshov bases

The library also contains various projects, looking at:
  • symmetries (automorphisms) of graphs and other combinatorial structures (finite geometries, designs, etc.) - in the course of which we meet a few of the sporadic finite simple groups
  • root systems and Coxeter groups
  • Chevalley groups (finite simple groups of Lie type)
  • Knot theory - calculating the Jones and HOMFLY polynomials using Temperley-Lieb and (Iwahori-)Hecke algebras
There's also further code, still in the labs, for things like:
  • Algebraic geometry, including invariant theory, Grassmannians
  • Clifford algebras
What I want to do in this blog is explain some nice maths, and how we can investigate it in Haskell.

As a taster, here's a pretty picture:


This is the Clebsch graph. It's obvious from the way it's drawn that it has a five-fold symmetry, by rotating about the centre, and several two-fold symmetries, by reflecting in various axes through the centre (eg the vertical). A graph symmetry is any way of swapping the vertices around (taking connected edges with them), that leaves the configuration as a whole looking the same. Individual vertices and edges may end up in different places, but collectively the vertices and edges are still in the same places. Anyway, it turns out that this graph has 1920 symmetries. (For example, you might be able to see that there is a symmetry that kind of interchanges the inner and the outer rings of 5 vertices, unfolding the inner star and folding the outer pentagon as it goes.)

More next time.

Followers