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

Data.Type.Witness.Specific.List.Product

Synopsis

Documentation

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

Equations

ListProduct '[] = () 
ListProduct (t ': tt) = (t, ListProduct tt) 

listProductEq :: (forall a. w a -> Dict (Eq a)) -> ListType w t -> Dict (Eq (ListProduct t)) Source #

listProductShow :: (forall a. w a -> Dict (Show a)) -> ListType w t -> Dict (Show (ListProduct t)) Source #

fillListProduct :: ListType w t -> (forall a. w a -> a) -> ListProduct t Source #

mapListProduct :: ListType w t -> (forall a. w a -> a -> a) -> ListProduct t -> ListProduct t Source #

lift2ListProduct :: ListType w t -> (forall a. w a -> a -> a -> a) -> ListProduct t -> ListProduct t -> ListProduct t Source #

data ListProductType wit t where Source #

Constructors

MkListProductType :: forall (wit :: Type -> Type) (lt :: [Type]). ListType wit lt -> ListProductType wit (ListProduct lt) 

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 #

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

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

Methods

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

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

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

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

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

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

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