Re: [Haskell-cafe] Re: QuickCheck: Arbitrary for a complex type

2007-04-04 Thread Fawzi Mohamed

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 1 rnd $ vector 5 :: [Foo]

gen =
do { rnd - newStdGen
   ; return $ gen' rnd
   }

--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: QuickCheck: Arbitrary for a complex type

2007-04-04 Thread Joel Reymont

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.


--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: QuickCheck: Arbitrary for a complex type

2007-04-04 Thread Stefan O'Rear
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)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe