
Joel Reymont wrote:
I got this simple example working so I think I have my question answered. Great, just one thing that could be important : when you have recursive structures (like your Statement through Compound) be sure to use sized (\mySize -> ...) as generator for arbitrary so that you can avoid infinite looping. Look at http://www.cs.chalmers.se/~rjmh/QuickCheck/manual_body.html#15 for an example.
Fawzi
Now I just have to learn to write generators of my own to produce valid and invalid input for my parser.
module Foo where
import Control.Monad import System.Random import Test.QuickCheck
data Foo = Foo Int | Bar | Baz deriving Show
instance Arbitrary Foo where coarbitrary = undefined arbitrary = oneof [ return Bar , return Baz , liftM Foo arbitrary ]
gen' rnd = generate 10000 rnd $ vector 5 :: [Foo]
gen = do { rnd <- newStdGen ; return $ gen' rnd }
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe