Difference between revisions of "Zipper"

From HaskellWiki
Jump to navigation Jump to search
(un-camel case)
m (zippers package)
(67 intermediate revisions by 15 users not shown)
Line 1: Line 1:
The Zipper is an idiom that uses the idea of "context" to the means of
+
The Zipper is an idiom that uses the idea of “context” to the means of
 
manipulating locations in a data structure. [[Zipper monad]] is a monad
 
manipulating locations in a data structure. [[Zipper monad]] is a monad
 
which implements the zipper for binary trees.
 
which implements the zipper for binary trees.
  +
  +
__TOC__
   
 
Sometimes you want to manipulate a ''location'' inside a data structure,
 
Sometimes you want to manipulate a ''location'' inside a data structure,
Line 11: Line 13:
   
 
and a sample tree t:
 
and a sample tree t:
  +
{|
 
<haskell>
+
| <haskell>
 
t = Fork (Fork (Leaf 1)
 
t = Fork (Fork (Leaf 1)
 
(Leaf 2))
 
(Leaf 2))
Line 18: Line 20:
 
(Leaf 4))
 
(Leaf 4))
 
</haskell>
 
</haskell>
  +
| [[Image:Tree-12-34.png]]
 
  +
|}
 
Each subtree of this tree occupies a certain location in the tree taken as a whole. The location consists of the subtree, along with the rest of the tree, which we think of the ''context'' of that subtree. For example, the context of
 
Each subtree of this tree occupies a certain location in the tree taken as a whole. The location consists of the subtree, along with the rest of the tree, which we think of the ''context'' of that subtree. For example, the context of
   
Line 27: Line 30:
 
in the above tree is
 
in the above tree is
   
  +
{|
<haskell>
 
  +
| <haskell>
 
Fork (Fork (Leaf 1) @)
 
Fork (Fork (Leaf 1) @)
 
(Fork (Leaf 3) (Leaf 4))
 
(Fork (Leaf 3) (Leaf 4))
 
</haskell>
 
</haskell>
  +
| [[Image:Context-1X-34.png]]
  +
|}
  +
where @ marks a hole: the spot that the subtree appears in. This is the way we shall implement a tree with a focus. One way of expressing this context is as a path from the root of the tree to the hole (to which the required subtree will be attached). To reach our subtree, we needed to go down the left branch, and then down the right one. Note that the context is essentially a way of representing the tree, “missing out” a subtree (the subtree we are interested in).
   
  +
A naive implementation of the context, inspired directly by the graphical representation might be to use <hask>Tree (Maybe a)</hask> instead of <hask>Tree a</hask>. However, this would lose an essential point: in any given context, there is exactly one hole.
where @ marks the spot that the subtree appears in. One way of expressing this context is as a path from the root of the tree to the required subtree. To reach our subtree, we needed to go down the left branch, and then down the right one. Note that the context is essentially a way of representing the tree, "missing out" a subtree (the subtree we are interested in).
 
   
We can represent a context as follows:
+
Therefore, we will represent a context as follows:
   
 
<haskell>
 
<haskell>
Line 40: Line 47:
 
</haskell>
 
</haskell>
   
<code>L c t</code> represents the left part of a branch of which the right part was <code>t</code> and whose parent had context <code>c</code>. The <code>R</code> constructor is similar. <code>Top</code> represents the top of a tree. (Note that in the original paper, Huet dealt with B-trees (ones where nodes have arbitrary numbers of branches), so lists are used instead of the (Tree a) parameters.)
+
<code>L c t</code> represents the left part of a branch of which the right part was <code>t</code> and whose parent had context <code>c</code>. The <code>R</code> constructor is similar. <code>Top</code> represents the top of a tree.
  +
  +
Remarks:
  +
* In fact, this is equivalent to a list, whose elements are the appropriate collateral trees, each element labeled with the information which direction was chosen:
  +
:<hask>type Context a = [(Direction, Tree a)]</hask>
  +
:<hask>data Direction = Lft | Rght</hask>
  +
* We chose to propagate from the hole towards the root. This is an independent idea of the above considerations: it is not the unicity of the hole that forced us to do so. It is simply more efficient if we want to define operations later for a tree with a focus (move focus left, right, up).
  +
