module Test.Sample where import qualified Numeric.Interpolation.Type as Type import qualified Numeric.Interpolation.Piecewise as Piecewise import qualified Data.Set as Set import Data.Array (accumArray, listArray, ) import Data.List.HT (lengthAtLeast, ) import Test.QuickCheck (Property, quickCheck, (==>), ) withSortedRatios :: ([Rational] -> Rational -> a) -> ([Integer] -> Integer -> a) withSortedRatios f nodeXs x = f (map fromInteger $ Set.toAscList $ Set.fromList nodeXs) (fromInteger x) checkEq :: (Ord x, Eq y, Num y) => Type.T x y ny -> [x] -> x -> Bool checkEq typ nodeXs x = let ys = map (flip (Piecewise.interpolateConstantExt typ) x) (Type.basisFunctions typ nodeXs) bounds = (0, length ys - 1) in listArray bounds ys == accumArray (flip const) 0 bounds (Type.sampleBasisFunctions typ nodeXs x) linear :: [Integer] -> Integer -> Bool linear = withSortedRatios $ checkEq Type.linear hermite1 :: [Integer] -> Integer -> Bool hermite1 = withSortedRatios $ checkEq Type.hermite1 derivativeFree :: Type.T Rational Rational ny -> [Integer] -> Integer -> Property derivativeFree typ = withSortedRatios $ \nodeXs x -> lengthAtLeast 4 nodeXs ==> checkEq typ nodeXs x cubicLinear :: [Integer] -> Integer -> Property cubicLinear = derivativeFree Type.cubicLinear cubicParabola :: [Integer] -> Integer -> Property cubicParabola = derivativeFree Type.cubicParabola tests :: [(String, IO ())] tests = ("linear", quickCheck linear) : ("hermite1", quickCheck hermite1) : ("cubicLinear", quickCheck cubicLinear) : ("cubicParabola", quickCheck cubicParabola) : []