Introduction to QuickCheck1

From HaskellWiki
Revision as of 11:38, 25 October 2008 by Achmed (talk | contribs)
Jump to navigation Jump to search

A quick introduction to QuickCheck, and testing Haskell code.

Мотивация

В сентябре 2006г. Bruno Martínez задал следующий вопрос:

-- Я написал функцию, которая выглядит примерно так

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

-- Я хочу протестировать эту функцию без использования файловой системы.  
-- В C++ я бы использовал istringstream. Я не смог найти функцию, которая 
-- возвращает Handle из String.
.  The closer thing that may work that I could find
-- was making a pipe and convertind the file descriptor.  Могу ли я упростить эту функцию, чтобы убрать из нее монаду IO?

Итак, проблема в том как эффективно протестировать эту функцию в Haskell. Решение к которому мы пришли это рефакторинг и QuickTest.

Сохранение чистоты кода

Причина, по которой сложно тестировать getList является монадический код с побочными эффектами смешанный с чистыми вычислениями, который делает трудным тестирование без полного перевода на модель “черного ящика”, основанного на IO. 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'])

Тестирование с QuickCheck

Теперь мы можем протестировать ‘внутренности’ алгоритма, то есть функцию take5, отдельно. Используем QuickCheck. Для начала нам нужно воплощение(instanse) Arbitrary для типа Char -- this takes care of generating random Chars for us to test with. Для простоты я ограничу это промежутком специальных символов:

import Data.Char
import Test.QuickCheck

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

Запустим GHCi(или Hugs) и испытаем какие-нибудь обобщенные свойства (хорошо что мы можем использовать QuickCheck прямо из Haskell promt). Сначала для простоты [Char] равен самому себе:

*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> quickCheck ((\s -> (reverse.reverse) s == s) :: [Char] -> Bool)
OK, passed 100 tests.

Великолепно!

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:

Note, QuickCheck doesn't need to just be an embedded domain specific language for testing Haskell code. By making instances of Arbitrary for FFI types you can use Haskell and QuickCheck to check code in other languages.