* Note that in the original paper, Huet dealt with B-trees (ones where nodes have arbitrary numbers of branches), so at each node, a list is used instead of the two (Tree a) parameters to represent children. Later we shall see that the solution of the problem can be formalized in a general way which covers solutions for both kinds of trees, as special cases.
   
 
Using this datatype, we can rewrite the sample context above in proper Haskell:
 
Using this datatype, we can rewrite the sample context above in proper Haskell:
Line 48: Line 62:
 
</haskell>
 
</haskell>
   
Note that the context is actually written by giving the path from the subtree to the root (rather than the other way round).
+
Note that the context is actually written by giving the path from the subtree to the root (rather than the other way round):
  +
{| border=1
  +
| <math>c_0</math>
  +
| <math>\begin{matrix}\mathrm{R\;(Leaf\;1)}\;\underbrace{\mathrm{(L\;Top\;(Fork\;(Leaf\;3)\;(Leaf\;4)))}}\\\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;c_1\end{matrix}</math>
  +
| [[Image:Context-1X-34.png]]
  +
|-
  +
| <math>c_1</math>
  +
| <math>\begin{matrix}\mathrm{L}\;\underbrace{\mathrm{Top}}\;\mathrm{(Fork\;(Leaf\;3)\;(Leaf\;4))}\\\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!\!c_2\end{matrix}</math>
  +
| [[Image:Context-X-34.png]]
  +
|-
  +
| <math>c_2</math>
  +
| Top
  +
| [[Image:Top.png]]
  +
|}
  +
  +
Or the more deconstructed representation:
  +
{| border=1
  +
| <math>\left[\begin{matrix}\mathrm{(Rght,\;Leaf\;1),\;\underbrace{\mathrm{(Lft,\;Fork\;(Leaf\;3)\;(Leaf\;4))}}}\\\underbrace{\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;c_1\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;\;}\\c_0\end{matrix}\right]</math>
  +
| [[Image:Path-1X-34.png]]
  +
|}
  +
where <math>c_0</math>, <math>c_1</math> are the appropriate correspondents of the <math>c_0</math>, <math>c_1</math> of the previous image. It is the empty list that represents <math>c_2</math>.
   
 
Now we can define a tree location:
 
Now we can define a tree location:
Line 55: Line 89:
 
type Loc a = (Tree a, Cxt a)
 
type Loc a = (Tree a, Cxt a)
 
</haskell>
 
</haskell>
  +
{|
  +
| [[Image:Circum-op12cl-34.png]]
  +
| [[Image:Mount-op12cl-34.png]]
  +
|}
  +
thus, a tree with a focus (drawn here as a tree with a marked subtree) shall be represented as “mounting” the focus (a tree) into the hole of the appropriate context.
   
and some useful functions for manipulating locations in a tree:
+
Now, we can define some useful functions for manipulating locations in a tree:
   
 
<haskell>
 
<haskell>
Line 64: Line 103:
 
right :: Loc a -> Loc a
 
right :: Loc a -> Loc a
 
right (Fork l r, c) = (r, R l c)
 
right (Fork l r, c) = (r, R l c)
  +
  +
top :: Tree a -> Loc a
  +
top t = (t, Top)
   
 
up :: Loc a -> Loc a
 
up :: Loc a -> Loc a
Line 69: Line 111:
 
up (t, R l c) = (Fork l t, c)
 
up (t, R l c) = (Fork l t, c)
   
top :: Tree a -> Loc a
+
upmost :: Loc a -> Loc a
top t = (t, Top)
+
upmost l@(t, Top) = l
  +
upmost l = upmost (up l)
   
 
modify :: Loc a -> (Tree a -> Tree a) -> Loc a
 
modify :: Loc a -> (Tree a -> Tree a) -> Loc a
Line 84: Line 127:
 
</haskell>
 
</haskell>
   
  +
Then to reach the location of <code>Leaf 2</code>:
Then:
 
   
 
<haskell>
 
<haskell>
(left . right . top) t
+
(right . left . top) t
= (left . right) (t, Top)
+
= (right . left) (t, Top)
= left (tr, R tl Top)
+
= right (tl, L Top tr)
= (Leaf 3, L (R tl Top) (Leaf 4))
+
= (Leaf 2, R (Leaf 1) (L Top tr))
  +
</haskell>
  +
  +
To reach that location and replace <code>Leaf 2</code> by <code>Leaf 0</code>:
  +
  +
