genvalidity-1.0.0.0: Testing utilities for the validity library
Safe HaskellNone
LanguageHaskell2010

Data.GenValidity

Description

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

To implement tests for this datatype, we would have to be able to generate both primes. We could do this with a generator like this one:

(Prime <$> 'arbitrary') `suchThat` isValid

However, this is tedious and inefficient, as well as quite naive (because arbitrary tends to use very naive generators).

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. The default implementation of GenValid already gives you a generator and shrinking function for free:

instance GenValid Prime

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 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
    forAllValid $ \input ->
        myFunction input `shouldSatisfy` isRight
it "produces valid output when it succeeds" $ do
    forAllValid $ \input ->
        case myFunction input of
            Nothing -> return () -- Can happen
            Just output -> output `shouldSatisfy` isValid

Definitely also look at the companion packages for more info on how to use this package.

Synopsis

Documentation

class Validity a => GenValid a where Source #

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

How to instantiate GenValid

Step 1: Try to instantiate GenValid without overriding any functions. It is possible that, if few values are valid or if validity checking is expensive, the resulting generator is too slow. In that case, go to Step 2.

Step 2: Consider using genValidStructurallyWithoutExtraChecking and shrinkValidStructurallyWithoutExtraFiltering to speed up generation. This only works if your type has a derived or trivial Validity instance.

Step 3: If that still is not fast enough, consider writing your own generator and shrinking function. Make sure to generate any possible valid value, but only valid values.

A note about Arbitrary

If you also write Arbitrary instances for GenValid types, it may be best to simply use

instance Arbitrary A where
  arbitrary = genValid
  shrink = shrinkValid

Minimal complete definition

Nothing

Methods

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 = genValidStructurally

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.

default genValid :: (Generic a, GGenValid (Rep a)) => Gen a Source #

shrinkValid :: a -> [a] Source #

Shrink a valid value.

The default implementation is as follows:

 shrinkValid = shrinkValidStructurally

It is important that this shrinking function only shrinks values to valid values. If shrinkValid ever shrinks a value to an invalid value, the test that is being shrunk for might fail for a different reason than for the reason that it originally failed. This would lead to very confusing error messages.

default shrinkValid :: (Generic a, GValidRecursivelyShrink (Rep a), GValidSubterms (Rep a) a) => a -> [a] Source #

Instances

Instances details
GenValid Bool Source # 
Instance details

Defined in Data.GenValidity

GenValid Char Source # 
Instance details

Defined in Data.GenValidity

GenValid Double Source # 
Instance details

Defined in Data.GenValidity

GenValid Float Source # 
Instance details

Defined in Data.GenValidity

GenValid Int Source # 
Instance details

Defined in Data.GenValidity

GenValid Int8 Source # 
Instance details

Defined in Data.GenValidity

GenValid Int16 Source # 
Instance details

Defined in Data.GenValidity

GenValid Int32 Source # 
Instance details

Defined in Data.GenValidity

GenValid Int64 Source # 
Instance details

Defined in Data.GenValidity

GenValid Integer Source # 
Instance details

Defined in Data.GenValidity

GenValid Natural Source # 
Instance details

Defined in Data.GenValidity

GenValid Ordering Source # 
Instance details

Defined in Data.GenValidity

GenValid Word Source # 
Instance details

Defined in Data.GenValidity

GenValid Word8 Source # 
Instance details

Defined in Data.GenValidity

GenValid Word16 Source # 
Instance details

Defined in Data.GenValidity

GenValid Word32 Source # 
Instance details

Defined in Data.GenValidity

GenValid Word64 Source # 
Instance details

Defined in Data.GenValidity

GenValid () Source # 
Instance details

Defined in Data.GenValidity

Methods

genValid :: Gen () Source #

shrinkValid :: () -> [()] Source #

GenValid a => GenValid [a] Source # 
Instance details

Defined in Data.GenValidity

Methods

genValid :: Gen [a] Source #

shrinkValid :: [a] -> [[a]] Source #

GenValid a => GenValid (Maybe a) Source # 
Instance details

Defined in Data.GenValidity

Methods

genValid :: Gen (Maybe a) Source #

shrinkValid :: Maybe a -> [Maybe a] Source #

(Integral a, Num a, Ord a, GenValid a) => GenValid (Ratio a) Source # 
Instance details

Defined in Data.GenValidity

Methods

genValid :: Gen (Ratio a) Source #

shrinkValid :: Ratio a -> [Ratio a] Source #

