genvalidity-hspec-0.6.0.3: Standard spec's for GenValidity instances

Safe HaskellNone
LanguageHaskell2010

Test.Validity

Contents

Description

To use the Spec functions in this module, you will need TypeApplications.

Synopsis

Documentation

forAllUnchecked :: (Show a, GenUnchecked a, Testable prop) => (a -> prop) -> Property #

forAllValid :: (Show a, GenValid a, Testable prop) => (a -> prop) -> Property #

forAllInvalid :: (Show a, GenInvalid a, Testable prop) => (a -> prop) -> Property #

Tests for Arbitrary instances involving Validity

arbitrarySpec :: forall a. (Typeable a, Show a, Validity a, Arbitrary a) => Spec Source #

A Spec that specifies that arbitrary only generates data that satisfy isValid

Example usage:

arbitrarySpec @Int

arbitraryGeneratesOnlyValid :: forall a. (Show a, Validity a, Arbitrary a) => Property Source #

arbitrary only generates valid data

arbitraryGeneratesOnlyValid @Int

Tests for GenValidity instances

genValiditySpec :: forall a. (Typeable a, Show a, GenValid a, GenInvalid a) => Spec Source #

A spec for properties of GenValid and GenInvalid instances.

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 @Int

genValidSpec :: forall a. (Typeable a, Show a, GenValid a) => Spec Source #

A Spec that specifies that genValid only generates valid data.

Example usage:

genValidSpec @Int

genInvalidSpec :: forall a. (Typeable a, Show a, GenInvalid a) => Spec Source #

A Spec that specifies that genInvalid only generates invalid data.

Example usage:

genInvalidSpec @Double

genValidGeneratesValid :: forall a. (Show a, GenValid a) => Property Source #

genValid only generates valid data

genValidGeneratesValid @()
genValidGeneratesValid @Bool
genValidGeneratesValid @Ordering
genValidGeneratesValid @Char
genValidGeneratesValid @Int
genValidGeneratesValid @Float
genValidGeneratesValid @Double
genValidGeneratesValid @Integer
genValidGeneratesValid @(Maybe Int)
genValidGeneratesValid @[Int]

genGeneratesValid :: (Show a, Validity a) => Gen a -> (a -> [a]) -> Property #

The given generator generates only valid data points

genInvalidGeneratesInvalid :: forall a. (Show a, GenInvalid a) => Property Source #

genValid only generates invalid data

genInvalidGeneratesInvalid @Float
genInvalidGeneratesInvalid @Double
genInvalidGeneratesInvalid @(Maybe Double)
genInvalidGeneratesInvalid @[Double]

genGeneratesInvalid :: (Show a, Validity a) => Gen a -> (a -> [a]) -> Property #

The given generator generates only invalid data points

shrinkValidSpec :: forall a. (Show a, Typeable a, GenValid a) => Spec Source #

shrinkPreservesValidOnGenValid :: (Show a, GenValid a) => (a -> [a]) -> Property #

shrinkPreservesValidOnGenValid (:[])

shrinkPreservesInvalidOnGenInvalid :: (Show a, GenInvalid a) => (a -> [a]) -> Property #

shrinkPreservesInvalidOnGenInvalid (:[])

shrinkValidPreservesValid :: (Show a, GenValid a) => Gen a -> Property #

shrinkValidPreservesValid (pure 5)

shrinkInvalidPreservesInvalid :: (Show a, GenInvalid a) => Gen a -> Property #

shrinkInvalidPreservesInvalid (pure (1/0) :: Gen Double)

shrinkingStaysValid :: (Show a, Validity a) => Gen a -> (a -> [a]) -> Property #

shrinkingStaysValid (pure 5 :: Gen Double) (\d -> [d - 1, d - 2])

shrinkingStaysInvalid :: (Show a, Validity a) => Gen a -> (a -> [a]) -> Property #

shrinkingStaysInvalid (pure (1/0) :: Gen Double) (:[])

shrinkingPreserves :: Show a => Gen a -> (a -> [a]) -> (a -> Bool) -> Property #

shrinkingPreserves (pure 5) (:[]) (== 5)

Tests for RelativeValidity instances