<haskell>
  +
modify ((right . left . top) t) (\_ -> Leaf 0)
  +
= ...
  +
= (Leaf 0, R (Leaf 1) (L Top tr))
  +
</haskell>
  +
  +
Afterwards some may like to continue walking to other parts of the new tree, in which case continue applying <code>left</code>, <code>right</code>, and <code>up</code>.
  +
  +
Some others may like to retrieve the new tree (and possibly forget about locations), in which case <code>upmost</code> is useful:
  +
  +
<haskell>
  +
(fst . upmost) (modify ((right . left . top) t) (\_ -> Leaf 0))
  +
= (fst . upmost) (Leaf 0, R (Leaf 1) (L Top tr))
  +
= fst (Fork (Fork (Leaf 1)
  +
(Leaf 0))
  +
tr
  +
, Top)
  +
= Fork (Fork (Leaf 1)
  +
(Leaf 0))
  +
tr
 
</haskell>
 
</haskell>
   
 
== Automation ==
 
== Automation ==
There's a principled way to get the necessary types for contexts and the context filling functions, namely by differentiating the data structure. [http://www.cs.nott.ac.uk/~ctm/ Some relevant papers].
 
   
  +
There's a principled way to get the necessary types for contexts and the
For an actual implementation in [[GenericHaskell]], see the paper "[http://www.cs.uu.nl/~johanj/publications/tidata.pdf Type-indexed data types]" by Ralf Hinze, Johan Jeuring and Andres Löh.
 
  +
context filling functions, namely by differentiating the data structure.
  +
