Difference between revisions of "Zipper"

From HaskellWiki
Jump to navigation Jump to search
m (cleanup)
(some more explanation)
Line 18: Line 18:
   
 
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
  +
 
<haskell>
 
<haskell>
 
Leaf 2
 
Leaf 2
 
</haskell>
 
</haskell>
  +
 
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>
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.
 
   
 
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).
Thus we can represent a context as follows:
 
  +
 
We can represent a context as follows:
  +
 
<haskell>
 
<haskell>
 
data Cxt a = Top | L (Cxt a) (Tree a) | R (Tree a) (Cxt a)
 
data Cxt a = Top | L (Cxt a) (Tree a) | R (Tree a) (Cxt a)
 
</haskell>
 
</haskell>
  +
  +
<haskell>L c t</haskell> represents the left part of a branch of which the right part was <haskell>t</haskell> and whose parent had context <haskell>c</haskell>. The <haskell>R</haskell> constructor is similar. <haskell>Top</haskell> represents the top of a tree.
  +
 
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:
  +
 
<haskell>
 
<haskell>
 
R (Leaf 1) (L Top (Fork (Leaf 3) (Leaf 4)))
 
R (Leaf 1) (L Top (Fork (Leaf 3) (Leaf 4)))
 
</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).
   
 
Now we can define a tree location:
 
Now we can define a tree location:
  +
 
<haskell>
 
<haskell>
 
type Loc a = (Tree a, Cxt a)
 
type Loc a = (Tree a, Cxt a)
 
</haskell>
 
</haskell>
  +
 
and some useful functions for manipulating locations in a tree:
 
and some useful functions for manipulating locations in a tree:
  +
 
<haskell>
 
<haskell>
 
left :: Loc a -> Loc a
 
left :: Loc a -> Loc a
Line 60: Line 73:
 
modify (t, c) f = (f t, c)
 
modify (t, c) f = (f t, c)
 
</haskell>
 
</haskell>
  +
 
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:
 
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:
  +
 
<haskell>
 
<haskell>
 
t = let tl = Fork (Leaf 1) (Leaf 2)
 
t = let tl = Fork (Leaf 1) (Leaf 2)
Line 66: Line 81:
 
in Fork tl tr
 
in Fork tl tr
 
</haskell>
 
</haskell>
  +
 
Then:
 
Then:
  +
 
<haskell>
 
<haskell>
 
(left . right . top) t
 
(left . right . top) t

Revision as of 15:33, 17 April 2006

The Zipper is an idiom that uses the idea of "context" to the means of manipulating locations in a data structure.

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))

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))

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:

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.

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).

Now we can define a tree location:

type Loc a = (Tree a, Cxt a)

and 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)

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

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

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:

(left . right . top) t
= (left . right) (t, Top)
= left (tr, R tl Top)
= (Leaf 3, L (R tl Top) (Leaf 4))

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 GenericHaskell, see the paper "Type-indexed data types" by Ralf Hinze, Johan Jeuring and Andres Löh.

Further Reading

  • Gerard Huet's paper where he originally proposed the concept of a zipper
  • The Web extends this pattern.