
27 Jun
2014
27 Jun
'14
1:41 p.m.
Hi Tom, You could push the use of that type family into the definition of MyProduct so that the type family can be fully applied:
{-# LANGUAGE DataKinds, PolyKinds, TypeFamilies, TypeOperators #-}
data MyProduct f a b c = MyProduct { foo :: MkF f a , bar :: MkF f b , baz :: MkF f c }
type family MkF (f :: k) (x :: *) :: *
type instance MkF () x = x type instance MkF (f ': fs) x = f (MkF fs x) type instance MkF '[] x = x type instance MkF f x = f x
Then your example signatures can be written as
type MP f = MyProduct f Int Bool String
type A = MP () type B = MP Maybe type C = MP [[], IO] type D = MP P
I'm not sure this approach gains you much over just writing out the type signatures has you had them. Adam