generic-random-1.2.0.0: Generic random generators

Safe HaskellNone
LanguageHaskell2010

Generic.Random

Contents

Description

Synopsis

Arbitrary implementations

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.

genericArbitrary' Source #

Arguments

:: (GArbitrary SizedOptsDef a, BaseCase a) 
=> Weights a

List of weights for every constructor

-> Gen a 

Decrease size to ensure termination for recursive types, looking for base cases once the size reaches 0.

genericArbitrary' (17 % 19 % 23 % ()) :: Gen a

N.B.: This replaces fields of type [t] with listOf' arbitrary.

genericArbitraryU' :: (GArbitrary SizedOptsDef a, BaseCase a, GUniformWeight a) => Gen a Source #

Equivalent to genericArbitrary' uniform.

genericArbitraryU :: 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.

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.

Minimal complete definition

baseCase

Methods

baseCase :: Gen a Source #

Generator of base cases.

Instances

BaseCaseSearching Nat a 0 => BaseCase a Source #

Overlappable

Methods

baseCase :: Gen a Source #

Specifying finite distributions

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

Instances

data 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") % ())

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 #

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

A binary constructor for building up trees of weights.

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

Uniform distribution.

Full options

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

Type-level options for GArbitrary.

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

sizedOpts :: SizedOpts Source #

Default options for sized generators.

sizedOptsDef :: SizedOptsDef Source #

Default options overriding the list generator using listOf'.

unsizedOpts :: UnsizedOpts Source #

Default options for unsized generators.

data Sizing Source #

Whether to decrease the size parameter before generating fields.

Constructors

Sized 
Unsized 

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 #

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 #

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

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

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

Derived uniform distribution of constructors for a.

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.