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

Polysemy.Check.Arbitrary.Generic

Synopsis

Documentation

type (:~~~:) a b = ('Kon (~~) :@: a) :@: b Source #

class GArbitraryK (a :: Type) (f :: LoT Type -> Type) where Source #

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

Methods

garbitraryk :: [Gen (f x)] Source #

Instances

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

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk :: forall (x :: LoT Type). [Gen (U1 x)] Source #

GArbitraryK1 (Field b) => GArbitraryK a (Field b) Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk :: forall (x :: LoT Type). [Gen (Field b x)] Source #

GArbitraryK a (('Kon (b ~~ c) :: Atom Type Constraint) :=>: f) Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk :: forall (x :: LoT Type). [Gen (('Kon (b ~~ c) :=>: f) x)] Source #

GArbitraryK a (('Kon (a ~~ b) :: Atom Type Constraint) :=>: f) Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk :: forall (x :: LoT Type). [Gen (('Kon (a ~~ b) :=>: f) x)] Source #

GArbitraryK1 f => GArbitraryK a (('Kon (a ~~ a) :: Atom Type Constraint) :=>: f) Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk :: forall (x :: LoT Type). [Gen (('Kon (a ~~ a) :=>: f) x)] Source #

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

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk :: forall (x :: LoT Type). [Gen ((f :+: g) x)] Source #

GArbitraryK1 (f :*: g) => GArbitraryK a (f :*: g) Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk :: forall (x :: LoT Type). [Gen ((f :*: g) x)] Source #

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

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk :: forall (x :: LoT Type). [Gen (M1 _1 _2 f x)] Source #

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

genEff @e @a @m gets a generator capable of producing every well-typed GADT constructor of e m a.

class GArbitraryK1 (f :: LoT Type -> Type) where Source #

Like GArbitraryK, but gets run after we've already discharged the a ~ T GADT constraint.

Methods

garbitraryk1 :: [Gen (f x)] Source #

Instances

Instances details
GArbitraryK1 (U1 :: LoT Type -> Type) Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk1 :: forall (x :: LoT Type). [Gen (U1 x)] Source #

GArbitraryKTerm t => GArbitraryK1 (Field ('Kon t :: Atom Type Type)) Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk1 :: forall (x :: LoT Type). [Gen (Field ('Kon t) x)] Source #

(GArbitraryK1 f, GArbitraryK1 g) => GArbitraryK1 (f :*: g) Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk1 :: forall (x :: LoT Type). [Gen ((f :*: g) x)] Source #

GArbitraryK1 f => GArbitraryK1 (M1 _1 _2 f) Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.Generic

Methods

garbitraryk1 :: forall (x :: LoT Type). [Gen (M1 _1 _2 f x)] Source #

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 #