TestDataGenerators.hs

-- | Test Data Generators
-- Examples to introduce QuickCheck test data generators
-- Functional Programming course 2018.
-- Thomas Hallgren

{-
This started as a skeleton, the definitions were filled in
during the lecture. We ran out of time, so the last few examples
will be completed next week.
-}

module TestDataGenerators where

import Data.List(nub)
import Test.QuickCheck
import Overloading hiding ((==>))

--------------------------------------------------------------------------------
-- * Test data generator for your own data types
-- (using the data types for playing cards from week 1)


--data Suit = Spades | Hearts | Diamonds | Clubs

rSuit :: Gen Suit
rSuit = elements [Spades,Hearts,Diamonds,Clubs]

--data Rank = Numeric Int | Jack | Queen | King | Ace
--all_ranks = [Numeric n|n<-[2..10]]++[Jack,Queen,King,Ace]


rRank_v1 :: Gen Rank
rRank_v1 = elements all_ranks


-- ** A more structured approach to generating ranks

rNumeric :: Gen Rank
rNumeric = elements [Numeric n | n<-[2..10]]

rFaceCard :: Gen Rank
rFaceCard = elements [Jack,Queen,King,Ace]

rRank_v2 :: Gen Rank
rRank_v2 = oneof [rNumeric,rFaceCard]

rRank_v3 :: Gen Rank
rRank_v3 = frequency [(9,rNumeric),(4,rFaceCard)]

rRank = rRank_v3

--data Card = Card Rank Suit

rCard :: Gen Card
rCard = do r <- rRank
           s <- rSuit
           return (Card r s)

--------------------------------------------------------------------------------
-- * More examples of generators defined using do and return

evenInteger :: Gen Integer
evenInteger = do n <- arbitrary
                 return (2*n)

nonNegative :: Gen Integer
nonNegative = do n <- arbitrary
                 return (abs n)

{-
pairsOfEvenIntegers = do x <- evenInteger
                         y <- evenInteger
                         return (x,y)
-}
pairsOfEvenIntegers = doTwice evenInteger

--doTwice :: IO a -> IO (a,a)
doTwice io = do x <- io
                y <- io
                return (x,y)

--data Hand = Empty | Add Card Hand

-- | Generating random hands
rHand_v1 :: Gen Hand
rHand_v1 = oneof [return Empty,
                  do c <- rCard
                     h <- rHand_v1
                     return (Add c h)]

-- | Changing the distribution to get more big hands
rHand_v2 :: Gen Hand
rHand_v2 = frequency [(1,return Empty),
                      (6,do c <- rCard
                            h <- rHand_v2
                            return (Add c h))]


-- | Generating a hand from a list of cards, eliminating duplicated cards
rHand_v3 :: Gen Hand
rHand_v3 = do cs <- arbitrary
              return (listToHand (nub cs))

listToHand :: [Card] -> Hand
listToHand = foldr Add Empty

rHand = rHand_v2

--------------------------------------------------------------------------------
-- * Making instances in the Arbitrary class to specify default test
-- data generators

instance Arbitrary Suit where arbitrary = rSuit
instance Arbitrary Rank where arbitrary = rRank
instance Arbitrary Card where arbitrary = rCard
instance Arbitrary Hand where arbitrary = rHand

--------------------------------------------------------------------------------
-- * Testing test data generators

-- | Not all values of type Rank are valid ranks.
validRank (Numeric n) = 2<=n && n<=10
validRank _           = True

-- | Specifying a test data generator explicitly (using forAll),
-- testing that rRank only generates valid ranks.
prop_all_validRank_1 = forAll rRank validRank

-- | Tesing that 'arbitrary' only generates valid ranks
--prop_all_validRank_2 r =

-- | Examining test data distribution (using collect)
--prop_all_validRank_3 r = 


-- | Examining the distribution of sizes of hands generated by 'arbitrary'
prop_Hand h = collect (size h) True

size Empty     = 0
size (Add c h) = 1+size h

--------------------------------------------------------------------------------
-- * Testing properties of algorithms

-- | Insert a new element at the right position in a sorted list
insert :: Ord a => a -> [a] -> [a]
insert x (y:ys) | x>y = y:insert x ys
insert x ys           = x:ys

-- | Testing if a list is ordered
isOrdered :: Ord a => [a] -> Bool
isOrdered (x1:x2:xs) = x1<=x2 && isOrdered (x2:xs)
isOrdered _          = True

----- We will continue with this on Monday in week 4. -----------

-- | Testing insert, first attempt
prop_insert_1 :: Int -> [Int] -> Bool
prop_insert_1 x xs = isOrdered (insert x xs)

-- | Testing insert, second attempt, adding a precondition
prop_insert_2 :: Int -> [Int] -> Property
prop_insert_2 x xs = isOrdered xs ==> isOrdered (insert x xs)

-- | How many of randomly generated the lists are ordered?
prop_isOrdered xs = collect (isOrdered (xs::[Int])) True

-- ** Testing with ordered lists

-- | Using generator orderedList
prop_insert_3 x = forAll orderedList (\xs -> isOrdered (insert x (xs::[Int])))

-- | Using the type Ordered
prop_insert_4 x (Ordered xs) = isOrdered (insert x (xs::[Int]))

Plain-text version of TestDataGenerators.hs | Valid HTML?