-- vim: sw=2: ts=2: expandtab: module Main where import Test.QuickCheck.PolyQC import Prop -- the module that defiens the properties p0, p1, p2, p3, p4 -- p0 x = x == x -- p1 x y z = x + (y + z) == (x + y) + z -- p2 x y = x + y == y + x -- p3 x = x == negate (negate x) -- p4 p = (fst p, snd p) == p main = do putStrLn "testing p0 =======================================" print =<< polyQuickCheck' "Prop" "p0" ["Bool","Int","Double"] putStrLn "testing p1 =======================================" print =<< polyQuickCheck' "Prop" "p1" ["Bool","Int","Double"] putStrLn "testing p2 =======================================" print =<< polyQuickCheck' "Prop" "p2" ["Bool","Int","Double"] putStrLn "testing p3 =======================================" print =<< polyQuickCheck' "Prop" "p3" ["Bool","Int","Double"] putStrLn "testing p4 =======================================" print =<< polyQuickCheck' "Prop" "p4" ["Bool","Int","Double"] return () {- *Main> :t p0 p0 :: (Eq a) => a -> Bool *Main> :t p1 p1 :: (Num a) => a -> a -> a -> Bool *Main> :t p2 p2 :: (Num a) => a -> a -> Bool *Main> :t p3 p3 :: (Num a) => a -> Bool *Main> :t p4 p4 :: (Eq a, Eq b) => (a, b) -> Bool *Main> main testing p0 ======================================= Right ["(\"(Eq Bool) => Bool -> Bool\",+++ OK, passed 100 tests. ())","(\"(Eq Int) => Int -> Bool\",+++ OK, passed 100 tests. ())","(\"(Eq Double) => Double -> Bool\",+++ OK, passed 100 tests. ())"] testing p1 ======================================= Right ["(\"(Num Int) => Int -> Int -> Int -> Bool\",+++ OK, passed 100 tests. ())","(\"(Num Double) => Double -> Double -> Double -> Bool\",*** Failed! Falsifiable (after 9 tests and 2 shrinks): 4.0 -26.0 8.777291602197652 ())"] testing p2 ======================================= Right ["(\"(Num Int) => Int -> Int -> Bool\",+++ OK, passed 100 tests. ())","(\"(Num Double) => Double -> Double -> Bool\",+++ OK, passed 100 tests. ())"] testing p3 ======================================= Right ["(\"(Num Int) => Int -> Bool\",+++ OK, passed 100 tests. ())","(\"(Num Double) => Double -> Bool\",+++ OK, passed 100 tests. ())"] testing p4 ======================================= Right ["(\"(Eq Bool, Eq Bool) => (Bool, Bool) -> Bool\",+++ OK, passed 100 tests. ())","(\"(Eq Bool, Eq Int) => (Bool, Int) -> Bool\",+++ OK, passed 100 tests. ())","(\"(Eq Bool, Eq Double) => (Bool, Double) -> Bool\",+++ OK, passed 100 tests. ())","(\"(Eq Int, Eq Bool) => (Int, Bool) -> Bool\",+++ OK, passed 100 tests. ())","(\"(Eq Int, Eq Int) => (Int, Int) -> Bool\",+++ OK, passed 100 tests. ())","(\"(Eq Int, Eq Double) => (Int, Double) -> Bool\",+++ OK, passed 100 tests. ())","(\"(Eq Double, Eq Bool) => (Double, Bool) -> Bool\",+++ OK, passed 100 tests. ())","(\"(Eq Double, Eq Int) => (Double, Int) -> Bool\",+++ OK, passed 100 tests. ())","(\"(Eq Double, Eq Double) => (Double, Double) -> Bool\",+++ OK, passed 100 tests. ())"] -}