Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type family ListProduct w = r | r -> w where ...
- injectiveListProduct :: forall (a :: [Type]) (b :: [Type]). ListProduct a ~ ListProduct b => a :~: b
- listProductEq :: (forall a. w a -> Dict (Eq a)) -> ListType w t -> Dict (Eq (ListProduct t))
- listProductShow :: (forall a. w a -> Dict (Show a)) -> ListType w t -> Dict (Show (ListProduct t))
- fillListProduct :: ListType w t -> (forall a. w a -> a) -> ListProduct t
- mapListProduct :: ListType w t -> (forall a. w a -> a -> a) -> ListProduct t -> ListProduct t
- lift2ListProduct :: ListType w t -> (forall a. w a -> a -> a -> a) -> ListProduct t -> ListProduct t -> ListProduct t
- identityListProduct :: ListType Identity lt -> ListProduct lt
- sequenceListProduct :: Applicative f => ListType f lt -> f (ListProduct lt)
- listProductGetElement :: ListElementType list t -> ListProduct list -> t
- listProductPutElement :: ListElementType list t -> t -> ListProduct list -> ListProduct list
- listProductModifyElement :: ListElementType list t -> (t -> t) -> ListProduct list -> ListProduct list
- data ListProductType wit t where
- MkListProductType :: forall (wit :: Type -> Type) (lt :: [Type]). ListType wit lt -> ListProductType wit (ListProduct lt)
Documentation
type family ListProduct w = r | r -> w where ... Source #
ListProduct '[] = () | |
ListProduct (t ': tt) = (t, ListProduct tt) |
injectiveListProduct :: forall (a :: [Type]) (b :: [Type]). ListProduct a ~ ListProduct b => a :~: b Source #
workaround for https://gitlab.haskell.org/ghc/ghc/issues/10833
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 #
identityListProduct :: ListType Identity lt -> ListProduct lt Source #
sequenceListProduct :: Applicative f => ListType f lt -> f (ListProduct lt) Source #
listProductGetElement :: ListElementType list t -> ListProduct list -> t Source #
listProductPutElement :: ListElementType list t -> t -> ListProduct list -> ListProduct list Source #
listProductModifyElement :: ListElementType list t -> (t -> t) -> ListProduct list -> ListProduct list Source #
data ListProductType wit t where Source #
MkListProductType :: forall (wit :: Type -> Type) (lt :: [Type]). ListType wit lt -> ListProductType wit (ListProduct lt) |
Instances
WitnessConstraint Eq w => WitnessConstraint Eq (ListProductType w :: Type -> Type) Source # | |
Defined in Data.Type.Witness.Specific.List.Product witnessConstraint :: forall (t :: k). ListProductType w t -> Dict (Eq t) Source # | |
TestEquality wit => TestEquality (ListProductType wit :: Type -> Type) Source # | |
Defined in Data.Type.Witness.Specific.List.Product testEquality :: forall (a :: k) (b :: k). ListProductType wit a -> ListProductType wit b -> Maybe (a :~: b) # | |
Representative w => Representative (ListProductType w :: Type -> Type) Source # | |
Defined in Data.Type.Witness.Specific.List.Product | |
Representative w => Is (ListProductType w :: Type -> Type) () Source # | |
Defined in Data.Type.Witness.Specific.List.Product representative :: ListProductType w () Source # | |
(Is w a, Is (ListProductType w) ar) => Is (ListProductType w :: Type -> Type) ((a, ar) :: Type) Source # | |
Defined in Data.Type.Witness.Specific.List.Product representative :: ListProductType w (a, ar) Source # |