witness-0.6.2: values that witness types
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Type.Witness.Specific.Either

Documentation

data EitherType w1 w2 t Source #

Constructors

LeftType (w1 t) 
RightType (w2 t) 

Instances

Instances details
(WitnessConstraint c p, WitnessConstraint c q) => WitnessConstraint (c :: k -> Constraint) (EitherType p q :: k -> Type) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Either

Methods

witnessConstraint :: forall (t :: k0). EitherType p q t -> Dict (c t) Source #

(TestEquality w1, TestEquality w2) => TestEquality (EitherType w1 w2 :: k -> Type) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Either

Methods

testEquality :: forall (a :: k0) (b :: k0). EitherType w1 w2 a -> EitherType w1 w2 b -> Maybe (a :~: b) #

(FiniteWitness p, FiniteWitness q) => FiniteWitness (EitherType p q :: k -> Type) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Either

Methods

assembleAllFor :: Applicative m => (forall (t :: k0). EitherType p q t -> m (f t)) -> m (AllFor f (EitherType p q)) Source #

ListElementWitness lt => ListElementWitness (ConsType a lt :: k -> Type) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Either

Associated Types

type WitnessTypeList (ConsType a lt) :: [k] Source #

Methods

toListElementWitness :: forall (t :: k0). ConsType a lt t -> ListElementType (WitnessTypeList (ConsType a lt)) t Source #

fromListElementWitness :: forall (t :: k0). ListElementType (WitnessTypeList (ConsType a lt)) t -> ConsType a lt t Source #

(AllConstraint Show p, AllConstraint Show q) => AllConstraint Show (EitherType p q :: kt -> Type) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Either

Methods

allConstraint :: forall (t :: kt0). Dict (Show (EitherType p q t)) Source #

(Show (p t), Show (q t)) => Show (EitherType p q t) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Either

Methods

showsPrec :: Int -> EitherType p q t -> ShowS #

show :: EitherType p q t -> String #

showList :: [EitherType p q t] -> ShowS #

type WitnessTypeList (ConsType a lt :: k -> Type) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Either

type WitnessTypeList (ConsType a lt :: k -> Type) = a ': WitnessTypeList lt

eitherAllOf :: AllOf sel1 -> AllOf sel2 -> AllOf (EitherType sel1 sel2) Source #

eitherAllFor :: AllFor f sel1 -> AllFor f sel2 -> AllFor f (EitherType sel1 sel2) Source #