3

kind の型レベル リストがある一般的なパターンがあり、リスト内の各要素に[*]kind の型コンストラクターを適用したいと考えています。たとえば、タイプを* -> *に変更したいと思います。'[Int, Double, Integer]'[Maybe Int, Maybe Double, Maybe Integer]

これが 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'

これにより、エラーが発生します

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''

大量の型注釈を追加しようとしましたが、エラーは多かれ少なかれ同じになります: GHC は、HList の最初の要素が (通常の) リストであると推測することさえできません。私はここでばかげたことをしていますか?何か違法?それとも回避策はありますか?

4

2 に答える 2

6

あなたが書いたときTypeMap a (b1 ': b2 ': bs)、それはMapを定義するために行った再帰と一致しません...これは、1つまたは2つの要素の長さではないTypeMapリストを試行したときにのみエラーにつながります。また、あなたのケースでは、このための型ファミリを持つ方がきれいです。

type family TypeMap (a :: * -> *) (xs :: [*]) :: [*]
type instance TypeMap t '[] = '[]
type instance TypeMap t (x ': xs) = t x ': TypeMap t xs

これはほとんど直訳であることに注意してください:

map f [] = []
map f (x:xs) = f x : map f xs
于 2013-10-05T00:07:18.710 に答える