
Hello, I was trying to wrap my head around the stuff at http://haskell.org/haskellwiki/Tying_the_Knot (again) and along the way came a question: Is it possible to change a particular node of the doubly linked list? That is to say, that would like to have a function: update :: DList a -> a -> DList a where update node newValue returns a list where only the value at the node which is passed in is set to the new Value and all other values are the same. All this of course in a pure way, that is without using (M/T/TM)Vars or IORefs. I do apologize if the answer is really obvious and am thankfull for any hints. Thanks in advance Stephan Günther

Hi Stephan, S. Günther wrote:
Is it possible to change a particular node of the doubly linked list? That is to say, that would like to have a function: update :: DList a -> a -> DList a where update node newValue returns a list where only the value at the node which is passed in is set to the new Value and all other values are the same. All this of course in a pure way, that is without using (M/T/TM)Vars or IORefs.
The short answer is: yes, but the complete DList structure will need to be built anew (if nodes in the updated list are needed). The longer answer is: Because everything is pure, 'update' will need to create a new DLNode with the new value. But then you will also want to update the node's neighbours to point to the newly created DLNode, because if you don't then moving forward and then backward one position would make you end up at the old value again. But to update the neighbours' links to the new node you need to create new neighbour DLNodes, because everything is pure. And so on, until the whole list has been recreated. To not need to recreate the whole list you will need some kind of assignment, and this is exactly what vars/refs are for. Hope this helps, Martijn.

