{-# LANGUAGE TemplateHaskell #-} import Test.QuickCheck import Data.List ( (\\), minimum, sort ) import Prelude hiding (Either(..)) qsort :: Ord a => [a] -> [a] qsort [] = [] qsort (x:xs) = qsort (filter (=x) xs) prop_idempotence :: [Int] -> Bool prop_idempotence xs = qsort (qsort xs) == qsort xs -- Property: keep all list elements in result prop_preservation :: [Int] -> Bool prop_preservation xs = null (qsort xs \\ xs) && null (xs \\ qsort xs) -- Property: is the first element of a sorted list the minimum? prop_smallest_first :: [Int] -> Property prop_smallest_first xs = not (null xs) ==> head (qsort xs) == minimum xs -- Regression test: test quicksort against another sort operation prop_regression :: [Int] -> Bool prop_regression xs = qsort xs == sort xs -- Unit tests: prop_qsort914 = qsort [9,1,4] == [1,4,9] prop_regression_small :: [Int] -> Property prop_regression_small xs = classify (length xs <= 5) "small" (qsort xs == sort xs) prop_regression_small_big :: [Int] -> Property prop_regression_small_big xs = classify (length xs <= 5) "small" $ classify (length xs >= 20) "big" $ classify (length xs >= 50) "verybig" $ qsort xs == sort xs prop_regression_collect :: [Int] -> Property prop_regression_collect xs = collect (length xs) $ qsort xs == sort xs -- Datatype for digits data Digit = Digit Int deriving (Eq,Ord) instance Show Digit where show (Digit i) = show i instance Arbitrary Digit where arbitrary = do --d <- elements [0..9] d <- choose (0,9) return (Digit d) prop_regression_digit :: [Digit] -> Property prop_regression_digit xs = collect (length xs) $ qsort xs == sort xs -- An arbitrary instance for the Either type: data Either a b = Left a | Right b deriving (Eq,Ord,Show) instance (Arbitrary a, Arbitrary b) => Arbitrary (Either a b) where arbitrary = do x <- arbitrary -- Left value y <- arbitrary -- Right value oneof [return (Left x), return (Right y)] {- -- An arbitrary instance for list types (predefined!): instance Arbitrary a => Arbitrary [a] where arbitrary = sized $ \n -> do k <- choose (0,n) makeArbitraryList k -- same as `vector`: makeArbitraryList :: Arbitrary a => Int -> Gen [a] makeArbitraryList | n <= 0 = return [] | otherwise = do x <- arbitrary xs <- makeArbitraryList (n - 1) return (x:xs) -} -- Check all properties in this module: return [] testAll = $quickCheckAll