Painting logs to get a coloured tree

Hi, I have a problem that, it seems, I can not solve cleanly without resorting to imperative programming (via ST): Assume you have a tree (and you can think of a real tree here), defined by something like this: data Tree a = Bud | Branch a Double Tree Tree -- | ` Lenght of this branch -- ` General storage field for additional information Now, I have a nice algorithm that calulates something for each branch, but it only works on lists of branches, so I have to cut them apart first, remembering their position in space, and then work on these, well, logs. data Point = Point Double Double data Log = Log Point Point type Info = ... noInfo :: Info cutTreeApart :: Tree a -> [(Log, a)] someAlgorithm :: [(Log,a)] -> [(a, Info)] Conveniently, the algorithm allows me to tag the logs with something, to be able to keep track at least somewhat of the logs. Unfortunately, I need this information in the storage field in my Tree, as the list of logs is not sufficient for later calculations. Idea: Using ST ============== annotateTree :: Tree a -> Tree Info annotateTree tree = runSt $ do -- Put an STRef in each node treeWithPointer <- mapM const (newSTRef noInfo) tree -- Cut this tree apart let logsWithPointers = cutTreeApart treeWithPointer -- Run the algorithm let informations = someAlgorithm logsWithPointers -- Put the information back, via the ST ref mapM (\(stRef, info) -> writeSTRef stRef info) informations -- Read the ST refs mapM readIORef tree Note that I assume a instance Traversable Tree here, and mapM is Data.Traversable.mapM. Now while this works, and while ST is still somewhat pure, I’m wondering if there is no better way of expressing "This piece of information came from the point in a data structure, so something else can be put here easily". Some ideas where numbering the Nodes and then using this number as the tag on the log, but this is not much different from using STRefs, it seems. Thanks, Joachim -- Joachim "nomeata" Breitner mail: mail@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C JID: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/ Debian Developer: nomeata@debian.org

2009/2/9 Joachim Breitner
Now while this works, and while ST is still somewhat pure, I'm wondering if there is no better way of expressing "This piece of information came from the point in a data structure, so something else can be put here easily".
You might want to look into zippers: http://haskell.org/haskellwiki/Zipper Luke

Hi, Am Montag, den 09.02.2009, 16:41 -0700 schrieb Luke Palmer:
2009/2/9 Joachim Breitner
Now while this works, and while ST is still somewhat pure, I'm wondering if there is no better way of expressing "This piece of information came from the point in a data structure, so something else can be put here easily". You might want to look into zippers: http://haskell.org/haskellwiki/Zipper
I thought about Zippers, but I understand that they improve _navigating_ in a Tree-like structure, or to refrence _one_ position in a tree. But if I would deconstruct my tree to the list of _all_ locations, with
type Loc a = (Tree a, Cxt a) and then run my algorithm that returns [(Loc a, Info)], it’s still not clear to me how I can combine all of these locations to get back my original Tree, annotated with the Info returned.
Thanks nevertheless, Joachim -- Joachim "nomeata" Breitner mail: mail@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C JID: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/ Debian Developer: nomeata@debian.org

2009/2/10 Joachim Breitner
Hi,
Am Montag, den 09.02.2009, 16:41 -0700 schrieb Luke Palmer:
2009/2/9 Joachim Breitner
Now while this works, and while ST is still somewhat pure, I'm wondering if there is no better way of expressing "This piece of information came from the point in a data structure, so something else can be put here easily". You might want to look into zippers: http://haskell.org/haskellwiki/Zipper
I thought about Zippers, but I understand that they improve _navigating_ in a Tree-like structure, or to refrence _one_ position in a tree.
But if I would deconstruct my tree to the list of _all_ locations, with
type Loc a = (Tree a, Cxt a) and then run my algorithm that returns [(Loc a, Info)], it's still not clear to me how I can combine all of these locations to get back my original Tree, annotated with the Info returned.
I guess I just repeat your last praragraph of your original mail but it seems to me you can mapAccump some 'names' on the tree, process an association list (or an IntMap) of the (name,log) then map the three again using the result. In spirits, it's the same thing than the STRef solution but it seems cleaner to me. Cheers, Thu

