| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Test.QuickCheck.Arbitrary.Generic
Description
Generic implementation of the arbitrary method. Example usage:
data Foo = Foo
{ _fooX :: X
, _fooY :: Y
} deriving (Generic)
instance Arbitrary Foo where
arbitrary = genericArbitrary
shrink = genericShrink
This instance can also be derived using DerivingVia language extension
data Foo = Foo
{ _fooX :: X
, _fooY :: Y
} deriving (Generic)
deriving (Arbitrary) via GenericArbitrary Foo
The generated arbitrary method is equivalent to
Synopsis
- newtype GenericArbitrary a = GenericArbitrary {
- unGenericArbitrary :: a
- class Arbitrary a where
- genericArbitrary :: (Generic a, GArbitrary ga, ga ~ Rep a) => Gen a
- genericShrink :: (Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) => a -> [a]
Documentation
newtype GenericArbitrary a Source #
Constructors
| GenericArbitrary | |
Fields
| |
Instances
| Eq a => Eq (GenericArbitrary a) Source # | |
Defined in Test.QuickCheck.Arbitrary.Generic Methods (==) :: GenericArbitrary a -> GenericArbitrary a -> Bool # (/=) :: GenericArbitrary a -> GenericArbitrary a -> Bool # | |
| Show a => Show (GenericArbitrary a) Source # | |
Defined in Test.QuickCheck.Arbitrary.Generic Methods showsPrec :: Int -> GenericArbitrary a -> ShowS # show :: GenericArbitrary a -> String # showList :: [GenericArbitrary a] -> ShowS # | |
| (Generic a, GArbitrary (Rep a), RecursivelyShrink (Rep a), GSubterms (Rep a) a) => Arbitrary (GenericArbitrary a) Source # | |
Defined in Test.QuickCheck.Arbitrary.Generic Methods arbitrary :: Gen (GenericArbitrary a) # shrink :: GenericArbitrary a -> [GenericArbitrary a] # | |
Random generation and shrinking of values.
QuickCheck provides Arbitrary instances for most types in base,
except those which incur extra dependencies.
For a wider range of Arbitrary instances see the
quickcheck-instances
package.
Minimal complete definition
Methods
A generator for values of the given type.
It is worth spending time thinking about what sort of test data
you want - good generators are often the difference between
finding bugs and not finding them. You can use sample,
label and classify to check the quality of your test data.
There is no generic arbitrary implementation included because we don't
know how to make a high-quality one. If you want one, consider using the
testing-feat or
generic-random packages.
The QuickCheck manual goes into detail on how to write good generators. Make sure to look at it, especially if your type is recursive!
Produces a (possibly) empty list of all the possible immediate shrinks of the given value.
The default implementation returns the empty list, so will not try to
shrink the value. If your data type has no special invariants, you can
enable shrinking by defining shrink = , but by customising
the behaviour of genericShrinkshrink you can often get simpler counterexamples.
Most implementations of shrink should try at least three things:
- Shrink a term to any of its immediate subterms.
You can use
subtermsto do this. - Recursively apply
shrinkto all immediate subterms. You can userecursivelyShrinkto do this. - Type-specific shrinkings such as replacing a constructor by a simpler constructor.
For example, suppose we have the following implementation of binary trees:
data Tree a = Nil | Branch a (Tree a) (Tree a)
We can then define shrink as follows:
shrink Nil = [] shrink (Branch x l r) = -- shrink Branch to Nil [Nil] ++ -- shrink to subterms [l, r] ++ -- recursively shrink subterms [Branch x' l' r' | (x', l', r') <- shrink (x, l, r)]
There are a couple of subtleties here:
- QuickCheck tries the shrinking candidates in the order they
appear in the list, so we put more aggressive shrinking steps
(such as replacing the whole tree by
Nil) before smaller ones (such as recursively shrinking the subtrees). - It is tempting to write the last line as
[Branch x' l' r' | x' <- shrink x, l' <- shrink l, r' <- shrink r]but this is the wrong thing! It will force QuickCheck to shrinkx,landrin tandem, and shrinking will stop once one of the three is fully shrunk.
There is a fair bit of boilerplate in the code above.
We can avoid it with the help of some generic functions.
The function genericShrink tries shrinking a term to all of its
subterms and, failing that, recursively shrinks the subterms.
Using it, we can define shrink as:
shrink x = shrinkToNil x ++ genericShrink x
where
shrinkToNil Nil = []
shrinkToNil (Branch _ l r) = [Nil]genericShrink is a combination of subterms, which shrinks
a term to any of its subterms, and recursivelyShrink, which shrinks
all subterms of a term. These may be useful if you need a bit more
control over shrinking than genericShrink gives you.
A final gotcha: we cannot define shrink as simply
as this shrinks shrink x = Nil:genericShrink xNil to Nil, and shrinking will go into an
infinite loop.
If all this leaves you bewildered, you might try to begin with,
after deriving shrink = genericShrinkGeneric for your type. However, if your data type has any
special invariants, you will need to check that genericShrink can't break those invariants.
Instances
genericShrink :: (Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) => a -> [a] #
Shrink a term to any of its immediate subterms, and also recursively shrink all subterms.