Saturday, August 02, 2008

Hopf Algebra = Group + Monad

I have two goals in this post. Firstly I want to revisit the vector space monad I've used before. This time I want to show how it provides a great domain specific language for working with multilinear functions on vector spaces. Secondly I want to apply this monad to talk about Hopf algebras. In particular I want to address the issue of why Hopf algebras and groups are actually the same thing. In fact, I want to push this idea to the point where I can use exactly the same code to perform operations in both groups and Hopf algebras. By parameterising the definition of groups in the right way, Hopf algebras appear as if by magic simply by tweaking one parameter. What this means is that if you understand groups and vector spaces, and are comfortable with monads in Haskell, then despite their notoriety as something whose definition is a little opaque, you'll have some idea of what a Hopf algebra is well before the end this post.

Of course there's the question of why anyone would want to know about Hopf algebras. They appear in combinatorics, topology and knot theory, and theoretical physics among other subjects. In fact, there's a review paper on their ubiquity. As topics in mathematics go, this is a hot one.

First some administrivia, because this is, as always, a literate Haskell post.


> {-# LANGUAGE MultiParamTypeClasses,FlexibleInstances,FunctionalDependencies,GeneralizedNewtypeDeriving #-}

> module Main where

> import qualified Data.Map as M
> import Control.Monad
> import Test.QuickCheck

> infixl 5 .+
> infixl 6 .*

> swap (x,y) = (y,x)


Vector Spaces



We'll start with a type class for vector spaces v over a base field k:


> class Num k => VectorSpace k v | v -> k where
> zero :: v
> (.+) :: v -> v -> v
> (.*) :: k -> v -> v
> (.-) :: v -> v -> v
> v1 .- v2 = v1 .+ ((-1).*v2)


.+ is vector space addition and .* is scalar multiplication by elements of the base field.

And now I need a concrete instance. I'll be working with vector spaces equipped with a basis. I'll use the obvious representation: a list of pairs of coefficients and basis elements. So 2x-3y is represented as V [(2,x),(3,y)]. Sometimes it will be clearer if I write 2ex-3ey. x and y aren't really the basis elements but labels. The ex and ey are the actual basis elements. But it's often more readable to write x and y.


> data V k a = V { unV :: [(k,a)] } deriving (Show)


The problem with this representation is that basis elements might appear in any order, the same basis element might appear multiple times, and some basis elements might appear with redundant zero coefficients. We need a suitable definition of equality. (I'm sidestepping the usual issues with Eq and Monad.)


> reduce x = filter ((/=0) . fst) $ fmap swap $ M.toList $ M.fromListWith (+) $ fmap swap $ x

> instance (Ord a,Num k) => Eq (V k a) where
> V x==V y = reduce x==reduce y

> instance (Ord a,Num k,Ord k) => Ord (V k a) where
> compare (V x) (V y) = compare (reduce x) (reduce y)


V is a functor. fmap f just applies f to the basis elements.


> instance Num k => Functor (V k) where
> fmap f (V as) = V $ map (\(k,a) -> (k,f a)) as


Given any type a, V k a is the type of vectors over k generated by elements of a. So V k (V k a) is the type of vectors whose basis elements are themselves labeled by vectors in V k a. We can think of an element of V k (V k a) looking something like 2(2x+3y)-5(3x-y). It's tempting to say this is equal to what we get when we multiply out, but where I wrote '2x+3y' I really meant e2x+3y. Nonetheless, we can define a function that does the multiplying out. I'll call this function join. So we get a function join :: V k (V k a) -> V k a. In fact, we get a monad.


> instance Num k => Monad (V k) where
> return a = V [(1,a)]
> x >>= f = join (fmap f x)
> where join x = V $ concat $ fmap (uncurry scale) $ unV $ fmap unV x
> scale k1 as = map (\(k2,a) -> (k1*k2,a)) as


What's really going on here is that the "vector space over basis" functor is a monad in the category Set, but in the category of Haskell types and functions we're stuck with lists.

V k is not just a monad, it's also a MonadPlus.


> instance Num r => MonadPlus (V r) where
> mzero = V []
> mplus (V x) (V y) = V (x++y)


So what's the use of making our vector space into a monad? If m is a monad, then any function f:a→mb can be lifted to a function f':ma→mb. f maps the basis elements in a to elements of mb. It's a standard fact about vector spaces that a linear function is completely defined by its value on a basis. f' is the corresponding linear function. So we only need to implement linear functions for basis elements and the function can be automatically lifted to a linear function on the whole vector space. An arrow of the form a→mb is a Kleisli arrow and what I've just argued is that the Kleisli category of the V k monad is the category of vector spaces with basis.

This gives us lots of advantages. For example, we can't accidentally implement a function that isn't linear this way. If we implement the action on a basis, the lift can't help but be linear. Also, working with basis elements rather than the vector space gives us greater flexibility. For example, it'll be easy to form tensor products of vector spaces by directly working with their bases.

Here's the instantiation of the vector space type:


> instance (Num k,Ord a) => VectorSpace k (V k a) where
> zero = V []
> V x .+ V y = V (x ++ y)
> (.*) k = (>>= (\a -> V [(k,a)]))

> e = return :: Num k => a -> V k a
> coefficient b (V bs) = maybe 0 id (lookup b (map swap (reduce bs)))


I could have implemented .* using scale but this definition is more in the spirit of what's to come.

Groups



Now we switch to groups. Here's a first attempt at writing a group type class


> class Group1 a where
> unit1 :: a
> mult1 :: a -> a -> a
> inverse1 :: a -> a

> newtype Z = Z Int deriving (Eq,Ord,Show,Arbitrary,Num)

> instance Group1 Z where
> unit1 = Z 0
> mult1 = (+)
> inverse1 = negate


Now we can try testing some of the group laws. For example


> test_inverse1 a = mult1 a (inverse1 a)
> ex1 = quickCheck (\a -> test_inverse1 a==(unit1::Z))


If we run ex1 we gain some confidence that we have a group. If we want to be more categorial then we need to express as much as possible as compositions of functions. So let's break down test_inverse1 as a composition of elementary operations.


> diag a = (a,a)
> both f g (a,b) = (f a,g b)
> test_inverse2 = uncurry mult1 . (id `both` inverse1) . diag
> ex2 = quickCheck (\a -> test_inverse2 a==(unit1::Z))


There's a nice symmetry in test_inverse2. If we make diag part of the definition of a group that we can make this highly symmetric definition of a group:


> class Group2 a where
> unit2 :: () -> a
> counit2 :: a -> ()
> mult2 :: (a,a) -> a
> comult2 :: a -> (a,a)
> anti2 :: a -> a


I've even made a (useless looking) symmetric partner for unit1 and I've renamed the inverse operation as anti, short for antipode. Let's make Z an instance of this class.


> instance Group2 Z where
> unit2 () = Z 0
> counit2 _ = ()
> mult2 = uncurry (+)
> comult2 a = diag a
> anti2 = negate


I hope I haven't done anything too tricky yet. This is just the familiar definition of a group except I've made a trivial 'counit' and the diagonal function part of the definition. Now comes the most important step in this post: I'll tweak this definition so that all of the associated functions are now Kleisli arrows:


> class Group m a where
> unit :: () -> m a
> counit :: a -> m ()
> mult :: (a,a) -> m a
> comult :: a -> m (a,a)
> anti :: a -> m a


We can now straightforwardly reimplement Z as an instance of this class.


> instance Monad m => Group m Z where
> unit _ = return (Z 0)
> counit _ = return ()
> mult = return . uncurry (+)
> comult = return . diag
> anti = return . negate


Apart from writing it monad-agnostically, it's just like before. We can exactly recover what we had before with the help of the identitiy monad.


> newtype Identity a = I a deriving (Eq,Ord,Show)

> instance Monad Identity where
> return x = I x
> I x >>= f = f x


Now we can rewrite the group laws. Before checking to see if aa-1=1 we'll make sure aa-1=a-1a.


> test_antipode1 a = do
> (u,t) <- comult a
> u' <- anti u
> mult (u',t)

> test_antipode2 a = do
> (u,t) <- comult a
> t' <- anti t
> mult (u,t')

> ex3 = quickCheck (\a -> lhs a==rhs a) where
> lhs = test_antipode1 :: Z -> Identity Z
> rhs = test_antipode2 :: Z -> Identity Z


For aa-1 we need to compare with the identity. We make an identity by applying unit to (). We could just provide a () but we get something more symmetrical if we construct it using the counit.


> test_antipode3 a = do
> x <- counit a
> unit x

> ex4 = quickCheck (\a -> lhs a==rhs a) where
> lhs = test_antipode1 :: Z -> Identity Z
> rhs = test_antipode3 :: Z -> Identity Z


We can test associativity easily


> test_assoc1 (a,b,c) = do
> ab <- mult (a,b)
> mult (ab,c)

> test_assoc2 (a,b,c) = do
> bc <- mult (b,c)
> mult (a,bc)

> ex5 = quickCheck (\a -> lhs a==rhs a) where
> lhs = test_assoc1 :: (Z,Z,Z) -> Identity Z
> rhs = test_assoc2 :: (Z,Z,Z) -> Identity Z


In the interest of symmetry, there ought to be a coassociativity law for comultiplication. Here it is:


> test_coassoc1 x = do
> (u,v) <- comult x
> (s,t) <- comult v
> return (u,s,t)

> test_coassoc2 x = do
> (u,v) <- comult x
> (s,t) <- comult u
> return (s,t,v)

> ex6 = quickCheck (\a -> lhs a==rhs a) where
> lhs = test_coassoc1 :: Z -> Identity (Z,Z,Z)
> rhs = test_coassoc2 :: Z -> Identity (Z,Z,Z)


One issue is that we've introduced comult without making much demand on it. Here's a law that is obviously true in any group that helps to pin down comult. It's simply evaluating (p,q) →(pq,pq) in two different ways.


> test_multcomult1 (u,v) = do
> (p,q) <- comult u
> (r,s) <- comult v
> u' <- mult (p,r)
> v' <- mult (q,s)
> return (u',v')

> test_multcomult2 (u,v) = do
> w <- mult (u,v)
> comult w

> ex7 = quickCheck (\a -> lhs a==rhs a) where
> lhs = test_multcomult1 :: (Z,Z) -> Identity (Z,Z)
> rhs = test_multcomult2 :: (Z,Z) -> Identity (Z,Z)


Out of laziness I'm not going to test every group law, but shortly I'll show you where to find all of the laws, including the new laws for comult.

Hopf Algebras



Identity Z is just the usual group of integers with addition. But the time has come to switch monads. What's H=V Float Z? It's clearly a vector space with basis elements labelled with integers. It's also an instance of Group (V Float) meaning it comes equipped with implementations of functions like unit and comult. But note this: counit is no longer trivial. We have counit :: Z -> V Float (). In other words counit lifts to a linear map from H to V Float (), which is isomorphic to Float. In fact, it sums the coefficients if the basis elements. unit now embeds the ground field in our new structure. But what's mult? Well V Float (Z,Z) is H⊗H. So mult lifts to a bilinear map from H×H to H. We have a vector space with a bilinear multiplication law. Is this law associative? We could write code to check. But here's the really cool bit: we can just reuse test_assocn from above.


> ex8 = quickCheck (\a -> lhs a==rhs a) where
> lhs = test_assoc1 :: (Z,Z,Z) -> V Float Z
> rhs = test_assoc2 :: (Z,Z,Z) -> V Float Z


By switching monad, we automatically get a new algebraic structure and new 'semantics' for the group laws. Unpacking ex8 reveals that it gives the associativity law for an algebra. Unpacking further group laws in this context gives bialgebra laws.


> ex9 = quickCheck (\a -> lhs a==rhs a) where
> lhs = test_multcomult1 :: (Z,Z) -> V Float (Z,Z)
> rhs = test_multcomult2 :: (Z,Z) -> V Float (Z,Z)


And 'monadifying' the laws about group inverses give rise to the Hopf algebra laws for the antipode:


> ex10 = quickCheck (\a -> lhs a==rhs a) where
> lhs = test_antipode1 :: Z -> V Float Z
> rhs = test_antipode2 :: Z -> V Float Z


In other words, a Hopf algebra over k is nothing other than a group in the generalised sense above using the monad V k. The underlying object and all of the Hopf algebra laws just follow automatically as soon as you switch monads. Groups and Hopf algebras are the same thing.

But we still have this example Hopf algebra V Float Z to think about. It's none other than the group algebra of Z. It's essentially the algebra of Laurent polynomials. Clearly we could repeat this group algebra construction for any group and Z was just an example.

Examples



Now I have this machinery for working with Hopf algebras I might as well construct some examples that aren't simply generated by some underlying group. I found some pretty combinatorial examples in this paper.

Firstly I'd like to define some combinatorial operations on lists: cat, chop, shuffle and excise.

cat simply joins a pair of lists.


> cat x = return $ uncurry (++) x


chop computes a kind of inverse of cat. This inverse is multivalued so depending on which monad is used it can return all of the possible pairs that could have been catted to make a particular list.


> chop :: (MonadPlus m, Functor m) => [a] -> m ([a], [a])
> chop [] = return ([],[])
> chop (a:as) = return ([],a:as) `mplus` fmap ((a:) `both` id) (chop as)


shuffle finds all the ways that two lists can be riffle shuffled together.


> shuffle ([],b) = return b
> shuffle (a,[]) = return a
> shuffle (a:as,b:bs) =
> fmap (a:) (shuffle (as,b:bs)) `mplus`
> fmap (b:) (shuffle (a:as,bs))


excise is the multivalued inverse of shuffle in that it finds all of the ways pairs of lists could have been riffle shuffled together to give a particular list.


> excise [] = return (mzero,mzero)
> excise (a:as) = do
> (x,y) <- excise as
> return (a:x,y) `mplus` return (x,a:y)


We can now define a pair of Hopf algebras as follows.


> newtype Hopf1 = H1 [Int] deriving (Ord,Eq,Show,Arbitrary)

> instance Group (V Float) Hopf1 where
> unit _ = return (H1 [])
> counit (H1 []) = return ()
> counit _ = zero
> mult (H1 x,H1 y) = fmap H1 $ cat (x,y)
> comult (H1 x) = fmap (\(x,y) -> (H1 x,H1 y)) $ excise x
> anti (H1 x) = (-1)^(length x) .* return (H1 $ reverse x)

> newtype Hopf2 = H2 [Int] deriving (Ord,Eq,Show,Arbitrary)

> instance Group (V Float) Hopf2 where
> unit _ = return (H2 [])
> counit (H2 []) = return ()
> counit _ = zero
> mult (H2 x,H2 y) = fmap H2 $ shuffle (x,y)
> comult (H2 x) = fmap (\(x,y) -> (H2 x,H2 y)) $ chop x
> anti (H2 x) = (-1)^(length x) .* return (H2 $ reverse x)


We can now test some of the Hopf algebra laws


> ex11 = quickCheck (\a -> lhs a==rhs a) where
> lhs = test_assoc1 :: (Hopf1,Hopf1,Hopf1) -> V Float Hopf1
> rhs = test_assoc2 :: (Hopf1,Hopf1,Hopf1) -> V Float Hopf1


Unfortunately my code is a inefficient, and the shuffles cause combinatorial explosions, so it's probably best not to run these examples. This post is about expressing algebraic structures rather than making practical computations in them.


> ex12 = quickCheck (\a -> lhs a==rhs a) where
> lhs = test_coassoc1 :: Hopf1 -> V Float (Hopf1,Hopf1,Hopf1)
> rhs = test_coassoc2 :: Hopf1 -> V Float (Hopf1,Hopf1,Hopf1)

> ex13 = quickCheck (\a -> lhs a==rhs a) where
> lhs = test_antipode1 :: Hopf1 -> V Float Hopf1
> rhs = test_antipode2 :: Hopf1 -> V Float Hopf1

> ex14 = quickCheck (\a -> lhs a==rhs a) where
> lhs = test_multcomult1 :: (Hopf1,Hopf1) -> V Float (Hopf1,Hopf1)
> rhs = test_multcomult2 :: (Hopf1,Hopf1) -> V Float (Hopf1,Hopf1)


And of course you can try the same with Hopf2.

Sweedler Notation


There's one last important thing to come out of these. We have a powerful notation for working with tensor products of vector spaces but the notation is so easy to use that it's hidden the fact that there's complex stuff going on under the hood. When we're dealing with the Identity monad then a line like (p,q) <- comult u is pretty straightforward to interpret as an assignment. But in the vector space monad it means something very different. Nonetheless, we can often reason (with care) as if it were just an assignment. This is what Sweedler Notation is about. But it kind of just appears automatically here.

Summary


What they say is right. Hopf algebras really are groups in disguise. Just take all of the functions that make up the structure of a group and convert each one to a Kleisli arrow for the vector space monad. You end up with Hopf algebras.

I'm amazed at the way I could express this level of abstraction in Haskell. I don't know of any computer algebra package that comes near to this level of expressivity. Although algebra packages often come with amazing implementations of algebraic algorithms, the programming languages they come with are generally completely uninteresting in themselves. I'm looking forward to the day when computational algebraists and programming language theorists get talking to each other.

By the way, this kind of manipulation was what monads were invented for. It's nice to see the two different applications work so well together.

16 Comments:

Anonymous Anonymous said...

I am not exactly sure if you have answered the following question before, but pardon me if I am repeating it anyway.

Are there some good online resources (articles, books,blogs, etc.) that may help one to (re)learn Haskell from a (more) categorical perspective?

Thanks,

Saturday, 02 August, 2008  
Blogger sigfpe said...

I think the intersection of Haskell programmers and mathematicians is still fairly small and there aren't too many books, if any at all, on the subject geared to someone with a categorical, but not computer science background.

Saturday, 02 August, 2008  
Anonymous Anonymous said...

Well, I do have a fair amount of background (though quite modest, I should say) in computer science. Thanks!

Sunday, 03 August, 2008  
Blogger sigfpe said...

In that case there so many papers I don't know where to start!

Sunday, 03 August, 2008  
Blogger sigfpe said...

That was a terse reply. I was on my way out to run half of the San Francisco marathon.

Anyway, I found this useful for getting the correspondence between a category theoretic notion of monads and the actual notation as used in a Haskell program. I also enjoy lots of papers by Uustaluand Vene as they come with category theoretical language and Haskell code so it's easy to see the correspondence.

Sunday, 03 August, 2008  
Anonymous Anonymous said...

Those were just the the kind of resources I was looking for. Greatly appreciate it. Hope you ran a good marathon!

Sunday, 03 August, 2008  
Blogger Unknown said...

I'm not sure if I need to read on to understand it but it seems to me that x in reduce x is already (k, a). I don't understand why there is a need to fmap swap x first. Is the definition of V a typo?

Tuesday, 05 August, 2008  
Blogger sigfpe said...

Christian,

Elements of vectors are written as lists of pairs (k,a) where k is the coefficient and a is the basis vector label. I need to collect together pairs with the same basis label. Data.Map can do this. But fromList and toList use the *first* element of the pair as key, not the second element, and they sort on the first element. So I needed to swap.

The code would have been slightly shorter if I'd used lists of (a,k). But it's more conventional in mathematics texts to write the coefficient before the basis element.

I'm pretty sure the definition of V is correct because the quickChecks work. Of course 'pretty sure' isn't a proof.

Tuesday, 05 August, 2008  
Blogger Unknown said...

Got it! I was looking at toListWith's data signature and I mixed up the (k, a) there and the (k, a) in V.

Tuesday, 05 August, 2008  
Anonymous Anonymous said...

Very interesting! I wonder what happens when you monadify/Kleislify the axioms of other algebraic structures, say monoids, fields or vector spaces.

I.e.
class Field m a where
zero :: m a
one :: m a
add :: a -> a -> m a
mult :: a -> a -> m a
...

instance (Monad m) => Field m Float where ...

With this setup: What is V Float Float? Because of the instance given in the previous paragraph this has (additionall to vector addition) a bilinear add and a bilinear mult.

Also, what is Maybe Z? Or [Z]? All of these come, thanks to the instance (Monad m) => Group m Z, equipped with a compatible multiplication, (>>= mult).

Friday, 08 August, 2008  
Anonymous Anonymous said...

Great blog!

Haskell does seem to be the perfect language for pure mathematics. I've been trying to do some computations involving ribbon graphs and the moduli space of curves in C++, but from reading your blog it looks like it would be far easier in Haskell.

Do you know of any implementations of things like chain complexes, homology, etc. in Haskell?

Best,
Kevin

Tuesday, 19 August, 2008  
Blogger sigfpe said...

Kevin,

Chain complexes and homology? Funny you should ask :-)

Years ago I read the paper by Penner on fat/ribbon graphs, matrix models and the computation of the Euler characteristics of moduli spaces and thought it was pretty amazing. I'd love to see some related Haskell code.

I (apparently) got fellow blogger Mikael Johannson interested in Haskell a while back and I think he did a bunch of homological algebra type things with it.

Tuesday, 19 August, 2008  
Anonymous Anonymous said...

Sigpfe -- thanks for that!

It's pretty amazing that it takes 20 lines to code to compute homology. (I'd been dreading trying to define a chain complex class in C++...)

The coolest thing about all this ribbon graph stuff is the way it links algebra and geometry (and physics!). For instance, Kontsevich has a great paper where he shows how to understand the cohomology of moduli space by thinking about homotopy-associative algebras. My project is ultimately related to this.

The only reason Haskell might not be appropriate for what I want to do is that at some stage I'll want to invert very large matrices. But I presume that Haskell can just call some fast + optimized C program to do this part, is that right?

Thanks,
Kevin

Tuesday, 19 August, 2008  
Blogger sigfpe said...

Kevin,

If you're interested in solving large linear systems there will be some bindings to the standard C libraries out there. But I suggest asking in haskell-cafe where I've seen people discuss these things. haskell-cafe is a pretty friendly place and there are a quite a few mathematicians 'there'.

Incidentally, the benchmark for compactly computing homology is probably this.

Tuesday, 19 August, 2008  
Anonymous Anonymous said...

Comoputational monads go back to the calculation of sine tables in antiquity, and then intersected algrebra under the influence of formal logic at about the time of the Asclepios (Hermetic monadology). This is not well known, because the true origin of differential calculus lies here. This history was touched on by Delambre on route to the SI (metric system), which accordingly holds the planet together! As errors of estimate, CMs then disappear behind the Weierstrass Approximation Theorem in tandem with statisticsal mechanics, and then colonize cosmology via Stone's extension to compactifications. The fabulous superstrings now fall to earth as M-branes, familiar as rigid rotators, or the atoms of the Ancients. Of course, this is only half of what topology now does, which is what bought me to this blog.

DiedLaughing

Saturday, 22 November, 2008  
Anonymous Yoyostein said...

Hi, I am interested in the paper regarding combinatorial applications of Hopf Algebra.
However the link is no longer working.

Any idea of what is the title of the paper?

Thanks a lot!
yoyostein88@gmail.com

"Now I have this machinery for working with Hopf algebras I might as well construct some examples that aren't simply generated by some underlying group. I found some pretty combinatorial examples in this paper."

Wednesday, 21 March, 2012  

Post a Comment

<< Home