genvalidity-0.7.0.1: Testing utilities for the validity library

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

Documentation

class GValidSubtermsIncl f a where Source #

Methods

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

Instances
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 #

class GValidSubterms f a where Source #

Methods

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

Instances
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 GValidRecursivelyShrink f where Source #

Methods

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

Instances
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 #

class GGenValid f where Source #

Methods

gGenValid :: Gen (f a) Source #

Instances
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 GUncheckedSubtermsIncl f a where Source #

Methods

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

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

Defined in Data.GenValidity

Methods

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

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

Defined in Data.GenValidity

Methods

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

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

Defined in Data.GenValidity

Methods

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

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

Defined in Data.GenValidity

Methods

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

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

Defined in Data.GenValidity

Methods

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

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

Defined in Data.GenValidity

Methods

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

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

Defined in Data.GenValidity

Methods

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

class GUncheckedSubterms f a where Source #

Methods

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

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

Defined in Data.GenValidity

Methods

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

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

Defined in Data.GenValidity

Methods

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

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

Defined in Data.GenValidity

Methods

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

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

Defined in Data.GenValidity

Methods

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

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

Defined in Data.GenValidity

Methods

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

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

Defined in Data.GenValidity

Methods

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

class GUncheckedRecursivelyShrink f where Source #

Methods

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

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

Defined in Data.GenValidity

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

Defined in Data.GenValidity

GenUnchecked a => GUncheckedRecursivelyShrink (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Data.GenValidity

Methods

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

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

Defined in Data.GenValidity

Methods

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

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

Defined in Data.GenValidity

Methods

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

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

Defined in Data.GenValidity

Methods

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

class GGenUnchecked f where Source #

Methods

gGenUnchecked :: Gen (f a) Source #

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

Defined in Data.GenValidity

Methods

gGenUnchecked :: Gen (U1 a) Source #

GenUnchecked a => GGenUnchecked (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Data.GenValidity

Methods

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

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

Defined in Data.GenValidity

Methods

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

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

Defined in Data.GenValidity

Methods

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

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

Defined in Data.GenValidity

Methods

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

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

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

Minimal complete definition

Nothing

Methods

genInvalid :: Gen a Source #

shrinkInvalid :: a -> [a] Source #

Instances
GenInvalid a => GenInvalid [a] Source #

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

Instance details

Defined in Data.GenValidity

Methods

genInvalid :: Gen [a] Source #

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

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

Defined in Data.GenValidity

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

Defined in Data.GenValidity

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

Defined in Data.GenValidity

(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.

Instance details

Defined in Data.GenValidity

Methods

genInvalid :: Gen (Either a b) Source #

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

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

Defined in Data.GenValidity

Methods

genInvalid :: Gen (a, b) Source #

shrinkInvalid :: (a, b) -> [(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.

Instance details

Defined in Data.GenValidity

Methods

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

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

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

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

Instance details

Defined in Data.GenValidity

Methods

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

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

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

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

Instance details

Defined in Data.GenValidity

Methods

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

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

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.

Minimal complete definition

Nothing

Methods

genValid :: Gen a Source #

shrinkValid :: a -> [a] Source #

Shrink a valid value.

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.

Instances
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 #

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

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 #

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 (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 #

(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 #

class GenUnchecked a where Source #

A class of types for which truly arbitrary values can be generated.

Automatic instances with Generic

An instance of this class can be made automatically if the type in question has a Generic instance. This instance will try to use genUnchecked to generate all structural sub-parts of the value that is being generated.

Example:

{-# LANGUAGE DeriveGeneric #-}

data MyType = MyType Rational String
    deriving (Show, Eq, Generic)

instance GenUnchecked MyType

generates something like:

instance GenUnchecked MyType where
    genUnchecked = MyType <$> genUnchecked <*> genUnchecked

Minimal complete definition

Nothing

Instances
GenUnchecked Bool Source # 
Instance details

Defined in Data.GenValidity

GenUnchecked Char Source # 
Instance details

Defined in Data.GenValidity

GenUnchecked Double Source # 
Instance details

Defined in Data.GenValidity

GenUnchecked Float Source # 
Instance details

Defined in Data.GenValidity

GenUnchecked Int Source # 
Instance details

Defined in Data.GenValidity

GenUnchecked Int8 Source # 
Instance details

Defined in Data.GenValidity

GenUnchecked Int16 Source # 
Instance details

Defined in Data.GenValidity

GenUnchecked Int32 Source # 
Instance details

Defined in Data.GenValidity

GenUnchecked Int64 Source # 
Instance details

Defined in Data.GenValidity

GenUnchecked Integer Source # 
Instance details

Defined in Data.GenValidity

GenUnchecked Natural Source # 
Instance details

Defined in Data.GenValidity

GenUnchecked Ordering Source # 
Instance details

Defined in Data.GenValidity

GenUnchecked Word Source # 
Instance details

Defined in Data.GenValidity

GenUnchecked Word8 Source # 
Instance details

Defined in Data.GenValidity

GenUnchecked Word16 Source # 
Instance details

Defined in Data.GenValidity

GenUnchecked Word32 Source # 
Instance details

Defined in Data.GenValidity

GenUnchecked Word64 Source # 
Instance details

Defined in Data.GenValidity

GenUnchecked () Source # 
Instance details

Defined in Data.GenValidity

Methods

genUnchecked :: Gen () Source #

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

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

Defined in Data.GenValidity

Methods

genUnchecked :: Gen [a] Source #

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

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

Defined in Data.GenValidity

(Integral a, GenUnchecked a) => GenUnchecked (Ratio a) Source # 
Instance details

Defined in Data.GenValidity

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

Defined in Data.GenValidity

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

Defined in Data.GenValidity

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

Defined in Data.GenValidity

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

Defined in Data.GenValidity

Methods

genUnchecked :: Gen (a, b) Source #

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

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

Defined in Data.GenValidity

Methods

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

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

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

Defined in Data.GenValidity

Methods

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

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

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

Defined in Data.GenValidity

Methods

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

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

shrinkT2 :: (a -> [a]) -> (a, a) -> [(a, a)] Source #

shrinkT3 :: (a -> [a]) -> (a, a, a) -> [(a, a, a)] 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 #

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

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

'genSplit4 a' generates a quadruple '(b, c, d, e)' such that 'b + c + d + e' equals a.

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

'genSplit5 a' generates a quadruple '(b, c, d, e, f)' such that 'b + c + d + e + f' 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.

genericShrinkUnchecked :: (Generic a, GUncheckedRecursivelyShrink (Rep a), GUncheckedSubterms (Rep a) a) => a -> [a] Source #

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

uncheckedRecursivelyShrink :: (Generic a, GUncheckedRecursivelyShrink (Rep a)) => a -> [a] Source #

Recursively shrink all immediate uncheckedSubterms.

uncheckedSubterms :: (Generic a, GUncheckedSubterms (Rep a) a) => a -> [a] Source #

All immediate uncheckedSubterms of a term.

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.

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

Recursively shrink all immediate structurally valid subterms.

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

All immediate validSubterms of a term.