-- Copyright (c) 2010, David Amos. All rights reserved. {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-} module Math.Algebras.GroupAlgebra where import Math.Algebras.VectorSpace import Math.Algebras.TensorProduct import Math.Algebras.Structures import Math.Algebra.Group.PermutationGroup hiding (action) import Math.Algebra.Field.Base instance Mon (Permutation Int) where munit = 1 mmult = (*) type GroupAlgebra k = Vect k (Permutation Int) -- Monoid Algebra instance instance Num k => Algebra k (Permutation Int) where unit 0 = zero -- V [] unit x = V [(munit,x)] mult = nf . fmap (\(a,b) -> a `mmult` b) -- Set Coalgebra instance -- instance SetCoalgebra (Permutation Int) where {} instance Num k => Coalgebra k (Permutation Int) where counit (V ts) = sum [x | (m,x) <- ts] -- trace comult = fmap (\m -> (m,m)) -- diagonal instance Num k => Bialgebra k (Permutation Int) where {} -- should check that the algebra and coalgebra structures are compatible instance (Num k) => HopfAlgebra k (Permutation Int) where antipode (V ts) = nf $ V [(g^-1,x) | (g,x) <- ts] -- inject permutation into group algebra ip :: [[Int]] -> GroupAlgebra Q ip cs = return $ p cs instance Num k => Module k (Permutation Int) Int where action = nf . fmap (\(g,x) -> x .^ g) -- use *. instead -- r *> m = action (r `te` m)