Module Core_kernel__Quickcheck.Generator

type +'a t

An 'a t a generates values of type 'a with a specific probability distribution.

Generators are constructed as functions that produce a value from a splittable pseudorandom number generator (see Splittable_random), with a ~size argument threaded through to bound the size of the result value and the depth of recursion.

There is no prescribed semantics for size other than that it must be non-negative. Non-recursive generators are free to ignore it, and recursive generators need only make sure it decreases in recursive calls and that recursion bottoms out at 0.

type -'a obs
val create : (size:Core_kernel__.Import.int ‑> Core_kernel.Splittable_random.State.t ‑> 'a) ‑> 'a t
val generate : 'a t ‑> size:Core_kernel__.Import.int ‑> Core_kernel.Splittable_random.State.t ‑> 'a

Generators form a monad. t1 >>= fun x -> t2 replaces each value x in t1 with the values in t2; each value's probability is the product of its probability in t1 and t2.

This can be used to form distributions of related values. For instance, the following expression creates a distribution of pairs x,y where x <= y:


        Int.gen
        >>= fun x ->
        Int.gen_incl x Int.max_value
        >>| fun y ->
        x, y
      
include Core_kernel__.Import.Monad.S with type t := a t
type 'a t
include Base__.Monad_intf.S_without_syntax with type t := a t
type 'a t

A monad is an abstraction of the concept of sequencing of computations. A value of type 'a monad represents a computation that returns a value of type 'a.

include Base__.Monad_intf.Infix with type t := a t
type 'a t
val (>>=) : 'a t ‑> ('a ‑> 'b t) ‑> 'b t

t >>= f returns a computation that sequences the computations represented by two monad elements. The resulting computation first does t to yield a value v, and then runs the computation returned by f v.

val (>>|) : 'a t ‑> ('a ‑> 'b) ‑> 'b t

t >>| f is t >>= (fun a -> return (f a)).

module Monad_infix : Base__.Monad_intf.Infix with type t := a t
val bind : 'a t ‑> f:('a ‑> 'b t) ‑> 'b t

bind t ~f = t >>= f

val return : 'a ‑> 'a t

return v returns the (trivial) computation that returns v.

val map : 'a t ‑> f:('a ‑> 'b) ‑> 'b t

map t ~f is t >>| f.

val join : 'a t t ‑> 'a t

join t is t >>= (fun t' -> t').

val ignore_m : 'a t ‑> unit t

ignore_m t is map t ~f:(fun _ -> ()). ignore_m used to be called ignore, but we decided that was a bad name, because it shadowed the widely used Pervasives.ignore. Some monads still do let ignore = ignore_m for historical reasons.

val all : 'a t list ‑> 'a list t
val all_ignore : unit t list ‑> unit t
include Base__.Monad_intf.Syntax with type t := a t
type 'a t
module Let_syntax : sig ... end
include Core_kernel__.Import.Applicative.S with type t := a t
type 'a t
val return : 'a ‑> 'a t
val apply : ('a ‑> 'b) t ‑> 'a t ‑> 'b t
val map : 'a t ‑> f:('a ‑> 'b) ‑> 'b t
val map2 : 'a t ‑> 'b t ‑> f:('a ‑> 'b ‑> 'c) ‑> 'c t
val map3 : 'a t ‑> 'b t ‑> 'c t ‑> f:('a ‑> 'b ‑> 'c ‑> 'd) ‑> 'd t
val all : 'a t list ‑> 'a list t
val all_ignore : unit t list ‑> unit t
val both : 'a t ‑> 'b t ‑> ('a * 'b) t
module Applicative_infix : sig ... end
include module type of Applicative_infix
val (<*>) : ('a ‑> 'b) t ‑> 'a t ‑> 'b t

same as apply

val (<*) : 'a t ‑> unit t ‑> 'a t
val (*>) : unit t ‑> 'a t ‑> 'a t
val size : Core_kernel__.Import.int t

size = create (fun ~size _ -> size)

val with_size : 'a t ‑> size:Core_kernel__.Import.int ‑> 'a t

with_size t ~size = create (fun ~size:_ random -> generate t ~size random)

val singleton : 'a ‑> 'a t
val doubleton : 'a ‑> 'a ‑> 'a t
val of_list : 'a Core_kernel__.Import.list ‑> 'a t

Produce any of the given values, weighted equally.

of_list [ v1 ; ... ; vN ] = union [ singleton v1 ; ... ; singleton vN ]

val union : 'a t Core_kernel__.Import.list ‑> 'a t

Combine arbitary generators, weighted equally.

union [ g1 ; ... ; gN ] = weighted_union [ (1.0, g1) ; ... ; (1.0, gN) ]

val of_sequence : p:Core_kernel__.Import.float ‑> 'a Core_kernel.Sequence.t ‑> 'a t

Generator for the values from a potentially infinite sequence. Chooses each value with probability p, or continues with probability 1-p. Must satisfy 0. < p && p <= 1..

val tuple2 : 'a t ‑> 'b t ‑> ('a * 'b) t
val tuple3 : 'a t ‑> 'b t ‑> 'c t ‑> ('a * 'b * 'c) t
val tuple4 : 'a t ‑> 'b t ‑> 'c t ‑> 'd t ‑> ('a * 'b * 'c * 'd) t
val tuple5 : 'a t ‑> 'b t ‑> 'c t ‑> 'd t ‑> 'e t ‑> ('a * 'b * 'c * 'd * 'e) t
val tuple6 : 'a t ‑> 'b t ‑> 'c t ‑> 'd t ‑> 'e t ‑> 'f t ‑> ('a * 'b * 'c * 'd * 'e * 'f) t
val variant2 : 'a t ‑> 'b t ‑> [ `A of 'a | `B of 'b ] t
val variant3 : 'a t ‑> 'b t ‑> 'c t ‑> [ `A of 'a | `B of 'b | `C of 'c ] t
val variant4 : 'a t ‑> 'b t ‑> 'c t ‑> 'd t ‑> [ `A of 'a | `B of 'b | `C of 'c | `D of 'd ] t
val variant5 : 'a t ‑> 'b t ‑> 'c t ‑> 'd t ‑> 'e t ‑> [ `A of 'a | `B of 'b | `C of 'c | `D of 'd | `E of 'e ] t
val variant6 : 'a t ‑> 'b t ‑> 'c t ‑> 'd t ‑> 'e t ‑> 'f t ‑> [ `A of 'a | `B of 'b | `C of 'c | `D of 'd | `E of 'e | `F of 'f ] t
val geometric : p:Core_kernel__.Import.float ‑> Core_kernel__.Import.int ‑> Core_kernel__.Import.int t

geometric ~p init produces a geometric distribution (think "radioactive decay") that produces init with probability p, and otherwise recursively chooses from geometric ~p (init+1). Must satisfy 0. < p && p <= 1..

val small_non_negative_int : Core_kernel__.Import.int t

small_non_negative_int = geometric ~p:0.25 0

val small_positive_int : Core_kernel__.Import.int t

small_positive_int = geometric ~p:0.25 1

val fn : 'a obs ‑> 'b t ‑> ('a ‑> 'b) t

Generators for functions; take observers for inputs and a generator for outputs.

val fn2 : 'a obs ‑> 'b obs ‑> 'c t ‑> ('a ‑> 'b ‑> 'c) t
val fn3 : 'a obs ‑> 'b obs ‑> 'c obs ‑> 'd t ‑> ('a ‑> 'b ‑> 'c ‑> 'd) t
val fn4 : 'a obs ‑> 'b obs ‑> 'c obs ‑> 'd obs ‑> 'e t ‑> ('a ‑> 'b ‑> 'c ‑> 'd ‑> 'e) t
val fn5 : 'a obs ‑> 'b obs ‑> 'c obs ‑> 'd obs ‑> 'e obs ‑> 'f t ‑> ('a ‑> 'b ‑> 'c ‑> 'd ‑> 'e ‑> 'f) t
val fn6 : 'a obs ‑> 'b obs ‑> 'c obs ‑> 'd obs ‑> 'e obs ‑> 'f obs ‑> 'g t ‑> ('a ‑> 'b ‑> 'c ‑> 'd ‑> 'e ‑> 'f ‑> 'g) t
val compare_fn : 'a obs ‑> ('a ‑> 'a ‑> Core_kernel__.Import.int) t

