
Hi, I'm trying to catch the connection between delimited continuations and zippers so I wrote a (kinda) zipper interface to a simple tree structure. Here's the code: ------- module Main where import Data.Maybe data Tree a = Leaf a | Fork (Tree a) (Tree a) deriving Show tree = Fork (Fork (Leaf 1) (Leaf 2)) (Fork (Leaf 3) (Fork (Leaf 4) (Leaf 5))) data ZContext a = ZContext { moveUp :: Maybe (ZContext a), moveLeft :: Maybe (ZContext a), moveRight :: Maybe (ZContext a), this :: Maybe a } initZ t = doInitZ Nothing t where doInitZ c (Leaf a) = ZContext c Nothing Nothing $ Just a doInitZ c t@(Fork l r) = ZContext c (Just $ doInitZ s l) (Just $ doInitZ s r) Nothing where s = Just $ doInitZ c t ------- You access the tree in the following way (session from ghci): *Main> this $ fromJust . moveLeft $ fromJust . moveLeft $ initZ tree I read Haskell book's Chapter about Zippers on Wikibooks and I think I understood the underlying concept even if the implementation still seems to me a bit arbitrary (i.e. different implementation can be provided even if the proposed one is neat thinking of differentiation). Hence, I decided to go experimenting myself and came up with the above solution. I know that the interface to a tree having values only on leaves is pointless as the main advantage of using a Zipper is to get O(1) performance on updating but I wanted to keep it as simple as possible. So, can you provide some comments on that implementation? Thank you all, as usual! -- Cristiano

Cristiano Paris wrote:
I'm trying to catch the connection between delimited continuations and zippers so I wrote a (kinda) zipper interface to a simple tree structure. Here's the code:
------- module Main where
import Data.Maybe
data Tree a = Leaf a | Fork (Tree a) (Tree a) deriving Show
tree = Fork (Fork (Leaf 1) (Leaf 2)) (Fork (Leaf 3) (Fork (Leaf 4) (Leaf 5)))
data ZContext a = ZContext { moveUp :: Maybe (ZContext a), moveLeft :: Maybe (ZContext a), moveRight :: Maybe (ZContext a), this :: Maybe a }
initZ t = doInitZ Nothing t where doInitZ c (Leaf a) = ZContext c Nothing Nothing $ Just a doInitZ c t@(Fork l r) = ZContext c (Just $ doInitZ s l) (Just $ doInitZ s r) Nothing where s = Just $ doInitZ c t -------
You access the tree in the following way (session from ghci):
*Main> this $ fromJust . moveLeft $ fromJust . moveLeft $ initZ tree
I read Haskell book's Chapter about Zippers on Wikibooks and I think I understood the underlying concept even if the implementation still seems to me a bit arbitrary (i.e. different implementation can be provided even if the proposed one is neat thinking of differentiation).
Hence, I decided to go experimenting myself and came up with the above solution. I know that the interface to a tree having values only on leaves is pointless as the main advantage of using a Zipper is to get O(1) performance on updating but I wanted to keep it as simple as possible.
So, can you provide some comments on that implementation? Thank you all, as usual!
The unusual thing about your implementation is probably that you're tying a knot by making both moveUp and moveLeft record fields. This reminds me of Weaving a web. Ralf Hinze and Johan Jeuring. 2001. http://www.informatik.uni-bonn.de/~ralf/publications/TheWeb.ps.gz The problem with knot-tying / sharing is of course that they are tricky to update. What about the crucial function update :: ZContext a -> Maybe a -> ZContext a that changes the data at a leaf? I think that with your current approach, you'd have to regenerate the whole context which pretty much defeats the purpose of a zipper. Regards, apfelmus -- http://apfelmus.nfshost.com

On Wed, Mar 4, 2009 at 12:50 PM, Heinrich Apfelmus
... The unusual thing about your implementation is probably that you're tying a knot by making both moveUp and moveLeft record fields. This reminds me of
Weaving a web. Ralf Hinze and Johan Jeuring. 2001. http://www.informatik.uni-bonn.de/~ralf/publications/TheWeb.ps.gz
The problem with knot-tying / sharing is of course that they are tricky to update. What about the crucial function
update :: ZContext a -> Maybe a -> ZContext a
that changes the data at a leaf? I think that with your current approach, you'd have to regenerate the whole context which pretty much defeats the purpose of a zipper.
Hi Heinrich and thanks for your reply. I haven't read the paper (which I'm going to read now) but I don't fully understand your point. I'd (and indeed I did) write 'update' as: update z x = z { this = this z >> Just x } exploiting the '>>' operator's logic. How would this differ from the corresponding 'update' in the original Huet's FP? Maybe I don't get how my update would impact performances. In both cases the update functions leave context unchanged, don't they? If my update function have to replicate the context since functional values are immutable, doesn't Huet's do the same? Thank you for any further comments. Cristiano

