Safe Haskell | None |
---|---|
Language | Haskell2010 |
Generic.Random
Contents
Description
GHC.Generics-based arbitrary
generators.
Basic usage
{-# LANGUAGE DeriveGeneric #-}
data Foo = A | B | C -- some generic data type
deriving Generic
Derive instances of Arbitrary
.
instance Arbitrary Foo where arbitrary =genericArbitrary
uniform
-- Give a distribution of constructors. shrink =genericShrink
-- Generic shrinking is provided by the QuickCheck library.
Or derive standalone generators (the fields must still be instances of
Arbitrary
, or use custom generators).
genFoo :: Gen Foo genFoo =genericArbitrary
uniform
Using DerivingVia
{-# LANGUAGE DerivingVia, TypeOperators #-} data Foo = A | B | C derivingGeneric
deriving Arbitrary via (GenericArbitraryU
`AndShrinking
` Foo)
For more information:
Synopsis
- genericArbitrary :: GArbitrary UnsizedOpts a => Weights a -> Gen a
- genericArbitraryU :: (GArbitrary UnsizedOpts a, GUniformWeight a) => Gen a
- genericArbitrarySingle :: (GArbitrary UnsizedOpts a, Weights_ (Rep a) ~ L c0) => Gen a
- genericArbitraryRec :: GArbitrary SizedOptsDef a => Weights a -> Gen a
- genericArbitrary' :: (GArbitrary SizedOptsDef a, BaseCase a) => Weights a -> Gen a
- genericArbitraryU' :: (GArbitrary SizedOptsDef a, BaseCase a, GUniformWeight a) => Gen a
- genericArbitraryG :: GArbitrary (SetGens genList UnsizedOpts) a => genList -> Weights a -> Gen a
- genericArbitraryUG :: (GArbitrary (SetGens genList UnsizedOpts) a, GUniformWeight a) => genList -> Gen a
- genericArbitrarySingleG :: (GArbitrary (SetGens genList UnsizedOpts) a, Weights_ (Rep a) ~ L c0) => genList -> Gen a
- genericArbitraryRecG :: GArbitrary (SetGens genList SizedOpts) a => genList -> Weights a -> Gen a
- data Weights a
- data W (c :: Symbol)
- (%) :: (WeightBuilder' w, c ~ First' w) => W c -> Prec' w -> w
- uniform :: UniformWeight_ (Rep a) => Weights a
- data a :+ b = a :+ b
- newtype FieldGen (s :: Symbol) a = FieldGen {
- unFieldGen :: Gen a
- fieldGen :: proxy s -> Gen a -> FieldGen s a
- newtype ConstrGen (c :: Symbol) (i :: Nat) a = ConstrGen {
- unConstrGen :: Gen a
- constrGen :: proxy '(c, i) -> Gen a -> ConstrGen c i a
- newtype Gen1 f = Gen1 {}
- newtype Gen1_ f = Gen1_ {}
- listOf' :: Gen a -> Gen [a]
- listOf1' :: Gen a -> Gen [a]
- vectorOf' :: Int -> Gen a -> Gen [a]
- withBaseCase :: Gen a -> Gen a -> Gen a
- class BaseCase a where
- data Options (c :: Coherence) (s :: Sizing) (genList :: Type)
- genericArbitraryWith :: GArbitrary opts a => opts -> Weights a -> Gen a
- type family SetOptions (x :: k) (o :: Type) :: Type
- type (<+) o x = SetOptions x o
- setOpts :: forall x o. Coercible o (SetOptions x o) => o -> SetOptions x o
- data Sizing
- type family SetSized (o :: Type) :: Type
- type family SetUnsized (o :: Type) :: Type
- setSized :: Options c s g -> Options c 'Sized g
- setUnsized :: Options c s g -> Options c 'Unsized g
- type family SetGens (g :: Type) opts
- setGenerators :: genList -> Options c s g0 -> Options c s genList
- data Coherence
- newtype Incoherent g = Incoherent g
- type SizedOpts = Options 'INCOHERENT 'Sized ()
- sizedOpts :: SizedOpts
- type SizedOptsDef = Options 'INCOHERENT 'Sized (Gen1 [] :+ ())
- sizedOptsDef :: SizedOptsDef
- type UnsizedOpts = Options 'INCOHERENT 'Unsized ()
- unsizedOpts :: UnsizedOpts
- type CohUnsizedOpts = Options 'COHERENT 'Unsized ()
- cohUnsizedOpts :: CohUnsizedOpts
- type CohSizedOpts = Options 'COHERENT 'Sized ()
- cohSizedOpts :: CohSizedOpts
- class (Generic a, GA opts (Rep a)) => GArbitrary opts a
- class UniformWeight_ (Rep a) => GUniformWeight a
- newtype GenericArbitrary weights a = GenericArbitrary {
- unGenericArbitrary :: a
- newtype GenericArbitraryU a = GenericArbitraryU {
- unGenericArbitraryU :: a
- newtype GenericArbitrarySingle a = GenericArbitrarySingle {}
- newtype GenericArbitraryRec weights a = GenericArbitraryRec {}
- newtype GenericArbitraryG genList weights a = GenericArbitraryG {
- unGenericArbitraryG :: a
- newtype GenericArbitraryUG genList a = GenericArbitraryUG {
- unGenericArbitraryUG :: a
- newtype GenericArbitrarySingleG genList a = GenericArbitrarySingleG {}
- newtype GenericArbitraryRecG genList weights a = GenericArbitraryRecG {}
- newtype GenericArbitraryWith opts weights a = GenericArbitraryWith {}
- newtype AndShrinking f a = AndShrinking a
- class TypeLevelGenList a where
- type TypeLevelGenList' a :: Type
- toGenList :: Proxy a -> TypeLevelGenList' a
- class TypeLevelOpts a where
- type TypeLevelOpts' a :: Type
- toOpts :: Proxy a -> TypeLevelOpts' a
Arbitrary implementations
The suffixes for the variants have the following meanings:
U
: pick constructors with uniform distribution (equivalent to passinguniform
to the non-U
variant).Single
: restricted to types with a single constructor.G
: with custom generators.Rec
: decrease the size at every recursive call (ensuring termination for (most) recursive types).'
: automatic discovery of "base cases" when size reaches 0.
Arguments
:: GArbitrary UnsizedOpts a | |
=> Weights a | List of weights for every constructor |
-> Gen a |
Pick a constructor with a given distribution, and fill its fields
with recursive calls to arbitrary
.
Example
genericArbitrary (2 % 3 % 5 % ()) :: Gen a
Picks the first constructor with probability 2/10
,
the second with probability 3/10
, the third with probability 5/10
.
genericArbitraryU :: (GArbitrary UnsizedOpts a, GUniformWeight a) => Gen a Source #
Pick every constructor with equal probability.
Equivalent to
.genericArbitrary
uniform
genericArbitraryU :: Gen a
genericArbitrarySingle :: (GArbitrary UnsizedOpts a, Weights_ (Rep a) ~ L c0) => Gen a Source #
arbitrary
for types with one constructor.
Equivalent to genericArbitraryU
, with a stricter type.
genericArbitrarySingle :: Gen a
Arguments
:: GArbitrary SizedOptsDef a | |
=> Weights a | List of weights for every constructor |
-> Gen a |
Arguments
:: (GArbitrary SizedOptsDef a, BaseCase a) | |
=> Weights a | List of weights for every constructor |
-> Gen a |
genericArbitraryU' :: (GArbitrary SizedOptsDef a, BaseCase a, GUniformWeight a) => Gen a Source #
Equivalent to
.genericArbitrary'
uniform
genericArbitraryU' :: Gen a
N.B.: This replaces the generator for fields of type [t]
with
instead of listOf'
arbitrary
(i.e., listOf
arbitraryarbitrary
for
lists).
With custom generators
Note about incoherence
The custom generator feature relies on incoherent instances, which can lead to surprising behaviors for parameterized types.
Example
For example, here is a pair type and a custom generator of Int
(always
generating 0).
data Pair a b = Pair a b deriving (Generic, Show) customGen :: Gen Int customGen = pure 0
The following two ways of defining a generator of Pair Int Int
are
not equivalent.
The first way is to use genericArbitrarySingleG
to define a
Gen (Pair a b)
parameterized by types a
and b
, and then
specialize it to Gen (Pair Int Int)
.
In this case, the customGen
will be ignored.
genPair :: (Arbitrary a, Arbitrary b) => Gen (Pair a b)
genPair = genericArbitrarySingleG
customGen
genPair' :: Gen (Pair Int Int)
genPair' = genPair
-- Will generate nonzero pairs
The second way is to define Gen (Pair Int Int)
directly using
genericArbitrarySingleG
(as if we inlined genPair
in genPair'
above.
Then the customGen
will actually be used.
genPair2 :: Gen (Pair Int Int)
genPair2 = genericArbitrarySingleG
customGen
-- Will only generate (Pair 0 0)
In other words, the decision of whether to use a custom generator
is done by comparing the type of the custom generator with the type of
the field only in the context where genericArbitrarySingleG
is being
used (or any other variant with a G
suffix).
In the first case above, those fields have types a
and b
, which are
not equal to Int
(or rather, there is no available evidence that they
are equal to Int
, even if they could be instantiated as Int
later).
In the second case, they both actually have type Int
.
genericArbitraryG :: GArbitrary (SetGens genList UnsizedOpts) a => genList -> Weights a -> Gen a Source #
genericArbitrary
with explicit generators.
Example
genericArbitraryG customGens (17 % 19 % ())
where, the generators for String
and Int
fields are overridden as
follows, for example:
customGens :: Gen String:+
Gen Int customGens = (filter (/= 'NUL')<$>
arbitrary):+
(getNonNegative<$>
arbitrary)
Note on multiple matches
Multiple generators may match a given field: the first will be chosen.
genericArbitraryUG :: (GArbitrary (SetGens genList UnsizedOpts) a, GUniformWeight a) => genList -> Gen a Source #
genericArbitraryU
with explicit generators.
See also genericArbitraryG
.
genericArbitrarySingleG :: (GArbitrary (SetGens genList UnsizedOpts) a, Weights_ (Rep a) ~ L c0) => genList -> Gen a Source #
genericArbitrarySingle
with explicit generators.
See also genericArbitraryG
.
Arguments
:: GArbitrary (SetGens genList SizedOpts) a | |
=> genList | |
-> Weights a | List of weights for every constructor |
-> Gen a |
genericArbitraryRec
with explicit generators.
See also genericArbitraryG
.
Specifying finite distributions
Trees of weights assigned to constructors of type a
,
rescaled to obtain a probability distribution.
Two ways of constructing them.
(x1%
x2%
...%
xn%
()) ::Weights
auniform
::Weights
a
Using (
, there must be exactly as many weights as
there are constructors.%
)
uniform
is equivalent to (1
(automatically fills out the right number of 1s).%
... %
1 %
())
(%) :: (WeightBuilder' w, c ~ First' w) => W c -> Prec' w -> w infixr 1 Source #
A binary constructor for building up trees of weights.
Custom generators
Custom generators can be specified in a list constructed with (
,
and passed to functions such as :+
)genericArbitraryG
to override how certain
fields are generated.
Example:
customGens :: Gen String:+
Gen Int customGens = (filter (/= 'NUL')<$>
arbitrary):+
(getNonNegative<$>
arbitrary)
There are also different types of generators, other than Gen
, providing
more ways to select the fields the generator than by simply comparing types:
: override fields of typeGen
aa
;
: override fields of typeGen1
ff x
for somex
, requiring a generator forx
;
: override fields of typeGen1_
ff x
for somex
, not requiring a generator forx
;
: override record fields namedFieldGen
s as
, which must have typea
;
: override the field at indexConstrGen
c i ai
of constructorc
, which must have typea
(0-indexed);
Multiple generators may match a given field: the first, leftmost generator in the list will be chosen.
Heterogeneous list of generators.
Constructors
a :+ b infixr 1 |
Instances
FindGen 'Shift s b g a => FindGen 'Shift s () (b :+ g) a Source # | Examine the next candidate |
Defined in Generic.Random.Internal.Generic | |
FindGen 'Shift s g (h :+ gs) a => FindGen 'Shift s (g :+ h) gs a Source # | This can happen if the generators form a tree rather than a list, for whatever reason. |
Defined in Generic.Random.Internal.Generic | |
(TypeLevelGenList a, TypeLevelGenList b) => TypeLevelGenList (a :+ b :: Type) Source # | |
Defined in Generic.Random.DerivingVia Associated Types type TypeLevelGenList' (a :+ b) Source # | |
type TypeLevelGenList' (a :+ b :: Type) Source # | |
Defined in Generic.Random.DerivingVia |
newtype FieldGen (s :: Symbol) a Source #
Custom generator for record fields named s
.
If there is a field named s
with a different type,
this will result in a type error.
Constructors
FieldGen | |
Fields
|
fieldGen :: proxy s -> Gen a -> FieldGen s a Source #
FieldGen
constructor with the field name given via a proxy.
newtype ConstrGen (c :: Symbol) (i :: Nat) a Source #
Custom generator for the i
-th field of the constructor named c
.
Fields are 0-indexed.
Constructors
ConstrGen | |
Fields
|
Instances
a ~ a' => FindGen ('MatchCoh 'True) s (ConstrGen c i a) gs a' Source # | Matching custom generator for |
a ~ a' => FindGen ('Match 'INCOHERENT) ('S _fg _coh '('Just c, i, s)) (ConstrGen c i a) gs a' Source # | Matching custom generator for |
Defined in Generic.Random.Internal.Generic |
constrGen :: proxy '(c, i) -> Gen a -> ConstrGen c i a Source #
ConstrGen
constructor with the constructor name given via a proxy.
Custom generators for "containers" of kind Type -> Type
, parameterized
by the generator for "contained elements".
A custom generator
will be used for any field whose type has the
form Gen1
ff x
, requiring a generator of x
. The generator for x
will be
constructed using the list of custom generators if possible, otherwise
an instance Arbitrary x
will be required.
Instances
(f x ~ a', FindGen 'Shift ('S fg coh (DummySel :: (Maybe Symbol, Nat, Maybe Symbol))) () fg x) => FindGen ('MatchCoh 'True) ('S fg coh _sel) (Gen1 f) gs a' Source # | |
FindGen 'Shift ('S fg coh (DummySel :: (Maybe Symbol, Nat, Maybe Symbol))) () fg a => FindGen ('Match 'INCOHERENT) ('S fg coh _sel) (Gen1 f) gs (f a) Source # | Matching custom generator for container |
Defined in Generic.Random.Internal.Generic |
Custom generators for unary type constructors that are not "containers",
i.e., which don't require a generator of a
to generate an f a
.
A custom generator
will be used for any field whose type has the
form Gen1_
ff x
.
Instances
f x ~ a' => FindGen ('MatchCoh 'True) s (Gen1_ f) gs a' Source # | |
FindGen ('Match 'INCOHERENT) s (Gen1_ f) gs (f a) Source # | Matching custom generator for non-container |
Defined in Generic.Random.Internal.Generic Methods findGen :: (Proxy ('Match 'INCOHERENT), Proxy s, FullGenListOf s) -> Gen1_ f -> gs -> Gen (f a) Source # |
Helpful combinators
listOf' :: Gen a -> Gen [a] Source #
An alternative to listOf
that divides the size parameter
by the length of the list.
The length follows a geometric distribution of parameter
1/(sqrt size + 1)
.
listOf1' :: Gen a -> Gen [a] Source #
An alternative to listOf1
(nonempty lists) that divides
the size parameter by the length of the list.
The length (minus one) follows a geometric distribution of parameter
1/(sqrt size + 1)
.
vectorOf' :: Int -> Gen a -> Gen [a] Source #
An alternative to vectorOf
that divides the size parameter by the
length of the list.
Base cases for recursive types
withBaseCase :: Gen a -> Gen a -> Gen a Source #
Run the first generator if the size is positive. Run the second if the size is zero.
defaultGen `withBaseCase` baseCaseGen
class BaseCase a where Source #
Custom instances can override the default behavior.
Instances
BaseCaseSearching a 0 => BaseCase a Source # | Overlappable |
Defined in Generic.Random.Internal.BaseCase |
Full options
data Options (c :: Coherence) (s :: Sizing) (genList :: Type) Source #
Type-level options for GArbitrary
.
Note: it is recommended to avoid referring to the Options
type
explicitly in code, as the set of options may change in the future.
Instead, use the provided synonyms (UnsizedOpts
, SizedOpts
, SizedOptsDef
)
and the setter SetOptions
(abbreviated as (
).<+
)
Instances
HasGenerators (Options c s g) Source # | |
Defined in Generic.Random.Internal.Generic Methods generators :: Options c s g -> GeneratorsOf (Options c s g) Source # | |
type SetOptions (g :: Type) (Options c s _g) Source # | |
Defined in Generic.Random.Internal.Generic | |
type SetOptions (c :: Coherence) (Options _c s g) Source # | |
Defined in Generic.Random.Internal.Generic | |
type SetOptions (s :: Sizing) (Options c _s g) Source # | |
Defined in Generic.Random.Internal.Generic | |
type SetGens g (Options c s _g) Source # | |
Defined in Generic.Random.Internal.Generic | |
type GeneratorsOf (Options _c _s g) Source # | |
Defined in Generic.Random.Internal.Generic | |
type CoherenceOf (Options c _s _g) Source # | |
Defined in Generic.Random.Internal.Generic | |
type SetUnsized (Options c s g) Source # | |
Defined in Generic.Random.Internal.Generic | |
type SetSized (Options c s g) Source # | |
Defined in Generic.Random.Internal.Generic | |
type SizingOf (Options _c s _g) Source # | |
Defined in Generic.Random.Internal.Generic |
genericArbitraryWith :: GArbitrary opts a => opts -> Weights a -> Gen a Source #
General generic generator with custom options.
Setters
type family SetOptions (x :: k) (o :: Type) :: Type Source #
Instances
type SetOptions (g :: Type) (Options c s _g) Source # | |
Defined in Generic.Random.Internal.Generic | |
type SetOptions (c :: Coherence) (Options _c s g) Source # | |
Defined in Generic.Random.Internal.Generic | |
type SetOptions (s :: Sizing) (Options c _s g) Source # | |
Defined in Generic.Random.Internal.Generic |
type (<+) o x = SetOptions x o infixl 1 Source #
Infix flipped synonym for Options
.
Since: 1.4.0.0
setOpts :: forall x o. Coercible o (SetOptions x o) => o -> SetOptions x o Source #
Coerce an Options
value between types with the same representation.
Since: 1.4.0.0
Size modifiers
Whether to decrease the size parameter before generating fields.
The Sized
option makes the size parameter decrease in the following way:
- Constructors with one field decrease the size parameter by 1 to generate
that field.
- Constructors with more than one field split the size parameter among all
fields; the size parameter is rounded down to then be divided equally.
Constructors
Sized | Decrease the size parameter when running generators for fields |
Unsized | Don't touch the size parameter |
Instances
type SetOptions (s :: Sizing) (Options c _s g) Source # | |
Defined in Generic.Random.Internal.Generic |
type family SetUnsized (o :: Type) :: Type Source #
Instances
type SetUnsized (Options c s g) Source # | |
Defined in Generic.Random.Internal.Generic |
Custom generators
setGenerators :: genList -> Options c s g0 -> Options c s genList Source #
Define the set of custom generators.
Note: for recursive types which can recursively appear inside lists or other containers, you may want to include a custom generator to decrease the size when generating such containers.
See also the Note about lists in Generic.Random.Tutorial.
Coherence options
For custom generators to work with parameterized types, incoherent instances must be used internally. In practice, the resulting behavior is what users want 100% of the time, so you should forget this option even exists.
Details
The default configuration of generic-random does a decent job if we trust GHC implements precisely the instance resolution algorithm as described in the GHC manual:
While that assumption holds in practice, it is overly context-dependent (to know the context leading to a particular choice, we must replay the whole resolution algorithm). In particular, this algorithm may find one solution, but it is not guaranteed to be unique: the behavior of the program is dependent on implementation details.
An notable property to consider of an implicit type system (such as type classes) is coherence: the behavior of the program is stable under specialization.
This sounds nice on paper, but actually leads to surprising behavior for generic implementations with parameterized types, such as generic-random.
To address that, the coherence property can be relaxd by users, by explicitly allowing some custom generators to be chosen incoherently. With appropriate precautions, it is possible to ensure a weaker property which nevertheless helps keep type inference predictable: when a solution is found, it is unique. (This is assuredly weaker, i.e., is not stable under specialization.)
Since: 1.4.0.0
Constructors
INCOHERENT | Match custom generators incoherently. |
COHERENT | Match custom generators coherently by default
(can be manually bypassed with |
Instances
type SetOptions (c :: Coherence) (Options _c s g) Source # | |
Defined in Generic.Random.Internal.Generic |
newtype Incoherent g Source #
Match this generator incoherently when the COHERENT
option is set.
Constructors
Incoherent g |
Instances
FindGen ('Match 'INCOHERENT) s g gs a => FindGen 'Shift s (Incoherent g) gs a Source # | |
Defined in Generic.Random.Internal.Generic Methods findGen :: (Proxy 'Shift, Proxy s, FullGenListOf s) -> Incoherent g -> gs -> Gen a Source # |
Common options
type SizedOptsDef = Options 'INCOHERENT 'Sized (Gen1 [] :+ ()) Source #
sizedOptsDef :: SizedOptsDef Source #
Default options overriding the list generator using listOf'
.
type UnsizedOpts = Options 'INCOHERENT 'Unsized () Source #
unsizedOpts :: UnsizedOpts Source #
Default options for unsized generators.
Advanced options
See Coherence
type CohUnsizedOpts = Options 'COHERENT 'Unsized () Source #
Like UnsizedOpts
, but using coherent instances by default.
Since: 1.4.0.0
cohUnsizedOpts :: CohUnsizedOpts Source #
Like unsizedOpts
, but using coherent instances by default.
type CohSizedOpts = Options 'COHERENT 'Sized () Source #
Like SizedOpts
, but using coherent instances by default.
Since: 1.4.0.0
cohSizedOpts :: CohSizedOpts Source #
Like sizedOpts
but using coherent instances by default.
Generic classes
class (Generic a, GA opts (Rep a)) => GArbitrary opts a Source #
Generic Arbitrary
Instances
(Generic a, GA opts (Rep a)) => GArbitrary opts a Source # | |
Defined in Generic.Random.Internal.Generic |
class UniformWeight_ (Rep a) => GUniformWeight a Source #
Derived uniform distribution of constructors for a
.
Instances
UniformWeight_ (Rep a) => GUniformWeight a Source # | |
Defined in Generic.Random.Internal.Generic |
Newtypes for DerivingVia
These newtypes correspond to the variants of genericArbitrary
above.
newtype GenericArbitrary weights a Source #
Pick a constructor with a given distribution, and fill its fields
with recursive calls to arbitrary
.
Example
data X = ... deriving Arbitrary via (GenericArbitrary '[2, 3, 5] X)
Picks the first constructor with probability 2/10
,
the second with probability 3/10
, the third with probability 5/10
.
This newtype does no shrinking. To add generic shrinking, use AndShrinking
.
Uses genericArbitrary
.
Since: 1.5.0.0
Constructors
GenericArbitrary | |
Fields
|
Instances
Eq a => Eq (GenericArbitrary weights a) Source # | |
Defined in Generic.Random.DerivingVia Methods (==) :: GenericArbitrary weights a -> GenericArbitrary weights a -> Bool # (/=) :: GenericArbitrary weights a -> GenericArbitrary weights a -> Bool # | |
Show a => Show (GenericArbitrary weights a) Source # | |
Defined in Generic.Random.DerivingVia Methods showsPrec :: Int -> GenericArbitrary weights a -> ShowS # show :: GenericArbitrary weights a -> String # showList :: [GenericArbitrary weights a] -> ShowS # | |
(GArbitrary UnsizedOpts a, TypeLevelWeights' weights a) => Arbitrary (GenericArbitrary weights a) Source # | |
Defined in Generic.Random.DerivingVia Methods arbitrary :: Gen (GenericArbitrary weights a) # shrink :: GenericArbitrary weights a -> [GenericArbitrary weights a] # |
newtype GenericArbitraryU a Source #
Pick every constructor with equal probability.
This newtype does no shrinking. To add generic shrinking, use AndShrinking
.
Uses genericArbitraryU
.
Since: 1.5.0.0
Constructors
GenericArbitraryU | |
Fields
|
Instances
Eq a => Eq (GenericArbitraryU a) Source # | |
Defined in Generic.Random.DerivingVia Methods (==) :: GenericArbitraryU a -> GenericArbitraryU a -> Bool # (/=) :: GenericArbitraryU a -> GenericArbitraryU a -> Bool # | |
Show a => Show (GenericArbitraryU a) Source # | |
Defined in Generic.Random.DerivingVia Methods showsPrec :: Int -> GenericArbitraryU a -> ShowS # show :: GenericArbitraryU a -> String # showList :: [GenericArbitraryU a] -> ShowS # | |
(GArbitrary UnsizedOpts a, GUniformWeight a) => Arbitrary (GenericArbitraryU a) Source # | |
Defined in Generic.Random.DerivingVia Methods arbitrary :: Gen (GenericArbitraryU a) # shrink :: GenericArbitraryU a -> [GenericArbitraryU a] # |
newtype GenericArbitrarySingle a Source #
arbitrary
for types with one constructor.
Equivalent to GenericArbitraryU
, with a stricter type.
This newtype does no shrinking. To add generic shrinking, use AndShrinking
.
Uses genericArbitrarySingle
.
Since: 1.5.0.0
Constructors
GenericArbitrarySingle | |
Fields |
Instances
Eq a => Eq (GenericArbitrarySingle a) Source # | |
Defined in Generic.Random.DerivingVia Methods (==) :: GenericArbitrarySingle a -> GenericArbitrarySingle a -> Bool # (/=) :: GenericArbitrarySingle a -> GenericArbitrarySingle a -> Bool # | |
Show a => Show (GenericArbitrarySingle a) Source # | |
Defined in Generic.Random.DerivingVia Methods showsPrec :: Int -> GenericArbitrarySingle a -> ShowS # show :: GenericArbitrarySingle a -> String # showList :: [GenericArbitrarySingle a] -> ShowS # | |
(GArbitrary UnsizedOpts a, Weights_ (Rep a) ~ L c0) => Arbitrary (GenericArbitrarySingle a) Source # | |
Defined in Generic.Random.DerivingVia Methods arbitrary :: Gen (GenericArbitrarySingle a) # shrink :: GenericArbitrarySingle a -> [GenericArbitrarySingle a] # |
newtype GenericArbitraryRec weights a Source #
Decrease size at every recursive call, but don't do anything different at size 0.
data X = ... deriving Arbitrary via (GenericArbitraryRec '[2, 3, 5] X)
N.B.: This replaces the generator for fields of type [t]
with
instead of listOf'
arbitrary
(i.e., listOf
arbitraryarbitrary
for
lists).
This newtype does no shrinking. To add generic shrinking, use AndShrinking
.
Uses genericArbitraryRec
.
Since: 1.5.0.0
Constructors
GenericArbitraryRec | |
Fields |
Instances
Eq a => Eq (GenericArbitraryRec weights a) Source # | |
Defined in Generic.Random.DerivingVia Methods (==) :: GenericArbitraryRec weights a -> GenericArbitraryRec weights a -> Bool # (/=) :: GenericArbitraryRec weights a -> GenericArbitraryRec weights a -> Bool # | |
Show a => Show (GenericArbitraryRec weights a) Source # | |
Defined in Generic.Random.DerivingVia Methods showsPrec :: Int -> GenericArbitraryRec weights a -> ShowS # show :: GenericArbitraryRec weights a -> String # showList :: [GenericArbitraryRec weights a] -> ShowS # | |
(GArbitrary SizedOptsDef a, TypeLevelWeights' weights a) => Arbitrary (GenericArbitraryRec weights a) Source # | |
Defined in Generic.Random.DerivingVia Methods arbitrary :: Gen (GenericArbitraryRec weights a) # shrink :: GenericArbitraryRec weights a -> [GenericArbitraryRec weights a] # |
newtype GenericArbitraryG genList weights a Source #
GenericArbitrary
with explicit generators.
Example
data X = ... deriving Arbitrary via (GenericArbitraryG CustomGens '[2, 3, 5] X)
where, for example, custom generators to override String
and Int
fields
might look as follows:
type CustomGens = CustomString :+
CustomInt
Note on multiple matches
Multiple generators may match a given field: the first will be chosen.
This newtype does no shrinking. To add generic shrinking, use AndShrinking
.
Uses genericArbitraryG
.
Since: 1.5.0.0
Constructors
GenericArbitraryG | |
Fields
|
Instances
Eq a => Eq (GenericArbitraryG genList weights a) Source # | |
Defined in Generic.Random.DerivingVia Methods (==) :: GenericArbitraryG genList weights a -> GenericArbitraryG genList weights a -> Bool # (/=) :: GenericArbitraryG genList weights a -> GenericArbitraryG genList weights a -> Bool # | |
Show a => Show (GenericArbitraryG genList weights a) Source # | |
Defined in Generic.Random.DerivingVia Methods showsPrec :: Int -> GenericArbitraryG genList weights a -> ShowS # show :: GenericArbitraryG genList weights a -> String # showList :: [GenericArbitraryG genList weights a] -> ShowS # | |
(GArbitrary (SetGens genList UnsizedOpts) a, GUniformWeight a, TypeLevelWeights' weights a, TypeLevelGenList genList', genList ~ TypeLevelGenList' genList') => Arbitrary (GenericArbitraryG genList' weights a) Source # | |
Defined in Generic.Random.DerivingVia Methods arbitrary :: Gen (GenericArbitraryG genList' weights a) # shrink :: GenericArbitraryG genList' weights a -> [GenericArbitraryG genList' weights a] # |
newtype GenericArbitraryUG genList a Source #
GenericArbitraryU
with explicit generators.
See also GenericArbitraryG
.
This newtype does no shrinking. To add generic shrinking, use AndShrinking
.
Uses genericArbitraryUG
.
Since: 1.5.0.0
Constructors
GenericArbitraryUG | |
Fields
|
Instances
Eq a => Eq (GenericArbitraryUG genList a) Source # | |
Defined in Generic.Random.DerivingVia Methods (==) :: GenericArbitraryUG genList a -> GenericArbitraryUG genList a -> Bool # (/=) :: GenericArbitraryUG genList a -> GenericArbitraryUG genList a -> Bool # | |
Show a => Show (GenericArbitraryUG genList a) Source # | |
Defined in Generic.Random.DerivingVia Methods showsPrec :: Int -> GenericArbitraryUG genList a -> ShowS # show :: GenericArbitraryUG genList a -> String # showList :: [GenericArbitraryUG genList a] -> ShowS # | |
(GArbitrary (SetGens genList UnsizedOpts) a, GUniformWeight a, TypeLevelGenList genList', genList ~ TypeLevelGenList' genList') => Arbitrary (GenericArbitraryUG genList' a) Source # | |
Defined in Generic.Random.DerivingVia Methods arbitrary :: Gen (GenericArbitraryUG genList' a) # shrink :: GenericArbitraryUG genList' a -> [GenericArbitraryUG genList' a] # |
newtype GenericArbitrarySingleG genList a Source #
genericArbitrarySingle
with explicit generators.
See also GenericArbitraryG
.
This newtype does no shrinking. To add generic shrinking, use AndShrinking
.
Uses genericArbitrarySingleG
.
Since: 1.5.0.0
Constructors
GenericArbitrarySingleG | |
Fields |
Instances
Eq a => Eq (GenericArbitrarySingleG genList a) Source # | |
Defined in Generic.Random.DerivingVia Methods (==) :: GenericArbitrarySingleG genList a -> GenericArbitrarySingleG genList a -> Bool # (/=) :: GenericArbitrarySingleG genList a -> GenericArbitrarySingleG genList a -> Bool # | |
Show a => Show (GenericArbitrarySingleG genList a) Source # | |
Defined in Generic.Random.DerivingVia Methods showsPrec :: Int -> GenericArbitrarySingleG genList a -> ShowS # show :: GenericArbitrarySingleG genList a -> String # showList :: [GenericArbitrarySingleG genList a] -> ShowS # | |
(GArbitrary (SetGens genList UnsizedOpts) a, Weights_ (Rep a) ~ L c0, TypeLevelGenList genList', genList ~ TypeLevelGenList' genList') => Arbitrary (GenericArbitrarySingleG genList' a) Source # | |
Defined in Generic.Random.DerivingVia Methods arbitrary :: Gen (GenericArbitrarySingleG genList' a) # shrink :: GenericArbitrarySingleG genList' a -> [GenericArbitrarySingleG genList' a] # |
newtype GenericArbitraryRecG genList weights a Source #
genericArbitraryRec
with explicit generators.
See also genericArbitraryG
.
This newtype does no shrinking. To add generic shrinking, use AndShrinking
.
Uses genericArbitraryRecG
.
Since: 1.5.0.0
Constructors
GenericArbitraryRecG | |
Fields |
Instances
newtype GenericArbitraryWith opts weights a Source #
General generic generator with custom options.
This newtype does no shrinking. To add generic shrinking, use AndShrinking
.
Uses genericArbitraryWith
.
Since: 1.5.0.0
Constructors
GenericArbitraryWith | |
Fields |
Instances
Eq a => Eq (GenericArbitraryWith opts weights a) Source # | |
Defined in Generic.Random.DerivingVia Methods (==) :: GenericArbitraryWith opts weights a -> GenericArbitraryWith opts weights a -> Bool # (/=) :: GenericArbitraryWith opts weights a -> GenericArbitraryWith opts weights a -> Bool # | |
Show a => Show (GenericArbitraryWith opts weights a) Source # | |
Defined in Generic.Random.DerivingVia Methods showsPrec :: Int -> GenericArbitraryWith opts weights a -> ShowS # show :: GenericArbitraryWith opts weights a -> String # showList :: [GenericArbitraryWith opts weights a] -> ShowS # | |
(GArbitrary opts a, TypeLevelWeights' weights a, TypeLevelOpts opts', opts ~ TypeLevelOpts' opts') => Arbitrary (GenericArbitraryWith opts' weights a) Source # | |
Defined in Generic.Random.DerivingVia Methods arbitrary :: Gen (GenericArbitraryWith opts' weights a) # shrink :: GenericArbitraryWith opts' weights a -> [GenericArbitraryWith opts' weights a] # |
newtype AndShrinking f a Source #
Add generic shrinking to a newtype wrapper for Arbitrary
, using genericShrink
.
data X = ... deriving Arbitrary via (GenericArbitrary
'[1,2,3] `AndShrinking
` X)
Equivalent to:
instance Arbitrary X where arbitrary =genericArbitrary
(1 % 2 % 3 % ()) shrink =genericShrink
Since: 1.5.0.0
Constructors
AndShrinking a |
Instances
Eq a => Eq (AndShrinking f a) Source # | |
Defined in Generic.Random.DerivingVia Methods (==) :: AndShrinking f a -> AndShrinking f a -> Bool # (/=) :: AndShrinking f a -> AndShrinking f a -> Bool # | |
Show a => Show (AndShrinking f a) Source # | |
Defined in Generic.Random.DerivingVia Methods showsPrec :: Int -> AndShrinking f a -> ShowS # show :: AndShrinking f a -> String # showList :: [AndShrinking f a] -> ShowS # | |
(Arbitrary (f a), Coercible (f a) a, Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) => Arbitrary (AndShrinking f a) Source # | |
Defined in Generic.Random.DerivingVia |
Helpers typeclasses
class TypeLevelGenList a where Source #
Since: 1.5.0.0
Associated Types
type TypeLevelGenList' a :: Type Source #
Methods
toGenList :: Proxy a -> TypeLevelGenList' a Source #
Instances
Arbitrary a => TypeLevelGenList (Gen a :: Type) Source # | |
Defined in Generic.Random.DerivingVia Associated Types type TypeLevelGenList' (Gen a) Source # | |
(TypeLevelGenList a, TypeLevelGenList b) => TypeLevelGenList (a :+ b :: Type) Source # | |
Defined in Generic.Random.DerivingVia Associated Types type TypeLevelGenList' (a :+ b) Source # |
class TypeLevelOpts a where Source #
Since: 1.5.0.0
Associated Types
type TypeLevelOpts' a :: Type Source #
Methods
toOpts :: Proxy a -> TypeLevelOpts' a Source #