[Haskell-cafe] Generating random enums

Ryan Ingram ryani.spam at gmail.com
Fri May 1 17:13:44 EDT 2009


On Fri, May 1, 2009 at 11:08 AM, Thomas Hartman <tphyahoo at gmail.com> wrote:
> For quickchecking, the code below "cheats" by not defining the
> coarbitrary funciton, which I confess I don't really understand and
> never use.

coarbitrary is simple; it's used for generating arbitrary functions.
If you don't know how to define it for your type, "coarbitrary _ = id"
is a reasonable definition.  But it's usually easy to define, and I'll
show you how!

But first, the motivation for its existence.  You have an instance of
arbitrary "X", and an instance of arbitrary "Y", and some
transformations:

> transformX :: X -> X
> transformY :: Y -> Y
>
> prop_natural_transform :: (X -> Y) -> X -> Bool
> prop_natural_transform f x = f (transformX x) == transformY (f x)

This says, for all f, (f . transformX) = (transformY . f).

A real example of a property similar to this is for "map" and "reverse":
> prop_map_reverse :: Eq b => (a -> b) -> [a] -> Bool
> prop_map_reverse f xs = map f (reverse xs) == reverse (map f xs)

Now, how can QuickCheck generate functions to pass to these
properties?  The function f is *pure*; it can't use a random generator
to determine what Y to output.

What QuickCheck *can* do, however, is "split" the random generator at
the point where it needs to create "f", then uses "coarbitrary" to
adjust the state of the generator based on the argument passed in:

> mkArbFunction :: forall a b. (Arbitrary a, Arbitrary b) => Gen (a -> b)
> mkArbFunction = sized $ \size -> do
>    randomSource <- rand
>    let
>        f :: a -> b
>        f x = generate size randomSource (coarbitrary x arbitrary)
>    return f

Inside of "f", we have a single generator that is fixed; without
coarbitrary, we would only be able to generate a single object of type
"b", the one that is a result of running "arbitrary" with that fixed
generator.

But with coarbitrary, the argument can affect the response!  The
simplest thing to do is to extract some random values from the
generator before using it to generate the result:

> -- only works for non-negative values
> twist :: Int -> Gen a -> Gen a
> twist 0 g = g
> twist n g = do
>    () <- elements [(), ()]  -- just make the random generator do some work
>    coarbitrary (n-1) g

It's really easy to implement coarbitrary for many types in terms of "twist":

> data Color = Red | Green | Blue
> instance Arbitrary Color where
>     arbitrary = elements [Red, Green, Blue]
>     coarbitrary Red   = twist 0
>     coarbitrary Green = twist 1
>     coarbitrary Blue  = twist 2

> instance Arbitrary a => Arbitrary (Maybe a) where
>     arbitrary = oneOf [return Nothing, liftM Just arbitrary]
>     coarbitrary Nothing = twist 0
>     coarbitrary (Just x) = twist 1 . coarbitrary x

A better version of "twist" is in Test.QuickCheck with the name
"variant".  In fact, for Bounded/Enum types like your code uses, it's
easy to define coarbitrary from variant:

> coarbEnum :: (Bounded a, Enum a) => a -> Gen b -> Gen b
> coarbEnum a = variant (fromEnum a - fromEnum (minBound `asTypeOf` a))

   -- ryan


More information about the Haskell-Cafe mailing list