generic-random-1.2.0.0: Generic random generators

Safe HaskellNone
LanguageHaskell2010

Generic.Random.Internal.Generic

Contents

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 fields of type [t] with listOf' arbitrary.

genericArbitraryG :: GArbitrary (SetGens genList UnsizedOpts) a => genList -> Weights a -> Gen a Source #

genericArbitrary with explicit generators.

Example

genericArbitraryG customGens (17 % 19 % ())

where, for example to override generators for String and Int fields,

customGens :: GenList '[String, Int]
customGens =
  (filter (/= '\NUL') <$> arbitrary) :@
  (getNonNegative <$> arbitrary) :@
  Nil

Note on multiple matches

If the list contains multiple matching types for a field x of type a (i.e., either a or Field "x" a), the generator for the first match will be picked.

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 :: * -> *) :: * 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

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

Methods

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

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

Associated Types

type Prec (a :| b) r :: * Source #

Methods

(%.) :: W (First (a :| b)) -> Prec (a :| b) r -> (a :| b, Int, r) Source #

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

data L (c :: Symbol) Source #

Constructors

L 

Instances

UniformWeight (L c) Source # 

Methods

uniformWeight :: (L c, Int) Source #

WeightBuilder (L c) Source # 

Associated Types

type Prec (L c) r :: * Source #

Methods

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

type Prec (L c) r Source # 
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

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

Num (W c) Source # 

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 #

Minimal complete definition

(%)

Methods

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

A binary constructor for building up trees of weights.

Instances

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

Methods

