generic-random-1.5.0.1: Generic random generators for QuickCheck
Safe HaskellNone
LanguageHaskell2010

Generic.Random.Internal.Generic

Description

Core implementation.

Warning

This is an internal module: it is not subject to any versioning policy, breaking changes can happen at any time.

If something here seems useful, please report it or create a pull request to export it from an external module.

Synopsis

Random generators

genericArbitrary Source #

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

genericArbitraryRec Source #

Arguments

:: GArbitrary SizedOptsDef a 
=> Weights a

List of weights for every constructor

-> Gen a 

Decrease size at every recursive call, but don't do anything different at size 0.

genericArbitraryRec (7 % 11 % 13 % ()) :: Gen a

N.B.: This replaces the generator for fields of type [t] with listOf' arbitrary instead of listOf arbitrary (i.e., arbitrary for lists).

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.

genericArbitraryRecG Source #

Arguments

:: GArbitrary (SetGens genList SizedOpts) a 
=> genList 
-> Weights a

List of weights for every constructor

-> Gen a 

genericArbitraryRec with explicit generators. See also genericArbitraryG.

genericArbitraryWith :: GArbitrary opts a => opts -> Weights a -> Gen a Source #

General generic generator with custom options.

Internal

type family Weights_ (f :: Type -> Type) :: Type where ... Source #

Equations