Also, it's actually really hard to tie the knot in the update; without some kind of distinguished node that allows you to know that it is the beginning/end of the list. For example, in this DList: 1,1,1, .... lots of times, 1, 2, 1, 1, ... lots of times, 1, (loop) If you change the 3rd "1", how do you know when to tie the knot and attach the list back together? This is a big problem with knot-tied datastructures in Haskell; it's very difficult to *untie* the knot and find the ends of the string again! Another example:
-- constant space no matter how many elements you access list_1 = repeat 1 :: [Int]
-- blows up to infinite size even though it's just "repeat (1 + 1)" list_2 = map (+1) list_1
--ryan
On Wed, Dec 31, 2008 at 5:07 AM, Martijn van Steenbergen
Hi Stephan,
S. Günther wrote:
Is it possible to change a particular node of the doubly linked list? That is to say, that would like to have a function: update :: DList a -> a -> DList a where update node newValue returns a list where only the value at the node which is passed in is set to the new Value and all other values are the same. All this of course in a pure way, that is without using (M/T/TM)Vars or IORefs.
The short answer is: yes, but the complete DList structure will need to be built anew (if nodes in the updated list are needed).
The longer answer is: Because everything is pure, 'update' will need to create a new DLNode with the new value. But then you will also want to update the node's neighbours to point to the newly created DLNode, because if you don't then moving forward and then backward one position would make you end up at the old value again. But to update the neighbours' links to the new node you need to create new neighbour DLNodes, because everything is pure. And so on, until the whole list has been recreated.
To not need to recreate the whole list you will need some kind of assignment, and this is exactly what vars/refs are for.
Hope this helps,
Martijn. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thanks for the answers to all.
Untying the knot was (and still is) exactly the problem I was facing.
I knew that the whole list had to be rebuild and wasn't concerned
with performance since at that point I just wanted to know how to
do it and if it is possible at all. After I realized that it maybe just to
hard in the circular case I tried my hand on a non circular version
coming up with the following.
data DList a =
DLNode {left::(DList a), value::a, right::(DList a)} |
Leaf
update :: DList a -> a -> DList a
update n newValue = n' where
n' = DLNode (linkleft n n') newValue (linkright n n')
linkleft, linkright :: DList a -> DList a -> DList a
linkleft Leaf _ = Leaf
linkleft old new = l' where
l = left old
l' = case l of {~Leaf -> l; _ -> l{left = linkleft l l', right = new}}
linkright Leaf _ = Leaf
linkright old new = r' where
r = right old
r' = case r of {~Leaf -> r; _ -> r{right = linkright r r', left = new}}
Not the most elegant solution but relatively straightforward.
And it does what it should if the list is terminated with Leaves on
the left and
right. One can also run it on an circular list but then it just
doesn't work like
it should (which isn't surprising):
*T> let l = mkDList [1..5]
*T> takeF 11 l
[1,2,3,4,5,1,2,3,4,5,1]
*T> let l' = update l (-1)
*T> takeF 11 l'
[-1,2,3,4,5,1,2,3,4,5,1]
So my problem is whether it possible to implement update in a way that
makes takeF 11 l' return [-1,2,3,4,5,-1,2,3,4,5,-1], and if it is possible I
would appreciate any pointers on how because I just can't figure it out.
But I'm already thankful for the answers so far, especially for the pointer
to map (+1) (repeat (1::Int)) since I really didn't expect it to behave like
that. And I would like to apologize for being too short in the formulation of
my original question.
cheers
Stephan
On Thu, Jan 1, 2009 at 8:11 AM, Ryan Ingram
Also, it's actually really hard to tie the knot in the update; without some kind of distinguished node that allows you to know that it is the beginning/end of the list.
For example, in this DList:
1,1,1, .... lots of times, 1, 2, 1, 1, ... lots of times, 1, (loop)
If you change the 3rd "1", how do you know when to tie the knot and attach the list back together?
This is a big problem with knot-tied datastructures in Haskell; it's very difficult to *untie* the knot and find the ends of the string again!
Another example:
-- constant space no matter how many elements you access list_1 = repeat 1 :: [Int]
-- blows up to infinite size even though it's just "repeat (1 + 1)" list_2 = map (+1) list_1
--ryan
On Wed, Dec 31, 2008 at 5:07 AM, Martijn van Steenbergen
wrote: Hi Stephan,
S. Günther wrote:
Is it possible to change a particular node of the doubly linked list? That is to say, that would like to have a function: update :: DList a -> a -> DList a where update node newValue returns a list where only the value at the node which is passed in is set to the new Value and all other values are the same. All this of course in a pure way, that is without using (M/T/TM)Vars or IORefs.
The short answer is: yes, but the complete DList structure will need to be built anew (if nodes in the updated list are needed).
The longer answer is: Because everything is pure, 'update' will need to create a new DLNode with the new value. But then you will also want to update the node's neighbours to point to the newly created DLNode, because if you don't then moving forward and then backward one position would make you end up at the old value again. But to update the neighbours' links to the new node you need to create new neighbour DLNodes, because everything is pure. And so on, until the whole list has been recreated.
To not need to recreate the whole list you will need some kind of assignment, and this is exactly what vars/refs are for.
Hope this helps,
Martijn. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

S. Günther wrote:
Untying the knot was (and still is) exactly the problem I was facing. I knew that the whole list had to be rebuild and wasn't concerned with performance since at that point I just wanted to know how to do it and if it is possible at all. After I realized that it maybe just to hard in the circular case I tried my hand on a non circular version coming up with the following.
data DList a = DLNode {left::(DList a), value::a, right::(DList a)} | Leaf
Whether circular or not, sharing values by using a "back pointer" is problematic for any update. Why not use a zipper instead? data Zipper a = Zip [a] a [a] value :: Zipper a -> a value (Zip _ x _) = x right, left :: Zipper a -> Zipper a left (Zip (l:ls) x rs) = Zip ls l (x:rs) right (Zip ls x (r:rs)) = Zip (x:ls) r rs update :: Zipper a -> a -> Zipper a update (Zip ls _ rs) x = Zip ls x rs In other words, you don't have to implement left and right as record labels, implementing them as normal functions may be better. For more about zippers, see also http://en.wikibooks.org/wiki/Haskell/Zippers There are also some ready-made packages on hackage, like ListZipper . Regards, H. Apfelmus

Whether circular or not, sharing values by using a "back pointer" is problematic for any update. Why not use a zipper instead? I looked into zippers before and the problem I had was that they never really matched the structure which I needed and which led me to think about this whole knot tying thing again.[1] The things I read about them always assumed either a list like (i.e. linear) or a tree like (i.e. existence of a root) structure on the type to be plugged into the zipper. Now I know that this is not necessary and there are references to a generic zipper implementation but the thing is that I only found the source code and decided to first look into the knot tying thing before opening another can of worms with delimited continuations since I already spend too muchtime thinking about that stuff.[2] So if anyone has pointers to a good generic zipper explanation I would be thankful. Note that I don't need full blown error handling. I would first like to understand the basics. Now I think I came to the conclusion that locally updating a tied knot in a pure way really is hard and that it's not me just not seeing some obvious solution. So I just have to decide whether to use IORefs/Vars (clunky) or to implement zippers for the structure I need (probably toohard for me). Anyways thanks for all the answers from which I learned a few unexpected things and which assured me that my instincts aren't that far off.
Cheers and warm regards (and a happy new year) Stephan [1]: "Again" means that I already looked into both tying the knot and zippers about a year ago out of curiosity. This time it was out of necessity although the original question I posed was more a necessity diverging into curiosity again. [2]: Note that "too much time" rather refers to the quantity I have at my disposal than to personal preferences. If I could I would like nothing more than to think about this "stuff" for the rest of my life.

On Fri, 2009-01-02 at 10:48 +1100, S. Günther wrote:
Whether circular or not, sharing values by using a "back pointer" is problematic for any update. Why not use a zipper instead? I looked into zippers before and the problem I had was that they never really matched the structure which I needed and which led me to think about this whole knot tying thing again.[1] The things I read about them always assumed either a list like (i.e. linear) or a tree like (i.e. existence of a root) structure on the type to be plugged into the zipper. Now I know that this is not necessary and there are references to a generic zipper implementation but the thing is that I only found the source code and decided to first look into the knot tying thing before opening another can of worms with delimited continuations since I already spend too muchtime thinking about that stuff.[2] So if anyone has pointers to a good generic zipper explanation I would be thankful. Note that I don't need full blown error handling. I would first like to understand the basics. Now I think I came to the conclusion that locally updating a tied knot in a pure way really is hard and that it's not me just not seeing some obvious solution. So I just have to decide whether to use IORefs/Vars (clunky) or to implement zippers for the structure I need (probably toohard for me). Anyways thanks for all the answers from which I learned a few unexpected things and which assured me that my instincts aren't that far off.
Read this http://strictlypositive.org/diff.pdf (again)

S. Günther wrote:
Whether circular or not, sharing values by using a "back pointer" is problematic for any update. Why not use a zipper instead?
I looked into zippers before and the problem I had was that they never really matched the structure which I needed and which led me to think about this whole knot tying thing again.
What kind of structure do you need exactly?
The things I read about them always assumed either a list like (i.e. linear) or a tree like (i.e. existence of a root) structure on the type to be plugged into the zipper.
Viewing the zipper as the derivative of a data type opens up more possibilities. That being said, every algebraic data types has a tree-like structure. The extra invariants like left . right = right . left that the programmer imposes are what make them different from trees.
So I just have to decide whether to use IORefs/Vars (clunky) or to implement zippers for the structure I need (probably too hard for me).
It's not too hard for you. You've got a whole haskell-cafe and #haskell at your fingertips, after all. ;) Regards, H. Apfelmus

What kind of structure do you need exactly? What I really need is a structure which represents a two dimensional grid, i.e. it consists of nodes having a value and a list of neighbours attached to it. Point is
The things I read about them always assumed either a list like (i.e. linear) or a tree like (i.e. existence of a root) structure on the type to be plugged into the zipper.
Viewing the zipper as the derivative of a data type opens up more possibilities.
That being said, every algebraic data types has a tree-like structure. The extra invariants like
left . right = right . left
that the programmer imposes are what make them different from trees. That's right. After I wrote I that I realized that the distinction I made was a little bit of nonsense since a linear structure is a degenerated case of a tree
So I just have to decide whether to use IORefs/Vars (clunky) or to implement zippers for the structure I need (probably too hard for me).
It's not too hard for you. You've got a whole haskell-cafe and #haskell at your fingertips, after all. ;) Righty right, but there's still the possibility that given all the time in the world and
There goes my promise like a new years resolution... ;) that if node 1 has node 2 as a neighbour then node 2 has to have node 1 as a neighbour and each node has the same number of neighbours (currently 4, but may vary). So it really is just an undirected planar graph with some restrictions. And it isn't even circular because nodes may have Leaves as neighbours signalling that they are boundary nodes. And since the algorithm I would like to implement is specified in a purely imperative way I need to be able to update the values stored at the nodes and insert new nodes at where there a Leaves. So I figured since the structure isn't even circular I could do it the inefficient way and just use a generalization of the update function for doubly linked lists I came up with before and thus always rebuild the whole structure. That's why I said that thinking about the circular case was just a divergence that rally got me wondering/interested which is why I posted the question in it's short form at the beginning. Anyways, back to the structure I need. One additional thing which will happen during the algorithm is that there will be updates to a certain local neighbourhood of a node. Now I understand, that that might very well be possible with zippers. Instead of lists of neighbouring nodes I might as well save the paths through the graphs separately from the nodes although I only have a very vague intuition about how that would look like. And instead of calculating a lists of nodes to update, I could calculate a path visting the nodes and update them (again beeing unable to escape from the prison of an imperative mindset) traversing the path. like structure. But the point was that I just had a hard time generalizing what I read about zippers to structures where you can have embedded cycles, e.g. up . left . down . right = id. the clearest explanations I'm just to dense to get a hold of it. That said I hope that's note the case but I might still be better off timewise to just go with MVars and a straightforward way first and then doing the reading and maybe refactoring to a different approach. cheers Stephan

