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

Generics.Kind.Unexported

Documentation

class SubstRep' (f :: LoT (t -> k) -> *) (x :: t) (xs :: LoT k) where Source #

Associated Types

type SubstRep f x :: LoT k -> * Source #

Methods

substRep :: f (x :&&: xs) -> SubstRep f x xs Source #

unsubstRep :: SubstRep f x xs -> f (x :&&: xs) Source #

Instances

Instances details
SubstRep' (U1 :: LoT (t -> k) -> Type) (x :: t) (xs :: LoT k) Source # 
Instance details

Defined in Generics.Kind.Unexported

Associated Types

type SubstRep U1 x :: LoT k -> Type Source #

Methods

substRep :: U1 (x :&&: xs) -> SubstRep U1 x xs Source #

unsubstRep :: SubstRep U1 x xs -> U1 (x :&&: xs) Source #

Interpret (SubstAtom t2 x) xs ~ Interpret t2 (x :&&: xs) => SubstRep' (Field t2 :: LoT (t1 -> k) -> Type) (x :: t1) (xs :: LoT k) Source # 
Instance details

Defined in Generics.Kind.Unexported

Associated Types

type SubstRep (Field t2) x :: LoT k -> Type Source #

Methods

substRep :: Field t2 (x :&&: xs) -> SubstRep (Field t2) x xs Source #

unsubstRep :: SubstRep (Field t2) x xs -> Field t2 (x :&&: xs) Source #

(Interpret (SubstAtom c x) xs, Interpret c (x :&&: xs), SubstRep' f x xs) => SubstRep' (c :=>: f :: LoT (t -> k) -> Type) (x :: t) (xs :: LoT k) Source # 
Instance details

Defined in Generics.Kind.Unexported

Associated Types

type SubstRep (c :=>: f) x :: LoT k -> Type Source #

Methods

substRep :: (c :=>: f) (x :&&: xs) -> SubstRep (c :=>: f) x xs Source #

unsubstRep :: SubstRep (c :=>: f) x xs -> (c :=>: f) (x :&&: xs) Source #

(SubstRep' f x xs, SubstRep' g x xs) => SubstRep' (f :*: g :: LoT (t -> k) -> Type) (x :: t) (xs :: LoT k) Source # 
Instance details

Defined in Generics.Kind.Unexported

Associated Types

type SubstRep (f :*: g) x :: LoT k -> Type Source #

Methods

substRep :: (f :*: g) (x :&&: xs) -> SubstRep (f :*: g) x xs Source #

unsubstRep :: SubstRep (f :*: g) x xs -> (f :*: g) (x :&&: xs) Source #

(SubstRep' f x xs, SubstRep' g x xs) => SubstRep' (f :+: g :: LoT (t -> k) -> Type) (x :: t) (xs :: LoT k) Source # 
Instance details

Defined in Generics.Kind.Unexported

Associated Types

type SubstRep (f :+: g) x :: LoT k -> Type Source #

Methods

substRep :: (f :+: g) (x :&&: xs) -> SubstRep (f :+: g) x xs Source #

unsubstRep :: SubstRep (f :+: g) x xs -> (f :+: g) (x :&&: xs) Source #

SubstRep' f x xs => SubstRep' (M1 i c f :: LoT (t -> k) -> Type) (x :: t) (xs :: LoT k) Source # 
Instance details

Defined in Generics.Kind.Unexported

Associated Types

type SubstRep (M1 i c f) x :: LoT k -> Type Source #

Methods

substRep :: M1 i c f (x :&&: xs) -> SubstRep (M1 i c f) x xs Source #

unsubstRep :: SubstRep (M1 i c f) x xs -> M1 i c f (x :&&: xs) Source #