教堂编码清单更有效率的尾巴 [英] More efficient tail of church encoded list

查看:172
本文介绍了教堂编码清单更有效率的尾巴的处理方法,对大家解决问题具有一定的参考价值,需要的朋友们下面随着小编来一起学习吧!

问题描述

这是一个有识字的haskell文章。只需将其保存为ChurchList.lhs即可运行它。

 > { - #LANGUAGE Rank2Types# - } 

Church编码列表是一种通过功能。它类似于折叠和延续传球的风格。

 > newtype ChurchList a = CList {runCList :: forall r。 (a→r→r)→> r  - > r} 

为了说明这如何对应一个列表,下面是一个O(n)同构

 > fromList :: [a]  - > ChurchList a 
> fromList xs = CList $ \cons empty - > foldr缺货xs

> toList :: ChurchList a - > [a]
> toList cl = runCList cl(:) []

>实例Show a => Show(ChurchList a)其中
> show cl =fromList++ show(toList cl)

这些东西具有良好的性能特征。 / p>

 > singleton :: a  - > ChurchList a  -  O(1)
> singleton a = CList $ \cons empty - > 'cons'空
> append :: ChurchList a - > ChurchList a - > ChurchList a - O(1)!!!这也意味着cons和snoc是O(1)
> append cl1 cl2 = CList $ \cons empty - > runCList cl1 cons(runCList cl2 cons empty)
> concatCl :: ChurchList(ChurchList a) - > ChurchList a - O(n)
> concatCl clcl = CList $ \cons empty - > runCList clcl(\cl r - > runCList cl cons r)empty
> headCl :: ChurchList a - >也许一个 - O(1)
> headCl cl = runCList cl(\a_ - >只是)没有

现在,问题附带尾巴

 > tailClbad :: ChurchList a  - >也许(ChurchList a)--O(n)?!! 
> tailClbad cl =(fmap snd)$ runCList cl
>
> (\ar->> Just(a,case b of
> Nothing - > CList $ \cons empty - > empty
> Just(s,t) - > append (单身s)t)) - 收入
>
> Nothing --Empty

基本上我的实现是将列表分割为头部和尾部。 Cons取代头部,并将旧头部追加到尾部。这是相当低效的。
看起来教堂名单在分裂方面一般效率低下。


我希望我错了。是否存在 tailCl 的实现比O(n)(最好是O(1))要好。

解决方案

论文 数据类型的教会编码被认为对实现有害 Koopman,Plasmeijer和Jansen似乎正在处理这个问题。特别是,引用摘要(我强调):


[...]



我们证明在Church的编码选择器中,构造函数
产生递归类型,就像列表的 tail 一样,在数据的脊柱中有一个不理想的
严格性结构体。 Scott编码
不会妨碍懒惰评估。 由Church编码对
递归脊椎的评估使
这些析构函数的复杂性 O(n)中的相同析构函数>斯科特编码
只需要一定的时间
。此外,教会编码在图减少方面存在
严重问题。 Parigot编码结合了两个世界中最好的
,但实际上这并不能提供
的优势。

然而,虽然斯科特编码提供了性能优势,它似乎是有问题在System F中定义它而不添加递归类型。


This is a literate haskell post. Simply save it as "ChurchList.lhs" to run it.

> {-# LANGUAGE Rank2Types #-}

A Church encoded list is a way of representing a list via a function. It resembles both folding and continuation passing style.

> newtype ChurchList a = CList {runCList :: forall r. (a -> r -> r) -> r -> r}

For illustration as to how this corresponds to a list, here is a O(n) isomorphism

> fromList :: [a] -> ChurchList a
> fromList xs = CList $ \cons empty -> foldr cons empty xs

> toList :: ChurchList a -> [a]
> toList cl = runCList cl (:) []

> instance Show a => Show (ChurchList a) where
>   show cl = "fromList " ++ show (toList cl)

These things have good performance charecteristics.

> singleton :: a -> ChurchList a -- O(1)
> singleton a = CList $ \cons empty -> a `cons` empty
> append :: ChurchList a -> ChurchList a -> ChurchList a -- O(1)!!! This also means cons and snoc are O(1)
> append cl1 cl2 = CList $ \cons empty -> runCList cl1 cons (runCList cl2 cons empty)
> concatCl :: ChurchList (ChurchList a) -> ChurchList a -- O(n)
> concatCl clcl = CList $ \cons empty -> runCList clcl (\cl r -> runCList cl cons r) empty
> headCl :: ChurchList a -> Maybe a -- O(1)
> headCl cl = runCList cl (\a _ -> Just a) Nothing

Now, the problem comes with tail.

> tailClbad :: ChurchList a -> Maybe (ChurchList a) --O(n)?!!
> tailClbad cl = (fmap snd) $ runCList cl
>
>    (\a r -> Just (a, case r of
>    Nothing -> CList $ \cons empty -> empty
>    Just (s,t) -> append (singleton s) t)) --Cons
>
>    Nothing --Empty

Essentially what my implementation does is split the list into head and tail. Cons replaces the head, and appends the old head unto the tail. This is rather inefficient. It seems that Church Lists are inefficient in general at splitting.

I'm hoping that I'm wrong. Is there an implementation of tailCl that is better than O(n) (preferably O(1)).

解决方案

Paper Church Encoding of Data Types Considered Harmful for Implementations by Koopman, Plasmeijer and Jansen seems to deal with the issue in detail. In particular, quoting the abstract (my emphasis):

[...]

We show that in the Church encoding selectors of constructors yielding the recursive type, like the tail of a list, have an undesirable strictness in the spine of the data structure. The Scott encoding does not hamper lazy evaluation in any way. The evaluation of the recursive spine by the Church encoding makes the complexity of these destructors O(n). The same destructors in the Scott encoding requires only constant time. Moreover, the Church encoding has serious problems with graph reduction. The Parigot encoding combines the best of both worlds, but in practice this does not offer an advantage.

However, while Scott encoding provides the performance advantage, it appears to be problematic to define it in System F without adding recursive types.

这篇关于教堂编码清单更有效率的尾巴的文章就介绍到这了,希望我们推荐的答案对大家有所帮助,也希望大家多多支持IT屋!

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