Posted on August 9, 2021 by Volodya Kalnitsky

Property-based Testing With QuickCheck

Showing how the real code can be effectively tested using QuickCheck

What Is Property-Based Testing?

Property-based testing (PBT) is the approach to software testing that implies an automatic check of the function properties (predicates) specified by the tester. Checking, i.e. search for counter-examples is carried out using the automatically generated input data. PBT allows developers to increase the test coverage significantly and spend their time efficiently saving them the trouble of inventing the input data for tests on their own. Normally, the values generated during property-based testing is not limited by anything, which is why the check can be carried out using the values the developer may have forgotten or neglected to include in the unit tests (surely, you won’t brute force all the values of input parameters).

Green check mark The PBT approach was popularized by the QuickCheck library written in Haskell, and in this post, we’ll show how to use this tool effectively.

As a rule, PBT libraries consist of two parts:

  • Runners, which are in charge of running the tests and checking the validity of the predicate.
  • Arbitraries that take care of pseudo-random data generation while enabling shrinking, i.e. the way to “simplify” the found counter-example.

In my opinion, the skill of PBT consists in the ability to create a fast and effective data generator that allows obtaining potentially “problematic” values. To that end, you need both the knowledge of the subject domain and the skill of using the tools provided by the QuickCheck library.

In this post, I’ll show how the real code can be tested using QuickCheck.

QuickCheck library

The type responsible for data generation is the wrapper around a function that accepts the pseudo-random generator and also an integer parameter setting restrictions on the generated data size.

newtype Gen a = MkGen { unGen :: QCGen -> Int -> a }

The size constraint is needed for inductive types, e.g. for the tree depth (so that the tree wouldn’t be infinite).

The generator size can be changed using the functions resize and scale, and the current generator parameter can be obtained using the sized function:

resize :: Int -> Gen a -> Gen a
scale :: (Int -> Int) -> Gen a -> Gen a
sized :: (Int -> Gen a) -> Gen a

Implementation of the arbitrary values generation and shrinking for a specific type is an instance of the Arbitrary class that has two methods: arbitrary, i.e. the value generator itself, and shrink, which is the function used to get the list of “shrunken” values.

class Arbitrary a where
  arbitrary :: Gen a
  shrink :: a -> [a]

Properties are set using the type Property. We won’t go into the details of its implementation because the library provides combinators to create various properties of the functions which allow, among other things, checking the truth or the falsehood of predicates.

The properties check is started by the function that goes by the same name, quickCheck.

In addition to the above said, QuickCheck allows displaying information about the test data values distribution analysis.

Further, we’ll describe all these features of the library using a small example.

QuickCheck usage example

By way of example, let’s consider a naive parser and serializer for a JSON subset where there are no Boolean or Null types, and where spaces that are optional in JSON are prohibited.

The data type is declared in the following way:

data Json
  = Object [(String, Json)]
  | Array [Json]
  | String String
  | Number Double
  deriving (Show, Eq, Generic)

To set the limit for the tree size, we should avoid creating new branches if the size parameter is equal to zero and enable the parameter reduction in recursive calls.

Let’s write a correct instance for the Arbitrary class:

instance Arbitrary Json where
  arbitrary = sized arbitrary'
    where
      arbitrary' 0 = pure $ Array []
      arbitrary' n =
        oneof [ Object <$> resize (n `div` 2) arbitrary
              , Array <$> resize (n `div` 2) arbitrary
              , String <$> arbitrary
              , Number <$> arbitrary
              ]

It should be noted that here we’re dividing the size by 2 and don’t decrease by one. The instance Arbitrary for the list will produce a list of the length not exceeding the size. In this way, we can create a logarithmic, not exponential, dependency of a medium-size tree on the size. In practice, we don’t need a linear dependency, we only need to avoid the discrepancy occurring because each of the constructors Array or Object generates an infinite tree (this is because the exit from recursion is statistically rarer than the generation of new constructors). Here the constant “2” is selected randomly.

Let’s test our generator:

 V1> generate (arbitrary  :: Gen Json)
Object [("%\1003607*SF\STX\166973ti\59844B",Array [Number 3.575309217492902]),("",String "4\USO\DLE\1065483e\STX\FS}\146478"),("\DEL\59467AU\1020011\997210I\57595\EM\fDm\DEL",Object []),("sX%8\1083528D-r\146202{S",Array [Array [],Array [Object [],Array [],Array []]]),("",Number 4.890220146762664),("\158800m\1047365\&07",Array [String "\5524\1069330"])]

 V1> generate (arbitrary  :: Gen Json)
