| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Test.Validity
Contents
- module Data.GenValidity
- data Proxy k t :: forall k. k -> * = Proxy
- arbitrarySpec :: (Typeable a, Show a, Validity a, Arbitrary a) => Proxy a -> Spec
- arbitraryGeneratesOnlyValid :: (Show a, Validity a, Arbitrary a) => Proxy a -> Property
- shrinkProducesOnlyValids :: (Show a, Validity a, Arbitrary a) => Proxy a -> Property
- genValiditySpec :: (Typeable a, Show a, GenValidity a) => Proxy a -> Spec
- genValidityValidGeneratesValid :: (Show a, GenValidity a) => Proxy a -> Property
- genValidityInvalidGeneratesInvalid :: (Show a, GenValidity a) => Proxy a -> Property
- relativeValiditySpec :: (Typeable a, Typeable b, Data a, Data b, Show a, Show b, GenValidity a, GenValidity b, GenRelativeValidity a b) => Proxy a -> Proxy b -> Spec
- relativeValidityImpliesValidA :: (Show a, Show b, GenValidity a, GenValidity b, RelativeValidity a b) => Proxy a -> Proxy b -> Property
- relativeValidityImpliesValidB :: (Show a, Show b, GenValidity a, GenValidity b, RelativeValidity a b) => Proxy a -> Proxy b -> Property
- genRelativeValiditySpec :: (Typeable a, Typeable b, Show a, Show b, GenValidity a, GenValidity b, RelativeValidity a b, GenRelativeValidity a b) => Proxy a -> Proxy b -> Spec
- genRelativeValidityValidGeneratesValid :: (Show a, Show b, GenValidity a, GenValidity b, RelativeValidity a b, GenRelativeValidity a b) => Proxy a -> Proxy b -> Property
- genRelativeValidityInvalidGeneratesInvalid :: (Show a, Show b, GenValidity a, GenValidity b, RelativeValidity a b, GenRelativeValidity a b) => Proxy a -> Proxy b -> Property
- producesValidsOnGen :: (Show a, Show b, Validity b) => (a -> b) -> Gen a -> Property
- alwaysProducesValid :: (Show a, Show b, GenValidity a, Validity b) => (a -> b) -> Property
- producesValidsOnValids :: (Show a, Show b, GenValidity a, Validity b) => (a -> b) -> Property
- producesValidsOnGens2 :: (Show a, Show b, Show c, Validity c) => (a -> b -> c) -> Gen a -> Gen b -> Property
- alwaysProducesValid2 :: (Show a, Show b, Show c, GenValidity a, GenValidity b, Validity c) => (a -> b -> c) -> Property
- producesValidsOnValids2 :: (Show a, Show b, Show c, GenValidity a, GenValidity b, Validity c) => (a -> b -> c) -> Property
- class CanFail f where
- succeedsOnGen :: (Show a, Show b, Show (f b), CanFail f) => (a -> f b) -> Gen a -> Property
- succeedsOnValidInput :: (Show a, Show b, Show (f b), GenValidity a, CanFail f) => (a -> f b) -> Property
- failsOnGen :: (Show a, Show b, Show (f b), CanFail f) => (a -> f b) -> Gen a -> Property
- failsOnInvalidInput :: (Show a, Show b, Show (f b), GenValidity a, CanFail f) => (a -> f b) -> Property
- validIfSucceedsOnGen :: (Show a, Show b, Show (f b), Validity b, CanFail f) => (a -> f b) -> Gen a -> Property
- validIfSucceeds :: (Show a, Show b, Show (f b), GenValidity a, Validity b, CanFail f) => (a -> f b) -> Property
- succeedsOnGens2 :: (Show a, Show b, Show c, Show (f c), CanFail f) => (a -> b -> f c) -> Gen a -> Gen b -> Property
- succeedsOnValidInput2 :: (Show a, Show b, Show c, Show (f c), GenValidity a, GenValidity b, CanFail f) => (a -> b -> f c) -> Property
- failsOnGens2 :: (Show a, Show b, Show c, Show (f c), CanFail f) => (a -> b -> f c) -> Gen a -> Gen b -> Property
- failsOnInvalidInput2 :: (Show a, Show b, Show c, Show (f c), GenValidity a, GenValidity b, CanFail f) => (a -> b -> f c) -> Property
- validIfSucceedsOnGens2 :: (Show a, Show b, Show c, Show (f c), Validity c, CanFail f) => (a -> b -> f c) -> Gen a -> Gen b -> Property
- validIfSucceeds2 :: (Show a, Show b, Show c, Show (f c), GenValidity a, GenValidity b, Validity c, CanFail f) => (a -> b -> f c) -> Property
Documentation
module Data.GenValidity
data Proxy k t :: forall k. k -> * #
A concrete, poly-kinded proxy type
Constructors
| Proxy |
Instances
| Monad (Proxy *) | |
| Functor (Proxy *) | |
| Applicative (Proxy *) | |
| Foldable (Proxy *) | |
| Generic1 (Proxy *) | |
| Eq1 (Proxy *) | Since: 4.9.0.0 |
| Ord1 (Proxy *) | Since: 4.9.0.0 |
| Read1 (Proxy *) | Since: 4.9.0.0 |
| Show1 (Proxy *) | Since: 4.9.0.0 |
| Alternative (Proxy *) | |
| MonadPlus (Proxy *) | |
| Bounded (Proxy k s) | |
| Enum (Proxy k s) | |
| Eq (Proxy k s) | |
| Data t => Data (Proxy * t) | |
| Ord (Proxy k s) | |
| Read (Proxy k s) | |
| Show (Proxy k s) | |
| Ix (Proxy k s) | |
| Generic (Proxy k t) | |
| Monoid (Proxy k s) | |
| type Rep1 (Proxy *) | |
| type Rep (Proxy k t) | |
Tests for Arbitrary instances involving Validity
arbitrarySpec :: (Typeable a, Show a, Validity a, Arbitrary a) => Proxy a -> Spec Source #
A Spec that specifies that arbitrary only generates data that
satisfy isValid and that shrink only produces data that satisfy
isValid.
Example usage:
arbitrarySpec (Proxy :: Proxy MyData)
arbitraryGeneratesOnlyValid :: (Show a, Validity a, Arbitrary a) => Proxy a -> Property Source #
arbitrary only generates valid data
shrinkProducesOnlyValids :: (Show a, Validity a, Arbitrary a) => Proxy a -> Property Source #
shrink only produces valid data
Tests for GenValidity instances
genValiditySpec :: (Typeable a, Show a, GenValidity a) => Proxy a -> Spec Source #
A Spec that specifies that genValid only generates valid data and that
genInvalid only generates invalid data.
In general it is a good idea to add this spec to your test suite if you
write a custom implementation of genValid or genInvalid.
Example usage:
genValiditySpec (Proxy :: Proxy MyData)
genValidityValidGeneratesValid :: (Show a, GenValidity a) => Proxy a -> Property Source #
genValid only generates valid data
genValidityInvalidGeneratesInvalid :: (Show a, GenValidity a) => Proxy a -> Property Source #
genValid only generates invalid data
Tests for RelativeValidity instances
relativeValiditySpec :: (Typeable a, Typeable b, Data a, Data b, Show a, Show b, GenValidity a, GenValidity b, GenRelativeValidity a b) => Proxy a -> Proxy b -> Spec Source #
A Spec that specifies that isValidFor implies isValid
In general it is a good idea to add this spec to your test suite if
the a in RelativeValidity a b also has a Validity instance.
Example usage:
relativeValiditySpec
(Proxy :: Proxy MyDataFor)
(Proxy :: Proxy MyOtherData)relativeValidityImpliesValidA :: (Show a, Show b, GenValidity a, GenValidity b, RelativeValidity a b) => Proxy a -> Proxy b -> Property Source #
isValidFor a b implies isValid a for all b
relativeValidityImpliesValidB :: (Show a, Show b, GenValidity a, GenValidity b, RelativeValidity a b) => Proxy a -> Proxy b -> Property Source #
isValidFor a b implies isValid b for all a
Tests for GenRelativeValidity instances
genRelativeValiditySpec :: (Typeable a, Typeable b, Show a, Show b, GenValidity a, GenValidity b, RelativeValidity a b, GenRelativeValidity a b) => Proxy a -> Proxy b -> Spec Source #
A Spec that specifies that genValidFor and genInvalidFor work as
intended.
In general it is a good idea to add this spec to your test suite if you
write a custom implementation of genValidFor or genInvalidFor.
Example usage:
relativeGenValiditySpec (proxy :: MyDataFor) (proxy :: MyOtherData)
genRelativeValidityValidGeneratesValid :: (Show a, Show b, GenValidity a, GenValidity b, RelativeValidity a b, GenRelativeValidity a b) => Proxy a -> Proxy b -> Property Source #
genValidFor b only generates values that satisfy isValidFor b
genRelativeValidityInvalidGeneratesInvalid :: (Show a, Show b, GenValidity a, GenValidity b, RelativeValidity a b, GenRelativeValidity a b) => Proxy a -> Proxy b -> Property Source #
genInvalidFor b only generates values that do not satisfy isValidFor b
Standard tests involving validity
producesValidsOnGen :: (Show a, Show b, Validity b) => (a -> b) -> Gen a -> Property Source #
The function produces valid output when the input is generated as specified by the given generator.
alwaysProducesValid :: (Show a, Show b, GenValidity a, Validity b) => (a -> b) -> Property Source #
The function produces valid output when the input is generated by
genUnchecked
producesValidsOnValids :: (Show a, Show b, GenValidity a, Validity b) => (a -> b) -> Property Source #
The function produces valid output when the input is generated by
genValid
producesValidsOnGens2 :: (Show a, Show b, Show c, Validity c) => (a -> b -> c) -> Gen a -> Gen b -> Property Source #
alwaysProducesValid2 :: (Show a, Show b, Show c, GenValidity a, GenValidity b, Validity c) => (a -> b -> c) -> Property Source #
producesValidsOnValids2 :: (Show a, Show b, Show c, GenValidity a, GenValidity b, Validity c) => (a -> b -> c) -> Property Source #
Standard tests involving functions that can fail
class CanFail f where Source #
A class of types that are the result of functions that can fail
You should not use this class yourself.
Minimal complete definition
succeedsOnGen :: (Show a, Show b, Show (f b), CanFail f) => (a -> f b) -> Gen a -> Property Source #
The function succeeds if the input is generated by the given generator
succeedsOnValidInput :: (Show a, Show b, Show (f b), GenValidity a, CanFail f) => (a -> f b) -> Property Source #
The function succeeds if the input is generated by genValid
failsOnGen :: (Show a, Show b, Show (f b), CanFail f) => (a -> f b) -> Gen a -> Property Source #
The function fails if the input is generated by the given generator
failsOnInvalidInput :: (Show a, Show b, Show (f b), GenValidity a, CanFail f) => (a -> f b) -> Property Source #
The function fails if the input is generated by genInvalid
validIfSucceedsOnGen :: (Show a, Show b, Show (f b), Validity b, CanFail f) => (a -> f b) -> Gen a -> Property Source #
The function produces output that satisfies isValid if it is given input
that is generated by the given generator.
validIfSucceeds :: (Show a, Show b, Show (f b), GenValidity a, Validity b, CanFail f) => (a -> f b) -> Property Source #
The function produces output that satisfies isValid if it is given input
that is generated by genUnchecked.
succeedsOnGens2 :: (Show a, Show b, Show c, Show (f c), CanFail f) => (a -> b -> f c) -> Gen a -> Gen b -> Property Source #
succeedsOnValidInput2 :: (Show a, Show b, Show c, Show (f c), GenValidity a, GenValidity b, CanFail f) => (a -> b -> f c) -> Property Source #
failsOnGens2 :: (Show a, Show b, Show c, Show (f c), CanFail f) => (a -> b -> f c) -> Gen a -> Gen b -> Property Source #
failsOnInvalidInput2 :: (Show a, Show b, Show c, Show (f c), GenValidity a, GenValidity b, CanFail f) => (a -> b -> f c) -> Property Source #
validIfSucceedsOnGens2 :: (Show a, Show b, Show c, Show (f c), Validity c, CanFail f) => (a -> b -> f c) -> Gen a -> Gen b -> Property Source #
validIfSucceeds2 :: (Show a, Show b, Show c, Show (f c), GenValidity a, GenValidity b, Validity c, CanFail f) => (a -> b -> f c) -> Property Source #