如何正确包装由归纳数据类型索引的数据类型?

How to properly wrap over a datatype indexed by an inductive datatype?

我正在尝试将列表的单例版本简单地包装起来。我无法解构它。这是一个最小的实现:

{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ExplicitForAll #-}

module InductiveWrapper where

import Data.Kind (Type)
import Data.Proxy (Proxy)

import GHC.Prim (coerce)

data List a = Nil | Cons a (List a)

data SList :: [ k ] -> Type where
  SNil  ::                        SList '[]
  SCons :: Proxy k -> SList ks -> SList (k ': ks)

newtype Set a = S [ a ]

data SSet :: Set k -> Type where
  SS :: SList xs -> SSet ('S xs)

type family Add (el :: k) (set :: Set k) :: Set k where
  Add el ('S xs) = 'S (el ': xs)

uncons :: forall k (el :: k) (set :: Set k)
        . SSet (Add el set) -> (Proxy el, SSet set)
uncons (SS (x `SCons` xs)) = (x, SS xs)

这是错误的相关部分:

Could not deduce: set ~ 'S ks
      from the context: Add el set ~ 'S xs
        bound by a pattern with constructor:
                   SS :: forall k (xs :: [k]). SList xs -> SSet ('S xs),
                 in an equation for ‘uncons’
[...]
 or from: xs ~ (k1 : ks)
        bound by a pattern with constructor:
                   SCons :: forall k1 (k2 :: k1) (ks :: [k1]).
                            Proxy k2 -> SList ks -> SList (k2 : ks),
[...]
• Relevant bindings include
        xs :: SList ks (bound at InductiveWrapper.hs:37:29)
        x :: Proxy k1 (bound at InductiveWrapper.hs:37:19)
        xs' :: SList xs (bound at InductiveWrapper.hs:37:14)
        s :: SSet (Add el set) (bound at InductiveWrapper.hs:37:8)

据我了解,问题是 Add el set 卡住了,因为类型检查器不明白 set 的唯一构造方法是使用 'S.

如何解除卡住或通过其他方式解决此问题?除了使用 type 而不是 newtype。我这样做的全部原因是完全隐藏 [ k ]SList.

的使用

类型族是非单射的,这在技术上意味着您不能从结果到参数,从右到左。除了没有。 GHC 8.0 引入了 TypeFamilyDependencies,它允许您为类型族指定单射性,如下所示:

type family Add (el :: k) (set :: Set k) = (set' :: Set k) | set' -> el set where
  Add el ('S xs) = 'S (el ': xs)

但是,出于某种我还没有完全理解的原因,这对你的情况仍然不起作用,导致了同样的问题。我怀疑这可能与所讨论的列表被双重包装有关,不确定。

但我确实有另一种解决方法:您可以放弃整个内射性问题并以相反的方式指定您的类型族 - 从列表到元组。除了你需要 两个 类型族 - 一个用于头部,一个用于尾部:

type family Head set where Head ('S (el ': xs)) = el
type family Tail set where Tail ('S (el ': xs)) = 'S xs

uncons :: SSet set -> (Proxy (Head set), SSet (Tail set))
uncons (SS (x `SCons` xs)) = (x, SS xs)

但这对我来说似乎有点过度设计。如果你只需要取消这些类型集,我会选择一个好的 ol' type class,它具有将类型和值包装在一起的无与伦比的优势,所以你不必跳过箍来匹配它们手动:

class Uncons set res | set -> res  where
    uncons :: SSet set -> res

instance Uncons ('S (el ': xs)) (Proxy el, SSet ('S xs)) where
    uncons (SS (x `SCons` xs)) = (x, SS xs)