I wanted to generate some random table
data, and decided to use quickcheck to do this. I didn't want to be checking
properties, I actually wanted to output the examples that quickcheck came
up with using arbitrary. In this case, I wanted to generate lists of lists
of strings.
In case this is of use to anyone else
here's an example...
One thing I don't understand is the
purpose of the first argument to generate. If it's zero it's always the
same data, so I made it a larger number (10000). Seems ok, but it would
be nice to understand why. Or if there is a better bway to accomplish this.
t.
{-# OPTIONS -fno-monomorphism-restriction
#-}
module GenTestData where
import Test.QuickCheck
import Control.Monad
import System.Random
import Test.QuickCheck
import Misc
import ArbitraryInstances
f >>=^ g = f >>= return
. g
infixl 1 >>=^
rgenIntList = rgen (arbitrary :: Gen
[Int]) :: IO [Int]
rgenInt = rgen (arbitrary :: Gen Int)
:: IO Int
rgenFoo = rgen (arbitrary :: Gen Foo
) :: IO Foo
rgenFoos = rgen (arbitrary :: Gen [Foo])
:: IO [Foo]
rgenString' = rgen (arbitrary :: Gen
[Char]) :: IO [Char]
rgenString len = rgenString' >>=^
take len
rgenStringRow' = rgen (arbitrary ::
Gen [[Char]]) :: IO [[Char]]
rgenStringRow maxlenstr maxcols =
do
rgenStringRow'
>>=^ take maxcols
>>=^ map ( take maxlenstr
)
rgenStringTable' = rgen (arbitrary
:: Gen [[[Char]]]) :: IO [[[Char]]]
rgenStringTable maxlenstr maxcols maxrows
= do
rgenStringTable'
>>=^ take maxrows
>>=^ map ( take maxcols
)
>>=^ ( map . map ) (take
maxlenstr)
rgen gen = do
sg <- newStdGen
return $ generate 10000 sg gen
module ArbitraryInstances where
import Test.QuickCheck
import Data.Char
import Control.Monad
instance Arbitrary Char where
arbitrary
= choose ('\32', '\128')
coarbitrary c = variant
(ord c `rem` 4)
-- joel reymont's example I think
data Foo
= Foo Int
| Bar
| Baz
deriving
Show
instance Arbitrary Foo where
coarbitrary = undefined
arbitrary
= oneof [ return Bar
, return Baz
, liftM Foo arbitrary
---
This e-mail may contain confidential and/or privileged information. If you
are not the intended recipient (or have received this e-mail in error)
please notify the sender immediately and destroy this e-mail. Any
unauthorized copying, disclosure or distribution of the material in this
e-mail is strictly forbidden.