是个懒人,广度优先单子玫瑰树展开可能吗? [英] Is a lazy, breadth-first monadic rose tree unfold possible?

查看:235
本文介绍了是个懒人,广度优先单子玫瑰树展开可能吗?的处理方法,对大家解决问题具有一定的参考价值,需要的朋友们下面随着小编来一起学习吧!

问题描述

Data.Tree 包括 unfoldTreeM_BF unfoldForestM_BF 功能构建广度优先使用一元行动的结果树。展平可以很容易地编写使用林展平的树,所以我会着重于后者:

Data.Tree includes unfoldTreeM_BF and unfoldForestM_BF functions to construct trees breadth-first using the results of monadic actions. The tree unfolder can be written easily using the forest unfolder, so I'll focus on the latter:

unfoldForestM_BF :: Monad m =>
             (b -> m (a, [b])) -> [b] -> m [Tree a]

种子的列表开始,它应用一个函数的每个,生成将产生树根和种子为展开的下一级的行动。所使用的算法有点严格,所以使用 unfoldForestM_BF 身份单子是不完全一样的使用纯 unfoldForest 。我一直在试图找出是否有一种方法,使之懒不牺牲其 O(n)的约束的时间。如果(爱德华Kmett建议我)这是不可能的,我不知道是否有可能以更加约束类型做到这一点,特别是要求 MonadFix ,而不是单子。这一概念也将是(在某种程度上)设立了指向未来计算的结果,同时将这些计算的待办事项列表,这样,如果他们是懒惰的前面计算的影响,他们将立即可用。

Starting with a list of seeds, it applies a function to each, generating actions that will produce the tree roots and the seeds for the next level of unfolding. The algorithm used is somewhat strict, so using unfoldForestM_BF with the Identity monad is not exactly the same as using the pure unfoldForest. I've been trying to figure out if there's a way to make it lazy without sacrificing its O(n) time bound. If (as Edward Kmett suggested to me) this is impossible, I wonder if it would be possible to do it with a more constrained type, specifically requiring MonadFix rather than Monad. The concept there would be to (somehow) set up the pointers to the results of future computations while adding those computations to the to-do list, so if they are lazy in the effects of earlier computations they will be available immediately.

推荐答案

我pviously声称$ P $,以下psented第三个解决方案$ P $有相同的严格的深度优先 unfoldForest ,这是不正确的。

I previously claimed that the third solution presented below has the same strictness as the depth-first unfoldForest, which is not correct.

您的直觉,树木可以懒洋洋地展开广度优先至少部分正确的,即使我们不需要 MonadFix 实例。解时的分支因子已知是有限的,当分支因子已知是大的特殊情况下存在。我们将开始与运行在的解决方案为O(n)的时间与有限的分支因素,包括退化树,每个节点只有一个孩子的树木。对于有限的分支因素,该解决方案将无法终止的树木无限的分支因素,我们将有一个解决方案,运行在 O(N)的时间与树整顿大的分支因素大于一,包括与无限的分支因子的树。对于大的分支因素,该解决方案将在运行为O(n ^ 2)简并树上时间只有一个子女或每节点没有孩子。当我们把从两个步骤的方法,企图使运行在 O(N)时间任何支因素,我们将得到一个解决方案,就是懒比混合解决方案对于有限的分支因素,第一个解决方案,但不能容纳的树木,使从无限的分支因子迅速过渡到无分支。

Your intuition that trees can be lazily unfolded breadth first is at least partially correct, even if we don't require a MonadFix instance. Solutions exist for the special cases when the branching factor is known to be finite and when the branching factor is known to be "large". We will start with a solution that runs in O(n) time for trees with finite branching factors including degenerate trees with only one child per node. The solution for finite branching factors will fail to terminate on trees with infinite branching factors, which we will rectify with a solution that that runs in O(n) time for trees with "large" branching factors greater than one including trees with infinite branching factor. The solution for "large" branching factors will run in O(n^2) time on degenerate trees with only one child or no children per node. When we combine the methods from both steps in an attempt to make a hybrid solution that runs in O(n) time for any branching factor we will get a solution that is lazier than the first solution for finite branching factors but cannot accommodate trees that make a rapid transition from an infinite branching factor to having no branches.

