我们如何在 Haskell 中构建明确的类别?
How can we build explicit categories in Haskell?
对应类别的数学思想,Haskell有一个Category typeclass. I'd like to build some small finite categories and work with them, along the lines of the book Computational Category Theory但有更好的类型检查。
例如,在数学中有一个很小但很重要的类别,称为“终端类别”,它只有一个对象,一个箭头是该对象的标识。这是我的最佳尝试:
data TcObjectType = TcObject
data TcArrowType a0 a1 where
TcArrow :: TcObjectType -> TcObjectType -> TcArrowType TcObjectType TcObjectType
instance Category TcArrowType where
id TcObject = TcArrow TcObject TcObject
(TcArrow TcObject TcObject) . (TcArrow TcObject TcObject) = TcArrow TcObject TcObject
当前错误为Couldn't match expected type ‘TcArrowType a a’ with actual type ‘TcObjectType -> TcArrowType TcObjectType TcObjectType’
。 TcArrow TcObject TcObject
应该是表示唯一箭头的值,但出于某种原因,编译器似乎将其视为函数。
有什么合理的方法吗?
编辑:我想描述任何有限的范畴,而不仅仅是终端范畴。这意味着我想明确地说箭头 X 从对象 A 指向对象 B。下一个示例可能是具有两个对象和它们之间的两个平行箭头的类别。
tl;dr 请参阅 https://gist.github.com/leftaroundabout/d5347d06dfcfc1d8ce796bb2966b3343 以获得完整的编译安全版本。
问题是 Control.Category.id
需要量化给定类型的 所有 类型:
class Category c where
id :: <b>∀ a</b> . c a a
...
IOW,如果对象属于 Type
(如您的 TcObject
),那么 Category
实例必须具有 all Haskell 类型作为对象,这当然会立即取消终端类别作为实例的资格。
周围有几个不同的替代类别 class 允许在对象的选择上指定 约束;使用 constrained-categories
实例将如下所示:
{-# LANGUAGE TypeFamilies, ConstraintKinds #-}
import qualified Control.Category.Constrained.Class as CC
instance CC.Category TcArrowType where
type Object TcArrowType a = a ~ TcObjectType
id = TcArrow TcObject TcObject
TcArrow TcObject TcObject . TcArrow TcObject TcObject = TcArrow TcObject TcObject
但是有一个可以说更优雅的选择:因为你的对象根本没有真正用作类型(你将它用作类型来标记带有运行时值的箭头,但该信息是多余的),所以没有首先要点 Type
。实际上,标准 Category
class 是 poly-kinded (从文档中看并不明显),因此您可以使用 data TcObjectType = TcObject
一个提升数据构造函数来表达同样的事情:
{-# LANGUAGE DataKinds, KindSignatures #-}
data TcObjectKind = TcObject
data TcArrowType (a₀ :: TcObjectKind) (a₁ :: TcObjectKind) where
TcArrow :: TcArrowType 'TcObject 'TcObject
instance Category TcArrowType where
id = TcArrow
TcArrow . TcArrow = TcArrow
...或者至少它在概念上看起来是这样的。实际上这 完全 行不通,因为尽管 TcObject
是 唯一的类型 † TcObjectKind
,编译器不会自动为每个 o :: TcObjectKind
推断出 o ~ TcObject
。但是你可以手动告诉它:
import Unsafe.Coerce
instance Category TcArrowType where
id = unsafeCoerce TcArrow -- Safe because `a` can only ever be `TcObject`.
@dfeuer 评论说这实际上 相当 安全,因为 GHC 处理类型族与类型构造函数的方式有一个怪癖,请参阅 https://gist.github.com/treeowl/6104ef553dadf0d1faf01da0850ddb01。 IMO 这不是 unsafeCoerce
的错,而是 GHC 的错,但这仍然不是一个很好的解决方案。
†迂腐地说,它不是一个类型,而是一个 type-level 值。
对于比终端类别具有更多对象和箭头的更复杂的工作和类别,您需要使其更加规范,而不是 id
中的手动 unsafeCoerce
。这本质上是 singletons 应该解决的问题。
{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
{-# LANGUAGE DataKinds, KindSignatures #-}
{-# LANGUAGE TypeFamilies, GADTs #-}
import Data.Singletons.TH
$(singletons [d|
data TcObjectKind = TcObject
|])
data TcArrowType (a₀ :: TcObjectKind) (a₁ :: TcObjectKind) where
TcArrow :: TcArrowType 'TcObject 'TcObject
tcId :: ∀ a . SingI a => TcArrowType a a
tcId = case sing :: Sing a of
STcObject -> TcArrow
这现在推广到具有多个对象的类别,例如
$(singletons [d|
data Trap = Free | Trapped
|])
data TrapArrowType (a₀ :: Trap) (a₁ :: Trap) where
StillFree :: TrapArrowType 'Free 'Free
Falling :: TrapArrowType 'Free 'Trapped
Stuck :: TrapArrowType 'Trapped 'Trapped
trapId :: ∀ a . SingI a => TrapArrowType a a
trapId = case sing :: Sing a of
SFree -> StillFree
STrapped -> Stuck
不幸的是,对于单例,我们又回到了我们有 SingI a
基本 Category
class 无法提供的约束的问题。但同样,constrained-categories
版本可以。
对应类别的数学思想,Haskell有一个Category typeclass. I'd like to build some small finite categories and work with them, along the lines of the book Computational Category Theory但有更好的类型检查。
例如,在数学中有一个很小但很重要的类别,称为“终端类别”,它只有一个对象,一个箭头是该对象的标识。这是我的最佳尝试:
data TcObjectType = TcObject
data TcArrowType a0 a1 where
TcArrow :: TcObjectType -> TcObjectType -> TcArrowType TcObjectType TcObjectType
instance Category TcArrowType where
id TcObject = TcArrow TcObject TcObject
(TcArrow TcObject TcObject) . (TcArrow TcObject TcObject) = TcArrow TcObject TcObject
当前错误为Couldn't match expected type ‘TcArrowType a a’ with actual type ‘TcObjectType -> TcArrowType TcObjectType TcObjectType’
。 TcArrow TcObject TcObject
应该是表示唯一箭头的值,但出于某种原因,编译器似乎将其视为函数。
有什么合理的方法吗?
编辑:我想描述任何有限的范畴,而不仅仅是终端范畴。这意味着我想明确地说箭头 X 从对象 A 指向对象 B。下一个示例可能是具有两个对象和它们之间的两个平行箭头的类别。
tl;dr 请参阅 https://gist.github.com/leftaroundabout/d5347d06dfcfc1d8ce796bb2966b3343 以获得完整的编译安全版本。
问题是 Control.Category.id
需要量化给定类型的 所有 类型:
class Category c where
id :: <b>∀ a</b> . c a a
...
IOW,如果对象属于 Type
(如您的 TcObject
),那么 Category
实例必须具有 all Haskell 类型作为对象,这当然会立即取消终端类别作为实例的资格。
周围有几个不同的替代类别 class 允许在对象的选择上指定 约束;使用 constrained-categories
实例将如下所示:
{-# LANGUAGE TypeFamilies, ConstraintKinds #-}
import qualified Control.Category.Constrained.Class as CC
instance CC.Category TcArrowType where
type Object TcArrowType a = a ~ TcObjectType
id = TcArrow TcObject TcObject
TcArrow TcObject TcObject . TcArrow TcObject TcObject = TcArrow TcObject TcObject
但是有一个可以说更优雅的选择:因为你的对象根本没有真正用作类型(你将它用作类型来标记带有运行时值的箭头,但该信息是多余的),所以没有首先要点 Type
。实际上,标准 Category
class 是 poly-kinded (从文档中看并不明显),因此您可以使用 data TcObjectType = TcObject
一个提升数据构造函数来表达同样的事情:
{-# LANGUAGE DataKinds, KindSignatures #-}
data TcObjectKind = TcObject
data TcArrowType (a₀ :: TcObjectKind) (a₁ :: TcObjectKind) where
TcArrow :: TcArrowType 'TcObject 'TcObject
instance Category TcArrowType where
id = TcArrow
TcArrow . TcArrow = TcArrow
...或者至少它在概念上看起来是这样的。实际上这 完全 行不通,因为尽管 TcObject
是 唯一的类型 † TcObjectKind
,编译器不会自动为每个 o :: TcObjectKind
推断出 o ~ TcObject
。但是你可以手动告诉它:
import Unsafe.Coerce
instance Category TcArrowType where
id = unsafeCoerce TcArrow -- Safe because `a` can only ever be `TcObject`.
@dfeuer 评论说这实际上 相当 安全,因为 GHC 处理类型族与类型构造函数的方式有一个怪癖,请参阅 https://gist.github.com/treeowl/6104ef553dadf0d1faf01da0850ddb01。 IMO 这不是 unsafeCoerce
的错,而是 GHC 的错,但这仍然不是一个很好的解决方案。
†迂腐地说,它不是一个类型,而是一个 type-level 值。
对于比终端类别具有更多对象和箭头的更复杂的工作和类别,您需要使其更加规范,而不是 id
中的手动 unsafeCoerce
。这本质上是 singletons 应该解决的问题。
{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
{-# LANGUAGE DataKinds, KindSignatures #-}
{-# LANGUAGE TypeFamilies, GADTs #-}
import Data.Singletons.TH
$(singletons [d|
data TcObjectKind = TcObject
|])
data TcArrowType (a₀ :: TcObjectKind) (a₁ :: TcObjectKind) where
TcArrow :: TcArrowType 'TcObject 'TcObject
tcId :: ∀ a . SingI a => TcArrowType a a
tcId = case sing :: Sing a of
STcObject -> TcArrow
这现在推广到具有多个对象的类别,例如
$(singletons [d|
data Trap = Free | Trapped
|])
data TrapArrowType (a₀ :: Trap) (a₁ :: Trap) where
StillFree :: TrapArrowType 'Free 'Free
Falling :: TrapArrowType 'Free 'Trapped
Stuck :: TrapArrowType 'Trapped 'Trapped
trapId :: ∀ a . SingI a => TrapArrowType a a
trapId = case sing :: Sing a of
SFree -> StillFree
STrapped -> Stuck
不幸的是,对于单例,我们又回到了我们有 SingI a
基本 Category
class 无法提供的约束的问题。但同样,constrained-categories
版本可以。