{-# LANGUAGE RebindableSyntax #-} module Test.Number.GaloisField2p32m5 where import qualified Number.GaloisField2p32m5 as GF import qualified Algebra.Laws as Laws import Test.NumericPrelude.Utility (testUnit) import Test.QuickCheck (Testable, quickCheck, (==>)) import qualified Test.HUnit as HUnit import NumericPrelude.Base as P import NumericPrelude.Numeric as NP test :: Testable a => (GF.T -> a) -> IO () test = quickCheck tests :: HUnit.Test tests = HUnit.TestLabel "galois field 2^32-5" $ HUnit.TestList $ map testUnit $ ("addition, zero", test (Laws.identity (+) zero)) : ("addition, commutative", test (Laws.commutative (+))) : ("addition, associative", test (Laws.associative (+))) : ("addition, negate", test (Laws.inverse (+) negate zero)) : ("addition, subtract", test (\x -> Laws.inverse (+) (x-) x)) : ("multiplication, one", test (Laws.identity (*) one)) : ("multiplication, commutative", test (Laws.commutative (*))) : ("multiplication, associative", test (Laws.associative (*))) : ("multiplication, recip", test (\y -> y /= 0 ==> Laws.inverse (*) recip one y)) : ("multiplication, division", test (\y x -> y /= 0 ==> Laws.inverse (*) (x/) x y)) : ("multiplication and addition, distributive", test (Laws.leftDistributive (*) (+))) : []