Testing

For the exercises below you may want to consult the functions provided by the QuickCheck library, in particular functions such as choose, sized, elements and frequency. We encourage experimenting with your code in an interpreter session. To be able to experiment with QuickCheck, the first two exercises work better if you can show functions. For that you can add the following instance definition to your code:

{-# LANGUAGE FlexibleInstances #-} -- put this at the top of your file

instance (Enum a, Bounded a, Show  a) => Show (a -> Bool) where
  show f = intercalate "\n" (map (\x -> "f " ++ show x ++ " = " ++ show (f x)) [minBound .. maxBound])

Also when you run your tests, you sometimes need to specialize the types a bit. For example, the following code calls all kinds of test functions that the exercises below (except for 4) expect you to come up with.

runTests :: IO ()
runTests = do
  putStrLn "\nExercise 14.1"
  quickCheck (propFilterNoLonger      :: (Bool -> Bool) -> [Bool] -> Bool)
  quickCheck (propFilterAllSatisfy    :: (Bool -> Bool) -> [Bool] -> Bool)
  quickCheck (propFilterAllElements   :: (Bool -> Bool) -> [Bool] -> Bool)
  quickCheck (propFilterCorrect       :: (Bool -> Bool) -> [Bool] -> Bool)
  putStrLn "\nExercise 14.2"
  quickCheck (propMapLength :: (Bool -> Bool) -> [Bool] -> Bool)
  putStrLn "\nExercise 14.3"
  quickCheck $ once (propPermsLength   :: [Int] -> Bool)
  quickCheck $ once (propPermsArePerms :: [Int] -> Bool)
  quickCheck $ once (propPermsCorrect  :: [Int] -> Bool)
  putStrLn "\nExercise 14.5"
  quickCheck (forAll genBSTI isSearchTree)    -- Use forAll to use custom generator
  quickCheck (forAll genBSTI propInsertIsTree)
  quickCheck (forAll genBSTI propInsertIsTreeWrong)
  1. Consider the ubiquitous filter function. There are many properties that you can formulate for the input-output behaviour of filter.

    • Formulate the QuickCheck property that the result list cannot be longer than the input.

      propFilterNoLonger      :: (a -> Bool) -> [a] -> Bool
      propFilterNoLonger p xs = length (filter p xs) <= length xs
    • Formulate the QuickCheck property that all elements in the result list satisfy the given property.

      propFilterAllSatisfy      :: (a -> Bool) -> [a] -> Bool
      propFilterAllSatisfy p xs = all p (filter p xs)
    • Formulate the QuickCheck property that all elements in the result list are present in the input list.

      propFilterAllElements      :: Eq a => (a -> Bool) -> [a] -> Bool
      propFilterAllElements p xs = all (`elem` xs) $ filter p xs
    • Formulate a set of QuickCheck properties to completely characterize the filter function (you may choose also from among the three you have just implemented). Make sure to remove properties that are implied by (a subset of) the other properties.

      -- If some element of xs satisfies p it should be in the result
      propAllPresent      :: Eq a => (a -> Bool) -> [a] -> Bool
      propAllPresent p xs = all notSatisfiedOrPresent xs
        where
          ys = filter p xs
          notSatisfiedOrPresent x = not (p x) || x `elem` ys
      
       -- note that this already implies the propFilterAllElements property,
       -- moreover prevents duplicates (since isIncreasing is strict)
       propSameOrder      :: (a -> Bool) -> [a] -> Bool
       propSameOrder p xs = isIncreasing
                          . map snd
                          . filter (p . fst)
                          $ zip xs [0..]
         where
           isIncreasing ys = all (\(x,y) -> x < y) $ zip ys (tail ys)
      
       propFilterCorrect p xs = all (\p' -> p' p xs) [ propSameOrder
                                                     , propFilterAllSatisfy
                                                     , propAllPresent
                                                     ]
  2. Try to come up with a number of QuickCheck-verifiable properties for the map function, and implement these. Are there any properties of map that are awkward to verify?

  3. Consider the function permutations from the Data.List library, which computes all the possible permutations of elements in a list. We shall be writing QuickCheck tests to verify that this function.

    • Write a QuickCheck property that checks that the correct number of permutations is generated.

      fac 0 = 1
      fac n = n * fac (n-1)
      
      propPermsLength xs = length (permutations xs) == fac (length xs)
    • Write a function isPerm :: Eq a => [a] -> [a] -> Bool that verifies that the two argument lists are permutations of each other.

      isPerm xs ys = all (sameNumOcc xs ys) xs && all (sameNumOcc xs ys) ys
      
      sameNumOcc xs ys x = numOcc xs x == numOcc ys x
      numOcc xs x = length . filter (== x) $ xs
    • Write the QuickCheck property that every list in the output of permutations is a permutation of the input.

      propPermsArePerms    :: Eq a => [a] -> Bool
      propPermsArePerms xs = all (isPerm xs) $ permutations xs
    • Formulate a set of properties to completely characterize the permutations function (you may choose also from among the ones you have just implemented). Make sure to remove properties that are implied by (a subset of) the other properties. Implement the properties that you still need as QuickCheck properties.

  4. Do something similar for the function inits defined in Lecture 3.

  5. Consider the following datatype definition for binary trees that we shall want to use to implement binary search trees:

    data Tree a = Branch a (Tree a) (Tree a) | Leaf

    Write a function isSearchTree :: Ord a => Tree a -> Bool that verifies that its argument is a binary search tree. Then write a function genBSTI :: Gen (Tree Int) that generates binary search trees. Now test the property that given a binary search tree t, inserting a value into the tree results in yet another binary search tree. The code for inserting a new value into the tree is:

    insertTree :: Ord a => a -> Tree a -> Tree a
    insertTree e Leaf = Branch e Leaf Leaf
    insertTree e (Branch x li re)
      | e <= x = Branch x (insertTree e li) re
      | e >  x = Branch x li (insertTree e re)

    Experiment with mutating the implementation of insertTree to find out whether your property can in fact discover that the mutated implementation no longer maps binary search trees to binary search trees.