问题
I have a common pattern where I have a type-level list of kind [*]
, and I would like to apply a type constructor of kind * -> *
to each element in the list. For example, I would like to change the type '[Int, Double, Integer]
to '[Maybe Int, Maybe Double, Maybe Integer]
.
Here's my attempt to implement a type-level map
.
{-# LANGUAGE TypeFamilies, MultiParamTypeClasses, FlexibleInstances, FlexibleContexts, TypeOperators, DataKinds, ScopedTypeVariables, GADTs #-}
-- turns a type list '[b1, b2, b3]
-- into the type list '[a b1, a b2, a b3]
class TypeMap (a :: * -> *) (bs :: [*]) where
type Map a bs :: [*]
instance TypeMap a '[b] where
type Map a '[b] = '[a b]
instance TypeMap a (b1 ': b2 ': bs) where
type Map a (b1 ': b2 ': bs) = ((a b1) ': (Map a (b2 ': bs)))
data HList :: [*] -> * where
HNil :: HList '[]
HCons :: a -> HList as -> HList (a ': as)
class Foo as where
toLists :: HList as -> HList (Map [] as)
instance Foo '[a] where
toLists (HCons a HNil) = HCons [a] HNil
instance (Foo (a2 ': as)) => Foo (a1 ': a2 ': as) where
toLists (HCons a as) =
let as' = case (toLists as) of
(HCons a2 as'') -> HCons [head a2] as'' -- ERROR
in HCons [a] as'
This results in the error
Could not deduce (a3 ~ [t0])
from the context (Foo ((':) * a2 as))
bound by the instance declaration at Test.hs:35:10-50
or from ((':) * a1 ((':) * a2 as) ~ (':) * a as1)
bound by a pattern with constructor
HCons :: forall a (as :: [*]).
a -> HList as -> HList ((':) * a as),
in an equation for `toLists'
at Test.hs:36:14-23
or from (Map [] as1 ~ (':) * a3 as2)
bound by a pattern with constructor
HCons :: forall a (as :: [*]).
a -> HList as -> HList ((':) * a as),
in a case alternative
at Test.hs:38:22-34
`a3' is a rigid type variable bound by
a pattern with constructor
HCons :: forall a (as :: [*]).
a -> HList as -> HList ((':) * a as),
in a case alternative
at Test.hs:38:22
Expected type: HList (Map [] ((':) * a2 as))
Actual type: HList ((':) * [t0] as2)
In the return type of a call of `HCons'
In the expression: HCons [head a2] as''
In a case alternative: (HCons a2 as'') -> HCons [head a2] as''
I've tried adding copious type annotations, but the error more or less comes out the same: GHC can't even infer that the first element of the HList is a (normal) list. Am I doing something silly here? Something illegal? Or is there any way around?
回答1:
When you wrote TypeMap a (b1 ': b2 ': bs)
, that isn't consistent with the recursion you did to define Map... which only leads to an error when you try to TypeMap lists that aren't 1 or 2 elements long. Also, it's cleaner in your case to just have a type family for this.
type family TypeMap (a :: * -> *) (xs :: [*]) :: [*]
type instance TypeMap t '[] = '[]
type instance TypeMap t (x ': xs) = t x ': TypeMap t xs
Note this is pretty much a direct translation of:
map f [] = []
map f (x:xs) = f x : map f xs
回答2:
The minimal change that makes your code compile is to change your instances for [a]
and b1:b2:bs
into instances for []
and b:bs
.
instance TypeMap a '[] where
type Map a '[] = '[]
instance TypeMap a (b ': bs) where
type Map a (b ': bs) = a b ': Map a bs
来源:https://stackoverflow.com/questions/19191348/type-level-map-with-datakinds