On Sun, Mar 16, 2008 at 5:42 PM, rodrigo.bonifacio <
[EMAIL PROTECTED]> wrote:

> Hi all,
>
> I'm trying to use the quick-check library for checking some properties of
> a user defined data type. Bellow the target data type:
>
> data Feature =
>  Feature Id Name FeatureType GroupType Children Properties |
>  FeatureError
>
> where:
>
> Id = String
> Name = String
> FeatureType = int
> GroupType = int
> Children = [Feature]
> Propertyes = [String]
>
>
> I've written the following quick-check property:
>
> prop_AlternativeFeature :: Feature -> Feature -> QuickCheck.Property
> prop_AlternativeFeature fm fc = length (children fc) == 0 ==> length
>  (checkAlternativeFeature fm fc) > 0
>
> When I try to check such property, the result is:
>
> ERROR "./EshopModelChecking.hs":11 - Type error in instance member binding
> *** Term           : arbitrary
> *** Type           : Feature
> *** Does not match : Gen Feature
>
> I think that I need to write some arbitrary or generator functions, but I
> didn't realize how to do that with the availalble quick-checking
> documentation.
>
> Any help will be welcome.
>
>
You use the available functions to build up a generator for your data type.

First, let's give the instanc itself. For this I'm just going to use the
frequency function to use "featureGenNormal" five times more often than
"return FeatureError". This means that will get a FeatureError every now and
then, but mostly you'll get featureGenNormal (see below). You can change
these frequences, of course.

instance Arbitrary Feature where
    arbitrary = do
        frequency [ (5, featureGenNormal),  (1, return FeatureError) ]

In order to write featureGenNormal, we need to be able to generate random
values of each of the parts of the data type. Often these types will already
have Arbitrary instances, so generating an isntance for your type is quite
often just a matter of calling "arbitrary" for each component, and then
returning a datatype. However, there is no Arbitrary instance for String,
which is a bit annoying, so let's write our own generator for strings.

First a generator for a single letter:

letterGen = oneof $ map return $ ['a'..'z'] ++ ['A'..'Z']

Then a combinator for generating a list of values given a generator for a
single value:

listGen :: Gen a -> Gen [a]
listGen g = do
    x <- g
    xs <- frequency [ (1, return []), (10, listGen g) ]
    return (x:xs)

And then we use this to build our "stringGen" generator.

stringGen :: Gen String
stringGen = listGen letterGen

Now, we have all we need to write the featureGenNormal generator:

featureGenNormal = do
    id <- stringGen
    name <- stringGen
    featuretype <- arbitrary
    grouptype <- arbitrary
    children <- arbitrary
    properties <- listGen stringGen
    return (Feature id name featuretype grouptype children properties)


Note that we use "arbitrary" to generate the list of children recursively.

-- 
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to