falsify-0.1.1: Property-based testing with internal integrated shrinking
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.Falsify.Generator

Description

Generator

Intended for qualified import.

import Test.Falsify.Generator (Gen)
import qualified Test.Falsify.Generator qualified as Gen
Synopsis

Definition

data Gen a Source #

Generator of a random value

Generators can be combined through their Functor, Applicative and Monad interfaces. The primitive generator is prim, but most users will probably want to construct their generators using the predefined from Test.Falsify.Generator as building blocks.

Generators support "internal integrated shrinking". Shrinking is integrated in the sense of Hedgehog, meaning that we don't write a separate shrinker at all, but the shrink behaviour is implied by the generator. For example, if you have a generator genList for a list of numbers, then

filter even <$> genList

will only generate even numbers, and that property is automatically preserved during shrinking. Shrinking is internal in the sense of Hypothesis, meaning that unlike in Hedgehog, shrinking works correctly even in the context of monadic bind. For example, if you do

do n <- genListLength
   replicateM n someOtherGen

then we can shrink n and the results from someOtherGen in any order (that said, users may prefer to use the dedicated list generator for this purpose, which improves on this in a few ways).

NOTE: Gen is NOT an instance of Alternative; this would not be compatible with the generation of infinite data structures. For the same reason, we do not have a monad transformer version of Gen either.

Instances

Instances details
Applicative Gen Source # 
Instance details

Defined in Test.Falsify.Internal.Generator.Definition

Methods

pure :: a -> Gen a #

(<*>) :: Gen (a -> b) -> Gen a -> Gen b #

liftA2 :: (a -> b -> c) -> Gen a -> Gen b -> Gen c #

(*>) :: Gen a -> Gen b -> Gen b #

(<*) :: Gen a -> Gen b -> Gen a #

Functor Gen Source # 
Instance details

Defined in Test.Falsify.Internal.Generator.Definition

Methods

fmap :: (a -> b) -> Gen a -> Gen b #

(<$) :: a -> Gen b -> Gen a #

Monad Gen Source # 
Instance details

Defined in Test.Falsify.Internal.Generator.Definition

Methods

(>>=) :: Gen a -> (a -> Gen b) -> Gen b #

(>>) :: Gen a -> Gen b -> Gen b #

return :: a -> Gen a #

Selective Gen Source # 
Instance details

Defined in Test.Falsify.Internal.Generator.Definition

Methods

select :: Gen (Either a b) -> Gen (a -> b) -> Gen b #

Simple (non-compound) generators

bool :: Bool -> Gen Bool Source #

Generate random bool, shrink towards the given value

Chooses with equal probability between True and False.

integral :: Integral a => Range a -> Gen a Source #

Generate value of integral type

int :: Range Int -> Gen Int Source #

Type-specialization of integral

enum :: forall a. Enum a => Range a -> Gen a Source #

Generate value of enumerable type

For most types integral is preferred; the Enum class goes through Int, and is therefore also limited by the range of Int.

Compound generators

Taking advantage of Selective

choose :: Gen a -> Gen a -> Gen a Source #

Generate a value with one of two generators

Shrinks towards the first generator;the two generators can shrink independently from each other.

Background

In the remainder of this docstring we give some background to this function, which may be useful for general understanding of the falsify library.

The implementation takes advantage of the that Gen is a selective functor to ensure that the two generators can shrink independently: if the initial value of the generator is some y produced by the second generator, later shrunk to some y', then if the generator can shrink to x at some point, produced by the first generator, then shrinking effectively "starts over": the value of x is independent of y'.

That is different from doing this:

do b <- bool
   if b then l else r

In this case, l and r will be generated from the same sample tree, and so cannot shrink independently.

It is also different from

do x <- l
   y <- r
   b <- bool
   return $ if b then x else y

