{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} module Test.MathObj.Polynomial where import qualified MathObj.Polynomial as Poly import qualified Algebra.IntegralDomain as Integral import qualified Algebra.Ring as Ring import qualified Algebra.ZeroTestable as ZeroTestable import qualified Algebra.Laws as Laws import qualified Data.List as List import Test.NumericPrelude.Utility (testUnit) import Test.QuickCheck (Property, quickCheck, (==>), Testable, ) import qualified Test.HUnit as HUnit import PreludeBase as P import NumericPrelude as NP tensorProductTranspose :: (Ring.C a, Eq a) => [a] -> [a] -> Property tensorProductTranspose xs ys = not (null xs) && not (null ys) ==> Poly.tensorProduct xs ys == List.transpose (Poly.tensorProduct ys xs) mul :: (Ring.C a, Eq a, ZeroTestable.C a) => [a] -> [a] -> Bool mul xs ys = Poly.equal (Poly.mul xs ys) (Poly.mulShear xs ys) test :: Testable a => (Poly.T Integer -> a) -> IO () test = quickCheck testRat :: Testable a => (Poly.T Rational -> a) -> IO () testRat = quickCheck tests :: HUnit.Test tests = HUnit.TestLabel "polynomial" $ HUnit.TestList $ map testUnit $ ("tensor product", quickCheck (tensorProductTranspose :: [Integer] -> [Integer] -> Property)) : ("mul speed", quickCheck (mul :: [Integer] -> [Integer] -> Bool)) : ("addition, zero", test (Laws.identity (+) zero)) : ("addition, commutative", test (Laws.commutative (+))) : ("addition, associative", test (Laws.associative (+))) : ("multiplication, one", test (Laws.identity (*) one)) : ("multiplication, commutative", test (Laws.commutative (*))) : ("multiplication, associative", test (Laws.associative (*))) : ("multiplication and addition, distributive", test (Laws.leftDistributive (*) (+))) : ("division", testRat (Integral.propInverse)) : []