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

Polysemy.Check

Synopsis

Effect Properties

prepropCommutative Source #

Arguments

:: forall e1 e2 r f. (forall a. Show a => Show (f a), forall a. Eq a => Eq (f a)) 
=> (ArbitraryEff r r, ArbitraryEff '[e1] r, ArbitraryEff '[e2] r) 
=> (forall a. Sem r a -> IO (f a))

An interpreter for the effect stack down to IO. Pure effect stacks can be lifted into IO via pure after the final run.

-> Property 

Prove that two effects are commutative (a la Reasoning about effect interaction by fusion) under the given interpreter.

Humans naturally expect that disparate effects do not interact, thus commutativity is an important property for reasoning about the correctness of your program.

For example,

prepropCommutative @(State Int) @Trace @EffStack runEffStack

will interleave random State Int and Trace actions, within a bigger context of EffStack actions. The resulting Property will fail if permuting the State Int and Trace effects changes the outcome of the entire computation.

prepropEquivalent Source #

Arguments

:: forall effs x r1 r2. (Eq x, Show x, Inject effs r1, Inject effs r2, Members effs effs) 
=> (forall a. Sem r1 a -> IO a)

The first interpreter for the effect stack.Pure effect stacks can be lifted into IO via pure after the final run.

-> (forall a. Sem r2 a -> IO a)

The second interpreter to prove equivalence for.

-> (forall r. Members effs r => Gen (Sem r x))

A generator producing arbitrary programs in r. The property will hold true if both interpreters produce the same output for every program generated by this.

-> Property 

Prove that two interpreters are equivalent. For the given generator, this property ensures that the two interpreters give the same result for every arbitrary program.

prepropLaw Source #

Arguments

:: (Eq x, Show x) 
=> Gen (Sem r a, Sem r a)

A generator for two equivalent programs.

-> (Sem r a -> IO x)

An interpreter for the effect stack down to IO. Pure effect stacks can be lifted into IO via pure after the final run.

-> Property 

Prove that two programs in r are equivalent under a given interpretation. This is useful for proving laws about particular effects (or stacks of effects).

For example, any lawful interpretation of State must satisfy the put s1 >> put s2 = put s2 law.

Generators for Effects

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 (Sem r) a), GArbitraryK a (RepK (e (Sem 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.

Types for Generators for Effects

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

Constraints for Generators of Effects

class GArbitraryK (a :: Type) (f :: LoT Type -> Type) 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.

Minimal complete definition

garbitraryk

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 #

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

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

Minimal complete definition

genSomeAction

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 (Sem r) a), CoArbitrary a, GArbitraryK a (RepK (e (Sem r) a))) => ArbitraryAction (a ': as) e r Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.AnyEff

Methods

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

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

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

Minimal complete definition

genSomeEff

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) Source #

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

Minimal complete definition

genSomeEffOfType

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 (Sem r) a), GArbitraryK a (RepK (e (Sem r) a)), CoArbitrary a, Member e r) => ArbitraryEffOfType a (e ': es) r Source # 
Instance details

Defined in Polysemy.Check.Arbitrary.AnyEff

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

Re-exports

send :: forall e (r :: [(Type -> Type) -> Type -> Type]) a. Member e r => e (Sem r) a -> Sem r a #

Embed an effect into a Sem. This is used primarily via makeSem to implement smart constructors.

deriveGenericK :: Name -> Q [Dec] #

Given the Name of a data type (or, the Name of a constructor belonging to a data type), generate GenericK instances for that data type. You will likely need to enable most of these language extensions in order for GHC to accept the generated code:

  • DataKinds
  • EmptyCase (if using an empty data type)
  • FlexibleInstances
  • MultiParamTypeClasses
  • PolyKinds (if using a poly-kinded data type)
  • TemplateHaskell
  • TypeFamilies

class GenericK (f :: k) #

Representable types of any kind. Examples:

instance GenericK Int
instance GenericK []
instance GenericK Either
instance GenericK (Either a)
instance GenericK (Either a b)

Instances

Instances details
GenericK (Resource m a :: Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Resource m a) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Resource m a :@@: x) -> RepK (Resource m a) x #