Weights_ (f :+: g) = Weights_ f :| Weights_ g 
Weights_ (M1 D _c f) = Weights_ f 
Weights_ (M1 C ('MetaCons c _i _j) _f) = L c 

data a :| b Source #

Constructors

N a Int b 

Instances

Instances details
(UniformWeight a, UniformWeight b) => UniformWeight (a :| b) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

uniformWeight :: (a :| b, Int) Source #

WeightBuilder a => WeightBuilder (a :| b) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Associated Types

type Prec (a :| b) r Source #

Methods

(%.) :: forall (c :: Symbol) r. c ~ First (a :| b) => W c -> Prec (a :| b) r -> (a :| b, Int, r) Source #

type Prec (a :| b) r Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type Prec (a :| b) r = Prec a (b, Int, r)

data L (c :: Symbol) Source #

Constructors

L 

Instances

Instances details
UniformWeight (L c) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

uniformWeight :: (L c, Int) Source #

WeightBuilder (L c) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Associated Types

type Prec (L c) r Source #

Methods

(%.) :: forall (c0 :: Symbol) r. c0 ~ First (L c) => W c0 -> Prec (L c) r -> (L c, Int, r) Source #

type Prec (L c) r Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type Prec (L c) r = r

data Weights a Source #

Trees of weights assigned to constructors of type a, rescaled to obtain a probability distribution.

Two ways of constructing them.

(x1 % x2 % ... % xn % ()) :: Weights a
uniform :: Weights a

Using (%), there must be exactly as many weights as there are constructors.

uniform is equivalent to (1 % ... % 1 % ()) (automatically fills out the right number of 1s).

Constructors

Weights (Weights_ (Rep a)) Int 

Instances

Instances details
WeightBuilder (Weights_ (Rep a)) => WeightBuilder' (Weights a) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

(%) :: forall (c :: Symbol). c ~ First' (Weights a) => W c -> Prec' (Weights a) -> Weights a Source #

newtype W (c :: Symbol) Source #

Type of a single weight, tagged with the name of the associated constructor for additional compile-time checking.

((9 :: W "Leaf") % (8 :: W "Node") % ())

Constructors

W Int 

Instances

Instances details
Num (W c) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

(+) :: W c -> W c -> W c #

(-) :: W c -> W c -> W c #

(*) :: W c -> W c -> W c #

negate :: W c -> W c #

abs :: W c -> W c #

signum :: W c -> W c #

fromInteger :: Integer -> W c #

weights :: (Weights_ (Rep a), Int, ()) -> Weights a Source #

A smart constructor to specify a custom distribution. It can be omitted for the % operator is overloaded to insert it.

uniform :: UniformWeight_ (Rep a) => Weights a Source #

Uniform distribution.

type family First a :: Symbol where ... Source #

Equations

First (a :| _b) = First a 
First (L c) = c 

type family First' w where ... Source #

Equations

First' (Weights a) = First (Weights_ (Rep a)) 
First' (a, Int, r) = First a 

type family Prec' w where ... Source #

Equations

Prec' (Weights a) = Prec (Weights_ (Rep a)) () 
Prec' (a, Int, r) = Prec a r 

class WeightBuilder' w where Source #

Methods

(%) :: c ~ First' w => W c -> Prec' w -> w infixr 1 Source #

A binary constructor for building up trees of weights.

Instances

Instances details
WeightBuilder (Weights_ (Rep a)) => WeightBuilder' (Weights a) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

(%) :: forall (c :: Symbol). c ~ First' (Weights a) => W c -> Prec' (Weights a) -> Weights a Source #

WeightBuilder a => WeightBuilder' (a, Int, r) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

(%) :: forall (c :: Symbol). c ~ First' (a, Int, r) => W c -> Prec' (a, Int, r) -> (a, Int, r) Source #

class WeightBuilder a where Source #

Associated Types

type Prec a r Source #

Methods

(%.) :: c ~ First a => W c -> Prec a r -> (a, Int, r) Source #

Instances

Instances details
WeightBuilder () Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Associated Types

type Prec () r Source #

Methods

(%.) :: forall (c :: Symbol) r. c ~ First () => W c -> Prec () r -> ((), Int, r) Source #

WeightBuilder (L c) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Associated Types

type Prec (L c) r Source #

Methods

(%.) :: forall (c0 :: Symbol) r. c0 ~ First (L c) => W c0 -> Prec (L c) r -> (L c, Int, r) Source #

WeightBuilder a => WeightBuilder (a :| b) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Associated Types

type Prec (a :| b) r Source #

Methods

(%.) :: forall (c :: Symbol) r. c ~ First (a :| b) => W c -> Prec (a :| b) r -> (a :| b, Int, r) Source #

class UniformWeight a where Source #

Methods

uniformWeight :: (a, Int) Source #

Instances

Instances details
UniformWeight () Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

uniformWeight :: ((), Int) Source #

UniformWeight (L c) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

uniformWeight :: (L c, Int) Source #

(UniformWeight a, UniformWeight b) => UniformWeight (a :| b) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

uniformWeight :: (a :| b, Int) Source #

class UniformWeight (Weights_ f) => UniformWeight_ f Source #

Instances

Instances details
UniformWeight (Weights_ f) => UniformWeight_ f Source # 
Instance details

Defined in Generic.Random.Internal.Generic

class UniformWeight_ (Rep a) => GUniformWeight a Source #

Derived uniform distribution of constructors for a.

Instances

Instances details
UniformWeight_ (Rep a) => GUniformWeight a Source # 
Instance details

Defined in Generic.Random.Internal.Generic

newtype 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 (<+)).

Constructors

Options 

Fields

Instances

Instances details
HasGenerators (Options c s g) Source # 
Instance details

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 # 
Instance details

Defined in Generic.Random.Internal.Generic

type SetOptions (g :: Type) (Options c s _g) = Options c s g
type SetOptions (c :: Coherence) (Options _c s g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type SetOptions (c :: Coherence) (Options _c s g) = Options c s g
type SetOptions (s :: Sizing) (Options c _s g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type SetOptions (s :: Sizing) (Options c _s g) = Options c s g
type SetGens g (Options c s _g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type SetGens g (Options c s _g) = Options c s g
type GeneratorsOf (Options _c _s g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type GeneratorsOf (Options _c _s g) = g
type CoherenceOf (Options c _s _g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type CoherenceOf (Options c _s _g) = c
type SetUnsized (Options c s g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type SetUnsized (Options c s g) = Options c 'Unsized g
type SetSized (Options c s g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type SetSized (Options c s g) = Options c 'Sized g
type SizingOf (Options _c s _g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type SizingOf (Options _c s _g) = s

type family SetOptions (x :: k) (o :: Type) :: Type Source #

Setter for Options.

This subsumes the other setters: SetSized, SetUnsized, SetGens.

Since: 1.4.0.0

Instances

Instances details
type SetOptions (g :: Type) (Options c s _g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type SetOptions (g :: Type) (Options c s _g) = Options c s g
type SetOptions (c :: Coherence) (Options _c s g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type SetOptions (c :: Coherence) (Options _c s g) = Options c s g
type SetOptions (s :: Sizing) (Options c _s g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type SetOptions (s :: Sizing) (Options c _s g) = Options c s g

type (<+) o x = SetOptions x o infixl 1 Source #

Infix flipped synonym for Options.

Since: 1.4.0.0

type CohUnsizedOpts = Options 'COHERENT 'Unsized () Source #

Like UnsizedOpts, but using coherent instances by default.

Since: 1.4.0.0

type CohSizedOpts = Options 'COHERENT 'Sized () Source #

Like SizedOpts, but using coherent instances by default.

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

unsizedOpts :: UnsizedOpts Source #

Default options for unsized generators.

sizedOpts :: SizedOpts Source #

Default options for sized generators.

sizedOptsDef :: SizedOptsDef Source #

Default options overriding the list generator using listOf'.

cohUnsizedOpts :: CohUnsizedOpts Source #

Like unsizedOpts, but using coherent instances by default.

cohSizedOpts :: CohSizedOpts Source #

Like sizedOpts but using coherent instances by default.

data Sizing Source #

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

Instances details
type SetOptions (s :: Sizing) (Options c _s g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type SetOptions (s :: Sizing) (Options c _s g) = Options c s g

type family SizingOf opts :: Sizing Source #

Instances

Instances details
type SizingOf (Options _c s _g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type SizingOf (Options _c s _g) = s

type family SetSized (o :: Type) :: Type Source #

Instances

Instances details
type SetSized (Options c s g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type SetSized (Options c s g) = Options c 'Sized g

type family SetUnsized (o :: Type) :: Type Source #

Instances

Instances details
type SetUnsized (Options c s g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type SetUnsized (Options c s g) = Options c 'Unsized g

data Coherence Source #

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

Expand

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 Incoherent).

Instances

Instances details
type SetOptions (c :: Coherence) (Options _c s g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type SetOptions (c :: Coherence) (Options _c s g) = Options c s g

type family CoherenceOf (o :: Type) :: Coherence Source #

Instances

Instances details
type CoherenceOf (Options c _s _g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type CoherenceOf (Options c _s _g) = c

newtype Incoherent g Source #

Match this generator incoherently when the COHERENT option is set.

Constructors

Incoherent g 

Instances

Instances details
FindGen ('Match 'INCOHERENT) s g gs a => FindGen 'Shift s (Incoherent g) gs a Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy 'Shift, Proxy s, FullGenListOf s) -> Incoherent g -> gs -> Gen a Source #

data a :+ b infixr 1 Source #

Heterogeneous list of generators.

Constructors

a :+ b infixr 1 

Instances

Instances details
FindGen 'Shift s b g a => FindGen 'Shift s () (b :+ g) a Source #

Examine the next candidate

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy 'Shift, Proxy s, FullGenListOf s) -> () -> (b :+ g) -> Gen a Source #

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.

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy 'Shift, Proxy s, FullGenListOf s) -> (g :+ h) -> gs -> Gen a Source #

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

Defined in Generic.Random.DerivingVia

Associated Types

type TypeLevelGenList' (a :+ b) Source #

Methods

toGenList :: Proxy (a :+ b) -> TypeLevelGenList' (a :+ b) Source #

type TypeLevelGenList' (a :+ b :: Type) Source # 
Instance details

Defined in Generic.Random.DerivingVia

type family GeneratorsOf opts :: Type Source #

Instances

Instances details
type GeneratorsOf (Options _c _s g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type GeneratorsOf (Options _c _s g) = g

class HasGenerators opts where Source #

Methods

generators :: opts -> GeneratorsOf opts Source #

Instances

Instances details
HasGenerators (Options c s g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

generators :: Options c s g -> GeneratorsOf (Options c s g) Source #

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.

type family SetGens (g :: Type) opts Source #

Instances

Instances details
type SetGens g (Options c s _g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type SetGens g (Options c s _g) = Options c s g

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

Instances

Instances details
a ~ a' => FindGen ('MatchCoh 'True) s (FieldGen sn a) gs a' Source #

Matching custom generator for field s.

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('MatchCoh 'True), Proxy s, FullGenListOf s) -> FieldGen sn a -> gs -> Gen a' Source #

a ~ a' => FindGen ('Match 'INCOHERENT) ('S _fg _coh '(con, i, 'Just s)) (FieldGen s a) gs a' Source #

Matching custom generator for field s.

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('Match 'INCOHERENT), Proxy ('S _fg _coh '(con, i, 'Just s)), FullGenListOf ('S _fg _coh '(con, i, 'Just s))) -> FieldGen s a -> gs -> Gen a' Source #

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

Instances details
a ~ a' => FindGen ('MatchCoh 'True) s (ConstrGen c i a) gs a' Source #

Matching custom generator for i-th field of constructor c.

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('MatchCoh 'True), Proxy s, FullGenListOf s) -> ConstrGen c i a -> gs -> Gen a' Source #

a ~ a' => FindGen ('Match 'INCOHERENT) ('S _fg _coh '('Just c, i, s)) (ConstrGen c i a) gs a' Source #

Matching custom generator for i-th field of constructor c.

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('Match 'INCOHERENT), Proxy ('S _fg _coh '('Just c, i, s)), FullGenListOf ('S _fg _coh '('Just c, i, s))) -> ConstrGen c i a -> gs -> Gen a' Source #

constrGen :: proxy '(c, i) -> Gen a -> ConstrGen c i a Source #

ConstrGen constructor with the constructor name given via a proxy.

newtype Gen1 f Source #

Custom generators for "containers" of kind Type -> Type, parameterized by the generator for "contained elements".

A custom generator Gen1 f will be used for any field whose type has the form f 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.

Constructors

Gen1 

Fields

Instances

Instances details
(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 # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('MatchCoh 'True), Proxy ('S fg coh _sel), FullGenListOf ('S fg coh _sel)) -> Gen1 f -> gs -> Gen 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 f. Start the search for containee a, discarding field information.

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('Match 'INCOHERENT), Proxy ('S fg coh _sel), FullGenListOf ('S fg coh _sel)) -> Gen1 f -> gs -> Gen (f a) Source #

newtype Gen1_ f Source #

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 Gen1_ f will be used for any field whose type has the form f x.

Constructors

Gen1_ 

Fields

Instances

Instances details
f x ~ a' => FindGen ('MatchCoh 'True) s (Gen1_ f) gs a' Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('MatchCoh 'True), Proxy s, FullGenListOf s) -> Gen1_ f -> gs -> Gen a' Source #

FindGen ('Match 'INCOHERENT) s (Gen1_ f) gs (f a) Source #

Matching custom generator for non-container f.

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('Match 'INCOHERENT), Proxy s, FullGenListOf s) -> Gen1_ f -> gs -> Gen (f a) Source #

vectorOf' :: Int -> Gen a -> Gen [a] Source #

An alternative to vectorOf that divides the size parameter by the length of the list.

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

geom :: Int -> Gen Int Source #

Geometric distribution of parameter 1/(sqrt n + 1) (n >= 0).

class GA opts f where Source #

Generic Arbitrary

Methods

ga :: opts -> Weights_ f -> Int -> Gen (f p) Source #

Instances

Instances details
(GASum opts f, GASum opts g) => GA opts (f :+: g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

ga :: opts -> Weights_ (f :+: g) -> Int -> Gen ((f :+: g) p) Source #

GAProduct (SizingOf opts) (Name c) opts f => GA opts (M1 C c f) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

ga :: opts -> Weights_ (M1 C c f) -> Int -> Gen (M1 C c f p) Source #

GA opts f => GA opts (M1 D c f) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

ga :: opts -> Weights_ (M1 D c f) -> Int -> Gen (M1 D c f p) Source #

class (Generic a, GA opts (Rep a)) => GArbitrary opts a Source #

Generic Arbitrary

Instances

Instances details
(Generic a, GA opts (Rep a)) => GArbitrary opts a Source # 
Instance details

Defined in Generic.Random.Internal.Generic

gaSum' :: GASum opts f => opts -> Weights_ f -> Int -> Gen (f p) Source #

class GASum opts f where Source #

Methods

gaSum :: opts -> Int -> Weights_ f -> Gen (f p) Source #

Instances

Instances details
(GASum opts f, GASum opts g) => GASum opts (f :+: g) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

gaSum :: opts -> Int -> Weights_ (f :+: g) -> Gen ((f :+: g) p) Source #

GAProduct (SizingOf opts) (Name c) opts f => GASum opts (M1 C c f) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

gaSum :: opts -> Int -> Weights_ (M1 C c f) -> Gen (M1 C c f p) Source #

class GAProduct (s :: Sizing) (c :: Maybe Symbol) opts f where Source #

Methods

gaProduct :: proxys '(s, c) -> opts -> Gen (f p) Source #

Instances

Instances details
GAProduct' c 0 opts f => GAProduct 'Unsized c opts (f :: k -> Type) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

gaProduct :: forall proxys (p :: k0). proxys '('Unsized, c) -> opts -> Gen (f p) Source #

(GAProduct' c 0 opts f, KnownNat (Arity f)) => GAProduct 'Sized c opts (f :: k -> Type) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

gaProduct :: forall proxys (p :: k0). proxys '('Sized, c) -> opts -> Gen (f p) Source #

GAProduct 'Sized c opts (U1 :: k -> Type) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

gaProduct :: forall proxys (p :: k0). proxys '('Sized, c) -> opts -> Gen (U1 p) Source #

GAProduct' c 0 opts (S1 d f) => GAProduct 'Sized c opts (S1 d f :: k -> Type) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

gaProduct :: forall proxys (p :: k0). proxys '('Sized, c) -> opts -> Gen (S1 d f p) Source #

class GAProduct' (c :: Maybe Symbol) (i :: Nat) opts f where Source #

Methods

gaProduct' :: proxy '(c, i) -> opts -> Gen (f p) Source #

Instances

Instances details
GAProduct' c i opts (U1 :: k -> Type) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

gaProduct' :: forall proxy (p :: k0). proxy '(c, i) -> opts -> Gen (U1 p) Source #

(GAProduct' c i opts f, GAProduct' c (i + Arity f) opts g) => GAProduct' c i opts (f :*: g :: k -> Type) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

gaProduct' :: forall proxy (p :: k0). proxy '(c, i) -> opts -> Gen ((f :*: g) p) Source #

(HasGenerators opts, FindGen 'Shift ('S gs coh '(c, i, Name d)) () gs a, gs ~ GeneratorsOf opts, coh ~ CoherenceOf opts) => GAProduct' c i opts (S1 d (K1 _k a :: k -> Type) :: k -> Type) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

gaProduct' :: forall proxy (p :: k0). proxy '(c, i) -> opts -> Gen (S1 d (K1 _k a) p) Source #

type family Arity f :: Nat where ... Source #

Equations

Arity (f :*: g) = Arity f + Arity g 
Arity (M1 _i _c _f) = 1 

class FindGen (i :: AInstr) (s :: AStore) (g :: Type) (gs :: Type) (a :: Type) where Source #

Given a list of custom generators g :+ gs, find one that applies, or use Arbitrary a by default.

g and gs follow this little state machine:

          g,      gs | result
---------------------+-----------------------------
         (),      () | END
         (), g :+ gs | g, gs
         (),      g  | g, () when g is not (_ :+ _)
     g :+ h,      gs | g, h :+ gs
      Gen a,      gs | END if g matches, else ((), gs)
 FieldGen a,      gs | idem
ConstrGen a,      gs | idem
     Gen1 a,      gs | idem
    Gen1_ a,      gs | idem

Methods

findGen :: (Proxy i, Proxy s, FullGenListOf s) -> g -> gs -> Gen a Source #

Instances

Instances details
FindGen ('Match (ACoherenceOf s)) s g gs a => FindGen 'Shift s g gs a Source #

If none of the above matches, then g should be a simple generator, and we test whether it matches the type a.

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy 'Shift, Proxy s, FullGenListOf s) -> g -> gs -> Gen a Source #

FindGen 'Shift s g () a => FindGen 'Shift s () g a Source #

Examine the last candidate (g is not of the form _ :+ _)

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy 'Shift, Proxy s, FullGenListOf s) -> () -> g -> Gen a Source #

Arbitrary a => FindGen 'Shift s () () a Source #

All candidates have been exhausted

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy 'Shift, Proxy s, FullGenListOf s) -> () -> () -> Gen a Source #

FindGen 'Shift s b g a => FindGen 'Shift s () (b :+ g) a Source #

Examine the next candidate

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy 'Shift, Proxy s, FullGenListOf s) -> () -> (b :+ g) -> Gen a Source #

FindGen ('Match 'INCOHERENT) s g gs a => FindGen 'Shift s (Incoherent g) gs a Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy 'Shift, Proxy s, FullGenListOf s) -> Incoherent g -> gs -> Gen a Source #

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.

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy 'Shift, Proxy s, FullGenListOf s) -> (g :+ h) -> gs -> Gen a Source #

FindGen 'Shift s () gs a => FindGen ('Match 'INCOHERENT) s _g gs a Source #

None of the INCOHERENT instances match, discard the candidate g and look at the rest of the list gs.

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('Match 'INCOHERENT), Proxy s, FullGenListOf s) -> _g -> gs -> Gen a Source #

FindGen ('MatchCoh (Matches (ASelOf s) g a)) s g gs a => FindGen ('Match 'COHERENT) s g gs a Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('Match 'COHERENT), Proxy s, FullGenListOf s) -> g -> gs -> Gen a Source #

FindGen 'Shift s () gs a => FindGen ('MatchCoh 'False) s _g gs a Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('MatchCoh 'False), Proxy s, FullGenListOf s) -> _g -> gs -> Gen a Source #

FindGen ('Match 'INCOHERENT) s (Gen a) gs a Source #

Matching custom generator for a.

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('Match 'INCOHERENT), Proxy s, FullGenListOf s) -> Gen a -> gs -> Gen a Source #

a ~ a' => FindGen ('MatchCoh 'True) s (Gen a) gs a' Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('MatchCoh 'True), Proxy s, FullGenListOf s) -> Gen a -> gs -> Gen a' Source #

a ~ a' => FindGen ('MatchCoh 'True) s (FieldGen sn a) gs a' Source #

Matching custom generator for field s.

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('MatchCoh 'True), Proxy s, FullGenListOf s) -> FieldGen sn a -> gs -> Gen a' Source #

f x ~ a' => FindGen ('MatchCoh 'True) s (Gen1_ f) gs a' Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('MatchCoh 'True), Proxy s, FullGenListOf s) -> Gen1_ f -> gs -> Gen a' Source #

FindGen ('Match 'INCOHERENT) s (Gen1_ f) gs (f a) Source #

Matching custom generator for non-container f.

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('Match 'INCOHERENT), Proxy s, FullGenListOf s) -> Gen1_ f -> gs -> Gen (f a) Source #

a ~ a' => FindGen ('MatchCoh 'True) s (ConstrGen c i a) gs a' Source #

Matching custom generator for i-th field of constructor c.

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('MatchCoh 'True), Proxy s, FullGenListOf s) -> ConstrGen c i a -> gs -> Gen a' Source #

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

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('MatchCoh 'True), Proxy ('S fg coh _sel), FullGenListOf ('S fg coh _sel)) -> Gen1 f -> gs -> Gen 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 f. Start the search for containee a, discarding field information.

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('Match 'INCOHERENT), Proxy ('S fg coh _sel), FullGenListOf ('S fg coh _sel)) -> Gen1 f -> gs -> Gen (f a) Source #

