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

Data.Type.Witness.General.WitnessConstraint

Documentation

class WitnessConstraint c w where Source #

Methods

witnessConstraint :: forall t. w t -> Dict (c t) Source #

Instances

Instances details
WitnessConstraint Eq w => WitnessConstraint Eq (ListProductType w :: Type -> Type) Source # 
Instance details

Defined in Data.Type.Witness.Specific.List.Product

Methods

witnessConstraint :: forall (t :: k). ListProductType w t -> Dict (Eq t) Source #

WitnessConstraint Eq w => WitnessConstraint Eq (ListSumType w :: Type -> Type) Source # 
Instance details

Defined in Data.Type.Witness.Specific.List.Sum

Methods

witnessConstraint :: forall (t :: k). ListSumType w t -> Dict (Eq t) Source #

WitnessConstraint (c :: k -> Constraint) (EmptyType :: k -> Type) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Empty

Methods

witnessConstraint :: forall (t :: k0). EmptyType t -> Dict (c t) Source #

c t => WitnessConstraint (c :: k -> Constraint) ((:~:) t :: k -> Type) Source # 
Instance details

Defined in Data.Type.Witness.General.WitnessConstraint

Methods

witnessConstraint :: forall (t0 :: k0). (t :~: t0) -> Dict (c t0) Source #

(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 #

WitnessConstraint c w2 => WitnessConstraint (c :: k -> Constraint) (PairType w1 w2 :: k -> Type) Source #

right-biased

Instance details

Defined in Data.Type.Witness.Specific.Pair

Methods

witnessConstraint :: forall (t :: k0). PairType w1 w2 t -> Dict (c t) Source #

WitnessConstraint (c :: k1 -> Constraint) (Compose Dict c :: k1 -> Type) Source # 
Instance details

Defined in Data.Type.Witness.General.WitnessConstraint

Methods

witnessConstraint :: forall (t :: k). Compose Dict c t -> Dict (c t) Source #