什么类型:匹配 m s = m == fromSing s?

what is the type of: matches m s = m == fromSing s?

使用 singletons 库,这个简单的函数可以编译并运行。但是,ghci 和 ghc 不同意它的类型签名,如果将他们的任何一个建议粘贴到代码中,它将无法编译。

GHC 接受什么类型的签名? ghc-7.10.3, singletons-2.0.1

{-# LANGUAGE DataKinds, PolyKinds, TypeOperators, TypeFamilies, GADTs, UndecidableInstances, FlexibleContexts #-}

import Data.Proxy (KProxy(..))
import Data.Singletons
import Data.Singletons.Prelude

-- ghc rejects this type signature, but if I leave it off, ghci :t shows exactly this.
matches :: (Eq (DemoteRep 'KProxy), SingKind 'KProxy) => DemoteRep 'KProxy -> Sing a -> Bool
matches m s = m == fromSing s

t :: Sing True
t = sing

demo :: Bool
demo = matches True t

GHC 的上述类型签名错误:

Couldn't match type ‘DemoteRep 'KProxy’ with ‘DemoteRep 'KProxy’
NB: ‘DemoteRep’ is a type function, and may not be injective
The kind variable ‘k2’ is ambiguous
Use -fprint-explicit-kinds to see the kind arguments
Expected type: DemoteRep 'KProxy -> Sing a -> Bool
  Actual type: DemoteRep 'KProxy -> Sing a -> Bool
In the ambiguity check for the type signature for ‘matches’:
  matches :: forall (k :: BOX)
                    (k1 :: BOX)
                    (k2 :: BOX)
                    (k3 :: BOX)
                    (a :: k3).
             (Eq (DemoteRep 'KProxy), SingKind 'KProxy) =>
             DemoteRep 'KProxy -> Sing a -> Bool
To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
In the type signature for ‘matches’:
  matches :: (Eq (DemoteRep KProxy), SingKind KProxy) =>
             DemoteRep KProxy -> Sing a -> Bool

ghc -Wall 建议使用不同的类型签名,但 BOX 内容也不会被接受:

Top-level binding with no type signature:
         matches :: forall (k :: BOX) (a :: k).
                    (Eq (DemoteRep 'KProxy), SingKind 'KProxy) =>
                    DemoteRep 'KProxy -> Sing a -> Bool

'KProxy 在类型级别就像 Proxy 在值级别:它有一个幻影。就像我们在值级别用幻像类型 aProxy :: Proxy a 一样,我们必须打开种类签名并在类型级别用幻像类型 k'KProxy :: KProxy k .希望这个类比有意义。这是它的样子:

{-# LANGUAGE DataKinds, PolyKinds, TypeOperators, TypeFamilies, GADTs, UndecidableInstances, FlexibleContexts, KindSignatures #-}

import Data.Proxy (KProxy(..))
import Data.Singletons
import Data.Singletons.Prelude

matches ::
  ( Eq (DemoteRep ('KProxy :: KProxy k))
  , SingKind ('KProxy :: KProxy k)
  ) => DemoteRep ('KProxy :: KProxy k) -> Sing (a :: k) -> Bool
matches m s = m == fromSing s

这个类型变量 k 将同时出现在 DemoteRep ...Sing ... 中,这就是让我们对 m == fromSing s.

进行类型检查的原因

GHCi,虽然可爱而且通常很聪明,但不知道类型签名需要 "another level of indirection" 并且需要引入类型变量。

一边

我要提醒大家反对这里的大多数意见,即 -fprint-explicit-kinds 是有帮助的:

λ> :t matches
matches
  :: (Eq (DemoteRep * ('KProxy *)), SingKind * ('KProxy *)) =>
     DemoteRep * ('KProxy *) -> Sing * a -> Bool

对我来说,这并没有真正指向这里发生的事情。我只能通过使用方便的 :info 命令查找 DemoteRep'KProxySing 的签名来拼凑所有内容。

问题在于您正在使用(本质上)一种 class,但您没有正确确定种类。特别是,出现的三个 'KProxy 都可以指代 不同的 种类。一种常见的方法是 name 使用相等约束的代理,并重复使用该名称。与给每个代理一个签名相比,这节省了一些输入:

matches :: (kproxy ~ ('KProxy :: KProxy k),
            Eq (DemoteRep kproxy),
            SingKind kproxy)
        => DemoteRep kproxy
            -> Sing (a :: k) -> Bool

这清楚地表明代理应该都是相同的,特别是应该与传递给 Sing 的类型相同。