genvalidity-0.3.0.0: 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 GenValid type class allows you to specify how to (efficiently) generate valid data of the given type to allow for easier and quicker testing. Just instantiating GenUnchecked already gives you access to a default instance of 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 GenUnchecked Prime where
    genUnchecked = Prime <$> arbitrary
instance GenValid Prime where
    genValid = Prime <$>
       (oneof
         [ pure 2
         , ((\y -> 2 * abs y + 1) <$> arbitrary) `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, GenUnchecked a) => GenValid a where Source #

A class of types for which valid values can be generated.

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

Methods

genValid :: Gen a Source #

Instances

GenValid Bool Source # 
GenValid Char Source # 
GenValid Double Source # 
GenValid Float Source # 
GenValid Int Source # 

Methods

genValid :: Gen Int Source #

GenValid Integer Source # 
GenValid Ordering Source # 
GenValid Word Source # 
GenValid () Source # 

Methods

genValid :: Gen () Source #

GenValid a => GenValid [a] Source #

If we can generate values of a certain type, we can also generate lists of them.

Methods

genValid :: Gen [a] Source #

GenValid a => GenValid (Maybe a) Source # 

Methods

genValid :: Gen (Maybe a) Source #

(GenValid a, GenValid b) => GenValid (Either a b) Source # 

Methods

genValid :: Gen (Either a b) Source #

(GenValid a, GenValid b) => GenValid (a, b) Source # 

Methods

genValid :: Gen (a, b) Source #

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

Methods

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

class (Validity a, GenUnchecked a) => GenInvalid a where Source #

A class of types for which invalid values can be generated.

Methods

genInvalid :: Gen a Source #

Instances

GenInvalid Double Source #

Either NaN or Infinity.

GenInvalid Float Source #

Either NaN or Infinity.

GenInvalid a => GenInvalid [a] Source #

This instance ensures that the generated list contains at least one element that satisfies isInvalid. The rest is unchecked.

Methods

genInvalid :: Gen [a] Source #

GenInvalid a => GenInvalid (Maybe a) Source # 

Methods

genInvalid :: Gen (Maybe a) Source #

(GenInvalid a, GenInvalid b) => GenInvalid (Either a b) Source #

This instance ensures that the generated tupse contains at least one invalid element. The other element is unchecked.

Methods

genInvalid :: Gen (Either a b) Source #

(GenInvalid a, GenInvalid b) => GenInvalid (a, b) Source # 

Methods

genInvalid :: Gen (a, b) Source #

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

This instance ensures that the generated triple contains at least one invalid element. The other two are unchecked.

Methods

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

upTo :: Int -> Gen Int Source #

upTo generates an integer between 0 (inclusive) and n.

genSplit :: Int -> Gen (Int, Int) Source #

'genSplit a' generates a tuple '(b, c)' such that 'b + c' equals a.

genSplit3 :: Int -> Gen (Int, Int, Int) Source #

'genSplit a' generates a triple '(b, c, d)' such that 'b + c + d' equals a.

arbPartition :: Int -> Gen [Int] Source #

'arbPartition n' generates a list ls such that 'sum ls' equals n.

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

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