[Haskell-cafe] Painting logs to get a coloured tree

minh thu noteed at gmail.com
Tue Feb 10 10:36:34 EST 2009


2009/2/10 minh thu <noteed at gmail.com>:
> 2009/2/10 Joachim Breitner <mail at joachim-breitner.de>:
>> 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)


More information about the Haskell-Cafe mailing list