generic-random-0.2.0.0: Generic random generators

Safe HaskellNone
LanguageHaskell2010

Generic.Random.Generic

Description

Simple Generics-based arbitrary generators.

Here is an example. Define your type.

data Tree a = Leaf a | Node (Tree a) (Tree a)

Derive Generic.

  deriving 'Generic'  -- Turn on the DeriveGeneric extension

Pick an arbitrary implementation.

instance Arbitrary a => Arbitrary (Tree a) where
  arbitrary = genericArbitraryFrequency [9, 8]

arbitrary :: Gen (Tree a) picks a Leaf with probability 9/17, or a Node with probability 8/17, and recursively fills their fields with arbitrary.

Synopsis

Documentation

genericArbitrary :: (Generic a, GA Unsized (Rep a)) => Gen a Source #

Pick a constructor with uniform probability, and fill its fields recursively.

An equivalent definition for Tree is:

genericArbitrary :: Arbitrary a => Gen (Tree a)
genericArbitrary =
  oneof
    [ Leaf <$> arbitrary                -- Uses Arbitrary a
    , Node <$> arbitrary <*> arbitrary  -- Uses Arbitrary (Tree a)
    ]

Note that for many types, genericArbitrary tends to produce big values. For instance for Tree a values are finite but the average number of Leaf and Node constructors is infinite.

genericArbitraryFrequency Source #

Arguments

:: (Generic a, GA Unsized (Rep a)) 
=> [Int]

List of weights for every constructor

-> Gen a 

This allows to specify the probability distribution of constructors as a list of weights, in the same order as the data type definition.

An equivalent definition for Tree is:

genericArbitraryFrequency :: Arbitrary a => [Int] -> Gen (Tree a)
genericArbitraryFrequency [x, y] =
  frequency
    [ (x, Leaf <$> arbitrary)
    , (y, Node <$> arbitrary <*> arbitrary)
    ]

genericArbitraryFrequency' Source #

Arguments

:: forall (n :: Nat). (Generic a, GA (Sized n) (Rep a)) 
=> [Int]

List of weights for every constructor

-> Gen a 

The size parameter of Gen is divided among the fields of the chosen constructor. When it reaches zero, the generator selects a finite term whenever it can find any of the given type.

The type of genericArbitraryFrequency' has an ambiguous n parameter; it is a type-level natural number of type Nat. That number determines the maximum depth of terms that can be used to end recursion.

You'll need the TypeApplications and DataKinds extensions.

genericArbitraryFrequency' @n weights

With n ~ 'Z, the generator looks for a simple nullary constructor. If none exist at the current type, as is the case for our Tree type, it carries on as in genericArbitraryFrequency.

genericArbitraryFrequency' @'Z :: Arbitrary a => [Int] -> Gen (Tree a)
genericArbitraryFrequency' @'Z [x, y] =
  frequency
    [ (x, Leaf <$> arbitrary)
    , (y, scale (`div` 2) $ Node <$> arbitrary <*> arbitrary)
    ]
    -- 2 because Node is 2-ary.

Here is another example:

data Tree' = Leaf1 | Leaf2 | Node3 Tree' Tree' Tree'
  deriving Generic

instance Arbitrary Tree' where
  arbitrary = genericArbitraryFrequency' @'Z [1, 2, 3]

genericArbitraryFrequency' is equivalent to:

genericArbitraryFrequency' @'Z :: [Int] -> Gen Tree'
genericArbitraryFrequency' @'Z [x, y, z] =
  sized $ \n ->
    if n == 0 then
      -- If the size parameter is zero, the non-nullary alternative is discarded.
      frequency $
        [ (x, return Leaf1)
        , (y, return Leaf2)
        ]
    else
      frequency $
        [ (x, return Leaf1)
        , (y, return Leaf2)
        , (z, resize (n `div` 3) node)
        ]
        -- 3 because Node3 is 3-ary
  where
    node = Node3 <$> arbitrary <*> arbitrary <*> arbitrary

To increase the chances of termination when no nullary constructor is directly available, such as in Tree, we can pass a larger depth n. The effectiveness of this parameter depends on the concrete type the generator is used for.

For instance, if we want to generate a value of type Tree (), there is a value of depth 1 (represented by 'S 'Z) that we can use to end recursion: Leaf ().

genericArbitraryFrequency' @('S 'Z) :: [Int] -> Gen (Tree ())
genericArbitraryFrequency' @('S 'Z) [x, y] =
  sized $ \n ->
    if n == 0 then
      return (Leaf ())
    else
      frequency
        [ (x, Leaf <$> arbitrary)
        , (y, scale (`div` 2) $ Node <$> arbitrary <*> arbitrary)
        ]

Because the argument of Tree must be inspected in order to discover values of type Tree (), we incur some extra constraints if we want polymorphism.

FlexibleContexts and UndecidableInstances are also required.

instance (Arbitrary a, Generic a, BaseCases 'Z (Rep a))
  => Arbitrary (Tree a) where
  arbitrary = genericArbitraryFrequency' @('S 'Z) [1, 2]

A synonym is provided for brevity.

instance (Arbitrary a, BaseCases' 'Z a) => Arbitrary (Tree a) where
  arbitrary = genericArbitraryFrequency' @('S 'Z) [1, 2]

genericArbitrary' :: forall n a. (Generic a, GA (Sized n) (Rep a)) => Gen a Source #

Like genericArbitraryFrequency', but with uniformly distributed constructors.

data Nat Source #

Peano-encoded natural numbers.

Constructors

Z 
S Nat 

type BaseCases' n a = (Generic a, BaseCases n (Rep a)) Source #

For convenience.

class BaseCases n f Source #

A BaseCases n (Rep a) constraint basically provides the list of values of type a with depth at most n.

Minimal complete definition

baseCases

Instances

BaseCases n U1 Source # 

Methods

baseCases :: Tagged n [[U1 p]] Source #

(BaseCases n f, BaseCases n g) => BaseCases n ((:*:) f g) Source # 

Methods

baseCases :: Tagged n [[(f :*: g) p]] Source #

(BaseCases n f, BaseCases n g) => BaseCases n ((:+:) f g) Source # 

Methods

baseCases :: Tagged n [[(f :+: g) p]] Source #

BaseCases Z (K1 i c) Source # 

Methods

baseCases :: Tagged Z [[K1 i c p]] Source #

BaseCases n f => BaseCases n (M1 i c f) Source # 

Methods

baseCases :: Tagged n [[M1 i c f p]] Source #

(Generic c, BaseCases n (Rep c)) => BaseCases (S n) (K1 i c) Source # 

Methods

baseCases :: Tagged (S n) [[K1 i c p]] Source #