12

根据 Bartosz Milewski 的文章(),我定义了一个F-Algebra

(这并不是说我的代码是 Bartosz 思想的准确体现,这只是我对它们的有限理解,任何错误都是我一个人的问题。)

module Algebra where

data Expr a = Branch [a] | Leaf Int

instance Functor Expr where
    fmap f (Branch xs) = Branch (fmap f xs)
    fmap _ (Leaf   i ) = Leaf    i

newtype Fix a = Fix { unFix :: a (Fix a) }

branch = Fix . Branch
leaf   = Fix . Leaf

-- | This is an example algebra.
evalSum (Branch xs) = sum xs
evalSum (Leaf   i ) =     i

cata f = f . fmap (cata f) . unFix

我现在几乎可以做任何我想做的事情,例如,对叶子求和:

λ cata evalSum $ branch [branch [leaf 1, leaf 2], leaf 3]
6

这是我专门为这个问题编造的一个人为的例子,但我实际上尝试了一些不那么琐碎的事情(例如评估和简化具有任意数量变量的多项式),它就像一个魅力。One may indeed fold and replace any parts of a structure as one runs a catamorphism through, with a suitably chosen algebra . 所以,我很确定 F-Algebra 包含了 Foldable,它甚至似乎也包含了 Traversable。

现在,我可以根据 F 代数定义可折叠/可遍历实例吗?

在我看来,我不能。

  • 我只能在初始 algebra上运行 catamorphism ,这是一个空类型构造函数。而且我给它的代数有一个类型,a b -> b而不是a -> b,也就是说,“in”和“out”类型之间存在函数依赖关系。
  • Algebra a => Foldable a在类型签名中看不到任何地方。如果不这样做,那一定是不可能的。

在我看来,我不能Foldable用 F 代数来定义,因为一个Expr必须是 aFunctor在两个变量中:一个是载体,另一个是,然后是Foldable第二个。因此,双函子可能更合适。我们也可以构造一个带有双函子的 F-代数:

module Algebra2 where

import Data.Bifunctor

data Expr a i = Branch [a] | Leaf i

instance Bifunctor Expr where
    bimap f _ (Branch xs) = Branch (fmap f xs)
    bimap _ g (Leaf   i ) = Leaf   (g i)

newtype Fix2 a i = Fix2 { unFix2 :: a (Fix2 a i) i }

branch = Fix2 . Branch
leaf   = Fix2 . Leaf

evalSum (Branch xs) = sum xs
evalSum (Leaf   i ) =     i

cata2 f g = f . bimap (cata2 f g) g . unFix2

它像这样运行:

λ cata2 evalSum (+1) $ branch [branch [leaf 1, leaf 2], leaf 3]
9

但我仍然无法定义可折叠。它会有这样的类型:

instance Foldable \i -> Expr (Fix2 Expr i) i where ...

不幸的是,没有得到关于类型的 lambda 抽象,也没有办法同时将隐含的类型变量放在两个地方。

我不知道该怎么办。

4

2 回答 2

17

F 代数定义了在评估所有子级之后评估递归数据结构的单个级别的方法。Foldable定义了一种评估(不一定是递归的)数据结构的方法,前提是您知道如何将存储在其中的值转换为幺半群的元素。

要实现foldMap递归数据结构,您可以从定义一个代数开始,其载体是一个幺半群。您将定义如何将叶子转换为单曲面值。然后,假设一个节点的所有子节点都被评估为 monoidal 值,您将定义一种将它们组合在节点中的方法。一旦你定义了这样一个代数,你就可以运行一个 catamorphism 来评估foldMap整个树。

所以你的问题的答案是,要Foldable为定点数据结构创建一个实例,你必须定义一个适当的代数,其载体是一个幺半群。

编辑:这是可折叠的实现:

data Expr e a = Branch [a] | Leaf e

newtype Ex e = Ex { unEx :: Fix (Expr e) }

evalM :: Monoid m => (e -> m) -> Algebra (Expr e) m
evalM _ (Branch xs) = mconcat xs
evalM f (Leaf   i ) = f i

instance Foldable (Ex) where
  foldMap f = cata (evalM f) . unEx

tree :: Ex Int
tree = Ex $ branch [branch [leaf 1, leaf 2], leaf 3]

x = foldMap Sum tree

实现Traversable为 catamorphism 涉及更多一点,因为您希望结果不仅仅是一个摘要 - 它必须包含完整的重建数据结构。因此,代数的载体必须是 的最终结果的类型traverse,即(f (Fix (Expr b)))where fis Applicative

tAlg :: Applicative f => (e -> f b) -> Algebra (Expr e) (f (Fix (Expr b)))

这是这个代数:

tAlg g (Leaf e)    = leaf   <$> g e
tAlg _ (Branch xs) = branch <$> sequenceA xs

这就是您实施的方式traverse