a ~ a' => FindGen ('Match 'INCOHERENT) ('S _fg _coh '(con, i, 'Just s)) (FieldGen s a) gs a' Source #

Matching custom generator for field s.

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('Match 'INCOHERENT), Proxy ('S _fg _coh '(con, i, 'Just s)), FullGenListOf ('S _fg _coh '(con, i, 'Just s))) -> FieldGen s a -> gs -> Gen a' Source #

a ~ a' => FindGen ('Match 'INCOHERENT) ('S _fg _coh '('Just c, i, s)) (ConstrGen c i a) gs a' Source #

Matching custom generator for i-th field of constructor c.

Instance details

Defined in Generic.Random.Internal.Generic

Methods

findGen :: (Proxy ('Match 'INCOHERENT), Proxy ('S _fg _coh '('Just c, i, s)), FullGenListOf ('S _fg _coh '('Just c, i, s))) -> ConstrGen c i a -> gs -> Gen a' Source #

data AStore Source #

Constructors

S Type Coherence ASel 

type family FullGenListOf (s :: AStore) :: Type where ... Source #

Equations

FullGenListOf ('S fg _coh _sel) = fg 

type family ACoherenceOf (s :: AStore) :: Coherence where ... Source #

Equations

ACoherenceOf ('S _fg coh _sel) = coh 

type family ASelOf (s :: AStore) :: ASel where ... Source #

Equations

ASelOf ('S _fg _coh sel) = sel 

type DummySel = '('Nothing, 0, 'Nothing) Source #

type family Name (d :: Meta) :: Maybe Symbol Source #

Get the name contained in a Meta tag.

Instances

Instances details
type Name ('MetaCons n _f _s) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type Name ('MetaCons n _f _s) = 'Just n
type Name ('MetaSel mn su ss ds) Source # 
Instance details

Defined in Generic.Random.Internal.Generic

type Name ('MetaSel mn su ss ds) = mn

type family Matches (s :: ASel) (g :: Type) (a :: Type) :: Bool where ... Source #

Equations

Matches _sel (Gen b) a = b == a 
Matches _sel (Gen1_ f) (f a) = 'True 
Matches _sel (Gen1_ f) a = 'False 
Matches _sel (Gen1 f) (f a) = 'True 
Matches _sel (Gen1 f) a = 'False 
Matches '(_c, i, s) (FieldGen s1 b) a = (s == 'Just s1) && (b == a) 
Matches '(c, i, _s) (ConstrGen c1 j b) a = (c == 'Just c1) && ((i == j) && (b == a)) 

newtype Weighted a Source #

Constructors

Weighted (Maybe (Int -> Gen a, Int)) 

Instances

Instances details
Functor Weighted Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

fmap :: (a -> b) -> Weighted a -> Weighted b #

(<$) :: a -> Weighted b -> Weighted a #

Applicative Weighted Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

pure :: a -> Weighted a #

(<*>) :: Weighted (a -> b) -> Weighted a -> Weighted b #

liftA2 :: (a -> b -> c) -> Weighted a -> Weighted b -> Weighted c #

(*>) :: Weighted a -> Weighted b -> Weighted b #

(<*) :: Weighted a -> Weighted b -> Weighted a #

Alternative Weighted Source # 
Instance details

Defined in Generic.Random.Internal.Generic

Methods

empty :: Weighted a #

(<|>) :: Weighted a -> Weighted a -> Weighted a #

some :: Weighted a -> Weighted [a] #

many :: Weighted a -> Weighted [a] #