QuickCheck: Arbitrary for a complex type

Suppose I have a type describing a statement and that I'm trying to make it an instance of arbitrary. The type looks like this: data Statement = InputDecs [InputDecl] | VarDecs [VarDecl] | ArrayDecs [ArrayDecl] | Compound [Statement] | Assign (VarIdent, Expr) | ArrayAssign (VarIdent, [Expr], Expr) Assuming that other types involved were instances of arbitrary, how do I write arbitrary for Statement? Poking around various bits of source code I think that for a type like the following data Style = StyleValue Expr | Solid | Dashed | Dotted | Dashed2 | Dashed3 deriving Show I can write instance Arbitrary Style where arbitrary = oneOf [ StyleValue . arbitrary, elements [ Solid , Dashed , Dotted , Dashed2 , Dashed3 ] ] I'm not sure if this is correct, though, so any help is appreciated! Thanks in advance, Joel -- http://wagerlabs.com/

I got this simple example working so I think I have my question answered. 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/

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

One last bit then... My identifiers should start with letter <|> char '_' and the tail should be alphaNum <|> char '_'. I guess I can use choose and oneof to produce the right set of characters but how do I combine the two into a single identifier of a given length (up to 20 chars, say)? Thanks, Joel On Apr 4, 2007, at 5:27 PM, Fawzi Mohamed wrote:
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.

On Wed, Apr 04, 2007 at 10:59:45PM +0100, Joel Reymont wrote:
One last bit then...
My identifiers should start with letter <|> char '_' and the tail should be alphaNum <|> char '_'.
I guess I can use choose and oneof to produce the right set of characters but how do I combine the two into a single identifier of a given length (up to 20 chars, say)?
Thanks, Joel
On Apr 4, 2007, at 5:27 PM, Fawzi Mohamed wrote:
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.
quickcheck is a monad so you can just do: do first <- elements $ '_' : ['a' .. 'z'] len <- elements $ [5..19] rest <- replicateM len $ elements $ '_' : ['a' .. 'z'] ++ ['0' .. '9'] return (first : rest)
participants (3)
-
Fawzi Mohamed
-
Joel Reymont
-
Stefan O'Rear