2009/2/10 minh thu
2009/2/10 Joachim Breitner
: Hi,
Am Montag, den 09.02.2009, 16:41 -0700 schrieb Luke Palmer:
2009/2/9 Joachim Breitner
Now while this works, and while ST is still somewhat pure, I'm wondering if there is no better way of expressing "This piece of information came from the point in a data structure, so something else can be put here easily". You might want to look into zippers: http://haskell.org/haskellwiki/Zipper
I thought about Zippers, but I understand that they improve _navigating_ in a Tree-like structure, or to refrence _one_ position in a tree.
But if I would deconstruct my tree to the list of _all_ locations, with
type Loc a = (Tree a, Cxt a) and then run my algorithm that returns [(Loc a, Info)], it's still not clear to me how I can combine all of these locations to get back my original Tree, annotated with the Info returned.
I guess I just repeat your last praragraph of your original mail but it seems to me you can mapAccump some 'names' on the tree, process an association list (or an IntMap) of the (name,log) then map the three again using the result. In spirits, it's the same thing than the STRef solution but it seems cleaner to me.
I forgot to mention you can try to tie the knot too, using the result of the processing in the first mapping (and then you don't need the second one)...

Hi, Am Dienstag, den 10.02.2009, 10:05 +0100 schrieb minh thu:
I forgot to mention you can try to tie the knot too, using the result of the processing in the first mapping (and then you don't need the second one)...
could you elaborate who to tie that particular knot? I unfortunately, I don’t see it. Thanks, Joachim -- Joachim "nomeata" Breitner mail: mail@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C JID: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/ Debian Developer: nomeata@debian.org

2009/2/10 Joachim Breitner
Hi,
Am Dienstag, den 10.02.2009, 10:05 +0100 schrieb minh thu:
I forgot to mention you can try to tie the knot too, using the result of the processing in the first mapping (and then you don't need the second one)...
could you elaborate who to tie that particular knot? I unfortunately, I don't see it.
Thanks, Joachim
I can post some code later but here is the idea. You conceptually label the tree with Int's. If you go through the tree visiting the node in a specific order, you don't have to actually label it since the label of a node is just its position in the parcour. The goal is to map the tree with some data drawn from an association-list. Again, a straight-forward association is just a plain list indexed by Int's. Thus, when visiting the nodes of the tree, if you have the above-mentionned list, you can use that information when doing the mapping, replacing the data in the node by the data in the list (where the index used for the list is the 'label' of the node). The list is the result of going to the tree too, thus tying the knot. To construct it, you simply make some kind of mapAccum, using [] as the starting value and : (cons) to accumulate the data. To understand this intuitiveley, just note that a three can be flattened into a list. Thus if you want to process the 'association-list' which is represented by a plain list, just zipWith it [0..]. Cheers, Thu

2009/2/10 minh thu
2009/2/10 Joachim Breitner
: Hi,
Am Dienstag, den 10.02.2009, 10:05 +0100 schrieb minh thu:
I forgot to mention you can try to tie the knot too, using the result of the processing in the first mapping (and then you don't need the second one)...
could you elaborate who to tie that particular knot? I unfortunately, I don't see it.
Thanks, Joachim
I can post some code later but here is the idea.
You conceptually label the tree with Int's. If you go through the tree visiting the node in a specific order, you don't have to actually label it since the label of a node is just its position in the parcour.
The goal is to map the tree with some data drawn from an association-list. Again, a straight-forward association is just a plain list indexed by Int's.
Thus, when visiting the nodes of the tree, if you have the above-mentionned list, you can use that information when doing the mapping, replacing the data in the node by the data in the list (where the index used for the list is the 'label' of the node).
The list is the result of going to the tree too, thus tying the knot. To construct it, you simply make some kind of mapAccum, using [] as the starting value and : (cons) to accumulate the data.
To understand this intuitiveley, just note that a three can be flattened into a list. Thus if you want to process the 'association-list' which is represented by a plain list, just zipWith it [0..].
So here some code, notice the process function which work on a list of data (drawn from the tree). As said above, it can make use of a [0..] list if the 'tags' or 'names' are needed for processing. Is it applicable to your problem ? -------------------------- module Log where data Tree a = Bud | Branch a (Tree a) (Tree a) -- no length here deriving Show mapAcc f acc Bud = (acc, Bud) mapAcc f acc (Branch a l r) = (acc2, Branch a' l' r') where (acc0,a') = f acc a (acc1,l') = mapAcc f acc0 l (acc2,r') = mapAcc f acc1 r tree0 = Bud tree1 = Branch "a" Bud Bud tree2 = Branch "r" (Branch "s" Bud Bud) Bud tree3 = Branch "x" (Branch "y" tree1 tree2) Bud process :: [String] -> [String] process l = zipWith (\a b -> a ++ show b) l [0..] tie tree = tree' where ((acc,q),tree') = mapAcc (\(acc,p) a -> ((acc + 1,a:p),r !! acc)) (0,[]) tree r = process (reverse q)

Hi, Am Dienstag, den 10.02.2009, 16:36 +0100 schrieb minh thu:
So here some code, notice the process function which work on a list of data (drawn from the tree). As said above, it can make use of a [0..] list if the 'tags' or 'names' are needed for processing.
Is it applicable to your problem ?
--------------------------
module Log where
data Tree a = Bud | Branch a (Tree a) (Tree a) -- no length here deriving Show
mapAcc f acc Bud = (acc, Bud) mapAcc f acc (Branch a l r) = (acc2, Branch a' l' r') where (acc0,a') = f acc a (acc1,l') = mapAcc f acc0 l (acc2,r') = mapAcc f acc1 r
tree0 = Bud tree1 = Branch "a" Bud Bud tree2 = Branch "r" (Branch "s" Bud Bud) Bud tree3 = Branch "x" (Branch "y" tree1 tree2) Bud
process :: [String] -> [String] process l = zipWith (\a b -> a ++ show b) l [0..]
tie tree = tree' where ((acc,q),tree') = mapAcc (\(acc,p) a -> ((acc + 1,a:p),r !! acc)) (0,[]) tree r = process (reverse q)
thanks for your work. It doesn’t fit directly (if the process operation reorders the elements of the list, it fails). But if I first number them, and later sort them again, or use lookup instead of !!, it would work. But the knot-tying (and thus the single traversal of the tree) is a very neat idea. Greetings, Joachim -- Joachim Breitner e-Mail: mail@joachim-breitner.de Homepage: http://www.joachim-breitner.de ICQ#: 74513189 Jabber-ID: nomeata@joachim-breitner.de

minh thu wrote:
Joachim Breitner:
I thought about Zippers, but I understand that they improve _navigating_ in a Tree-like structure, or to refrence _one_ position in a tree.
But if I would deconstruct my tree to the list of _all_ locations, with
type Loc a = (Tree a, Cxt a) and then run my algorithm that returns [(Loc a, Info)], it's still not clear to me how I can combine all of these locations to get back my original Tree, annotated with the Info returned.
I guess I just repeat your last praragraph of your original mail but it seems to me you can mapAccump some 'names' on the tree, process an association list (or an IntMap) of the (name,log) then map the three again using the result. In spirits, it's the same thing than the STRef solution but it seems cleaner to me.
It might also be worth looking at Okasaki's algorithm for (breadth-first) numbering of nodes in a tree[1]. Assuming your tree doesn't have interesting invariants to maintain, a similar/inverse algorithm could be used to "unfold" a list of logs back into a tree. As minh thu says, the numbering seems like it only needs to be conceptual rather than actual. In which case you should be able to fuse the code that traverses the tree to produce logs and the code that traverses the logs to produce a tree (aka a hylomorphism, if you're familiar). The knot-tying step should only be necessary if constructing the tree from logs requires more information than whatever's local to the log itself. Of course, if global information is necessary then you probably _do_ need to actually label the tree. At least it's cleaner than STRefs since you don't need mutability. [1] http://www.eecs.usma.edu/webs/people/okasaki/pubs.html#icfp00 -- Live well, ~wren

Joachim Breitner wrote:
Assume you have a tree (and you can think of a real tree here), defined by something like this:
data Tree a = Bud | Branch a Double Tree Tree -- | ` Lenght of this branch -- ` General storage field for additional information
Now, I have a nice algorithm that calulates something for each branch, but it only works on lists of branches, so I have to cut them apart first, remembering their position in space, and then work on these, well, logs.
data Point = Point Double Double data Log = Log Point Point type Info = ... noInfo :: Info
cutTreeApart :: Tree a -> [(Log, a)] someAlgorithm :: [(Log,a)] -> [(a, Info)]
Conveniently, the algorithm allows me to tag the logs with something, to be able to keep track at least somewhat of the logs.
[...]
Some ideas where numbering the Nodes and then using this number as the tag on the log, but this is not much different from using STRefs, it seems.
Yes, tagging the logs with their position in the tree isn't really different from using STRefs. There are many options for representing positions (depth/breath first numbers; paths like [L,R,L,...] etc.) but in the end, it boils down to the same thing. Here's an example with with numbers annotate tree = thread tree (\(x:xs) -> (x,xs)) . map snd . sort (comparing fst) . someAlgorithm . cutTreeApart . thread tree (\n -> (n, succ n)) $ (0 :: Int) where thread tree f x = evalState (mapM (const $ State f) tree) x However, I would be surprised if someAlgorithm could not be formulated directly on the tree or at least satisfies a few invariants like for example map fst . someAlgorithm = map snd Also, how does cutTreeApart arrange the list? The idea is that most of the tree structure survives in the list and can be reconstructed. Regards, apfelmus -- http://apfelmus.nfshost.com

Hi, Am Dienstag, den 10.02.2009, 11:59 +0100 schrieb Heinrich Apfelmus:
However, I would be surprised if someAlgorithm could not be formulated directly on the tree or at least satisfies a few invariants like for example
map fst . someAlgorithm = map snd
Also, how does cutTreeApart arrange the list? The idea is that most of the tree structure survives in the list and can be reconstructed.
Probably not. My algorithm calculates the amount of light that shines through the branches, and the amount of light cought by the branches (seeing branches as approximations for leaves here :-)). The algorithm works by taking the list of branches (represented by their start and end point), projects them along the direction of light, creates a list of start and endpoints, sorts them (to be able to sweep the line somewhat efficiently) and adds the projections of all intersections of branches. Then it iterates through the intervals on this line, gets the list of branches that are hit by this interval, sorts them by hights and adds, from top to bottom, the appropriate, decreasing portion of the light that comes in this interval. In this process, the branches are sorted around quite a bit, and I assume it would be hard to preserve the structure. If you want to see code (not sure though if you really want to see that code :-)), it’s in http://git.nomeata.de/?p=L-seed.git;a=blob;f=src/Lseed/Geometry.hs Lines 74-142. Greetings, Joachim -- Joachim Breitner e-Mail: mail@joachim-breitner.de Homepage: http://www.joachim-breitner.de ICQ#: 74513189 Jabber-ID: nomeata@joachim-breitner.de
participants (5)
-
Heinrich Apfelmus
-
Joachim Breitner
-
Luke Palmer
-
minh thu
-
wren ng thornton