是否可以确保两个 GADT 类型变量在没有依赖类型的情况下相同?

Is it possible to ensure that two GADT type variables are the same without dependent types?

我正在编写一个编译器,我在其中将 GADT 用于 IR,但将标准数据类型用于其他一切。我在从旧数据类型转换为 GADT 的过程中遇到了问题。我试图用下面的 smaller/simplified 语言重现这种情况。

首先,我有以下数据类型:

data OldLVal = VarOL Int -- The nth variable. Can be used to construct a Temp later.
             | LDeref OldLVal

data Exp = Var Int -- See above
         | IntT Int32
         | Deref Exp

data Statement = AssignStmt OldLVal Exp
               | ...

我想将这些转换成这种中间形式:

{-# LANGUAGE DataKinds      #-}
{-# LANGUAGE GADTs          #-}
{-# LANGUAGE KindSignatures #-}

-- Note: this is a Phantom type
data Temp a = Temp Int

data Type = IntT
          | PtrT Type

data Command where
    Assign :: NewLVal a -> Pure a -> Command
    ...

data NewLVal :: Type -> * where
    VarNL :: Temp a -> NewLVal a
    DerefNL :: NewLVal ('PtrT ('Just a)) -> NewLVal a

data Pure :: Type -> * where
    ConstP :: Int32 -> Pure 'IntT
    ConstPtrP :: Int32 -> Pure ('PtrT a)
    VarP :: Temp a -> Pure a

此时,我只想写一个从旧数据类型到新GADT的转换。现在,我有一些看起来像这样的东西。

convert :: Statement -> Either String Command
convert (AssignStmt oldLval exp) = do
   newLval <- convertLVal oldLval -- Either String (NewLVal a)
   pure <- convertPure exp -- Either String (Pure b)
   -- return $ Assign newLval pure -- Obvious failure. Can't ensure a ~ b.
   pure' <- matchType newLval pure -- Either String (Pure a)
   return $ Assign newLval pure'

-- Converts Pure b into Pure a. Should essentially be a noop, but simply 
-- proves that it is possible.
matchType :: NewLVal a -> Pure b -> Either String (Pure a)
matchType = undefined

我意识到我不能简单地写出 convert,所以我尝试使用 matchType 这个想法来解决这个问题,它作为这两种类型确实相等的证明。问题是:我实际上如何写 matchType?如果我有完全依赖的类型(或者有人告诉我),这会容易得多,但是我可以在这里完成这段代码吗?

替代方法是以某种方式提供 newLval 作为 convertPure 的参数,但我认为这本质上只是尝试使用依赖类型。

欢迎提出任何其他建议。

如果有帮助,我还有一个函数可以将 ExpOldLVal 转换为其类型:

class Typed a where
    typeOf :: a -> Type
instance Typed Exp where
    ...
instance Typed OldLVal where
    ...

编辑:

多亏了下面的优秀回答,我才能够完成这个模块的编写。

我最终使用了下面提到的 the singletons package。一开始有点奇怪,但是在我开始理解我在做什么之后,我发现使用起来还是很合理的。然而,我运行陷入了一个陷阱:convertLValconvertPure的类型需要一个existential来表达。

data WrappedPure = forall a. WrappedPure (Pure a, SType a)
data WrappedLVal = forall a. WrappedLVal (NewLVal a, SType a)

convertPure :: Exp -> Either String WrappedPure
convertLVal :: OldLVal -> Either String WrappedLVal

这意味着您必须解包 convert 中的存在性,但除此之外,下面的答案为您指明了方向。再次感谢。

matchType写的是不可能实现的,但是你想要的想法绝对是可能的。你知道Data.Typeable吗? Typeable 是一个 class,它为检查类型提供了一些基本的反射操作。要使用它,您需要在范围内对您想了解的任何类型变量 a 进行 Typeable a 约束。所以 matchType 你会

matchType :: (Typeable a, Typeable b) => NewLVal a -> Pure b -> Either String (Pure a)

每当您想隐藏类型变量时,它还需要感染您的 GADT:

data Command where
    Assign :: (Typeable a) => NewLVal a -> Pure a -> Command
    ...

但如果您在范围内有适当的约束,则可以使用 eqT 进行类型安全的运行时类型比较。例如

-- using ScopedTypeVariables and TypeApplications
matchType :: forall a b. (Typeable a, Typeable b) => NewLVal a -> Pure b -> Either String (Pure b)
matchType = case eqT @a @b of
                Nothing -> Left "types are not equal"
                Just Refl -> {- in this scope the compiler knows that
                                a and b are the same type -}

您想在 运行 时间对某些类型级别的数据(即您的值索引的 Type 进行比较)。但是当你 运行 你的代码和 values 开始交互时,types 早已不复存在。它们被编译器以生成高效代码的名义删除。因此,您需要手动重建被擦除的类型级别数据,使用一个能让您想起您忘记正在查看的类型的值。您需要 Type.

单例 副本
data SType t where
    SIntT :: SType IntT
    SPtrT :: SType t -> SType (PtrT t)

SType 的成员看起来像 Type 的成员 - 比较 SPtrT (SPtrT SIntT)PtrT (PtrT IntT) 的值的结构 - 但它们是由(类型级别)Type 它们相似。对于每个 t :: Type 恰好有一个 SType t(因此得名 singleton),并且因为 SType 是一个 GADT,[=21] 上的模式匹配=] 告诉类型检查器 t。单例跨越类型和值之间严格执行的分离。

因此,当您构建类型化树时,需要跟踪值的 运行 时间 SType 并在必要时进行比较。 (这基本上相当于编写一个部分验证的类型检查器。)a class in Data.Type.Equality 包含一个比较两个单例并告诉您它们的索引是否匹配的函数。

instance TestEquality SType where
    -- testEquality :: SType t1 -> SType t2 -> Maybe (t1 :~: t2)
    testEquality SIntT SIntT = Just Refl
    testEquality (SPtrT t1) (SPtrT t2)
        | Just Refl <- testEquality t1 t2 = Just Refl
    testEquality _ _ = Nothing

在您的 convert 函数中应用它大致如下所示:

convert :: Statement -> Either String Command
convert (AssignStmt oldLval exp) = do
    (newLval, newLValSType) <- convertLVal oldLval
    (pure, pureSType) <- convertPure exp
    case testEquality newLValSType pureSType of
        Just Refl -> return $ Assign newLval pure'
        Nothing -> Left "type mismatch"

实际上没有很多依赖类型的程序你不能用 TypeInType 和单例来伪造(有吗?),但是复制你所有的数据类型真的很麻烦"normal" 和 "singleton" 形式。 (如果您想隐式传递单例,重复会变得更糟 - 请参阅 Hasochism for the details.) The singletons package 可以为您生成很多样板,但它并不能真正减轻因概念本身重复而造成的痛苦。这就是人们想要的原因将真正的依赖类型添加到 Haskell,但我们距离那还差几年。

The new Type.Reflection module 包含重写的 Typeable class。它的 TypeRep 类似于 GADT,可以作为一种 "universal singleton"。但在我看来,用它编程比用单例编程更笨拙。