
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