Difference between revisions of "Introduction to QuickCheck1"

From HaskellWiki
Jump to navigation Jump to search
m (Introduction to QuickCheck moved to Introduction to QuickCheck1: QuickCheck2 is what people will be using.)
(14 intermediate revisions by 7 users not shown)
Line 1: Line 1:
A quick introduction to QuickCheck, and testing Haskell code.
+
A quick introduction to QuickCheck, and testing Haskell code. See [[Introduction_to_QuickCheck2| Introduction to QuickCheck2]] for the QC2 version
   
== Мотивация ==
+
== Motivation ==
   
В сентябре 2006г. Bruno Martínez
+
In September 2006, Bruno Martínez
[http://www.haskell.org/pipermail/haskell-cafe/2006-September/018302.html задал]
+
[http://www.haskell.org/pipermail/haskell-cafe/2006-September/018302.html asked]
  +
the following question:
следующий вопрос:
 
   
 
<haskell>
 
<haskell>
  +
-- I've written a function that looks similar to this one
-- Я написал функцию, которая выглядит примерно так
 
   
 
getList = find 5 where
 
getList = find 5 where
Line 19: Line 19:
 
find n
 
find n
   
  +
-- I want to test this function, without hitting the filesystem. In C++ I
-- Я хочу протестировать эту функцию без использования файловой системы.
 
-- В C++ я бы использовал istringstream. Я не смог найти функцию, которая
+
-- 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
-- возвращает Handle из String.
 
  +
-- was making a pipe and converting the file descriptor. Can I simplify
. The closer thing that may work that I could find
 
  +
-- that function to take it out of the IO monad?
-- was making a pipe and convertind the file descriptor. Могу ли я упростить эту функцию, чтобы убрать из нее монаду IO?
 
 
 
</haskell>
 
</haskell>
   
  +
So the problem is: how to effectively test this function in Haskell? The
Итак, проблема в том как эффективно протестировать эту функцию в Haskell. Решение к которому мы пришли это рефакторинг и QuickTest.
 
  +
solution we turn to is refactoring and QuickCheck.
 
== Сохранение чистоты кода ==
 
   
  +
== Keeping things pure ==
Причина, по которой сложно тестировать getList является монадический код с побочными эффектами смешанный с чистыми вычислениями, который делает трудным тестирование без полного перевода на модель “черного ящика”, основанного на IO. Such a mixture is not good for reasoning about code.
 
   
  +
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
 
Let's untangle that, and then test the referentially transparent
Line 51: Line 53:
 
</haskell>
 
</haskell>
   
== Тестирование с QuickCheck ==
+
== Testing with QuickCheck ==
   
  +
Now we can test the 'guts' of the algorithm, the take5 function, in
Теперь мы можем протестировать ‘внутренности’ алгоритма, то есть функцию take5, отдельно. Используем QuickCheck. Для начала нам нужно воплощение(instanse) Arbitrary для типа Char -- this takes care of generating random Chars for us to
 
  +
isolation. Let's use QuickCheck. First we need an Arbitrary instance for
test with. Для простоты я ограничу это промежутком специальных символов:
 
  +
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:
   
 
<haskell>
 
<haskell>
Line 65: Line 70:
 
</haskell>
 
</haskell>
   
  +
Let's fire up GHCi (or Hugs) and try some generic properties (its nice
Запустим GHCi(или Hugs) и испытаем какие-нибудь обобщенные свойства (хорошо что мы можем использовать QuickCheck прямо из Haskell promt). Сначала для простоты [Char] равен самому себе:
 
  +
that we can use the QuickCheck testing framework directly from the
  +
Haskell prompt). An easy one first, a [Char] is equal to itself:
   
 
<haskell>
 
<haskell>
Line 76: Line 83:
 
QuickCheck ''generated the test sets for us''!
 
QuickCheck ''generated the test sets for us''!
   
  +
A more interesting property now: reversing twice is the identity:
Теперь более интересное свойство: двойное обращение тождественно:
 
   
 
<haskell>
 
<haskell>
Line 83: Line 90:
 
</haskell>
 
</haskell>
   
  +
Great!
Великолепно!
 
   
 
== Testing take5 ==
 
== Testing take5 ==
Line 143: Line 150:
 
[Char], is that the standard 100 tests isn't enough for our situation.
 
[Char], is that the standard 100 tests isn't enough for our situation.
 
In fact, QuickCheck never generates a String greater than 5 characters
 
In fact, QuickCheck never generates a String greater than 5 characters
long, when using the supplied Arbtrary instance for Char! We can confirm
+
long, when using the supplied Arbitrary instance for Char! We can confirm
 
this:
 
this:
   
Line 192: Line 199:
 
those you've seen here to be tested. Some sources for further reading
 
those you've seen here to be tested. Some sources for further reading
 
are:
 
are:
* [http://www.cse.unsw.edu.au/~dons/data/QuickCheck.html The QuickCheck source]
+
* [http://code.haskell.org/QuickCheck/stable/Test/ The QuickCheck source]
** [http://mathburritos.org/code/darcsweb/browse?r=ghcQC;a=summary QuickCheck GHC batch script]
+
* [http://hackage.haskell.org/package/QuickCheck-2.4.2 QuickCheck Library documentation]
* [http://haskell.org/ghc/docs/latest/html/libraries/QuickCheck/Test-QuickCheck.html Library documentation]
+
* [http://www.cse.chalmers.se/~rjmh/QuickCheck/manual.html QuickCheck v1 Manual]
* [http://www.cse.unsw.edu.au/~dons/code/fps/tests/Properties.hs A large testsuite of QuickCheck code]
+
* [http://hackage.haskell.org/trac/ghc/browser/libraries/bytestring/tests?rev=bc96abdb6d3777bdc4eaaccf37494f535405d4e1 A large testsuite of QuickCheck code]
* [http://www.cs.chalmers.se/~rjmh/QuickCheck/manual.html QuickCheck Manual]
 
* Paper [http://www.cs.chalmers.se/~koen/pubs/icfp00-quickcheck.ps QuickCheck: A Lightweight Tool for Random Testing of Haskell Programs], Koen Claessen and John Hughes. In Proc. of International Conference on Functional Programming (ICFP), ACM SIGPLAN, 2000.
 
* Paper [http://www.math.chalmers.se/~koen/pubs/entry-fop-quickcheck.html Specification Based Testing with QuickCheck], Koen Claessen and John Hughes. In Jeremy Gibbons and Oege de Moor (eds.), The Fun of Programming, Cornerstones of Computing, pp. 17--40, Palgrave, 2003.
 
* Paper [http://www.math.chalmers.se/~koen/pubs/entry-tt04-quickcheck.html QuickCheck: Specification-based Random Testing], Koen Claessen. Presentation at Summer Institute on Trends in Testing: Theory, Techniques and Tools, August 2004.
 
* Paper [http://www.cs.chalmers.se/~rjmh/Papers/QuickCheckST.ps Testing Monadic Programs with QuickCheck], Koen Claessen, John Hughes. SIGPLAN Notices 37(12): 47-59 (2002):
 
* More [http://haskell.org/haskellwiki/Research_papers/Testing_and_correctness research on correctness and testing] in Haskell
 
 
* Tutorial: [[QuickCheck as a test set generator]]
 
* Tutorial: [[QuickCheck as a test set generator]]
 
* Tutorial: [[QuickCheck / GADT]]
 
* Tutorial: [[QuickCheck / GADT]]
 
* More [[Research_papers/Testing_and_correctness | research on correctness and testing]] in Haskell
  +
  +
* 2012 Blog article: [http://ics.p.lodz.pl/~stolarek/blog/2012/10/code-testing-in-haskell/ Code testing in Haskell]
  +
* 2009 Blog article: [http://koweycode.blogspot.com/2009/07/some-ideas-for-practical-quickcheck.html some ideas for practical QuickCheck]
 
* 2004 Paper [http://dl.acm.org/citation.cfm?doid=351240.351266 QuickCheck: Specification-based Random Testing], Koen Claessen. Presentation at Summer Institute on Trends in Testing: Theory, Techniques and Tools, August 2004.
 
* 2003 Paper [http://www.cs.utexas.edu/~ragerdl/fmcad11/slides/tutorial-a.pdf Specification Based Testing with QuickCheck], Koen Claessen and John Hughes. In Jeremy Gibbons and Oege de Moor (eds.), The Fun of Programming, Cornerstones of Computing, pp. 17--40, Palgrave, 2003.
 
* 2002 Paper [http://www.cse.chalmers.se/~rjmh/Papers/QuickCheckST.ps Testing Monadic Programs with QuickCheck], Koen Claessen, John Hughes. SIGPLAN Notices 37(12): 47-59 (2002):
 
* 2000 Paper [http://www.eecs.northwestern.edu/~robby/courses/395-495-2009-fall/quick.pdf QuickCheck: A Lightweight Tool for Random Testing of Haskell Programs], Koen Claessen and John Hughes. In Proc. of International Conference on Functional Programming (ICFP), ACM SIGPLAN, 2000.
   
 
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.
 
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.

Revision as of 19:54, 13 January 2013

A quick introduction to QuickCheck, and testing Haskell code. See Introduction to QuickCheck2 for the QC2 version

Motivation

In September 2006, Bruno Martínez 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 converting 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 Arbitrary 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.