82

给定任何容器类型,我们可以形成(以元素为中心的)拉链,并且知道这个结构是一个 Comonad。最近在另一个 Stack Overflow 问题中对以下类型进行了非常详细的探讨:

data Bin a = Branch (Bin a) a (Bin a) | Leaf a deriving Functor

搭配以下拉链

data Dir = L | R
data Step a = Step a Dir (Bin a)   deriving Functor
data Zip  a = Zip [Step a] (Bin a) deriving Functor
instance Comonad Zip where ...

虽然它的实例的构造有点毛茸茸,但情况确实Zip如此。Comonad也就是说,Zip可以完全机械地派生自Tree并且(我相信)以这种方式派生的任何类型都自动是 a Comonad,所以我认为我们应该可以通用和自动地构造这些类型及其comonads。

实现拉链构造通用性的一种方法是使用以下类和类型族

data Zipper t a = Zipper { diff :: D t a, here :: a }

deriving instance Diff t => Functor (Zipper t)

class (Functor t, Functor (D t)) => Diff t where
  data D t :: * -> *
  inTo  :: t a -> t (Zipper t a)
  outOf :: Zipper t a -> t a

它(或多或少)出现在 Haskell Cafe 线程和 Conal Elliott 的博客中。此类可以针对各种核心代数类型进行实例化,从而为讨论 ADT 的导数提供了一个通用框架。

所以,最终,我的问题是我们是否可以写

instance Diff t => Comonad (Zipper t) where ...

可用于包含上述特定的 Comonad 实例:

instance Diff Bin where
  data D Bin a = DBin { context :: [Step a], descend :: Maybe (Bin a, Bin a) }
  ...

不幸的是,我没有运气写出这样的例子。inTo/签名是否outOf足够?是否需要其他东西来限制类型?这种情况甚至可能吗?

4

3 回答 3

115

就像 Chitty-Chitty-Bang-Bang 中的儿童捕手用糖果和玩具引诱孩子们被囚禁一样,本科物理的招聘人员喜欢用肥皂泡和回旋镖来玩弄,但是当门关上时,“是的,孩子们,是时候学习了关于偏微分!”。我也是。别说我没警告过你。

这是另一个警告:以下代码需要{-# LANGUAGE KitchenSink #-},或者更确切地说

{-# LANGUAGE TypeFamilies, FlexibleContexts, TupleSections, GADTs, DataKinds,
    TypeOperators, FlexibleInstances, RankNTypes, ScopedTypeVariables,
    StandaloneDeriving, UndecidableInstances #-}

没有特别的顺序。

可微函子给出共通拉链

到底什么是可微函子?

class (Functor f, Functor (DF f)) => Diff1 f where
  type DF f :: * -> *
  upF      ::  ZF f x  ->  f x
  downF    ::  f x     ->  f (ZF f x)
  aroundF  ::  ZF f x  ->  ZF f (ZF f x)

data ZF f x = (:<-:) {cxF :: DF f x, elF :: x}

它是一个具有导数的函子,它也是一个函子。导数表示元素的单孔上下文。拉链类型ZF f x表示单孔上下文和孔中元素的对。

用于Diff1描述我们可以在拉链上进行的导航类型的操作(没有任何“向左”和“向右”的概念,请参阅我的小丑和小丑论文)。我们可以“向上”,通过将元件插入孔中来重新组装结构。我们可以“向下”,找到访问给定结构中元素的各种方法:我们用它的上下文装饰每个元素。我们可以“四处走动”,采用现有的拉链并用其上下文装饰每个元素,因此我们找到了重新聚焦的所有方法(以及如何保持我们当前的焦点)。

现在, 的类型aroundF可能会让你们中的一些人想起

class Functor c => Comonad c where
  extract    :: c x -> x
  duplicate  :: c x -> c (c x)

你被提醒是对的!我们有一个跳跃和一个跳跃,

instance Diff1 f => Functor (ZF f) where
  fmap f (df :<-: x) = fmap f df :<-: f x

instance Diff1 f => Comonad (ZF f) where
  extract    = elF
  duplicate  = aroundF

我们坚持认为

extract . duplicate == id
fmap extract . duplicate == id
duplicate . duplicate == fmap duplicate . duplicate

我们也需要那个

fmap extract (downF xs) == xs              -- downF decorates the element in position
fmap upF (downF xs) = fmap (const xs) xs   -- downF gives the correct context

多项式函子是可微的

常数函子是可微的。

data KF a x = KF a
instance Functor (KF a) where
  fmap f (KF a) = KF a

instance Diff1 (KF a) where
  type DF (KF a) = KF Void
  upF (KF w :<-: _) = absurd w
  downF (KF a) = KF a
  aroundF (KF w :<-: _) = absurd w

没有地方可以放置元素,因此不可能形成上下文。无处可去upF,无处可去downF,我们很容易找到所有的路都没有downF

等函子是可微的。

data IF x = IF x
instance Functor IF where
  fmap f (IF x) = IF (f x)

instance Diff1 IF where
  type DF IF = KF ()
  upF (KF () :<-: x) = IF x
  downF (IF x) = IF (KF () :<-: x)
  aroundF z@(KF () :<-: x) = KF () :<-: z

在微不足道的上下文中有一个元素,downF找到它,upF重新包装它,并且aroundF只能留在原地。

Sum保留了可微性。

data (f :+: g) x = LF (f x) | RF (g x)
instance (Functor f, Functor g) => Functor (f :+: g) where
  fmap h (LF f) = LF (fmap h f)
  fmap h (RF g) = RF (fmap h g)

instance (Diff1 f, Diff1 g) => Diff1 (f :+: g) where
  type DF (f :+: g) = DF f :+: DF g
  upF (LF f' :<-: x) = LF (upF (f' :<-: x))
  upF (RF g' :<-: x) = RF (upF (g' :<-: x))

