registry-hedgehog-0.8.0.0: utilities to work with Hedgehog generators and `registry`
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Registry.Hedgehog

Synopsis

Documentation

data Chooser Source #

A "chooser" strategy The type can be used to debug specializations

Constructors

Chooser 

Fields

Instances

Instances details
Show Chooser Source # 
Instance details

Defined in Data.Registry.Internal.Hedgehog

genFun :: forall a b. (ApplyVariadic Gen a b, Typeable a, Typeable b) => a -> Typed b Source #

Create a Gen a for a given constructor of type a

genVal :: forall a. Typeable a => Gen a -> Typed (Gen a) Source #

Create a Gen a for a given constructor of type a

genWith :: forall a ins out. Typeable a => Registry ins out -> Gen a Source #

Extract a generator from a registry We use makeUnsafe assuming that the registry has been checked before

setGen :: forall a ins out. Typeable a => Gen a -> Registry ins out -> Registry ins out Source #

Set a specific generator on the registry the value of a generator in a given registry

specializeGen :: forall (a :: Type) b ins out. (Typeable a, Typeable b) => Gen b -> Registry ins out -> Registry ins out Source #

Specialize a generator in a given context

tweakGen :: forall a ins out. Typeable a => (a -> a) -> Registry ins out -> Registry ins out Source #

Modify the value of a generator in a given registry

makeNonEmpty :: forall (a :: Type) ins out. Typeable a => Registry ins out -> Registry ins out Source #

Make sure there is always one element of a given type in a list of elements

genListOf :: forall a. Typeable a => Typed (Gen a -> Gen [a]) Source #

Add a generator for a list of elements

genListOfMinMax :: forall a. Typeable a => Int -> Int -> Typed (Gen a -> Gen [a]) Source #

Add a generator for a bounded list of elements

genNonEmptyOfMinMax :: forall a. Typeable a => Int -> Int -> Typed (Gen a -> Gen (NonEmpty a)) Source #

Add a generator for a bounded non-empty list of elements

genNonEmptyOf :: forall a. Typeable a => Typed (Gen a -> Gen (NonEmpty a)) Source #

Add a generator for a non-empty list of elements

genMaybeOf :: forall a. Typeable a => Typed (Gen a -> Gen (Maybe a)) Source #

Add a generator for an optional element

genOneOf :: (Typeable a, Show a) => [a] -> Typed (Gen a) Source #

Add a generator for a element picked from a list

genPairOf :: forall a b. (Typeable a, Typeable b) => Typed (Gen a -> Gen b -> Gen (a, b)) Source #

Add a generator for a pair of elements

genTripleOf :: forall a b c. (Typeable a, Typeable b, Typeable c) => Typed (Gen a -> Gen b -> Gen c -> Gen (a, b, c)) Source #

Add a generator for a triple of elements

genTuple4Of :: forall a b c d. (Typeable a, Typeable b, Typeable c, Typeable d) => Typed (Gen a -> Gen b -> Gen c -> Gen d -> Gen (a, b, c, d)) Source #

Add a generator for 4 elements

genMapOf :: forall k v. (Ord k, Typeable k, Typeable v) => Typed (Gen k -> Gen v -> Gen (Map k v)) Source #

Add a generator for a map of elements

genNonEmptyMapOf :: forall k v. (Ord k, Typeable k, Typeable v) => Typed (Gen k -> Gen v -> Gen (Map k v)) Source #

Add a generator for a non empty map of elements

genHashMapOf :: forall k v. (Ord k, Hashable k, Typeable k, Typeable v) => Typed (Gen k -> Gen v -> Gen (HashMap k v)) Source #

Add a generator for a hashmap of elements

setDistinctPairOf :: forall a. (Typeable a, Eq a) => Registry _ _ -> Registry _ _ Source #

Add the generation of a pair of distinct elements

setDistinctPairOfOn :: forall a b. (Typeable a, Eq b) => (a -> b) -> Registry _ _ -> Registry _ _ Source #

Add the generation of a pair of distinct elements, according to one of their part

setDistinctTripleOf :: forall a. (Typeable a, Eq a) => Registry _ _ -> Registry _ _ Source #

Add the generation of a triple of distinct elements

setDistinctTripleOfOn :: forall a b. (Typeable a, Eq b) => (a -> b) -> Registry _ _ -> Registry _ _ Source #

Add the generation of a triple of distinct elements, according to one of their part

distinctPairOf :: forall a. Eq a => Gen a -> Gen (a, a) Source #

Make a generator for a pair of distinct values

distinctPairOfOn :: forall a b. Eq b => (a -> b) -> Gen a -> Gen (a, a) Source #

Make a generator for a pair of distinct values according to one of their part

distinctTripleOf :: forall a. Eq a => Gen a -> Gen (a, a, a) Source #

Make a generator for a triple of distinct values

distinctTripleOfOn :: forall a b. Eq b => (a -> b) -> Gen a -> Gen (a, a, a) Source #

Make a generator for a triple of distinct values according to one of their part

eitherOf :: forall a b. Gen a -> Gen b -> Gen (Either a b) Source #

Create a default generator for a Either, choosing evenly between Left and Right

hashMapOf :: forall k v. (Ord k, Hashable k) => Gen k -> Gen v -> Gen (HashMap k v) Source #

Create a default generator for HashMap of key/values

listOf :: forall a. Gen a -> Gen [a] Source #

Create a default generator for a small list of elements

listOfMinMax :: forall a. Int -> Int -> Gen a -> Gen [a] Source #

Create a default generator for a list of elements of min elements and max elements

nonEmptyOfMinMax :: Int -> Int -> Gen a -> Gen (NonEmpty a) Source #

Make a generator for a non empty list of elements of a given type

mapOf :: forall k v. Ord k => Gen k -> Gen v -> Gen (Map k v) Source #

Create a default generator for map of key/values

maybeOf :: forall a. Gen a -> Gen (Maybe a) Source #

Create a default generator for a Maybe, choosing evenly between Nothing and Just

nonEmptyMapOf :: forall k v. Ord k => Gen k -> Gen v -> Gen (Map k v) Source #

Create a default generator for a small non-empty map of elements

nonEmptyOf :: Gen a -> Gen (NonEmpty a) Source #

Create a default generator for a small non-empty list of elements

pairOf :: forall a b. Gen a -> Gen b -> Gen (a, b) Source #

Create a generator for a pair

setOf :: forall a. Ord a => Gen a -> Gen (Set a) Source #

Create a default generator for a small set of elements

setOfMinMax :: forall a. Ord a => Int -> Int -> Gen a -> Gen (Set a) Source #

Create a default generator for a set with a minimum and a maximum number of elements The implementation uses Gen.filter to make sure that the elements are unique

tripleOf :: forall a b c. Gen a -> Gen b -> Gen c -> Gen (a, b, c) Source #

Create a generator for a triple

tuple4Of :: forall a b c d. Gen a -> Gen b -> Gen c -> Gen d -> Gen (a, b, c, d) Source #

Create a generator for a quadruple

tuple5Of :: forall a b c d e. Gen a -> Gen b -> Gen c -> Gen d -> Gen e -> Gen (a, b, c, d, e) Source #

Create a generator for a quintuple

choiceChooser :: Chooser Source #

Chooser for randomly selecting a generator

chooseOne :: Gen Chooser -> [Gen a] -> Gen a Source #

Given a choosing strategy pick a generator This is possibly a stateful operation

sampleIO :: GenT IO a -> IO a Source #

Sample Gen values