在没有 unsafeCoerce 的情况下处理存在主义

Juggling existentials without unsafeCoerce

最近我一直在玩这个类型,我知道它是自由分配函子的编码(关于它的切线背景,见 ):

data Ev g a where
    Ev :: ((g x -> x) -> a) -> Ev g a

deriving instance Functor (Ev g)

存在构造函数确保我只能通过提供多态提取器forall x. g x -> x来使用Ev g,并且可以为自由构造的提升和降低函数提供兼容类型:

runEv :: Ev g a -> (forall x. g x -> x) -> a
runEv (Ev s) f = s f

evert :: g a -> Ev g a
evert u = Ev $ \f -> f u

revert :: Distributive g => Ev g a -> g a
revert (Ev s) = s <$> distribute id

然而,尝试给 Ev g 一个 Distributive 实例有困难。鉴于 Ev g 最终只是一个具有奇怪参数类型的函数,人们可能希望只是线程化 distribute 函数(相当于 (??) :: Functor f => f (a -> b) -> a -> f b from lens,而不是通过 Ev 包装器以任何方式检查参数类型:

instance Distributive (Ev g) where
    distribute = Ev . distribute . fmap (\(Ev s) -> s)

然而,这不起作用:

Flap3.hs:95:53: error:
    • Couldn't match type ‘x’ with ‘x0’
      ‘x’ is a rigid type variable bound by
        a pattern with constructor:
          Ev :: forall (g :: * -> *) x a. ((g x -> x) -> a) -> Ev g a,
        in a lambda abstraction
        at Flap3.hs:95:44-47
      Expected type: (g x0 -> x0) -> a
        Actual type: (g x -> x) -> a
    • In the expression: s
      In the first argument of ‘fmap’, namely ‘(\ (Ev s) -> s)’
      In the second argument of ‘(.)’, namely ‘fmap (\ (Ev s) -> s)’
    • Relevant bindings include
        s :: (g x -> x) -> a (bound at Flap3.hs:95:47)
   |
95 |     distribute = Ev . distribute . fmap (\(Ev s) -> s) 
   |                                                     ^
Failed, no modules loaded.

GHC 反对重新包装存在主义,即使我们在展开和重新包装之间没有对它做任何不当的事情。我找到的唯一出路是求助于 unsafeCoerce:

instance Distributive (Ev g) where
    distribute = Ev . distribute . fmap (\(Ev s) -> unsafeCoerce s)

或者,以更谨慎的方式拼写:

instance Distributive (Ev g) where
    distribute = eevee . distribute . fmap getEv
        where
        getEv :: Ev g a -> (g Any -> Any) -> a
        getEv (Ev s) = unsafeCoerce s
        eevee :: ((g Any -> Any) -> f a) -> Ev g (f a)
        eevee s = Ev (unsafeCoerce s)

没有 unsafeCoerce 是否可以解决这个问题?还是真的没有别的办法?

补充说明:


以下给 Ev g 一个 Representable 实例的做法可能会使问题更加明显。 ,这实际上是不可能的;不出所料,我不得不再次使用 unsafeCoerce

-- Cf. dfeuer's answer.
newtype Goop g = Goop { unGoop :: forall y. g y -> y }

instance Representable (Ev g) where
    type Rep (Ev g) = Goop g
    tabulate f = Ev $ \e -> f (Goop (goopify e))
        where
        goopify :: (g Any -> Any) -> g x -> x
        goopify = unsafeCoerce
    index (Ev s) = \(Goop e) -> s e

虽然 goopify 确实看起来令人担忧,但我认为这里有一个安全的理由。存在编码意味着任何传递给包装函数的 e 都必然是元素类型上的提取器多态,它专门用于 Any 仅仅是因为我要求它发生。既然如此,forall x. g x -> xe 的合理类型。这种专注于 Any 只是为了迅速用 unsafeCoerce 撤消它的舞蹈是必要的,因为 GHC 迫使我通过做出选择来摆脱存在主义。如果我在这种情况下省略 unsafeCoerce 会发生这种情况:

Flap4.hs:64:37: error:
    • Couldn't match type ‘y’ with ‘x0’
      ‘y’ is a rigid type variable bound by
        a type expected by the context:
          forall y. g y -> y
        at Flap4.hs:64:32-37
      Expected type: g y -> y
        Actual type: g x0 -> x0
    • In the first argument of ‘Goop’, namely ‘e’
      In the first argument of ‘f’, namely ‘(Goop e)’
      In the expression: f (Goop e)
    • Relevant bindings include
        e :: g x0 -> x0 (bound at Flap4.hs:64:24)
   |
64 |     tabulate f = Ev $ \e -> f (Goop e) 
   |                                     ^
Failed, no modules loaded.

Prolegomena 需要 运行 这里的代码:

{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}

import Data.Distributive
import Data.Functor.Rep
import Unsafe.Coerce
import GHC.Exts (Any)

-- A tangible distributive, for the sake of testing.
data Duo a = Duo { fstDuo :: a, sndDuo :: a }
    deriving (Show, Eq, Ord, Functor)

instance Distributive Duo where
    distribute u = Duo (fstDuo <$> u) (sndDuo <$> u)

每个 Distributive 仿函数都可以构成 Representable,尽管我们无法在 Haskell 中证明这一点(我想这不是建设性的)。但是解决问题的一种方法是切换 类.

newtype Evv f a = Evv
  {unEvv :: forall g. Representable g
         => (forall x. f x -> g x) -> g a}

instance Functor (Evv g) where
  fmap f (Evv q) = Evv $ \g -> fmap f (q g)

evert :: g a -> Evv g a
evert ga = Evv $ \f -> f ga

revert :: Representable g => Evv g a -> g a
revert (Evv f) = f id

newtype Goop f = Goop
  {unGoop :: forall x. f x -> x}

instance Distributive (Evv g) where
  collect = collectRep

instance Representable (Evv g) where
  type Rep (Evv g) = Goop g
  tabulate f = Evv $ \g -> fmap (\rg -> f (Goop $ \fx -> index (g fx) rg)) $ tabulate id
  index (Evv g) (Goop z) = runIdentity $ g (Identity . z)

我还没有直接用 Distributive 尝试过这个(正如 HTNW 所建议的),但如果由于某种原因根本不可能,我也不会感到惊讶。

警告:我还没有证明这实际上是免费的Representable

danidiaz 和 dfeuer 的建议使我得到了更简洁的编码,尽管 unsafeCoerce 仍然是必要的:

{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}

import Unsafe.Coerce
import GHC.Exts (Any)
import Data.Distributive
import Data.Functor.Rep

-- Px here stands for "polymorphic extractor".
newtype Px g = Px { runPx :: forall x. g x -> x }

newtype Ev g a = Ev { getEv :: Px g -> a }
    deriving Functor

runEv :: Ev g a -> (forall x. g x -> x) -> a
runEv s e = s `getEv` Px e

evert :: g a -> Ev g a
evert u = Ev $ \e -> e `runPx` u

revert :: Distributive g => Ev g a -> g a
revert (Ev s) = (\e -> s (mkPx e)) <$> distribute id
    where
    mkPx :: (g Any -> Any) -> Px g
    mkPx e = Px (unsafeCoerce e) 

instance Distributive (Ev g) where
    distribute = Ev . distribute . fmap getEv

instance Representable (Ev g) where
    type Rep (Ev g) = Px g
    tabulate = Ev 
    index = getEv

我最初的 Ev 公式中的 x 变量本质上是被普遍量化的;我只是把它伪装成函数箭头后面的存在主义。虽然这种编码使得在没有 unsafeCoerce 的情况下编写 revert 成为可能,但它将负担转移到了实例实现上。在这种情况下,直接使用通用量化最终会更好,因为它可以将魔力集中在一个地方。

此处的 unsafeCoerce 技巧与问题中的 tabulate 基本相同:distribute id :: Distributive g => g (g x -> x) 中的 x 专用于 Any,并且然后专业化立即撤消,在 fmapunsafeCoerce 下。我相信这个技巧是安全的,因为我对输入 unsafeCoerce.

的内容有足够的控制权

至于去掉unsafeCoerce,我实在是想不出办法。部分问题是我似乎需要某种形式的指示类型,因为 unsafeCoerce 技巧最终相当于将 forall x. g (g x -> x) 变成 g (forall x. g x -> x)。为了进行比较,我可以编写一个模糊类似的场景,如果更简单的话,使用将属于拟议的 ExplicitImpredicativeTypes 扩展范围的命令类型功能的子集(参见 GHC ticket #14859 和链接供讨论):

{-# LANGUAGE ImpredicativeTypes #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE RankNTypes #-}

newtype Foo = Foo ([forall x. Num x => x] -> Int)

testFoo :: Applicative f => Foo -> f Int
testFoo (Foo f) = fmap @_ @[forall x. Num x => x] f 
    $ pure @_ @[forall x. Num x => x] [1,2,3]
GHCi> :set -XImpredicativeTypes 
GHCi> :set -XTypeApplications 
GHCi> testFoo @Maybe (Foo length)
Just 3
然而,

distribute id[1,2,3]更棘手。在 id :: g x -> g x 中,我想保持量化的类型变量出现在两个地方,其中之一是 distribute 的第二个类型参数((->) (g x) 仿函数)。至少在我未经训练的眼睛看来,这看起来非常棘手。