{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE InstanceSigs #-} -- In order to use quickcheck library, -- you will need to do: cabal install QuickCheck --lib -- in the command line. import Test.QuickCheck import Control.Monad import Data.List hiding (insert) -- quickCheck :: Testable prop => prop -> IO () -- verboseCheck :: Testable prop => prop -> IO () -- withMaxSuccess :: Testable prop => Int -> prop -> Property -- QuickCheck's Testable class. qsort :: Ord a => [a] -> [a] qsort [] = [] qsort (x:xs) = qsort lhs ++ [x] ++ qsort rhs where lhs = filter (< x) xs rhs = filter (>= x) xs prop_idempotent :: [Int] -> Bool prop_idempotent xs = qsort (qsort xs) == qsort xs -- Note that testing is best done with concrete types. -- Because quickcheck will instantiate a value of a -- polymorphic type to Unit type (). prop_idempotent' :: Ord a => [a] -> Bool prop_idempotent' xs = qsort (qsort xs) == qsort xs sorted :: Ord a => [a] -> Bool sorted [] = True sorted [x] = True sorted (x:y:xs) = if x <= y then sorted (xs) else False -- if x <= y then sorted (y:xs) else False prop1 xs = sorted xs && sorted (tail xs) -- A (false) property stating that every list is sorted prop_sorted :: [Int] -> Bool prop_sorted xs = sorted xs prop_quick_sort :: [Int] -> Property prop_quick_sort xs = not (null xs) ==> (prop1 $ qsort xs) -- How to find properties to test? -- 1. Algebraic laws. prop_app_unit :: [Int] -> Bool prop_app_unit xs = [] ++ xs == xs prop_app_unit' :: [Int] -> Bool prop_app_unit' xs = xs == xs ++ [] prop_app_assoc :: [Int] -> [Int] -> [Int] -> Bool prop_app_assoc xs ys zs = (xs ++ ys) ++ zs == xs ++ (ys ++ zs) -- 2. Equivalent of implementations. prop_qsort_sort :: [Int] -> Bool prop_qsort_sort xs = qsort xs == sort xs -- Some other way to build testable properties. -- Let's test the 'replicate' function. prop_replicate :: Int -> Int -> Int -> Bool prop_replicate n x i = replicate n x !! i == x -- A better property using '==>' prop_replicate' :: Int -> Int -> Int -> Property prop_replicate' n x i = (i < n && 0 <= i) ==> replicate n x !! i == x -- Quickcheck's Arbitrary class and the 'generate' function. -- Some useful combinators for generators -- generate $ choose (0,1) -- generate $ elements ['a','e','i','o','u'] -- generate $ (vector 100 :: Gen [Int]) -- generate $ frequency [(99, elements [True]), (1, elements [False])] -- generate $ shuffle [0 .. 10] data Color = Red | Blue | Green deriving (Show) instance Arbitrary Color where arbitrary :: Gen Color arbitrary = elements [Red, Blue, Green] -- A better property using forAll combinator. prop_replicate'' :: Int -> Property prop_replicate'' x = forAll (elements [1 .. 100]) (\ n -> forAll (choose (0, n-1)) (\ i -> replicate n x !! i == x))