
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