quickcheck
quickcheck copied to clipboard
Generate edge cases
Generate edge cases (minBound, maxBound, minBound + 1, ...) with some low frequency.
abs always returns a positive number right?
>>> quickCheck (\(n :: Int) -> abs n >= 0)
+++ OK, passed 100 tests.
Alright let's ship it — well — the test fails if we run it on Int8s often enough
>>> quickCheck (\(n :: Int8) -> abs n >= 0)
+++ OK, passed 100 tests.
>>> quickCheck (\(n :: Int8) -> abs n >= 0)
+++ OK, passed 100 tests.
>>> quickCheck (\(n :: Int8) -> abs n >= 0)
+++ OK, passed 100 tests.
>>> quickCheck (\(n :: Int8) -> abs n >= 0)
*** Failed! Falsifiable (after 23 tests):
-128
Turns out it doesn't actually hold for Ints
>>> abs @Int minBound
-9223372036854775808
This could be detected for larger sample spaces like Int if minBound were generated. I would like to see this in the Arbitrary Int instance but maybe a modifier is better?
Minimal modifier that produces a counterexample for Int
newtype XTreme a = XTreme a deriving Show
instance (Arbitrary a, Num a, Bounded a) => Arbitrary (XTreme a) where
arbitrary = let
prob = [(1, pure minBound), (1, pure (minBound + 1)), (1, pure (minBound + 2)),
(1, pure maxBound), (1, pure (maxBound - 1)), (1, pure (maxBound - 2)),
(1000-6, arbitrary)]
in XTreme <$> frequency prob
>>> quickCheckWith stdArgs { maxSuccess = 1000 } (\(XTreme (a :: Int)) -> abs a >= 0)
*** Failed! Falsifiable (after 94 tests):
XTreme (-9223372036854775808)
Found a similar version in the tests:
newtype Extremal a = Extremal { getExtremal :: a } deriving (Show, Eq, Ord, Num, Enum, Real, Integral)
instance (Arbitrary a, Bounded a) => Arbitrary (Extremal a) where
arbitrary =
fmap Extremal $
frequency
[(1, return minBound),
(1, return maxBound),
(8, arbitrary)]
shrink (Extremal x) = map Extremal (shrink x)
I'd rather do
{-# LANGUAGE ScopedTypeVariables, GeneralizedNewtypeDeriving #-}
import Test.QuickCheck
newtype EB a = EB { getEB :: a }
deriving (Show, Eq, Ord, Num, Enum, Real, Integral)
instance (Enum a, Bounded a) => Arbitrary (EB a) where
arbitrary = EB <$> frequency
[ (20, toEnum <$> choose (i, j))
, (1, return minBound)
, (1, return maxBound)
]
where
i = fromEnum (minBound :: a)
j = fromEnum (maxBound :: a)
shrink = fmap (EB . toEnum) . shrink . fromEnum . getEB
Seems like a good idea!
However, we shouldn't do it for the default Int generator. That deliberately only generates small numbers, as people use Ints as (e.g.) lengths of lists, this kind of thing:
prop_replicate_length :: Int -> String -> Property
prop_replicate_length n x = n >= 0 ==> length (replicate n x) === n
But adding it to the Large modifier might be sensible. To do that we should change arbitrarySizedBoundedIntegral. Then the fixed-size integer types (Int32 and friends) would generate extreme values by default, but not Int.
Thanks for the comments, I think this should be mentioned in the documentation — a user may not know to use a modifier if their tests pass for the default generator. Jotting down some ideas
Alternative reality where Large generates minBound/maxBound:
The default generator for
Intgenerates small numbers, it will miss edge cases likeminBound @IntandmaxBound @Int.>>> quickCheck (\(n :: Int) -> abs n >= 0) +++ OK, passed 100 tests.that get caught by using a
Largemodifier>>> quickCheck (\(Large (n :: Int)) -> abs n >= 0) *** Failed! Falsifiable (after 21 tests): Large (-9223372036854775808)
Using a modifier to generate small numbers explicitly makes sense, not suggesting that as a change though
prop_replicate_length :: Small Int -> String -> Property
prop_replicate_length (Small n) x = n >= 0 ==> length (replicate n x) === n
unrelated, given Integral a => Integral (Positive a) we can nest them
prop_replicate_length :: Positive (Small Int) -> String -> Property
prop_replicate_length (Positive (Small n)) x = length (replicate n x) === n
Hi,
I had some issues with quickcheck not generating special values, so I made a small package for it which uses a Special newtype similar to what was proposed here.
- http://hackage.haskell.org/package/quickcheck-special
- https://github.com/minad/quickcheck-special
Is this going in the right direction concerning this issue? Maybe something like that could be added to QuickCheck at some point?
Yes, generating special values is definitely a good idea!
The approach I would take is to change the existing Arbitrary instances for Char, Float etc., rather than having a modifier, so that you always get special values (I don't see any advantage to not generating them).
"Small" special values like Nothing, [], 0 are already generated with high probability, so the important thing is to get those special values that are hard to find currently.
In principle I agree that everything should be generated. However for Float, the NaN values are problematic since they violate the typeclass laws.
Oh yes, good point. NaN should be left out of that. Maybe things like infinity are also problematic.
Perhaps we should be conservative and have the principle that we only change the distribution of generated values, i.e. we generate values that it was unlikely to generate before, but not values that it was impossible to generate before. Probably that means we don't change the distribution of Float, but then have a modifier like in your package. But we can still do something for other types.
Humour me, how about an additional method or subclass of Arbitrary, with a default value like shrink
class Arbitrary a where
arbitrary :: Gen a
shrink :: a -> [a]
shrink _ = []
extreme :: [a]
extreme = []
tooExtreme :: [a]
tooExtreme = []
Now we have some control over extreme values: how extreme we want them as well as their frequency
instance Arbitrary Float where
...
extreme :: [Float]
extreme = [0, -0, 2.22044604925031308085e-16, 4.94065645841246544177e-324, 2.22507385850720138309e-308, 1.79769313486231570815e+308]
tooExtreme :: [Float]
tooExtreme = [0/0, 1/0, -1/0]
instance Arbitrary Int where
extreme :: [Int]
extreme = [0, 1, -1, minBound, maxBound, minBound + 1, maxBound - 1]
instance Arbitrary Char where
extreme :: [Char]
extreme = [minBound, maxBound, succ minBound, pred maxBound]
Edit: Just ike specialValues from @minad's package, making it a method of Arbitrary means any data type can be tested with special values but making it a special type class means we know which values support special values... bleh
class SpecialValues a where
-- | Finite list of special values
specialValues :: [a]
It could include frequency information, extreme :: [(Int, a)] but that feels arbitrary (pun intended).
Just found out that quickcheck doesn't generate NaN and was quiet surprised. @nick8325, you said that NaN should be left out.
Can you explain why exactly?
Because for me it seems that this value should definitely present in generation as soon as developers tend to forget about it and then weird things happen and this is what the quickcheck for - to help to reveal edge cases, isn't it?
That an input contains no NaN seems like a reasonable precondition to assume implicitly, similar to inputs not being undefined.
Right, my thinking was that passing NaN to a function means that an error has already occurred - in this respect it seems very similar to undefined. I would expect most numeric algorithms to implicitly have a precondition that the input does not contain NaN.
However, it would definitely be useful to have a modifier so that the programmer can opt into testing with NaN.
:+1: to the modifier for NaN
Sorry, I'm not that familiar with Haskell, but as far as I understand NaN is a valid floating point number representation and the code won't throw error if you try to operate on that, which is not the case for undefined.
And it would make perfect sense for me as a maintainer of a library to check my code against NaN if I have function accepting floats.
I can totally see that it is a breaking change if you would introduce the NaN as a generated float value, but theoretically I see it more as a profit that when I test my function with your library I would be forced to check input value for NaN. It might be in function itself, or in the test: both will make behaviour of my code more clear to the reader.
And regarding the switch, I can say that personally I would prefer the switch to turn it off rather than turn it on. If I may exaggerate, it is similar to generating values only in the range (0, 1) but having a switch to expand it. Most of the people will not know about that switch (for this you need to read more than 1 page of docs, but who does it? I don't) and their code just won't be tested against all the possible values. On the contrary, if you generate all the possible stuff then people who doesn't need values outside the range, will discover this switch eventually.
I found this bug after being surprised at how hard it is to hit the abs minBound condition. I'd like that behavior by default, but I can understand why it's not. But it'd definitely be nice if XTreme and the like were included in the modifier library.
I imagine other values such as map (2^) [0..62](±1) would be helpful for finding some bugs, too.
Using @minad's package and a future extension -XDerivingVia you can derive Arbitrary with a Special modifier a property of the type (whether I encourage that is another story). The modifier can then be parameterized by “levels of Xtremeness”.
It would be nice to have similar feature for Float / Double. Even if NaN was decided to be out-of-scope, one can benefit from generating +Infinity / -Infinity values. At the moment I have to write separate test cases for infinities, which is error prone.
Here's my hacky (EDIT: and not carefully tested) implementation of a modifier that tries to give the full range of possible Double values, edge cases included. It would be nice to have something like this as an option, even if it's not the default.
I release this under the current QuickCheck licence (which is the 3-clause BSD licence).
(EDIT: It uses Data.Bits.Floating.coerceToFloat from the floating-bits package, but that part could be removed and you'll still get the special cases I listed.)
-- Double, except the Arbitrary instance can NaN, infinity and negative zero.
-- (I don't know which of these the Double instance generates.) This generates
-- strange doubles in two ways: first, by coercing an arbitrary word to a
-- double; and second, through an incomplete list of special cases.
--
-- It could probably be included by adding more special cases; e.g. I don't
-- know how likely this is to generate a "signalling NaN", NaNs with different
-- payloads, or subnormal values.
newtype DoubleWithEdgeCases = DoubleWithEdgeCases Double
instance Arbitrary DoubleWithEdgeCases where
arbitrary =
let fromBits = do Large x <- arbitrary
return (DoubleWithEdgeCases (coerceToFloat x))
in oneof
( fmap DoubleWithEdgeCases arbitrary
: fromBits
: map (return . DoubleWithEdgeCases . read) ["Infinity", "-Infinity", "NaN", "-0.0"]
)
instance Show DoubleWithEdgeCases where
showsPrec prec (DoubleWithEdgeCases x) = showsPrec prec x