polysemy-check-0.4.0.0: QuickCheck for Polysemy
Safe HaskellNone
LanguageHaskell2010

Polysemy.Check.Arbitrary.Generic

Synopsis

Documentation

data family ExistentialFor (e :: Effect) Source #

Data family for the instantiation of existential variables. If you want to check properties for an effect e that contains an existential type, the synthesized Arbitrary instance will instantiate all of e's existential types at ExistentialFor e.

ExistentialFor e must have instances for every dictionary required by e, and will likely require an Arbitrary instance.

class GArbitraryK (e :: Effect) (f :: LoT Effect -> Type) (r :: EffectRow) (a :: Type) where Source #

Given GArbitraryK a (RepK e) r a, this typeclass computes generators for every well-typed constructor of e (Sem r) a. It is capable of building generators for GADTs.

Methods

garbitraryk :: [Gen (f (LoT2 (Sem r) a))] Source #

Instances

Instances details
GArbitraryK e (U1 :: LoT Effect -> Type) r a Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk :: [Gen (U1 (LoT2 (Sem r) a))] Source #

GArbitraryKTerm (Interpret f (LoT2 (Sem r) a)) => GArbitraryK e (Field f) r a Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk :: [Gen (Field f (LoT2 (Sem r) a))] Source #

GArbitraryK e (((('Kon ((~~) :: Type -> k1 -> Constraint) :: Atom ((Type -> Type) -> Type -> Type) (Type -> k1 -> Constraint)) :@: (Var1 :: Atom ((Type -> Type) -> Type -> Type) Type)) :@: ('Kon b :: Atom ((Type -> Type) -> Type -> Type) k1)) :=>: f) r a Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk :: [Gen (((('Kon (~~) :@: Var1) :@: 'Kon b) :=>: f) (LoT2 (Sem r) a))] Source #

GArbitraryK e ((('Kon ((~~) b :: Type -> Constraint) :: Atom ((Type -> Type) -> Type -> Type) (Type -> Constraint)) :@: (Var1 :: Atom ((Type -> Type) -> Type -> Type) Type)) :=>: f) r a Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk :: [Gen ((('Kon ((~~) b) :@: Var1) :=>: f) (LoT2 (Sem r) a))] Source #

GArbitraryK e f r a => GArbitraryK e (((('Kon ((~~) :: Type -> Type -> Constraint) :: Atom ((Type -> Type) -> Type -> Type) (Type -> Type -> Constraint)) :@: (Var1 :: Atom ((Type -> Type) -> Type -> Type) Type)) :@: ('Kon a :: Atom ((Type -> Type) -> Type -> Type) Type)) :=>: f) r a Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk :: [Gen (((('Kon (~~) :@: Var1) :@: 'Kon a) :=>: f) (LoT2 (Sem r) a))] Source #

GArbitraryK e f r a => GArbitraryK e ((('Kon ((~~) a :: Type -> Constraint) :: Atom ((Type -> Type) -> Type -> Type) (Type -> Constraint)) :@: (Var1 :: Atom ((Type -> Type) -> Type -> Type) Type)) :=>: f) r a Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk :: [Gen ((('Kon ((~~) a) :@: Var1) :=>: f) (LoT2 (Sem r) a))] Source #

GArbitraryK e (c1 :=>: (c2 :=>: f)) r a => GArbitraryK e ((c1 :&: c2) :=>: f) r a Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk :: [Gen (((c1 :&: c2) :=>: f) (LoT2 (Sem r) a))] Source #

(Interpret c (LoT2 (Sem r) a), GArbitraryK e f r a) => GArbitraryK e (c :=>: f) r a Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk :: [Gen ((c :=>: f) (LoT2 (Sem r) a))] Source #

(GArbitraryK e f r a, GArbitraryK e g r a) => GArbitraryK e (f :+: g) r a Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk :: [Gen ((f :+: g) (LoT2 (Sem r) a))] Source #

(GArbitraryK e (SubstRep f (ExistentialFor e)) r a, SubstRep' f (ExistentialFor e) (LoT2 (Sem r) a)) => GArbitraryK e (Exists Type f) r a Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk :: [Gen (Exists Type f (LoT2 (Sem r) a))] Source #

(GArbitraryK e f r a, GArbitraryK e g r a) => GArbitraryK e (f :*: g) r a Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk :: [Gen ((f :*: g) (LoT2 (Sem r) a))] Source #

GArbitraryK e f r a => GArbitraryK e (M1 _1 _2 f) r a Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk :: [Gen (M1 _1 _2 f (LoT2 (Sem r) a))] Source #

genEff :: forall e r a. (GenericK e, GArbitraryK e (RepK e) r a) => Gen (e (Sem r) a) Source #

genEff @e @r @a gets a generator capable of producing every well-typed GADT constructor of e (Sem r) a.

class GArbitraryKTerm (t :: Type) where Source #

Instances

Instances details
Arbitrary a => GArbitraryKTerm a Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

(CoArbitrary a, GArbitraryKTerm b) => GArbitraryKTerm (a -> b) Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitrarykterm :: Gen (a -> b) Source #

ArbitraryEffOfType a r r => GArbitraryKTerm (Sem r a) Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitrarykterm :: Gen (Sem r a) Source #