Safe Haskell | None |
---|---|
Language | Haskell2010 |
Generic.Random.DerivingVia
Synopsis
- newtype GenericArbitrary weights a = GenericArbitrary {
- unGenericArbitrary :: a
- newtype GenericArbitraryU a = GenericArbitraryU {
- unGenericArbitraryU :: a
- newtype GenericArbitrarySingle a = GenericArbitrarySingle {}
- newtype GenericArbitraryRec weights a = GenericArbitraryRec {}
- newtype GenericArbitraryG genList weights a = GenericArbitraryG {
- unGenericArbitraryG :: a
- newtype GenericArbitraryUG genList a = GenericArbitraryUG {
- unGenericArbitraryUG :: a
- newtype GenericArbitrarySingleG genList a = GenericArbitrarySingleG {}
- newtype GenericArbitraryRecG genList weights a = GenericArbitraryRecG {}
- newtype GenericArbitraryWith opts weights a = GenericArbitraryWith {}
- newtype AndShrinking f a = AndShrinking a
- class TypeLevelGenList a where
- type TypeLevelGenList' a :: Type
- toGenList :: Proxy a -> TypeLevelGenList' a
- class TypeLevelOpts a where
- type TypeLevelOpts' a :: Type
- toOpts :: Proxy a -> TypeLevelOpts' a
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
Eq a => Eq (GenericArbitrary weights a) Source # | |
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 # | |
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 # | |
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
|
Instances
Eq a => Eq (GenericArbitraryU a) Source # | |
Defined in Generic.Random.DerivingVia Methods (==) :: GenericArbitraryU a -> GenericArbitraryU a -> Bool # (/=) :: GenericArbitraryU a -> GenericArbitraryU a -> Bool # | |
Show a => Show (GenericArbitraryU a) Source # | |
Defined in Generic.Random.DerivingVia Methods showsPrec :: Int -> GenericArbitraryU a -> ShowS # show :: GenericArbitraryU a -> String # showList :: [GenericArbitraryU a] -> ShowS # | |
(GArbitrary UnsizedOpts a, GUniformWeight a) => Arbitrary (GenericArbitraryU a) Source # | |
Defined in Generic.Random.DerivingVia Methods arbitrary :: Gen (GenericArbitraryU a) # shrink :: GenericArbitraryU a -> [GenericArbitraryU a] # |
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
Constructors
GenericArbitrarySingle | |
Fields |
Instances
Eq a => Eq (GenericArbitrarySingle a) Source # | |
Defined in Generic.Random.DerivingVia Methods (==) :: GenericArbitrarySingle a -> GenericArbitrarySingle a -> Bool # (/=) :: GenericArbitrarySingle a -> GenericArbitrarySingle a -> Bool # | |
Show a => Show (GenericArbitrarySingle a) Source # | |
Defined in Generic.Random.DerivingVia Methods showsPrec :: Int -> GenericArbitrarySingle a -> ShowS # show :: GenericArbitrarySingle a -> String # showList :: [GenericArbitrarySingle a] -> ShowS # | |
(GArbitrary UnsizedOpts a, Weights_ (Rep a) ~ L c0) => Arbitrary (GenericArbitrarySingle a) Source # | |
Defined in Generic.Random.DerivingVia Methods arbitrary :: Gen (GenericArbitrarySingle a) # shrink :: GenericArbitrarySingle a -> [GenericArbitrarySingle a] # |
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
instead of listOf'
arbitrary
(i.e., listOf
arbitraryarbitrary
for
lists).
This newtype does no shrinking. To add generic shrinking, use AndShrinking
.
Uses genericArbitraryRec
.
Since: 1.5.0.0
Constructors
GenericArbitraryRec | |
Fields |
Instances
Eq a => Eq (GenericArbitraryRec weights a) Source # | |
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 # | |
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 # | |
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
Eq a => Eq (GenericArbitraryG genList weights a) Source # | |
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 # | |
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 # | |
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 | |
Fields
|
Instances
Eq a => Eq (GenericArbitraryUG genList a) Source # | |
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 # | |
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 # | |
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
Constructors
GenericArbitrarySingleG | |
Fields |
Instances
Eq a => Eq (GenericArbitrarySingleG genList a) Source # | |
Defined in Generic.Random.DerivingVia Methods (==) :: GenericArbitrarySingleG genList a -> GenericArbitrarySingleG genList a -> Bool # (/=) :: GenericArbitrarySingleG genList a -> GenericArbitrarySingleG genList a -> Bool # | |
Show a => Show (GenericArbitrarySingleG genList a) Source # | |
Defined in Generic.Random.DerivingVia Methods showsPrec :: Int -> GenericArbitrarySingleG genList a -> ShowS # show :: GenericArbitrarySingleG genList a -> String # showList :: [GenericArbitrarySingleG genList a] -> ShowS # | |
(GArbitrary (SetGens genList UnsizedOpts) a, Weights_ (Rep a) ~ L c0, TypeLevelGenList genList', genList ~ TypeLevelGenList' genList') => Arbitrary (GenericArbitrarySingleG genList' a) Source # | |
Defined in Generic.Random.DerivingVia Methods arbitrary :: Gen (GenericArbitrarySingleG genList' a) # shrink :: GenericArbitrarySingleG genList' a -> [GenericArbitrarySingleG genList' a] # |
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
Constructors
GenericArbitraryRecG | |
Fields |
Instances
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
Constructors
GenericArbitraryWith | |
Fields |
Instances
Eq a => Eq (GenericArbitraryWith opts weights a) Source # | |
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 # | |
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 # | |
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
Eq a => Eq (AndShrinking f a) Source # | |
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 # | |
Defined in Generic.Random.DerivingVia Methods showsPrec :: Int -> AndShrinking f a -> ShowS # show :: AndShrinking f a -> String # showList :: [AndShrinking f a] -> ShowS # | |
(Arbitrary (f a), Coercible (f a) a, Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) => Arbitrary (AndShrinking f a) Source # | |
Defined in Generic.Random.DerivingVia |
class TypeLevelGenList a where Source #
Since: 1.5.0.0
Associated Types
type TypeLevelGenList' a :: Type Source #
Methods
toGenList :: Proxy a -> TypeLevelGenList' a Source #
Instances
Arbitrary a => TypeLevelGenList (Gen a :: Type) Source # | |
Defined in Generic.Random.DerivingVia Associated Types type TypeLevelGenList' (Gen a) Source # | |
(TypeLevelGenList a, TypeLevelGenList b) => TypeLevelGenList (a :+ b :: Type) Source # | |
Defined in Generic.Random.DerivingVia Associated Types type TypeLevelGenList' (a :+ b) Source # |
class TypeLevelOpts a where Source #
Since: 1.5.0.0
Associated Types
type TypeLevelOpts' a :: Type Source #
Methods
toOpts :: Proxy a -> TypeLevelOpts' a Source #