| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Generic.Random
Contents
Description
Simple GHC.Generics-based arbitrary generators.
For more information:
- 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 SizedOpts a => Weights a -> Gen a
- genericArbitrary' :: (GArbitrary SizedOpts a, BaseCase a) => Weights a -> Gen a
- genericArbitraryU' :: (GArbitrary SizedOpts a, BaseCase a, GUniformWeight a) => Gen a
- genericArbitraryG :: GArbitrary (SetGens g UnsizedOpts) a => GenList g -> Weights a -> Gen a
- genericArbitraryUG :: (GArbitrary (SetGens g UnsizedOpts) a, GUniformWeight a) => GenList g -> Gen a
- genericArbitrarySingleG :: (GArbitrary (SetGens g UnsizedOpts) a, Weights_ (Rep a) ~ L c0) => GenList g -> Gen a
- genericArbitraryRecG :: GArbitrary (SetGens g SizedOpts) a => GenList g -> Weights a -> Gen a
- genericArbitraryWith :: GArbitrary opts a => opts -> Weights a -> Gen a
- withBaseCase :: Gen a -> Gen a -> Gen a
- class BaseCase a where
- data Weights a
- data W (c :: Symbol)
- (%) :: WeightBuilder' w => W (First' w) -> Prec' w -> w
- uniform :: UniformWeight_ (Rep a) => Weights a
- data Options (s :: Sizing) (g :: [Type])
- type SizedOpts = (Options Sized '[] :: Type)
- sizedOpts :: SizedOpts
- type UnsizedOpts = (Options Unsized '[] :: Type)
- unsizedOpts :: UnsizedOpts
- data Sizing
- setSized :: Options s g -> Options Sized g
- setUnsized :: Options s g -> Options Unsized g
- data GenList (g :: [Type]) where
- newtype Field (s :: Symbol) a = Field {
- unField :: a
- field :: proxy s -> a -> Field s a
- setGenerators :: GenList g -> Options s g0 -> Options s g
- class (Generic a, GA opts (Rep a)) => GArbitrary opts a
- class UniformWeight_ (Rep a) => GUniformWeight a
Arbitrary implementations
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 SizedOpts 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
Arguments
| :: (GArbitrary SizedOpts 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
genericArbitraryU' :: (GArbitrary SizedOpts a, BaseCase a, GUniformWeight a) => Gen a Source #
Equivalent to .genericArbitrary' uniform
genericArbitraryU :: Gen a
genericArbitraryG :: GArbitrary (SetGens g UnsizedOpts) a => GenList g -> 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 ), the generator for the first
match will be picked.Field "x" a
genericArbitraryUG :: (GArbitrary (SetGens g UnsizedOpts) a, GUniformWeight a) => GenList g -> Gen a Source #
genericArbitraryU with explicit generators.
See also genericArbitraryG.
genericArbitrarySingleG :: (GArbitrary (SetGens g UnsizedOpts) a, Weights_ (Rep a) ~ L c0) => GenList g -> Gen a Source #
genericArbitrarySingle with explicit generators.
See also genericArbitraryG.
Arguments
| :: GArbitrary (SetGens g SizedOpts) a | |
| => GenList g | |
| -> 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
Instances
| BaseCaseSearching Nat a 0 => BaseCase a Source # | Overlappable |
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%()) ::Weightsauniform::Weightsa
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 % ())
Instances
| WeightBuilder (Weights_ (Rep a)) => WeightBuilder' (Weights a) Source # | |
(%) :: WeightBuilder' w => W (First' w) -> Prec' w -> w infixr 1 Source #
A binary constructor for building up trees of weights.
Full options
Whether to decrease the size parameter before generating fields.
newtype Field (s :: Symbol) a Source #
A marker for a generator which overrides a specific field
named s.
Available only for base >= 4.9.
Public classes
class UniformWeight_ (Rep a) => GUniformWeight a Source #
Derived uniform distribution of constructors for a.
Instances
| UniformWeight_ (Rep a) => GUniformWeight a Source # | |