GenValid a => GenValid (NonEmpty a) Source # 
Instance details

Defined in Data.GenValidity

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

Defined in Data.GenValidity

Methods

genValid :: Gen (Either a b) Source #

shrinkValid :: Either a b -> [Either a b] Source #

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

Defined in Data.GenValidity

Methods

genValid :: Gen (a, b) Source #

shrinkValid :: (a, b) -> [(a, b)] Source #

HasResolution a => GenValid (Fixed a) Source # 
Instance details

Defined in Data.GenValidity

Methods

genValid :: Gen (Fixed a) Source #

shrinkValid :: Fixed a -> [Fixed a] Source #

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

Defined in Data.GenValidity

Methods

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

shrinkValid :: (a, b, c) -> [(a, b, c)] Source #

(GenValid a, GenValid b, GenValid c, GenValid d) => GenValid (a, b, c, d) Source # 
Instance details

Defined in Data.GenValidity

Methods

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

shrinkValid :: (a, b, c, d) -> [(a, b, c, d)] Source #

(GenValid a, GenValid b, GenValid c, GenValid d, GenValid e) => GenValid (a, b, c, d, e) Source # 
Instance details

Defined in Data.GenValidity

Methods

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

shrinkValid :: (a, b, c, d, e) -> [(a, b, c, d, e)] Source #

Helper functions

genValidStructurally :: (Validity a, Generic a, GGenValid (Rep a)) => Gen a Source #

Generate a valid value by generating all the sub parts using the Generic instance, and trying that until a valid value has been generated

genValidStructurally = genValidStructurallyWithoutExtraChecking `suchThat` isValid

This is probably the function that you are looking for. If you do use this function to override genValid, you probably also want to use shrinkValidStructurally to override shrinkValid.

genValidStructurallyWithoutExtraChecking :: (Generic a, GGenValid (Rep a)) => Gen a Source #

Generate a valid value by generating all the sub parts using the Generic instance,

This generator is _not_ guaranteed to generate a valid value.

This is probably _not_ the function that you are looking for when overriding genValid _unless_ the type in question has no _extra_ validity constraints on top of the validity of its sub parts.

shrinkValidStructurally :: (Validity a, Generic a, GValidRecursivelyShrink (Rep a), GValidSubterms (Rep a) a) => a -> [a] Source #

Shrink a term to any of its immediate valid subterms, and also recursively shrink all subterms, and then filtering out the results that are not valid.

shrinkValidStructurally = filter isValid . shrinkValidStructurallyWithoutExtraFiltering

This is probably the function that you are looking for.

shrinkValidStructurallyWithoutExtraFiltering :: (Generic a, GValidRecursivelyShrink (Rep a), GValidSubterms (Rep a) a) => a -> [a] Source #

Shrink a term to any of its immediate valid subterms, and also recursively shrink all subterms.

This shrinking function is _not_ guaranteed to shrink to valid values.

This is probably _not_ the function that you are looking for when overriding shrinkValid _unless_ the type in question has no _extra_ validity constraints on top of the validity of its sub parts.

Helper functions for specific types

Char

String

Re-exports

The Generics magic

class GGenValid f where Source #

Methods

gGenValid :: Gen (f a) Source #

Instances

Instances details
GGenValid (U1 :: Type -> Type) Source # 
Instance details

Defined in Data.GenValidity

Methods

gGenValid :: Gen (U1 a) Source #

