Safe Haskell | None |
---|---|
Language | Haskell2010 |
Base case discovery.
Warning
This is an internal module: it is not subject to any versioning policy, breaking changes can happen at any time.
If something here seems useful, please report it or create a pull request to export it from an external module.
Synopsis
- genericArbitrary' :: (GArbitrary SizedOptsDef a, BaseCase a) => Weights a -> Gen a
- genericArbitraryU' :: (GArbitrary SizedOptsDef a, BaseCase a, GUniformWeight a) => Gen a
- withBaseCase :: Gen a -> Gen a -> Gen a
- class BaseCaseSearch (a :: Type) (z :: Nat) (y :: Maybe Nat) (e :: Type) where
- baseCaseSearch :: prox y -> proxy '(z, e) -> IfM y Gen Proxy a
- class BaseCaseSearching_ a z y where
- baseCaseSearching_ :: proxy y -> proxy2 '(z, a) -> IfM y Gen Proxy a -> Gen a
- class BaseCaseSearching a z where
- baseCaseSearching :: proxy '(z, a) -> Gen a
- class BaseCase a where
- type family IfM (b :: Maybe t) (c :: k) (d :: k) :: k
- type (==) m n = IsEQ (CmpNat m n)
- type family IsEQ (e :: Ordering) :: Bool
- type family (b :: Maybe Nat) ||? (c :: Maybe Nat) :: Maybe Nat
- type family (b :: Maybe Nat) &&? (c :: Maybe Nat) :: Maybe Nat
- type Max m n = MaxOf (CmpNat m n) m n
- type family MaxOf (e :: Ordering) (m :: k) (n :: k) :: k
- type Min m n = MinOf (CmpNat m n) m n
- type family MinOf (e :: Ordering) (m :: k) (n :: k) :: k
- class Alternative (IfM y Weighted Proxy) => GBCS (f :: k -> Type) (z :: Nat) (y :: Maybe Nat) (e :: Type) where
- class Alternative (IfM (yf ||? yg) Weighted Proxy) => GBCSSum f g z e yf yg where
- class GBCSSumCompare f g z e o where
- gbcsSumCompare :: proxy0 o -> proxy '(z, e) -> Weighted (f p) -> Weighted (g p) -> Weighted ((f :+: g) p)
- class Alternative (IfM (yf &&? yg) Weighted Proxy) => GBCSProduct f g z e yf yg where
- class IsMaybe b where
- class GBaseCaseSearch a z y e where
- gBaseCaseSearch :: prox y -> proxy '(z, e) -> IfM y Gen Proxy a
Documentation
:: (GArbitrary SizedOptsDef a, BaseCase a) | |
=> Weights a | List of weights for every constructor |
-> Gen a |
genericArbitraryU' :: (GArbitrary SizedOptsDef a, BaseCase a, GUniformWeight a) => Gen a Source #
Equivalent to
.genericArbitrary'
uniform
genericArbitraryU' :: Gen a
N.B.: This replaces the generator for fields of type [t]
with
instead of listOf'
arbitrary
(i.e., listOf
arbitraryarbitrary
for
lists).
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 BaseCaseSearch (a :: Type) (z :: Nat) (y :: Maybe Nat) (e :: Type) where Source #
Find a base case of type a
with maximum depth z
,
recursively using BaseCaseSearch
instances to search deeper levels.
y
is the depth of a base case, if found.
e
is the original type the search started with, that a
appears in.
It is used for error reporting.
Instances
class BaseCaseSearching_ a z y where Source #
Instances
BaseCaseSearching a (z + 1) => BaseCaseSearching_ a (z :: Nat) ('Nothing :: Maybe t) Source # | |
Defined in Generic.Random.Internal.BaseCase | |
BaseCaseSearching_ a (z :: k) ('Just m :: Maybe t) Source # | |
Defined in Generic.Random.Internal.BaseCase |
class BaseCaseSearching a z where Source #
Progressively increase the depth bound for BaseCaseSearch
.
baseCaseSearching :: proxy '(z, a) -> Gen a Source #
Instances
(BaseCaseSearch a z y a, BaseCaseSearching_ a z y) => BaseCaseSearching a (z :: Nat) Source # | |
Defined in Generic.Random.Internal.BaseCase baseCaseSearching :: proxy '(z, a) -> Gen a Source # |
class BaseCase a where Source #
Custom instances can override the default behavior.
Instances
BaseCaseSearching a 0 => BaseCase a Source # | Overlappable |
Defined in Generic.Random.Internal.BaseCase |
type family IfM (b :: Maybe t) (c :: k) (d :: k) :: k Source #
type family (b :: Maybe Nat) ||? (c :: Maybe Nat) :: Maybe Nat Source #
type family (b :: Maybe Nat) &&? (c :: Maybe Nat) :: Maybe Nat Source #
type family MaxOf (e :: Ordering) (m :: k) (n :: k) :: k Source #
Instances
type MaxOf 'LT (m :: k) (n :: k) Source # | |
Defined in Generic.Random.Internal.BaseCase | |
type MaxOf 'EQ (m :: k) (n :: k) Source # | |
Defined in Generic.Random.Internal.BaseCase | |
type MaxOf 'GT (m :: k) (n :: k) Source # | |
Defined in Generic.Random.Internal.BaseCase |
type family MinOf (e :: Ordering) (m :: k) (n :: k) :: k Source #
Instances
type MinOf 'LT (m :: k) (n :: k) Source # | |
Defined in Generic.Random.Internal.BaseCase | |
type MinOf 'EQ (m :: k) (n :: k) Source # | |
Defined in Generic.Random.Internal.BaseCase | |
type MinOf 'GT (m :: k) (n :: k) Source # | |
Defined in Generic.Random.Internal.BaseCase |
class Alternative (IfM y Weighted Proxy) => GBCS (f :: k -> Type) (z :: Nat) (y :: Maybe Nat) (e :: Type) where Source #
Instances
(TypeError (((('Text "Unrecognized Rep: " :<>: 'ShowType f) :$$: 'Text "Possible causes:") :$$: (('Text " Missing (" :<>: 'ShowType (BaseCase e)) :<>: 'Text ") constraint")) :$$: 'Text " Missing Generic instance") :: Constraint, Alternative (IfM y Weighted (Proxy :: Type -> Type))) => GBCS (f :: k -> Type) z y e Source # | |
y ~ 'Just 0 => GBCS (U1 :: k -> Type) z y e Source # | |
y ~ ('Nothing :: Maybe Nat) => GBCS (K1 i c :: k -> Type) 0 y e Source # | |
(Alternative (IfM y Weighted (Proxy :: Type -> Type)), GBCSSum f g z e yf yg, GBCS f z yf e, GBCS g z yg e, y ~ (yf ||? yg)) => GBCS (f :+: g :: k -> Type) z y e Source # | |
(Alternative (IfM y Weighted (Proxy :: Type -> Type)), GBCSProduct f g z e yf yg, GBCS f z yf e, GBCS g z yg e, y ~ (yf &&? yg)) => GBCS (f :*: g :: k -> Type) z y e Source # | |
(BaseCaseSearch c (z - 1) y e, (z == 0) ~ 'False, Alternative (IfM y Weighted (Proxy :: Type -> Type)), IsMaybe y) => GBCS (K1 i c :: k -> Type) z y e Source # | |
GBCS f z y e => GBCS (M1 i c f :: k -> Type) z y e Source # | |
class Alternative (IfM (yf ||? yg) Weighted Proxy) => GBCSSum f g z e yf yg where Source #
gbcsSum :: prox '(yf, yg) -> proxy '(z, e) -> IfM yf Weighted Proxy (f p) -> IfM yg Weighted Proxy (g p) -> IfM (yf ||? yg) Weighted Proxy ((f :+: g) p) Source #
Instances
GBCSSum (f :: k1 -> Type) (g :: k1 -> Type) (z :: k2) (e :: k3) ('Nothing :: Maybe Nat) ('Nothing :: Maybe Nat) Source # | |
GBCSSum (f :: k1 -> Type) (g :: k1 -> Type) (z :: k2) (e :: k3) ('Nothing :: Maybe Nat) ('Just n) Source # | |
GBCSSum (f :: k1 -> Type) (g :: k1 -> Type) (z :: k2) (e :: k3) ('Just m) ('Nothing :: Maybe Nat) Source # | |
GBCSSumCompare f g z e (CmpNat m n) => GBCSSum (f :: k1 -> Type) (g :: k1 -> Type) (z :: k2) (e :: k3) ('Just m) ('Just n) Source # | |
class GBCSSumCompare f g z e o where Source #
gbcsSumCompare :: proxy0 o -> proxy '(z, e) -> Weighted (f p) -> Weighted (g p) -> Weighted ((f :+: g) p) Source #
Instances
GBCSSumCompare (f :: k1 -> Type) (g :: k1 -> Type) (z :: k2) (e :: k3) 'GT Source # | |
Defined in Generic.Random.Internal.BaseCase | |
GBCSSumCompare (f :: k1 -> Type) (g :: k1 -> Type) (z :: k2) (e :: k3) 'LT Source # | |
Defined in Generic.Random.Internal.BaseCase | |
GBCSSumCompare (f :: k1 -> Type) (g :: k1 -> Type) (z :: k2) (e :: k3) 'EQ Source # | |
Defined in Generic.Random.Internal.BaseCase |
class Alternative (IfM (yf &&? yg) Weighted Proxy) => GBCSProduct f g z e yf yg where Source #
gbcsProduct :: prox '(yf, yg) -> proxy '(z, e) -> IfM yf Weighted Proxy (f p) -> IfM yg Weighted Proxy (g p) -> IfM (yf &&? yg) Weighted Proxy ((f :*: g) p) Source #
class GBaseCaseSearch a z y e where Source #