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

Polysemy.Check.Arbitrary.AnyEff

Synopsis

Documentation

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].

type family ArbitraryForAll (e :: Effect) (as :: [Type]) (r :: EffectRow) :: Constraint where ... Source #

A type family that expands to a GArbitraryK constaint for every type in the first list.

Equations

ArbitraryForAll e '[] f = () 
ArbitraryForAll e (a ': as) r = (Eq a, Show a, GArbitraryK e (RepK e) r a, ArbitraryForAll e as r) 

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.AnyEff

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.AnyEff

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

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.AnyEff

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.AnyEff

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.AnyEff

(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.AnyEff

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.AnyEff

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.AnyEff

Methods

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