singleraeh-0.4.0: raehik's singletons
Safe HaskellSafe-Inferred
LanguageGHC2021

Singleraeh.Either

Synopsis

Documentation

data SEither sl sr elr where Source #

Singleton Either.

Constructors

SLeft :: sl l -> SEither sl sr (Left l) 
SRight :: sr r -> SEither sl sr (Right r) 

Instances

Instances details
(Demotable sl, Demotable sr) => Demotable (SEither sl sr :: Either l r -> Type) Source # 
Instance details

Defined in Singleraeh.Either

Associated Types

type Demote (SEither sl sr) Source #

Methods

demote :: forall (k1 :: k). SEither sl sr k1 -> Demote (SEither sl sr) Source #

type Demote (SEither sl sr :: Either l r -> Type) Source # 
Instance details

Defined in Singleraeh.Either

type Demote (SEither sl sr :: Either l r -> Type) = Either (Demote sl) (Demote sr)

demoteSEither :: forall dl dr sl sr elr. (forall l. sl l -> dl) -> (forall r. sr r -> dr) -> SEither sl sr elr -> Either dl dr Source #

class SingEither (cl :: lk -> Constraint) (cr :: rk -> Constraint) (sl :: lk -> Type) (sr :: rk -> Type) (elr :: Either lk rk) where Source #

Methods

singEither' :: (forall l. cl l => sl l) -> (forall r. cr r => sr r) -> SEither sl sr elr Source #

Instances

Instances details
cl l => SingEither (cl :: a -> Constraint) (cr :: rk -> Constraint) (sl :: a -> Type) (sr :: rk -> Type) ('Left l :: Either a rk) Source # 
Instance details

Defined in Singleraeh.Either

Methods

singEither' :: (forall (l0 :: lk). cl l0 => sl l0) -> (forall (r :: rk0). cr r => sr r) -> SEither sl sr ('Left l) Source #

cr r => SingEither (cl :: lk -> Constraint) (cr :: b -> Constraint) (sl :: lk -> Type) (sr :: b -> Type) ('Right r :: Either lk b) Source # 
Instance details

Defined in Singleraeh.Either

Methods

singEither' :: (forall (l :: lk0). cl l => sl l) -> (forall (r0 :: rk). cr r0 => sr r0) -> SEither sl sr ('Right r) Source #

singEither :: forall cl cr sl sr elr. SingEither cl cr sl sr elr => (forall l. cl l => sl l) -> (forall r. cr r => sr r) -> SEither sl sr elr Source #