module Test.Piece where import qualified Numeric.Interpolation.Piece as Piece import qualified Numeric.Interpolation.Private.Piece as PiecePriv import Test.QuickCheck (Property, quickCheck, (==>), ) type Point = (Rational, Rational) linearCommutative :: Point -> Point -> Rational -> Property linearCommutative p1@(x1,_) p2@(x2,_) x = x1/=x2 ==> Piece.linear p1 p2 x == Piece.linear p2 p1 x type PointSlope = (Rational, (Rational, Rational)) hermite1Commutative :: PointSlope -> PointSlope -> Rational -> Property hermite1Commutative p1@(x1,_) p2@(x2,_) x = x1/=x2 ==> Piece.hermite1 p1 p2 x == Piece.hermite1 p2 p1 x linearHermite1 :: Point -> Point -> Rational -> Property linearHermite1 p1@(x1,y1) p2@(x2,y2) x = x1/=x2 ==> Piece.linear p1 p2 x == let slope = (y2-y1)/(x2-x1) in Piece.hermite1 (x1, (y1,slope)) (x2, (y2, slope)) x hermite1Alternative :: PointSlope -> PointSlope -> Rational -> Property hermite1Alternative p1@(x1,_) p2@(x2,_) x = x1/=x2 ==> Piece.hermite1 p1 p2 x == PiecePriv.hermite1 p1 p2 x tests :: [(String, IO ())] tests = ("linearCommutative", quickCheck linearCommutative) : ("hermite1Commutative", quickCheck hermite1Commutative) : ("linearHermite1", quickCheck linearHermite1) : ("hermite1Alternative", quickCheck hermite1Alternative) : []