Looking for practical examples of Zippers

Hi, my quest for data structures continues. Lately I came across "Zippers". Can anybody point be to some useful examples? Günther

xmonad's state is represented as a zipper on nested lists. The wikipedia article on zippers lists this and other examples. gue.schmidt:
Hi,
my quest for data structures continues. Lately I came across "Zippers".
Can anybody point be to some useful examples?
Günther
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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. Günther Don Stewart schrieb:
xmonad's state is represented as a zipper on nested lists.
The wikipedia article on zippers lists this and other examples.
gue.schmidt:
Hi,
my quest for data structures continues. Lately I came across "Zippers".
Can anybody point be to some useful examples?
Günther
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, Mar 30, 2009 at 9:46 PM, Gü?nther Schmidt
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.

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
On Mon, Mar 30, 2009 at 9:46 PM, Gü?nther Schmidt
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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.
To clarify: there is no magic that turns a data structure into O(1) access, just as a CPS transformation is not a magic bullet for speeding up programs. Only the move functions (changing focus to some subset of "adjacent" substructures) are O(1). Update functions need not be O(1). And amortized random access time via a zipper is never less than amortized random access of the optimal equivalent un-zippered data structure. Zippers are most effective when a structure is accessed by some quasicontinuous path through it. Fortunately, this happens quite a lot, although laziness does obviate the need for a zipper in many of these cases. Dan Cristiano Paris wrote:
On Mon, Mar 30, 2009 at 9:46 PM, Gü?nther Schmidt
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tue, Mar 31, 2009 at 10:13 PM, Dan Weston
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.
To clarify: there is no magic that turns a data structure into O(1) access, just as a CPS transformation is not a magic bullet for speeding up programs. Only the move functions (changing focus to some subset of "adjacent" substructures) are O(1). Update functions need not be O(1). And amortized random access time via a zipper is never less than amortized random access of the optimal equivalent un-zippered data structure.
That's true. But, correct me if I'm wrong, updates on the focus site are O(1). Cristiano

Cristiano Paris wrote:
On Tue, Mar 31, 2009 at 10:13 PM, Dan Weston
wrote: 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.
To clarify: there is no magic that turns a data structure into O(1) access, just as a CPS transformation is not a magic bullet for speeding up programs. Only the move functions (changing focus to some subset of "adjacent" substructures) are O(1). Update functions need not be O(1). And amortized random access time via a zipper is never less than amortized random access of the optimal equivalent un-zippered data structure.
That's true. But, correct me if I'm wrong, updates on the focus site are O(1).
Yes. It's just that shifting the focus to the site from scratch does not take constant time, obviously. Regards, apfelmus -- http://apfelmus.nfshost.com

Gü?nther Schmidt 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.
You can't. Or rather, you can't unless you have access to the implementation of the datastructure itself; and Data.Map doesn't provide enough details to do it. One of the problems with trying to make a zipper for Data.Map is that it maintains a number of invariants on structure which would be tricky to fix up if someone changes things at the focused point. (Not impossible, but certainly tricky.) Another tricky thing for this particular example is answering the question of what you want to call the "focus". Usually zippered datastructures are functors, so given F X we can pick one X to be the focus and then unzip the F around it. You can treat Map X Y as a functor (Map X) applied to Y. Here we'd get a zipper of (Map X) with amortized access time to the other Ys at neighboring Xs, which is nice but maybe not worth the overhead since we already have O(log n) access from the root. But (Map X) Y misses half the point of Map: we can't change the Xs. We'd prefer something like Map as a functor on (X,Y), but if we took (X,Y) as the focus, then what should happen if someone changes the X? Changing X changes our position in the unzipped Map X Y, so we'd have to do some tricky things in order to refocus and maintain the balancing invariants of Map. Which is to say that Map isn't really a functor on (X,Y) so we can't rely on the structural properties of functors like we're used to when making zippers. -- Live well, ~wren

On Tue, Mar 31, 2009 at 11:44 PM, wren ng thornton
Another tricky thing for this particular example is answering the question of what you want to call the "focus". Usually zippered datastructures are functors, so given F X we can pick one X to be the focus and then unzip the F around it.
The functor part isn't important. You can make a zipper from any
recursive structure.
data Expr = Var String | Lit Int | App Expr Expr | Abs String Expr
data ExprCtx = AppC1 Expr | AppC2 Expr | AbsC String
data ExprZ = ExprZ { ctx :: [ExprCtx], focus :: Expr }
In general, if I have a type T and functors F and F' such that T is
isomorphic to F T and F' is the derivative of F, then ([F' T], T) is a
zipper for T.
--
Dave Menendez