S. Günther wrote:
What kind of structure do you need exactly?
What I really need is a structure which represents a two dimensional grid, i.e. it consists of nodes having a value and a list of neighbours attached to it. Point is that if node 1 has node 2 as a neighbour then node 2 has to have node 1 as a neighbour and each node has the same number of neighbours (currently 4, but may vary).
Ah, so you have a rectangular (or later hexagonal?) 2D grid? I suggest representing it as Data.Map (Integer, Integer) a as explained below.
That's why I said that thinking about the circular case was just a divergence that really got me wondering/interested which is why I posted the question in it's short form at the beginning.
Exploring a related easier problem is always a good way to get some intuition for tackling the harder one. :)
Anyways, back to the structure I need. One additional thing which will happen during the algorithm is that there will be updates to a certain local neighboruhood of a node. Now I understand, that that might very well be possible with zippers.
Instead of lists of neighbouring nodes I might as well save the paths through the graphs separately from the nodes although I only have a very vague intuition about how that would look like. And instead of calculating a lists of nodes to update, I could calculate a path visting the nodes and update them (again beeing unable to escape from the prison of an imperative mindset) traversing the path.
A zipper indeed allows you to move to neighbors and update them.
But the point was that I just had a hard time generalizing what I read about zippers to structures where you can have embedded cycles, e.g.
up . left . down . right = id.
If you interpret zippers as the original data structure with a hole, this is not so difficult. For instance, consider a rectangular grid +--+--+--+--+--+--+--+ | | | | | | | | +--+--+--+--+--+--+--+ | | | | | | | | +--+--+--+--+--+--+--+ | | | | | | | | +--+--+--+--+--+--+--+ where you store some data at every node. Now, a zipper is just the old data structure but one node is marked as "hole" +--+--+--+--+--+--+--+ | | | | | | | | +--+--+--O--+--+--+--+ | | | | | | | | +--+--+--+--+--+--+--+ | | | | | | | | +--+--+--+--+--+--+--+ If you represent the grid as a rectangular table type Position = (Integer, Integer) type Grid a = Data.Map Position a a zipper is simply the grid with an extra marker type Zipper a = (Grid a, Position) left,right,up,down :: Zipper a -> Zipper a left (g,(x,y)) = (g,(x-1,y)) right (g,(x,y)) = (g,(x+1,y)) up (g,(x,y)) = (g,(x,y-1)) down (g,(x,y)) = (g,(x,y+1)) update :: a -> Zipper a -> Zipper a update a (g,(x,y)) = (insert (x,y) a g, (x,y)) Note that the left, right etc. are not "baked into" the data type but implemented as normal functions. In principle, the same could be done for lists type ZipperL a = ([a], Int) left, right :: ZipperL a -> ZipperL a left (xs,i) = (xs,i-1) right (xs,i) = (xs,i+1) update :: a -> ZipperL a -> ZipperL a update a (xs,i) = (take i xs ++ [a] ++ drop (i+1) xs, i) This is a valid implementation of a zipper for lists, but of course is very inefficient, update is O(n) . The key thing about the original list zipper with back and front list is that all operations are O(1). For the 2D grid zipper above, moving around is O(1) but update is O(log n). This is acceptable; also because I'm quite confident that a zipper for a 2D grid with everything O(1) does not exist. I can prove that for a special case and should probably write it down at some point. In other words, I suggest representing your grid as a Data.Map (Integer,Integer) a and accept the minor inconvenience of a O(log n) update. Choosing a different finite map implementation may give a better constant factor. For instance you can nest two Data.IntMap etc.
Righty right, but there's still the possibility that given all the time in the world and the clearest explanations I'm just to dense to get a hold of it. That said I hope that's not the case but I might still be better off timewise to just go with MVars and a straightforward way first and then doing the reading and maybe refactoring to a different approach.
My personal experience is that not going with the obvious but messy solution but searching for a more elegant one is always faster in the long run. :) Regards, H. Apfelmus

