GHC错误消息逐字引用类型族定义



下面的代码导致一条错误消息,乍一看,这似乎意味着GHC不理解类型族WrapParams:的定义

{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
import GHC.TypeLits( Nat, type (-) )
import Data.Kind( Type )
newtype Wrapped a = Wrapped a
-- |
-- E.g., `WrapParams 2 (Int -> String -> Bool)` is `Wrapped Int -> Wrapped String -> Bool`
--
type family WrapParams (n :: Nat) (f :: Type) where
WrapParams 0 f = f
WrapParams n (p -> f) = Wrapped p -> WrapParams (n - 1) f

-- |
-- E.g., `extendToWrappedParams @2 (+) (Wrapped 1) (wrapped 2)` is supposed to be 3.
--
class ExtendToWrappedParams (n :: Nat) (f :: Type)  where
extendToWrappedParams :: f -> WrapParams n f
instance ExtendToWrappedParams 0 t where
extendToWrappedParams t = t
instance (ExtendToWrappedParams (n - 1) f) => ExtendToWrappedParams n (p -> f) where
extendToWrappedParams g = h
where
h (Wrapped p) = extendToWrappedParams @(n - 1) @f (g p)

以下是错误(使用GHC 8.10.7(:

• Couldn't match expected type ‘WrapParams n (p -> f)’
with actual type ‘Wrapped p -> WrapParams (n - 1) f’
• In the expression: h
In an equation for ‘extendToWrappedParams’:
extendToWrappedParams g
= h
where
h (Wrapped p) = extendToWrappedParams @(n - 1) @f (g p)
In the instance declaration for ‘ExtendToWrappedParams n (p -> f)’

前两行逐字引用了WrapParams的定义,给人的印象是GHC不知何故不理解它。显然,这不可能是实际发生的事情——那么,我缺少了什么?有没有任何方法(除了使用unsafeCoerce(可以编译上面的代码?

只有当n不是0时,WrapParams n (p -> f)才等于Wrapped p -> WrapParams (n - 1) f。哈斯克尔没有直接的方式来表达不平等。通常的解决方案包括切换到Peano naturals,或者分支布尔比较(Data.Type.Equality.==(,而不是Nat上的模式匹配,这样您就可以将(n == 0) ~ 'False作为约束。

相关内容

  • 没有找到相关文章

最新更新