总的想法是,我们将先建立所有的整体水平和标签的种子为森林的一个新的水平。然后,我们将陷入一个新的水平,打造这一切。我们将收集起来,从更深层次的结果,建立森林的外层。我们将会把标签一起打造的树木森林。

The general idea is that we will first build all the labels for an entire level and the seeds for the forests for the next level. We will then descend into the next level, building all of it. We will collect together the results from the deeper level to build the forests for the outer level. We will put the labels together with the forests to build the trees.

unfoldForestM_BF 是相当简单的。如果没有种子它返回的水平。构建所有的标签后,它需要的种子,每个林和他们一起收集到所有的建设一个新的水平的种子列表并展开整个更深的层次。最后,构建森林从种子的结构,每个树。

unfoldForestM_BF is fairly simple. If there are no seeds for the level it returns. After building all the labels, it takes the seeds for each forest and collects them together into one list of all the seeds to build the next level and unfolds the entire deeper level. Finally it constructs the forest for each tree from the structure of the seeds.

import Data.Tree hiding (unfoldTreeM_BF, unfoldForestM_BF)

unfoldForestM_BF :: Monad m => (b->m (a, [b])) -> [b] -> m [Tree a]
unfoldForestM_BF f []    = return []
unfoldForestM_BF f seeds = do
    level <- sequence . fmap f $ seeds
    let (labels, bs) = unzip level
    deeper <- unfoldForestM_BF f (concat bs)
    let forests = trace bs deeper
    return $ zipWith Node labels forests

跟踪重建嵌套列表从扁平list.It结构假设有在项[B] 为每个项目> [一] 。使用 CONCAT ... 跟踪的扁平化所有关于祖先各级prevents此实现从工作信息在与孩子们无限的节点树。

trace reconstructs the structure of nested lists from a flattened list.It is assumed that there is an item in [b] for each of the items anywhere in [[a]]. The use of concat ... trace to flatten all the information about ancestor levels prevents this implementation from working on trees with infinite children for a node.

