[Haskell-cafe] Re: Coarbitrary (was QuickCheckM for IO testing)

Shae Matijs Erisson shae at ScannedInAvian.com
Thu Oct 27 13:38:08 EDT 2005


Joel Reymont <joelr1 at gmail.com> writes:

> How is this supposed to work? Does anyone have a simple explanation?

Here's a demonstration of an arbitrary instance for a datatype.
<code>
module ProtoArbitrary where

import Test.QuickCheck
import Control.Monad

data Tree a = Nil | Node (Tree a) a (Tree a) deriving (Eq,Ord,Show)

instance (Arbitrary a) => Arbitrary (Tree a) where
    arbitrary = oneof [return Nil, liftM3 Node arbitrary arbitrary arbitrary]
    coarbitrary = error "not implemented"

prop_TreeI   :: Tree Int -> Bool
prop_TreeI x = True

prop_TreeF   :: Tree Float -> Bool
prop_TreeF x = True
</code>

> I could not understand how to define this for arbitraries of my
> choosing and Shae seems to have defined coarbitrary = error "Not
> implemented" :-).

Coarbitrary is for generator transformers, see section 3.3 on page 5 of
the original paper http://www.md.chalmers.se/~koen/Papers/quick.ps
-- 
Shae Matijs Erisson - http://www.ScannedInAvian.com/ - Sockmonster once said:
You could switch out the unicycles for badgers, and the game would be the same.



More information about the Haskell-Cafe mailing list