为什么这个等效程序不能编译?

Why does this equivalent program not compile?

这个程序:

{-# LANGUAGE RankNTypes, ImpredicativeTypes #-}

import qualified Data.Vector.Mutable as MV
import qualified Data.Vector as V
import Control.Monad.ST
import Control.Monad.Primitive

unsafeModify :: [(forall s . MV.MVector s Int -> ST s ())] -> V.Vector Int -> V.Vector Int
unsafeModify mods vec = runST $ do
    mvec <- V.unsafeThaw vec
    (mods !! 0) mvec
    V.unsafeFreeze mvec

编译。这个节目:

{-# LANGUAGE RankNTypes, ImpredicativeTypes #-}

import qualified Data.Vector.Mutable as MV
import qualified Data.Vector as V
import Control.Monad.ST
import Control.Monad.Primitive

unsafeModify :: [(forall s . MV.MVector s Int -> ST s ())] -> V.Vector Int -> V.Vector Int
unsafeModify mods vec = runST $ do
    mvec <- V.unsafeThaw vec
    ($ mvec) (mods !! 0)
    V.unsafeFreeze mvec

未编译并出现以下错误:

Muts.hs:10:15:
    Couldn't match type ‘forall s1. UV.MVector s1 Int -> ST s1 ()’
                  with ‘UV.MVector s Int -> ST s a0’
    Expected type: [UV.MVector s Int -> ST s a0]
      Actual type: [forall s. UV.MVector s Int -> ST s ()]
    Relevant bindings include
      mvec :: UV.MVector s Int (bound at Muts.hs:9:5)
    In the first argument of ‘(!!)’, namely ‘mods’
    In the first argument of ‘$ mvec’, namely ‘(mods !! 0)’

为什么?

注:这个post是写文的Haskell。您可以将其保存为 Unsafe.lhs 并在您的 GHCi 中尝试。


让我们比较一下不同线路的类型:

 mods                ::     [(forall s . MV.MVector s Int -> ST s ())]
(mods !! 0)          ::      (forall s . MV.MVector s Int -> ST s ())
(mods !! 0)  mvec    ::       forall s. ST s ()


($ mvec)             ::     (MV.Vector s Int -> b) -> b
         (mods !! 0) ::     (forall s . MV.MVector s Int -> ST s ())
($ mvec) (mods !! 0) ::     ????????????????????????

由于 $ 的类型,它们不等价:

($) :: forall a b. (a -> b) -> a -> b

而你需要一些东西

($)  :: (a ~ (forall s . MV.MVector s Int -> ST s ())) =>
      (a -> b) -> a -> b

这是不合法的。

不过,让我们看看你到底想做什么。

> {-# LANGUAGE RankNTypes #-}

> import qualified Data.Vector.Mutable as MV
> import qualified Data.Vector as V
> import Control.Monad.ST
> import Control.Monad.Primitive

  unsafeModify :: ??? -> V.Vector Int -> V.Vector Int

> unsafeModify mods vec = runST $ do
>   mvec <- V.unsafeThaw vec
>   mapM_ ($ mvec) (mods !! 0)
>   V.unsafeFreeze mvec

由于 unsafeModify 的多态第一个参数 mods,事情变得一团糟。你原来的类型

[(forall s . MV.MVector s Int -> ST s ())]

告诉我们这是一个函数列表,其中每个函数都是多态的参数 s,因此每个函数 都可以使用另一个 s。然而,这太过分了。如果 s 在整个列表中共享就没问题:

(forall s. [MV.MVector s Int -> ST s ()])

毕竟,我们希望在同一个ST计算中使用所有函数,因此流状态令牌的类型s可以相同。我们最终得到

> unsafeModify :: (forall s. [MV.MVector s Int -> ST s ()]) -> V.Vector Int -> V.Vector Int

现在,无论您使用 ($ mvec) (mods !! 0)(mods !! 0) mvec 还是 mapM_,您的代码都能顺利编译,因为 s 现在已由 [=29= 正确修复] 在整个列表中。

(这应该是评论,但我需要更多 space。)

遗憾的是,正如@dfeuer 指出的那样,谓词类型在 GHC 中不能很好地工作。 考虑这个例子:

{-# LANGUAGE ImpredicativeTypes, PartialTypeSignatures #-}
import qualified Data.Vector.Mutable as MV
import Control.Monad.ST

-- myIndex :: [forall s. MV.MVector s Int -> ST s ()] 
--         -> Int
--         -> (forall s. MV.MVector s Int -> ST s ())
myIndex = (!!) :: [forall s. MV.MVector s Int -> ST s ()] -> Int -> _

它编译成功,尽管由于类型漏洞而出现警告:

VectorTest.hs:9:69: Warning:
    Found hole ‘_’ with type: forall s. MV.MVector s Int -> ST s ()
    Relevant bindings include
      myIndex :: [forall s. MV.MVector s Int -> ST s ()]
                 -> Int -> forall s. MV.MVector s Int -> ST s ()
        (bound at VectorTest.hs:9:1)

我们可以尝试删除 PartialTypeSignatures 扩展名并用它的类型 forall s. MV.MVector s Int -> ST s () 填充这个洞。但这非常失败:

VectorTest.hs:9:11:
    Couldn't match type ‘forall s2. MV.MVector s2 Int -> ST s2 ()’
                   with ‘MV.MVector s1 Int -> ST s1 ()’
    Expected type: [forall s. MV.MVector s Int -> ST s ()]
                   -> Int -> MV.MVector s1 Int -> ST s1 ()
      Actual type: [MV.MVector s1 Int -> ST s1 ()]
                   -> Int -> MV.MVector s1 Int -> ST s1 ()

最后一个 forall 被提升到顶层,现在 GHC 推断 (!!) 的第一个参数必须是单态元素列表 [MV.MVector s1 Int -> ST s1 ()] 尽管我们的注解!基本上,GHC 有两个选择:

-- Note the hoisted forall s1
myIndex = (!!) :: forall s1. [forall s. MV.MVector s Int -> ST s ()] -> Int 
               -- ^ first choice for instantiating the type of (!!)
               -> MV.MVector s1 Int -> ST s1 ()
               -- ^ second choice

GHC 选择了第二个,但失败了。只有使用部分类型签名,我才能删除第二个选择,以便 GHC 被迫做正确的事情。

如果我们有像 GHC Core 那样的显式类型应用程序,我们本可以编写 (!!) @ (forall s. ...),但可惜我们没有。