-- Copyright (c) 2010, David Amos. All rights reserved. {-# LANGUAGE FlexibleInstances, TypeSynonymInstances #-} module Math.Test.TAlgebras.TQuaternions where import Test.QuickCheck import Math.Algebras.VectorSpace import Math.Algebras.TensorProduct import Math.Algebras.Quaternions import Math.Test.TAlgebras.TStructures instance Arbitrary HBasis where arbitrary = elements [One,I,J,K] instance Arbitrary (Quaternion Integer) where arbitrary = do ts <- arbitrary :: Gen [(HBasis, Integer)] return $ nf $ V ts prop_Algebra_Quaternion (k,x,y,z) = prop_Algebra (k,x,y,z) where types = (k,x,y,z) :: (Integer, Quaternion Integer, Quaternion Integer, Quaternion Integer) prop_Coalgebra_Quaternion x = prop_Coalgebra x where types = x :: Quaternion Integer -- Fails - the algebra and coalgebra structures I've given are not compatible prop_Bialgebra_Quaternion (k,x,y) = prop_Bialgebra (k,x,y) where types = (k,x,y) :: (Integer, Quaternion Integer, Quaternion Integer) {- prop_FrobeniusRelation_Quaternion (x,y) = prop_FrobeniusRelation (x,y) where types = (x,y) :: (Quaternion Integer, Quaternion Integer) -- !! fails, because the counit we have given is not a Frobenius form -}