package qcheck-core

  1. Overview
  2. Docs

QuickCheck-inspired property-based testing

Introduction

This library takes inspiration from Haskell's QuickCheck library. The rough idea is that the programmer describes invariants that values of a certain type need to satisfy ("properties"), as functions from this type to bool. They also need to describe how to generate random values of the type, so that the property is tried and checked on a number of random instances.

This explains the organization of this module:

  • Gen is used to describe how to generate random values. Auxiliary module Print can be used along with Test.make to build one's own generator instances.
  • Test is used to describe a single test, that is, a property of type 'a -> bool combined with an 'a Gen.t that is used to generate the test cases for this property. Optional parameters allow to specify the random generator state, number of instances to generate and test, etc.

💡 If you are migrating from QCheck, check the migration guide below.

Examples

  • "List.rev is involutive" (the test passes so check_exn returns ()):
let test =
  QCheck2.(Test.make ~count:1000
            ~print:Print.(list int)
            Gen.(list int)
            (fun l -> List.rev (List.rev l) = l));;

QCheck2.Test.check_exn test;;
  • "All lists are sorted" (false property that will fail):

    • QCheck tests this property on random lists and finds a counter-example
    • QCheck then looks for the smallest counter-example possible (here [1; 0]) to help you find the problem (called "shrinking")
let test = QCheck2.(
    Test.make
      ~name:"All lists are sorted"
      ~count:10_000
      ~print:Print.(list int)
      Gen.(list small_nat)
      (fun l -> l = List.sort compare l));;

QCheck2.Test.check_exn test;;

Exception:
  test `All lists are sorted` failed on ≥ 1 cases:
  [1; 0] (after 5 shrink steps)
  • Generate 20 random trees using Gen.fix :
type tree = Leaf of int | Node of tree * tree

let leaf x = Leaf x
let node x y = Node (x,y)

let tree_gen = QCheck2.Gen.(sized @@ fix
                              (fun self n -> match n with
                                 | 0 -> map leaf nat
                                 | n ->
                                   frequency
                                     [1, map leaf nat;
                                      2, map2 node (self (n/2)) (self (n/2))]
                              ));;

QCheck2.Gen.generate ~n:20 tree_gen;;
  • since 0.18
module Tree : sig ... end

A tree represents a generated value and its successive shrunk values.

module Gen : sig ... end

A generator is responsible for generating pseudo-random values and provide shrinks (smaller values) when a test fails.

module Print : sig ... end

Printing functions and helpers, used to print generated values on test failures.

module Shrink : sig ... end

Shrinking helper functions.

module Observable : sig ... end

An observable is a random function argument.

module Tuple : sig ... end

Utils on combining function arguments.

type 'f fun_repr

Used by QCheck to shrink and print generated functions of type 'f in case of test failure. You cannot and should not use it yourself. See fun_ for more information.

type 'f fun_ =
  1. | Fun of 'f fun_repr * 'f

A function packed with the data required to print/shrink it.

The idiomatic way to use any fun_ Gen.t is to directly pattern match on it to obtain the executable function.

For example (note the Fun (_, f) part):

