generic-random-1.5.0.0: Generic random generators for QuickCheck
Safe HaskellNone
LanguageHaskell2010

Generic.Random.DerivingVia

Synopsis

Documentation

newtype GenericArbitrary weights a Source #

Pick a constructor with a given distribution, and fill its fields with recursive calls to arbitrary.

Example

data X = ...
  deriving Arbitrary via (GenericArbitrary '[2, 3, 5] X)

Picks the first constructor with probability 2/10, the second with probability 3/10, the third with probability 5/10.

This newtype does no shrinking. To add generic shrinking, use AndShrinking.

Uses genericArbitrary.

Since: 1.5.0.0

Constructors

GenericArbitrary 

Fields

Instances

Instances details
Eq a => Eq (GenericArbitrary weights a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Methods

(==) :: GenericArbitrary weights a -> GenericArbitrary weights a -> Bool #

(/=) :: GenericArbitrary weights a -> GenericArbitrary weights a -> Bool #

Show a => Show (GenericArbitrary weights a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Methods

showsPrec :: Int -> GenericArbitrary weights a -> ShowS #

show :: GenericArbitrary weights a -> String #

showList :: [GenericArbitrary weights a] -> ShowS #

(GArbitrary UnsizedOpts a, TypeLevelWeights' weights a) => Arbitrary (GenericArbitrary weights a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Methods

arbitrary :: Gen (GenericArbitrary weights a) #

shrink :: GenericArbitrary weights a -> [GenericArbitrary weights a] #

newtype GenericArbitraryU a Source #

Pick every constructor with equal probability.

This newtype does no shrinking. To add generic shrinking, use AndShrinking.

Uses genericArbitraryU.

Since: 1.5.0.0

Constructors

GenericArbitraryU 

Fields

newtype GenericArbitrarySingle a Source #

arbitrary for types with one constructor. Equivalent to GenericArbitraryU, with a stricter type.

This newtype does no shrinking. To add generic shrinking, use AndShrinking.

Uses genericArbitrarySingle.

Since: 1.5.0.0

newtype GenericArbitraryRec weights a Source #

Decrease size at every recursive call, but don't do anything different at size 0.

data X = ...
  deriving Arbitrary via (GenericArbitraryRec '[2, 3, 5] X)

N.B.: This replaces the generator for fields of type [t] with listOf' arbitrary instead of listOf arbitrary (i.e., arbitrary for lists).

This newtype does no shrinking. To add generic shrinking, use AndShrinking.

Uses genericArbitraryRec.

Since: 1.5.0.0

Constructors

GenericArbitraryRec 

Instances

Instances details
Eq a => Eq (GenericArbitraryRec weights a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Methods

(==) :: GenericArbitraryRec weights a -> GenericArbitraryRec weights a -> Bool #

(/=) :: GenericArbitraryRec weights a -> GenericArbitraryRec weights a -> Bool #

Show a => Show (GenericArbitraryRec weights a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Methods

showsPrec :: Int -> GenericArbitraryRec weights a -> ShowS #

show :: GenericArbitraryRec weights a -> String #

showList :: [GenericArbitraryRec weights a] -> ShowS #

(GArbitrary SizedOptsDef a, TypeLevelWeights' weights a) => Arbitrary (GenericArbitraryRec weights a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Methods

arbitrary :: Gen (GenericArbitraryRec weights a) #

shrink :: GenericArbitraryRec weights a -> [GenericArbitraryRec weights a] #

newtype GenericArbitraryG genList weights a Source #

GenericArbitrary with explicit generators.

Example

data X = ...
  deriving Arbitrary via (GenericArbitraryG CustomGens '[2, 3, 5] X)

where, for example, custom generators to override String and Int fields might look as follows:

type CustomGens = CustomString :+ CustomInt

Note on multiple matches

Multiple generators may match a given field: the first will be chosen.

This newtype does no shrinking. To add generic shrinking, use AndShrinking.

Uses genericArbitraryG.

Since: 1.5.0.0

Constructors

GenericArbitraryG 

Fields

Instances

Instances details
Eq a => Eq (GenericArbitraryG genList weights a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Methods

(==) :: GenericArbitraryG genList weights a -> GenericArbitraryG genList weights a -> Bool #

(/=) :: GenericArbitraryG genList weights a -> GenericArbitraryG genList weights a -> Bool #

Show a => Show (GenericArbitraryG genList weights a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Methods

showsPrec :: Int -> GenericArbitraryG genList weights a -> ShowS #

show :: GenericArbitraryG genList weights a -> String #

showList :: [GenericArbitraryG genList weights a] -> ShowS #

(GArbitrary (SetGens genList UnsizedOpts) a, GUniformWeight a, TypeLevelWeights' weights a, TypeLevelGenList genList', genList ~ TypeLevelGenList' genList') => Arbitrary (GenericArbitraryG genList' weights a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Methods

arbitrary :: Gen (GenericArbitraryG genList' weights a) #

shrink :: GenericArbitraryG genList' weights a -> [GenericArbitraryG genList' weights a] #

newtype GenericArbitraryUG genList a Source #

GenericArbitraryU with explicit generators. See also GenericArbitraryG.

This newtype does no shrinking. To add generic shrinking, use AndShrinking.

Uses genericArbitraryUG.

Since: 1.5.0.0

Constructors

GenericArbitraryUG 

Instances

Instances details
Eq a => Eq (GenericArbitraryUG genList a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Methods

(==) :: GenericArbitraryUG genList a -> GenericArbitraryUG genList a -> Bool #

(/=) :: GenericArbitraryUG genList a -> GenericArbitraryUG genList a -> Bool #

Show a => Show (GenericArbitraryUG genList a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Methods

showsPrec :: Int -> GenericArbitraryUG genList a -> ShowS #

show :: GenericArbitraryUG genList a -> String #

showList :: [GenericArbitraryUG genList a] -> ShowS #

(GArbitrary (SetGens genList UnsizedOpts) a, GUniformWeight a, TypeLevelGenList genList', genList ~ TypeLevelGenList' genList') => Arbitrary (GenericArbitraryUG genList' a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Methods

arbitrary :: Gen (GenericArbitraryUG genList' a) #

shrink :: GenericArbitraryUG genList' a -> [GenericArbitraryUG genList' a] #

newtype GenericArbitrarySingleG genList a Source #

genericArbitrarySingle with explicit generators. See also GenericArbitraryG.

This newtype does no shrinking. To add generic shrinking, use AndShrinking.

Uses genericArbitrarySingleG.

Since: 1.5.0.0

Instances

Instances details
Eq a => Eq (GenericArbitrarySingleG genList a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Show a => Show (GenericArbitrarySingleG genList a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

(GArbitrary (SetGens genList UnsizedOpts) a, Weights_ (Rep a) ~ L c0, TypeLevelGenList genList', genList ~ TypeLevelGenList' genList') => Arbitrary (GenericArbitrarySingleG genList' a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

newtype GenericArbitraryRecG genList weights a Source #

genericArbitraryRec with explicit generators. See also genericArbitraryG.

This newtype does no shrinking. To add generic shrinking, use AndShrinking.

Uses genericArbitraryRecG.

Since: 1.5.0.0

Instances

Instances details
Eq a => Eq (GenericArbitraryRecG genList weights a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Methods

(==) :: GenericArbitraryRecG genList weights a -> GenericArbitraryRecG genList weights a -> Bool #

(/=) :: GenericArbitraryRecG genList weights a -> GenericArbitraryRecG genList weights a -> Bool #

Show a => Show (GenericArbitraryRecG genList weights a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Methods

showsPrec :: Int -> GenericArbitraryRecG genList weights a -> ShowS #

show :: GenericArbitraryRecG genList weights a -> String #

showList :: [GenericArbitraryRecG genList weights a] -> ShowS #

(GArbitrary (SetGens genList SizedOpts) a, TypeLevelWeights' weights a, TypeLevelGenList genList', genList ~ TypeLevelGenList' genList') => Arbitrary (GenericArbitraryRecG genList' weights a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Methods

arbitrary :: Gen (GenericArbitraryRecG genList' weights a) #

shrink :: GenericArbitraryRecG genList' weights a -> [GenericArbitraryRecG genList' weights a] #

newtype GenericArbitraryWith opts weights a Source #

General generic generator with custom options.

This newtype does no shrinking. To add generic shrinking, use AndShrinking.

Uses genericArbitraryWith.

Since: 1.5.0.0

Instances

Instances details
Eq a => Eq (GenericArbitraryWith opts weights a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Methods

(==) :: GenericArbitraryWith opts weights a -> GenericArbitraryWith opts weights a -> Bool #

(/=) :: GenericArbitraryWith opts weights a -> GenericArbitraryWith opts weights a -> Bool #

Show a => Show (GenericArbitraryWith opts weights a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Methods

showsPrec :: Int -> GenericArbitraryWith opts weights a -> ShowS #

show :: GenericArbitraryWith opts weights a -> String #

showList :: [GenericArbitraryWith opts weights a] -> ShowS #

(GArbitrary opts a, TypeLevelWeights' weights a, TypeLevelOpts opts', opts ~ TypeLevelOpts' opts') => Arbitrary (GenericArbitraryWith opts' weights a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Methods

arbitrary :: Gen (GenericArbitraryWith opts' weights a) #

shrink :: GenericArbitraryWith opts' weights a -> [GenericArbitraryWith opts' weights a] #

newtype AndShrinking f a Source #

Add generic shrinking to a newtype wrapper for Arbitrary, using genericShrink.

data X = ...
  deriving Arbitrary via (GenericArbitrary '[1,2,3] `AndShrinking` X)

Equivalent to:

instance Arbitrary X where
  arbitrary = genericArbitrary (1 % 2 % 3 % ())
  shrink = genericShrink

Since: 1.5.0.0

Constructors

AndShrinking a 

Instances

Instances details
Eq a => Eq (AndShrinking f a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Methods

(==) :: AndShrinking f a -> AndShrinking f a -> Bool #

(/=) :: AndShrinking f a -> AndShrinking f a -> Bool #

Show a => Show (AndShrinking f a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

(Arbitrary (f a), Coercible (f a) a, Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) => Arbitrary (AndShrinking f a) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Methods

arbitrary :: Gen (AndShrinking f a) #

shrink :: AndShrinking f a -> [AndShrinking f a] #

class TypeLevelGenList a where Source #

Since: 1.5.0.0

Associated Types

type TypeLevelGenList' a :: Type Source #

Instances

Instances details
Arbitrary a => TypeLevelGenList (Gen a :: Type) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Associated Types

type TypeLevelGenList' (Gen a) Source #

(TypeLevelGenList a, TypeLevelGenList b) => TypeLevelGenList (a :+ b :: Type) Source # 
Instance details

Defined in Generic.Random.DerivingVia

Associated Types

type TypeLevelGenList' (a :+ b) Source #

Methods

toGenList :: Proxy (a :+ b) -> TypeLevelGenList' (a :+ b) Source #

class TypeLevelOpts a where Source #

Since: 1.5.0.0

Associated Types

type TypeLevelOpts' a :: Type Source #