Why are difference lists not an instance of foldable?

僤鯓⒐⒋嵵緔 提交于 2019-11-30 16:55:19

问题


The dlist package contains the DList data type, which has lots of instances, but not Foldable or Traversable. In my mind, these are two of the most "list-like" type classes. Is there a performance reason that DList is not an instance of these classes?

Also, the package does implement foldr and unfoldr, but none of the other folding functions.


回答1:


DList a is a newtype wrapper around [a] -> [a], which has an a in a contravariant position, so it cannot implement Foldable or Traversable, or even Functor directly. The only way to implement them is to convert to and from regular lists (see the foldr implementation), which defeats the performance advantage of difference lists.




回答2:


One alternative you should consider instead of DList is to use Church-encoded lists. The idea is that you represent a list as an opaque value that knows how to execute a foldr over a list. This requires using the RankNTypes extension:

{-# LANGUAGE RankNTypes #-}

import Prelude 
import Control.Applicative
import Data.Foldable (Foldable)
import qualified Data.Foldable as F
import Data.Traversable (Traversable)
import qualified Data.Traversable as T

-- | Laws:
--
-- > runList xs cons nil == xs
-- > runList (fromList xs) f z == foldr f z xs
-- > foldr f z (toList xs) == runList xs f z
newtype ChurchList a = 
    ChurchList { runList :: forall r. (a -> r -> r) -> r -> r }

-- | Make a 'ChurchList' out of a regular list.
fromList :: [a] -> ChurchList a
fromList xs = ChurchList $ \k z -> foldr k z xs

-- | Turn a 'ChurchList' into a regular list.
toList :: ChurchList a -> [a]
toList xs = runList xs (:) []

-- | We can construct an empty 'ChurchList' without using a @[]@.
nil :: ChurchList a 
nil = ChurchList $ \_ z -> z

-- | The 'ChurchList' counterpart to '(:)'.  Unlike 'DList', whose
-- implementation uses the regular list type, 'ChurchList' doesn't
-- rely on it at all.
cons :: a -> ChurchList a -> ChurchList a
cons x xs = ChurchList $ \k z -> k x (runList xs k z)

-- | Append two 'ChurchList's.  This runs in O(1) time.  Note that
-- there is no need to materialize the lists as @[a]@.
append :: ChurchList a -> ChurchList a -> ChurchList a
append xs ys = ChurchList $ \k z -> runList xs k (runList ys k z)

-- | Map over a 'ChurchList'.  No need to materialize the list.
instance Functor ChurchList where
    fmap f xs = ChurchList $ \k z -> runList xs (\x xs' -> k (f x) xs') z

-- | The 'Foldable' instance is trivial, given the 'ChurchList' law.
instance Foldable ChurchList where
    foldr f z xs = runList xs f z

instance Traversable ChurchList where
    traverse f xs = runList xs step (pure nil)
        where step x rest = cons <$> f x <*> rest

The downside to this is that there is no efficient tail operation for a ChurchList—folding a ChurchList is cheap, but taking repeated tails is costly...



来源:https://stackoverflow.com/questions/15589556/why-are-difference-lists-not-an-instance-of-foldable

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!