String "\ACK[Q\1038205\64353EFz|\159918\77959\&0\1013613-\12406\1042312"

 V1> generate (arbitrary  :: Gen Json)
Number (-6.706967599855459)

As we can see, the Arbitrary instance for the String type generates “potentially problematic” lines to try and trigger typical errors in the applications using the data. The programmer should keep in mind special symbols, empty lines, whitespaces, etc.

Now let’s implement the serializer and the parser for our data type.

Serialization is implemented rather bluntly:

serialize :: Json -> String
serialize (Object props) =
  "{" ++ intercalate "," (map toKeyValue props) ++ "}"
  where
    toKeyValue (key, value) = serializeString key ++ ":" ++ serialize value
serialize (Array entries) =
  "[" ++ intercalate "," (map serialize entries) ++ "]"
serialize (String str) = show str
serialize (Number n) = show n

We’ll carry out parsing using the standard approach implemented in the libraries of parser combinators – all parsing functions will be of the type String -> Maybe (a, String), where a is the type we want to obtain as the result, and the second component of the pair (of the String type) is the line part that was not taken up by the parser.

The selected format is convenient because we can see from the first symbol what type we’re dealing with, which makes backtracking unnecessary.

Here we won’t describe the code itself but will move on to testing.

decode :: String -> Maybe (Json, String)
decode ('{' : rest)                = first Object <$> decodeProps rest
decode ('[' : rest)                = first Array <$> decodeArray rest
decode ('"' : rest)                = first String <$> decodeString rest
decode (c : rest)
  | isDigit c = first Number <$> decodeNumber (c:rest)
decode _ = Nothing

