折叠异构,编译时,列表
Fold over a heterogeneous, compile time, list
我有一个异构类型的列表(或者至少这是我的想法):
data Nul
data Bits b otherBits where
BitsLst :: b -> otherBits -> Bits b otherBits
NoMoreBits :: Bits b Nul
现在,给定输入类型 b
,我想遍历 Bits
类型为 b
的所有 slab 并对其进行汇总,忽略类型为 [=16] 的其他 slab =]:
class Monoid r => EncodeBit b r | b -> r where
encodeBit :: b -> r
class AbstractFoldable aMulti r where
manyFold :: r -> aMulti -> r
instance (EncodeBit b r, AbstractFoldable otherBits r) =>
AbstractFoldable (Bits b otherBits ) r where
manyFold r0 (BitsLst bi other) = manyFold (r0 `mappend` (encodeBit bi)) other
manyFold b0 NoMoreBits = b0
instance AbstractFoldable otherBits r =>
AbstractFoldable (Bits nb otherBits ) r where
manyFold r0 (BitsLst _ other) = manyFold r0 other
manyFold b0 NoMoreBits = b0
但是编译器需要它的 none。并且有充分的理由,因为两个实例声明具有相同的头。问题:用任意类型折叠 Bits
的正确方法是什么?
注意:上面的例子是用
编译的
{-# LANGUAGE MultiParamTypeClasses,
FunctionalDependencies,
GADTs,
DataKinds,
FlexibleInstances,
FlexibleContexts
#-}
正在回复您的评论:
Actually, I can do if I can filter the heterogeneous list by type. Is that possible?
如果在 b
中添加 Typeable
约束,则可以按类型过滤异构列表。
主要思想是我们将使用 Data.Typeable
的 cast :: (Typeable a, Typeable b) => a -> Maybe b
来确定列表中的每个项目是否属于某种类型。这将需要对列表中的每个项目进行 Typeable
约束。我们将能够检查列表中的 All
类型是否满足某些约束,而不是构建一个内置此约束的新列表类型。
我们的目标是使以下程序输出 [True,False]
,将异构列表过滤为其 Bool
个元素。我将努力将语言扩展和导入放在它们需要的第一个片段中
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
example :: HList (Bool ': String ': Bool ': String ': '[])
example = HCons True $ HCons "Jack" $ HCons False $ HCons "Jill" $ HNil
main = do
print (ofType example :: [Bool])
HList
这是 haskell 中使用 DataKinds
的异构列表的相当标准的定义
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
data HList (l :: [*]) where
HCons :: h -> HList t -> HList (h ': t)
HNil :: HList '[]
我们想写 ofType
带有签名,如“如果 All
异构列表中的事物是 Typeable
,获取特定 [=19= 的那些事物的列表]类型。
import Data.Typeable
ofType :: (All Typeable l, Typeable a) => HList l -> [a]
为此,我们需要在满足某些约束的类型列表中发展 All
事物的概念。我们将满足约束的字典存储在 GADT
中,它要么捕获头部约束字典和尾部 All
的约束,要么证明列表为空。如果我们可以为它捕获字典,则类型列表满足 All
项的约束。
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ConstraintKinds #-}
-- requires the constraints† package.
-- Constraint is actually in GHC.Prim
-- it's just easier to get to this way
import Data.Constraint (Constraint)
class All (c :: * -> Constraint) (l :: [*]) where
allDict :: p1 c -> p2 l -> DList c l
data DList (ctx :: * -> Constraint) (l :: [*]) where
DCons :: (ctx h, All ctx t) => DList ctx (h ': t)
DNil :: DList ctx '[]
DList
确实是字典列表。 DCons
捕获应用于头项 (ctx h
) 的约束的字典和列表其余部分 (All ctx t
) 的所有字典。我们不能直接从构造函数中获取 tail 的字典,但我们可以编写一个函数从 All ctx t
.
的字典中提取它们
{-# LANGUAGE ScopedTypeVariables #-}
import Data.Proxy
dtail :: forall ctx h t. DList ctx (h ': t) -> DList ctx t
dtail DCons = allDict (Proxy :: Proxy ctx) (Proxy :: Proxy t)
一个空的类型列表平凡地满足应用于其所有项目的任何约束
instance All c '[] where
allDict _ _ = DNil
如果列表的头部满足约束并且所有尾部也满足约束,则列表中的所有内容都满足约束。
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
instance (c h, All c t) => All c (h ': t) where
allDict _ _ = DCons
我们现在可以编写 ofType
,这需要 forall
s 用于 ScopedTypeVariables
的范围类型变量。
import Data.Maybe
ofType :: forall a l. (All Typeable l, Typeable a) => HList l -> [a]
ofType l = ofType' (allDict (Proxy :: Proxy Typeable) l) l
where
ofType' :: forall l. (All Typeable l) => DList Typeable l -> HList l -> [a]
ofType' d@DCons (HCons x t) = maybeToList (cast x) ++ ofType' (dtail d) t
ofType' DNil HNil = []
我们正在将 HList
及其字典与 maybeToList . cast
压缩在一起,并将结果串联起来。我们可以用 RankNTypes
.
来明确这一点
{-# LANGUAGE RankNTypes #-}
import Data.Monoid (Monoid, (<>), mempty)
zipDHWith :: forall c w l p. (All c l, Monoid w) => (forall a. (c a) => a -> w) -> p c -> HList l -> w
zipDHWith f p l = zipDHWith' (allDict p l) l
where
zipDHWith' :: forall l. (All c l) => DList c l -> HList l -> w
zipDHWith' d@DCons (HCons x t) = f x <> zipDHWith' (dtail d) t
zipDHWith' DNil HNil = mempty
ofType :: (All Typeable l, Typeable a) => HList l -> [a]
ofType = zipDHWith (maybeToList . cast) (Proxy :: Proxy Typeable)
我有一个异构类型的列表(或者至少这是我的想法):
data Nul
data Bits b otherBits where
BitsLst :: b -> otherBits -> Bits b otherBits
NoMoreBits :: Bits b Nul
现在,给定输入类型 b
,我想遍历 Bits
类型为 b
的所有 slab 并对其进行汇总,忽略类型为 [=16] 的其他 slab =]:
class Monoid r => EncodeBit b r | b -> r where
encodeBit :: b -> r
class AbstractFoldable aMulti r where
manyFold :: r -> aMulti -> r
instance (EncodeBit b r, AbstractFoldable otherBits r) =>
AbstractFoldable (Bits b otherBits ) r where
manyFold r0 (BitsLst bi other) = manyFold (r0 `mappend` (encodeBit bi)) other
manyFold b0 NoMoreBits = b0
instance AbstractFoldable otherBits r =>
AbstractFoldable (Bits nb otherBits ) r where
manyFold r0 (BitsLst _ other) = manyFold r0 other
manyFold b0 NoMoreBits = b0
但是编译器需要它的 none。并且有充分的理由,因为两个实例声明具有相同的头。问题:用任意类型折叠 Bits
的正确方法是什么?
注意:上面的例子是用
编译的{-# LANGUAGE MultiParamTypeClasses,
FunctionalDependencies,
GADTs,
DataKinds,
FlexibleInstances,
FlexibleContexts
#-}
正在回复您的评论:
Actually, I can do if I can filter the heterogeneous list by type. Is that possible?
如果在 b
中添加 Typeable
约束,则可以按类型过滤异构列表。
主要思想是我们将使用 Data.Typeable
的 cast :: (Typeable a, Typeable b) => a -> Maybe b
来确定列表中的每个项目是否属于某种类型。这将需要对列表中的每个项目进行 Typeable
约束。我们将能够检查列表中的 All
类型是否满足某些约束,而不是构建一个内置此约束的新列表类型。
我们的目标是使以下程序输出 [True,False]
,将异构列表过滤为其 Bool
个元素。我将努力将语言扩展和导入放在它们需要的第一个片段中
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
example :: HList (Bool ': String ': Bool ': String ': '[])
example = HCons True $ HCons "Jack" $ HCons False $ HCons "Jill" $ HNil
main = do
print (ofType example :: [Bool])
HList
这是 haskell 中使用 DataKinds
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
data HList (l :: [*]) where
HCons :: h -> HList t -> HList (h ': t)
HNil :: HList '[]
我们想写 ofType
带有签名,如“如果 All
异构列表中的事物是 Typeable
,获取特定 [=19= 的那些事物的列表]类型。
import Data.Typeable
ofType :: (All Typeable l, Typeable a) => HList l -> [a]
为此,我们需要在满足某些约束的类型列表中发展 All
事物的概念。我们将满足约束的字典存储在 GADT
中,它要么捕获头部约束字典和尾部 All
的约束,要么证明列表为空。如果我们可以为它捕获字典,则类型列表满足 All
项的约束。
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ConstraintKinds #-}
-- requires the constraints† package.
-- Constraint is actually in GHC.Prim
-- it's just easier to get to this way
import Data.Constraint (Constraint)
class All (c :: * -> Constraint) (l :: [*]) where
allDict :: p1 c -> p2 l -> DList c l
data DList (ctx :: * -> Constraint) (l :: [*]) where
DCons :: (ctx h, All ctx t) => DList ctx (h ': t)
DNil :: DList ctx '[]
DList
确实是字典列表。 DCons
捕获应用于头项 (ctx h
) 的约束的字典和列表其余部分 (All ctx t
) 的所有字典。我们不能直接从构造函数中获取 tail 的字典,但我们可以编写一个函数从 All ctx t
.
{-# LANGUAGE ScopedTypeVariables #-}
import Data.Proxy
dtail :: forall ctx h t. DList ctx (h ': t) -> DList ctx t
dtail DCons = allDict (Proxy :: Proxy ctx) (Proxy :: Proxy t)
一个空的类型列表平凡地满足应用于其所有项目的任何约束
instance All c '[] where
allDict _ _ = DNil
如果列表的头部满足约束并且所有尾部也满足约束,则列表中的所有内容都满足约束。
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
instance (c h, All c t) => All c (h ': t) where
allDict _ _ = DCons
我们现在可以编写 ofType
,这需要 forall
s 用于 ScopedTypeVariables
的范围类型变量。
import Data.Maybe
ofType :: forall a l. (All Typeable l, Typeable a) => HList l -> [a]
ofType l = ofType' (allDict (Proxy :: Proxy Typeable) l) l
where
ofType' :: forall l. (All Typeable l) => DList Typeable l -> HList l -> [a]
ofType' d@DCons (HCons x t) = maybeToList (cast x) ++ ofType' (dtail d) t
ofType' DNil HNil = []
我们正在将 HList
及其字典与 maybeToList . cast
压缩在一起,并将结果串联起来。我们可以用 RankNTypes
.
{-# LANGUAGE RankNTypes #-}
import Data.Monoid (Monoid, (<>), mempty)
zipDHWith :: forall c w l p. (All c l, Monoid w) => (forall a. (c a) => a -> w) -> p c -> HList l -> w
zipDHWith f p l = zipDHWith' (allDict p l) l
where
zipDHWith' :: forall l. (All c l) => DList c l -> HList l -> w
zipDHWith' d@DCons (HCons x t) = f x <> zipDHWith' (dtail d) t
zipDHWith' DNil HNil = mempty
ofType :: (All Typeable l, Typeable a) => HList l -> [a]
ofType = zipDHWith (maybeToList . cast) (Proxy :: Proxy Typeable)