Fwd: [Haskell-cafe] Data.Tree.Zipper in the standard libraries
apfelmus
apfelmus at quantentunnel.de
Wed Jun 4 17:11:58 EDT 2008
Ian Lynagh wrote:
> I've just skimmed http://citeseer.ist.psu.edu/472190.html
> The Derivative of a Regular Type is its Type of One-Hole Contexts
> (Extended Abstract) (2001)
> Conor McBride
>
> Given the way people had been appealing to it, I has assumed that
> datastructure derivatives were some general thing, but it looks like
> they are actually just a way of describing a particular concrete
> implementation of zippers. I'm not even sure how well the theoretical
> connection applies to the variable branching degree of Data.Tree.
This is quite right, the connection between zippers and derivatives is
not as straightforward as it seems.
First, they are different things. You can obtain a zipper for an
inductive data structure
type Foo = µ x. F x
by differentiating the functor F , but you can't differentiate Foo
itself. (I think that the zipper may even depend on the particular
choice of F.) Yet, both may coincide; the derivative of
type List a = µ x . 1 + (a, x)
with respect to a and the zipper for lists are pretty much the same.
> Also, I think that technically it doesn't follow the paper, in that it
> stores the parents in the reverse order.
>
> That aside, the fact the datastructure is a derivative doesn't tell us
> that it is efficient (in fact, it is more efficient because it /isn't/ a
> straightforward derivative, but reverses the parent order as above),
> that we have implemented the "right" methods to operate on it, that we
> have chosen the "best" names for those methods, etc.
Correct, applying the rules of differentiation directly usually does not
give the most efficient structure. When differentiating fixed points,
one usually ends up with something like
type DF a = µ x . T a + (S a, x)
which is basically a list of S a that doesn't end with [] but with a
value of type T a . Of course, this is isomorphic to
type DF' a = ([S a], T a)
with the list reversed; but this isomorphism is an optimization.
> Also, it's actually the derivative of Forest, not Tree, right? Which is
> why toTree can lose information, here the b and c trees:
> Data.Tree.Zipper> toTree (Loc (Node 'a' []) [Node 'b' []] [Node 'c' []] [])
> Node {rootLabel = 'a', subForest = []}
> This feels a little scary to me.
Yes. A zipper for a tree would have to carry the value a around.
Regards,
apfelmus
PS: The article in the wikibook
http://en.wikibooks.org/wiki/Haskell/Zippers
tries to point out the above distinctions.
More information about the Libraries
mailing list