[Haskell-cafe] Re: QuickCheck: Arbitrary for a complex type
Fawzi Mohamed
fmohamed at mac.com
Wed Apr 4 12:27:25 EDT 2007
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
> }
>
> --
> http://wagerlabs.com/
>
>
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
More information about the Haskell-Cafe
mailing list