For the 2D grid zipper above, moving around is O(1) but update is O(log n). This is acceptable; also because I'm quite confident that a zipper for a 2D grid with everything O(1) does not exist. I can prove that for a special case and should probably write it down at some point.
Really? My solution (rose tree zipper where tree depth is manhattan distance from origin and forest width is nodes around concentric diamonds, see http://permalink.gmane.org/gmane.comp.lang.haskell.cafe/49948) was designed specifically to be amortized constant for everything for paths that do not specifically move helically around the origin. The complexity of lookup is O(d) where d is the number of defined nodes at a given radius. Until the grid gets pretty dense, d grows very slowly for most sane paths. Have I missed something? Dan Apfelmus, Heinrich wrote:
S. Günther wrote:
What kind of structure do you need exactly? What I really need is a structure which represents a two dimensional grid, i.e. it consists of nodes having a value and a list of neighbours attached to it. Point is that if node 1 has node 2 as a neighbour then node 2 has to have node 1 as a neighbour and each node has the same number of neighbours (currently 4, but may vary).
Ah, so you have a rectangular (or later hexagonal?) 2D grid? I suggest representing it as
Data.Map (Integer, Integer) a
as explained below.
That's why I said that thinking about the circular case was just a divergence that really got me wondering/interested which is why I posted the question in it's short form at the beginning.
Exploring a related easier problem is always a good way to get some intuition for tackling the harder one. :)
Anyways, back to the structure I need. One additional thing which will happen during the algorithm is that there will be updates to a certain local neighboruhood of a node. Now I understand, that that might very well be possible with zippers.
Instead of lists of neighbouring nodes I might as well save the paths through the graphs separately from the nodes although I only have a very vague intuition about how that would look like. And instead of calculating a lists of nodes to update, I could calculate a path visting the nodes and update them (again beeing unable to escape from the prison of an imperative mindset) traversing the path.
A zipper indeed allows you to move to neighbors and update them.
But the point was that I just had a hard time generalizing what I read about zippers to structures where you can have embedded cycles, e.g.
up . left . down . right = id.
If you interpret zippers as the original data structure with a hole, this is not so difficult. For instance, consider a rectangular grid
+--+--+--+--+--+--+--+ | | | | | | | | +--+--+--+--+--+--+--+ | | | | | | | | +--+--+--+--+--+--+--+ | | | | | | | | +--+--+--+--+--+--+--+
where you store some data at every node. Now, a zipper is just the old data structure but one node is marked as "hole"
+--+--+--+--+--+--+--+ | | | | | | | | +--+--+--O--+--+--+--+ | | | | | | | | +--+--+--+--+--+--+--+ | | | | | | | | +--+--+--+--+--+--+--+
If you represent the grid as a rectangular table
type Position = (Integer, Integer) type Grid a = Data.Map Position a
a zipper is simply the grid with an extra marker
type Zipper a = (Grid a, Position)
left,right,up,down :: Zipper a -> Zipper a left (g,(x,y)) = (g,(x-1,y)) right (g,(x,y)) = (g,(x+1,y)) up (g,(x,y)) = (g,(x,y-1)) down (g,(x,y)) = (g,(x,y+1))
update :: a -> Zipper a -> Zipper a update a (g,(x,y)) = (insert (x,y) a g, (x,y))
Note that the left, right etc. are not "baked into" the data type but implemented as normal functions.
In principle, the same could be done for lists
type ZipperL a = ([a], Int)
left, right :: ZipperL a -> ZipperL a left (xs,i) = (xs,i-1) right (xs,i) = (xs,i+1)
update :: a -> ZipperL a -> ZipperL a update a (xs,i) = (take i xs ++ [a] ++ drop (i+1) xs, i)
This is a valid implementation of a zipper for lists, but of course is very inefficient, update is O(n) . The key thing about the original list zipper with back and front list is that all operations are O(1).
For the 2D grid zipper above, moving around is O(1) but update is O(log n). This is acceptable; also because I'm quite confident that a zipper for a 2D grid with everything O(1) does not exist. I can prove that for a special case and should probably write it down at some point.
In other words, I suggest representing your grid as a
Data.Map (Integer,Integer) a
and accept the minor inconvenience of a O(log n) update. Choosing a different finite map implementation may give a better constant factor. For instance you can nest two Data.IntMap etc.
Righty right, but there's still the possibility that given all the time in the world and the clearest explanations I'm just to dense to get a hold of it. That said I hope that's not the case but I might still be better off timewise to just go with MVars and a straightforward way first and then doing the reading and maybe refactoring to a different approach.
My personal experience is that not going with the obvious but messy solution but searching for a more elegant one is always faster in the long run. :)
Regards, H. Apfelmus
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Dan Weston wrote:
For the 2D grid zipper above, moving around is O(1) but update is O(log n). This is acceptable; also because I'm quite confident that a zipper for a 2D grid with everything O(1) does not exist. I can prove that for a special case and should probably write it down at some point.
Really? My solution (rose tree zipper where tree depth is manhattan distance from origin and forest width is nodes around concentric diamonds, see http://permalink.gmane.org/gmane.comp.lang.haskell.cafe/49948) was designed specifically to be amortized constant for everything for paths that do not specifically move helically around the origin. The complexity of lookup is O(d) where d is the number of defined nodes at a given radius. Until the grid gets pretty dense, d grows very slowly for most sane paths.
Have I missed something?
From your description (without reading the code ;)), I gather that your tree looks something like this?
-+- / \ -+ -+- +- / / \ \ -+ -+ -+- +- +- / / / \ \ \ -+ -+ -+ -+- +- +- +- / / / / \ \ \ \ + B A + +--+--C--+--+-- ... \ \ \ \ / / / / -+ -+ -+ -+- +- +- +- \ \ \ / / / -+ -+ -+- +- +- \ \ / / -+ -+- +- \ / -+- The root of the tree is the center and you can descend on the right. But with this structure, walking from A to B is O(d) = O(n) (where d is the distance from the origin, n the side length of the grid) instead of O(1). Put differently, using Data.Tree.Zipper.parent on B will move you to C, not to A. I mean, O(d) may be fine for you, but it's not O(1) for everything as advertised. :) Regards, H. Apfelmus

