[Haskell-cafe] Re: Looking for practical examples of Zippers

Ryan Ingram ryani.spam at gmail.com
Tue Mar 31 05:51:17 EDT 2009


Perhaps an example will help.

Here's a useful operation on lists:

> grab :: [a] -> [(a, [a])]
> grab [] = []
> grab (x:xs) = (x, xs) : [ (y, x : ys) | (y,ys) <- grab xs ]

This takes a list and gives you a new list with one element extracted
from the original list:

ghci> grab [1,2,3,4]
[(1,[2,3,4]),(2,[1,3,4]),(3,[1,2,4]),(4,[1,2,3])]

One problem with this operation is that it has no *context*; you've
lost all the information about where the item came from in the
original list, so if you want to put it back, or do anything else with
that information, you can't.

A zipper is one way to solve this problem.  (The other usual way is
(zip [0..] xs) to add indices to each element, but I find that less
elegant; it feels ugly and error prone)

Using Data.List.Zipper from the ListZipper package[1], we can keep
that information around:

> import qualified Data.List.Zipper as Z
>
> select :: [a] -> [(a, Z.Zipper a)]
> select = select' . Z.fromList where
>    select' z
>        | Z.endp z = []
>        | otherwise = (Z.cursor z, Z.delete z) : select' (Z.right z)

Now, the result of "select" remembers where in the list the element came from:

ghci> select [1,2,3,4]
[(1,Zip [] [2,3,4]),(2,Zip [1] [3,4]),(3,Zip [2,1] [4]),(4,Zip [3,2,1] [])]

This is extremely useful if you want to modify an element of the list
and put it back in place; you use select to split up the list into
elements, examine each one in turn to see if it's the one you care
about, and then, when you find the right one, modify it and
reconstruct the list (using Z.insert and Z.toList)

I recommend checking out the source code for Data.List.Zipper, it's
quite simple.

The same idea can be used for most any data structure; you have a
"history" part of the zipper which remembers where you've been, and
the data you passed by, and a "future" part of the zipper which stores
where you can go.  For example:

> data BinTree a = Tip | Node a (BinTree a) (BinTree a)
> data BinTreeZipper a = BTZip (Path a) (BinTree a)
> data Path a = Head | Left a (BinTree a) (Path a) | Right a (BinTree a) (Path a)

> fromTree :: BinTree a -> BinTreeZipper a
> fromTree = BTZip Head

You then can move around and modify the tree with O(1) operations much
like you would in an imperative language by traversing pointers:

> type BTZ = BinTreeZipper

> update x (BTZip p (Node _ l r)) = BTZip p (Node x l r)
> update _ z = z

> right (BTZip p (Node x l r)) = BTZip (Right x l p) r
> right z = z
> left (BTZip p (Node x l r) = BTZip (Left x r p) l
> left z = z
> up (BTZip (Left x r p) l) = BTZip p (Node x l r)
> up (BTZip (Right x l p) r) = BTZip p (Node x l r)
> up z = z

And convert back to a regular tree:

> toTree :: BTZ a -> BinTree a
> toTree (BTZ Head t) = t
> toTree z = toTree (up z)

However, this structure has a big advantages over imperative
traversal: it's pure and persistent.  If you want to revert back to an
old version of the tree, just keep that zipper around!  If someone
doing work in another thread has access to the tree, you don't have to
worry about them racing to update; neither of you are changing the
tree itself, but instead building new data that shares structure where
possible.

[1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ListZipper

On Tue, Mar 31, 2009 at 12:46 AM, Cristiano Paris
<cristiano.paris at gmail.com> wrote:
> On Mon, Mar 30, 2009 at 9:46 PM, Gü?nther Schmidt <gue.schmidt at web.de> wrote:
>> Thanks Don,
>>
>> I followed some examples but have not yet seen anything that would show me
>> how, for instance, turn a nested Map like
>>
>> Map Int (Map Int (Map String Double)
>>
>> into a "zipped" version.
>>
>> That is presuming of course that this use is feasible at all.
>
> Hi Günther,
>
> a couple of weeks ago I was looking into Zippers my self as well.
> After reading all the documents mentioned in the other messages, I
> decided to go for my implementation as the proposed ones seemed to me
> unnecessarily complicated. You can see the discussion here:
>
> http://www.haskell.org/pipermail/haskell-cafe/2009-March/056942.html
>
> I have to thank Heinrich Apfelmus and Ryan Ingram because they pointed
> out a major flaw in my implementation and so I got Zippers and why
> they are implemented as such.
>
> What I've learned: Zippers are "structured collections[1] with a
> focus". Through a Zipper you can O(1) change the value of the focused
> element: that's the fundamental property. In addition, you can change
> the focus through a series of "moving" functions. Regarding their
> implementation, it's important to understand that the moving functions
> must be "aware" of the changes you made to the focused element. This
> is carried out by having the moving functions rebuild the context of
> the new focused element starting from the current focus' context.
>
> On the contrary, my implementation relied on laziness and partial
> application but lacked the "awareness" of the changes. If you can
> catch this difference, it's easy to grasp the Zipper/Delimited
> Continuation link and the statement "a zipper is a delimited
> continuation reified to data".
>
> Sorry for my explanation using elementary terms: I'm no computer
> science theorist ;)
>
> Hope this helped.
>
> Cristiano
>
> [1] By structured collection I mean lists, trees, graphs and so on.
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list