Difference between revisions of "Introduction to QuickCheck1"

From HaskellWiki
Jump to navigation Jump to search
Line 46: Line 46:
 
-- A thin monadic skin layer
 
-- A thin monadic skin layer
 
getList :: IO [Char]
 
getList :: IO [Char]
getList = take5 `fmap` getContents
+
getList = fmap take5 getContents
   
 
-- The actual worker
 
-- The actual worker

Revision as of 20:05, 21 September 2006

A quick introduction to QuickCheck, and testing Haskell code.

Motivation

In September 2006, Bruno Martnez asked the following question:

-- I've written a function that looks similar to this one

getList = find 5 where
     find 0 = return []
     find n = do
       ch <- getChar
       if ch `elem` ['a'..'e'] then do
             tl <- find (n-1)
             return (ch : tl) else
           find n

-- I want to test this function, without hitting the filesystem.  In C++ I
-- would use a istringstream.  I couldn't find a function that returns a
-- Handle from a String.  The closer thing that may work that I could find
-- was making a pipe and convertind the file descriptor.  Can I simplify
-- that function to take it out of the IO monad?

So the problem is: how to effectively test this function in Haskell? The solution we turn to is refactoring and QuickCheck.

Keeping things pure

The reason your getList is hard to test, is that the side effecting monadic code is mixed in with the pure computation, making it difficult to test without moving entirely into a "black box" IO-based testing model. Such a mixture is not good for reasoning about code.

Let's untangle that, and then test the referentially transparent parts simply with QuickCheck. We can take advantage of lazy IO firstly, to avoid all the unpleasant low-level IO handling.

So the first step is to factor out the IO part of the function into a thin "skin" layer:

-- A thin monadic skin layer
getList :: IO [Char]
getList = fmap take5 getContents

-- The actual worker
take5 :: [Char] -> [Char]
take5 = take 5 . filter (`elem` ['a'..'e'])

Testing with QuickCheck

Now we can test the 'guts' of the algorithm, the take5 function, in isolation. Let's use QuickCheck. First we need an Arbitrary instance for the Char type -- this takes care of generating random Chars for us to test with. I'll restrict it to a range of nice chars just for simplicity:

import Data.Char
import Test.QuickCheck

instance Arbitrary Char where
    arbitrary     = choose ('\32', '\128')
    coarbitrary c = variant (ord c `rem` 4)

Let's fire up GHCi (or Hugs) and try some generic properties (its nice that we can use the QuickCheck testing framework directly from the Haskell prompt). An easy one first, a [Char] is equal to itself:

*A> quickCheck ((\s -> s == s) :: [Char] -> Bool)
OK, passed 100 tests.

What just happened? QuickCheck generated 100 random [Char] values, and applied our property, checking the result was True for all cases. QuickCheck generated the test sets for us!

A more interesting property now: reversing twice is the identity:

*A> quickCheck ((\s -> (reverse.reverse) s == s) :: [Char] -> Bool)
OK, passed 100 tests.

Great!

Testing take5

The first step to testing with QuickCheck is to work out some properties that are true of the function, for all inputs. That is, we need to find invariants.

A simple invariant might be:

   

So let's write that as a QuickCheck property:

\s -> length (take5 s) == 5

Which we can then run in QuickCheck as:

*A> quickCheck (\s -> length (take5 s) == 5)
Falsifiable, after 0 tests:
""

Ah! QuickCheck caught us out. If the input string contains less than 5 filterable characters, the resulting string will be less than 5 characters long. So let's weaken the property a bit:

   

That is, take5 returns a string of at most 5 characters long. Let's test this:

*A> quickCheck (\s -> length (take5 s) <= 5)
OK, passed 100 tests.

Good!

Another property

Another thing to check would be that the correct characters are returned. That is, for all returned characters, those characters are members of the set ['a','b','c','d','e'].

We can specify that as:

And in QuickCheck:

*A> quickCheck (\s -> all (`elem` ['a'..'e']) (take5 s))
OK, passed 100 tests.

Excellent. So we can have some confidence that the function neither returns strings that are too long, nor includes invalid characters.

Coverage

One issue with the default QuickCheck configuration, when testing [Char], is that the standard 100 tests isn't enough for our situation. In fact, QuickCheck never generates a String greater than 5 characters long, when using the supplied Arbtrary instance for Char! We can confirm this:

*A> quickCheck (\s -> length (take5 s) < 5)
OK, passed 100 tests.

QuickCheck wastes its time generating different Chars, when what we really need is longer strings. One solution to this is to modify QuickCheck's default configuration to test deeper:

deepCheck p = check (defaultConfig { configMaxTest = 10000}) p

This instructs the system to find at least 10000 test cases before concluding that all is well. Let's check that it is generating longer strings:

*A> deepCheck (\s -> length (take5 s) < 5)
Falsifiable, after 125 tests:
";:iD^*NNi~Y\\RegMob\DEL@krsx/=dcf7kub|EQi\DELD*"

We can check the test data QuickCheck is generating using the 'verboseCheck' hook. Here, testing on integers lists:

*A> verboseCheck (\s -> length s < 5)
0: []
1: [0]
2: []
3: []
4: []
5: [1,2,1,1]
6: [2]
7: [-2,4,-4,0,0]
Falsifiable, after 7 tests:
[-2,4,-4,0,0]

Going further

QuickCheck is effectively an embedded domain specific language for testing Haskell code, and allows for much more complex properties than those you've seen here to be tested. Some sources for further reading are: