[Haskell-cafe] Compiler's bane

Ryan Ingram ryani.spam at gmail.com
Thu Sep 4 15:57:25 EDT 2008


On Thu, Sep 4, 2008 at 10:41 AM, Andrew Coppin
<andrewcoppin at btinternet.com> wrote:
> I love the way other people have wildly different ideas of "simple" than me.
> I'm staring at this and completely failing to comprehend it. (But then,
> anything with "co" in the name generally makes little sense to me...) Why on
> earth would you need a reader monad? Surely if you want to add bound
> variables and then later query what variables are bound, you'd want a state
> monad? Hmm, I'm completely lost here.

Other people have already covered the reader vs. state issue; but to
sum up, this is a state monad, but the state can only be mutated in
sub-expressions, not in future expressions.

In my quick implementation, the branch of arbExp that makes a
lambda-expression looks something like this:

> do
>    -- get a new variable name
>    v <- lift arbitrary
>    -- construct a new expression that may use v as a variable
>    e <- local (v:) arbExp
>    -- return the new expression
>    return (Lambda v e)

As to all the crazy "co" stuff, it's just an implementation detail for
QuickCheck.  It took me a while figure out what was actually going on,
but the implementation is basically just boilerplate at this point.  A
simpler implementation is

> coarbitrary _ = id

A full explanation:

> coarbitrary :: Arbitrary a => a -> Gen b -> Gen b

Gen is a simple state monad that holds the random number generator
state and some additional QuickCheck data.  What "coarbitrary" is
supposed to do is to modify the state of the random number generator
based on the input data.  This allows quickCheck to create automatic
arbitrary instances for functions that output your type a; that is, if
you had a property

> prop_compose_assoc h g f x = (f . (g . h)) x == ((f . g) . h) x

ghci> quickCheck (prop_compose_assoc ::
            (Int -> Expression) ->
            (Expression -> Expression) ->
            (Expression -> Int) ->
            Int -> Bool)
... OK, passed 100 tests.

In order to do this, it needs to be able to generate a function of
type (Expression -> Expression), but at the time that function is
constructed you have just the random number generator state at that
point.  In order to do this, it creates a function that uses
coarbitrary on the input Expression to modify that fixed random number
generator state to get a new state which is then used to generate the
output expression.  Using the "simple" implementation of coarbitrary
above, QuickCheck will only generate constant functions; that is,
functions which generate the same (random) expression each time they
are called.

The internals of doing so are kind of ugly, but thankfully you are
free to ignore that and build your coarbitrary out of a couple of
simple building blocks:

> variant :: Int -> Gen b -> Gen b
> coarbitrary :: Arbitrary a => a -> Gen b -> Gen b

But wait, aren't you supposed to be defining coarbitrary?  Well, as
long as you use coarbitrary on smaller data structures, you're fine.
The strategy for finite data structures is really simple:

- Each constructor uses "variant" with a number representing that constructor.
- Each data inside a constructor uses coarbitrary recursively.

The reason I included the 'coarbitrary' code in my post is that it is
the more complicated part of the instance to understand and write
before you "get it"; understanding how to write "arbitrary" is the
important part.

  -- ryan

> Ryan Ingram wrote:
>>
>> It's pretty simple, I think.
>>
>> type ExpGen = ReaderT [String] Gen
>>
>> arbExp :: ExpGen Expression
>> -- exercise for the reader
>>
>> instance Arbitrary Expression where
>>    arbitrary = runReaderT arbExp []
>>    coarbitrary = coarbExp
>>
>> coarbExp (Var s)      = variant 0 . coarbitrary s
>> coarbExp (Apply a b)  = variant 1 . coarbitrary a . coarbitrary b
>> coarbExp (Lambda s e) = variant 2 . coarbitrary s . coarbitrary e
>>
>> instance Arbitrary Char where
>>  arbitrary   = elements "abcdefghijklmnopqrstuvwxyz_"
>>  coarbitrary = coarbitrary . fromEnum
>>


More information about the Haskell-Cafe mailing list