David Menendez wrote:
On Tue, Mar 31, 2009 at 11:44 PM, wren ng thornton
wrote: Another tricky thing for this particular example is answering the question of what you want to call the "focus". Usually zippered datastructures are functors, so given F X we can pick one X to be the focus and then unzip the F around it.
The functor part isn't important. You can make a zipper from any recursive structure.
This seems at odds with the below
In general, if I have a type T and functors F and F' such that T is isomorphic to F T and F' is the derivative of F, then ([F' T], T) is a zipper for T.
Right, for any equi-recursive type we can rewrite it as an iso-recursive type (Fix F ~ F (Fix F)) and the rest follows. But the F we feed into the fixed-point is a functor, otherwise Fix isn't going to like it; which goes against the claim that functorness isn't important. I didn't mean that T itself needs to be a functor, only that most often T = Fix F for some F, and the functorness of F is the helpful bit. Perhaps I was unclear. Of course, if T _is_ a functor then we can take the derivative of T instead, which may be sufficient for the task; I'd still call this a zipper. (The derivative of F is implicit here, but it can be hidden which is good for abstract types.) The point I was making, though, is that the abstract type "Map" is in fact smaller than the recursive type defined by the ADT we use to model it. For the type defined only by the ADT: convert to iso-recursion, take the derivative, and voila. But for the abstract type the ADT approximates, it's not as easy. -- Live well, ~wren

On Mon, Mar 30, 2009 at 3:46 PM, Gü?nther Schmidt
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.
Are you asking about the technique for navigating recursive
structures, or did you mean something having to do with the
isomorphism between "Map Int (Map Int (Map String Double))" and "Map
(Int,Int,String) Double"?
For the latter, the term you want is "generalized trie".
--
Dave Menendez

David, guys, sorry, this all started with a misconception on my behalf of what a Zipper is and what it is good for. In the days that followed my post this became much clearer though and I now realize my original question was pointless. It seems you spotted that and yes, "generalized trie" is probably more what I'm looking for, thanks! Günther David Menendez schrieb:
On Mon, Mar 30, 2009 at 3:46 PM, Gü?nther Schmidt
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.
Are you asking about the technique for navigating recursive structures, or did you mean something having to do with the isomorphism between "Map Int (Map Int (Map String Double))" and "Map (Int,Int,String) Double"?
For the latter, the term you want is "generalized trie".

On Mon, 30 Mar 2009 21:21:14 +0200, Gü?nther Schmidt
Hi,
my quest for data structures continues. Lately I came across "Zippers".
Can anybody point be to some useful examples?
Günther
Searching for "Haskell ziper" leads to the following pages: http://en.wikibooks.org/wiki/Haskell/Zippers http://www.haskell.org/haskellwiki/Zipper (not as readable as the previous one) http://hackage.haskell.org/cgi-bin/hackage-scripts/package/zipper (a zipper package) http://donsbot.wordpress.com/2007/05/ (how zippers are used in xmonad) -- Met vriendelijke groet, Henk-Jan van Tuyl -- http://functor.bamikanarie.com http://Van.Tuyl.eu/ --

G'day all.
Quoting Gü?nther Schmidt
my quest for data structures continues. Lately I came across "Zippers".
Can anybody point be to some useful examples?
This is a good example, currently in use in GHC: http://www.cs.tufts.edu/~nr/pubs/zipcfg-abstract.html Cheers, Andrew Bromage

my quest for data structures continues. Lately I came across "Zippers". Can anybody point be to some useful examples?
Once upon a time, there was a hardware implementation of a lambda calculus based functional language (mostly, I was told, to show that it could be done:-). The program representation was a string of symbols (graph reduction came later; implementation of graph reduction on stock hardware came much later) in a constructor syntax (think fully applied data constructors in Haskell, each constructor annotated with its arity). The problem: if you were to do beta-reductions somewhere in the middle of such a string, you'd have to make space or fill gaps, to adjust for the differing lengths of redex and reduced, not to mention the issue of finding and identifying the redices in the first place. Working in hardware, you couldn't quite ignore those details. The solution: use a hardware zipper representation, consisting of a system of 3 main stacks (there were auxiliary stacks to handle things like substitution), often likened to a railway shunting yard: output|_|input c o n t r o l To traverse a program expression: - the program starts on the input stack, in pre-order form (the constructors before their arguments). - take a constructor from the front of the input stack, put it on the control stack, initialising a counter for the arguments. - while there are still arguments left, recursively traverse them from input to output stack, decrementing the constructor count. - after all parameters of the constructor on top of the control stack have been traversed to the output stack, move the constructor to the output stack - the program ends up on the output stack, in post-order form (the constructors after their arguments, though still on top of them, stack-wise). That way, all sub-expressions would, at some point of the traversal, appear on the top of the three stacks, so if there was a redex on top (application constructor on control, function on one stack, argument on the other stack), the processor could replace the redex by a reduced expression without having to make room or fill gaps, or look anywhere but at the top of the stacks. There was even a special graphical notation, to specify the elaborate mix of control- and data-flow going on, but at the heart of it all was that traversal scheme over a shunting yard of stacks, based on a zipper in hardware. Claus
participants (12)
-
ajb@spamcop.net
-
Claus Reinke
-
Cristiano Paris
-
Dan Weston
-
David Menendez
-
Don Stewart
-
Gü?nther Schmidt
-
Günther Schmidt
-
Heinrich Apfelmus
-
Henk-Jan van Tuyl
-
Ryan Ingram
-
wren ng thornton