toK :: forall (x :: LoT k). RepK (Resource m a) x -> Resource m a :@@: x #

GenericK (NonDet m a :: Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (NonDet m a) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (NonDet m a :@@: x) -> RepK (NonDet m a) x #

toK :: forall (x :: LoT k). RepK (NonDet m a) x -> NonDet m a :@@: x #

GenericK (Fixpoint m a :: Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Fixpoint m a) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Fixpoint m a :@@: x) -> RepK (Fixpoint m a) x #

toK :: forall (x :: LoT k). RepK (Fixpoint m a) x -> Fixpoint m a :@@: x #

GenericK (Trace m a :: Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Trace m a) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Trace m a :@@: x) -> RepK (Trace m a) x #

toK :: forall (x :: LoT k). RepK (Trace m a) x -> Trace m a :@@: x #

GenericK (Reader i m a :: Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Reader i m a) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Reader i m a :@@: x) -> RepK (Reader i m a) x #

toK :: forall (x :: LoT k). RepK (Reader i m a) x -> Reader i m a :@@: x #

GenericK (Writer o m a :: Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Writer o m a) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Writer o m a :@@: x) -> RepK (Writer o m a) x #

toK :: forall (x :: LoT k). RepK (Writer o m a) x -> Writer o m a :@@: x #

GenericK (Embed m z a :: Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Embed m z a) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Embed m z a :@@: x) -> RepK (Embed m z a) x #

toK :: forall (x :: LoT k). RepK (Embed m z a) x -> Embed m z a :@@: x #

GenericK (Output o m a :: Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Output o m a) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Output o m a :@@: x) -> RepK (Output o m a) x #

toK :: forall (x :: LoT k). RepK (Output o m a) x -> Output o m a :@@: x #

GenericK (State s m a :: Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (State s m a) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (State s m a :@@: x) -> RepK (State s m a) x #

toK :: forall (x :: LoT k). RepK (State s m a) x -> State s m a :@@: x #

GenericK (Error e m a :: Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Error e m a) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Error e m a :@@: x) -> RepK (Error e m a) x #

toK :: forall (x :: LoT k). RepK (Error e m a) x -> Error e m a :@@: x #

GenericK (Fail m a :: Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Fail m a) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Fail m a :@@: x) -> RepK (Fail m a) x #

toK :: forall (x :: LoT k). RepK (Fail m a) x -> Fail m a :@@: x #

GenericK (View v m a :: Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (View v m a) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (View v m a :@@: x) -> RepK (View v m a) x #

toK :: forall (x :: LoT k). RepK (View v m a) x -> View v m a :@@: x #

GenericK (Input i m a :: Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Input i m a) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Input i m a :@@: x) -> RepK (Input i m a) x #

toK :: forall (x :: LoT k). RepK (Input i m a) x -> Input i m a :@@: x #

GenericK (Tagged k3 e m a :: Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Tagged k3 e m a) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Tagged k3 e m a :@@: x) -> RepK (Tagged k3 e m a) x #

toK :: forall (x :: LoT k). RepK (Tagged k3 e m a) x -> Tagged k3 e m a :@@: x #

GenericK Embed Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK Embed :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Embed :@@: x) -> RepK Embed x #

toK :: forall (x :: LoT k). RepK Embed x -> Embed :@@: x #

GenericK Resource Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK Resource :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Resource :@@: x) -> RepK Resource x #

toK :: forall (x :: LoT k). RepK Resource x -> Resource :@@: x #

GenericK NonDet Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK NonDet :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (NonDet :@@: x) -> RepK NonDet x #

toK :: forall (x :: LoT k). RepK NonDet x -> NonDet :@@: x #