(%) :: W (First' (Weights a)) -> Prec' (Weights a) -> Weights a Source #

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

Methods

(%) :: W (First' (a, Int, r)) -> Prec' (a, Int, r) -> (a, Int, r) Source #

class WeightBuilder a where Source #

Minimal complete definition

(%.)

Associated Types

type Prec a r Source #

Methods

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

Instances

WeightBuilder () Source # 

Associated Types

type Prec () r :: * Source #

Methods

(%.) :: W (First ()) -> Prec () r -> ((), Int, r) Source #

WeightBuilder (L c) Source # 

Associated Types

type Prec (L c) r :: * Source #

Methods

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

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

Associated Types

type Prec (a :| b) r :: * Source #

Methods

(%.) :: W (First (a :| b)) -> Prec (a :| b) r -> (a :| b, Int, r) Source #

class UniformWeight a where Source #

Minimal complete definition

uniformWeight

Methods

uniformWeight :: (a, Int) Source #

Instances

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

Derived uniform distribution of constructors for a.

newtype Options (s :: Sizing) (genList :: Type) Source #

Type-level options for GArbitrary.

Constructors

Options 

Fields

Instances

HasGenerators (Options s g) Source # 
type SetGens g (Options s _g) Source # 
type SetGens g (Options s _g) = Options s g
type GeneratorsOf (Options _s g) Source # 
type GeneratorsOf (Options _s g) = g
type SizingOf (Options s _g) Source # 
type SizingOf (Options s _g) = s

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

data Sizing Source #

Whether to decrease the size parameter before generating fields.

Constructors

Sized 
Unsized 

type family SizingOf opts :: Sizing Source #

Instances

type SizingOf (Options s _g) Source # 
type SizingOf (Options s _g) = s

proxySizing :: opts -> Proxy (SizingOf opts) Source #

data a :+ b infixr 1 Source #

Heterogeneous list of generators.

Constructors

a :+ b infixr 1 

Instances

ArbitraryOr fg g sel a => ArbitraryOr fg ((:+) b g) sel a Source # 

Methods

arbitraryOr :: proxy sel -> fg -> (b :+ g) -> Gen a Source #

ArbitraryOr fg ((:+) (Gen a) g) sel a Source # 

Methods

arbitraryOr :: proxy sel -> fg -> (Gen a :+ g) -> Gen a Source #

ArbitraryOr fg fg (Nothing Symbol) a => ArbitraryOr fg ((:+) (Gen1 f) g) sel (f a) Source # 

Methods

arbitraryOr :: proxy sel -> fg -> (Gen1 f :+ g) -> Gen (f a) Source #

ArbitraryOr fg ((:+) (Gen1_ k f) g) sel (f a) Source # 

Methods

arbitraryOr :: proxy sel -> fg -> (Gen1_ k f :+ g) -> Gen (f a) Source #

ArbitraryOr fg ((:+) (FieldGen n a) g) (Just Symbol n) a Source # 

Methods

arbitraryOr :: proxy (Just Symbol n) -> fg -> (FieldGen n a :+ g) -> Gen a Source #

type family GeneratorsOf opts :: Type Source #

Instances

type GeneratorsOf (Options _s g) Source # 
type GeneratorsOf (Options _s g) = g

class HasGenerators opts where Source #

Minimal complete definition

generators

Methods

generators :: opts -> GeneratorsOf opts Source #

Instances

setGenerators :: genList -> Options s g0 -> Options s genList Source #

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

Instances

type SetGens g (Options s _g) Source # 
type SetGens g (Options s _g) = Options s g

newtype FieldGen (s :: Symbol) a Source #

A generator which overrides a specific field named s.

Available only for base >= 4.9.

Constructors

FieldGen 

Fields

Instances

ArbitraryOr fg ((:+) (FieldGen n a) g) (Just Symbol n) a Source # 

Methods

arbitraryOr :: proxy (Just Symbol n) -> fg -> (FieldGen n a :+ g) -> Gen a Source #

fieldGen :: proxy s -> Gen a -> FieldGen s a Source #

Field constructor with the field name given via a proxy.

newtype Gen1 f Source #

Generators for containers of kind * -> *, parameterized by the generator for each element.

Constructors

Gen1 

Fields

Instances

ArbitraryOr fg fg (Nothing Symbol) a => ArbitraryOr fg ((:+) (Gen1 f) g) sel (f a) Source # 

Methods

arbitraryOr :: proxy sel -> fg -> (Gen1 f :+ g) -> Gen (f a) Source #

newtype Gen1_ f Source #

Generators for unary type constructors that are not containers.

Constructors

Gen1_ 

Fields

Instances

ArbitraryOr fg ((:+) (Gen1_ k f) g) sel (f a) Source # 

Methods

arbitraryOr :: proxy sel -> fg -> (Gen1_ k f :+ g) -> 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

Minimal complete definition

ga

Methods

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

Instances

(GASum opts f, GASum opts g) => GA opts ((:+:) * f g) Source # 

Methods

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

GAProduct * (SizingOf opts) opts f => GA opts (M1 * C c f) Source # 

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 # 

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

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

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

class GASum opts f where Source #

Minimal complete definition

gaSum

Methods

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

Instances

(GASum opts f, GASum opts g) => GASum opts ((:+:) * f g) Source # 

Methods

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

GAProduct * (SizingOf opts) opts f => GASum opts (M1 * i c f) Source # 

Methods

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

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

Minimal complete definition

gaProduct

Methods

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

Instances

GAProduct' k opts f => GAProduct k Unsized opts f Source # 

Methods

gaProduct :: proxys opts -> f -> Gen (f p) Source #

(GAProduct' k opts f, KnownNat (Arity k f)) => GAProduct k Sized opts f Source # 

Methods

gaProduct :: proxys opts -> f -> Gen (f p) Source #

GAProduct k Sized opts (U1 k) Source # 

Methods

gaProduct :: proxys opts -> U1 k -> Gen (f p) Source #

GAProduct' k opts (S1 k d f) => GAProduct k Sized opts (S1 k d f) Source # 

Methods

gaProduct :: proxys opts -> S1 k d f -> Gen (f p) Source #

class GAProduct' opts f where Source #

Minimal complete definition

gaProduct'

Methods

gaProduct' :: opts -> Gen (f p) Source #

Instances

GAProduct' k opts (U1 k) Source # 

Methods

gaProduct' :: U1 k -> Gen (f p) Source #

(GAProduct' k opts f, GAProduct' k opts g) => GAProduct' k opts ((:*:) k f g) Source # 

Methods

gaProduct' :: (k :*: f) g -> Gen (f p) Source #

(HasGenerators opts, ArbitraryOr gs gs (SelectorName d) c, (~) Type gs (GeneratorsOf opts)) => GAProduct' k opts (S1 k d (K1 k i c)) Source # 

Methods

gaProduct' :: S1 k d (K1 k i c) -> Gen (f p) Source #

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

Equations

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

class ArbitraryOr (fullGenList :: Type) (genList :: Type) (sel :: Maybe Symbol) a where Source #

Minimal complete definition

arbitraryOr

Methods

arbitraryOr :: proxy sel -> fullGenList -> genList -> Gen a Source #

Instances

Arbitrary a => ArbitraryOr fg () sel a Source # 

Methods

arbitraryOr :: proxy sel -> fg -> () -> Gen a Source #

ArbitraryOr fg g sel a => ArbitraryOr fg ((:+) b g) sel a Source # 

Methods

arbitraryOr :: proxy sel -> fg -> (b :+ g) -> Gen a Source #

ArbitraryOr fg ((:+) (Gen a) g) sel a Source # 

Methods

arbitraryOr :: proxy sel -> fg -> (Gen a :+ g) -> Gen a Source #

ArbitraryOr fg fg (Nothing Symbol) a => ArbitraryOr fg ((:+) (Gen1 f) g) sel (f a) Source # 

Methods

arbitraryOr :: proxy sel -> fg -> (Gen1 f :+ g) -> Gen (f a) Source #

ArbitraryOr fg ((:+) (Gen1_ k f) g) sel (f a) Source # 

Methods

arbitraryOr :: proxy sel -> fg -> (Gen1_ k f :+ g) -> Gen (f a) Source #

ArbitraryOr fg ((:+) (FieldGen n a) g) (Just Symbol n) a Source # 

Methods

arbitraryOr :: proxy (Just Symbol n) -> fg -> (FieldGen n a :+ g) -> Gen a Source #

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

Instances

type SelectorName (MetaSel mn su ss ds) Source # 
type SelectorName (MetaSel mn su ss ds) = mn

newtype Weighted a Source #

Constructors

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

Instances

Functor Weighted Source # 

Methods

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

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

Applicative Weighted Source # 

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 # 

Methods

empty :: Weighted a #

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

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

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