relativeValiditySpec :: forall a b. (Typeable a, Typeable b, Show a, Show b, Validity a, Validity b, GenUnchecked a, GenUnchecked b, RelativeValidity a 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 and b in RelativeValidity a b also have a Validity instance.

Example usage:

relativeValiditySpec @MyDataFor @MyOtherData

relativeValidityImpliesValidA :: forall a b. (Show a, Show b, Validity a, GenUnchecked a, GenUnchecked b, RelativeValidity a b) => Property Source #

isValidFor a b implies isValid a for all b

relativeValidityImpliesValidB :: forall a b. (Show a, Show b, Validity b, GenUnchecked a, GenUnchecked b, RelativeValidity a b) => Property Source #

isValidFor a b implies isValid b for all a

Tests for GenRelativeValidity instances

genRelativeValiditySpec :: forall a b. (Typeable a, Typeable b, Show a, Show b, GenValid b, GenRelativeValid a b, GenRelativeInvalid a 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 @MyDataFor @MyOtherData

genRelativeValidGeneratesValid :: forall a b. (Show a, Show b, GenValid b, RelativeValidity a b, GenRelativeValid a b) => Property Source #

genValidFor b only generates values that satisfy isValidFor b

genRelativeInvalidGeneratesInvalid :: forall a b. (Show a, Show b, GenUnchecked b, RelativeValidity a b, GenRelativeInvalid a b) => Property Source #

genInvalidFor b only generates values that do not satisfy isValidFor b

Standard tests involving functions

Standard tests involving validity

producesValidsOnGen :: (Show a, Show b, Validity b) => (a -> b) -> Gen a -> (a -> [a]) -> Property #

The function produces valid output when the input is generated as specified by the given generator.

producesValidsOnValids :: (Show a, Show b, GenValid a, Validity b) => (a -> b) -> Property #

The function produces valid output when the input is generated by genValid

producesValid :: (Show a, Show b, GenUnchecked a, Validity b) => (a -> b) -> Property #

The function produces valid output when the input is generated by genUnchecked

producesValidsOnArbitrary :: (Show a, Show b, Arbitrary a, Validity b) => (a -> b) -> Property #

The function produces valid output when the input is generated by arbitrary

producesValidsOnGens2 :: (Show a, Show b, Show c, Validity c) => (a -> b -> c) -> Gen (a, b) -> ((a, b) -> [(a, b)]) -> Property #

producesValidsOnValids2 :: (Show a, Show b, Show c, GenValid a, GenValid b, Validity c) => (a -> b -> c) -> Property #

producesValid2 :: (Show a, Show b, Show c, GenUnchecked a, GenUnchecked b, Validity c) => (a -> b -> c) -> Property #

producesValidsOnArbitrary2 :: (Show a, Show b, Show c, Arbitrary a, Arbitrary b, Validity c) => (a -> b -> c) -> Property #

producesValidsOnGens3 :: (Show a, Show b, Show c, Show d, Validity d) => (a -> b -> c -> d) -> Gen (a, b, c) -> ((a, b, c) -> [(a, b, c)]) -> Property #

producesValidsOnValids3 :: (Show a, Show b, Show c, Show d, GenValid a, GenValid b, GenValid c, Validity d) => (a -> b -> c -> d) -> Property #

producesValid3 :: (Show a, Show b, Show c, Show d, GenUnchecked a, GenUnchecked b, GenUnchecked c, Validity d) => (a -> b -> c -> d) -> Property #

producesValidsOnArbitrary3 :: (Show a, Show b, Show c, Show d, Arbitrary a, Arbitrary b, Arbitrary c, Validity d) => (a -> b -> c -> d) -> Property #

Standard tests involving functions that can fail

class CanFail (f :: * -> *) where #

A class of types that are the result of functions that can fail

Minimal complete definition

hasFailed, resultIfSucceeded

Methods

hasFailed :: f a -> Bool #

resultIfSucceeded :: f a -> Maybe a #

Instances

succeedsOnGen :: (Show a, Show b, Show (f b), CanFail f) => (a -> f b) -> Gen a -> (a -> [a]) -> Property #

The function succeeds if the input is generated by the given generator

succeedsOnValid :: (Show a, Show b, Show (f b), GenValid a, CanFail f) => (a -> f b) -> Property #

The function succeeds if the input is generated by genValid

succeeds :: (Show a, Show b, Show (f b), GenUnchecked a, CanFail f) => (a -> f b) -> Property #

The function succeeds if the input is generated by genUnchecked

succeedsOnArbitrary :: (Show a, Show b, Show (f b), Arbitrary a, CanFail f) => (a -> f b) -> Property #

The function succeeds if the input is generated by arbitrary

succeedsOnGens2 :: (Show a, Show b, Show c, Show (f c), CanFail f) => (a -> b -> f c) -> Gen (a, b) -> ((a, b) -> [(a, b)]) -> Property #

succeedsOnValids2 :: (Show a, Show b, Show c, Show (f c), GenValid a, GenValid b, CanFail f) => (a -> b -> f c) -> Property #

succeeds2 :: (Show a, Show b, Show c, Show (f c), GenUnchecked a, GenUnchecked b, CanFail f) => (a -> b -> f c) -> Property #

succeedsOnArbitrary2 :: (Show a, Show b, Show c, Show (f c), Arbitrary a, Arbitrary b, CanFail f) => (a -> b -> f c) -> Property #

failsOnGen :: (Show a, Show b, Show (f b), CanFail f) => (a -> f b) -> Gen a -> (a -> [a]) -> Property #

The function fails if the input is generated by the given generator

failsOnInvalid :: (Show a, Show b, Show (f b), GenInvalid a, CanFail f) => (a -> f b) -> Property #

The function fails if the input is generated by genInvalid

failsOnGens2 :: (Show a, Show b, Show c, Show (f c), CanFail f) => (a -> b -> f c) -> Gen a -> (a -> [a]) -> Gen b -> (b -> [b]) -> Property #

failsOnInvalid2 :: (Show a, Show b, Show c, Show (f c), GenInvalid a, GenInvalid b, CanFail f) => (a -> b -> f c) -> Property #

validIfSucceedsOnGen :: (Show a, Show b, Show (f b), Validity b, CanFail f) => (a -> f b) -> Gen a -> (a -> [a]) -> Property #

The function produces output that satisfies isValid if it is given input that is generated by the given generator.

validIfSucceedsOnValid :: (Show a, Show b, Show (f b), GenValid a, Validity b, CanFail f) => (a -> f b) -> Property #

The function produces output that satisfies isValid if it is given input that is generated by arbitrary.

validIfSucceedsOnArbitrary :: (Show a, Show b, Show (f b), Arbitrary a, Validity b, CanFail f) => (a -> f b) -> Property #

The function produces output that satisfies isValid if it is given input that is generated by arbitrary.

validIfSucceeds :: (Show a, Show b, Show (f b), GenUnchecked a, Validity b, CanFail f) => (a -> f b) -> Property #

The function produces output that satisfies isValid if it is given input that is generated by genUnchecked.

validIfSucceedsOnGens2 :: (Show a, Show b, Show c, Show (f c), Validity c, CanFail f) => (a -> b -> f c) -> Gen (a, b) -> ((a, b) -> [(a, b)]) -> Property #

validIfSucceedsOnValids2 :: (Show a, Show b, Show c, Show (f c), GenValid a, GenValid b, Validity c, CanFail f) => (a -> b -> f c) -> Property #

validIfSucceeds2 :: (Show a, Show b, Show c, Show (f c), GenUnchecked a, GenUnchecked b, Validity c, CanFail f) => (a -> b -> f c) -> Property #

validIfSucceedsOnArbitrary2 :: (Show a, Show b, Show c, Show (f c), Arbitrary a, Arbitrary b, Validity c, CanFail f) => (a -> b -> f c) -> Property #

validIfSucceedsOnGens3 :: (Show a, Show b, Show c, Show d, Show (f d), Validity d, CanFail f) => (a -> b -> c -> f d) -> Gen (a, b, c) -> ((a, b, c) -> [(a, b, c)]) -> Property #

validIfSucceedsOnValids3 :: (Show a, Show b, Show c, Show d, Show (f d), GenValid a, GenValid b, GenValid c, Validity d, CanFail f) => (a -> b -> c -> f d) -> Property #

validIfSucceeds3 :: (Show a, Show b, Show c, Show d, Show (f d), GenUnchecked a, GenUnchecked b, GenUnchecked c, Validity d, CanFail f) => (a -> b -> c -> f d) -> Property #

validIfSucceedsOnArbitrary3 :: (Show a, Show b, Show c, Show d, Show (f d), Arbitrary a, Arbitrary b, Arbitrary c, Validity d, CanFail f) => (a -> b -> c -> f d) -> Property #

Standard tests involving equivalence of functions

Simple functions

One argument

equivalentOnGen :: (Show a, Eq a, Show b, Eq b) => (a -> b) -> (a -> b) -> Gen a -> (a -> [a]) -> Property #

equivalentOnValid :: (Show a, Eq a, GenValid a, Show b, Eq b) => (a -> b) -> (a -> b) -> Property #

equivalent :: (Show a, Eq a, GenUnchecked a, Show b, Eq b) => (a -> b) -> (a -> b) -> Property #

equivalentOnArbitrary :: (Show a, Eq a, Arbitrary a, Show b, Eq b) => (a -> b) -> (a -> b) -> Property #

equivalentOnArbitrary ((* 2) . (+ 1)) ((+ 2) . (* 2) :: Int -> Int)

Two arguments

equivalentOnGens2 :: (Show a, Show b, Show c, Eq c) => (a -> b -> c) -> (a -> b -> c) -> Gen (a, b) -> ((a, b) -> [(a, b)]) -> Property #

equivalentOnValids2 :: (Show a, GenValid a, Show b, GenValid b, Show c, Eq c) => (a -> b -> c) -> (a -> b -> c) -> Property #

equivalent2 :: (Show a, GenUnchecked a, Show b, GenUnchecked b, Show c, Eq c) => (a -> b -> c) -> (a -> b -> c) -> Property #

equivalentOnArbitrary2 :: (Show a, Arbitrary a, Show b, Arbitrary b, Show c, Eq c) => (a -> b -> c) -> (a -> b -> c) -> Property #

equivalentOnArbitrary2 (+) ((+) :: Int -> Int -> Int)

Three arguments

equivalentOnGens3 :: (Show a, Show b, Show c, Show d, Eq d) => (a -> b -> c -> d) -> (a -> b -> c -> d) -> Gen (a, b, c) -> ((a, b, c) -> [(a, b, c)]) -> Property #

equivalentOnValids3 :: (Show a, GenValid a, Show b, GenValid b, Show c, GenValid c, Show d, Eq d) => (a -> b -> c -> d) -> (a -> b -> c -> d) -> Property #

equivalent3 :: (Show a, GenUnchecked a, Show b, GenUnchecked b, Show c, GenUnchecked c, Show d, Eq d) => (a -> b -> c -> d) -> (a -> b -> c -> d) -> Property #

equivalentOnArbitrary3 :: (Show a, Arbitrary a, Show b, Arbitrary b, Show c, Arbitrary c, Show d, Eq d) => (a -> b -> c -> d) -> (a -> b -> c -> d) -> Property #

First function can fail

One argument

equivalentWhenFirstSucceedsOnGen :: (Show a, Eq a, Show b, Eq b, CanFail f) => (a -> f b) -> (a -> b) -> Gen a -> (a -> [a]) -> Property #

equivalentWhenFirstSucceedsOnValid :: (Show a, Eq a, GenValid a, Show b, Eq b, CanFail f) => (a -> f b) -> (a -> b) -> Property #

equivalentWhenFirstSucceeds :: (Show a, Eq a, GenUnchecked a, Show b, Eq b, CanFail f) => (a -> f b) -> (a -> b) -> Property #

equivalentWhenFirstSucceedsOnArbitrary :: (Show a, Eq a, Arbitrary a, Show b, Eq b, CanFail f) => (a -> f b) -> (a -> b) -> Property #

Two arguments

equivalentWhenFirstSucceedsOnGens2 :: (Show a, Eq a, Show b, Eq b, Show c, Eq c, CanFail f) => (a -> b -> f c) -> (a -> b -> c) -> Gen (a, b) -> ((a, b) -> [(a, b)]) -> Property #

equivalentWhenFirstSucceedsOnValids2 :: (Show a, Eq a, GenValid a, Show b, Eq b, GenValid b, Show c, Eq c, CanFail f) => (a -> b -> f c) -> (a -> b -> c) -> Property #

equivalentWhenFirstSucceeds2 :: (Show a, Eq a, GenUnchecked a, Show b, Eq b, GenUnchecked b, Show c, Eq c, CanFail f) => (a -> b -> f c) -> (a -> b -> c) -> Property #

equivalentWhenFirstSucceedsOnArbitrary2 :: (Show a, Eq a, Arbitrary a, Show b, Eq b, Arbitrary b, Show c, Eq c, CanFail f) => (a -> b -> f c) -> (a -> b -> c) -> Property #

Second function can fail

One argument

equivalentWhenSecondSucceedsOnGen :: (Show a, Eq a, Show b, Eq b, CanFail f) => (a -> b) -> (a -> f b) -> Gen a -> (a -> [a]) -> Property #

equivalentWhenSecondSucceedsOnValid :: (Show a, Eq a, GenValid a, Show b, Eq b, CanFail f) => (a -> b) -> (a -> f b) -> Property #

equivalentWhenSecondSucceeds :: (Show a, Eq a, GenUnchecked a, Show b, Eq b, CanFail f) => (a -> b) -> (a -> f b) -> Property #

equivalentWhenSecondSucceedsOnArbitrary :: (Show a, Eq a, Arbitrary a, Show b, Eq b, CanFail f) => (a -> b) -> (a -> f b) -> Property #

Two arguments

equivalentWhenSecondSucceedsOnGens2 :: (Show a, Eq a, Show b, Eq b, Show c, Eq c, CanFail f) => (a -> b -> c) -> (a -> b -> f c) -> Gen (a, b) -> ((a, b) -> [(a, b)]) -> Property #

equivalentWhenSecondSucceedsOnValids2 :: (Show a, Eq a, GenValid a, Show b, Eq b, GenValid b, Show c, Eq c, CanFail f) => (a -> b -> c) -> (a -> b -> f c) -> Property #

equivalentWhenSecondSucceeds2 :: (Show a, Eq a, GenUnchecked a, Show b, Eq b, GenUnchecked b, Show c, Eq c, CanFail f) => (a -> b -> c) -> (a -> b -> f c) -> Property #

equivalentWhenSecondSucceedsOnArbitrary2 :: (Show a, Eq a, Arbitrary a, Show b, Eq b, Arbitrary b, Show c, Eq c, CanFail f) => (a -> b -> c) -> (a -> b -> f c) -> Property #

Both functions can fail

One argument

equivalentWhenSucceedOnGen :: (Show a, Eq a, Show b, Eq b, CanFail f) => (a -> f b) -> (a -> f b) -> Gen a -> (a -> [a]) -> Property #

equivalentWhenSucceedOnValid :: (Show a, Eq a, GenValid a, Show b, Eq b, CanFail f) => (a -> f b) -> (a -> f b) -> Property #

equivalentWhenSucceed :: (Show a, Eq a, GenUnchecked a, Show b, Eq b, CanFail f) => (a -> f b) -> (a -> f b) -> Property #

equivalentWhenSucceedOnArbitrary :: (Show a, Eq a, Arbitrary a, Show b, Eq b, CanFail f) => (a -> f b) -> (a -> f b) -> Property #

Two arguments

equivalentWhenSucceedOnGens2 :: (Show a, Eq a, Show b, Eq b, Show c, Eq c, CanFail f) => (a -> b -> f c) -> (a -> b -> f c) -> Gen (a, b) -> ((a, b) -> [(a, b)]) -> Property #

equivalentWhenSucceedOnValids2 :: (Show a, Eq a, GenValid a, Show b, Eq b, GenValid b, Show c, Eq c, CanFail f) => (a -> b -> f c) -> (a -> b -> f c) -> Property #

equivalentWhenSucceed2 :: (Show a, Eq a, GenUnchecked a, Show b, Eq b, GenUnchecked b, Show c, Eq c, CanFail f) => (a -> b -> f c) -> (a -> b -> f c) -> Property #

equivalentWhenSucceedOnArbitrary2 :: (Show a, Eq a, Arbitrary a, Show b, Eq b, Arbitrary b, Show c, Eq c, CanFail f) => (a -> b -> f c) -> (a -> b -> f c) -> Property #

Standard tests involving inverse functions

inverseFunctionsOnGen :: (Show a, Eq a) => (a -> b) -> (b -> a) -> Gen a -> (a -> [a]) -> Property #

inverseFunctionsOnValid :: (Show a, Eq a, GenValid a) => (a -> b) -> (b -> a) -> Property #

inverseFunctions :: (Show a, Eq a, GenUnchecked a) => (a -> b) -> (b -> a) -> Property #

inverseFunctionsOnArbitrary :: (Show a, Eq a, Arbitrary a) => (a -> b) -> (b -> a) -> Property #

id is its own inverse function for every type: prop> inverseFunctionsOnArbitrary id (id :: Int -> Int)

inverseFunctionsIfFirstSucceedsOnGen :: (Show a, Eq a, CanFail f) => (a -> f b) -> (b -> a) -> Gen a -> (a -> [a]) -> Property #

inverseFunctionsIfFirstSucceedsOnValid :: (Show a, Eq a, GenValid a, CanFail f) => (a -> f b) -> (b -> a) -> Property #

inverseFunctionsIfFirstSucceeds :: (Show a, Eq a, GenUnchecked a, CanFail f) => (a -> f b) -> (b -> a) -> Property #

inverseFunctionsIfFirstSucceedsOnArbitrary :: (Show a, Eq a, Arbitrary a, CanFail f) => (a -> f b) -> (b -> a) -> Property #

inverseFunctionsIfSecondSucceedsOnGen :: (Show a, Eq a, CanFail f) => (a -> b) -> (b -> f a) -> Gen a -> (a -> [a]) -> Property #

inverseFunctionsIfSecondSucceedsOnValid :: (Show a, Eq a, GenValid a, CanFail f) => (a -> b) -> (b -> f a) -> Property #

inverseFunctionsIfSecondSucceeds :: (Show a, Eq a, GenUnchecked a, CanFail f) => (a -> b) -> (b -> f a) -> Property #

inverseFunctionsIfSecondSucceedsOnArbitrary :: (Show a, Eq a, Arbitrary a, CanFail f) => (a -> b) -> (b -> f a) -> Property #

inverseFunctionsIfSucceedOnGen :: (Show a, Eq a, CanFail f, CanFail g) => (a -> f b) -> (b -> g a) -> Gen a -> (a -> [a]) -> Property #

inverseFunctionsIfSucceedOnValid :: (Show a, Eq a, GenValid a, CanFail f, CanFail g) => (a -> f b) -> (b -> g a) -> Property #

inverseFunctionsIfSucceed :: (Show a, Eq a, GenUnchecked a, CanFail f, CanFail g) => (a -> f b) -> (b -> g a) -> Property #

inverseFunctionsIfSucceedOnArbitrary :: (Show a, Eq a, Arbitrary a, CanFail f, CanFail g) => (a -> f b) -> (b -> g a) -> Property #

Properties involving idempotence

idempotentOnGen :: (Show a, Eq a) => (a -> a) -> Gen a -> (a -> [a]) -> Property #

idempotentOnValid :: (Show a, Eq a, GenValid a) => (a -> a) -> Property #

idempotent :: (Show a, Eq a, GenUnchecked a) => (a -> a) -> Property #

idempotentOnArbitrary :: (Show a, Eq a, Arbitrary a) => (a -> a) -> Property #

id is idempotent for any type:

idempotentOnArbitrary (id :: Int -> Int)

const, given any input, is idempotent for any type as well:

\int -> idempotentOnArbitrary (const int :: Int -> Int)

Properties of relations

Reflexivity

reflexiveOnElem #

Arguments

:: (a -> a -> Bool)

A relation

-> a

An element

-> Bool 

\[ Reflexive(\prec) \quad\equiv\quad \forall a: (a \prec a) \]

reflexivityOnGen :: Show a => (a -> a -> Bool) -> Gen a -> (a -> [a]) -> Property #

reflexivityOnValid :: (Show a, GenValid a) => (a -> a -> Bool) -> Property #

reflexivityOnValid ((<=) :: Double -> Double -> Bool)
reflexivityOnValid ((==) :: Double -> Double -> Bool)
reflexivityOnValid ((>=) :: Double -> Double -> Bool)
reflexivityOnValid (Data.List.isPrefixOf :: [Double] -> [Double] -> Bool)
reflexivityOnValid (Data.List.isSuffixOf :: [Double] -> [Double] -> Bool)
reflexivityOnValid (Data.List.isInfixOf :: [Double] -> [Double] -> Bool)

reflexivity :: (Show a, GenUnchecked a) => (a -> a -> Bool) -> Property #

reflexivity ((<=) :: Int -> Int -> Bool)
reflexivity ((==) :: Int -> Int -> Bool)
reflexivity ((>=) :: Int -> Int -> Bool)
reflexivity (Data.List.isPrefixOf :: [Int] -> [Int] -> Bool)
reflexivity (Data.List.isSuffixOf :: [Int] -> [Int] -> Bool)
reflexivity (Data.List.isInfixOf :: [Int] -> [Int] -> Bool)

reflexivityOnArbitrary :: (Show a, Arbitrary a) => (a -> a -> Bool) -> Property #

reflexivityOnArbitrary ((<=) :: Int -> Int -> Bool)
reflexivityOnArbitrary ((==) :: Int -> Int -> Bool)
reflexivityOnArbitrary ((>=) :: Int -> Int -> Bool)
reflexivityOnArbitrary (Data.List.isPrefixOf :: [Int] -> [Int] -> Bool)
reflexivityOnArbitrary (Data.List.isSuffixOf :: [Int] -> [Int] -> Bool)
reflexivityOnArbitrary (Data.List.isInfixOf :: [Int] -> [Int] -> Bool)

Transitivity

transitiveOnElems #

Arguments

:: (a -> a -> Bool)

A relation

-> a 
-> a 
-> a

Three elements

-> Bool 

\[ Transitive(\prec) \quad\equiv\quad \forall a, b, c: ((a \prec b) \wedge (b \prec c)) \Rightarrow (a \prec c) \]

transitivityOnGens :: Show a => (a -> a -> Bool) -> Gen (a, a, a) -> (a -> [a]) -> Property #

transitivityOnValid :: (Show a, GenValid a) => (a -> a -> Bool) -> Property #

transitivityOnValid ((>) :: Double -> Double -> Bool)
transitivityOnValid ((>=) :: Double -> Double -> Bool)
transitivityOnValid ((==) :: Double -> Double -> Bool)
transitivityOnValid ((<=) :: Double -> Double -> Bool)
transitivityOnValid ((<) :: Double -> Double -> Bool)
transitivityOnValid (Data.List.isPrefixOf :: [Double] -> [Double] -> Bool)
transitivityOnValid (Data.List.isSuffixOf :: [Double] -> [Double] -> Bool)
transitivityOnValid (Data.List.isInfixOf :: [Double] -> [Double] -> Bool)

transitivity :: (Show a, GenUnchecked a) => (a -> a -> Bool) -> Property #

transitivity ((>) :: Int -> Int -> Bool)
transitivity ((>=) :: Int -> Int -> Bool)
transitivity ((==) :: Int -> Int -> Bool)
transitivity ((<=) :: Int -> Int -> Bool)
transitivity ((<) :: Int -> Int -> Bool)
transitivity (Data.List.isPrefixOf :: [Int] -> [Int] -> Bool)
transitivity (Data.List.isSuffixOf :: [Int] -> [Int] -> Bool)
transitivity (Data.List.isInfixOf :: [Int] -> [Int] -> Bool)

transitivityOnArbitrary :: (Show a, Arbitrary a) => (a -> a -> Bool) -> Property #

transitivityOnArbitrary ((>) :: Int -> Int -> Bool)
transitivityOnArbitrary ((>=) :: Int -> Int -> Bool)
transitivityOnArbitrary ((==) :: Int -> Int -> Bool)
transitivityOnArbitrary ((<=) :: Int -> Int -> Bool)
transitivityOnArbitrary ((<) :: Int -> Int -> Bool)
transitivityOnArbitrary (Data.List.isPrefixOf :: [Int] -> [Int] -> Bool)
transitivityOnArbitrary (Data.List.isSuffixOf :: [Int] -> [Int] -> Bool)
transitivityOnArbitrary (Data.List.isInfixOf :: [Int] -> [Int] -> Bool)

Antisymmetry

antisymmetricOnElemsWithEquality #

Arguments

:: (a -> a -> Bool)

A relation

-> (a -> a -> Bool)

An equivalence relation

-> a 
-> a

Two elements

-> Bool 

\[ Antisymmetric(\prec, \doteq) \quad\equiv\quad \forall a, b: ((a \prec b) \wedge (b \prec a)) \Rightarrow (a \doteq b) \]

antisymmetryOnGensWithEquality :: Show a => (a -> a -> Bool) -> Gen (a, a) -> (a -> a -> Bool) -> (a -> [a]) -> Property #

antisymmetryOnGens :: (Show a, Eq a) => (a -> a -> Bool) -> Gen (a, a) -> (a -> [a]) -> Property #

antisymmetryOnValid :: (Show a, Eq a, GenValid a) => (a -> a -> Bool) -> Property #

antisymmetryOnValid ((>) :: Double -> Double -> Bool)
antisymmetryOnValid ((>=) :: Double -> Double -> Bool)
antisymmetryOnValid ((<=) :: Double -> Double -> Bool)
antisymmetryOnValid ((<) :: Double -> Double -> Bool)
antisymmetryOnValid (Data.List.isPrefixOf :: [Double] -> [Double] -> Bool)
antisymmetryOnValid (Data.List.isSuffixOf :: [Double] -> [Double] -> Bool)
antisymmetryOnValid (Data.List.isInfixOf :: [Double] -> [Double] -> Bool)

antisymmetry :: (Show a, Eq a, GenUnchecked a) => (a -> a -> Bool) -> Property #

antisymmetry ((>) :: Int -> Int -> Bool)
antisymmetry ((>=) :: Int -> Int -> Bool)
antisymmetry ((<=) :: Int -> Int -> Bool)
antisymmetry ((<) :: Int -> Int -> Bool)
antisymmetry (Data.List.isPrefixOf :: [Int] -> [Int] -> Bool)
antisymmetry (Data.List.isSuffixOf :: [Int] -> [Int] -> Bool)
antisymmetry (Data.List.isInfixOf :: [Int] -> [Int] -> Bool)
antisymmetry ((\x y -> even x && odd y) :: Int -> Int -> Bool)

antisymmetryOnArbitrary :: (Show a, Eq a, Arbitrary a) => (a -> a -> Bool) -> Property #

antisymmetryOnArbitrary ((>) :: Int -> Int -> Bool)
antisymmetryOnArbitrary ((>=) :: Int -> Int -> Bool)
antisymmetryOnArbitrary ((<=) :: Int -> Int -> Bool)
antisymmetryOnArbitrary ((<) :: Int -> Int -> Bool)
antisymmetryOnArbitrary (Data.List.isPrefixOf :: [Int] -> [Int] -> Bool)
antisymmetryOnArbitrary (Data.List.isSuffixOf :: [Int] -> [Int] -> Bool)
antisymmetryOnArbitrary (Data.List.isInfixOf :: [Int] -> [Int] -> Bool)
antisymmetryOnArbitrary ((\x y -> even x && odd y) :: Int -> Int -> Bool)

Antireflexivity

antireflexiveOnElem #

Arguments

:: (a -> a -> Bool)

A relation

-> a

An element

-> Bool 

\[ Antireflexive(\prec) \quad\equiv\quad \forall a: \neg (a \prec a) \]

antireflexivityOnGen :: Show a => (a -> a -> Bool) -> Gen a -> (a -> [a]) -> Property #

antireflexivityOnValid :: (Show a, GenValid a) => (a -> a -> Bool) -> Property #

antireflexivityOnValid ((<) :: Double -> Double -> Bool)
antireflexivityOnValid ((/=) :: Double -> Double -> Bool)
antireflexivityOnValid ((>) :: Double -> Double -> Bool)

antireflexivity :: (Show a, GenUnchecked a) => (a -> a -> Bool) -> Property #

antireflexivity ((<) :: Int -> Int -> Bool)
antireflexivity ((/=) :: Int -> Int -> Bool)
antireflexivity ((>) :: Int -> Int -> Bool)

antireflexivityOnArbitrary :: (Show a, Arbitrary a) => (a -> a -> Bool) -> Property #

antireflexivityOnArbitrary ((<) :: Int -> Int -> Bool)
antireflexivityOnArbitrary ((/=) :: Int -> Int -> Bool)
antireflexivityOnArbitrary ((>) :: Int -> Int -> Bool)

Symmetry

symmetricOnElems #

Arguments

:: (a -> a -> Bool)

A relation

-> a 
-> a

Two elements

-> Bool 

\[ Symmetric(\prec) \quad\equiv\quad \forall a, b: (a \prec b) \Leftrightarrow (b \prec a) \]

symmetryOnGens :: Show a => (a -> a -> Bool) -> Gen (a, a) -> (a -> [a]) -> Property #

symmetryOnValid :: (Show a, GenValid a) => (a -> a -> Bool) -> Property #

symmetryOnValid ((==) :: Double -> Double -> Bool)
symmetryOnValid ((/=) :: Double -> Double -> Bool)

symmetry :: (Show a, GenUnchecked a) => (a -> a -> Bool) -> Property #

symmetry ((==) :: Int -> Int -> Bool)
symmetry ((/=) :: Int -> Int -> Bool)

symmetryOnArbitrary :: (Show a, Arbitrary a) => (a -> a -> Bool) -> Property #

symmetryOnArbitrary ((==) :: Int -> Int -> Bool)
symmetryOnArbitrary ((/=) :: Int -> Int -> Bool)

Properties of operations

Identity element

Left Identity

leftIdentityOnElemWithEquality #

Arguments

:: (b -> a -> a)

A binary operation

-> (a -> a -> Bool)

An equality

-> b

A candidate left-identity

-> a

An element

-> Bool 

\[ LeftIdentity(\star, \doteq, b) \quad\equiv\quad \forall a: (b \star a) \doteq a \]

leftIdentityOnGenWithEquality #

Arguments

:: Show a 
=> (b -> a -> a)

A binary operation

-> (a -> a -> Bool)

An equality

-> b

A candidate left-identity

-> Gen a 
-> (a -> [a]) 
-> Property 

leftIdentityOnGen #

Arguments

:: (Show a, Eq a) 
=> (b -> a -> a)

A binary operation

-> b

A candidate left-identity

-> Gen a 
-> (a -> [a]) 
-> Property 

leftIdentityOnValid :: (Show a, Eq a, GenValid a) => (b -> a -> a) -> b -> Property #

leftIdentityOnValid (flip ((^) :: Double -> Int -> Double)) 1

leftIdentity :: (Show a, Eq a, GenUnchecked a) => (b -> a -> a) -> b -> Property #

leftIdentity (flip ((^) :: Int -> Int -> Int)) 1

leftIdentityOnArbitrary :: (Show a, Eq a, Arbitrary a) => (b -> a -> a) -> b -> Property #

leftIdentityOnArbitrary (flip ((^) :: Int -> Int -> Int)) 1

Right Identity

rightIdentityOnElemWithEquality #

Arguments

:: (a -> b -> a)

A binary operation

-> (a -> a -> Bool)

An equality

-> b

A candidate right-identity

-> a

An element

-> Bool 

\[ RightIdentity(\star, \doteq, b) \quad\equiv\quad \forall a: (a \star b) \doteq a \]

rightIdentityOnGenWithEquality #

Arguments

:: Show a 
=> (a -> b -> a)

A binary operation

-> (a -> a -> Bool)

An equality

-> b

A candidate right-identity

-> Gen a 
-> (a -> [a]) 
-> Property 

rightIdentityOnGen #

Arguments

:: (Show a, Eq a) 
=> (a -> b -> a)

A binary operation

-> b

A candidate right-identity

-> Gen a 
-> (a -> [a]) 
-> Property 

rightIdentityOnValid :: (Show a, Eq a, GenValid a) => (a -> b -> a) -> b -> Property #

rightIdentityOnValid ((^) :: Double -> Int -> Double) 1

rightIdentity :: (Show a, Eq a, GenUnchecked a) => (a -> b -> a) -> b -> Property #

rightIdentity ((^) :: Int -> Int -> Int) 1

rightIdentityOnArbitrary :: (Show a, Eq a, Arbitrary a) => (a -> b -> a) -> b -> Property #

rightIdentityOnArbitrary ((^) :: Int -> Int -> Int) 1

Identity

identityOnGen :: (Show a, Eq a) => (a -> a -> a) -> a -> Gen a -> (a -> [a]) -> Property #

\[ Identity(\star, \doteq, b) \quad\equiv\quad LeftIdentity(\star, \doteq, b) \wedge RightIdentity(\star, \doteq, b) \]

identityOnValid :: (Show a, Eq a, GenValid a) => (a -> a -> a) -> a -> Property #

identityOnValid ((*) :: Double -> Double -> Double) 1
identityOnValid ((+) :: Double -> Double -> Double) 0

identity :: (Show a, Eq a, GenUnchecked a) => (a -> a -> a) -> a -> Property #

identity ((*) :: Int -> Int -> Int) 1
identity ((+) :: Int -> Int -> Int) 0

identityOnArbitrary :: (Show a, Eq a, Arbitrary a) => (a -> a -> a) -> a -> Property #

identityOnArbitrary ((*) :: Int -> Int -> Int) 1
identityOnArbitrary ((+) :: Int -> Int -> Int) 0

Associativity

associativeOnGens :: (Show a, Eq a) => (a -> a -> a) -> Gen (a, a, a) -> ((a, a, a) -> [(a, a, a)]) -> Property #

\[ Associative(\star) \quad\equiv\quad \forall a, b, c: (a \star b) \star c = a \star (b \star c) \]

associativeOnValids :: (Show a, Eq a, GenValid a) => (a -> a -> a) -> Property #

associative :: (Show a, Eq a, GenUnchecked a) => (a -> a -> a) -> Property #

associative ((*) :: Int -> Int -> Int)
associative ((+) :: Int -> Int -> Int)

associativeOnArbitrary :: (Show a, Eq a, Arbitrary a) => (a -> a -> a) -> Property #

associativeOnArbitrary ((*) :: Int -> Int -> Int)
associativeOnArbitrary ((+) :: Int -> Int -> Int)

Commutativity

commutativeOnGens :: (Show a, Eq a) => (a -> a -> a) -> Gen (a, a) -> ((a, a) -> [(a, a)]) -> Property #

\[ Commutative(\star) \quad\equiv\quad \forall a, b: a \star b = b \star a \]

commutativeOnValids :: (Show a, Eq a, GenValid a) => (a -> a -> a) -> Property #

commutative ((+) :: Double -> Double -> Double)
commutative ((*) :: Double -> Double -> Double)

commutative :: (Show a, Eq a, GenUnchecked a) => (a -> a -> a) -> Property #

commutative ((+) :: Int -> Int -> Int)
commutative ((*) :: Int -> Int -> Int)

commutativeOnArbitrary :: (Show a, Eq a, Arbitrary a) => (a -> a -> a) -> Property #

commutativeOnArbitrary ((+) :: Int -> Int -> Int)
commutativeOnArbitrary ((*) :: Int -> Int -> Int)

Eq properties

eqSpecOnValid :: forall a. (Show a, Eq a, Typeable a, GenValid a) => Spec Source #

Standard test spec for properties of Eq instances for valid values

Example usage:

eqSpecOnValid @Double

eqSpecOnInvalid :: forall a. (Show a, Eq a, Typeable a, GenInvalid a) => Spec Source #

Standard test spec for properties of Eq instances for invalid values

Example usage:

eqSpecOnInvalid @Double

eqSpec :: forall a. (Show a, Eq a, Typeable a, GenUnchecked a) => Spec Source #

Standard test spec for properties of Eq instances for unchecked values

Example usage:

eqSpec @Int

eqSpecOnArbitrary :: forall a. (Show a, Eq a, Typeable a, Arbitrary a) => Spec Source #

Standard test spec for properties of Eq instances for arbitrary values

Example usage:

eqSpecOnArbitrary @Int

eqSpecOnGen :: forall a. (Show a, Eq a, Typeable a) => Gen a -> String -> (a -> [a]) -> Spec Source #

Standard test spec for properties of Eq instances for values generated by a given generator (and name for that generator).

Example usage:

eqSpecOnGen ((* 2) <$> genValid @Int) "even"

Ord properties

ordSpecOnGen :: forall a. (Show a, Eq a, Ord a, Typeable a) => Gen a -> String -> (a -> [a]) -> Spec Source #

Standard test spec for properties of Ord instances for values generated by a given generator (and name for that generator).

Example usage:

ordSpecOnGen ((* 2) <$> genValid @Int) "even"

ordSpecOnValid :: forall a. (Show a, Ord a, Typeable a, GenValid a) => Spec Source #

Standard test spec for properties of Ord instances for valid values

Example usage:

ordSpecOnValid @Double

ordSpecOnInvalid :: forall a. (Show a, Ord a, Typeable a, GenInvalid a) => Spec Source #

Standard test spec for properties of Ord instances for invalid values

Example usage:

ordSpecOnInvalid @Double

ordSpec :: forall a. (Show a, Ord a, Typeable a, GenUnchecked a) => Spec Source #

Standard test spec for properties of Ord instances for unchecked values

Example usage:

ordSpec @Int

ordSpecOnArbitrary :: forall a. (Show a, Ord a, Typeable a, Arbitrary a) => Spec Source #

Standard test spec for properties of Ord instances for arbitrary values

Example usage:

ordSpecOnArbitrary @Int

Monoid properties

monoidSpecOnValid :: forall a. (Show a, Eq a, Monoid a, Typeable a, GenValid a) => Spec Source #

Standard test spec for properties of Monoid instances for valid values

Example usage:

monoidSpecOnValid @[Double]

monoidSpec :: forall a. (Show a, Eq a, Monoid a, Typeable a, GenUnchecked a) => Spec Source #

Standard test spec for properties of Monoid instances for unchecked values

Example usage:

monoidSpec @[Int]

monoidSpecOnArbitrary :: forall a. (Show a, Eq a, Monoid a, Typeable a, Arbitrary a) => Spec Source #

Standard test spec for properties of Monoid instances for arbitrary values

Example usage:

monoidSpecOnArbitrary @[Int]

monoidSpecOnGen :: forall a. (Show a, Eq a, Monoid a, Typeable a) => Gen a -> String -> (a -> [a]) -> Spec Source #

Standard test spec for properties of Monoid instances for values generated by a given generator (and name for that generator).

Example usage:

monoidSpecOnGen (pure "a") "singleton list of 'a'"

Functor properties

functorSpecOnValid :: forall (f :: * -> *). (Eq (f Int), Show (f Int), Functor f, Typeable f, GenValid (f Int)) => Spec Source #

Standard test spec for properties of Functor instances for values generated with GenValid instances

Example usage:

functorSpecOnArbitrary @[]

functorSpec :: forall (f :: * -> *). (Eq (f Int), Show (f Int), Functor f, Typeable f, GenUnchecked (f Int)) => Spec Source #

Standard test spec for properties of Functor instances for values generated with GenUnchecked instances

Example usage:

functorSpecOnArbitrary @[]

functorSpecOnArbitrary :: forall (f :: * -> *). (Eq (f Int), Show (f Int), Functor f, Typeable f, Arbitrary (f Int)) => Spec Source #

Standard test spec for properties of Functor instances for values generated with Arbitrary instances

Example usage:

functorSpecOnArbitrary @[]

functorSpecOnGens :: forall (f :: * -> *) (a :: *) (b :: *) (c :: *). (Show a, Show (f a), Show (f c), Eq (f a), Eq (f c), Functor f, Typeable f, Typeable a, Typeable b, Typeable c) => Gen a -> String -> Gen (f a) -> String -> Gen (b -> c) -> String -> Gen (a -> b) -> String -> Spec Source #

Standard test spec for properties of Functor instances for values generated by given generators (and names for those generator).

Example usage:

functorSpecOnGens
    @[]
    @Int
    (pure 4) "four"
    (genListOf $ pure 5) "list of fives"
    ((+) <$> genValid) "additions"
    ((*) <$> genValid) "multiplications"

Applicative properties

applicativeSpecOnValid :: forall (f :: * -> *). (Eq (f Int), Show (f Int), Applicative f, Typeable f, GenValid (f Int)) => Spec Source #

Standard test spec for properties of Applicative instances for values generated with GenValid instances

Example usage:

applicativeSpecOnArbitrary @[]

applicativeSpec :: forall (f :: * -> *). (Eq (f Int), Show (f Int), Applicative f, Typeable f, GenUnchecked (f Int)) => Spec Source #

Standard test spec for properties of Applicative instances for values generated with GenUnchecked instances

Example usage:

applicativeSpecOnArbitrary @[]

applicativeSpecOnArbitrary :: forall (f :: * -> *). (Eq (f Int), Show (f Int), Applicative f, Typeable f, Arbitrary (f Int)) => Spec Source #

Standard test spec for properties of Applicative instances for values generated with Arbitrary instances

Example usage:

applicativeSpecOnArbitrary @[]

applicativeSpecOnGens :: forall (f :: * -> *) (a :: *) (b :: *) (c :: *). (Show a, Eq a, Show (f a), Eq (f a), Show (f b), Eq (f b), Show (f c), Eq (f c), Applicative f, Typeable f, Typeable a, Typeable b, Typeable c) => Gen a -> String -> Gen (f a) -> String -> Gen (f b) -> String -> Gen (a -> b) -> String -> Gen (f (a -> b)) -> String -> Gen (f (b -> c)) -> String -> Spec Source #

Standard test spec for properties of Applicative instances for values generated by given generators (and names for those generator).

Unless you are building a specific regression test, you probably want to use the other applicativeSpec functions.

Example usage:

applicativeSpecOnGens
    @Maybe
    @String
    (pure "ABC")
    "ABC"
    (Just <$> pure "ABC")
    "Just an ABC"
    (pure Nothing)
    "purely Nothing"
    ((++) <$> genValid)
    "prepends"
    (pure <$> ((++) <$> genValid))
    "prepends in a Just"
    (pure <$> (flip (++) <$> genValid))
    "appends in a Just"

Monad properties

monadSpecOnValid :: forall (f :: * -> *). (Eq (f Int), Show (f Int), Monad f, Typeable f, GenValid (f Int)) => Spec Source #

Standard test spec for properties of Monad instances for values generated with GenValid instances

Example usage:

monadSpecOnArbitrary @[]

monadSpec :: forall (f :: * -> *). (Eq (f Int), Show (f Int), Monad f, Typeable f, GenUnchecked (f Int)) => Spec Source #

Standard test spec for properties of Monad instances for values generated with GenUnchecked instances

Example usage:

monadSpecOnArbitrary @[]

monadSpecOnArbitrary :: forall (f :: * -> *). (Eq (f Int), Show (f Int), Monad f, Typeable f, Arbitrary (f Int)) => Spec Source #

Standard test spec for properties of Monad instances for values generated with Arbitrary instances

Example usage:

monadSpecOnArbitrary @[]

monadSpecOnGens :: forall (f :: * -> *) (a :: *) (b :: *) (c :: *). (Show a, Eq a, Show (f a), Show (f b), Show (f c), Eq (f a), Eq (f b), Eq (f c), Monad f, Typeable f, Typeable a, Typeable b, Typeable c) => Gen a -> String -> Gen (f a) -> String -> Gen (f b) -> String -> Gen (a -> b) -> String -> Gen (a -> f b) -> String -> Gen (b -> f c) -> String -> Gen (f (a -> b)) -> String -> Spec Source #

Standard test spec for properties of Monad instances for values generated by given generators (and names for those generator).

Example usage:

monadSpecOnGens
    @[]
    @Int
    (pure 4)
    "four"
    (genListOf $ pure 5)
    "list of fives"
    (genListOf $ pure 6)
    "list of sixes"
    ((*) <$> genValid)
    "factorisations"
    (pure $ \a -> [a])
    "singletonisation"
    (pure $ \a -> [a])
    "singletonisation"
    (pure $ pure (+ 1))
    "increment in list"