从结构上反映异构推广类型回到价值观

时间:2015-01-19 17:15:21

标签: haskell reflection typeclass dependent-type data-kinds

我最近一直在玩-XDataKinds,并希望采用类型系列的升级结构构建并将其拉回到值级别。我相信这是可能的,因为组成组件非常简单,终端表达式也很简单。

背景

我想降级/反映Strings的简单玫瑰树,它们变成了Tree Symbol类型(当使用GHC.TypeLits.Symbol作为类型级字符串时)。这是我的样板代码:

{-# LANGUAGE DataKinds #-}

import GHC.TypeLits
import Data.Proxy

data Tree a = Node a [Tree a]

type TestInput = '[ 'Node "foo" '[ 'Node "bar" '[]
                                 , 'Node "baz" '[]
                                 ]
                  , 'Node "bar" '[]
                  ]

这是一个简单的类型级玫瑰森林,看起来像这个非常详细的图表:

 *-- "foo" -- "bar"
 |         \_ "baz"
  \_ "bar"

尝试解决方案

理想情况下,我想遍历此结构并将1对1映射返回到*类型的,但是如何异构地执行此操作并不是很明显由于超载,仍然在进行(必要的)实例。

<{1}}上的vanila建议我使用类型类来绑定这两个世界,但它似乎比我想象的要复杂一些。我的第一次尝试尝试通过实例头部约束对类型级别模式匹配的内容进行编码,但我的关联类型(用于编码映射的#haskell - kinded类型结果)重叠 - 显然instance heads are somewhat ignored by GHC

理想情况下,我还希望列表和树的反射是通用的,这似乎会导致问题 - 就像使用类型类来组织类型/类型层一样。

以下是我想要的非功能性示例:

*

...

这段代码通常有一些错误。这就是我所看到的:

  • 我需要某种形式的预测才能知道通用类型级列表反射的高级反射结果 - class Reflect (a :: k) where type Result :: * reflect :: Proxy a -> Result class ReflectEmpty (empty :: [k]) where reflectEmpty :: forall q. Proxy empty -> [q] reflectEmpty _ = [] instance ReflectEmpty '[] where instance ReflectEmpty a => Reflect a where type Result = forall q. [q] reflect = reflectEmpty -- | The superclass constraint is where we get compositional class Reflect (x :: k) => ReflectCons (cons :: [x]) where reflectCons :: PostReflection x ~ c => Proxy cons -> [c] instance ( Reflect x , ReflectCons xs ) => ReflectCons (x ': xs) where reflectCons _ = reflect (Proxy :: Proxy x) : reflectCons (Proxy :: Proxy xs) instance ( Reflect x , ReflectEmpty e ) => ReflectCons (x ': e) where reflectCons _ = reflect (Proxy :: Proxy x) : reflectEmpty (Proxy :: Proxy e) 类型函数
  • 我需要动态创建和销毁PostReflection。我不确定目前是否会编译,但我不相信这些类型会像我期望的那样统一。

但是,这种类型角色heirarchy感觉是捕获异构语法的唯一方法,所以这可能仍然是一个开始。对此有任何帮助都是巨大的!

1 个答案:

答案 0 :(得分:9)

懒惰的解决方案

安装singletons包:

{-# LANGUAGE
  TemplateHaskell, DataKinds, PolyKinds, TypeFamilies,
  ScopedTypeVariables, FlexibleInstances, UndecidableInstances, GADTs #-}

import GHC.TypeLits
import Data.Singletons.TH
import Data.Singletons.Prelude
import Data.Proxy

$(singletons [d|
  data Tree a = Node a [Tree a] deriving (Eq, Show)
  |])

reflect ::
  forall (a :: k).
  (SingI a, SingKind ('KProxy :: KProxy k)) =>
  Proxy a -> Demote a
reflect _ = fromSing (sing :: Sing a)

-- reflect (Proxy :: Proxy (Node "foo" '[])) == Node "foo" []

我们已经完成了。

不幸的是,图书馆的文档很少,也非常复杂。我建议查看project homepage以获取更多文档。我试着解释下面的基础知识。

Sing是定义单例表示的数据系列。单身人士在结构上与未提升的类型相同,但他们的价值由相应的提升值索引。例如,data Nat = Z | S Nat的单例将是

data instance Sing (n :: Nat) where
  SZ :: Sing Z
  SS :: Sing n -> Sing (S n)

singletons是生成单例的模板函数(它还可以提升派生实例,也可以提升函数)。

SingKind本质上是种类,为我们提供了Demote类型和fromSingDemote为我们提供了相应的未提升类型。例如,Demote FalseBool,而Demote "foo"SymbolfromSing将单例值转换为相应的未提升值。因此fromSing SZ等于Z

SingI是一个将提升值反映为单值的类。 sing是其方法,sing :: Sing x为我们提供了x的单例值。这几乎是我们想要的;要完成reflect的定义,我们只需要在fromSing上使用sing来获取未提升的值。

KProxyData.Proxy的导出。它允许我们从环境中捕获类型变量并在定义中使用它们。请注意,可以使用任何类型的可推广数据类型(* - > *)代替KProxy。有关数据类型提升的详细信息see this.

请注意,在种类上有一种较弱的调度形式,不需要KProxy

type family Demote (a :: k)
type instance Demote (s :: Symbol) = String
type instance Demote (b :: Bool)   = Bool

到目前为止一切顺利,但我们如何编写提升列表的实例?

type instance Demote (xs :: [a]) = [Demote ???] 
当然,

Demote a是不允许的,因为a是一种,而不是一种类型。因此,我们需要KProxy才能在右侧使用a

自己动手解决方案

这与singletons解决方案类似,但我们故意跳过单例表示并直接进行反思。这应该有点高效,我们甚至可能在这个过程中学到一点(我当然做到了!)。

import GHC.TypeLits
import Data.Proxy

data Tree a = Node a [Tree a] deriving (Eq, Show)

我们将类型调度实现为开放类型系列,并为方便起见提供类型同义词:

type family Demote' (kparam :: KProxy k) :: *  
type Demote (a :: k) = Demote' ('KProxy :: KProxy k)  

一般情况是,只要我们想提一种'KProxy :: KProxy k,我们就会使用k

type instance Demote' ('KProxy :: KProxy Symbol) = String
type instance Demote' ('KProxy :: KProxy (Tree a)) = Tree (Demote' ('KProxy :: KProxy a))
type instance Demote' ('KProxy :: KProxy [a]) = [Demote' ('KProxy :: KProxy a)]

现在进行反思非常简单:

class Reflect (a :: k) where
  reflect :: Proxy (a :: k) -> Demote a

instance KnownSymbol s => Reflect (s :: Symbol) where
  reflect = symbolVal

instance Reflect ('[] :: [k]) where
  reflect _ = []

instance (Reflect x, Reflect xs) => Reflect (x ': xs) where
  reflect _ = reflect (Proxy :: Proxy x) : reflect (Proxy :: Proxy xs)

instance (Reflect n, Reflect ns) => Reflect (Node n ns) where
  reflect _ = Node (reflect (Proxy :: Proxy n)) (reflect (Proxy :: Proxy ns))