trace :: [[a]] -> [b] -> [[b]]
trace []       ys = []
trace (xs:xxs) ys =
    let (ys', rem) = takeRemainder xs ys
    in   ys':trace xxs rem
    where
        takeRemainder []        ys  = ([], ys)
        takeRemainder (x:xs) (y:ys) = 
            let (  ys', rem) = takeRemainder xs ys
            in  (y:ys', rem)

展开树是微不足道的在展开森林方面写。

Unfolding a tree is trivial to write in terms of unfolding a forest.

unfoldTreeM_BF :: MonadFix m => (b->m (a, [b])) -> b -> m (Tree a)
unfoldTreeM_BF f = (>>= return . head) . unfoldForestMFix_BF f . (:[])

大分支因子

在大致相同的方式,作为有限分支因子的溶液为大分支因子所得的溶液,除了它保持树的整个结构,而不是围绕的concat enating在一个水平上了一个单独的列表和跟踪荷兰国际集团的列表中的分支。除了进口取值,我们将使用撰写组成的仿函数用在previous节对于多层次树一起 Traversable的在多层次结构。

Large Branching Factor

The solution for large branching factor proceeds in much the same way as the solution for finite branching factor, except it keeps the entire structure of the tree around instead of concatenating the branches in a level to a single list and traceing that list. In addition to the imports used in the previous section, we will be using Compose to compose the functors for multiple levels of a tree together and Traversable to sequence across multi-level structures.

import Data.Tree hiding (unfoldForestM_BF, unfoldTreeM_BF)

import Data.Foldable
import Data.Traversable
import Data.Functor.Compose
import Prelude hiding (sequence, foldr)

而不是用压扁所有的祖先结构一起CONCAT ,我们将与撰写的祖先和种子包装为下一级并递归在整个结构上。

Instead of flattening all of the ancestor structures together with concat we will wrap with Compose the ancestors and the seeds for the next level and recurse on the entire structure.

unfoldForestM_BF :: (Traversable t, Traceable t, Monad m) =>
                    (b->m (a, [b])) -> t b -> m (t (Tree a))
unfoldForestM_BF f seeds
    | isEmpty seeds = return (fmap (const undefined) seeds)
    | otherwise     = do
        level <- sequence . fmap f $ seeds
        deeper <- unfoldForestM_BF f (Compose (fmap snd level))
        return $ zipWithIrrefutable Node (fmap fst level) (getCompose deeper)

zipWithIrrefutable 是一个懒惰的版本 zipWith 依赖的假设是存在在第二个列表中的项目对于在第一列表中的每个项目。该可溯源结构是函子,可以提供一个 zipWithIrrefutable 。该法律对可溯源是每个 A XS ,和 YS 如果 FMAP(常量一)XS == FMAP(常量一)YS 然后 zipWithIrrefutable(\ x _ - &GT; X)XS YS == XS zipWithIrrefutable(\ _Ÿ - &GT; Y)XS YS == YS 。它的严格性,给出了每个 F XS zipWithIrrefutable˚FXS⊥= = FMAP( \ x - &GT; FX⊥)XS

zipWithIrrefutable is a lazier version of zipWith that relies on the assumption that there is an item in the second list for each item in the first list. The Traceable structures are the Functors that can provide a zipWithIrrefutable. The laws for Traceable are for every a, xs, and ys if fmap (const a) xs == fmap (const a) ys then zipWithIrrefutable (\x _ -> x) xs ys == xs and zipWithIrrefutable (\_ y -> y) xs ys == ys. Its strictness is given for every f and xs by zipWithIrrefutable f xs ⊥ == fmap (\x -> f x ⊥) xs.

class Functor f => Traceable f where
    zipWithIrrefutable :: (a -> b -> c) -> f a -> f b -> f c 

我们可以结合两个列表懒洋洋地,如果我们已经知道它们具有相同的结构。

We can combine two lists lazily if we already know they have the same structure.

instance Traceable [] where
    zipWithIrrefutable f []       ys    = []
    zipWithIrrefutable f (x:xs) ~(y:ys) = f x y : zipWithIrrefutable f xs ys 

我们可以结合两个函子组成,如果我们知道,我们可以将每个仿函数。

We can combine the composition of two functors if we know that we can combine each functor.

instance (Traceable f, Traceable g) => Traceable (Compose f g) where
    zipWithIrrefutable f (Compose xs) (Compose ys) =
        Compose (zipWithIrrefutable (zipWithIrrefutable f) xs ys)

的isEmpty 检查节点的空结构,扩大像模式匹配[] 于溶液做对于有限的分支因素。

isEmpty checks for an empty structure of nodes to expand like the pattern match on [] did in the solution for finite branching factors.

isEmpty :: Foldable f => f a -> Bool
isEmpty = foldr (\_ _ -> False) True

聪明的读者可能会注意到 zipWithIrrefutable 可溯源非常相似 liftA2 的一半应用型

The astute reader may notice that zipWithIrrefutable from Traceable is very similar to liftA2 which is half of the definition of Applicative.

混合动力解决方案结合了有限的解决方案和大的解决方案的方法。像有限的解决方案,我们将COM preSS和DECOM preSS树再presentation在每一步。像大的分支因素的解决方案,我们将使用一个数据结构,使跨过完整的分支机构。在有限的分支因子的解决方案使用的是无处不在扁平化的数据类型, [B] 。而大的分支因数的解决方案使用的是无处扁平化的数据类型:首先是日益嵌套列表[B] 然后 [[B] 然后 [[[B]] 等。在这些结构之间将嵌套的列表,要么停止筑巢,只是持有 B 或保持嵌套按住 [B] 秒。递归这种模式一般由免费单子描述。

The hybrid solution combines the approaches of the finite solution and the "large" solution. Like the finite solution, we will compress and decompress the tree representation at each step. Like the solution for "large" branching factors we will use a data structure that allows stepping over complete branches. The finite branching factor solution used a data type that is flattened everywhere, [b]. The "large" branching factor solution used a data type that was flattened nowhere: increasingly nested lists starting with [b] then [[b]] then [[[b]]] and so on. In between these structures would be nested lists that either stop nesting and just hold a b or keep nesting and hold [b]s. That pattern of recursion is described in general by the Free monad.

data Free f a = Pure a | Free (f (Free f a))

我们将进行具体的工作免费[] 它看起来像。

We will be working specifically with Free [] which looks like.

data Free [] a = Pure a | Free [Free [] a]

有关混合动力解决方案,我们将重复所有的进口和组件,使下面这里code应该是完整的工作code。

For the hybrid solution we will repeat all of its imports and components so that the code below here should be complete working code.

import Data.Tree hiding (unfoldTreeM_BF, unfoldForestM_BF)

import Data.Traversable
import Prelude hiding (sequence, foldr)

由于我们将要共事免费[] ,我们会为他提供了 zipWithIrrefutable

Since we will be working with Free [], we will provide it with a zipWithIrrefutable.

class Functor f => Traceable f where
    zipWithIrrefutable :: (a -> b -> c) -> f a -> f b -> f c  

instance Traceable [] where
    zipWithIrrefutable f []       ys    = []
    zipWithIrrefutable f (x:xs) ~(y:ys) = f x y : zipWithIrrefutable f xs ys 

instance (Traceable f) => Traceable (Free f) where
    zipWithIrrefutable f (Pure x)  ~(Pure y ) = Pure (f x y)
    zipWithIrrefutable f (Free xs) ~(Free ys) =
        Free (zipWithIrrefutable (zipWithIrrefutable f) xs ys)

广度优先遍历看起来非常类似于原来的版本为有限分支树。我们建立了目前的标签和种子目前的水平,COM preSS的树的其余部分的结构,做好各项工作,为剩余的深处,DECOM preSS的结果结构得到森林去的标签。

The breadth first traversal will look very similar to the original version for the finitely branching tree. We build the current labels and seeds for the current level, compress the structure of the remainder of the tree, do all the work for the remaining depths, and decompress the structure of the results to get the forests to go with the labels.

unfoldFreeM_BF :: (Monad m) => (b->m (a, [b])) -> Free [] b -> m (Free [] (Tree a))
unfoldFreeM_BF f (Free []) = return (Free [])
unfoldFreeM_BF f seeds = do
    level <- sequence . fmap f $ seeds
    let (compressed, decompress) = compress (fmap snd level)
    deeper <- unfoldFreeM_BF f compressed
    let forests = decompress deeper
    return $ zipWithIrrefutable Node (fmap fst level) forests

COM preSS 需要免费[] 拿着种子森林 [B] 和展平了 [B] 免费获得免费[] b 。它还返回 DECOM preSS 的功能,可用于撤消扁平化,以获得原始结构回来。我们COM preSS远枝没有剩余的种子和分支机构的唯一分支机构的一种方式。

compress takes a Free [] holding the seeds for forests [b] and flattens the [b] into the Free to get a Free [] b. It also returns a decompress function that can be used to undo the flattening to get the original structure back. We compress away branches with no remaining seeds and branches that only branch one way.

compress :: Free [] [b] -> (Free [] b, Free [] a -> Free [] [a])
compress (Pure [x]) = (Pure x, \(Pure x) -> Pure [x])
compress (Pure xs ) = (Free (map Pure xs), \(Free ps) -> Pure (map getPure ps))
compress (Free xs)  = wrapList . compressList . map compress $ xs
    where    
        compressList []                 = ([], const [])
        compressList ((Free [],dx):xs) = let (xs', dxs) = compressList xs
                                         in  (xs', \xs -> dx (Free []):dxs xs)
        compressList (      (x,dx):xs) = let (xs', dxs) = compressList xs
                                         in  (x:xs', \(x:xs) -> dx x:dxs xs)
        wrapList ([x], dxs) = (x,             \x   -> Free (dxs [x]))
        wrapList (xs , dxs) = (Free xs, \(Free xs) -> Free (dxs xs ))

每个COM pression步也将返回当应用于免费[] 树具有相同的结构,将取消它的功能。所有这些功能都部分地限定;他们做什么免费[] 具有不同结构的树是不确定的。为简单起见,我们还定义的逆部分功能免费

Each compression step also returns a function that will undo it when applied to a Free [] tree with the same structure. All of these functions are partially defined; what they do to Free [] trees with a different structure is undefined. For simplicity we also define partial functions for the inverses of Pure and Free.

getPure (Pure x)  = x
getFree (Free xs) = xs

两个 unfoldForestM_BF unfoldTreeM_BF 通过包装他们的说法成,定义了免费[ ] b 和解包结果假定它们是在相同的结构。

Both unfoldForestM_BF and unfoldTreeM_BF are defined by packaging their argument up into a Free [] b and unpackaging the results assuming they are in the same structure.

unfoldTreeM_BF :: MonadFix m => (b->m (a, [b])) -> b -> m (Tree a)
unfoldTreeM_BF f = (>>= return . getPure) . unfoldFreeM_BF f . Pure


unfoldForestM_BF :: MonadFix m => (b->m (a, [b])) -> [b] -> m [Tree a]
unfoldForestM_BF f = (>>= return . map getPure . getFree) . unfoldFreeM_BF f . Free . map Pure

此算法的更优雅的版本或许可以通过识别&GT进行;&GT; = 单子被嫁接树木和两个免费孚瑞特提供单子实例。无论 COM preSS COM pressList 可能有更优雅的presentations。

A more elegant version of this algorithm can probably be made by recognizing that >>= for a Monad is grafting on trees and both Free and FreeT provide monad instances. Both compress and compressList probably have more elegant presentations.

以上psented算法$ P $是不够的懒惰,让查询树的分支无数的方式,然后终止。一个简单的反例是从下面的生成函数展开 0

The algorithm presented above is not lazy enough to allow querying trees that branch an infinite number of ways and then terminate. A simple counter example is the following generating function unfolded from 0.

counterExample :: Int -> (Int, [Int])
counterExample 0 = (0, [1, 2])
counterExample 1 = (1, repeat 3)
counterExample 2 = (2, [3])
counterExample 3 = (3, [])

这棵树看起来像

0
|
+- 1
|  |
|  +- 3
|  |
|  `- 3
|  |
|  ...
|
`- 2
   |
   +- 3

试图降落第二支(以 2 ),并检查剩余的有限的子树将无法终止。

Attempting to descend the second branch (to 2) and inspect the remaining finite sub-tree will fail to terminate.

下面的例子演示了 unfoldForestM_BF的所有实现在广度优先顺序和 runIdentity运行的行为。 unfoldTreeM_BF(身份。F)具有有限分支因子的树一样严格的 unfoldTree 。对于inifinite分支因子的树,只为大的分支因素,该解决方案具有相同的严格的 unfoldTree 。为了证明懒惰,我们将定义三个无限的树木 - 一个分支,有两个分支二叉树,并设有分公司的每个节点无限数量的infinitary树一元树

The following examples demonstrate that all implementations of unfoldForestM_BF run actions in breadth first order and that runIdentity . unfoldTreeM_BF (Identity . f) has the same strictness as unfoldTree for trees with finite branching factor. For trees with inifinite branching factor, only the solution for "large" branching factors has the same strictness as unfoldTree. To demonstrate laziness we'll define three infinite trees - a unary tree with one branch, a binary tree with two branches, and an infinitary tree with an infinite number of branches for each node.

mkUnary :: Int -> (Int, [Int])
mkUnary x = (x, [x+1])

mkBinary :: Int -> (Int, [Int])
mkBinary x = (x, [x+1,x+2])

mkInfinitary :: Int -> (Int, [Int])
mkInfinitary x = (x, [x+1..])

连同 unfoldTree ,我们将定义 unfoldTreeDF unfoldTreeM 检查 unfoldTreeM 真的是懒惰像你声称和 unfoldTreeBF unfoldTreeMFix_BF 来检查新的实现是一样懒惰。

Together with unfoldTree, we will define unfoldTreeDF in terms of unfoldTreeM to check that unfoldTreeM really is lazy like you claimed and unfoldTreeBF in terms of unfoldTreeMFix_BF to check that the new implementation is just as lazy.

import Data.Functor.Identity

unfoldTreeDF f = runIdentity . unfoldTreeM    (Identity . f)
unfoldTreeBF f = runIdentity . unfoldTreeM_BF (Identity . f)

要获得有限的部分,这些无限的树木,甚至是无限的分支之一,我们将定义一个方法,采取从树上只要其标签匹配predicate。这可以在一个函数适用于所有的能力方面更简洁地写成 subForest

To get finite pieces of these infinite trees, even the infinitely branching one, we'll define a way to take from a tree as long as its labels match a predicate. This could be written more succinctly in terms of the ability to apply a function to every subForest.

takeWhileTree :: (a -> Bool) -> Tree a -> Tree a
takeWhileTree p (Node label branches) = Node label (takeWhileForest p branches)

takeWhileForest :: (a -> Bool) -> [Tree a] -> [Tree a]
takeWhileForest p = map (takeWhileTree p) . takeWhile (p . rootLabel)

这可以让我们定义9个示例树。

This lets us define nine example trees.

unary   = takeWhileTree (<= 3) (unfoldTree   mkUnary 0)
unaryDF = takeWhileTree (<= 3) (unfoldTreeDF mkUnary 0)
unaryBF = takeWhileTree (<= 3) (unfoldTreeBF mkUnary 0)

binary   = takeWhileTree (<= 3) (unfoldTree   mkBinary 0)
binaryDF = takeWhileTree (<= 3) (unfoldTreeDF mkBinary 0)
binaryBF = takeWhileTree (<= 3) (unfoldTreeBF mkBinary 0)

infinitary   = takeWhileTree (<= 3) (unfoldTree   mkInfinitary 0)
infinitaryDF = takeWhileTree (<= 3) (unfoldTreeDF mkInfinitary 0)
infinitaryBF = takeWhileTree (<= 3) (unfoldTreeBF mkInfinitary 0)

所有五种方法都有相同的输出为一元和二元树。输出来自 putStrLn。 drawTree。 FMAP秀

0
|
`- 1
   |
   `- 2
      |
      `- 3

0
|
+- 1
|  |
|  +- 2
|  |  |
|  |  `- 3
|  |
|  `- 3
|
`- 2
   |
   `- 3

然而,从有限分支因子溶液的广度优先遍历不够懒惰为具有无限分支因子的树。其他四种方法输出整个树

However, the breadth first traversal from the finite branching factor solution is not sufficiently lazy for a tree with an infinite branching factor. The other four methods output the entire tree

0
|
+- 1
|  |
|  +- 2
|  |  |
|  |  `- 3
|  |
|  `- 3
|
+- 2
|  |
|  `- 3
|
`- 3

unfoldTreeBF 产生了有限的分支因子溶液中的树永远不能被完全拉过去它的第一个分支机构。

The tree generated with unfoldTreeBF for the finite branching factor solution can never be completely drawn past its first branches.

0
|
+- 1
|  |
|  +- 2
|  |  |
|  |  `- 3
|  |
|  `- 3

建设肯定是先广度。

The construction is definitely breadth first.

mkDepths :: Int -> IO (Int, [Int])
mkDepths d = do
    print d
    return (d, [d+1, d+1])

mkFiltered :: (Monad m) => (b -> Bool) -> (b -> m (a, [b])) -> (b -> m (a, [b]))
mkFiltered p f x = do
    (a, bs) <- f x
    return (a, filter p bs)

binaryDepths = unfoldTreeM_BF (mkFiltered (<= 2) mkDepths) 0

运行 binaryDepths 之前,内部的输出外周水平

Running binaryDepths outputs the outer levels before the inner ones

0
1
1
2
2
2
2

从懒得彻头彻尾的懒惰

从前面的部分的混合解决方案是不够的懒惰有同样严格的语义 Data.Tree unfoldTree 。它是第一个在一系列的算法,比他们的predecessor每个稍微懒,但没有足够的懒惰,具有相同的严格的语义 unfoldTree

From Lazy to Downright Slothful

The hybrid solution from the earlier section is not lazy enough to have the same strictness semantics as Data.Tree's unfoldTree. It is the first in a series of algorithms, each slightly lazier than their predecessor, but none lazy enough to have the same strictness semantics as unfoldTree.

的混合溶液不提供保证探索树部分不要求探索相同的树的其它部分。 也将在code presented以下。在一个特定但常见的情况<一href="http://stackoverflow.com/questions/27748526/is-a-lazy-breadth-first-monadic-rose-tree-unfold-possible/27752984#comment43961729_27752984">identified通过dfeuer 探索只是一个日志(N)尺寸有限的树片迫使树的全部内容。出现这种情况与探索不断深入树的每个分支的最后后裔时。当COM pressing树,我们抛出了每一个平凡的分支没有后代,这是必要的,以避免为O(n ^ 2)运行时间。我们只能懒洋洋地跳过的COM pression这一部分,如果我们能够很快证明一个分支至少有一个后代,因此,我们可以拒绝模式免费[] 。在恒定的深度树的最大深度,没有任何分支机构有任何剩余的后代,所以也不可能跳过的COM pression的一个步骤。这导致在探索整个树才能够访问的最后节点。当整个树的深度非限定由于无限的分支因子,探索树的部分发生故障,终止时,将终止由 unfoldTree 时产生的。

The hybrid solution does not provide a guarantee that exploring a portion of a tree doesn't demand exploring other portions of the same tree. Nor will the code presented below. In one particular yet common case identified by dfeuer exploring only a log(N) sized slice of a finite tree forces the entirety of the tree. This happens when exploring the last descendant of each branch of a tree with constant depth. When compressing the tree we throw out every trivial branch with no descendants, which is necessary to avoid O(n^2) running time. We can only lazily skip over this portion of compression if we can quickly show that a branch has at least one descendant and we can therefore reject the pattern Free []. At the greatest depth of the tree with constant depth, none of the branches have any remaining descendants, so we can never skip a step of the compression. This results in exploring the entire tree to be able to visit the very last node. When the entire tree to that depth is non-finite due to infinite branching factor, exploring a portion of the tree fails to terminate when it would terminate when generated by unfoldTree.

在混合溶液部分COM $ P $的玉米pression步骤psses远分支与在第一代,它们可被发现,这是最佳的玉米pression但不是最佳的懒惰没有后代。我们可以通过在该COM pression发生延迟使算法懒惰。如果我们拖延它由一个单一的代(代甚至任何常数),我们将保持 O(N)上限的时间。如果我们拖延它由若干代人,不知怎的,依赖于 N 我们必然会牺牲 O(N)时间界。在本节中,我们将通过一个单一的一代耽误COM pression。

The compression step in the hybrid solution section compresses away branches with no descendants in the first generation that they can be discovered in, which is optimal for compression but not optimal for laziness. We can make the algorithm lazier by delaying when this compression occurs. If we delay it by a single generation (or even any constant number of generations) we will maintain the O(n) upper bound on time. If we delay it by a number of generations that somehow depends on N we would necessarily sacrifice the O(N) time bound. In this section we will delay the compression by a single generation.

要控制如何COM pression发生,我们将单独馅最里面的 [] 免费[] 从COM $ P $结构pssing走退化枝0或1的后裔。

To control how compression happens, we will separate stuffing the innermost [] into the Free [] structure from compressing away degenerate branches with 0 or 1 descendants.

由于这一招的一部分,并不没有很多懒惰的COM pression工作,我们会采取过分懒惰懒惰的偏执水平随处可见。如果对结果不是元组构造其他任何(,)可以在不迫使其输入的一部分与模式匹配,我们将避免强迫它,直到它是必要的决定。对于元组,对它们的任何模式匹配会这么懒洋洋地做。因此,一些code以下的样子核心甚至更糟。

Because part of this trick doesn't work without a lot of laziness in the compression, we will adopt a paranoid level of excessively slothful laziness everywhere. If anything about a result other than the tuple constructor (,) could be determined without forcing part of its input with a pattern match we will avoid forcing it until it is necessary. For tuples, anything pattern matching on them will do so lazily. Consequently, some of the code below will look like core or worse.

bindFreeInvertible 替换纯[B,...] 免费[纯B ,...]

bindFreeInvertible :: Free [] ([] b) -> (Free [] b, Free [] a -> Free [] ([] a))
bindFreeInvertible = wrapFree . go
    where
        -- wrapFree adds the {- Free -} that would have been added in both branches
        wrapFree ~(xs, dxs) = (Free xs, dxs)
        go (Pure xs) = ({- Free -} (map Pure xs), Pure . map getPure . getFree)
        go (Free xs) = wrapList . rebuildList . map bindFreeInvertible $ xs
        rebuildList = foldr k ([], const [])
        k ~(x,dx) ~(xs, dxs) = (x:xs, \(~(x:xs)) -> dx x:dxs xs)
        wrapList ~(xs, dxs) = ({- Free -} xs, \(~(Free xs)) -> Free (dxs xs)))

COM pressFreeList 删除事件免费[] 和替换免费[ XS] XS

compressFreeList removes occurrences of Free [] and replaces Free [xs] with xs.

compressFreeList :: Free [] b -> (Free [] b, Free [] a -> Free [] a)
compressFreeList (Pure x) = (Pure x, id)
compressFreeList (Free xs) = wrapList . compressList . map compressFreeList $ xs
    where
        compressList = foldr k ([], const [])
        k ~(x,dx) ~(xs', dxs) = (x', dxs')
            where
                x' = case x of
                        Free []   -> xs'
                        otherwise -> x:xs'
                dxs' cxs = dx x'':dxs xs''
                    where
                        x'' = case x of
                            Free []   -> Free []
                            otherwise -> head cxs
                        xs'' = case x of
                            Free []   -> cxs
                            otherwise -> tail cxs
        wrapList ~(xs, dxs) = (xs', dxs')
            where
                xs' = case xs of
                        [x]       -> x
                        otherwise -> Free xs
                dxs' cxs = Free (dxs xs'')
                    where
                        xs'' = case xs of
                            [x]       -> [cxs]
                            otherwise -> getFree cxs

整体融为一体pression将不绑定纯[] s转换免费取值后才简免费取值已经融为一体pressed远,贻误COM $ P $退化的pssion 免费 S在介绍一代到下一代的COM pression。

The overall compression will not bind the Pure []s into Frees until after the degenerate Frees have been compressed away, delaying compression of degenerate Frees introduced in one generation to the next generation's compression.

compress :: Free [] [b] -> (Free [] b, Free [] a -> Free [] [a])
compress xs = let ~(xs' , dxs' ) = compressFreeList xs
                  ~(xs'', dxs'') = bindFreeInvertible xs'
                  in (xs'', dxs' . dxs'')

走出持续的偏执,佣工 getFree getPure 也取得了无可辩驳地懒。

Out of continued paranoia, the helpers getFree and getPure are also made irrefutably lazy.

getFree ~(Free xs) = xs
getPure ~(Pure x)  = x

这非常迅速解决发现的问题的例子dfeuer

This very quickly solves the problematic example dfeuer discovered

print . until (null . subForest) (last . subForest) $
    flip unfoldTreeBF 0 (\x -> (x, if x > 5 then [] else replicate 10 (x+1)))

不过,由于我们只是推迟了COM pression由 1 的产生,我们可以重新创建完全相同的问题,如果最后分支的最后节点是 1 水平比所有其他分支的更深。

But since we only delayed the compression by 1 generation, we can recreate exactly the same problem if the very last node of the very last branch is 1 level deeper than all of the other branches.

print . until (null . subForest) (last . subForest) $
    flip unfoldTreeBF (0,0) (\(x,y) -> ((x,y), 
        if x==y
        then if x>5 then [] else replicate 9 (x+1, y) ++ [(x+1, y+1)]
        else if x>4 then [] else replicate 10 (x+1, y)))

这篇关于是个懒人,广度优先单子玫瑰树展开可能吗?的文章就介绍到这了,希望我们推荐的答案对大家有所帮助,也希望大家多多支持IT屋!

查看全文
登录 关闭
扫码关注1秒登录
发送“验证码”获取 | 15天全站免登陆