GenericK Fixpoint Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK Fixpoint :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Fixpoint :@@: x) -> RepK Fixpoint x #

toK :: forall (x :: LoT k). RepK Fixpoint x -> Fixpoint :@@: x #

GenericK Reader Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK Reader :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Reader :@@: x) -> RepK Reader x #

toK :: forall (x :: LoT k). RepK Reader x -> Reader :@@: x #

GenericK Writer Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK Writer :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Writer :@@: x) -> RepK Writer x #

toK :: forall (x :: LoT k). RepK Writer x -> Writer :@@: x #

GenericK (Reader i :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Reader i) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Reader i :@@: x) -> RepK (Reader i) x #

toK :: forall (x :: LoT k). RepK (Reader i) x -> Reader i :@@: x #

GenericK (Writer o :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Writer o) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Writer o :@@: x) -> RepK (Writer o) x #

toK :: forall (x :: LoT k). RepK (Writer o) x -> Writer o :@@: x #

GenericK (Embed m :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Embed m) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Embed m :@@: x) -> RepK (Embed m) x #

toK :: forall (x :: LoT k). RepK (Embed m) x -> Embed m :@@: x #

GenericK (Error :: Type -> (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK Error :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k0). (Error :@@: x) -> RepK Error x #

toK :: forall (x :: LoT k0). RepK Error x -> Error :@@: x #

GenericK (Output :: Type -> k -> Type -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK Output :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k0). (Output :@@: x) -> RepK Output x #

toK :: forall (x :: LoT k0). RepK Output x -> Output :@@: x #

GenericK (State :: Type -> k -> Type -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK State :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k0). (State :@@: x) -> RepK State x #

toK :: forall (x :: LoT k0). RepK State x -> State :@@: x #

GenericK (Resource m :: Type -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Resource m) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Resource m :@@: x) -> RepK (Resource m) x #

toK :: forall (x :: LoT k). RepK (Resource m) x -> Resource m :@@: x #

GenericK (NonDet m :: Type -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (NonDet m) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (NonDet m :@@: x) -> RepK (NonDet m) x #

toK :: forall (x :: LoT k). RepK (NonDet m) x -> NonDet m :@@: x #

GenericK (Fixpoint m :: Type -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Fixpoint m) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Fixpoint m :@@: x) -> RepK (Fixpoint m) x #

toK :: forall (x :: LoT k). RepK (Fixpoint m) x -> Fixpoint m :@@: x #

GenericK (Trace :: k -> Type -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK Trace :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k0). (Trace :@@: x) -> RepK Trace x #

toK :: forall (x :: LoT k0). RepK Trace x -> Trace :@@: x #

GenericK (Error e :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Error e) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k0). (Error e :@@: x) -> RepK (Error e) x #

toK :: forall (x :: LoT k0). RepK (Error e) x -> Error e :@@: x #

GenericK (Trace m :: Type -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Trace m) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Trace m :@@: x) -> RepK (Trace m) x #

toK :: forall (x :: LoT k). RepK (Trace m) x -> Trace m :@@: x #

GenericK (Reader i m :: Type -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Reader i m) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Reader i m :@@: x) -> RepK (Reader i m) x #

toK :: forall (x :: LoT k). RepK (Reader i m) x -> Reader i m :@@: x #

GenericK (Writer o m :: Type -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Writer o m) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Writer o m :@@: x) -> RepK (Writer o m) x #

toK :: forall (x :: LoT k). RepK (Writer o m) x -> Writer o m :@@: x #

GenericK (Embed m z :: Type -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Embed m z) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Embed m z :@@: x) -> RepK (Embed m z) x #

toK :: forall (x :: LoT k). RepK (Embed m z) x -> Embed m z :@@: x #

GenericK (Input :: k -> k1 -> k -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK Input :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k0). (Input :@@: x) -> RepK Input x #