Apfelmus, Thanks for the reply.
From your description (without reading the code ;))
I hope the code is better than my description! :) The structure is more like Nothing(RK 0 _) Nothing(RK 1 _) A(RK 2 4) B(RK 3 6) C(RK 2 0)
The root of the tree is the center and you can descend on the right. But with this structure, walking from A to B is O(d) = O(n) (where d is the distance from the origin, n the side length of the grid) instead of O(1).
No. The tree is [[Node]], where the outer list has one element for each radius that has an occupied node and each inner list has the number of nodes at the given radius. You descend the spine of the outer list radially in O(deltaR) time, which for incremental moves is O(1). Then you search for an existing inner list element in O(nk(r)), which stays fairly constant for reasonable paths (basically, the width of a path swath).
I mean, O(d) may be fine for you, but it's not O(1) for everything as advertised. :)
d is not the distance from the origin, it is nk(r), the number of nodes at a given radius: d(2) = 2, d(3) = 1. An outward radial path will only expand the tree linearly, not quadratically, in size.
Put differently, using Data.Tree.Zipper.parent on B will move you to C, not to A.
The parent of C is either A or B, depending on the path that created it, but parent teleports you in O(1). Walking from A to B only involves: (bX,bY) = (-3,0) (aX,aY) = (-2,0) (bR,bK) = (|bX| + |bY|, bR - bX) = (3,6) -- left halfplane (aR,aK) = (|aX| + |aY|, aR - aX) = (2,4) -- left halfplane deltaR = bR - aR = 1 maybe (insertDownFirst (newNode rk) z) (moveAround rk) $ firstChild z When firstChild fails, insertDownFirst and we're done! All operations are O(1). When firstChild succeeds, moveAround queries each of the defined nodes -- but not any of the undefined nodes! -- at that radius. There is at most one defined node with Nothing value to ensure a path from the origin to every node (where path is not contiguous in X,Y, or K, only in R!) The diagram you describe can be created with: Prelude> :l GridZipper *GridZipper> let f &&& g = \x -> (f x, g x) *GridZipper> let f >>> g = g . f *GridZipper> const (newGrid :: Grid String) >>> fromTree
west >>> west >>> setValue (Just "A: X=-2,Y=0,R=2,K=4") west >>> setValue (Just "B: X=-3,Y=0,R=3,K=6") east >>> east >>> east east >>> east >>> setValue (Just "C: X= 2,Y=0,R=2,K=0") assocList >>> show >>> putStrLn $ ()
-- The tree is this: [(XY (-2) 0,"A: X=-2,Y=0,R=2,K=4"), (XY (-3) 0,"B: X=-3,Y=0,R=3,K=6"), (XY 2 0,"C: X= 2,Y=0,R=2,K=0")] -- Zipper starts at origin: Loc {tree = Node {rootLabel = GridLabel (RK 0 0) Nothing, subForest = []}, lefts = [], rights = [], parents = []} -- Zipper after walking to A and setting value: Loc {tree = Node {rootLabel = GridLabel (RK 2 4) (Just "A: X=-2,Y=0,R=2,K=4"), subForest = []}, lefts = [], rights = [], parents = [([],GridLabel (RK 1 2) Nothing,[]) ,([],GridLabel (RK 0 0) Nothing,[])]} -- Zipper after walking to B and setting value: Loc {tree = Node {rootLabel = GridLabel (RK 3 6) (Just "B: X=-3,Y=0,R=3,K=6"), subForest = []}, lefts = [], rights = [], parents = [([],GridLabel (RK 2 4) (Just "A: X=-2,Y=0,R=2,K=4"), []),([],GridLabel (RK 1 2) Nothing,[]) ,([],GridLabel (RK 0 0) Nothing,[])]} -- Zipper where it left off at C: (Loc {tree = Node {rootLabel = GridLabel (RK 2 0) (Just "C: X=2,Y=0,R=2,K=0"), subForest = []}, lefts = [], rights = [], parents = [([Node {rootLabel = GridLabel (RK 1 2) Nothing, subForest = [Node {rootLabel = GridLabel (RK 2 4) (Just "A: X=-2,Y=0,R=2,K=4"), subForest = [Node {rootLabel = GridLabel (RK 3 6) (Just "B: X=-3,Y=0,R=3,K=6"), subForest = []}]}]}], GridLabel (RK 1 0) Nothing,[]), ([],GridLabel (RK 0 0) Nothing,[])]}, -- Zipper at origin Loc {tree = Node {rootLabel = GridLabel (RK 0 0) Nothing, subForest = [Node {rootLabel = GridLabel (RK 1 2) Nothing, subForest = [Node {rootLabel = GridLabel (RK 2 4) (Just "A: X=-2,Y=0,R=2,K=4"), subForest = [Node {rootLabel = GridLabel (RK 3 6) (Just "B: X=-3,Y=0,R=3,K=6"), subForest = [] } ]} ]}, Node {rootLabel = GridLabel (RK 1 0) Nothing, subForest = [Node {rootLabel = GridLabel (RK 2 0) (Just "C: X=2,Y=0,R=2,K=0"), subForest = [] }] }]}, lefts = [], rights = [], parents = []}) Apfelmus, Heinrich wrote:
Dan Weston wrote:
For the 2D grid zipper above, moving around is O(1) but update is O(log n). This is acceptable; also because I'm quite confident that a zipper for a 2D grid with everything O(1) does not exist. I can prove that for a special case and should probably write it down at some point. Really? My solution (rose tree zipper where tree depth is manhattan distance from origin and forest width is nodes around concentric diamonds, see http://permalink.gmane.org/gmane.comp.lang.haskell.cafe/49948) was designed specifically to be amortized constant for everything for paths that do not specifically move helically around the origin. The complexity of lookup is O(d) where d is the number of defined nodes at a given radius. Until the grid gets pretty dense, d grows very slowly for most sane paths.
Have I missed something?
From your description (without reading the code ;)), I gather that your tree looks something like this?
-+- / \ -+ -+- +- / / \ \ -+ -+ -+- +- +- / / / \ \ \ -+ -+ -+ -+- +- +- +- / / / / \ \ \ \ + B A + +--+--C--+--+-- ... \ \ \ \ / / / / -+ -+ -+ -+- +- +- +- \ \ \ / / / -+ -+ -+- +- +- \ \ / / -+ -+- +- \ / -+-
The root of the tree is the center and you can descend on the right. But with this structure, walking from A to B is O(d) = O(n) (where d is the distance from the origin, n the side length of the grid) instead of O(1).
Put differently, using Data.Tree.Zipper.parent on B will move you to C, not to A.
I mean, O(d) may be fine for you, but it's not O(1) for everything as advertised. :)
Regards, H. Apfelmus
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Dan Weston wrote:
I hope the code is better than my description! :) The structure is more like
Nothing(RK 0 _) Nothing(RK 1 _) A(RK 2 4) B(RK 3 6) C(RK 2 0)
The root of the tree is the center and you can descend on the right. But with this structure, walking from A to B is O(d) = O(n) (where d is the distance from the origin, n the side length of the grid) instead of O(1).
No. The tree is [[Node]], where the outer list has one element for each radius that has an occupied node and each inner list has the number of nodes at the given radius.
You descend the spine of the outer list radially in O(deltaR) time, which for incremental moves is O(1).
Then you search for an existing inner list element in O(nk(r)), which stays fairly constant for reasonable paths (basically, the width of a path swath).
Ah, so you're using a sparse representation for grids. That's a good idea! Unfortunately, it doesn't help when the grid is a full rectangle, i.e. when nk(r) becomes proportional to r. The (most likely unattainable) goal I had in mind is to create a zipper for the full grid that supports O(1) operations.
I mean, O(d) may be fine for you, but it's not O(1) for everything as advertised. :)
d is not the distance from the origin, it is nk(r), the number of nodes at a given radius: d(2) = 2, d(3) = 1.
Oh, right.
An outward radial path will only expand the tree linearly, not quadratically, in size.
Well, that's still linear in the side length of a full grid. Directly using Data.Map (Integer,Integer) a would improve that to a logarithm. Of course, your structure can be enhanced by using a Data.Map instead of a linked list for each ring à la [Data.Map Integer a] This will give O(log nk(r)) movements, but that's still not constant time. Regards, H. Apfelmus

