Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
- class Validity a => GenValid a where
- genValid :: Gen a
- shrinkValid :: a -> [a]
- genValidStructurally :: (Validity a, Generic a, GGenValid (Rep a)) => Gen a
- genValidStructurallyWithoutExtraChecking :: (Generic a, GGenValid (Rep a)) => Gen a
- shrinkValidStructurally :: (Validity a, Generic a, GValidRecursivelyShrink (Rep a), GValidSubterms (Rep a) a) => a -> [a]
- shrinkValidStructurallyWithoutExtraFiltering :: (Generic a, GValidRecursivelyShrink (Rep a), GValidSubterms (Rep a) a) => a -> [a]
- module Data.GenValidity.Utils
- genUtf16SurrogateCodePoint :: Gen Char
- genLineSeparator :: Gen Char
- genNonLineSeparator :: Gen Char
- genSingleLineString :: Gen String
- module Data.Validity
- class GGenValid f where
- class GValidRecursivelyShrink f where
- gValidRecursivelyShrink :: f a -> [f a]
- structurallyValidSubterms :: (Generic a, GValidSubterms (Rep a) a) => a -> [a]
- class GValidSubterms f a where
- gValidSubterms :: f a -> [a]
- class GValidSubtermsIncl f a where
- gValidSubtermsIncl :: f a -> [a]
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
Nothing
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.
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
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.
module Data.GenValidity.Utils
Helper functions for specific types
Char
String
Re-exports
module Data.Validity
The Generics magic
class GValidRecursivelyShrink f where Source #
gValidRecursivelyShrink :: f a -> [f a] Source #
Instances
GValidRecursivelyShrink (U1 :: Type -> Type) Source # | |
Defined in Data.GenValidity gValidRecursivelyShrink :: U1 a -> [U1 a] Source # | |
GValidRecursivelyShrink (V1 :: Type -> Type) Source # | |
Defined in Data.GenValidity gValidRecursivelyShrink :: V1 a -> [V1 a] Source # | |
(GValidRecursivelyShrink f, GValidRecursivelyShrink g) => GValidRecursivelyShrink (f :*: g) Source # | |
Defined in Data.GenValidity gValidRecursivelyShrink :: (f :*: g) a -> [(f :*: g) a] Source # | |
(GValidRecursivelyShrink f, GValidRecursivelyShrink g) => GValidRecursivelyShrink (f :+: g) Source # | |
Defined in Data.GenValidity gValidRecursivelyShrink :: (f :+: g) a -> [(f :+: g) a] Source # | |
GenValid a => GValidRecursivelyShrink (K1 i a :: Type -> Type) Source # | |
Defined in Data.GenValidity gValidRecursivelyShrink :: K1 i a a0 -> [K1 i a a0] Source # | |
GValidRecursivelyShrink f => GValidRecursivelyShrink (M1 i c f) Source # | |
Defined in Data.GenValidity 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 #
gValidSubterms :: f a -> [a] Source #
Instances
GValidSubterms (U1 :: Type -> Type) a Source # | |
Defined in Data.GenValidity gValidSubterms :: U1 a -> [a] Source # | |
GValidSubterms (V1 :: Type -> Type) a Source # | |
Defined in Data.GenValidity gValidSubterms :: V1 a -> [a] Source # | |
(GValidSubtermsIncl f a, GValidSubtermsIncl g a) => GValidSubterms (f :*: g) a Source # | |
Defined in Data.GenValidity gValidSubterms :: (f :*: g) a -> [a] Source # | |
(GValidSubtermsIncl f a, GValidSubtermsIncl g a) => GValidSubterms (f :+: g) a Source # | |
Defined in Data.GenValidity gValidSubterms :: (f :+: g) a -> [a] Source # | |
GValidSubterms (K1 i a :: Type -> Type) b Source # | |
Defined in Data.GenValidity gValidSubterms :: K1 i a b -> [b] Source # | |
GValidSubterms f a => GValidSubterms (M1 i c f) a Source # | |
Defined in Data.GenValidity gValidSubterms :: M1 i c f a -> [a] Source # |
class GValidSubtermsIncl f a where Source #
gValidSubtermsIncl :: f a -> [a] Source #
Instances
GValidSubtermsIncl (U1 :: Type -> Type) a Source # | |
Defined in Data.GenValidity gValidSubtermsIncl :: U1 a -> [a] Source # | |
GValidSubtermsIncl (V1 :: Type -> Type) a Source # | |
Defined in Data.GenValidity gValidSubtermsIncl :: V1 a -> [a] Source # | |
(GValidSubtermsIncl f a, GValidSubtermsIncl g a) => GValidSubtermsIncl (f :*: g) a Source # | |
Defined in Data.GenValidity gValidSubtermsIncl :: (f :*: g) a -> [a] Source # | |
(GValidSubtermsIncl f a, GValidSubtermsIncl g a) => GValidSubtermsIncl (f :+: g) a Source # | |
Defined in Data.GenValidity gValidSubtermsIncl :: (f :+: g) a -> [a] Source # | |
GValidSubtermsIncl (K1 i a :: Type -> Type) a Source # | |
Defined in Data.GenValidity gValidSubtermsIncl :: K1 i a a -> [a] Source # | |
GValidSubtermsIncl (K1 i a :: Type -> Type) b Source # | |
Defined in Data.GenValidity gValidSubtermsIncl :: K1 i a b -> [b] Source # | |
GValidSubtermsIncl f a => GValidSubtermsIncl (M1 i c f) a Source # | |
Defined in Data.GenValidity gValidSubtermsIncl :: M1 i c f a -> [a] Source # |