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

Polysemy.Check.Arbitrary

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 e (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

Methods

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

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

Defined in Polysemy.Check.Arbitrary

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

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

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

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

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

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

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

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

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

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

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.

arbitraryAction Source #

Arguments

:: forall e r. ArbitraryAction (TypesOf e) e r 
=> Gen (SomeAction e r) 

Generate any action for effect e.

arbitraryActionOfType Source #

Arguments

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

Generate any action for effect e that produces type a.

arbitraryActionFromRow Source #

Arguments

:: forall (effs :: EffectRow) r. ArbitraryEff effs r 
=> Gen (SomeEff r) 

Generate any action from any effect in effs.

arbitraryActionFromRowOfType Source #

Arguments

:: forall (effs :: EffectRow) r a. ArbitraryEffOfType a effs r 
=> Gen (SomeEffOfType r a) 

Generate any action from any effect in effs that produces type a.

type family GTypesOf (f :: LoT Effect -> Type) :: [Type] where ... Source #

Helper function for implementing GTypesOf

Equations

GTypesOf (M1 _1 _2 f) = GTypesOf f 
GTypesOf (f :+: g) = Append (GTypesOf f) (GTypesOf g) 
GTypesOf ((('Kon (~~) :@: Var1) :@: 'Kon a) :=>: f) = '[a] 
GTypesOf (('Kon ((~~) a) :@: Var1) :=>: f) = '[a] 
GTypesOf _1 = '[()] 

type TypesOf (e :: Effect) = GTypesOf (RepK e) Source #

TypesOf e is a list of every type that can be bound via e's actions.

For example, given:

data MyEffect m a where
  Foo :: MyEffect m Int
  Blah :: Bool -> MyEffect m String

the result of TypesOf MyEffect is '[Int, String].

data SomeAction e (r :: EffectRow) where Source #

SomeAction e r is some action for effect e in effect row r.

Constructors

SomeAction 

Fields

Instances

Instances details
Show (SomeAction e r) Source # 
Instance details

Defined in Polysemy.Check.Arbitrary

Methods

showsPrec :: Int -> SomeAction e r -> ShowS #

show :: SomeAction e r -> String #

showList :: [SomeAction e r] -> ShowS #

data SomeEff (r :: EffectRow) where Source #

SomeEff r is some action for some effect in the effect row r.

Constructors

SomeEff 

Fields

Instances

Instances details
Show (SomeEff r) Source # 
Instance details

Defined in Polysemy.Check.Arbitrary

Methods

showsPrec :: Int -> SomeEff r -> ShowS #

show :: SomeEff r -> String #

showList :: [SomeEff r] -> ShowS #

data SomeEffOfType (r :: EffectRow) a where Source #

SomeEff r is some action for some effect in the effect row r.

Constructors

SomeEffOfType 

Fields

Instances

Instances details
Show (SomeEffOfType r a) Source # 
Instance details

Defined in Polysemy.Check.Arbitrary

class ArbitraryEff (es :: EffectRow) (r :: EffectRow) where Source #

ArbitraryEff es r lets you randomly generate an action in any of the effects es.

Methods

genSomeEff :: [Gen (SomeEff r)] Source #

Instances

Instances details
ArbitraryEff ('[] :: [Effect]) r Source # 
Instance details

Defined in Polysemy.Check.Arbitrary

Methods

genSomeEff :: [Gen (SomeEff r)] Source #

(ArbitraryEff es r, ArbitraryAction (TypesOf e) e r) => ArbitraryEff (e ': es) r Source # 
Instance details

Defined in Polysemy.Check.Arbitrary

Methods

genSomeEff :: [Gen (SomeEff r)] Source #

class ArbitraryEffOfType (a :: Type) (es :: EffectRow) (r :: EffectRow) where Source #

ArbitraryEffOfType a es r lets you randomly generate an action in any of the effects es that produces type a.

Instances

Instances details
ArbitraryEffOfType a ('[] :: [Effect]) r Source # 
Instance details

Defined in Polysemy.Check.Arbitrary

(Eq a, Show a, Show (e (Sem r) a), ArbitraryEffOfType a es r, GenericK e, GArbitraryK e (RepK e) r a, CoArbitrary a, Member e r) => ArbitraryEffOfType a (e ': es) r Source # 
Instance details

Defined in Polysemy.Check.Arbitrary

class ArbitraryAction (as :: [Type]) (e :: Effect) (r :: EffectRow) where Source #

ArbitraryAction as e r lets you randomly generate an action producing any type in as from the effect e.

Methods

genSomeAction :: [Gen (SomeAction e r)] Source #

Instances

Instances details
ArbitraryAction ('[] :: [Type]) e r Source # 
Instance details

Defined in Polysemy.Check.Arbitrary

Methods

genSomeAction :: [Gen (SomeAction e r)] Source #

(ArbitraryAction as e r, Eq a, Show a, Member e r, Show (e (Sem r) a), GenericK e, CoArbitrary a, GArbitraryK e (RepK e) r a) => ArbitraryAction (a ': as) e r Source # 
Instance details

Defined in Polysemy.Check.Arbitrary

Methods

genSomeAction :: [Gen (SomeAction e r)] Source #

Orphan instances

(Arbitrary a, ArbitraryEff r r, ArbitraryEffOfType a r r) => Arbitrary (Sem r a) Source # 
Instance details

Methods

arbitrary :: Gen (Sem r a) #

shrink :: Sem r a -> [Sem r a] #