
I've notice a behaviour of quickcheck that is unexpected to me. With this code: import Test.QuickCheck main = check myconfig ((\v -> v == v) :: (Maybe Double,Maybe Double) -> Bool) myconfig = defaultConfig{configMaxTest=100000, configEvery = \n args -> show n ++ ":\n" ++ unlines args} I am relying on the default Arbitrary instances to generate pairs of maybe doubles. But to my surprise, all of the pairs have these patterns: (Just _ Just _) (Nothing, Nothing) I never see patterns: (Just _, Nothing) (Nothing, Just _) Why is this the case? Thanks, Tim

your quick check property (in a different way of writing) is the following:
prop_1 :: Maybe Double -> Bool
prop_1 v = v == v
but what you want is actually the following:
prop_2 :: Maybe Double -> Maybe Double -> Bool
prop_2 v1 v2 = v2 == v2
if I understood the problem correctly, using prop_2 should solve it. just
run verboseCheckhttp://hackage.haskell.org/packages/archive/QuickCheck/1.1.0.0/doc/html/Test...on
these two and observe the results.
Best,
On 5 May 2010 08:47, Tim Docker
I've notice a behaviour of quickcheck that is unexpected to me. With this code:
import Test.QuickCheck
main = check myconfig ((\v -> v == v) :: (Maybe Double,Maybe Double) -> Bool)
myconfig = defaultConfig{configMaxTest=100000, configEvery = \n args -> show n ++ ":\n" ++ unlines args}
I am relying on the default Arbitrary instances to generate pairs of maybe doubles. But to my surprise, all of the pairs have these patterns:
(Just _ Just _) (Nothing, Nothing)
I never see patterns:
(Just _, Nothing) (Nothing, Just _)
Why is this the case?
Thanks,
Tim
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ozgur Akgun

There is a typo, in my previous post, It should have been: prop_2 v1 v2 = v1
== v2
not: prop_2 v1 v2 = v2 == v2
Moreover, I realised that the (nice) function verboseCheck doesn't exist in
QuickCheck 2. However you can always do the following in ghci, to see
whether my suggestion works or not:
sample (arbitrary :: Gen (Maybe Double, Maybe Double) )
On 5 May 2010 09:01, Ozgur Akgun
your quick check property (in a different way of writing) is the following:
prop_1 :: Maybe Double -> Bool prop_1 v = v == v
but what you want is actually the following:
prop_2 :: Maybe Double -> Maybe Double -> Bool prop_2 v1 v2 = v2 == v2
if I understood the problem correctly, using prop_2 should solve it. just run verboseCheckhttp://hackage.haskell.org/packages/archive/QuickCheck/1.1.0.0/doc/html/Test...on these two and observe the results.
Best,
On 5 May 2010 08:47, Tim Docker
wrote: I've notice a behaviour of quickcheck that is unexpected to me. With this code:
import Test.QuickCheck
main = check myconfig ((\v -> v == v) :: (Maybe Double,Maybe Double) -> Bool)
myconfig = defaultConfig{configMaxTest=100000, configEvery = \n args -> show n ++ ":\n" ++ unlines args}
I am relying on the default Arbitrary instances to generate pairs of maybe doubles. But to my surprise, all of the pairs have these patterns:
(Just _ Just _) (Nothing, Nothing)
I never see patterns:
(Just _, Nothing) (Nothing, Just _)
Why is this the case?
Thanks,
Tim
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ozgur Akgun
-- Ozgur Akgun

On 5 May 2010 09:01, Ozgur Akgun
your quick check property (in a different way of writing) is the following:
prop_1 :: Maybe Double -> Bool prop_1 v = v == v
I think you misunderstood me. The property was fabricated just for the example. My question was why, when I generate random values for (Maybe t, Maybe t) using the Arbitrary type class, do I always see two Nothing values or two Just values, and never one of each? Tim

On 5 May 2010 11:38, Tim Docker
On 5 May 2010 09:01, Ozgur Akgun
wrote: your quick check property (in a different way of writing) is the following:
prop_1 :: Maybe Double -> Bool prop_1 v = v == v
I think you misunderstood me. The property was fabricated just for the example.
OK that's possible :)
My question was why, when I generate random values for (Maybe t, Maybe t) using the Arbitrary type class, do I always see two Nothing values or two Just values, and never one of each?
Let me try to understand you then. What happens when you run the following command in ghci? sample (arbitrary :: Gen (Maybe Int, Maybe Int) ) Do you still always get (Just _, Just _) or (Nothing, Nothing) pairs, or do you also get some (Nothing, Just _) or (Just _, Nothing) pairs? Ozgur

On May 5, 10:57 pm, Ozgur Akgun
Let me try to understand you then. What happens when you run the following command in ghci?
sample (arbitrary :: Gen (Maybe Int, Maybe Int) )
Do you still always get (Just _, Just _) or (Nothing, Nothing) pairs, or do you also get some (Nothing, Just _) or (Just _, Nothing) pairs?
Well, I couldn't run the above code, as "sample" isn't part of quickcheck-1.2. But this made me wonder whether it's a version issue. This seems to be the case. If I run this with quickcheck 2.1:
import Test.QuickCheck
main = quickCheckWith stdArgs{maxSuccess=100000} f
f :: (Maybe Int,Maybe Int) -> Bool f (Just _,Just _) = True f (Nothing,Nothing) = True f _ = False
I see a failure almost instantly. This is what I want... I don't expect all of the generated pairs to have the same constructor in each field. However, running this with quickcheck 1.2:
import Test.QuickCheck
main = quickCheckWith stdArgs{maxSuccess=100000} f
f :: (Maybe Int,Maybe Int) -> Bool f (Just _,Just _) = True f (Nothing,Nothing) = True f _ = False
I see no failures... all of the generatd pairs have the same constructor in each field. So the good news is that quickcheck 2.1 behaves as I expected. I'm still curious as to the behaviour of the older version. Tim

So the good news is that quickcheck 2.1 behaves as I expected. I'm still curious as to the behaviour of the older version.
In QC 1.2, the instance of Arbitrary for the Maybe type uses the "sized" combinator to choose between Nothing and Just, whereas in QC 2.1, the instance uses the "frequency" combinator. I'm guessing that the notion of size applies to the whole enclosing value, so gets replicated to all of its parts, whereas frequency is independently generated for each component. Regards, Malcolm
participants (3)
-
Malcolm Wallace
-
Ozgur Akgun
-
Tim Docker