-- Copyright (c) 2010, David Amos. All rights reserved. {-# LANGUAGE FlexibleInstances, TypeSynonymInstances #-} module Math.Test.TAlgebras.TGroupAlgebra where import Test.QuickCheck import Math.Algebra.Group.PermutationGroup import Math.Test.TPermutationGroup -- for instance Arbitrary (Permutation Int) import Math.Algebras.VectorSpace import Math.Algebras.TensorProduct import Math.Algebras.Structures import Math.Algebras.GroupAlgebra import Math.Test.TAlgebras.TStructures {- instance Arbitrary (TensorAlgebra Integer) where arbitrary = do ts <- arbitrary :: Gen [([Int], Integer)] return $ nf $ V ts -} instance Arbitrary (GroupAlgebra Integer) where arbitrary = do ts <- arbitrary :: Gen [(Permutation Int, Integer)] return $ nf $ V ts {- prop_Algebra_TensorAlgebra (k,x,y,z) = prop_Algebra (k,x,y,z) where types = (k,x,y,z) :: (Integer, TensorAlgebra Integer, TensorAlgebra Integer, TensorAlgebra Integer) prop_Coalgebra_TensorAlgebra x = prop_Coalgebra x where types = x :: TensorAlgebra Integer -} prop_Algebra_GroupAlgebra (k,x,y,z) = prop_Algebra (k,x,y,z) where types = (k,x,y,z) :: (Integer, GroupAlgebra Integer, GroupAlgebra Integer, GroupAlgebra Integer) -- have to split the 8-tuple into two 4-tuples to avoid having to write Arbitrary instance prop_Algebra_Linear_GroupAlgebra ((k,l,m,n),(x,y,z,w)) = prop_Algebra_Linear (k,l,m,n,x,y,z,w) where types = (k,l,m,n,x,y,z,w) :: (Integer, Integer, Integer, Integer, GroupAlgebra Integer, GroupAlgebra Integer, GroupAlgebra Integer, GroupAlgebra Integer) prop_Coalgebra_GroupAlgebra x = prop_Coalgebra x where types = x :: GroupAlgebra Integer prop_Coalgebra_Linear_GroupAlgebra (k,l,x,y) = prop_Coalgebra_Linear (k,l,x,y) where types = (k,l,x,y) :: (Integer, Integer, GroupAlgebra Integer, GroupAlgebra Integer) prop_Bialgebra_GroupAlgebra (k,x,y) = prop_Bialgebra (k,x,y) where types = (k,x,y) :: (Integer, GroupAlgebra Integer, GroupAlgebra Integer) prop_HopfAlgebra_GroupAlgebra x = prop_HopfAlgebra x where types = x :: GroupAlgebra Integer