多态常量可以映射到*类型*列表吗?

Can a polymorphic constant be mapped over a list of *types*?

Haskell 业余爱好者 - 是否有可能以通用方式将 多态常数 映射到 类型 的列表上?

更准确地说,考虑这个片段:

{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
  
module Main where

import Data.Kind( Type )

class HasName a where name :: String

instance HasName Int where name = "Int"

instance HasName Double where name = "Double"


class AllNames (ts :: [Type]) where
  allNames :: [String]

instance AllNames '[] where
  allNames = []

instance (HasName t, AllNames rest) => AllNames (t ': rest) where
  allNames = name @t : allNames @rest

  
main :: IO ()
main = print $ allNames @'[Int, Double]

毫不奇怪,这按预期工作,即打印 ["Int","Double"]。但是,如果我尝试概括上面的模式,以便代码可以与 any name 类似的多态常量一起使用,那么我 运行 就会遇到问题。

这是我的概括尝试:

{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
  
module Main where

import Data.Kind( Constraint, Type )

--
-- Intended to be the generalized version of 'name'
--
type PolymorphicConstant (c :: Type -> Constraint) (a :: Type) = forall t . c t => a

--
-- Intended to be the generalized version of 'AllNames'
--
class AllPolymorphicConstants (c :: Type -> Constraint) (ts :: [Type]) (a :: Type) where
  allPolymorphicConstants :: PolymorphicConstant c a -> [ a ]

instance AllPolymorphicConstants c '[] a where
  allPolymorphicConstants _ = []

instance (c t, AllPolymorphicConstants c rest a) => AllPolymorphicConstants c (t ': rest) a where
  allPolymorphicConstants f = f @t : allPolymorphicConstants @c @rest @a f

唉,这无法编译(顺便说一句,我使用的是 GHC 8.10.7):

Main.hs:31:74: error:
    • Could not deduce: c t0 arising from a use of ‘f’
      from the context: (c t, AllPolymorphicConstants c rest a)
        bound by the instance declaration at Main.hs:30:10-91
      or from: c t1
        bound by a type expected by the context:
                  PolymorphicConstant c a
        at Main.hs:31:74
    • In the fourth argument of ‘allPolymorphicConstants’, namely ‘f’
      In the second argument of ‘(:)’, namely
        ‘allPolymorphicConstants @c @rest @a f’
      In the expression: f @t : allPolymorphicConstants @c @rest @a f
    • Relevant bindings include
        f :: PolymorphicConstant c a (bound at Main.hs:31:27)
        allPolymorphicConstants :: PolymorphicConstant c a -> [a]
          (bound at Main.hs:31:3)
   |
31 |   allPolymorphicConstants f = f @t : allPolymorphicConstants @c @rest @a f
   |                                                                          ^

我可能遗漏了一些基本的东西,使这种概括成为不可能 - 但它到底是什么?

我希望有人能证明我是错的,但这是我们遇到当前 GHC 限制的少数极端情况之一,我们无法摆脱使用 ProxyTagged 或过去类似的“遗物”。

一个最小的例子

让我们考虑一个更简单的例子:

class C a where

-- Ambiguous type
type T a = forall t. C t => a

请注意,如果我们有一个值 x :: T a,除了显式类型参数 x @t 外,没有明确的方法来使用它。这是使用不明确类型的代价,但没关系。

下面的代码 type-checks 符合预期。

foo :: forall t a. (C t) => T a -> a
foo f = f @t

相反,这不是。

-- Error: Could not deduce (C t0) arising from a use of `foo'
foo2 :: forall t a. (C t) => T a -> a
foo2 = foo

起初这可能令人惊讶。的确,foo2正好同类型的foo,所以foo2=foo显然是可以的!然而,它失败了。原因再次是不明确的类型,经验法则仍然是:如果某物具有不明确的类型,如果我们不传递额外的 @t @a 个参数,我们就不能使用它。

这样做会使一切正常。

foo3 :: forall t a. (C t) => T a -> a
foo3 = foo @t @a

上面有点奇怪,因为我们不会写(也不必写)foo3 @t @a = foo @t @a。我想如果 GHC 强迫我们这样做,那么它也可以让我们“eta-contract 类型参数”一切并写 foo3 = foo.

现在,如果我们 eta-expand 值参数(不是类型!)会怎么样?我们得到一个错误:

-- Error: Could not deduce (C t0) arising from a use of `x'
foo4 :: forall t a. (C t) => T a -> a
foo4 x = foo @t @a x

呻吟。这只是 foo3 = foo @t @a eta-expanded。这里出了什么问题?好吧,问题是一样的:现在我们引入了 x :: T a,这是一个不明确的类型,所以我们不能在没有 @... 参数的情况下使用 x。即使 foo 期望多态值!

在这里我们发现自己无法逃脱。 GHC 看到多态参数并在 x 上添加隐式类型参数抽象,在前面添加 (\@t0 -> ...。但是那是我们不允许使用的一种语法,并且没有办法捕获新鲜类型变量t0。换句话说,我们想写

foo4 :: forall t a. (C t) => T a -> a
foo4 x = foo @t @a (\@t0 -> x @t0)

但我们只能写

foo4 :: forall t a. (C t) => T a -> a
foo4 x = foo @t @a (x @something)

而且没有办法在那里提到 t0。叹息

使用代理

我能看到的唯一“解决方案”是使用 Proxy(或类似的遗物),并避免模棱两可的类型。

-- No longer ambiguous
type T a = forall t. C t => Proxy t -> a

foo :: forall t a. (C t) => T a -> a
foo f = f (Proxy @t)

foo4 :: forall t a. (C t) => T a -> a
foo4 x = foo @t @a x

现在我们可以使用 x as-is 因为它不再是模糊类型。

使用 Tagged 或将多态值包装在 newtypedata 中也可以,因为它使类型不再模糊。

原代码,proxy-fied

type PolymorphicConstant (c :: Type -> Constraint) (a :: Type) 
   = forall t . c t => Proxy t -> a

--
-- Intended to be the generalized version of 'AllNames'
--
class AllPolymorphicConstants (c :: Type -> Constraint) (ts :: [Type]) (a :: Type) where
  allPolymorphicConstants :: PolymorphicConstant c a -> [ a ]

instance AllPolymorphicConstants c '[] a where
  allPolymorphicConstants _ = []

instance (c t, AllPolymorphicConstants c rest a) 
    => AllPolymorphicConstants c (t ': rest) a where
  allPolymorphicConstants f = f (Proxy @t) : allPolymorphicConstants @c @rest @a f