是否可以将类型族用作高阶“类型函数”以传递给另一个类型族?下面的代码是一个简单的示例:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Test where
import GHC.TypeLits as T
type family Apply (f :: Nat -> Nat -> Nat) (n :: Nat) (m :: Nat) :: Nat where
Apply f n m = f n m
type family Plus (n :: Nat) (m :: Nat) :: Nat where
Plus n m = n T.+ m
type family Plus' (n :: Nat) (m :: Nat) :: Nat where
Plus' n m = Apply (T.+) n m
Plus
的第一个声明是有效的,而第二个声明(Plus'
)则产生以下错误:
Test.hs:19:3: error:
• The type family ‘+’ should have 2 arguments, but has been given none
• In the equations for closed type family ‘Plus'’
In the type family declaration for ‘Plus'’
|
19 | Plus' n m = Apply (T.+) n m
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^
是否可以使用Apply
类型的函数来实现Plus
?
编辑:评论者,链接到https://ghc.haskell.org/trac/ghc/ticket/9898上的功能请求报告。它提到了singleton
库。我很乐意使用它或其他“替代方法”来实现对Nat
(例如+
,*
,{{1})上的算术运算进行抽象的类似效果的示例}和-
。
答案 0 :(得分:7)
有用的方法是去功能化。您可以自己实现,也可以在singletons
库中找到实现。
核心是一种“开放式”:
data TYFUN :: Type -> Type -> Type
type TyFun a b = TYFUN a b -> Type
TyFun a b
是开放式的;它没有像普通的data
那样封闭。您可以按以下方式“声明”新功能。
data Plus :: TyFun Nat (TyFun Nat Nat)
然后您可以定义此类型族以链接声明和定义
type family Apply (f :: TyFun a b) (x :: a) :: b
data PlusSym1 :: Nat -> TyFun Nat Nat -- see how we curry
type instance Apply Plus x = PlusSym1 x
type instance Apply (PlusSym1 x) y = x + y
现在,Plus
是一个普通的类型构造函数:数据类型,而不是类型族。这意味着您可以将其传递给其他类型的族。请注意,他们必须TyFun
意识到自己。
type family Foldr (cons :: TyFun a (TyFun b b)) (nil :: b) (xs :: [a]) :: b where
Foldr _ n '[] = n
Foldr c n (x:xs) = Apply (Apply c x) (Foldr c n xs)
type Example = Foldr Plus 0 [1,2,3]
开放种类背后的想法是Type
已经是开放种类,并且A -> Type
,A -> B -> Type
之类的种类本身也是开放的。 TYFUN
是将事物标识为TyFun
的标签,而TyFun
是一种开放类型,与其他开放类型实际上是脱节的。您还可以直接使用Type
开放类:
type family TyFunI :: Type -> Type
type family TyFunO :: Type -> Type
type family Apply (f :: Type) (x :: TyFunI f) :: TyFunO f
data Plus :: Type
data PlusSym1 :: Nat -> Type
type instance TyFunI Plus = Nat
type instance TyFunO Plus = Type
type instance TyFunI (PlusSym1 _) = Nat
type instance TyFunO (PlusSym1 _) = Nat
type instance Apply Plus x = PlusSym1 x
type instance Apply (PlusSym1 x) y = x + y
从好的方面来说,它可以处理依赖类型的函数,但是,之所以这样做,是因为它通过使所有内容均为“ Type
”而无耻地抛出了类型检查。这不是String
类型的代码的坏处,因为它全是编译时的,但仍然如此。