toK :: forall (x :: LoT k0). RepK Input x -> Input :@@: x #

GenericK (Output o :: k -> Type -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Output o) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k0). (Output o :@@: x) -> RepK (Output o) x #

toK :: forall (x :: LoT k0). RepK (Output o) x -> Output o :@@: x #

GenericK (State s :: k -> Type -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (State s) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k0). (State s :@@: x) -> RepK (State s) x #

toK :: forall (x :: LoT k0). RepK (State s) x -> State s :@@: x #

GenericK (Fail :: k -> k1 -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK Fail :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k0). (Fail :@@: x) -> RepK Fail x #

toK :: forall (x :: LoT k0). RepK Fail x -> Fail :@@: x #

GenericK (View :: k -> k1 -> k -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK View :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k0). (View :@@: x) -> RepK View x #

toK :: forall (x :: LoT k0). RepK View x -> View :@@: x #

GenericK (Output o m :: Type -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Output o m) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Output o m :@@: x) -> RepK (Output o m) x #

toK :: forall (x :: LoT k). RepK (Output o m) x -> Output o m :@@: x #

GenericK (State s m :: Type -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (State s m) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (State s m :@@: x) -> RepK (State s m) x #

toK :: forall (x :: LoT k). RepK (State s m) x -> State s m :@@: x #

GenericK (Error e m :: k -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Error e m) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k0). (Error e m :@@: x) -> RepK (Error e m) x #

toK :: forall (x :: LoT k0). RepK (Error e m) x -> Error e m :@@: x #

GenericK (Input i :: k1 -> k -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Input i) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k0). (Input i :@@: x) -> RepK (Input i) x #

toK :: forall (x :: LoT k0). RepK (Input i) x -> Input i :@@: x #

GenericK (Fail m :: k1 -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Fail m) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Fail m :@@: x) -> RepK (Fail m) x #

toK :: forall (x :: LoT k). RepK (Fail m) x -> Fail m :@@: x #

GenericK (Tagged :: k -> (k1 -> k2 -> Type) -> k1 -> k2 -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK Tagged :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k0). (Tagged :@@: x) -> RepK Tagged x #

toK :: forall (x :: LoT k0). RepK Tagged x -> Tagged :@@: x #

GenericK (View v :: k1 -> k -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (View v) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k0). (View v :@@: x) -> RepK (View v) x #

toK :: forall (x :: LoT k0). RepK (View v) x -> View v :@@: x #

GenericK (Tagged k3 :: (k1 -> k2 -> Type) -> k1 -> k2 -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Tagged k3) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Tagged k3 :@@: x) -> RepK (Tagged k3) x #

toK :: forall (x :: LoT k). RepK (Tagged k3) x -> Tagged k3 :@@: x #

GenericK (Input i m :: k -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Input i m) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k0). (Input i m :@@: x) -> RepK (Input i m) x #

toK :: forall (x :: LoT k0). RepK (Input i m) x -> Input i m :@@: x #

GenericK (View v m :: k -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (View v m) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k0). (View v m :@@: x) -> RepK (View v m) x #

toK :: forall (x :: LoT k0). RepK (View v m) x -> View v m :@@: x #

GenericK (Tagged k3 e :: k1 -> k2 -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Tagged k3 e) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Tagged k3 e :@@: x) -> RepK (Tagged k3 e) x #

toK :: forall (x :: LoT k). RepK (Tagged k3 e) x -> Tagged k3 e :@@: x #

GenericK (Tagged k3 e m :: k2 -> Type) Source # 
Instance details

Defined in Polysemy.Check.Orphans

Associated Types

type RepK (Tagged k3 e m) :: LoT k -> Type #

Methods

fromK :: forall (x :: LoT k). (Tagged k3 e m :@@: x) -> RepK (Tagged k3 e m) x #

toK :: forall (x :: LoT k). RepK (Tagged k3 e m) x -> Tagged k3 e m :@@: x #