{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} module Test.MathObj.Gaussian.Bell where import qualified MathObj.Gaussian.Bell as G -- import qualified Algebra.Ring as Ring import qualified Algebra.Laws as Laws import qualified Number.Complex as Complex import Test.NumericPrelude.Utility (testUnit) import Test.QuickCheck (Testable, quickCheck, (==>)) import qualified Test.HUnit as HUnit import Data.Function.HT (nest, ) import PreludeBase as P import NumericPrelude as NP simple :: (Testable t) => (G.T Rational -> t) -> IO () simple f = quickCheck (\x -> f (x :: G.T Rational)) tests :: HUnit.Test tests = HUnit.TestLabel "polynomial" $ HUnit.TestList $ map testUnit $ {- ("convolution, dirac", simple $ Laws.identity (+) zero) : -} ("convolution, commutative", simple $ Laws.commutative G.convolve) : ("convolution, associative", simple $ Laws.associative G.convolve) : ("multiplication, one", simple $ Laws.identity G.multiply G.constant) : ("multiplication, commutative", simple $ Laws.commutative G.multiply) : ("multiplication, associative", simple $ Laws.associative G.multiply) : ("convolution, multplication, fourier", simple $ \x y -> G.fourier (G.convolve x y) == G.multiply (G.fourier x) (G.fourier y)) : ("convolution via translation", simple $ \x y -> G.convolve x y == G.convolveByTranslation x y) : ("convolution via fourier", simple $ \x y -> G.convolve x y == G.convolveByFourier x y) : ("fourier reverse", simple $ \x -> nest 2 G.fourier x == G.reverse x) : ("reverse identity", simple $ \x -> nest 2 G.reverse x == x) : ("fourier unit", quickCheck $ G.fourier G.unit == (G.unit :: G.T Rational)) : ("translate additive", simple $ \x a b -> G.translate a (G.translate b x) == G.translate (a+b) x) : ("translateComplex additive", simple $ \x a b -> G.translateComplex a (G.translateComplex b x) == G.translateComplex (a+b) x) : ("translateComplex real", simple $ \x a -> G.translateComplex (Complex.fromReal a) x == G.translate a x) : ("modulate additive", simple $ \x a b -> G.modulate a (G.modulate b x) == G.modulate (a+b) x) : ("commute translate modulate", simple $ \x a b -> G.modulate b (G.translate a x) == G.turn (a*b) (G.translate a (G.modulate b x))) : ("fourier translate", simple $ \x a -> G.fourier (G.translate a x) == G.modulate a (G.fourier x)) : ("dilate multiplicative", simple $ \x a b -> a>0 && b>0 ==> G.dilate a (G.dilate b x) == G.dilate (a*b) x) : ("dilate by shrink", simple $ \x a -> a>0 ==> G.shrink a x == G.dilate (recip a) x) : ("fourier dilate", simple $ \x a -> a>0 ==> G.fourier (G.dilate a x) == G.amplify a (G.shrink a (G.fourier x))) : []