decodeProps :: String -> Maybe ([(String, Json)], String)
decodeProps ('}' : rest) = Just ([], rest)
decodeProps (',' : rest) = decodeProps rest
decodeProps ('"' : input) = do
  (key, ':' : input') <- decodeString input
  (value, input'') <- decode input'
  (restProps, input''') <- decodeProps input''
  return ((key, value) : restProps, input''')

decodeList :: String -> Maybe ([Json], String)
decodeList (']' : rest) = Just ([], rest)
decodeList (',' : rest) = decodeList rest
decodeList input = do
  (entry, rest) <- decode input
  first (entry :) <$> decodeList rest

decodeString :: String -> Maybe (String, String)
decodeString ('\\' : '"' : rest) = first ('"' :) <$> decodeString rest
decodeString ('"' : rest)        = Just ("", rest)
decodeString (c : rest)          = first (c :) <$> decodeString rest
decodeString _                   = Nothing

decodeNumber :: String -> Maybe (Double, String)
decodeNumber = listToMaybe . reads

Finally, the parse will let us get the result only if the line has been successfully parsed using decode:

parse :: String -> Maybe Json
parse input = case decode input of
  Just (json, "") -> Just json
  _               -> Nothing

Let’s formulate the property we’d like to test (parsing is the inverse function for serialization, i.e. the parse function applied to a serialized value produces the initial value).

prop_serialize_parse :: Json -> Property
prop_serialize_parse json = parse (serialize json) === Just json

Now let’s run the check of this property:

 V1> quickCheck prop_serialize_parse
*** Failed! Falsified (after 4 tests and 2 shrinks):
Array [String "\n"]

Obviously, we’ve forgotten about the part of escape sequences used in the instance Show String.

For the sake of simplicity, let’s give up our homebrewed implementation of the decodeString and reuse reads from the Prelude.

It is assumed that the opening quotation mark was taken up by the calling function, so it’s necessary to get it back:

decodeString :: String -> Maybe (String, String)
decodeString = listToMaybe . reads . ('"':)

We also find out that the numbers can be negative:

*> verboseCheck prop_serialize_parse
Failed:
*** Failed! Falsified (after 5 tests and 5 shrinks):
Array [Object [("",Number (-1.0))]]

Which can be also easily accounted for in our parser:

decode (c : rest)
  | isDigit c || c == '-' = first Number <$> decodeNumber (c:rest)
> quickCheck prop_serialize_parse
*** Failed! Falsified (after 4 tests and 7 shrinks):
Object [("",Object [("",String "\n")])]

Let’s try and test our implementation of the JSON subset with regard to the existing one (the library aeson). We want to make sure that serialization returns a valid JSON:

prop_serialize_returns_json :: Json -> Property
prop_serialize_returns_json json = Aeson.decode @Aeson.Value (BS.pack $ serialize json) =/= Nothing

The result:

*** Failed! Falsified (after 4 tests):
String "\ETB\171675^\153309mX"
Nothing == Nothing

Of course, we’re working with the escape sequences incorrectly. The instance Show for the String doesn’t process them in the same way as the aeson decoder.

Surely, we should have implemented the serialization correctly but since this post is devoted to QuickCheck, it would be more interesting to show how to make QuickCheck omit the values we are definitely not interested in.

Let’s assume that we’ve decided on limiting the lines only to printed characters with the code range 32-126.

To do this, we can use the function suchThat :: Gen a -> (a -> Bool) -> Gen a that allows generating the values satisfying the specified predicate (in our case, this is the code range constraint):

instance Arbitrary Json where
  arbitrary = sized arbitrary'
    where
      arbitraryString =
        arbitrary `suchThat` all ((\code -> code >= 32 && code <= 126) . ord)
      arbitrary' 0 = pure $ Array []
      arbitrary' n =
        oneof [ Object <$> listOf
                ((,) <$> arbitraryString <*> resize (n `div` 2) arbitrary)
              , Array <$> resize (n `div` 2) arbitrary
              , String <$> arbitraryString
              , Number <$> arbitrary
              ]

After running such a test, we’ll notice that the time of its operation has increased significantly because now we’re rejecting the lines containing even one symbol from the unspecified interval.

The following code lets us know that we use approximately 6% of generated examples. We use the function classify that prints out the percent of the test cases which were useful for us:

 > quickCheck (\s -> classify (all ((\code -> code >= 32 && code <= 126) . ord) s) "useful" (s === s))
+++ OK, passed 100 tests (6% useful).

6% is not much, that’s why this method of lines generation is not suitable. To make the tests fast, it’s necessary to try and generate the data meeting the desired invariants at once instead of using the function suchThat or similar functions.

The situation becomes somewhat better if you place the suchThat inside the listOf (the String in Haskell is the list of symbols ([Char])):

arbitraryString =
  listOf (arbitrary `suchThat` ((\code -> code >= 32 && code <= 126) . ord))

However, generating a symbol from the specified interval is even quicker:

arbitraryString = listOf (chr <$> chooseInt (32, 126))

Unfortunately, it’s not often easy to write a generator producing only the values meeting a specific predicate, especially if the predicate requires any constraints, which are interrelated in some way, for various parts of the structure.

Shrinking

Shrinking is a way to “reduce” the found example to the minimum possible. The function shrink :: Arbitrary a => a -> [a] comes in after the counter-example has been found.

shrink must return the finite (and probably empty) list of all possible “simplifications” of the value with the type a. An empty list will mean that the minimal counter-example has already been found.

You can view the result of the shrink operation by running verboseCheck. Suppose that we want to check a rather strange assertion that no lines contain exactly two 'a' symbols. Obviously, here the line "aa" is the minimum counter-example. After finding the first counter-example we see how shrink is trying, again and again, to reduce the line to find this minimum counter-example:

> verboseCheck (\str -> 2 /= length (filter (== 'a') str))

  ...

Failed:
"a8aL"

Passed:
""

Passed:
"aL"

Passed:
"a8"

Passed:
"8aL"

Failed:
"aaL"

Passed:
""

Passed:
"aL"

Passed:
"aL"

Failed:
"aa"

Passed:
""

Passed:
"a"

Passed:
"a"

*** Failed! Falsified (after 69 tests and 10 shrinks):
"aa"

This search algorithm was implemented in the function shrinkList:

shrinkList :: (a -> [a]) -> [a] -> [[a]]
shrinkList shr xs = concat [ removes k n xs | k <- takeWhile (>0) (iterate (`div`2) n) ]
                 ++ shrinkOne xs
 where
  n = length xs

  shrinkOne []     = []
  shrinkOne (x:xs) = [ x':xs | x'  <- shr x ]
                  ++ [ x:xs' | xs' <- shrinkOne xs ]

  removes k n xs
    | k > n     = []
    | null xs2  = [[]]
    | otherwise = xs2 : map (xs1 ++) (removes k (n-k) xs2)
   where
    xs1 = take k xs
    xs2 = drop k xs

The shrinkList is trying to:

  • Delete one half of the list, one-quarter of the list, one-eighth part and so on starting from the end and from the beginning
  • Apply shrink to one of the list elements

Let’s write shrink for JSON (we’ll just reuse shrink implementations for pair, list, line, and number):

shrink (Object props)  = Object <$> shrink props
shrink (Array entries) = Array <$> shrink entries
shrink (String str)    = String <$> shrink str
shrink (Number n)      = Number <$> shrink n

Using generic-random

In the example described above, we implemented the arbitrary method manually mostly for illustrative purposes. However, in a real production code where dozens or hundreds of data types are declared this may become a tiring process. The [generic-random] library (https://hackage.haskell.org/package/generic-random) allows obtaining the instance of Arbitrary automatically.

Its operation is based on the generic programming of data types (datatype-generic programming). To describe this approach briefly, we can represent the data types in a general way as a sum type (an alternative of several constructors, as in our example with Json) or as a product type (a structure with several fields).

If it’s known how to obtain an arbitrary value for each of the alternatives in this sum type, we can use these values to get an arbitrary value of the sum type itself. Moreover, each constructor in the alternative can have a certain weight so that it would occur more often or less often than the rest. For a product type (more simply, a structure), if it’s known how to obtain an arbitrary value of each field, we can use them to create an arbitrary value of the structure as a whole.

For recursive types, we can indicate the value for the recursion base during generation when the structure size reaches zero. In our “manual” implementation of the Arbitrary instance for the Json type, it was the value Array [].

Let’s use generic-random to write a new definition of arbitrary for Json:

instance Arbitrary Json where
  arbitrary = genericArbitraryRec uniform `withBaseCase` return (Array [])

genericArbitraryRec reduces the size of generated structure at each recursive call; uniform sets a uniform distribution for the constructors in the alternative; withBaseCase indicates what generator should be called for a zero-size structure.

Conclusion

Thus, we’ve seen in this tutorial how the QuickCheck library is used for property-based testing and in particular, learned how to:

  • Describe the test data generators and adjust them to improve the efficiency and reduce the test execution time;
  • Describe simple properties of the functions and run tests to check them;
  • Analyze the examples of data used for testing;
  • Search for the minimum counter-example for which the tests fail;
  • Generate the required instances automatically.

Thank you for your attention!

Recommended

You may also like

Want to know more?
Get in touch with us!
Contact Us

Privacy policy

Last updated: 1 September 2021

Typeable OU ("us", "we", or "our") operates https://typeable.io (the "Site"). This page informs you of our policies regarding the collection, use and disclosure of Personal Information we receive from users of the Site.

We use your Personal Information only for providing and improving the Site. By using the Site, you agree to the collection and use of information in accordance with this policy.

Information Collection And Use

While using our Site, we may ask you to provide us with certain personally identifiable information that can be used to contact or identify you. Personally identifiable information may include, but is not limited to your name ("Personal Information").

Log Data

Like many site operators, we collect information that your browser sends whenever you visit our Site ("Log Data").

This Log Data may include information such as your computer's Internet Protocol ("IP") address, browser type, browser version, the pages of our Site that you visit, the time and date of your visit, the time spent on those pages and other statistics.

In addition, we may use third party services such as Google Analytics that collect, monitor and analyze this ...

Cookies

Cookies are files with small amount of data, which may include an anonymous unique identifier. Cookies are sent to your browser from a web site and stored on your computer's hard drive.

Like many sites, we use "cookies" to collect information. You can instruct your browser to refuse all cookies or to indicate when a cookie is being sent. However, if you do not accept cookies, you may not be able to use some portions of our Site.

Security

The security of your Personal Information is important to us, so we don't store any personal information and use third-party GDPR-compliant services to store contact data supplied with a "Contact Us" form and job applications data, suplied via "Careers" page.

Changes To This Privacy Policy

This Privacy Policy is effective as of @@privacePolicyDate​ and will remain in effect except with respect to any changes in its provisions in the future, which will be in effect immediately after being posted on this page.

We reserve the right to update or change our Privacy Policy at any time and you should check this Privacy Policy periodically. Your continued use of the Service after we post any modifications to the Privacy Policy on this page will constitute your acknowledgment of the modifications and your consent to abide and be bound by the modified Privacy Policy.

If we make any material changes to this Privacy Policy, we will notify you either through the email address you have provided us, or by placing a prominent notice on our website.

Contact Us

If you have any questions about this Privacy Policy, please contact us.