In this case, l and r are run against different sample trees, like we do here, but in this case if the current value produced by the generator is produced by the right generator, then the sample tree used for the left generator will always shrink to Minimal (this must be possible because we're not currently using it); this means that we would then only be able to shrink to a value from the left generator if the minimal value produced by that generator happens to work.

To rephrase that last point: generating values that are not actually used will lead to poor shrinking, since those values can always be shrunk to their minimal value, independently from whatever property is being tested: the shrinker does not know that the value is not being used. The correct way to conditionally use a value is to use the selective interface, as we do here.

Lists

list :: Range Word -> Gen a -> Gen [a] Source #

Generate list of specified length

Shrinking behaviour:

  • The length of the list will shrink as specified by the given range.
  • We can drop random elements from the list, but prefer to drop them from near the end of the list.

Note on shrinking predictability: in the case that the specified Range has an origin which is neither the lower bound nor the upper bound (and only in that case), list can have confusing shrinking behaviour. For example, suppose we have a range (0, 10) with origin 5. Then we could start by generating an intermediate list of length of 10 and then subsequently drop 5 elements from that, resulting in an optimal list length. However, we can now shrink that length from 10 to 2 (which is closer to 5, after all), but now we only have 2 elements to work with, and hence the generated list will now drop from 5 elements to 2. This is not necessarily a problem, because that length 2 can now subsequently shrink further towards closer to the origin (5), but nonetheless it might result in confusing intermediate shrinking steps.

elem :: NonEmpty a -> Gen a Source #

Choose random element

Shrinks towards earlier elements.

NOTE: Does not work on infinite lists (it computes the length of the list).

pick :: NonEmpty a -> Gen ([a], a, [a]) Source #

Generalization of elem that additionally returns the parts of the list before and after the element

pickBiased :: NonEmpty a -> Gen ([a], a, [a]) Source #

Choose random element from a list

This is different from elem: it avoids first computing the length of the list, and is biased towards elements earlier in the list. The advantage is that this works for infinite lists, too.

Also returns the elements from the list before and after the chosen element.

shuffle :: [a] -> Gen [a] Source #

Shuffle list (construct a permutation)

Shrinking behaviour: shuffle is defined in terms of permutation, which provides some guarantees: it shrinks towards making changes near the start of the list, and towards swapping fewer elements of the list.

It is difficult to define precisely how this affects the resulting list, but we can say that if for a particular counter-example it suffices if two lists are different in one element, then the shuffled list will in fact only be different in one place from the original, and that one element will have been swapped with an immediate neighbour.

Permutations

type Permutation = [(Word, Word)] Source #

Permutation is a sequence of swaps

permutation :: Word -> Gen Permutation Source #

Generate permutation for a list of length n

This is essentially an implemention of Fisher-Yates, in that we generate a series of swaps (i, j), with 1 <= i <= n - 1 and 0 <= j <= i, except that

  • We can shrink a choice of i (towards 1).
  • We can drop arbitrary swaps.

This ensures that we shrink towards making swaps nearer the start of the list, as well as towards fewer swaps.

We make no attempt to make the permutation canonical; doing so makes it extremely difficult to get predicable shrinking behaviour.

Tweak test data distribution

frequency :: forall a. [(Word, Gen a)] -> Gen a Source #

Choose generator with the given frequency

For example,

frequency [
    (1, genA)
  , (2, genB)
  ]

will use genA 13rd of the time, and genB 23rds.

Shrinks towards generators earlier in the list; the generators themselves are independent from each other (shrinking of genB does not affect shrinking of genA).

Precondition: there should at least one generator with non-zero frequency.

Trees

data Tree a Source #

Constructors

Leaf 

Bundled Patterns

pattern Branch :: a -> Tree a -> Tree a -> Tree a 

Instances

Instances details
Foldable Tree Source # 
Instance details

Defined in Data.Falsify.Tree

Methods

fold :: Monoid m => Tree m -> m #

foldMap :: Monoid m => (a -> m) -> Tree a -> m #

foldMap' :: Monoid m => (a -> m) -> Tree a -> m #

foldr :: (a -> b -> b) -> b -> Tree a -> b #

foldr' :: (a -> b -> b) -> b -> Tree a -> b #

foldl :: (b -> a -> b) -> b -> Tree a -> b #

foldl' :: (b -> a -> b) -> b -> Tree a -> b #

foldr1 :: (a -> a -> a) -> Tree a -> a #

foldl1 :: (a -> a -> a) -> Tree a -> a #

toList :: Tree a -> [a] #

null :: Tree a -> Bool #

length :: Tree a -> Int #

elem :: Eq a => a -> Tree a -> Bool #

maximum :: Ord a => Tree a -> a #

minimum :: Ord a => Tree a -> a #

sum :: Num a => Tree a -> a #

product :: Num a => Tree a -> a #

Traversable Tree Source # 
Instance details

Defined in Data.Falsify.Tree

Methods

traverse :: Applicative f => (a -> f b) -> Tree a -> f (Tree b) #

sequenceA :: Applicative f => Tree (f a) -> f (Tree a) #

mapM :: Monad m => (a -> m b) -> Tree a -> m (Tree b) #

sequence :: Monad m => Tree (m a) -> m (Tree a) #

Functor Tree Source # 
Instance details

Defined in Data.Falsify.Tree

Methods

fmap :: (a -> b) -> Tree a -> Tree b #

(<$) :: a -> Tree b -> Tree a #

Show a => Show (Tree a) Source # 
Instance details

Defined in Data.Falsify.Tree

Methods

showsPrec :: Int -> Tree a -> ShowS #

show :: Tree a -> String #

showList :: [Tree a] -> ShowS #

Eq a => Eq (Tree a) Source # 
Instance details

Defined in Data.Falsify.Tree

Methods

(==) :: Tree a -> Tree a -> Bool #

(/=) :: Tree a -> Tree a -> Bool #

Binary trees

tree :: forall a. Range Word -> Gen a -> Gen (Tree a) Source #

Generate binary tree

bst :: forall a b. Integral a => (a -> Gen b) -> Interval a -> Gen (Tree (a, b)) Source #

Construct binary search tree

Shrinks by replacing entire subtrees by the empty tree.

Shrink trees

data IsValidShrink p n Source #

Does a given shrunk value represent a valid shrink step?

Constructors

ValidShrink p 
InvalidShrink n 

Instances

Instances details
(Show p, Show n) => Show (IsValidShrink p n) Source # 
Instance details

Defined in Test.Falsify.Internal.Generator.Shrinking

path Source #

Arguments

:: forall a p n. (a -> IsValidShrink p n)

Predicate

-> ShrinkTree a 
-> Gen (Either n (NonEmpty p)) 

Generate semi-random path through the tree

Will only construct paths that satisfy the given predicate (typically, a property that is being tested).

Shrinks towards shorter paths, and towards paths that use subtrees that appear earlier in the list of subtrees at any node in the tree.

See also pathAny.

pathAny :: ShrinkTree a -> Gen (NonEmpty a) Source #

Variation on path without a predicate.

Marking

data Marked f a Source #

Constructors

Marked 

Fields

Instances

Instances details
Show (f a) => Show (Marked f a) Source # 
Instance details

Defined in Data.Falsify.Marked

Methods

showsPrec :: Int -> Marked f a -> ShowS #

show :: Marked f a -> String #

showList :: [Marked f a] -> ShowS #

Eq (f a) => Eq (Marked f a) Source # 
Instance details

Defined in Data.Falsify.Marked

Methods

(==) :: Marked f a -> Marked f a -> Bool #

(/=) :: Marked f a -> Marked f a -> Bool #

Ord (f a) => Ord (Marked f a) Source # 
Instance details

Defined in Data.Falsify.Marked

Methods

compare :: Marked f a -> Marked f a -> Ordering #

(<) :: Marked f a -> Marked f a -> Bool #

(<=) :: Marked f a -> Marked f a -> Bool #

(>) :: Marked f a -> Marked f a -> Bool #

(>=) :: Marked f a -> Marked f a -> Bool #

max :: Marked f a -> Marked f a -> Marked f a #

min :: Marked f a -> Marked f a -> Marked f a #

data Mark Source #

Constructors

Keep 
Drop 

Instances

Instances details
Show Mark Source # 
Instance details

Defined in Data.Falsify.Marked

Methods

showsPrec :: Int -> Mark -> ShowS #

show :: Mark -> String #

showList :: [Mark] -> ShowS #

Eq Mark Source # 
Instance details

Defined in Data.Falsify.Marked

Methods

(==) :: Mark -> Mark -> Bool #

(/=) :: Mark -> Mark -> Bool #

Ord Mark Source # 
Instance details

Defined in Data.Falsify.Marked

Methods

compare :: Mark -> Mark -> Ordering #

(<) :: Mark -> Mark -> Bool #

(<=) :: Mark -> Mark -> Bool #

(>) :: Mark -> Mark -> Bool #

(>=) :: Mark -> Mark -> Bool #

max :: Mark -> Mark -> Mark #

min :: Mark -> Mark -> Mark #

selectAllKept :: (Traversable t, Selective f) => t (Marked f a) -> f (t (Maybe a)) Source #

Traverse the argument, generating all values marked Keep, and replacing all values marked Drop by Nothing

mark :: Gen a -> Gen (Marked Gen a) Source #

Mark an element, shrinking towards Drop

This is similar to shrinkToNothing, except that Marked still has a value in the Drop case: marks are merely hints, that we may or may not use.

Functions

Generation

data Fun a b Source #

Function a -> b which can be shown, generated, and shrunk

Instances

Instances details
Functor (Fun a) Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

fmap :: (a0 -> b) -> Fun a a0 -> Fun a b #

(<$) :: a0 -> Fun a b -> Fun a a0 #

(Show a, Show b) => Show (Fun a b) Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

showsPrec :: Int -> Fun a b -> ShowS #

show :: Fun a b -> String #

showList :: [Fun a b] -> ShowS #

applyFun :: Fun a b -> a -> b Source #

Apply function to argument

See also the Fn, Fn2, and Fn3 patter synonyms.

pattern Fn :: (a -> b) -> Fun a b Source #

Pattern synonym useful when generating functions of one argument

pattern Fn2 :: (a -> b -> c) -> Fun (a, b) c Source #

Pattern synonym useful when generating functions of two arguments

pattern Fn3 :: (a -> b -> c -> d) -> Fun (a, b, c) d Source #

Pattern synonym useful when generating functions of three arguments

fun :: Function a => Gen b -> Gen (Fun a b) Source #

Generate function a -> b given a generator for b

Construction

class Function a where Source #

Generating functions

Minimal complete definition

Nothing

Methods

function :: Gen b -> Gen (a :-> b) Source #

Build reified function

(:->) is an abstract type; if you need to add additional Function instances, you need to use functionMap, or rely on the default implementation in terms of generics.

default function :: (Generic a, GFunction (Rep a)) => Gen b -> Gen (a :-> b) Source #

Instances

Instances details
Function Int16 Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b -> Gen (Int16 :-> b) Source #

Function Int32 Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b -> Gen (Int32 :-> b) Source #

Function Int64 Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b -> Gen (Int64 :-> b) Source #

Function Int8 Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b -> Gen (Int8 :-> b) Source #

Function Word16 Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b -> Gen (Word16 :-> b) Source #

Function Word32 Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b -> Gen (Word32 :-> b) Source #

Function Word64 Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b -> Gen (Word64 :-> b) Source #

Function Word8 Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b -> Gen (Word8 :-> b) Source #

Function Integer Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b -> Gen (Integer :-> b) Source #

Function Natural Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b -> Gen (Natural :-> b) Source #

Function () Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b -> Gen (() :-> b) Source #

Function Bool Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b -> Gen (Bool :-> b) Source #

Function Char Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b -> Gen (Char :-> b) Source #

Function Double Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b -> Gen (Double :-> b) Source #

Function Float Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b -> Gen (Float :-> b) Source #

Function Int Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b -> Gen (Int :-> b) Source #

Function Word Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b -> Gen (Word :-> b) Source #

(Integral a, Function a) => Function (Ratio a) Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b -> Gen (Ratio a :-> b) Source #

Function a => Function (Maybe a) Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b -> Gen (Maybe a :-> b) Source #

Function a => Function [a] Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b -> Gen ([a] :-> b) Source #

(Function a, Function b) => Function (Either a b) Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b0 -> Gen (Either a b :-> b0) Source #

(Function a, Function b) => Function (a, b) Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b0 -> Gen ((a, b) :-> b0) Source #

(Function a, Function b, Function c) => Function (a, b, c) Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b0 -> Gen ((a, b, c) :-> b0) Source #

(Function a, Function b, Function c, Function d) => Function (a, b, c, d) Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b0 -> Gen ((a, b, c, d) :-> b0) Source #

(Function a, Function b, Function c, Function d, Function e) => Function (a, b, c, d, e) Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b0 -> Gen ((a, b, c, d, e) :-> b0) Source #

(Function a, Function b, Function c, Function d, Function e, Function f) => Function (a, b, c, d, e, f) Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b0 -> Gen ((a, b, c, d, e, f) :-> b0) Source #

(Function a, Function b, Function c, Function d, Function e, Function f, Function g) => Function (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

function :: Gen b0 -> Gen ((a, b, c, d, e, f, g) :-> b0) Source #

data (:->) :: Type -> Type -> Type Source #

Instances

Instances details
Functor ((:->) a) Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Function

Methods

fmap :: (a0 -> b) -> (a :-> a0) -> a :-> b #

(<$) :: a0 -> (a :-> b) -> a :-> a0 #

functionMap :: (b -> a) -> (a -> b) -> (a :-> c) -> b :-> c Source #

The basic building block for Function instances

Provides a Function instance by mapping to and from a type that already has a Function instance.

Reducing precision

data WordN Source #

n-bit word

Constructors

WordN Precision Word64 

Instances

Instances details
Show WordN Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Precision

Methods

showsPrec :: Int -> WordN -> ShowS #

show :: WordN -> String #

showList :: [WordN] -> ShowS #

Eq WordN Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Precision

Methods

(==) :: WordN -> WordN -> Bool #

(/=) :: WordN -> WordN -> Bool #

Ord WordN Source # 
Instance details

Defined in Test.Falsify.Reexported.Generator.Precision

Methods

compare :: WordN -> WordN -> Ordering #

(<) :: WordN -> WordN -> Bool #

(<=) :: WordN -> WordN -> Bool #

(>) :: WordN -> WordN -> Bool #

(>=) :: WordN -> WordN -> Bool #

max :: WordN -> WordN -> WordN #

min :: WordN -> WordN -> WordN #

wordN :: Precision -> Gen WordN Source #

Uniform selection of n-bit word of given precision, shrinking towards 0

properFraction :: HasCallStack => Precision -> Gen ProperFraction Source #

Uniform selection of fraction, shrinking towards 0

Precondition: precision must be at least 1 bit (a zero-bit number is constant 0; it is meaningless to have a fraction in a point range).

Overriding shrinking

withoutShrinking :: Gen a -> Gen a Source #

Disable shrinking in the given generator

Due to the nature of internal shrinking, it is always possible that a generator gets reapplied to samples that were shrunk wrt to a different generator. In this sense, withoutShrinking should be considered to be a hint only.

This function is only occassionally necessary; most users will probably not need to use it.

shrinkToOneOf :: forall a. a -> [a] -> Gen a Source #

Start with x, then shrink to one of the xs

Once shrunk, will not shrink again.

Minimal value is the first shrunk value, if it exists, and the original otherwise.

firstThen :: forall a. a -> a -> Gen a Source #

Generator that always produces x as initial value, and shrinks to y

shrinkWith :: forall a. (a -> [a]) -> Gen a -> Gen a Source #

Shrink with provided shrinker

This provides compatibility with QuickCheck-style manual shrinking.

Defined in terms of fromShrinkTree; see discussion there for some notes on performance.

shrinkToNothing :: Gen a -> Gen (Maybe a) Source #

Start with Just x for some x, then shrink to Nothing

Shrink trees

fromShrinkTree :: forall a. Tree a -> Gen a Source #

Construct generator from shrink tree

This provides compatibility with Hedgehog-style integrated shrinking.

This is O(n^2) in the number of shrink steps: as this shrinks, the generator is growing a path of indices which locates a particular value in the shrink tree (resulting from unfolding the provided shrinking function). At each step during the shrinking process the shrink tree is re-evaluated and the next value in the tree is located; since this path throws linearly, the overall cost is O(n^2).

The O(n^2) cost is only incurred on locating the next element to be tested; the property is not reevaluated at already-shrunk values.

toShrinkTree :: forall a. Gen a -> Gen (Tree a) Source #

Expose the full shrink tree of a generator

This generator does not shrink.

Generator independence

bindIntegral :: Integral a => Gen a -> (a -> Gen b) -> Gen b Source #

Selective bind

Unlike monadic bind, the RHS is generated and shrunk completely independently for each different value of a produced by the LHS.

This is a generalization of bindS to arbitrary integral values; it is also much more efficient than bindS.

NOTE: This is only one way to make a generator independent. See perturb for more primitive combinator.

perturb :: Integral a => a -> Gen b -> Gen b Source #

Run generator on different part of the sample tree depending on a

Low-level

prim :: Gen Word64 Source #

Uniform selection of Word64, shrinking towards 0, using binary search

This is a primitive generator; most users will probably not want to use this generator directly.

primWith :: (Sample -> [Word64]) -> Gen Sample Source #

Generalization of prim that allows to override the shrink behaviour

This is only required in rare circumstances. Most users will probably never need to use this generator.

exhaustive :: Word64 -> Gen Word64 Source #

Generate arbitrary value x <= n

Unlike prim, exhaustive does not execute binary search. Instead, all smaller values are considered. This is potentially very expensive; the primary use case for this generator is testing shrinking behaviour, where binary search can lead to some unpredicatable results.

This does NOT do uniform selection: for small n, the generator will with overwhelming probability produce n itself as initial value.

This is a primitive generator; most users will probably not want to use this generator directly.

captureLocalTree :: Gen SampleTree Source #

Capture the local sample tree

This generator does not shrink.

bindWithoutShortcut :: Gen a -> (a -> Gen b) -> Gen b Source #

Varation on (>>=) that doesn't apply the shortcut to Minimal

This function is primarily useful for debugging falsify itself; users will probably never need it.