其他零碎的东西有点多。要 go downF,我们必须进入downF标记组件内部,然后修复生成的拉链以在上下文中显示标记。

  downF (LF f) = LF (fmap (\ (f' :<-: x) -> LF f' :<-: x) (downF f))
  downF (RF g) = RF (fmap (\ (g' :<-: x) -> RF g' :<-: x) (downF g))

aroundF,我们剥离标签,弄清楚如何绕过未标记的东西,然后在所有生成的拉链中恢复标签。焦点元素 ,x被其整个拉链 替换z

  aroundF z@(LF f' :<-: (x :: x)) =
    LF (fmap (\ (f' :<-: x) -> LF f' :<-: x) . cxF $ aroundF (f' :<-: x :: ZF f x))
    :<-: z
  aroundF z@(RF g' :<-: (x :: x)) =
    RF (fmap (\ (g' :<-: x) -> RF g' :<-: x) . cxF $ aroundF (g' :<-: x :: ZF g x))
    :<-: z

请注意,我必须使用ScopedTypeVariables来消除对aroundF. 作为一个类型函数,DF不是单射的,所以这个事实f' :: D f x是不够的f' :<-: x :: Z f x

产品保留了可区分性。

data (f :*: g) x = f x :*: g x
instance (Functor f, Functor g) => Functor (f :*: g) where
  fmap h (f :*: g) = fmap h f :*: fmap h g

要专注于一对中的一个元素,您要么专注于左侧,要么只关注右侧,反之亦然。莱布尼茨著名的乘积法则对应一个简单的空间直觉!

instance (Diff1 f, Diff1 g) => Diff1 (f :*: g) where
  type DF (f :*: g) = (DF f :*: g) :+: (f :*: DF g)
  upF (LF (f' :*: g) :<-: x) = upF (f' :<-: x) :*: g
  upF (RF (f :*: g') :<-: x) = f :*: upF (g' :<-: x)

现在,downF它的工作方式与求和的方式类似,除了我们必须修复拉链上下文,不仅要使用标签(以显示我们走哪条路),还要使用未触及的其他组件。

  downF (f :*: g)
    =    fmap (\ (f' :<-: x) -> LF (f' :*: g) :<-: x) (downF f)
    :*:  fmap (\ (g' :<-: x) -> RF (f :*: g') :<-: x) (downF g)

但是aroundF是一大堆笑声。无论我们目前访问哪一方,我们都有两种选择:

  1. 移动到那aroundF一边。
  2. 从那upF一侧downF移到另一侧。

每种情况都要求我们利用子结构的操作,然后修复上下文。

  aroundF z@(LF (f' :*: g) :<-: (x :: x)) =
    LF (fmap (\ (f' :<-: x) -> LF (f' :*: g) :<-: x)
          (cxF $ aroundF (f' :<-: x :: ZF f x))
        :*: fmap (\ (g' :<-: x) -> RF (f :*: g') :<-: x) (downF g))
    :<-: z
    where f = upF (f' :<-: x)
  aroundF z@(RF (f :*: g') :<-: (x :: x)) =
    RF (fmap (\ (f' :<-: x) -> LF (f' :*: g) :<-: x) (downF f) :*:
        fmap (\ (g' :<-: x) -> RF (f :*: g') :<-: x)
          (cxF $ aroundF (g' :<-: x :: ZF g x)))
    :<-: z
    where g = upF (g' :<-: x)

呸!多项式都是可微的,因此给了我们comonads。

唔。这一切都有些抽象。所以我deriving Show到处都加了,然后扔了

deriving instance (Show (DF f x), Show x) => Show (ZF f x)

允许以下交互(手工整理)

> downF (IF 1 :*: IF 2)
IF (LF (KF () :*: IF 2) :<-: 1) :*: IF (RF (IF 1 :*: KF ()) :<-: 2)

> fmap aroundF it
IF  (LF (KF () :*: IF (RF (IF 1 :*: KF ()) :<-: 2)) :<-: (LF (KF () :*: IF 2) :<-: 1))
:*:
IF  (RF (IF (LF (KF () :*: IF 2) :<-: 1) :*: KF ()) :<-: (RF (IF 1 :*: KF ()) :<-: 2))

练习使用链式法则证明可微函子的组合是可微的。

甜的!我们现在可以回家了吗?当然不是。我们还没有区分任何递归结构。

从双函子制作递归函子

A Bifunctor,正如现有的关于数据类型泛型编程的文献(参见 Patrik Jansson 和 Johan Jeuring 的工作,或 Jeremy Gibbons 的优秀讲义)详细解释的那样,是一个具有两个参数的类型构造函数,对应于两种子结构。我们应该能够“映射”两者。

class Bifunctor b where
  bimap :: (x -> x') -> (y -> y') -> b x y -> b x' y'

我们可以使用Bifunctors 来给出递归容器的节点结构。每个节点都有子节点元素。这些可以只是两种子结构。

data Mu b y = In (b (Mu b y) y)

看?我们在 的第一个参数中“绑定递归结” b,并将参数保留y在第二个参数中。因此,我们一劳永逸地获得

instance Bifunctor b => Functor (Mu b) where
  fmap f (In b) = In (bimap (fmap f) f b)

要使用它,我们需要一个Bifunctor实例套件。

双函子套件

常量是双功能的。

newtype K a x y = K a

instance Bifunctor (K a) where
  bimap f g (K a) = K a

你可以说我先写了这段代码,因为标识符更短,但这很好,因为代码更长。

变量是双函数的。

我们需要一个参数对应的双函子,所以我做了一个数据类型来区分它们,然后定义了一个合适的GADT。

data Var = X | Y

data V :: Var -> * -> * -> * where
  XX :: x -> V X x y
  YY :: y -> V Y x y

这使得V X x y副本xV Y x y副本y。因此

instance Bifunctor (V v) where
  bimap f g (XX x) = XX (f x)
  bimap f g (YY y) = YY (g y)

双函子的和和是双函子

data (:++:) f g x y = L (f x y) | R (g x y) deriving Show

instance (Bifunctor b, Bifunctor c) => Bifunctor (b :++: c) where
  bimap f g (L b) = L (bimap f g b)
  bimap f g (R b) = R (bimap f g b)

data (:**:) f g x y = f x y :**: g x y deriving Show

instance (Bifunctor b, Bifunctor c) => Bifunctor (b :**: c) where
  bimap f g (b :**: c) = bimap f g b :**: bimap f g c

到目前为止,样板文件,但现在我们可以定义类似的东西

List = Mu (K () :++: (V Y :**: V X))

Bin = Mu (V Y :**: (K () :++: (V X :**: V X)))

如果您想将这些类型用于实际数据,而不是在 Georges Seurat 的点画传统中视而不见,请使用模式同义词

但是拉链呢?我们如何证明它Mu b是可微的?我们需要证明这b两个变量中都是可微的。铛!是时候学习偏微分了。

双函子的偏导数

因为我们有两个变量,所以我们需要能够有时集体讨论它们,而在其他时候单独讨论它们。我们需要单例家庭:

data Vary :: Var -> * where
  VX :: Vary X
  VY :: Vary Y

现在我们可以说明 Bifunctor 在每个变量上都有偏导数意味着什么,并给出相应的 zipper 概念。

class (Bifunctor b, Bifunctor (D b X), Bifunctor (D b Y)) => Diff2 b where
  type D b (v :: Var) :: * -> * -> *
  up      :: Vary v -> Z b v x y -> b x y
  down    :: b x y -> b (Z b X x y) (Z b Y x y)
  around  :: Vary v -> Z b v x y -> Z b v (Z b X x y) (Z b Y x y)

data Z b v x y = (:<-) {cxZ :: D b v x y, elZ :: V v x y}

D操作需要知道要定位哪个变量。相应的拉链Z b v告诉我们哪个变量v必须是焦点。当我们“用上下文装饰”时,我们必须用-contexts 装饰x-elements Xy用-contexts 装饰Y-elements。但除此之外,这是同一个故事。

我们还有两个任务:首先,证明我们的双函子套件是可微的;其次,显示Diff2 b允许我们建立Diff1 (Mu b).

区分 Bifunctor 套件

恐怕这一点很繁琐,而不是有启发性。随意跳过。

常数和以前一样。

instance Diff2 (K a) where
  type D (K a) v = K Void
  up _ (K q :<- _) = absurd q
  down (K a) = K a
  around _ (K q :<- _) = absurd q

在这种情况下,寿命太短,无法发展类型级 Kronecker-delta 的理论,所以我只是将变量分开处理。

instance Diff2 (V X) where
  type D (V X) X = K ()
  type D (V X) Y = K Void
  up VX (K () :<- XX x)  = XX x
  up VY (K q :<- _)      = absurd q
  down (XX x) = XX (K () :<- XX x)
  around VX z@(K () :<- XX x)  = K () :<- XX z
  around VY (K q :<- _)        = absurd q

instance Diff2 (V Y) where
  type D (V Y) X = K Void
  type D (V Y) Y = K ()
  up VX (K q :<- _)      = absurd q
  up VY (K () :<- YY y)  = YY y
  down (YY y) = YY (K () :<- YY y)
  around VX (K q :<- _)        = absurd q
  around VY z@(K () :<- YY y)  = K () :<- YY z

对于结构性案例,我发现引入一个帮助程序让我能够统一处理变量很有用。

vV :: Vary v -> Z b v x y -> V v (Z b X x y) (Z b Y x y)
vV VX z = XX z
vV VY z = YY z

然后我构建了一些小工具来促进我们需要的那种“重新标记”downaround. (当然,我在工作时看到了我需要哪些小工具。)

zimap :: (Bifunctor c) => (forall v. Vary v -> D b v x y -> D b' v x y) ->
         c (Z b X x y) (Z b Y x y) -> c (Z b' X x y) (Z b' Y x y)
zimap f = bimap
  (\ (d :<- XX x) -> f VX d :<- XX x)
  (\ (d :<- YY y) -> f VY d :<- YY y)

dzimap :: (Bifunctor (D c X), Bifunctor (D c Y)) =>
         (forall v. Vary v -> D b v x y -> D b' v x y) ->
         Vary v -> Z c v (Z b X x y) (Z b Y x y) -> D c v (Z b' X x y) (Z b' Y x y)
dzimap f VX (d :<- _) = bimap
  (\ (d :<- XX x) -> f VX d :<- XX x)
  (\ (d :<- YY y) -> f VY d :<- YY y)
  d
dzimap f VY (d :<- _) = bimap
  (\ (d :<- XX x) -> f VX d :<- XX x)
  (\ (d :<- YY y) -> f VY d :<- YY y)
  d

有了这么多准备好了,我们就可以研究出细节了。总和很容易。

instance (Diff2 b, Diff2 c) => Diff2 (b :++: c) where
  type D (b :++: c) v = D b v :++: D c v
  up v (L b' :<- vv) = L (up v (b' :<- vv))
  down (L b) = L (zimap (const L) (down b))
  down (R c) = R (zimap (const R) (down c))
  around v z@(L b' :<- vv :: Z (b :++: c) v x y)
    = L (dzimap (const L) v ba) :<- vV v z
    where ba = around v (b' :<- vv :: Z b v x y)
  around v z@(R c' :<- vv :: Z (b :++: c) v x y)
    = R (dzimap (const R) v ca) :<- vV v z
    where ca = around v (c' :<- vv :: Z c v x y)

产品是艰苦的工作,这就是为什么我是数学家而不是工程师的原因。

instance (Diff2 b, Diff2 c) => Diff2 (b :**: c) where
  type D (b :**: c) v = (D b v :**: c) :++: (b :**: D c v)
  up v (L (b' :**: c) :<- vv) = up v (b' :<- vv) :**: c
  up v (R (b :**: c') :<- vv) = b :**: up v (c' :<- vv)
  down (b :**: c) =
    zimap (const (L . (:**: c))) (down b) :**: zimap (const (R . (b :**:))) (down c)
  around v z@(L (b' :**: c) :<- vv :: Z (b :**: c) v x y)
    = L (dzimap (const (L . (:**: c))) v ba :**:
        zimap (const (R . (b :**:))) (down c))
      :<- vV v z where
      b = up v (b' :<- vv :: Z b v x y)
      ba = around v (b' :<- vv :: Z b v x y)
  around v z@(R (b :**: c') :<- vv :: Z (b :**: c) v x y)
    = R (zimap (const (L . (:**: c))) (down b):**:
        dzimap (const (R . (b :**:))) v ca)
      :<- vV v z where
      c = up v (c' :<- vv :: Z c v x y)
      ca = around v (c' :<- vv :: Z c v x y)

从概念上讲,它和以前一样,但有更多的官僚主义。我使用预类型孔技术构建了这些,undefined在我还没有准备好工作的地方用作存根,并在一个地方(在任何给定时间)引入故意的类型错误,我希望从类型检查器获得有用的提示. 即使在 Haskell 中,您也可以将类型检查作为视频游戏体验。

递归容器的子节点拉链

的偏导数b告诉X我们如何在节点内一步找到子节点,因此我们得到了 zipper 的传统概念。

data MuZpr b y = MuZpr
  {  aboveMu  :: [D b X (Mu b y) y]
  ,  hereMu   :: Mu b y
  }

X我们可以通过重复插入位置一直放大到根。

muUp :: Diff2 b => MuZpr b y -> Mu b y
muUp (MuZpr {aboveMu = [], hereMu = t}) = t
muUp (MuZpr {aboveMu = (dX : dXs), hereMu = t}) =
  muUp (MuZpr {aboveMu = dXs, hereMu = In (up VX (dX :<- XX t))})

但是我们需要元素-拉链。

用于双函子固定点的元素拉链

每个元素都位于节点内的某个位置。该节点位于一堆X-derivatives 下。但是该节点中元素的位置由-导数给出Y。我们得到

data MuCx b y = MuCx
  {  aboveY  :: [D b X (Mu b y) y]
  ,  belowY  :: D b Y (Mu b y) y
  }

instance Diff2 b => Functor (MuCx b) where
  fmap f (MuCx { aboveY = dXs, belowY = dY }) = MuCx
    {  aboveY  = map (bimap (fmap f) f) dXs
    ,  belowY  = bimap (fmap f) f dY
    }

大胆地,我声称

instance Diff2 b => Diff1 (Mu b) where
  type DF (Mu b) = MuCx b

但在我开发操作之前,我需要一些零碎的东西。

我可以在 functor-zippers 和 bifunctor-zippers 之间交换数据,如下所示:

zAboveY :: ZF (Mu b) y -> [D b X (Mu b y) y]  -- the stack of `X`-derivatives above me
zAboveY (d :<-: y) = aboveY d

zZipY :: ZF (Mu b) y -> Z b Y (Mu b y) y      -- the `Y`-zipper where I am
zZipY (d :<-: y) = belowY d :<- YY y

这足以让我定义:

  upF z  = muUp (MuZpr {aboveMu = zAboveY z, hereMu = In (up VY (zZipY z))})

也就是说,我们首先重新组装元素所在的节点,将元素拉链变成子节点拉链,然后一路缩小,如上。

接下来我说

  downF  = yOnDown []

从空堆栈开始向下,并定义down从任何堆栈下方重复执行的辅助函数:

yOnDown :: Diff2 b => [D b X (Mu b y) y] -> Mu b y -> Mu b (ZF (Mu b) y)
yOnDown dXs (In b) = In (contextualize dXs (down b))

现在,down b只带我们进入节点。我们需要的拉链还必须携带节点的上下文。这就是contextualise

contextualize :: (Bifunctor c, Diff2 b) =>
  [D b X (Mu b y) y] ->
  c (Z b X (Mu b y) y) (Z b Y (Mu b y) y) ->
  c (Mu b (ZF (Mu b) y)) (ZF (Mu b) y)
contextualize dXs = bimap
  (\ (dX :<- XX t) -> yOnDown (dX : dXs) t)
  (\ (dY :<- YY y) -> MuCx {aboveY = dXs, belowY = dY} :<-: y)

对于每个Y位置,我们必须给出一个元素拉链,所以我们知道整个上下文dXs回到根,以及dY描述元素如何位于其节点中的内容是很好的。对于每个X位置,都有一个进一步的子树要探索,所以我们增加堆栈并继续前进!

那只剩下转移焦点的业务了。我们可能会留在原地,或者从我们所在的位置下降,或者上升,或者上升,然后沿着其他路径走下去。开始。

  aroundF z@(MuCx {aboveY = dXs, belowY = dY} :<-: _) = MuCx
    {  aboveY = yOnUp dXs (In (up VY (zZipY z)))
    ,  belowY = contextualize dXs (cxZ $ around VY (zZipY z))
    }  :<-: z

与以往一样,现有元素被其整个拉链所取代。对于这一belowY部分,我们看看我们可以在现有节点中去哪里:我们将找到替代元素Y位置或进一步X探索的子节点,所以我们contextualise他们。就aboveY部分而言,我们必须在重新组装我们正在访问的节点后备份X-derivatives 堆栈。

yOnUp :: Diff2 b => [D b X (Mu b y) y] -> Mu b y ->
         [D b X (Mu b (ZF (Mu b) y)) (ZF (Mu b) y)]
yOnUp [] t = []
yOnUp (dX : dXs) (t :: Mu b y)
  =  contextualize dXs (cxZ $ around VX (dX :<- XX t))
  :  yOnUp dXs (In (up VX (dX :<- XX t)))

在每一步,我们要么转向其他地方around,要么继续往上走。

就是这样!我没有给出法律的正式证明,但在我看来,这些操作在爬取结构时似乎仔细地正确维护了上下文。

我们学到了什么?

可区分性引发了事物在其上下文中的概念,引发了一个共元结构,在该结构中extract为您提供事物并duplicate探索上下文以寻找其他事物以进行上下文化。如果我们有适当的节点微分结构,我们可以为整棵树开发微分结构。

哦,单独处理每个单独的类型构造函数是非常可怕的。更好的方法是在索引集之间使用函子

f :: (i -> *) -> (o -> *)

我们制作o不同类型的结构来存储i不同类型的元素。这些在雅可比结构下是封闭的

J f :: (i -> *) -> ((o, i) -> *)

其中每个生成的 -(o, i)结构都是偏导数,告诉您如何在 - 结构中制作i- 元素孔o。但这是另一种类型的乐趣。

于 2014-08-29T16:12:48.283 回答
12

拉链的Comonad实例不是

instance (Diff t, Diff (D t)) => Comonad (Zipper t) where
    extract = here
    duplicate = fmap outOf . inTo

实例本身的位置outOfinTo来源。上述例子触犯了法律。相反,它的行为类似于:DiffZipper tComonadfmap extract . duplicate == id

fmap extract . duplicate == \z -> fmap (const (here z)) z

差速器(拉链 t)

通过将它们标识为产品并重用产品代码(如下)来提供Diff实例。Zipper

-- Zippers are themselves products
toZipper :: (D t :*: Identity) a -> Zipper t a
toZipper (d :*: (Identity h)) = Zipper d h

fromZipper :: Zipper t a -> (D t :*: Identity) a
fromZipper (Zipper d h) = (d :*: (Identity h))

给定数据类型之间的同构以及它们的派生之间的同构,我们可以重用一种类型inTooutOf另一种类型。

inToFor' :: (Diff r) =>
            (forall a.   r a ->   t a) ->
            (forall a.   t a ->   r a) ->
            (forall a. D r a -> D t a) ->
            (forall a. D t a -> D r a) ->
            t a -> t (Zipper t a)
inToFor' to from toD fromD = to . fmap (onDiff toD) . inTo . from

outOfFor' :: (Diff r) =>
            (forall a.   r a ->   t a) ->
            (forall a.   t a ->   r a) ->
            (forall a. D r a -> D t a) ->
            (forall a. D t a -> D r a) ->
            Zipper t a -> t a
outOfFor' to from toD fromD = to . outOf . onDiff fromD

对于只是现有Diff实例的 newTypes 的类型,它们的派生是相同的类型。如果我们告诉类型检查器该类型相等D r ~ D t,我们可以利用它而不是为派生提供同构。

inToFor :: (Diff r, D r ~ D t) =>
           (forall a. r a -> t a) ->
           (forall a. t a -> r a) ->
           t a -> t (Zipper t a)
inToFor to from = inToFor' to from id id

outOfFor :: (Diff r, D r ~ D t) =>
            (forall a. r a -> t a) ->
            (forall a. t a -> r a) ->
            Zipper t a -> t a
outOfFor to from = outOfFor' to from id id

有了这些工具,我们就可以复用Diff产品的实例来实现Diff (Zipper t)

-- This requires undecidable instances, due to the need to take D (D t)
instance (Diff t, Diff (D t)) => Diff (Zipper t) where
    type D (Zipper t) = D ((D t) :*: Identity)
    -- inTo :: t        a -> t        (Zipper  t         a)
    -- inTo :: Zipper t a -> Zipper t (Zipper (Zipper t) a)
    inTo = inToFor toZipper fromZipper
    -- outOf :: Zipper  t         a -> t        a
    -- outOf :: Zipper (Zipper t) a -> Zipper t a
    outOf = outOfFor toZipper fromZipper

样板

为了实际使用这里提供的代码,我们需要一些语言扩展、导入和对所提出问题的重述。

{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE RankNTypes #-}

import Control.Monad.Identity
import Data.Proxy
import Control.Comonad

data Zipper t a = Zipper { diff :: D t a, here :: a }

onDiff :: (D t a -> D u a) -> Zipper t a -> Zipper u a
onDiff f (Zipper d a) = Zipper (f d) a

deriving instance Diff t => Functor (Zipper t)
deriving instance (Eq (D t a), Eq a) => Eq (Zipper t a)
deriving instance (Show (D t a), Show a) => Show (Zipper t a)

class (Functor t, Functor (D t)) => Diff t where
  type D t :: * -> *
  inTo  :: t a -> t (Zipper t a)
  outOf :: Zipper t a -> t a

乘积、总和和常数

Diff (Zipper t)实例依赖于Difffor products :*:、sum :+:、constantsIdentity和 zero的实现Proxy

data (:+:) a b x = InL (a x) | InR (b x)
    deriving (Eq, Show)
data (:*:) a b x = a x :*: b x
    deriving (Eq, Show)

infixl 7 :*:
infixl 6 :+:

deriving instance (Functor a, Functor b) => Functor (a :*: b)

instance (Functor a, Functor b) => Functor (a :+: b) where
    fmap f (InL a) = InL . fmap f $ a
    fmap f (InR b) = InR . fmap f $ b


instance (Diff a, Diff b) => Diff (a :*: b) where
    type D (a :*: b) = D a :*: b :+: a :*: D b
    inTo (a :*: b) = 
        (fmap (onDiff (InL . (:*: b))) . inTo) a :*:
        (fmap (onDiff (InR . (a :*:))) . inTo) b
    outOf (Zipper (InL (a :*: b)) x) = (:*: b) . outOf . Zipper a $ x
    outOf (Zipper (InR (a :*: b)) x) = (a :*:) . outOf . Zipper b $ x

instance (Diff a, Diff b) => Diff (a :+: b) where
    type D (a :+: b) = D a :+: D b
    inTo (InL a) = InL . fmap (onDiff InL) . inTo $ a
    inTo (InR b) = InR . fmap (onDiff InR) . inTo $ b
    outOf (Zipper (InL a) x) = InL . outOf . Zipper a $ x
    outOf (Zipper (InR a) x) = InR . outOf . Zipper a $ x

instance Diff (Identity) where
    type D (Identity) = Proxy
    inTo = Identity . (Zipper Proxy) . runIdentity
    outOf = Identity . here

instance Diff (Proxy) where
    type D (Proxy) = Proxy
    inTo = const Proxy
    outOf = const Proxy

箱示例

我将这个Bin例子作为产品总和的同构。我们不仅需要它的导数,还需要它的二阶导数

newtype Bin   a = Bin   {unBin   ::      (Bin :*: Identity :*: Bin :+: Identity)  a}
    deriving (Functor, Eq, Show)
newtype DBin  a = DBin  {unDBin  ::    D (Bin :*: Identity :*: Bin :+: Identity)  a}
    deriving (Functor, Eq, Show)
newtype DDBin a = DDBin {unDDBin :: D (D (Bin :*: Identity :*: Bin :+: Identity)) a}
    deriving (Functor, Eq, Show)

instance Diff Bin where
    type D Bin = DBin
    inTo  = inToFor'  Bin unBin DBin unDBin
    outOf = outOfFor' Bin unBin DBin unDBin

instance Diff DBin where
    type D DBin = DDBin
    inTo  = inToFor'  DBin unDBin DDBin unDDBin
    outOf = outOfFor' DBin unDBin DDBin unDDBin

上一个答案的示例数据是

aTree :: Bin Int    
aTree =
    (Bin . InL) (
        (Bin . InL) (
            (Bin . InR) (Identity 2)
            :*: (Identity 1) :*:
            (Bin . InR) (Identity 3)
        )
        :*: (Identity 0) :*:
        (Bin . InR) (Identity 4)
    )

不是 Comonad 实例

上面的示例为正确实现forBin提供了一个反例。特别是,它为法律提供了一个反例:fmap outOf . inToduplicateZipper tfmap extract . duplicate = id

fmap ( \z -> (fmap extract . duplicate) z == z) . inTo $ aTree

计算结果为(注意它是如何False到处都是 s,任何False都足以反驳法律)

Bin {unBin = InL ((Bin {unBin = InL ((Bin {unBin = InR (Identity False)} :*: Identity False) :*: Bin {unBin = InR (Identity False)})} :*: Identity False) :*: Bin {unBin = InR (Identity False)})}

inTo aTree是一棵与 具有相同结构的树aTree,但在任何地方都有一个值,而是一个带有该值的拉链,而树的其余部分则具有完整的所有原始值。fmap (fmap extract . duplicate) . inTo $ aTree也是一棵与 具有相同结构的树aTree,但只要有一个值,就会有一个带有该值的拉链,而树的其余部分将所有值替换为相同的值。换句话说:

fmap extract . duplicate == \z -> fmap (const (here z)) z

Comonad所有三个定律、extract . duplicate == idfmap extract . duplicate == id和的完整测试套件duplicate . duplicate == fmap duplicate . duplicate

main = do
    putStrLn "fmap (\\z -> (extract . duplicate) z == z) . inTo $ aTree"
    print   . fmap ( \z -> (extract . duplicate) z == z) . inTo $ aTree    
    putStrLn ""
    putStrLn  "fmap (\\z -> (fmap extract . duplicate) z == z) . inTo $ aTree"
    print    . fmap ( \z -> (fmap extract . duplicate) z == z) . inTo $ aTree    
    putStrLn ""
    putStrLn "fmap (\\z -> (duplicate . duplicate) z) == (fmap duplicate . duplicate) z) . inTo $ aTree"
    print   . fmap ( \z -> (duplicate . duplicate) z == (fmap duplicate . duplicate) z) . inTo $ aTree
于 2014-08-29T06:34:37.910 回答
8

给定一个无限可微的Diff类:

class (Functor t, Functor (D t)) => Diff t where
    type D t :: * -> *
    up :: Zipper t a -> t a
    down :: t a -> t (Zipper t a)  
    -- Require that types be infinitely differentiable
    ddiff :: p t -> Dict (Diff (D t))

around可以写成updown的导数Zipperdiff本质上为

around z@(Zipper d h) = Zipper ctx z
    where
        ctx = fmap (\z' -> Zipper (up z') (here z')) (down d)

Zipper t aaD t a和a 组成a。我们去downD t aD t (Zipper (D t) a)每个洞都有一个拉链。那些拉链由一个D (D t) aa那个在洞里组成。我们去up他们每个人,得到一个并将其与洞中D t a的那个配对。aA D t aand an amake a Zipper t a,给我们 a D t (Zipper t a),这是 a 所需的上下文Zipper t (Zipper t a)

然后该Comonad实例很简单

instance Diff t => Comonad (Zipper t) where
    extract   = here
    duplicate = around

捕获导数的Diff字典需要一些额外的管道,这可以使用 Data.Constraint 或根据相关答案中提供的方法来完成

around :: Diff t => Zipper t a -> Zipper t (Zipper t a)
around z = Zipper (withDict d' (fmap (\z' -> Zipper (up z') (here z')) (down (diff z)))) z
    where
        d' = ddiff . p' $ z
        p' :: Zipper t x -> Proxy t
        p' = const Proxy 
于 2014-09-01T07:47:59.007 回答