generic-random-1.3.0.0: Generic random generators

Safe HaskellNone
LanguageHaskell2010

Generic.Random.Internal.BaseCase

Description

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

Documentation

genericArbitrary' Source #

Arguments

:: (GArbitrary SizedOptsDef 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

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

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 listOf' arbitrary instead of listOf arbitrary (i.e., arbitrary 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 :: *) (z :: Nat) (y :: Maybe Nat) (e :: *) 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.

Methods

baseCaseSearch :: prox y -> proxy '(z, e) -> IfM y Gen Proxy a Source #

Instances
y ~ Just 0 => BaseCaseSearch Bool z y e Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

baseCaseSearch :: prox y -> proxy (z, e) -> IfM y Gen Proxy Bool Source #

y ~ Just 0 => BaseCaseSearch Char z y e Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

baseCaseSearch :: prox y -> proxy (z, e) -> IfM y Gen Proxy Char Source #

y ~ Just 0 => BaseCaseSearch Double z y e Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

baseCaseSearch :: prox y -> proxy (z, e) -> IfM y Gen Proxy Double Source #

y ~ Just 0 => BaseCaseSearch Float z y e Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

baseCaseSearch :: prox y -> proxy (z, e) -> IfM y Gen Proxy Float Source #

y ~ Just 0 => BaseCaseSearch Int z y e Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

baseCaseSearch :: prox y -> proxy (z, e) -> IfM y Gen Proxy Int Source #

y ~ Just 0 => BaseCaseSearch Integer z y e Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

baseCaseSearch :: prox y -> proxy (z, e) -> IfM y Gen Proxy Integer Source #

y ~ Just 0 => BaseCaseSearch Ordering z y e Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

baseCaseSearch :: prox y -> proxy (z, e) -> IfM y Gen Proxy Ordering Source #

y ~ Just 0 => BaseCaseSearch Word z y e Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

baseCaseSearch :: prox y -> proxy (z, e) -> IfM y Gen Proxy Word Source #

y ~ Just 0 => BaseCaseSearch () z y e Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

baseCaseSearch :: prox y -> proxy (z, e) -> IfM y Gen Proxy () Source #

GBaseCaseSearch a z y e => BaseCaseSearch a z y e Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

baseCaseSearch :: prox y -> proxy (z, e) -> IfM y Gen Proxy a Source #

y ~ Just 0 => BaseCaseSearch [a] z y e Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

baseCaseSearch :: prox y -> proxy (z, e) -> IfM y Gen Proxy [a] Source #

class BaseCaseSearching_ a z y where Source #

Methods

baseCaseSearching_ :: proxy y -> proxy2 '(z, a) -> IfM y Gen Proxy a -> Gen a Source #

Instances
BaseCaseSearching a (z + 1) => BaseCaseSearching_ a (z :: Nat) (Nothing :: Maybe t) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

baseCaseSearching_ :: proxy Nothing -> proxy2 (z, a) -> IfM Nothing Gen Proxy a -> Gen a Source #

BaseCaseSearching_ a (z :: k) (Just m :: Maybe t) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

baseCaseSearching_ :: proxy (Just m) -> proxy2 (z, a) -> IfM (Just m) Gen Proxy a -> Gen a Source #

class BaseCaseSearching a z where Source #

Progressively increase the depth bound for BaseCaseSearch.

Methods

baseCaseSearching :: proxy '(z, a) -> Gen a Source #

Instances
(BaseCaseSearch a z y a, BaseCaseSearching_ a z y) => BaseCaseSearching a (z :: Nat) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

baseCaseSearching :: proxy (z, a) -> Gen a Source #

class BaseCase a where Source #

Custom instances can override the default behavior.

Methods

baseCase :: Gen a Source #

Generator of base cases.

Instances
BaseCaseSearching a 0 => BaseCase a Source #

Overlappable

Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

baseCase :: Gen a Source #

type family IfM (b :: Maybe t) (c :: k) (d :: k) :: k Source #

Instances
type IfM (Nothing :: Maybe t) (c :: k) (d :: k) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

type IfM (Nothing :: Maybe t) (c :: k) (d :: k) = d
type IfM (Just t2 :: Maybe t1) (c :: k) (d :: k) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

type IfM (Just t2 :: Maybe t1) (c :: k) (d :: k) = c

type (==) m n = IsEQ (CmpNat m n) Source #

type family IsEQ (e :: Ordering) :: Bool Source #

Instances
type IsEQ LT Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

type IsEQ LT = False
type IsEQ EQ Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

type IsEQ EQ = True
type IsEQ GT Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

type IsEQ GT = False

type family (b :: Maybe Nat) ||? (c :: Maybe Nat) :: Maybe Nat Source #

Instances
type m ||? (Nothing :: Maybe Nat) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

type m ||? (Nothing :: Maybe Nat) = m
type (Nothing :: Maybe Nat) ||? n Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

type (Nothing :: Maybe Nat) ||? n = n
type (Just m) ||? (Just n) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

type (Just m) ||? (Just n) = Just (Min m n)

type family (b :: Maybe Nat) &&? (c :: Maybe Nat) :: Maybe Nat Source #

Instances
type m &&? (Nothing :: Maybe Nat) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

type m &&? (Nothing :: Maybe Nat) = (Nothing :: Maybe Nat)
type (Nothing :: Maybe Nat) &&? n Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

type (Nothing :: Maybe Nat) &&? n = (Nothing :: Maybe Nat)
type (Just m) &&? (Just n) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

type (Just m) &&? (Just n) = Just (Max m n)

type Max m n = MaxOf (CmpNat m n) m n Source #

type family MaxOf (e :: Ordering) (m :: k) (n :: k) :: k Source #

Instances
type MaxOf LT (m :: k) (n :: k) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

type MaxOf LT (m :: k) (n :: k) = n
type MaxOf EQ (m :: k) (n :: k) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

type MaxOf EQ (m :: k) (n :: k) = m
type MaxOf GT (m :: k) (n :: k) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

type MaxOf GT (m :: k) (n :: k) = m

type Min m n = MinOf (CmpNat m n) m n Source #

type family MinOf (e :: Ordering) (m :: k) (n :: k) :: k Source #

Instances
type MinOf LT (m :: k) (n :: k) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

type MinOf LT (m :: k) (n :: k) = m
type MinOf EQ (m :: k) (n :: k) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

type MinOf EQ (m :: k) (n :: k) = n
type MinOf GT (m :: k) (n :: k) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

type MinOf GT (m :: k) (n :: k) = n

class Alternative (IfM y Weighted Proxy) => GBCS (f :: k -> *) (z :: Nat) (y :: Maybe Nat) (e :: *) where Source #

Methods

gbcs :: prox y -> proxy '(z, e) -> IfM y Weighted Proxy (f p) 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 # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

gbcs :: prox y -> proxy (z, e) -> IfM y Weighted Proxy (f p) Source #

y ~ Just 0 => GBCS (U1 :: k -> Type) z y e Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

gbcs :: prox y -> proxy (z, e) -> IfM y Weighted Proxy (U1 p) Source #

y ~ (Nothing :: Maybe Nat) => GBCS (K1 i c :: k -> Type) 0 y e Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

gbcs :: prox y -> proxy (0, e) -> IfM y Weighted Proxy (K1 i c p) Source #

(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 # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

gbcs :: prox y -> proxy (z, e) -> IfM y Weighted Proxy ((f :+: g) p) Source #

(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 # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

gbcs :: prox y -> proxy (z, e) -> IfM y Weighted Proxy ((f :*: g) p) 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 # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

gbcs :: prox y -> proxy (z, e) -> IfM y Weighted Proxy (K1 i c p) Source #

GBCS f z y e => GBCS (M1 i c f :: k -> Type) z y e Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

gbcs :: prox y -> proxy (z, e) -> IfM y Weighted Proxy (M1 i c f p) Source #

class Alternative (IfM (yf ||? yg) Weighted Proxy) => GBCSSum f g z e yf yg where Source #

Methods

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 :: k3 -> Type) (g :: k3 -> Type) (z :: k2) (e :: k1) (Nothing :: Maybe Nat) (Nothing :: Maybe Nat) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

gbcsSum :: prox (Nothing, Nothing) -> proxy (z, e) -> IfM Nothing Weighted Proxy (f p) -> IfM Nothing Weighted Proxy (g p) -> IfM (Nothing ||? Nothing) Weighted Proxy ((f :+: g) p) Source #

GBCSSum (f :: k3 -> Type) (g :: k3 -> Type) (z :: k2) (e :: k1) (Nothing :: Maybe Nat) (Just n) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

gbcsSum :: prox (Nothing, Just n) -> proxy (z, e) -> IfM Nothing Weighted Proxy (f p) -> IfM (Just n) Weighted Proxy (g p) -> IfM (Nothing ||? Just n) Weighted Proxy ((f :+: g) p) Source #

GBCSSum (f :: k3 -> Type) (g :: k3 -> Type) (z :: k2) (e :: k1) (Just m) (Nothing :: Maybe Nat) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

gbcsSum :: prox (Just m, Nothing) -> proxy (z, e) -> IfM (Just m) Weighted Proxy (f p) -> IfM Nothing Weighted Proxy (g p) -> IfM (Just m ||? Nothing) Weighted Proxy ((f :+: g) p) Source #

GBCSSumCompare f g z e (CmpNat m n) => GBCSSum (f :: k3 -> Type) (g :: k3 -> Type) (z :: k2) (e :: k1) (Just m) (Just n) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

gbcsSum :: prox (Just m, Just n) -> proxy (z, e) -> IfM (Just m) Weighted Proxy (f p) -> IfM (Just n) Weighted Proxy (g p) -> IfM (Just m ||? Just n) Weighted Proxy ((f :+: g) p) Source #

class GBCSSumCompare f g z e o where Source #

Methods

gbcsSumCompare :: proxy0 o -> proxy '(z, e) -> Weighted (f p) -> Weighted (g p) -> Weighted ((f :+: g) p) Source #

Instances
GBCSSumCompare (f :: k3 -> Type) (g :: k3 -> Type) (z :: k2) (e :: k1) GT Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

gbcsSumCompare :: proxy0 GT -> proxy (z, e) -> Weighted (f p) -> Weighted (g p) -> Weighted ((f :+: g) p) Source #

GBCSSumCompare (f :: k3 -> Type) (g :: k3 -> Type) (z :: k2) (e :: k1) LT Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

gbcsSumCompare :: proxy0 LT -> proxy (z, e) -> Weighted (f p) -> Weighted (g p) -> Weighted ((f :+: g) p) Source #

GBCSSumCompare (f :: k3 -> Type) (g :: k3 -> Type) (z :: k2) (e :: k1) EQ Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

gbcsSumCompare :: proxy0 EQ -> proxy (z, e) -> Weighted (f p) -> Weighted (g p) -> Weighted ((f :+: g) p) Source #

class Alternative (IfM (yf &&? yg) Weighted Proxy) => GBCSProduct f g z e yf yg where Source #

Methods

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 #

Instances
(yf &&? yg) ~ (Nothing :: Maybe Nat) => GBCSProduct (f :: k3 -> Type) (g :: k3 -> Type) (z :: k2) (e :: k1) yf yg Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

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 #

GBCSProduct (f :: k3 -> Type) (g :: k3 -> Type) (z :: k2) (e :: k1) (Just m) (Just n) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

gbcsProduct :: prox (Just m, Just n) -> proxy (z, e) -> IfM (Just m) Weighted Proxy (f p) -> IfM (Just n) Weighted Proxy (g p) -> IfM (Just m &&? Just n) Weighted Proxy ((f :*: g) p) Source #

class IsMaybe b where Source #

Methods

ifMmap :: proxy b -> (c a -> c' a') -> (d a -> d' a') -> IfM b c d a -> IfM b c' d' a' Source #

ifM :: proxy b -> c a -> d a -> IfM b c d a Source #

Instances
IsMaybe (Nothing :: Maybe t) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

ifMmap :: proxy Nothing -> (c a -> c' a') -> (d a -> d' a') -> IfM Nothing c d a -> IfM Nothing c' d' a' Source #

ifM :: proxy Nothing -> c a -> d a -> IfM Nothing c d a Source #

IsMaybe (Just t2 :: Maybe t1) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

ifMmap :: proxy (Just t2) -> (c a -> c' a') -> (d a -> d' a') -> IfM (Just t2) c d a -> IfM (Just t2) c' d' a' Source #

ifM :: proxy (Just t2) -> c a -> d a -> IfM (Just t2) c d a Source #

class GBaseCaseSearch a z y e where Source #

Methods

gBaseCaseSearch :: prox y -> proxy '(z, e) -> IfM y Gen Proxy a Source #

Instances
(Generic a, GBCS (Rep a) z y e, IsMaybe y) => GBaseCaseSearch a (z :: Nat) (y :: Maybe Nat) (e :: Type) Source # 
Instance details

Defined in Generic.Random.Internal.BaseCase

Methods

gBaseCaseSearch :: prox y -> proxy (z, e) -> IfM y Gen Proxy a Source #