[QuickCheck] Obtaining value of QC counter example

Koen Claessen koen at chalmers.se
Mon Oct 15 10:18:41 BST 2012


Yes, but properties can also be of type "Property" (or "Int ->
Property", etc.) and in that case there is no way of knowing how much
quantification is going on inside such a property.

The solution I gave is more general in some sense because you can
decide to return any values form inside the property, not only the
quantified ones.

You can also write yourself:

  quickCheckArg :: (Arbitrary a, Testable prop) => (a -> prop) -> IO (Maybe a)
  quickCheckArg p =
    do ref <- newIORef Nothing
        quickCheck (\x -> whenFail (writeIORef ref (Just x)) (p x))
        readIORef ref

Or introduce a new type class if you want multiple arguments. (In
practice, you can tuple these yourself of course.)

/Koen

On Mon, Oct 15, 2012 at 11:12 AM, J. Stutterheim <j.stutterheim at me.com> wrote:
> Hi Koen,
>
>
> Thank you for the example! But suppose we have some monomorphic property prop_Foo :: [Int] -> Bool. Do we then not know the type of the counter example? The type of prop_Foo indicates that it would be some list of Int (e.g. [1,0]). Could we use this knowledge to somehow cast the value into a concrete counter-example, without relying on IORefs?
>
> Likewise, if we have some property prop_Bar :: [Int] -> Int -> Bool and we get some counter example (e.g. [1,2,3] and 4), would we then not have sufficient type information to produce a tuple of type ([Int], Int)?
>
>
> Jurriën
>
> On 15 Oct 2012, at 10:51, Koen Claessen <koen at chalmers.se> wrote:
>
>> Hi Jurien,
>>
>> Since it is impossible to know on the outside of the property what the
>> type is of the values you are interested in, this is not very easy.
>>
>> I usually use the following trick (a bit ugly, but it works).
>>
>> Suppose you have a property:
>>
>>  prop_Monkey =
>>    forAll ....
>>      ...
>>        x == y
>>
>> And you want to get the value of x and y. x and y can be quantified
>> variables, or other values that live inside the property.
>>
>> If you want to print them, you can say:
>>
>>  prop_Monkey =
>>    forAll ....
>>      ...
>>        whenFail (print (x,y)) $
>>          x == y
>>
>> If you want to get them and use them as Haskell values, you can say:
>>
>>  prop_Monkey ref =
>>    forAll ....
>>      ...
>>        whenFail (writeIORef ref (Just (x,y))) $
>>          x == y
>>
>> Now, before you QuickCheck the property, you create an IORef like so:
>>
>>  ref <- newIORef Nothing
>>  quickCheck (prop_Monkey ref)
>>
>> Afterwards you can look in the ref to see if there is a counter example.
>>
>> A bit ugly, but since the type of the internal values is not known,
>> the only way I know how to do it.
>>
>> Let me know if this works for you.
>>
>> /Koen
>>
>> On Sat, Oct 13, 2012 at 11:36 AM, Jurriën Stutterheim
>> <j.stutterheim at me.com> wrote:
>>> Dear QuickCheck developers,
>>>
>>>
>>> Is it possible to obtain the value of the shrunk counter example that QuickCheck produces, so that I may use it in the rest of my program? If so, how? :)
>>> I could imagine that it's possible (at least for non-function values) to return a single counter example value for functions with a single argument, and a tuple of values for functions with more than one argument.
>>>
>>> Cheers,
>>>
>>>
>>> Jurriën
>>> _______________________________________________
>>> QuickCheck mailing list
>>> QuickCheck at projects.haskell.org
>>> http://projects.haskell.org/cgi-bin/mailman/listinfo/quickcheck
>



More information about the QuickCheck mailing list