generic-random-1.0.0.0: Generic random generators

Safe HaskellNone
LanguageHaskell2010

Generic.Random.Internal.Generic

Contents

Synopsis

Random generators

genericArbitrary Source #

Arguments

:: (Generic a, GA Unsized (Rep 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 :: (Generic a, GA Unsized (Rep a), UniformWeight_ (Rep a)) => Gen a Source #

Pick every constructor with equal probability. Equivalent to genericArbitrary uniform.

genericArbitraryU :: Gen a

genericArbitrarySingle :: (Generic a, GA Unsized (Rep 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

:: (Generic a, GA Sized (Rep 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

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

Deprecated: Can be omitted

A smart constructor to specify a custom distribution.

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

data Sized Source #

Instances

GAProduct Sized U1 Source # 

Methods

gaProduct :: proxy Sized -> Gen (U1 p) Source #

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

Methods

gaProduct :: proxy Sized -> Gen (f p) Source #

data Unsized Source #

Instances

GAProduct' f => GAProduct Unsized f Source # 

Methods

gaProduct :: proxy Unsized -> Gen (f p) Source #

class GA sized f where Source #

Generic Arbitrary

Minimal complete definition

ga

Methods

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

Instances

TypeError Constraint ((:$$:) ((:<>:) (Text "Unrecognized Rep: ") (ShowType (* -> *) f)) (Text "Possible cause: missing Generic instance")) => GA sized f Source # 

Methods

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

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

Methods

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

GAProduct sized f => GA sized (M1 C c f) Source # 

Methods

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

GA sized f => GA sized (M1 D c f) Source # 

Methods

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

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

class GASum sized f where Source #

Minimal complete definition

gaSum

Methods

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

Instances

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

Methods

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

GAProduct sized f => GASum sized (M1 i c f) Source # 

Methods

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

class GAProduct sized f where Source #

Minimal complete definition

gaProduct

Methods

gaProduct :: proxy sized -> Gen (f p) Source #

Instances

GAProduct' f => GAProduct Unsized f Source # 

Methods

gaProduct :: proxy Unsized -> Gen (f p) Source #

GAProduct Sized U1 Source # 

Methods

gaProduct :: proxy Sized -> Gen (U1 p) Source #

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

Methods

gaProduct :: proxy Sized -> Gen (f p) Source #

class GAProduct' f where Source #

Minimal complete definition

gaProduct'

Methods

gaProduct' :: Gen (f p) Source #

Instances

GAProduct' U1 Source # 

Methods

gaProduct' :: Gen (U1 p) Source #

Arbitrary c => GAProduct' (K1 i c) Source # 

Methods

gaProduct' :: Gen (K1 i c p) Source #

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

Methods

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

GAProduct' f => GAProduct' (M1 i c f) Source # 

Methods

gaProduct' :: Gen (M1 i c f p) Source #

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

Equations

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

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 #

(*>) :: 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] #