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

Data.Type.Witness.Specific.List.Sum

Synopsis

Documentation

type family ListSum w = r | r -> w where ... Source #

Equations

ListSum '[] = Void 
ListSum (t ': tt) = Either t (ListSum tt) 

injectiveListSum :: forall (a :: [Type]) (b :: [Type]). ListSum a ~ ListSum b => a :~: b Source #

listSumEq :: (forall a. w a -> Dict (Eq a)) -> ListType w t -> Dict (Eq (ListSum t)) Source #

listSumShow :: (forall a. w a -> Dict (Show a)) -> ListType w t -> Dict (Show (ListSum t)) Source #

mapListSum :: ListType w t -> (forall a. w a -> a -> a) -> ListSum t -> ListSum t Source #

data ListSumType wit t where Source #

Constructors

MkListSumType :: forall (wit :: Type -> Type) (lt :: [Type]). ListType wit lt -> ListSumType wit (ListSum lt) 

Instances

Instances details
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 #

TestEquality wit => TestEquality (ListSumType wit :: Type -> Type) Source # 
Instance details

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

Methods

testEquality :: forall (a :: k) (b :: k). ListSumType wit a -> ListSumType wit b -> Maybe (a :~: b) #

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

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

Representative w => Is (ListSumType w :: Type -> Type) Void Source # 
Instance details

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

(Is w a, Is (ListSumType w) ar) => Is (ListSumType w :: Type -> Type) (Either a ar :: Type) Source # 
Instance details

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