QCheck2.(Test.make
  Gen.(pair (fun1 Observable.int bool) (small_list int))
  (fun (Fun (_, f), l) -> l = (List.rev_map f l |> List.rev l))

In this example f is a generated function of type int -> bool.

The ignored part _ of Fun (_, f) is useless to you, but is used by QCheck during shrinking/printing in case of test failure.

See also Fn for utils to print and apply such a function.

val fun1 : 'a Observable.t -> ?print:'b Print.t -> 'b Gen.t -> ('a -> 'b) fun_ Gen.t

fun1 obs gen generates random functions that take an argument observable via obs and map to random values generated with gen. To write functions with multiple arguments, it's better to use Tuple or Observable.pair rather than applying fun_ several times (shrinking will be faster).

  • since 0.6
val fun2 : 'a Observable.t -> 'b Observable.t -> ?print:'c Print.t -> 'c Gen.t -> ('a -> 'b -> 'c) fun_ Gen.t

Specialized version of fun_nary for functions of 2 arguments, for convenience.

  • since 0.6
val fun3 : 'a Observable.t -> 'b Observable.t -> 'c Observable.t -> ?print:'d Print.t -> 'd Gen.t -> ('a -> 'b -> 'c -> 'd) fun_ Gen.t

Specialized version of fun_nary for functions of 3 arguments, for convenience.

  • since 0.6
val fun4 : 'a Observable.t -> 'b Observable.t -> 'c Observable.t -> 'd Observable.t -> ?print:'e Print.t -> 'e Gen.t -> ('a -> 'b -> 'c -> 'd -> 'e) fun_ Gen.t

Specialized version of fun_nary for functions of 4 arguments, for convenience.

  • since 0.6
val fun_nary : 'a Tuple.obs -> ?print:'b Print.t -> 'b Gen.t -> ('a Tuple.t -> 'b) fun_ Gen.t

fun_nary tuple_obs gen generates random n-ary functions. Arguments are observed using tuple_obs and return values are generated using gen.

Example (the property is wrong as a random function may return false, this is for the sake of demonstrating the syntax):

let module O = Observable in
Test.make
  (fun_nary Tuple.(O.int @-> O.float @-> O.string @-> o_nil) bool)
  (fun (Fun (_, f)) -> f Tuple.(42 @:: 17.98 @:: "foobar" @:: nil))

Note that this particular example can be simplified using fun3 directly:

let module O = Observable in
Test.make
  (fun3 O.int O.float O.string bool)
  (fun (Fun (_, f)) -> f 42 17.98 "foobar")
  • since 0.6
module Fn : sig ... end

Utils on generated functions.

Assumptions

val assume : bool -> unit

assume cond checks the precondition cond, and does nothing if cond=true. If cond=false, it interrupts the current test (but the test will not be failed).

⚠️ This function must only be used in a test, not outside. Example:

Test.make (list int) (fun l ->
    assume (l <> []);
    List.hd l :: List.tl l = l)
  • since 0.5.1
val (==>) : bool -> bool -> bool

b1 ==> b2 is the logical implication b1 => b2 ie not b1 || b2 (except that it is strict and will interact better with Test.check_exn and the likes, because they will know the precondition was not satisfied.).

⚠️ This function should only be used in a property (see Test.make), because it raises a special exception in case of failure of the first argument, to distinguish between failed test and failed precondition. Because of OCaml's evaluation order, both b1 and b2 are always evaluated; if b2 should only be evaluated when b1 holds, see assume.

val assume_fail : unit -> 'a

assume_fail () is like assume false, but can take any type since we know it always fails (like assert false). This is useful to ignore some branches in if or match.

Example:

Test.make (list int) (function
    | [] -> assume_fail ()
    | _::_ as l -> List.hd l :: List.tl l = l)
  • since 0.5.1

Tests

A test is a universal property of type foo -> bool for some type foo, with an object of type foo Gen.t used to generate values of type foo.

See Test.make to build a test, and Test.check_exn to run one test simply. For more serious testing, it is better to create a testsuite and use QCheck_runner.

type 'a stat = string * ('a -> int)

A statistic on a distribution of values of type 'a. The function MUST return a positive integer.

module TestResult : sig ... end

Result of running a test

module Test_exceptions : sig ... end
module Test : sig ... end

A test is a pair of a generator and a property that all generated values must satisfy.

Sub-tests

The infrastructure used to find counter-examples to properties can also be used to find data satisfying a predicate, within a property being tested.

See https://github.com/c-cube/qcheck/issues/31

exception No_example_found of string

Raised by find_example and find_example_gen if no example was found.

val find_example : ?name:string -> ?count:int -> f:('a -> bool) -> 'a Gen.t -> 'a Gen.t

find_example ~f gen uses gen to generate some values of type 'a, and checks them against f. If such a value is found, it is returned. Otherwise an exception is raised.

⚠️ This should only be used from within a property in Test.make.

  • parameter name

    Description of the example to find (used in test results/errors).

  • parameter count

    Number of attempts.

  • parameter f

    The property that the generated values must satisfy.

  • since 0.6
val find_example_gen : ?rand:Stdlib.Random.State.t -> ?name:string -> ?count:int -> f:('a -> bool) -> 'a Gen.t -> 'a

Toplevel version of find_example. find_example_gen ~f gen is roughly the same as Gen.generate1 @@ find_example ~f gen.

  • parameter rand

    the random state to use to generate inputs.

  • since 0.6

Migration to QCheck2

QCheck2 is a major release and as such, there are (as few as possible) breaking changes, as well as functional changes you should be aware of.

Minimal changes

Most of your QCheck (v1) code should be able to compile and run the first time you upgrade your QCheck version to a QCheck2-compatible version. However you may need to do the following minimal changes:

Now you want to actually start using the QCheck2 features (most importantly: free shrinking!). To get started, change all your QCheck references to QCheck2 and follow the compiler errors. Below are the most common situations you may encounter:

  • as shrinking is now integrated, several function arguments like ~shrink or ~rev have been removed: you can remove such reverse functions, they will no longer be necessary.
  • accessor functions like QCheck.arbitrary.gen have been renamed to consistent names like get_gen.
  • QCheck.map_keep_input has been removed: you can use map directly.
  • Gen.t is no longer public, it is now abstract: it is recommended to use generator composition to make generators. Gen.make_primitive was added to create generators with finer control (in particular of shrinking).