genvalidity-0.2.0.3: Testing utilities for the validity library

Safe HaskellSafe
LanguageHaskell2010

Data.GenValidity

Description

GenValidity exists to make tests involving Validity types easier and speed up the generation of data for them.

Let's use the example from Data.Validity again: A datatype that represents primes. To implement tests for this datatype, we would have to be able to generate both primes and non-primes. We could do this with (Prime $ arbitrary) suchThat isValid but this is tedious and inefficient.

The GenValidity type class allows you to specify how to (efficiently) generate data of the given type to allow for easier and quicker testing. Just implementing genUnchecked already gives you access to genValid and genInvalid but writing custom implementations of these functions may speed up the generation of data.

For example, to generate primes, we don't have to consider even numbers other than 2. A more efficient implementation could then look as follows:

instance GenValidity Prime where
    genUnchecked = Prime <$> arbitrary
    genValid = Prime <$>
       (oneof
         [ pure 2
         , (\y -> 2 * y + 1) <$> (arbitrary `suchThat` (> 0) `suchThat` isPrime)
         ])

Typical examples of tests involving validity could look as follows:

it "succeeds when given valid input" $ do
    forAll genValid $ \input ->
        myFunction input `shouldSatisfy` isRight
it "produces valid output when it succeeds" $ do
    forAll genUnchecked $ \input ->
        case myFunction input of
            Nothing -> return () -- Can happen
            Just output -> output `shouldSatisfy` isValid

Synopsis

Documentation

class Validity a => GenValidity a where Source #

A class of types for which Validity-related values can be generated.

If you also write Arbitrary instances for GenValidity types, it may be best to simply write arbitrary = genValid.

Minimal complete definition

genUnchecked

Methods

genUnchecked :: Gen a Source #

Generate a truly arbitrary datum, this should cover all possible values in the type

genValid :: Gen a Source #

Generate a valid datum, this should cover all possible valid values in the type

The default implementation is as follows:

 genValid = genUnchecked `suchThat` isValid

To speed up testing, it may be a good idea to implement this yourself. If you do, make sure that it is possible to generate all possible valid data, otherwise your testing may not cover all cases.

genInvalid :: Gen a Source #

Generate an invalid datum, this should cover all possible invalid values

genInvalid = genUnchecked `suchThat` (not . isValid)

To speed up testing, it may be a good idea to implement this yourself. If you do, make sure that it is possible to generate all possible invalid data, otherwise your testing may not cover all cases.

Instances

GenValidity a => GenValidity [a] Source #

If we can generate values of a certain type, we can also generate lists of them. This instance ensures that genValid generates only lists of valid data and that genInvalid generates lists of data such that there is at least one value in there that does not satisfy isValid, the rest is unchecked.

GenValidity a => GenValidity (Maybe a) Source # 
(GenValidity a, GenValidity b) => GenValidity (a, b) Source # 

Methods

genUnchecked :: Gen (a, b) Source #

genValid :: Gen (a, b) Source #

genInvalid :: Gen (a, b) Source #

(GenValidity a, GenValidity b, GenValidity c) => GenValidity (a, b, c) Source # 

Methods

genUnchecked :: Gen (a, b, c) Source #

genValid :: Gen (a, b, c) Source #

genInvalid :: Gen (a, b, c) Source #

genListOf :: Gen a -> Gen [a] Source #

A version of listOf that takes size into account more accurately.