-- Copyright (c) 2010-2012, David Amos. All rights reserved. {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, TypeSynonymInstances #-} -- ScopedTypeVariables -- |A module for doing arithmetic in the group algebra. -- -- Group elements are represented as permutations of the integers, and are entered and displayed -- using a Haskell-friendly version of cycle notation. For example, the permutation (1 2 3)(4 5) -- would be entered as @p [[1,2,3],[4,5]]@, and displayed as [[1,2,3],[4,5]]. -- -- Given a field K and group G, the group algebra KG is the free K-vector space over the elements of G. -- Elements of the group algebra consist of arbitrary K-linear combinations of elements of G. -- For example, @p [[1,2,3]] + 2 * p [[1,2],[3,4]]@ module Math.Algebras.GroupAlgebra (GroupAlgebra, p) where import Math.Core.Field import Math.Core.Utils hiding (elts) import Math.Algebras.VectorSpace import Math.Algebras.TensorProduct import Math.Algebras.Structures import Math.Algebra.Group.PermutationGroup hiding (p, action) -- import qualified Math.Algebra.Group.PermutationGroup as P import Math.Algebra.LinearAlgebra (solveLinearSystem) -- hiding (inverse, (*>) ) import Math.CommutativeAlgebra.Polynomial import Math.CommutativeAlgebra.GroebnerBasis type GroupAlgebra k = Vect k (Permutation Int) instance (Eq k, Num k) => Algebra k (Permutation Int) where unit x = x *> return 1 mult = nf . fmap (\(g,h) -> g*h) {- instance Mon (Permutation Int) where munit = 1 mmult = (*) -- Monoid Algebra instance instance (Eq k, Num k) => Algebra k (Permutation Int) where unit x = x *> return munit mult = nf . fmap (\(g,h) -> g `mmult` h) -} -- Set Coalgebra instance -- instance SetCoalgebra (Permutation Int) where {} instance (Eq k, Num k) => Coalgebra k (Permutation Int) where -- counit (V ts) = sum [x | (g,x) <- ts] -- trace counit = unwrap . linear counit' where counit' g = 1 -- trace comult = fmap (\g -> (g,g)) -- diagonal instance (Eq k, Num k) => Bialgebra k (Permutation Int) where {} -- should check that the algebra and coalgebra structures are compatible instance (Eq k, Num k) => HopfAlgebra k (Permutation Int) where antipode = nf . fmap inverse -- antipode (V ts) = nf $ V [(g^-1,x) | (g,x) <- ts] -- |Construct a permutation, as an element of the group algebra, from a list of cycles. -- For example, @p [[1,2],[3,4,5]]@ constructs the permutation (1 2)(3 4 5), which is displayed -- as [[1,2],[3,4,5]]. p :: [[Int]] -> GroupAlgebra Q p = return . fromCycles instance (Eq k, Num k) => Module k (Permutation Int) Int where action = nf . fmap (\(g,x) -> x .^ g) instance (Eq k, Num k) => Module k (Permutation Int) [Int] where action = nf . fmap (\(g,xs) -> xs -^ g) -- use *. instead -- r *> m = action (r `te` m) newtype X a = X a deriving (Eq,Ord,Show) -- Find the inverse of a group algebra element using Groebner basis techniques -- This is overkill, but it was what I had to hand at first inv x@(V ts) = let gs = elts $ map fst $ terms x -- all elements in the group generated by the terms cs = map (glexvar . X) gs x' = V $ map (\(g,c) -> (g, unit c)) ts one = x' * (V $ zip gs cs) oneEquations = (coeff 1 one - 1) : [coeff g one - 0 | g <- tail gs] zeroEquations = [coeff g one - 0 | g <- gs] solution = gb oneEquations in if solution == [1] then Left (gb zeroEquations) -- it's a zero divisor else Right solution -- sum [-c *> p g | V [ (Glex (M 1 [(X g, 1)]), 1), (Glex (M 0 []), c) ] <- solution] -- should extract the solution into a group algebra element, but having trouble getting types right -- The following code can be made to work over an arbitrary field by using ScopedTypeVariables and var instead of glexvar. -- However, we should then probably also change the signature of p to p :: Fractional k => [[Int]] -> GroupAlgebra k -- |Note that the inverse of a group algebra element can only be efficiently calculated -- if the group generated by the non-zero terms is very small (eg \<100 elements). instance HasInverses (GroupAlgebra Q) where inverse x@(V ts) = let gs = elts $ map fst ts -- all elements in the group generated by the terms n = length gs y = V $ zip gs $ map (glexvar . X) [1..n] -- x1*1+x2*g2+...+xn*gn x' = V $ map (\(g,c) -> (g, unit c)) ts -- lift the coefficients in x into the polynomial algebra one = x' * y m = [ [coeff (mvar (X j)) c | j <- [1..n]] | i <- gs, let c = coeff i one] -- matrix of the linear system b = 1 : replicate (n-1) 0 in case solveLinearSystem m b of -- find v such that m v == b - ie find the values of x1, x2, ... xn Just v -> nf $ V $ zip gs v Nothing -> error "GroupAlgebra.inverse: not invertible" maybeInverse x@(V ts) = let gs = elts $ map fst $ terms x -- all elements in the group generated by the terms cs = map (glexvar . X) gs x' = V $ map (\(g,c) -> (g, unit c)) ts one = x' * (V $ zip gs cs) m = [ [coeff (mvar (X j)) c | j <- gs] | i <- gs, let c = coeff i one] b = 1 : replicate (length gs - 1) 0 in fmap (\v -> nf $ V $ zip gs v) (solveLinearSystem m b) {- in case solveLinearSystem m b of Just v -> Just $ nf $ V $ zip gs v Nothing -> Nothing -}