On Wed, Mar 4, 2009 at 9:53 PM, Cristiano Paris
... Thank you for any further comments.
I forgot to mention one drawback I found in my implementation: it can't be (de)serialized to a String, which is clearly possible with Huet's. I think this accounts for the "Zipper as a delimited continuation reified to data" statement :D Cristiano

On Wed, Mar 4, 2009 at 12:53 PM, Cristiano Paris
I'd (and indeed I did) write 'update' as:
update z x = z { this = this z >> Just x }
exploiting the '>>' operator's logic. How would this differ from the corresponding 'update' in the original Huet's FP? Maybe I don't get how my update would impact performances. In both cases the update functions leave context unchanged, don't they? If my update function have to replicate the context since functional values are immutable, doesn't Huet's do the same?
Thank you for any further comments.
The problem is that your zipper structure is too open, you don't have any specification of the "zipper laws". For example, I'd expect that for any zipper z, one of the following holds: a) moveUp z = Nothing b) moveUp z >>= moveLeft = Just z c) moveUp z >>= moveRight = Just z Here is the problem with your "update": tree = Fork (Leaf 1) (Leaf 2) ztree = initZ tree test = fromJust $ do z1 <- moveLeft ztree let z2 = update z1 3 z3 <- moveUp z2 z4 <- moveLeft z3 this z4 I'd expect "test" to equal 3, but I believe with your code that it still equals 1. As apfelmus said, update needs to completely re-construct the zipper structure with the tied knot, which defeats the purpose of using a zipper in the first place. -- ryan

On 3/5/09, Ryan Ingram
... Here is the problem with your "update":
tree = Fork (Leaf 1) (Leaf 2) ztree = initZ tree
test = fromJust $ do z1 <- moveLeft ztree let z2 = update z1 3 z3 <- moveUp z2 z4 <- moveLeft z3 this z4
I'd expect "test" to equal 3, but I believe with your code that it still equals 1. As apfelmus said, update needs to completely re-construct the zipper structure with the tied knot, which defeats the purpose of using a zipper in the first place.
I got it. I dont't know what your expression "tied knot" is referring to but I got the point. Thanks. Cristiano

Cristiano Paris wrote:
Ryan Ingram wrote:
... Here is the problem with your "update":
tree = Fork (Leaf 1) (Leaf 2) ztree = initZ tree
test = fromJust $ do z1 <- moveLeft ztree let z2 = update z1 3 z3 <- moveUp z2 z4 <- moveLeft z3 this z4
I'd expect "test" to equal 3, but I believe with your code that it still equals 1. As apfelmus said, update needs to completely re-construct the zipper structure with the tied knot, which defeats the purpose of using a zipper in the first place.
I got it. I dont't know what your expression "tied knot" is referring to but I got the point.
In doInitZ , you're basically using the s itself to define the moveLeft and moveRight fields of s . You could as well write it as initZ t = doInitZ Nothing t where doInitZ c (Leaf a) = ZContext c Nothing Nothing $ Just a doInitZ c t@(Fork l r) = s where s = ZContext c (Just $ doInitZ (Just s) l) (Just $ doInitZ (Just s) r) Nothing Such self-reference is usually called "tying the knot", see also http://www.haskell.org/haskellwiki/Tying_the_Knot Regards, apfelmus -- http://apfelmus.nfshost.com

On Thu, Mar 5, 2009 at 11:21 AM, Heinrich Apfelmus
... Such self-reference is usually called "tying the knot", see also
I didn't know. Would you call this "Tying the knot" as well? http://yi-editor.blogspot.com/2008/12/prototypes-encoding-oo-style.html Thank you. Cristiano

Cristiano Paris wrote:
Heinrich Apfelmus wrote:
... Such self-reference is usually called "tying the knot", see also
I didn't know. Would you call this "Tying the knot" as well?
http://yi-editor.blogspot.com/2008/12/prototypes-encoding-oo-style.html
Yes, or rather, I would call it "untying the knot". ;) Regards, apfelmus -- http://apfelmus.nfshost.com
participants (4)
-
Cristiano Paris
-
Cristiano Paris
-
Heinrich Apfelmus
-
Ryan Ingram