Generator for comparison functions; result is guaranteed to be a partial order.

val equal_fn : 'a obs ‑> ('a ‑> 'a ‑> Core_kernel__.Import.bool) t

Generator for equality functions; result is guaranteed to be an equivalence relation.

val filter_map : 'a t ‑> f:('a ‑> 'b Core_kernel__.Import.option) ‑> 'b t

filter_map t ~f produces y for every x in t such that f x = Some y. filter t ~f produces every x in t such that f x = true.

Caveat: Use filter and filter_map sparingly. Every time f rejects a value, it counts as a failed attempt to produce a value. Too many failures can cause Quickcheck to take a long time to generate values, or fail a test if it fails more times than the maximum configured number of attempts.

val filter : 'a t ‑> f:('a ‑> Core_kernel__.Import.bool) ‑> 'a t
val recursive : ('a t ‑> 'a t) ‑> 'a t

Fixed-point generator. Use size to bound the size of the value and the depth of the recursion. There is no prescribed semantics for size except that it must be non-negative. For example, the following produces a naive generator for natural numbers:


        recursive (fun self ->
          match%bind size with
          | 0 -> singleton 0
          | n -> with_size self ~size:(n-1) >>| Int.succ)
      
val weighted_union : (Core_kernel__.Import.float * 'a t) Core_kernel__.Import.list ‑> 'a t

weighted_union alist produces a generator that combines the distributions of each t in alist with the associated weights, which must be finite positive floating point values.

val of_fun : (Core_kernel__.Import.unit ‑> 'a t) ‑> 'a t

of_fun f produces a generator that lazily applies f.

It is recommended that f not be memoized. Instead, spread out the work of generating a whole distribution over many of_fun calls combined with weighted_union. This allows lazily generated generators to be garbage collected after each test and the relevant portions cheaply recomputed in subsequent tests, rather than accumulating without bound over time.

val list : ?min_len:Core_kernel__.Import.int ‑> ?max_len:Core_kernel__.Import.int ‑> 'a t ‑> 'a Core_kernel__.Import.list t

list ?min_len ?max_len t creates a list generator with elements drawn from t, with optional bounds on its length specified by min_len and max_len. The size passed to the list generator will be distributed among the generated elements. This is used to implement List.gen and List.gen'; they produce identical distributions.