如何从类型级别的列表生成术语级别的列表?
How can I generate term-level lists from a type-level ones?
我正在尝试从类型级别的值中生成术语级别的值。我有以下代码
class Term a where
type family Result a :: Type
term :: Result a
instance (KnownSymbol s) => Term s where
type instance Result s = String
term = symbolVal (Proxy @s)
instance (KnownNat n) => Term n where
type instance Result n = Integer
term = natVal (Proxy @n)
这很好用:
>>> :t term @"hello"
term @"hello" :: String
>>> term @"hello"
"hello"
我如何在类型级列表上传播这个想法?当我尝试这样的事情时
instance Term '[] where
type instance Result ('[] :: [a]) = [a]
term = []
instance (Term a, Term as) => Term (a ': as) where
type instance Result (a ': as) = Result a ': Result as
term = term @a : term @as
GHC 说 Result (a ': as)
的 RHS 具有类型 [*],但预期是 type
。
• Expected a type, but ‘Result a : Result as’ has kind ‘[*]’
• In the type ‘Result a : Result as’
In the type instance declaration for ‘Result’
In the instance declaration for ‘Term (a : as)’
我只有一个可以编译的解决方案,但它预计只会评估第一个元素:
instance (Term a, Term as) => Term (a ': as) where
type instance Result (a ': as) = [Result a]
term = [term @a]
>>> term @'["hello", "world"]
["hello"]
是否可以递归地将类型级列表转换为术语?
完整代码:
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Term where
import Data.Kind
import Data.Proxy
import GHC.TypeLits
class Term a where
type family Result a :: Type
term :: Result a
instance (KnownSymbol s) => Term s where
type instance Result s = String
term = symbolVal (Proxy @s)
instance (KnownNat n) => Term n where
type instance Result n = Integer
term = natVal (Proxy @n)
instance Term '[] where
type instance Result ('[] :: [a]) = [a]
term = []
instance (Term a, Term as) => Term (a ': as) where
type instance Result (a ': as) = Result a ': Result as
term = term @a : term @as
当 GHC 抱怨时:
• Expected a type, but ‘Result a : Result as’ has kind ‘[*]’
• In the type ‘Result a : Result as’
In the type instance declaration for ‘Result’
In the instance declaration for ‘Term (a : as)’
问题是 Result
应该给我们 term
的 return 类型,所以这应该是术语级列表的类型(这将是属于 Type
,或旧命名法 1 中的 *
)。然而,我们显然有一个 type-level 列表的表达式(它属于 [*]
因为 Result a
必须是 Type
,这是相同的如 *
).
实际上我们希望Result
在这里生成[Integer]
或[String]
,这取决于类型级列表是[Nat]
还是[=41] =].我们实际上并不想根据 as
是什么递归构造 Result (a ': as)
。因此,让我们将其更改为:
instance (Term a, Term as) => Term (a ': as) where
type instance Result (a ': as) = [Result a]
term = term @a : term @as
现在我们的错误是:
• Couldn't match expected type ‘[Result a1]’
with actual type ‘Result as’
• In the second argument of ‘(:)’, namely ‘term @as’
In the expression: term @a : term @as
In an equation for ‘term’: term = term @a : term @as
啊哈。我们实际上并没有保证 GHC 满意 Result as
将是一种可以附加 Result a
的列表。据 GHC 所知,这是从两个独立实例对类型族的两次独立调用,没有理由总是 return 一个类型是另一个结果的列表。但是我们从我们真正想要的实例中知道这实际上总是成立的,所以也许我们可以只添加等式约束?2
instance (Term a, Term as, Result as ~ [Result a]) => Term (a ': as) where
type instance Result (a ': as) = [Result a]
term = term @a : term @as
现在完全没有编译器错误!让我们试试吧:
>>> term @[1, 2, 3]
<interactive>:25:1: error:
• Couldn't match type ‘Nat’ with ‘Integer’
arising from a use of ‘term’
• In the expression: term @[1, 2, 3]
In an equation for ‘it’: it = term @[1, 2, 3]
嗯,这不是我们所期望的。
这个问题花了我一段时间才弄明白,但问题出在 Term '[]
的基础实例中,而不是递归实例。
type instance Result ('[] :: [a]) = [a]
这表示应用于空类型级别列表的 term
是包含与类型级别列表中相同类型的术语级别列表。当您直接使用 term @'[]
时它会起作用,因为类型级别的空列表是多类型的(就像术语级别的空列表是多态的一样)。它可以是我们想要的任何类型的类型级别列表。因此,如果我们在术语级别获取生成的空列表并将其提供给预期 [Bool]
的上下文,GHC 将尽职尽责地推断我们必须一直在做 term @('[] :: [Bool])
.
但是当从非空列表实例使用这个空列表实例时,我们不会使用可以自由推断为任何类型的文字'[]我们需要。当我们到达种类 [Nat]
或 [Symbol]
类型级别列表的末尾时,我们会使用它。这意味着我们最终得到类似 Result ('[] :: [Nat]) = [Nat]
的结果,即我们列表的尾部是 Nat
的术语级别列表。不幸的是,我们要求 Result as ~ [Result a]
,但现在情况并非如此;最后一个 Result a
是 Integer
,最后一个 Result as
是 [Nat]
。即使 GHC 没有把我们拉起来,你也不能将 Integer
转换为 [Nat]
.
如何解决这个问题是模糊的,因为 Term
确实有 两个 参数,而不是一个。在 Term a
中, a
的 种类 也因实例而异。 GHCI 知道这一点并可以告诉我们:
λ :info Term
type Term :: forall k. k -> Constraint
class Term a where
type Result :: forall {k}. k -> *
type family Result a
term :: Result a
注意 type Term
行; Monoid
之类的东西会显示 type Monoid :: * -> Constraint
,或者 KnownNat
会显示 type KnownNat :: Nat -> Constraint
.
其实还是不错的,不然早就被击落了。因为这两个实例头确实看起来确实重叠3:
instance (KnownSymbol s) => Term s
instance (KnownNat n) => Term n
但事实上,通过以不同方式实例化 kind 参数 k
,它们实际上是不同的,这让我们得救了:
instance (KnownSymbol s) => Term (s :: Symbol)
instance (KnownNat n) => Term (n :: Nat)
如果我们使 kind 参数更明确,我们可以使 Result
取决于 kind,而不是类型。无论如何,这实际上是我们想要的;类型级别 1
、2
和 3
都具有 Result
的 Integer
因为它们都具有 Nat
类型;我们不需要为每个人计算不同的结果类型 Nat
.
class Term (a :: k) where
type family Result k :: Type
term :: Result k
instance (KnownSymbol s) => Term (s :: Symbol) where
type instance Result Symbol = String
term = symbolVal (Proxy @s)
instance (KnownNat n) => Term (n :: Nat) where
type instance Result Nat = Integer
term = natVal (Proxy @n)
这也让我们摆脱了列表递归实例中烦人的相等约束。 Result
取决于类型,编译器可以像我们一样看到整个列表中只涉及一种类型(因为类型级列表必须具有所有相同类型的元素)。
instance (Term a, Term as) => Term ((a ': as) :: [k]) where
type instance Result [k] = [Result k]
term = term @k @a : term @[k] @as
现在我们有 Result
取决于种类而不是类型,我们可以针对基本情况执行此操作:
instance Term ('[] :: [k]) where
type instance Result [k] = [Result k]
term = []
老实说,我不是 100% 确定为什么会这样。我们 Result [k]
依赖于另一个 Term
供应 Result k
的实例,但我们没有保证这样一个实例将存在的约束(而且我不知道我们如何会写一个,没有类型 k
实际上可以传递给 Term
)。但它确实有效:
>>> term @_ @3
3
it :: Integer
>>> term @_ @[1, 2, 3]
[1,2,3]
it :: [Integer]
>>> term @_ @["hello", "world"]
["hello","world"]
it :: [String]
但最大的缺点是现在有一个额外的参数我们必须显式传递给 term
。 GHC 可以推断出它是什么(这就是我们可以使用 @_
的原因),但它必须排在第一位,因为它是后面的参数类型。
我想出的解决这个问题的最简单方法是将 term
重命名为 term'
,并提供一个新的 term
,将 kind 参数标记为已推断,以便它需要不(也不能)用类型应用程序指定。不过这需要 GHC 9 或更高版本。
term :: forall {k} (a :: k). Term (a :: k) => Result k
term = term' @k @a
不过后来我想到了更好的办法。在与列表有关的两个实例中,我们必须重复 type instance Result [k] = [Result k]
的相同定义,这已经让我有些恼火。那是因为 实例 取决于实际类型,但类型族 Result
仅取决于它的种类,所以当我们有两个实例覆盖同一种类的不同类型时,我们就结束了up 需要多余的定义。对我来说,这已经表明这并不是 class 的关联类型族,但作为独立类型族会更好。
type family Demote k where
Demote Symbol = String
Demote Nat = Integer
Demote [k] = [Demote k]
将类型族从 class 中移除后,如果我们不再需要显式类型参数 k
就好了(它仍将作为隐式参数存在)参数,但它不会弄乱我们的类型应用程序)。不幸的是,调用 Demote
我们仍然需要对该类型的显式引用。如果我们的 class 定义是 class Term a
而不是 class Term (a :: k)
,我们就没有那个。但是如果我们添加另一个间接层,我们可以创建一个类型同义词(甚至不必是一个类型族!),它得到类型 4:
type KindOf (a :: k) = k
class Term a where
term :: Demote (KindOf a)
现在终于可以了!
>>> term @19
19
it :: Integer
>>> term @[10, 5, 0]
[10,5,0]
it :: [Integer]
>>> term @["take", "that", "typechecker"]
["take","that","typechecker"]
it :: [String]
唯一(次要?)的问题是现在 term @'[]
不再独立工作,因为它需要真正知道空列表的种类(以解决 Demote
type family) 而不是给我们一个多态的空列表。
>>> term @'[]
<interactive>:26:1: error:
• Couldn't match type: Result k0
with: Result k
Expected: [Result k]
Actual: [Result k0]
NB: ‘Result’ is a non-injective type family
The type variable ‘k0’ is ambiguous
• In the ambiguity check for the inferred type for ‘it’
To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
When checking the inferred type
it :: forall {k}. [Result k]
>>> term @('[] :: [Symbol])
[]
it :: [String]
这是我最终得到的最终工作模块:
{-# LANGUAGE AllowAmbiguousTypes, DataKinds, PolyKinds, FlexibleInstances, ScopedTypeVariables, TypeApplications, TypeFamilies, TypeOperators #-}
module Term
where
import GHC.Types
import GHC.TypeLits
import Data.Proxy
type KindOf (a :: k) = k
type family Demote k where
Demote Symbol = String
Demote Nat = Integer
Demote [k] = [Demote k]
class Term a where
term :: Demote (KindOf a)
instance (KnownSymbol s) => Term (s :: Symbol) where
term = symbolVal (Proxy @s)
instance (KnownNat n) => Term (n :: Nat) where
term = natVal (Proxy @n)
instance Term ('[] :: [k]) where
term = []
instance (Term a, Term as) => Term ((a ': as) :: [k]) where
term = term @a : term @as
1 我认为 GHC 说“期望一种类型”意味着它期望 Type
/*
在这里因为这比初学者更容易混淆“类型不匹配,预期 *
,实际 [*]
”。
2 这是在实例中为 GHC 的类型推断添加额外“公理”的常用技巧。如果实例上的约束包括 foo ~ bar
,那么 GHC 将在对该实例进行类型检查时假定它通常为真,并在使用该实例时检查它是否真的(对于涉及的特定类型)。如果它是你“知道”的东西永远是真的但不能在 Haskell 中证明,那么该检查将永远通过;这使您可以利用无法在 Haskell.
中实际证明的事实
3 请记住,必须能够在不考虑其约束的情况下确定哪些实例适用于给定情况!
4我有一种预感,我在这里重新发现了一个轮子,果然KindOf
already exists in the singletons
package的确切定义。 singletons
包含许多用于执行此类类型级别对应术语级别内容的高级机制;我不知道该向你指出什么,但实际上你可以用 singletons
中的东西替换你所有的 Term
class 并且它已经可以工作并且是更一般。然而 singletons
是一个相当高级的包,所以不是最容易学习的东西。
如果您计划将此类代码用于持续的实际目的,我强烈建议您投入精力学习如何使用 singletons
。可能比自己写好。
如果您写这篇文章是为了了解这些类型级别的编程概念是如何工作的,那么 singletons
将会有很多示例说明您可以将其推进到什么程度,但它的实现可能很难对一个相对新手理解。
我正在尝试从类型级别的值中生成术语级别的值。我有以下代码
class Term a where
type family Result a :: Type
term :: Result a
instance (KnownSymbol s) => Term s where
type instance Result s = String
term = symbolVal (Proxy @s)
instance (KnownNat n) => Term n where
type instance Result n = Integer
term = natVal (Proxy @n)
这很好用:
>>> :t term @"hello"
term @"hello" :: String
>>> term @"hello"
"hello"
我如何在类型级列表上传播这个想法?当我尝试这样的事情时
instance Term '[] where
type instance Result ('[] :: [a]) = [a]
term = []
instance (Term a, Term as) => Term (a ': as) where
type instance Result (a ': as) = Result a ': Result as
term = term @a : term @as
GHC 说 Result (a ': as)
的 RHS 具有类型 [*],但预期是 type
。
• Expected a type, but ‘Result a : Result as’ has kind ‘[*]’
• In the type ‘Result a : Result as’
In the type instance declaration for ‘Result’
In the instance declaration for ‘Term (a : as)’
我只有一个可以编译的解决方案,但它预计只会评估第一个元素:
instance (Term a, Term as) => Term (a ': as) where
type instance Result (a ': as) = [Result a]
term = [term @a]
>>> term @'["hello", "world"]
["hello"]
是否可以递归地将类型级列表转换为术语?
完整代码:
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Term where
import Data.Kind
import Data.Proxy
import GHC.TypeLits
class Term a where
type family Result a :: Type
term :: Result a
instance (KnownSymbol s) => Term s where
type instance Result s = String
term = symbolVal (Proxy @s)
instance (KnownNat n) => Term n where
type instance Result n = Integer
term = natVal (Proxy @n)
instance Term '[] where
type instance Result ('[] :: [a]) = [a]
term = []
instance (Term a, Term as) => Term (a ': as) where
type instance Result (a ': as) = Result a ': Result as
term = term @a : term @as
当 GHC 抱怨时:
• Expected a type, but ‘Result a : Result as’ has kind ‘[*]’
• In the type ‘Result a : Result as’
In the type instance declaration for ‘Result’
In the instance declaration for ‘Term (a : as)’
问题是 Result
应该给我们 term
的 return 类型,所以这应该是术语级列表的类型(这将是属于 Type
,或旧命名法 1 中的 *
)。然而,我们显然有一个 type-level 列表的表达式(它属于 [*]
因为 Result a
必须是 Type
,这是相同的如 *
).
实际上我们希望Result
在这里生成[Integer]
或[String]
,这取决于类型级列表是[Nat]
还是[=41] =].我们实际上并不想根据 as
是什么递归构造 Result (a ': as)
。因此,让我们将其更改为:
instance (Term a, Term as) => Term (a ': as) where
type instance Result (a ': as) = [Result a]
term = term @a : term @as
现在我们的错误是:
• Couldn't match expected type ‘[Result a1]’
with actual type ‘Result as’
• In the second argument of ‘(:)’, namely ‘term @as’
In the expression: term @a : term @as
In an equation for ‘term’: term = term @a : term @as
啊哈。我们实际上并没有保证 GHC 满意 Result as
将是一种可以附加 Result a
的列表。据 GHC 所知,这是从两个独立实例对类型族的两次独立调用,没有理由总是 return 一个类型是另一个结果的列表。但是我们从我们真正想要的实例中知道这实际上总是成立的,所以也许我们可以只添加等式约束?2
instance (Term a, Term as, Result as ~ [Result a]) => Term (a ': as) where
type instance Result (a ': as) = [Result a]
term = term @a : term @as
现在完全没有编译器错误!让我们试试吧:
>>> term @[1, 2, 3]
<interactive>:25:1: error:
• Couldn't match type ‘Nat’ with ‘Integer’
arising from a use of ‘term’
• In the expression: term @[1, 2, 3]
In an equation for ‘it’: it = term @[1, 2, 3]
嗯,这不是我们所期望的。
这个问题花了我一段时间才弄明白,但问题出在 Term '[]
的基础实例中,而不是递归实例。
type instance Result ('[] :: [a]) = [a]
这表示应用于空类型级别列表的 term
是包含与类型级别列表中相同类型的术语级别列表。当您直接使用 term @'[]
时它会起作用,因为类型级别的空列表是多类型的(就像术语级别的空列表是多态的一样)。它可以是我们想要的任何类型的类型级别列表。因此,如果我们在术语级别获取生成的空列表并将其提供给预期 [Bool]
的上下文,GHC 将尽职尽责地推断我们必须一直在做 term @('[] :: [Bool])
.
但是当从非空列表实例使用这个空列表实例时,我们不会使用可以自由推断为任何类型的文字'[]我们需要。当我们到达种类 [Nat]
或 [Symbol]
类型级别列表的末尾时,我们会使用它。这意味着我们最终得到类似 Result ('[] :: [Nat]) = [Nat]
的结果,即我们列表的尾部是 Nat
的术语级别列表。不幸的是,我们要求 Result as ~ [Result a]
,但现在情况并非如此;最后一个 Result a
是 Integer
,最后一个 Result as
是 [Nat]
。即使 GHC 没有把我们拉起来,你也不能将 Integer
转换为 [Nat]
.
如何解决这个问题是模糊的,因为 Term
确实有 两个 参数,而不是一个。在 Term a
中, a
的 种类 也因实例而异。 GHCI 知道这一点并可以告诉我们:
λ :info Term
type Term :: forall k. k -> Constraint
class Term a where
type Result :: forall {k}. k -> *
type family Result a
term :: Result a
注意 type Term
行; Monoid
之类的东西会显示 type Monoid :: * -> Constraint
,或者 KnownNat
会显示 type KnownNat :: Nat -> Constraint
.
其实还是不错的,不然早就被击落了。因为这两个实例头确实看起来确实重叠3:
instance (KnownSymbol s) => Term s
instance (KnownNat n) => Term n
但事实上,通过以不同方式实例化 kind 参数 k
,它们实际上是不同的,这让我们得救了:
instance (KnownSymbol s) => Term (s :: Symbol)
instance (KnownNat n) => Term (n :: Nat)
如果我们使 kind 参数更明确,我们可以使 Result
取决于 kind,而不是类型。无论如何,这实际上是我们想要的;类型级别 1
、2
和 3
都具有 Result
的 Integer
因为它们都具有 Nat
类型;我们不需要为每个人计算不同的结果类型 Nat
.
class Term (a :: k) where
type family Result k :: Type
term :: Result k
instance (KnownSymbol s) => Term (s :: Symbol) where
type instance Result Symbol = String
term = symbolVal (Proxy @s)
instance (KnownNat n) => Term (n :: Nat) where
type instance Result Nat = Integer
term = natVal (Proxy @n)
这也让我们摆脱了列表递归实例中烦人的相等约束。 Result
取决于类型,编译器可以像我们一样看到整个列表中只涉及一种类型(因为类型级列表必须具有所有相同类型的元素)。
instance (Term a, Term as) => Term ((a ': as) :: [k]) where
type instance Result [k] = [Result k]
term = term @k @a : term @[k] @as
现在我们有 Result
取决于种类而不是类型,我们可以针对基本情况执行此操作:
instance Term ('[] :: [k]) where
type instance Result [k] = [Result k]
term = []
老实说,我不是 100% 确定为什么会这样。我们 Result [k]
依赖于另一个 Term
供应 Result k
的实例,但我们没有保证这样一个实例将存在的约束(而且我不知道我们如何会写一个,没有类型 k
实际上可以传递给 Term
)。但它确实有效:
>>> term @_ @3
3
it :: Integer
>>> term @_ @[1, 2, 3]
[1,2,3]
it :: [Integer]
>>> term @_ @["hello", "world"]
["hello","world"]
it :: [String]
但最大的缺点是现在有一个额外的参数我们必须显式传递给 term
。 GHC 可以推断出它是什么(这就是我们可以使用 @_
的原因),但它必须排在第一位,因为它是后面的参数类型。
我想出的解决这个问题的最简单方法是将 term
重命名为 term'
,并提供一个新的 term
,将 kind 参数标记为已推断,以便它需要不(也不能)用类型应用程序指定。不过这需要 GHC 9 或更高版本。
term :: forall {k} (a :: k). Term (a :: k) => Result k
term = term' @k @a
不过后来我想到了更好的办法。在与列表有关的两个实例中,我们必须重复 type instance Result [k] = [Result k]
的相同定义,这已经让我有些恼火。那是因为 实例 取决于实际类型,但类型族 Result
仅取决于它的种类,所以当我们有两个实例覆盖同一种类的不同类型时,我们就结束了up 需要多余的定义。对我来说,这已经表明这并不是 class 的关联类型族,但作为独立类型族会更好。
type family Demote k where
Demote Symbol = String
Demote Nat = Integer
Demote [k] = [Demote k]
将类型族从 class 中移除后,如果我们不再需要显式类型参数 k
就好了(它仍将作为隐式参数存在)参数,但它不会弄乱我们的类型应用程序)。不幸的是,调用 Demote
我们仍然需要对该类型的显式引用。如果我们的 class 定义是 class Term a
而不是 class Term (a :: k)
,我们就没有那个。但是如果我们添加另一个间接层,我们可以创建一个类型同义词(甚至不必是一个类型族!),它得到类型 4:
type KindOf (a :: k) = k
class Term a where
term :: Demote (KindOf a)
现在终于可以了!
>>> term @19
19
it :: Integer
>>> term @[10, 5, 0]
[10,5,0]
it :: [Integer]
>>> term @["take", "that", "typechecker"]
["take","that","typechecker"]
it :: [String]
唯一(次要?)的问题是现在 term @'[]
不再独立工作,因为它需要真正知道空列表的种类(以解决 Demote
type family) 而不是给我们一个多态的空列表。
>>> term @'[]
<interactive>:26:1: error:
• Couldn't match type: Result k0
with: Result k
Expected: [Result k]
Actual: [Result k0]
NB: ‘Result’ is a non-injective type family
The type variable ‘k0’ is ambiguous
• In the ambiguity check for the inferred type for ‘it’
To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
When checking the inferred type
it :: forall {k}. [Result k]
>>> term @('[] :: [Symbol])
[]
it :: [String]
这是我最终得到的最终工作模块:
{-# LANGUAGE AllowAmbiguousTypes, DataKinds, PolyKinds, FlexibleInstances, ScopedTypeVariables, TypeApplications, TypeFamilies, TypeOperators #-}
module Term
where
import GHC.Types
import GHC.TypeLits
import Data.Proxy
type KindOf (a :: k) = k
type family Demote k where
Demote Symbol = String
Demote Nat = Integer
Demote [k] = [Demote k]
class Term a where
term :: Demote (KindOf a)
instance (KnownSymbol s) => Term (s :: Symbol) where
term = symbolVal (Proxy @s)
instance (KnownNat n) => Term (n :: Nat) where
term = natVal (Proxy @n)
instance Term ('[] :: [k]) where
term = []
instance (Term a, Term as) => Term ((a ': as) :: [k]) where
term = term @a : term @as
1 我认为 GHC 说“期望一种类型”意味着它期望 Type
/*
在这里因为这比初学者更容易混淆“类型不匹配,预期 *
,实际 [*]
”。
2 这是在实例中为 GHC 的类型推断添加额外“公理”的常用技巧。如果实例上的约束包括 foo ~ bar
,那么 GHC 将在对该实例进行类型检查时假定它通常为真,并在使用该实例时检查它是否真的(对于涉及的特定类型)。如果它是你“知道”的东西永远是真的但不能在 Haskell 中证明,那么该检查将永远通过;这使您可以利用无法在 Haskell.
3 请记住,必须能够在不考虑其约束的情况下确定哪些实例适用于给定情况!
4我有一种预感,我在这里重新发现了一个轮子,果然KindOf
already exists in the singletons
package的确切定义。 singletons
包含许多用于执行此类类型级别对应术语级别内容的高级机制;我不知道该向你指出什么,但实际上你可以用 singletons
中的东西替换你所有的 Term
class 并且它已经可以工作并且是更一般。然而 singletons
是一个相当高级的包,所以不是最容易学习的东西。
如果您计划将此类代码用于持续的实际目的,我强烈建议您投入精力学习如何使用 singletons
。可能比自己写好。
如果您写这篇文章是为了了解这些类型级别的编程概念是如何工作的,那么 singletons
将会有很多示例说明您可以将其推进到什么程度,但它的实现可能很难对一个相对新手理解。