{-# LANGUAGE NoImplicitPrelude #-} module Test.MathObj.Polynomial where import qualified MathObj.Polynomial as Poly import qualified MathObj.Polynomial.Core as PolyCore 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 Data.Tuple.HT (mapPair, mapSnd, ) import Test.NumericPrelude.Utility (testUnit) import Test.QuickCheck (Property, quickCheck, (==>), Testable, ) import qualified Test.HUnit as HUnit import NumericPrelude.Base as P import NumericPrelude.Numeric as NP tensorProductTranspose :: (Ring.C a, Eq a) => [a] -> [a] -> Property tensorProductTranspose xs ys = not (null xs) && not (null ys) ==> PolyCore.tensorProduct xs ys == List.transpose (PolyCore.tensorProduct ys xs) mul :: (Ring.C a, Eq a, ZeroTestable.C a) => [a] -> [a] -> Bool mul xs ys = PolyCore.equal (PolyCore.mul xs ys) (PolyCore.mulShear xs ys) divNormal :: [Rational] -> [Rational] -> Property divNormal x y = case (PolyCore.normalize x, PolyCore.normalize y) of (nx, ny) -> not (null ny) ==> mapSnd PolyCore.normalize (PolyCore.divMod nx ny) == mapPair (PolyCore.normalize, PolyCore.normalize) (PolyCore.divMod x y) normalizedQuotient :: [Rational] -> [Rational] -> Property normalizedQuotient x y = case PolyCore.normalize x of nx -> not (isZero y) ==> let z = fst $ PolyCore.divMod nx y in PolyCore.normalize z == z modulusSize :: [Rational] -> [Rational] -> Property modulusSize x y = case PolyCore.normalize y of ny -> not (null ny) ==> List.length (snd $ PolyCore.divMod x y) < List.length ny 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) : ("division, normalize", quickCheck divNormal) : ("normalized quotient", quickCheck normalizedQuotient) : ("modulus size", quickCheck modulusSize) : []