Is it possible to change a particular node of the doubly linked list? That is to say, that would like to have a function: update :: DList a -> a -> DList a where update node newValue returns a list where only the value at the node which is passed in is set to the new Value and all other values are the same.
What you need is for the nodes to keep track of the length of the list. Here's a different solution from that oleg posted, to me it's slightly more intuitive, since the updates work directly on the dlists instead of via (elegant) proxy functions. ---------------------------------------------------------------------- module DList where data DList a = DNode Int (DList a) a (DList a) | Empty mkDList :: [a] -> DList a mkDList [] = Empty mkDList xs = let len = length xs this = DNode len farLeft (head xs) nearRight (nearRight,farLeft) = mkRestDList len (tail xs) this this in this mkRestDList :: Int -> [a] -> DList a -> DList a -> (DList a, DList a) mkRestDList _ [] _ farRight = (farRight, farRight) -- will only happen if the initial list is singleton mkRestDList len [x] nearLeft farRight = let this = DNode len nearLeft x farRight in (this, this) mkRestDList len (x:xs) nearLeft farRight = let this = DNode len nearLeft x nearRight (nearRight,farLeft) = mkRestDList len xs this farRight in (this,farLeft) takeD :: Int -> DList a -> [a] takeD 0 _ = [] takeD _ Empty = [] takeD n (DNode _ _ x r) = x : takeD (n-1) r leftD, rightD :: DList a -> DList a leftD Empty = Empty leftD (DNode _ l _ _) = l rightD Empty = Empty rightD (DNode _ _ _ r) = r updateD :: a -> DList a -> DList a updateD _ Empty = Empty updateD x (DNode len _ _ r) = let this = DNode len farLeft x nearRight (nearRight,farLeft) = updateRestD (len-1) r this this in this updateRestD :: Int -> DList a -> DList a -> DList a -> (DList a, DList a) updateRestD 0 _ _ farRight = (farRight, farRight) -- will only happen if the initial list is singleton updateRestD 1 (DNode len _ x _) nearLeft farRight = let this = DNode len nearLeft x farRight in (this, this) updateRestD n (DNode len _ x r) nearLeft farRight = let this = DNode len nearLeft x nearRight (nearRight,farLeft) = updateRestD (n-1) r this farRight in (this,farLeft) updateRestD _ Empty _ _ = undefined -- can't happen ----------------------------------------------------- *DList> let dl = mkDList [1..5] *DList> takeD 11 dl [1,2,3,4,5,1,2,3,4,5,1] *DList> let dl' = updateD (-1) dl *DList> takeD 11 dl' [-1,2,3,4,5,-1,2,3,4,5,-1] Cheers, /Niklas

