在 where 子句中指定函数的类型

Specifying the type of a function in a where clause

我有以下 Monad 实例,基于 these slides 中的 material:

{-# LANGUAGE InstanceSigs #-}

newtype Iter a = Iter { runIter :: Chunk -> Result a }

instance Monad Iter where
  return = Iter . Done
  (>>=) :: Iter a -> (a -> Iter b) -> Iter b
  (Iter iter0) >>= fiter = Iter $ \chunk -> continue (iter0 chunk)
    where continue :: Result a -> Result b
          continue (Done x rest)     = runIter (fiter x) rest
          continue (NeedInput iter1) = NeedInput (iter1 >>= fiter)
          continue (NeedIO ior)      = NeedIO (liftM continue ior)
          continue (Failed e)        = Failed e

这将给出以下错误:

• Couldn't match type ‘b’ with ‘b1’
  ‘b’ is a rigid type variable bound by
    the type signature for:
      (>>=) :: forall a b. Iter a -> (a -> Iter b) -> Iter b
    at Iteratee.hs:211:12
  ‘b1’ is a rigid type variable bound by
    the type signature for:
      continue :: forall a1 b1. Result a1 -> Result b1
    at Iteratee.hs:214:23
  Expected type: Result b1
    Actual type: Result b
• In the expression: runIter (fiter x) rest
  In an equation for ‘continue’:
      continue (Done x rest) = runIter (fiter x) rest
  In an equation for ‘>>=’:
      (Iter iter0) >>= fiter
        = Iter $ \ chunk -> continue (iter0 chunk)
        where
            continue :: Result a -> Result b
            continue (Done x rest) = runIter (fiter x) rest
            continue (NeedInput iter1) = NeedInput (iter1 >>= fiter)
            continue (NeedIO ior) = NeedIO (liftM continue ior)
            continue (Failed e) = Failed e
• Relevant bindings include
    continue :: Result a1 -> Result b1 (bound at Iteratee.hs:215:11)
    fiter :: a -> Iter b (bound at Iteratee.hs:212:20)
    (>>=) :: Iter a -> (a -> Iter b) -> Iter b
      (bound at Iteratee.hs:212:3)

更让我困惑的是,如果我未定义 continue 但我指定了代码编译的类型。

我的猜测是这个问题是由 continue 实际上有类型引起的

continue :: forall a1 b1. Result a1 -> Result b1

因此上述类型中的两个ab实际上是不同的。但是尽管如此,上面的 continue 必须有一个类型。那么我的问题是,当省略类型时,编译器分配的这个函数的类型是什么。

编辑:

如果显式传递 iter 参数,则代码编译:

instance Monad Iter where
  return = Iter . Done
  (>>=) :: Iter a -> (a -> Iter b) -> Iter b
  (Iter iter0) >>= fiter0 = Iter $ \chunk -> continue fiter0 (iter0 chunk)
    where continue :: (a -> Iter b) -> Result a -> Result b
          continue fiter (Done x rest)     = runIter (fiter x) rest
          continue fiter (NeedInput iter1) = NeedInput (iter1 >>= fiter)
          continue fiter (NeedIO ior)      = NeedIO (liftM (continue fiter) ior)
          continue _ (Failed e)        = Failed e

但是我想避免显式传递参数,同时能够给 continue 一个类型。

在基本Haskell中,每个类型签名都是隐式量化的

foo :: Bool -> a -> a -> a
foo b x y = bar y
   where bar :: a -> a
         bar y | b         = x
               | otherwise = y 

实际上意味着:

foo :: forall a. Bool -> a -> a -> a
foo b x y = bar y
   where bar :: forall a1. a1 -> a1
         bar y | b         = x
               | otherwise = y 

编译失败 因为 x 不是 a1.

类型

删除 bar 的类型签名使其可以编译,并且编译器将关联以阻止正确的类型 a -> a,其中 a 未被普遍量化。请注意,这是编译器可以推断的类型,但用户无法写入。

这样比较不方便!

因此,ScopedTypeVarables GHC 扩展规避了这一点,允许编写

foo :: forall a. Bool -> a -> a -> a
foo b x y = bar y
   where bar :: a -> a
         bar y | b         = x
               | otherwise = y 

这里的第一个 forall a. 使得 a 在内部声明的范围内。此外,bar 的类型仍然是 a -> a 并且没有普遍量化,因为 a 现在在范围内。因此,它编译并且用户现在能够编写想要的类型注释。