module Test.Sound.Synthesizer.Plain.Interpolation (T, ip, LinePreserving, lpIp, tests) where import qualified Synthesizer.Plain.Interpolation as Interpolation import Test.QuickCheck (test, Arbitrary(..), elements, {- Property, (==>), -} ) -- import Test.Utility import qualified Algebra.VectorSpace as VectorSpace import qualified Algebra.Module as Module -- import qualified Algebra.RealField as RealField import qualified Algebra.Field as Field -- import qualified Algebra.Ring as Ring -- import qualified Algebra.Additive as Additive import Test.Utility (equalList) import NumericPrelude import PreludeBase import Prelude () data T a v = Cons {name :: String, ip :: Interpolation.T a v} instance Show (T a v) where show x = name x instance (Field.C a, Module.C a v) => Arbitrary (T a v) where arbitrary = elements $ Cons "constant" Interpolation.constant : Cons "linear" Interpolation.linear : Cons "cubic" Interpolation.cubic : [] coarbitrary = undefined data LinePreserving a v = LPCons {lpName :: String, lpIp :: Interpolation.T a v} instance Show (LinePreserving a v) where show x = lpName x instance (Field.C a, Module.C a v) => Arbitrary (LinePreserving a v) where arbitrary = elements $ LPCons "linear" Interpolation.linear : LPCons "cubic" Interpolation.cubic : [] coarbitrary = undefined constant :: (Module.C a v, Eq v) => a -> v -> [v] -> Bool constant t x0 xs = equalList $ map ($(x0:xs)) $ map ($t) $ Interpolation.func Interpolation.constant : Interpolation.func Interpolation.piecewiseConstant : [] linear :: (Module.C a v, Eq v) => a -> v -> v -> [v] -> Bool linear t x0 x1 xs = equalList $ map ($(x0:x1:xs)) $ map ($t) $ Interpolation.func Interpolation.linear : Interpolation.func Interpolation.piecewiseLinear : [] cubic :: (VectorSpace.C a v, Eq v) => a -> v -> v -> v -> v -> [v] -> Bool cubic t x0 x1 x2 x3 xs = equalList $ map ($(x0:x1:x2:x3:xs)) $ map ($t) $ Interpolation.func Interpolation.cubic : Interpolation.func Interpolation.cubicAlt : Interpolation.func Interpolation.piecewiseCubic : [] tests :: [(String, IO ())] tests = ("constant", test (\t x -> constant (t::Rational) (x::Rational))) : ("linear", test (\t x -> linear (t::Rational) (x::Rational))) : ("cubic", test (\t x -> cubic (t::Rational) (x::Rational))) : []