G'Day,
and phew... quite a lot of code to grok. Thanks for the answers, they're much
appreciated.
On Sun, Jan 4, 2009 at 1:43 AM, Niklas Broberg
What you need is for the nodes to keep track of the length of the list. Here's a different solution from that oleg posted, to me it's slightly more intuitive, since the updates work directly on the dlists instead of via (elegant) proxy functions.
I had exactly the same thoughts after I realized that, if one wants to update only the non cyclic part of the list one has to know where the non cyclic part ends. But the only way to know that, is by keeping track of the length of the list and using this to find out when to tie the knot. So your solution is also more intuitive to me but if I'm not mistaken it has update complexity linear in the number of elements in the list whereas Oleg's solution is logarithmic.
mkRestDList :: Int -> [a] -> DList a -> DList a -> (DList a, DList a) mkRestDList _ [] _ farRight = (farRight, farRight) -- will only happen if the initial list is singleton mkRestDList len [x] nearLeft farRight = let this = DNode len nearLeft x farRight in (this, this) mkRestDList len (x:xs) nearLeft farRight = let this = DNode len nearLeft x nearRight (nearRight,farLeft) = mkRestDList len xs this farRight in (this,farLeft)
updateRestD :: Int -> DList a -> DList a -> DList a -> (DList a, DList a) updateRestD 0 _ _ farRight = (farRight, farRight) -- will only happen if the initial list is singleton updateRestD 1 (DNode len _ x _) nearLeft farRight = let this = DNode len nearLeft x farRight in (this, this) updateRestD n (DNode len _ x r) nearLeft farRight = let this = DNode len nearLeft x nearRight (nearRight,farLeft) = updateRestD (n-1) r this farRight in (this,farLeft) updateRestD _ Empty _ _ = undefined -- can't happen
I think you can drop the second case in those two functions if you rewrite the
first case like this:
mkRestDList _ [] nearLeft farRight = (farRight, nearLeft)
resp.
updateRestD 0 _ nearLeft farRight = (farRight, nearLeft)
On Sat, Jan 3, 2009 at 8:51 PM,
Stephan Guenther wrote:
The algorithm is essentially imperative (and so permits identity checking and in-place `updates') but implemented purely functionally. No destructive updates are ever used. Therefore, all the changes can be undone and re-done, and the code is MT-safe. The code is easily generalizable to 2D.
Thanks for your answer. As I'll explain below I also thought about using a Map for the 2D case, but wouldn't have thought of it in the one dimensional case as my intuition would have been to use Niklas' solution there. Thanks for putting my thoughts in a different direction. Yet the thing that really puzzled me in the list case was, that I was searching for a solution without using auxiliary data like the length or delegating the update to a data structure which already supported it. I'm pretty sure by now that its impossible without using zippers or something else.
It is not for nothing Haskell is called the best imperative language. One can implement imperative algorithms just as they are -- purely functionally, without any monads or other categorical notions. Amen to that.
-- The insert operation below makes a cyclic list -- The other operations don't care -- Insert to the right of the current element, if any -- Return the DL where the inserted node is the current one insert_right :: a -> DList a -> DList a insert_right x dl | is_empty dl = let ref = dl_counter dl -- the following makes the list cyclic node = Node{node_val = x, node_left = ref, node_right = ref} in DList{dl_counter = succ ref, dl_current = ref, dl_mem = IM.insert ref node (dl_mem dl)}
insert_right x dl@DList{dl_counter = ref, dl_current = curr, dl_mem = mem} = DList{dl_counter = succ ref, dl_current = ref, dl_mem = IM.insert ref new_node $ IM.insert curr curr_node' mem} where curr_node = get_curr_node dl curr_node'= curr_node{node_right = ref} new_node = Node{node_val = x, node_left = curr, node_right = node_right curr_node} Could it be that there's a small inconsistency in the fact that if you don't update the left_node ref of curr_node? This is nearly never a problem except when you do insert_right on a DList with only one element. In that case node_left of curr_node references itself and should be updated to reference it's new right (and therefore also left wraparound) neighbour. If I'm right this leads to the fact that DList is only right cyclic while the left end always wraps around to itself. I know that this is easily corrected (if wanted), I just want to know if I'm understanding the code correctly.
On Sat, Jan 3, 2009 at 10:37 PM, Apfelmus, Heinrich
Ah, so you have a rectangular (or later hexagonal?) 2D grid? I suggest representing it as
Data.Map (Integer, Integer) a
as explained below. Right on the button. This is exactly what I need. And I also contemplated doing it with indexing into Data.Map but decided against it because of the lookup complexity. It might very well be the case that this is a non issue but I'd rather not loose the O(1) neighbour lookup and O(1) update. OTOH hand I'm aware of the fact that using TVars very well might hurt performance if I'm not careful with my transactions since the way TVars are managed would give me worse complexity again. So for now I'm going with TVars while still keeping in mind to maybe try the Data.Map approach later to see how it pans out.
For the 2D grid zipper above, moving around is O(1) but update is O(log n). This is acceptable; also because I'm quite confident that a zipper for a 2D grid with everything O(1) does not exist. I can prove that for a special case and should probably write it down at some point.
I would be pretty interested in the proof, since when I was trying to generalize zippers I wanted to keep the nice O(1) on everything. And that was exactly what I couldn't bring together with non trivial cycles. I should point out that this is the point where my thoughts diverged. With the doubly linked list example I wasn't concerned with performance I just wanted to figure out a way to do updates in on circular DLists with proper sharing and no additional data or data structures. With my real world needs i.e. the 2D example I wanted to find a way to keep the performance while remaining pure.
My personal experience is that not going with the obvious but messy solution but searching for a more elegant one is always faster in the long run. :) Not only that but I also have the slight feeling that haskell would reward me for choosing the Data.Map approach. But I need a little bit of training on TVars and STM anyways so I'm going for this. For now that is. ;)
Big thanks. I already learned a lot from this thread. Cheers Stephan
participants (7)
-
Apfelmus, Heinrich
-
Dan Weston
-
Derek Elkins
-
Martijn van Steenbergen
-
Niklas Broberg
-
Ryan Ingram
-
S. Günther