instance Traversable Ex where
  traverse g = fmap Ex . cata (tAlg g) . unEx

的超类Traversable是 a Functor,因此您需要证明定点数据结构是函子。您可以通过实现一个简单的代数并在其上运行一个变态来做到这一点:

fAlg :: (a -> b) -> Algebra (Expr a) (Fix (Expr b))
fAlg g (Leaf e) = leaf (g e)
fAlg _ (Branch es) = branch es

instance Functor Ex where
  fmap g = Ex . cata (fAlg g) . unEx

(Michael Sloan 帮助我编写了这段代码。)

于 2018-01-29T14:46:14.963 回答
4

非常好,你用过Bifunctor。使用Bifunctor基函子 ( )在固定点 ( ) 上Expr进行定义。这种方法也适用于和(他们现在)。FunctorFix ExprBifoldableBitraversablebase

让我们看看这会如何使用recursion-schemes. 它看起来有点不同,因为我们在那里定义了正常的递归类型,比如Tree e,以及它的基本函子:Base (Tree e) = TreeF e a具有两个函数: project :: Tree e -> TreeF e (Tree e)embed :: TreeF e (Tree e) -> Tree e. 递归机制可以使用TemplateHaskell派生:

请注意,我们有Base (Fix f) = f( project = unFix, embed = Fix),因此我们可以使用refixconvert Tree etoFix (TreeF e)和 back。但是我们不需要使用Fix,我们可以cata Tree直接使用!

首先包括:

{-# LANGUAGE TemplateHaskell, KindSignatures, TypeFamilies, DeriveFunctor, DeriveFoldable, DeriveTraversable #-}
import Data.Functor.Foldable
import Data.Functor.Foldable.TH

import Data.Bifunctor
import Data.Bifoldable
import Data.Bitraversable

然后数据:

data Tree e = Branch [Tree e] | Leaf e deriving Show

-- data TreeF e r = BranchF [r] | LeafF e
-- instance Traversable (TreeF e)
-- instance Foldable (TreeF e)
-- instance Functor (TreeF e)
makeBaseFunctor ''Tree

现在我们有了机器,我们可以有变质

cata :: Recursive t => (Base t a -> a) -> t -> a
cata f = c where c = f . fmap c . project

或(我们稍后需要)

cataBi :: (Recursive t, Bifunctor p, Base t ~ p x) => (p x a -> a) -> t -> a
cataBi f = c where c = f . second c . project

先举个Functor例子。正如 OP 所写的那样,请注意它的Bifunctor实例是如何自行脱落的。TreeFFunctor

instance Bifunctor TreeF where
    bimap f _ (LeafF e)    = LeafF (f e)
    bimap _ g (BranchF xs) = BranchF (fmap g xs)

instance Functor Tree where
    fmap f = cata (embed . bimap f id)

毫不奇怪,Foldablefor fixpoint 可以根据Bifoldable基函子来定义:

instance Bifoldable TreeF where
    bifoldMap f _ (LeafF e)    = f e
    bifoldMap _ g (BranchF xs) = foldMap g xs

instance Foldable Tree where
    foldMap f = cata (bifoldMap f id)

最后Traversable

instance Bitraversable TreeF where
    bitraverse f _ (LeafF e)    = LeafF <$> f e
    bitraverse _ g (BranchF xs) = BranchF <$> traverse g xs

instance Traversable Tree where
    traverse f = cata (fmap embed . bitraverse f id)

如您所见,定义非常简单,并遵循类似的模式。

实际上,我们可以traverse为基函子所在的每个固定点定义 -like 函数Bitraversable

traverseRec
    :: ( Recursive t, Corecursive s, Applicative f
       , Base t ~ base a, Base s ~ base b, Bitraversable base)
    => (a -> f b) -> t -> f s
traverseRec f = cataBi (fmap embed . bitraverse f id)

在这里,我们cataBi用来使类型签名更漂亮:不Functor (base b),因为它是由Bitraversable base. 顺便说一句,这是一个很好的函数,因为它的类型签名比实现长三倍)。

最后,我必须提到Fix在 Haskell 中并不完美:我们使用最后一个参数来修复 base-functor:

Fix :: (* -> *) -> * -- example: Tree e ~ Fix (TreeF e)

因此,Bartosz 需要Ex在他的答案中定义以使种类对齐,但是最好解决第一个参数:

Fix :: (* -> k) -> k -- example: Tree e = Fix TreeF' e

其中data TreeF' a e = LeafF' e | BranchF' [a],即TreeF索引翻转。这样,我们就可以在 Functor (Fix b)(公共库中不存在)等方面拥有。Bifunctor fBifunctor (Fix b)Trifunctor

您可以在https://github.com/ekmett/recursion-schemes/pull/23中了解我的失败尝试以及 Edward Kmett 对此问题的评论

于 2018-01-31T08:15:45.927 回答