GenValid a => GGenValid (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Data.GenValidity

Methods

gGenValid :: Gen (K1 i a a0) Source #

(GGenValid a, GGenValid b) => GGenValid (a :+: b) Source # 
Instance details

Defined in Data.GenValidity

Methods

gGenValid :: Gen ((a :+: b) a0) Source #

(GGenValid a, GGenValid b) => GGenValid (a :*: b) Source # 
Instance details

Defined in Data.GenValidity

Methods

gGenValid :: Gen ((a :*: b) a0) Source #

GGenValid a => GGenValid (M1 i c a) Source # 
Instance details

Defined in Data.GenValidity

Methods

gGenValid :: Gen (M1 i c a a0) Source #

class GValidRecursivelyShrink f where Source #

Methods

gValidRecursivelyShrink :: f a -> [f a] Source #

Instances

Instances details
GValidRecursivelyShrink (V1 :: Type -> Type) Source # 
Instance details

Defined in Data.GenValidity

Methods

gValidRecursivelyShrink :: V1 a -> [V1 a] Source #

GValidRecursivelyShrink (U1 :: Type -> Type) Source # 
Instance details

Defined in Data.GenValidity

Methods

gValidRecursivelyShrink :: U1 a -> [U1 a] Source #

GenValid a => GValidRecursivelyShrink (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Data.GenValidity

Methods

gValidRecursivelyShrink :: K1 i a a0 -> [K1 i a a0] Source #

(GValidRecursivelyShrink f, GValidRecursivelyShrink g) => GValidRecursivelyShrink (f :+: g) Source # 
Instance details

Defined in Data.GenValidity

Methods

gValidRecursivelyShrink :: (f :+: g) a -> [(f :+: g) a] Source #

(GValidRecursivelyShrink f, GValidRecursivelyShrink g) => GValidRecursivelyShrink (f :*: g) Source # 
Instance details

Defined in Data.GenValidity

Methods

gValidRecursivelyShrink :: (f :*: g) a -> [(f :*: g) a] Source #

GValidRecursivelyShrink f => GValidRecursivelyShrink (M1 i c f) Source # 
Instance details

Defined in Data.GenValidity

Methods

gValidRecursivelyShrink :: M1 i c f a -> [M1 i c f a] Source #

structurallyValidSubterms :: (Generic a, GValidSubterms (Rep a) a) => a -> [a] Source #

All immediate validSubterms of a term.

class GValidSubterms f a where Source #

Methods

gValidSubterms :: f a -> [a] Source #

Instances

Instances details
GValidSubterms (V1 :: Type -> Type) a Source # 
Instance details

Defined in Data.GenValidity

Methods

gValidSubterms :: V1 a -> [a] Source #

GValidSubterms (U1 :: Type -> Type) a Source # 
Instance details

Defined in Data.GenValidity

Methods

gValidSubterms :: U1 a -> [a] Source #

GValidSubterms (K1 i a :: Type -> Type) b Source # 
Instance details

Defined in Data.GenValidity

Methods

gValidSubterms :: K1 i a b -> [b] Source #

(GValidSubtermsIncl f a, GValidSubtermsIncl g a) => GValidSubterms (f :+: g) a Source # 
Instance details

Defined in Data.GenValidity

Methods

gValidSubterms :: (f :+: g) a -> [a] Source #

(GValidSubtermsIncl f a, GValidSubtermsIncl g a) => GValidSubterms (f :*: g) a Source # 
Instance details

Defined in Data.GenValidity

Methods

gValidSubterms :: (f :*: g) a -> [a] Source #

GValidSubterms f a => GValidSubterms (M1 i c f) a Source # 
Instance details

Defined in Data.GenValidity

Methods

gValidSubterms :: M1 i c f a -> [a] Source #

class GValidSubtermsIncl f a where Source #

Methods

gValidSubtermsIncl :: f a -> [a] Source #

Instances

Instances details
GValidSubtermsIncl (V1 :: Type -> Type) a Source # 
Instance details

Defined in Data.GenValidity

Methods

gValidSubtermsIncl :: V1 a -> [a] Source #

GValidSubtermsIncl (U1 :: Type -> Type) a Source # 
Instance details

Defined in Data.GenValidity

Methods

gValidSubtermsIncl :: U1 a -> [a] Source #

GValidSubtermsIncl (K1 i a :: Type -> Type) b Source # 
Instance details

Defined in Data.GenValidity

Methods

gValidSubtermsIncl :: K1 i a b -> [b] Source #

GValidSubtermsIncl (K1 i a :: Type -> Type) a Source # 
Instance details

Defined in Data.GenValidity

Methods

gValidSubtermsIncl :: K1 i a a -> [a] Source #

(GValidSubtermsIncl f a, GValidSubtermsIncl g a) => GValidSubtermsIncl (f :+: g) a Source # 
Instance details

Defined in Data.GenValidity

Methods

gValidSubtermsIncl :: (f :+: g) a -> [a] Source #

(GValidSubtermsIncl f a, GValidSubtermsIncl g a) => GValidSubtermsIncl (f :*: g) a Source # 
Instance details

Defined in Data.GenValidity

Methods

gValidSubtermsIncl :: (f :*: g) a -> [a] Source #

GValidSubtermsIncl f a => GValidSubtermsIncl (M1 i c f) a Source # 
Instance details

Defined in Data.GenValidity

Methods

gValidSubtermsIncl :: M1 i c f a -> [a] Source #