[http://www.cs.nott.ac.uk/~ctm/ Some relevant papers].
  +
  +
For an actual implementation in [[Generic Haskell]], see the paper [http://www.staff.science.uu.nl/~jeuri101/homepage/Publications/tidata.pdf Type-indexed data types] by Ralf Hinze, Johan Jeuring and Andres Löh, or a similar paper [http://www.staff.science.uu.nl/~jeuri101/homepage/Publications/ghpractice.pdf Generic Haskell: Applications] by Ralf Hinze and Johan Jeuring
  +
  +
== Alternative formulation ==
  +
  +
The dual of Huet zipper is generic zipper -- which is a derivative of
  +
a traversal function rather than that of a data structure.
  +
Unlike Huet zipper,
  +
generic zipper can be implemented once and for all data structures,
  +
in the existing Haskell.
  +
[http://pobox.com/~oleg/ftp/Computation/Continuations.html#zipper Generic Zipper and its applications]
  +
  +
== Comonads and monads ==
  +
  +
Comonads
  +
* [http://cs.ioc.ee/~tarmo/tsem05/uustalu0812-slides.pdf Structured Computation on Trees or, What’s Behind That Zipper? (A Comonad)], slides by Tarmo Uustalu
  +
* [http://cs.ioc.ee/~tarmo/papers/tfp05-book.pdf Comonadic functional attribute evaluation] by Tarmo Uustalu1 and Varmo Vene, a more detailed treatment
  +
* [http://www.cs.nott.ac.uk/~txa/monads-more-4.pdf Monads and more (Part 4)] by Tarmo Uustalu
  +
* [http://sigfpe.blogspot.com/2006/12/evaluating-cellular-automata-is.html Evaluating cellular automata is comonadic], part of Sigfpe's ''A Neighborhood of Infinity''
  +
Monads:
  +
* [http://sigfpe.blogspot.com/2007/01/monads-hidden-behind-every-zipper.html The Monads Hidden Behind Every Zipper], part of Sigfpe's ''A Neighborhood of Infinity''
  +
  +
== Applications ==
  +
  +
;[http://okmij.org/ftp/Computation/Continuations.html#zipper-fs ZipperFS]
  +
:Oleg Kiselyov's zipper-based [[Libraries and tools/Operating system|file server/OS]] where threading and exceptions are all realized via [[Library/CC-delcont|delimited continuation]]s.
  +
;[http://donsbot.wordpress.com/2007/05/17/roll-your-own-window-manager-tracking-focus-with-a-zipper Roll Your Own Window Manager: Tracking Focus with a Zipper]
  +
:describes the use of zippers in [http://www.xmonad.org/ xmonad].
  +
* The [http://hackage.haskell.org/package/zippers zippers] package provides traversal-based zippers that are to be used with the [[Lens]] library
  +
* The [http://hackage.haskell.org/cgi-bin/hackage-scripts/package/AvlTree AVL Tree] package contains a zipper for navigating AVL trees.
  +
* A zipper for navigating rose trees (as found in the standard <code>Data.Tree</code> library) is available in the [http://code.haskell.org/yi/Data/Tree/ Yi code repository].
  +
* [http://hackage.haskell.org/cgi-bin/hackage-scripts/package/rosezipper An implementation of a zipper] for navigating rose trees (as found in the standard <code>Data.Tree</code> library).
   
== Further Reading ==
+
== Further reading ==
 
* Gerard Huet's [http://www.st.cs.uni-sb.de/edu/seminare/2005/advanced-fp/docs/huet-zipper.pdf paper] where he originally proposed the concept of a zipper
 
* Gerard Huet's [http://www.st.cs.uni-sb.de/edu/seminare/2005/advanced-fp/docs/huet-zipper.pdf paper] where he originally proposed the concept of a zipper
* [http://citeseer.ist.psu.edu/hinze01web.html The Web] extends this pattern.
+
* Hinz's [http://archive.cs.uu.nl/pub/RUU/CS/techreps/CS-2001/2001-33.pdf Weaving a Web] extends this pattern.
  +
* [http://sigfpe.blogspot.com/2006/09/infinitesimal-types.html Infinitesimal Types] writes on interesting generalizations (e.g. derivative of a type — to the analogy of the notion of derivative in rings, e.g. in analysis or for polinomials)
  +
* [http://en.wikibooks.org/wiki/Haskell/Zippers Haskell/Zippers] on Wikibooks, a detailed treatment of zippers, and generalizing the notion as derivative
  +
* [http://okmij.org/ftp/Computation/Continuations.html#zipper Generic Zipper and its applications], writing that “Zipper can be viewed as a [[Library/CC-delcont|delimited continuation]] reified as a data structure” (link added).
  +
* [http://www.cs.indiana.edu/~adamsmd/papers/scrap_your_zippers/ Scrap Your Zippers: A Generic Zipper for Heterogeneous Types], defines a generic zipper that works on arbitrary instances of the Data class. It uses GADTs instead of [[Library/CC-delcont|delimited continuations]].
   
 
[[Category:Idioms]]
 
[[Category:Idioms]]

Revision as of 07:25, 6 April 2014

The Zipper is an idiom that uses the idea of “context” to the means of manipulating locations in a data structure. Zipper monad is a monad which implements the zipper for binary trees.

Sometimes you want to manipulate a location inside a data structure, rather than the data itself. For example, consider a simple binary tree type:

data Tree a = Fork (Tree a) (Tree a) | Leaf a

and a sample tree t:

t = Fork (Fork (Leaf 1)
               (Leaf 2))
         (Fork (Leaf 3)
               (Leaf 4))
Tree-12-34.png

Each subtree of this tree occupies a certain location in the tree taken as a whole. The location consists of the subtree, along with the rest of the tree, which we think of the context of that subtree. For example, the context of

Leaf 2

in the above tree is

Fork (Fork (Leaf 1) @)
     (Fork (Leaf 3) (Leaf 4))
Context-1X-34.png

where @ marks a hole: the spot that the subtree appears in. This is the way we shall implement a tree with a focus. One way of expressing this context is as a path from the root of the tree to the hole (to which the required subtree will be attached). To reach our subtree, we needed to go down the left branch, and then down the right one. Note that the context is essentially a way of representing the tree, “missing out” a subtree (the subtree we are interested in).

A naive implementation of the context, inspired directly by the graphical representation might be to use Tree (Maybe a) instead of Tree a. However, this would lose an essential point: in any given context, there is exactly one hole.

Therefore, we will represent a context as follows:

data Cxt a = Top | L (Cxt a) (Tree a) | R (Tree a) (Cxt a)

L c t represents the left part of a branch of which the right part was t and whose parent had context c. The R constructor is similar. Top represents the top of a tree.

Remarks:

  • In fact, this is equivalent to a list, whose elements are the appropriate collateral trees, each element labeled with the information which direction was chosen:
type Context a = [(Direction, Tree a)]
data Direction = Lft | Rght
  • We chose to propagate from the hole towards the root. This is an independent idea of the above considerations: it is not the unicity of the hole that forced us to do so. It is simply more efficient if we want to define operations later for a tree with a focus (move focus left, right, up).
  • Note that in the original paper, Huet dealt with B-trees (ones where nodes have arbitrary numbers of branches), so at each node, a list is used instead of the two (Tree a) parameters to represent children. Later we shall see that the solution of the problem can be formalized in a general way which covers solutions for both kinds of trees, as special cases.

Using this datatype, we can rewrite the sample context above in proper Haskell:

R (Leaf 1) (L Top (Fork (Leaf 3) (Leaf 4)))

Note that the context is actually written by giving the path from the subtree to the root (rather than the other way round):

Context-1X-34.png
Context-X-34.png
Top Top.png

Or the more deconstructed representation:

Path-1X-34.png

where , are the appropriate correspondents of the , of the previous image. It is the empty list that represents .

Now we can define a tree location:

type Loc a = (Tree a, Cxt a)
Circum-op12cl-34.png Mount-op12cl-34.png

thus, a tree with a focus (drawn here as a tree with a marked subtree) shall be represented as “mounting” the focus (a tree) into the hole of the appropriate context.

Now, we can define some useful functions for manipulating locations in a tree:

left :: Loc a -> Loc a
left (Fork l r, c) = (l, L c r)

right :: Loc a -> Loc a
right (Fork l r, c) = (r, R l c)

top :: Tree a -> Loc a
top t = (t, Top)

up :: Loc a -> Loc a
up (t, L c r) = (Fork t r, c)
up (t, R l c) = (Fork l t, c)

upmost :: Loc a -> Loc a
upmost l@(t, Top) = l
upmost l = upmost (up l)

modify :: Loc a -> (Tree a -> Tree a) -> Loc a
modify (t, c) f = (f t, c)

It is instructive to look at an example of how a location gets transformed as we move from root to leaf. Recall our sample tree t. Let's name some of the relevant subtrees for brevity:

t = let tl = Fork (Leaf 1) (Leaf 2)
        tr = Fork (Leaf 3) (Leaf 4)
    in Fork tl tr

Then to reach the location of Leaf 2:

(right . left . top) t
= (right . left) (t, Top)
= right (tl, L Top tr)
= (Leaf 2, R (Leaf 1) (L Top tr))

To reach that location and replace Leaf 2 by Leaf 0:

modify ((right . left . top) t) (\_ -> Leaf 0)
= ...
= (Leaf 0, R (Leaf 1) (L Top tr))

Afterwards some may like to continue walking to other parts of the new tree, in which case continue applying left, right, and up.

Some others may like to retrieve the new tree (and possibly forget about locations), in which case upmost is useful:

(fst . upmost) (modify ((right . left . top) t) (\_ -> Leaf 0))
= (fst . upmost) (Leaf 0, R (Leaf 1) (L Top tr))
= fst (Fork (Fork (Leaf 1)
                  (Leaf 0))
            tr
      , Top)
= Fork (Fork (Leaf 1)
             (Leaf 0))
       tr

Automation

There's a principled way to get the necessary types for contexts and the context filling functions, namely by differentiating the data structure. Some relevant papers.

For an actual implementation in Generic Haskell, see the paper Type-indexed data types by Ralf Hinze, Johan Jeuring and Andres Löh, or a similar paper Generic Haskell: Applications by Ralf Hinze and Johan Jeuring

Alternative formulation

The dual of Huet zipper is generic zipper -- which is a derivative of a traversal function rather than that of a data structure. Unlike Huet zipper, generic zipper can be implemented once and for all data structures, in the existing Haskell. Generic Zipper and its applications

Comonads and monads

Comonads

Monads:

Applications

ZipperFS
Oleg Kiselyov's zipper-based file server/OS where threading and exceptions are all realized via delimited continuations.
Roll Your Own Window Manager: Tracking Focus with a Zipper
describes the use of zippers in xmonad.
  • The zippers package provides traversal-based zippers that are to be used with the Lens library
  • The AVL Tree package contains a zipper for navigating AVL trees.
  • A zipper for navigating rose trees (as found in the standard Data.Tree library) is available in the Yi code repository.
  • An implementation of a zipper for navigating rose trees (as found in the standard Data.Tree library).

Further reading