source: branches/stable/ARBDB/TreeNode.cxx

Last change on this file was 18643, checked in by westram, 3 years ago
  • allow to 'edit bootstraps'
    • document example.
    • when a replacement results in an empty string ⇒ remove remark.
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 31.9 KB
Line 
1// ================================================================ //
2//                                                                  //
3//   File      : TreeNode.cxx                                       //
4//   Purpose   :                                                    //
5//                                                                  //
6//   Coded by Ralf Westram (coder@reallysoft.de) in December 2013   //
7//   Institute of Microbiology (Technical University Munich)        //
8//   http://www.arb-home.de/                                        //
9//                                                                  //
10// ================================================================ //
11
12#include "TreeNode.h"
13#include <arb_progress.h>
14#include <arb_str.h>
15#include <map>
16#include <set>
17#include <cmath> // needed with 4.4.3 (but not with 4.7.3)
18
19// ------------------
20//      TreeRoot
21
22TreeRoot::~TreeRoot() {
23    deleteWithNodes = false; // avoid recursive call of ~TreeRoot (obsolete?)
24    rt_assert(!rootNode);    // you have to call TreeRoot::predelete() before dtor! you can do this is dtor of that derived class, which defines makeNode/destroyNode
25    // Note: destroying nodes from here is impossible (leads to pure virtual call, as derived class instance of 'this' is already under destruction)
26}
27
28void TreeRoot::change_root(TreeNode *oldroot, TreeNode *newroot) {
29    rt_assert(rootNode == oldroot);
30    rt_assert(implicated(newroot, !newroot->father));
31    rootNode = newroot;
32
33    if (oldroot && oldroot->get_tree_root() && !oldroot->is_inside(newroot)) oldroot->set_tree_root(NULp); // unlink from this
34    if (newroot && newroot->get_tree_root() != this) newroot->set_tree_root(this); // link to this
35}
36
37// --------------------
38//      TreeNode
39
40#if defined(PROVIDE_TREE_STRUCTURE_TESTS)
41
42Validity TreeNode::is_valid() const {
43    rt_assert(knownNonNull(this));
44    Validity valid;
45
46    TreeRoot *troot = get_tree_root();
47    if (troot) {
48        if (is_leaf()) {
49            valid = Validity(!rightson && !leftson, "leaf has son");
50        }
51        else {
52            valid            = Validity(rightson && leftson, "inner node lacks sons");
53            if (valid) valid = get_rightson()->is_valid();
54            if (valid) valid = get_leftson()->is_valid();
55        }
56        if (father) {
57            if (valid) valid = Validity(is_inside(get_father()), "node not inside father subtree");
58            if (valid) valid = Validity(troot->get_root_node()->is_ancestor_of(this), "root is not nodes ancestor");
59            if (valid) valid = Validity(get_father()->get_tree_root() == troot, "node and father have different TreeRoot");
60        }
61        else {
62            if (valid) valid = Validity(troot->get_root_node() == this, "node has no father, but isn't root-node");
63            if (valid) valid = Validity(!is_leaf(), "root-node is leaf"); // leaf@root (tree has to have at least 2 leafs)
64            if (valid) valid = Validity(has_valid_root_remarks(), "root-node has invalid remarks");
65        }
66    }
67    else { // removed node (may be incomplete)
68        if (is_leaf()) {
69            valid = Validity(!rightson && !leftson, "(removed) leaf has son");
70        }
71        else {
72            if (rightson)         valid = get_rightson()->is_valid();
73            if (leftson && valid) valid = get_leftson()->is_valid();
74        }
75        if (father) {
76            if (valid) valid = Validity(is_inside(get_father()), "(removed) node not inside father subtree");
77            if (valid) valid = Validity(get_father()->get_tree_root() == troot, "(removed) node and father have different TreeRoot");
78        }
79    }
80    return valid;
81}
82#endif // PROVIDE_TREE_STRUCTURE_TESTS
83
84void TreeNode::set_tree_root(TreeRoot *new_root) {
85    if (tree_root != new_root) {
86        tree_root = new_root;
87        if (leftson) get_leftson()->set_tree_root(new_root);
88        if (rightson) get_rightson()->set_tree_root(new_root);
89    }
90}
91
92void TreeNode::reorder_subtree(TreeOrder mode) {
93    static const char *smallest_leafname; // has to be set to the alphabetically smallest name (when function exits)
94
95    if (is_leaf()) {
96        smallest_leafname = name;
97    }
98    else {
99        int leftsize  = get_leftson() ->get_leaf_count();
100        int rightsize = get_rightson()->get_leaf_count();
101
102        {
103            bool big_at_top    = leftsize>rightsize;
104            bool big_at_bottom = leftsize<rightsize;
105            bool swap_branches = (mode&ORDER_BIG_DOWN) ? big_at_top : big_at_bottom;
106            if (swap_branches) swap_sons();
107        }
108
109        TreeOrder lmode, rmode;
110        if (mode & (ORDER_BIG_TO_EDGE|ORDER_BIG_TO_CENTER)) { // symmetric
111            if (mode & ORDER_ALTERNATING) mode = TreeOrder(mode^(ORDER_BIG_TO_EDGE|ORDER_BIG_TO_CENTER));
112
113            if (mode & ORDER_BIG_TO_CENTER) {
114                lmode = TreeOrder(mode | ORDER_BIG_DOWN);
115                rmode = TreeOrder(mode & ~ORDER_BIG_DOWN);
116            }
117            else {
118                lmode = TreeOrder(mode & ~ORDER_BIG_DOWN);
119                rmode = TreeOrder(mode | ORDER_BIG_DOWN);
120            }
121        }
122        else { // asymmetric
123            if (mode & ORDER_ALTERNATING) mode = TreeOrder(mode^ORDER_BIG_DOWN);
124
125            lmode = mode;
126            rmode = mode;
127        }
128
129        get_leftson()->reorder_subtree(lmode);
130        const char *leftleafname = smallest_leafname;
131
132        get_rightson()->reorder_subtree(rmode);
133        const char *rightleafname = smallest_leafname;
134
135        if (leftleafname && rightleafname) {
136            int name_cmp = strcmp(leftleafname, rightleafname);
137            if (name_cmp <= 0) {
138                smallest_leafname = leftleafname;
139            }
140            else {
141                smallest_leafname = rightleafname;
142                if (leftsize == rightsize) { // if sizes of subtrees are equal and rightleafname<leftleafname -> swap branches
143                    const char *smallest_leafname_save = smallest_leafname;
144
145                    swap_sons();
146                    get_leftson ()->reorder_subtree(lmode); rt_assert(strcmp(smallest_leafname, rightleafname)== 0);
147                    get_rightson()->reorder_subtree(rmode); rt_assert(strcmp(smallest_leafname, leftleafname) == 0);
148
149                    smallest_leafname = smallest_leafname_save;
150                }
151            }
152        }
153    }
154    rt_assert(smallest_leafname);
155}
156
157void TreeNode::reorder_tree(TreeOrder mode) {
158    /*! beautify tree (does not change topology, only swaps branches)
159     */
160    compute_tree();
161    reorder_subtree(mode);
162}
163
164void TreeNode::rotate_subtree() {
165    if (!is_leaf()) {
166        swap_sons();
167        get_leftson()->rotate_subtree();
168        get_rightson()->rotate_subtree();
169    }
170}
171
172void TreeNode::keelOver(TreeNode *prev, TreeNode *next, double len) {
173    /*! atomic part of set_root operation that keels over edges between new and old root
174     * @param prev previously a son of 'this', will become father
175     * @param next previously the father of 'this', will become son
176     * @param len  length of branch to nextSon
177     */
178
179    if (leftson == prev) {
180        leftson = next;
181        leftlen = len;
182
183        if (keeledOver) {
184            if (inverseLeft) keeledOver = false;
185        }
186        else {
187            keeledOver  = true;
188            inverseLeft = true;
189        }
190    }
191    else {
192        rightson = next;
193        rightlen = len;
194
195        if (keeledOver) {
196            if (!inverseLeft) keeledOver = false;
197        }
198        else {
199            keeledOver  = true;
200            inverseLeft = false;
201        }
202    }
203    father = prev;
204}
205
206void TreeNode::set_root() {
207    /*! set the root at parent edge of this
208     * pointers to tree-nodes remain valid, but all parent-nodes of this change their meaning
209     * (afterwards they will point to [father+brother] instead of [this+brother])
210     * esp. pointers to the root-node will still point to the root-node (which only changed children)
211     */
212
213    if (at_root()) return; // already root
214
215    TreeNode *old_root    = get_root_node();
216    TreeNode *old_brother = is_inside(old_root->get_leftson()) ? old_root->get_rightson() : old_root->get_leftson();
217
218    rt_assert(old_root->has_valid_root_remarks());
219
220    // move remark branches to top
221    {
222        // Note: no remark is lost here (duplicate removed from old root; new duplicate created at new root)
223        SmartCharPtr remarkPtr;
224        if (!is_leaf()) remarkPtr = get_remark_ptr();
225        for (TreeNode *node = this; node->father; node = node->get_father()) {
226            std::swap(node->remark_branch, remarkPtr);
227        }
228    }
229
230    GBT_LEN old_root_len = old_root->leftlen + old_root->rightlen;
231
232    // new node & this init
233    old_root->leftson  = this;
234    old_root->rightson = father; // will be set later
235
236    if (father->leftson == this) {
237        old_root->leftlen = old_root->rightlen = father->leftlen*.5;
238    }
239    else {
240        old_root->leftlen = old_root->rightlen = father->rightlen*.5;
241    }
242
243    TreeNode *next = get_father()->get_father();
244    TreeNode *prev = old_root;
245    TreeNode *pntr = get_father();
246
247    if (father->leftson == this)    father->leftson = old_root; // to set the flag correctly
248
249    // loop from father to son of root, rotate tree
250    while  (next->father) {
251        double len = (next->leftson == pntr) ? next->leftlen : next->rightlen;
252
253        pntr->keelOver(prev, next, len);
254
255        prev = pntr;
256        pntr = next;
257        next = next->get_father();
258    }
259    // now 'next' points to the old root, which has been destroyed above
260    // 'pntr' points to one former son-of-root (the one nearer to new root)
261    //
262    // pointer at oldroot
263    // pntr == brother before old root == next
264
265    pntr->keelOver(prev, old_brother, old_root_len);
266
267    old_brother->father = pntr;
268    father              = old_root;
269
270    rt_assert(get_root_node() == old_root); // the root node itself remains unchanged (its sons change)
271    rt_assert(old_root->has_valid_root_remarks());
272}
273
274TreeNode *TreeNode::findLeafNamed(const char *wantedName) {
275    TreeNode *found = NULp;
276    if (is_leaf()) {
277        if (name && strcmp(name, wantedName) == 0) found = this;
278    }
279    else {
280        found             = get_leftson()->findLeafNamed(wantedName);
281        if (!found) found = get_rightson()->findLeafNamed(wantedName);
282    }
283    return found;
284}
285
286// ----------------------------
287//      find_innermost_edge
288
289class NodeLeafDistance {
290    GBT_LEN downdist, updist;
291    enum { NLD_NODIST = 0, NLD_DOWNDIST, NLD_BOTHDIST } state;
292
293public:
294
295    NodeLeafDistance()
296        : downdist(-1.0),
297          updist(-1.0),
298          state(NLD_NODIST)
299    {}
300
301    GBT_LEN get_downdist() const { rt_assert(state >= NLD_DOWNDIST); return downdist; }
302    void set_downdist(GBT_LEN DownDist) {
303        if (state < NLD_DOWNDIST) state = NLD_DOWNDIST;
304        downdist = DownDist;
305    }
306
307    GBT_LEN get_updist() const { rt_assert(state >= NLD_BOTHDIST); return updist; }
308    void set_updist(GBT_LEN UpDist) {
309        if (state < NLD_BOTHDIST) state = NLD_BOTHDIST;
310        updist = UpDist;
311    }
312
313};
314
315class EdgeFinder {
316    std::map<TreeNode*, NodeLeafDistance> data; // maximum distance to farthest leaf
317
318    ARB_edge innermost;
319    double   min_distdiff; // abs diff between up- and downdiff
320
321    GBT_LEN calc_distdiff(GBT_LEN d1, GBT_LEN d2) { return fabs(d1-d2); }
322
323    void insert_tree(TreeNode *node) {
324        if (node->is_leaf()) {
325            data[node].set_downdist(0.0);
326        }
327        else {
328            insert_tree(node->get_leftson());
329            insert_tree(node->get_rightson());
330
331            data[node].set_downdist(std::max(data[node->get_leftson()].get_downdist()+node->leftlen,
332                                             data[node->get_rightson()].get_downdist()+node->rightlen));
333        }
334    }
335
336    void findBetterEdge_sub(TreeNode *node) {
337        TreeNode *father  = node->get_father();
338        TreeNode *brother = node->get_brother();
339
340        GBT_LEN len      = node->get_branchlength();
341        GBT_LEN brothLen = brother->get_branchlength();
342
343        GBT_LEN upDist   = std::max(data[father].get_updist(), data[brother].get_downdist()+brothLen);
344        GBT_LEN downDist = data[node].get_downdist();
345
346        {
347            GBT_LEN edge_dd = calc_distdiff(upDist, downDist);
348            if (edge_dd<min_distdiff) { // found better edge
349                innermost    = ARB_edge(node, father);
350                min_distdiff = edge_dd;
351            }
352        }
353
354        data[node].set_updist(upDist+len);
355
356        if (!node->is_leaf()) {
357            findBetterEdge_sub(node->get_leftson());
358            findBetterEdge_sub(node->get_rightson());
359        }
360    }
361
362    void findBetterEdge(TreeNode *node) {
363        if (!node->is_leaf()) {
364            findBetterEdge_sub(node->get_leftson());
365            findBetterEdge_sub(node->get_rightson());
366        }
367    }
368
369public:
370    EdgeFinder(TreeNode *rootNode)
371        : innermost(rootNode->get_leftson(), rootNode->get_rightson()) // root-edge
372    {
373        insert_tree(rootNode);
374
375        TreeNode *lson = rootNode->get_leftson();
376        TreeNode *rson = rootNode->get_rightson();
377
378        GBT_LEN rootEdgeLen = rootNode->leftlen + rootNode->rightlen;
379
380        GBT_LEN lddist = data[lson].get_downdist();
381        GBT_LEN rddist = data[rson].get_downdist();
382
383        data[lson].set_updist(rddist+rootEdgeLen);
384        data[rson].set_updist(lddist+rootEdgeLen);
385
386        min_distdiff = calc_distdiff(lddist, rddist);
387
388        findBetterEdge(lson);
389        findBetterEdge(rson);
390    }
391
392    const ARB_edge& innermost_edge() const { return innermost; }
393};
394
395ARB_edge TreeRoot::find_innermost_edge() {
396    EdgeFinder edgeFinder(get_root_node());
397    return edgeFinder.innermost_edge();
398}
399
400// ------------------------
401//      multifurcation
402
403class TreeNode::LengthCollector {
404    typedef std::map<TreeNode*,GBT_LEN> LengthMap;
405    typedef std::set<TreeNode*>         NodeSet;
406
407    LengthMap eliminatedParentLength;
408    LengthMap addedParentLength;
409
410public:
411    void eliminate_parent_edge(TreeNode *node) {
412        rt_assert(!node->is_root_node());
413        eliminatedParentLength[node] += parentEdge(node).eliminate();
414    }
415
416    void add_parent_length(TreeNode *node, GBT_LEN addLen) {
417        rt_assert(!node->is_root_node());
418        addedParentLength[node] += addLen;
419    }
420
421    void independent_distribution(bool useProgress) {
422        // step 2: (see caller)
423        arb_progress *progress    = NULp;
424        int           redistCount = 0;
425        if (useProgress) progress = new arb_progress("Distributing eliminated lengths", eliminatedParentLength.size());
426
427        while (!eliminatedParentLength.empty()) { // got eliminated lengths which need to be distributed
428            for (LengthMap::iterator from = eliminatedParentLength.begin(); from != eliminatedParentLength.end(); ++from) {
429                ARB_edge elimEdge = parentEdge(from->first);
430                GBT_LEN  elimLen  = from->second;
431
432                elimEdge.virtually_distribute_length(elimLen, *this);
433                if (progress) ++*progress;
434            }
435            eliminatedParentLength.clear(); // all distributed!
436
437            // handle special cases where distributed length is negative and results in negative destination branches.
438            // Avoid generating negative dest. branchlengths by
439            // - eliminating the dest. branch
440            // - redistributing the additional (negative) length (may cause additional negative lengths on other dest. branches)
441
442            NodeSet handled;
443            for (LengthMap::iterator to = addedParentLength.begin(); to != addedParentLength.end(); ++to) {
444                ARB_edge affectedEdge     = parentEdge(to->first);
445                GBT_LEN  additionalLen    = to->second;
446                double   effective_length = affectedEdge.length() + additionalLen;
447
448                if (effective_length<=0.0) { // negative or zero
449                    affectedEdge.set_length(effective_length);
450                    eliminate_parent_edge(to->first); // adds entry to eliminatedParentLength and causes another additional loop
451                    handled.insert(to->first);
452                }
453            }
454
455            if (progress && !eliminatedParentLength.empty()) {
456                delete progress;
457                ++redistCount;
458                progress = new arb_progress(GBS_global_string("Redistributing negative lengths (#%i)", redistCount), eliminatedParentLength.size());
459            }
460
461            // remove all redistributed nodes
462            for (NodeSet::iterator del = handled.begin(); del != handled.end(); ++del) {
463                addedParentLength.erase(*del);
464            }
465        }
466
467        // step 3:
468        for (LengthMap::iterator to = addedParentLength.begin(); to != addedParentLength.end(); ++to) {
469            ARB_edge affectedEdge     = parentEdge(to->first);
470            GBT_LEN  additionalLen    = to->second;
471            double   effective_length = affectedEdge.length() + additionalLen;
472
473            affectedEdge.set_length(effective_length);
474        }
475
476        if (progress) delete progress;
477    }
478};
479
480GBT_LEN ARB_edge::adjacent_distance() const {
481    //! return length of edges starting from this->dest()
482
483    if (is_edge_to_leaf()) return 0.0;
484    return next().length_or_adjacent_distance() + counter_next().length_or_adjacent_distance();
485}
486
487void ARB_edge::virtually_add_or_distribute_length_forward(GBT_LEN len, TreeNode::LengthCollector& collect) const {
488    rt_assert(!is_nan_or_inf(len));
489    if (length() > 0.0) {
490        collect.add_parent_length(son(), len);
491    }
492    else {
493        if (len != 0.0) virtually_distribute_length_forward(len, collect);
494    }
495}
496
497
498void ARB_edge::virtually_distribute_length_forward(GBT_LEN len, TreeNode::LengthCollector& collect) const {
499    /*! distribute length to edges adjacent in edge direction (i.e. edges starting from this->dest())
500     * Split 'len' proportional to adjacent edges lengths.
501     *
502     * Note: length will not be distributed to tree-struction itself (yet), but collected in 'collect'
503     */
504
505    rt_assert(is_normal(len));
506    rt_assert(!is_edge_to_leaf()); // cannot forward anything (nothing beyond leafs)
507
508    ARB_edge e1 = next();
509    ARB_edge e2 = counter_next();
510
511    GBT_LEN d1 = e1.length_or_adjacent_distance();
512    GBT_LEN d2 = e2.length_or_adjacent_distance();
513
514    len = len/(d1+d2);
515
516    e1.virtually_add_or_distribute_length_forward(len*d1, collect);
517    e2.virtually_add_or_distribute_length_forward(len*d2, collect);
518}
519
520void ARB_edge::virtually_distribute_length(GBT_LEN len, TreeNode::LengthCollector& collect) const {
521    /*! distribute length to all adjacent edges.
522     * Longer edges receive more than shorter ones.
523     *
524     * Edges with length zero will not be changed, instead both edges "beyond"
525     * the edge will be affected (they will be affected equally to direct edges,
526     * because edges at multifurcations are considered to BE direct edges).
527     *
528     * Note: length will not be distributed to tree-struction itself (yet), but collected in 'collect'
529     */
530
531    ARB_edge backEdge = inverse();
532    GBT_LEN len_fwd, len_bwd;
533    {
534        GBT_LEN dist_fwd = adjacent_distance();
535        GBT_LEN dist_bwd = backEdge.adjacent_distance();
536        GBT_LEN lenW     = len/(dist_fwd+dist_bwd);
537        len_fwd          = lenW*dist_fwd;
538        len_bwd          = lenW*dist_bwd;
539
540    }
541
542    if (is_normal(len_fwd)) virtually_distribute_length_forward(len_fwd, collect);
543    if (is_normal(len_bwd)) backEdge.virtually_distribute_length_forward(len_bwd, collect);
544}
545
546void TreeNode::eliminate_and_collect(const multifurc_limits& below, LengthCollector& collect) {
547    /*! eliminate edges specified by 'below' and
548     * store their length in 'collect' for later distribution.
549     */
550    rt_assert(!is_root_node());
551    if (!is_leaf() || below.applyAtLeafs) {
552        double value;
553        if (is_leaf()) {
554            value = 100.0;
555            goto hack; // @@@ remove applyAtLeafs from multifurc_limits (does that really make sense? rethink!)
556        }
557        switch (parse_bootstrap(value)) {
558            case REMARK_NONE:
559                value = 100.0;
560                // fall-through
561            case REMARK_BOOTSTRAP:
562            hack:
563                if (value<below.bootstrap && get_branchlength_unrooted()<below.branchlength) {
564                    collect.eliminate_parent_edge(this);
565                }
566                break;
567
568            case REMARK_OTHER: break;
569        }
570    }
571
572    if (!is_leaf()) {
573        get_leftson() ->eliminate_and_collect(below, collect);
574        get_rightson()->eliminate_and_collect(below, collect);
575    }
576}
577
578void ARB_edge::multifurcate() {
579    /*! eliminate edge and distribute length to adjacent edges
580     * - sets its length to zero
581     * - removes remark (bootstrap)
582     * - distributes length to neighbour-branches
583     */
584    TreeNode::LengthCollector collector;
585    collector.eliminate_parent_edge(son());
586    collector.independent_distribution(false);
587}
588void TreeNode::multifurcate() {
589    /*! eliminate branch from 'this' to 'father' (or brother @ root)
590     * @see ARB_edge::multifurcate()
591     */
592    rt_assert(father); // cannot multifurcate at root; call with son of root to multifurcate root-edge
593    if (father) parentEdge(this).multifurcate();
594}
595
596void TreeNode::set_branchlength_preserving(GBT_LEN new_len) {
597    /*! set branchlength to 'new_len' while preserving overall distance in tree.
598     *
599     * Always works on unrooted tree (i.e. lengths @ root are treated correctly).
600     * Length is preserved as in multifurcate()
601     */
602
603    GBT_LEN old_len = get_branchlength_unrooted();
604    GBT_LEN change  = new_len-old_len;
605
606    char *old_remark = is_leaf() ? NULp : nulldup(get_remark());
607
608    // distribute the negative 'change' to neighbours:
609    set_branchlength_unrooted(-change);
610    multifurcate();
611
612    set_branchlength_unrooted(new_len);
613    if (old_remark) {
614        use_as_remark(old_remark); // restore remark (was removed by multifurcate())
615    }
616#if defined(ASSERTION_USED)
617    else {
618        rt_assert(has_no_remark());
619    }
620#endif
621}
622
623void TreeNode::multifurcate_whole_tree(const multifurc_limits& below) {
624    /*! multifurcate all branches specified by 'below'
625     * - step 1: eliminate all branches, store eliminated lengths
626     * - step 2: calculate length distribution for all adjacent branches (proportionally to original length of each branch)
627     * - step 3: apply distributed length
628     */
629    TreeNode        *root = get_root_node();
630    LengthCollector  collector;
631    arb_progress progress("Multifurcating tree");
632
633    // step 1:
634    progress.subtitle("Collecting branches to eliminate");
635    root->get_leftson()->eliminate_and_collect(below, collector);
636    root->get_rightson()->eliminate_and_collect(below, collector);
637    // root-edge is handled twice by the above calls.
638    // Unproblematic: first call will eliminate root-edge, so second call will do nothing.
639
640    // step 2 and 3:
641    collector.independent_distribution(true);
642}
643
644void TreeNode::remove_bootstrap() {
645    remark_branch.setNull();
646    if (!is_leaf()) {
647        get_leftson()->remove_bootstrap();
648        get_rightson()->remove_bootstrap();
649    }
650}
651
652GB_ERROR TreeNode::apply_aci_to_remarks(const char *aci, const GBL_call_env& callEnv) {
653    GB_ERROR error = NULp;
654    if (!is_leaf()) {
655        {
656            char *new_remark = GB_command_interpreter_in_env(remark_branch.isSet() ? remark_branch.content() : "", aci, callEnv);
657            if (!new_remark) {
658                error = GB_await_error();
659            }
660            else {
661                freeset(new_remark, GBS_trim(new_remark));
662                if (!new_remark[0]) { // skip empty results
663                    free(new_remark);
664                    remark_branch.setNull();
665                }
666                else {
667                    remark_branch = new_remark;
668                }
669            }
670        }
671
672        if (!error) error = get_leftson()->apply_aci_to_remarks(aci, callEnv);
673        if (!error) error = get_rightson()->apply_aci_to_remarks(aci, callEnv);
674    }
675
676    return error;
677}
678void TreeNode::reset_branchlengths() {
679    if (!is_leaf()) {
680        leftlen = rightlen = DEFAULT_BRANCH_LENGTH;
681
682        get_leftson()->reset_branchlengths();
683        get_rightson()->reset_branchlengths();
684    }
685}
686
687void TreeNode::scale_branchlengths(double factor) {
688    if (!is_leaf()) {
689        leftlen  *= factor;
690        rightlen *= factor;
691
692        get_leftson()->scale_branchlengths(factor);
693        get_rightson()->scale_branchlengths(factor);
694    }
695}
696
697GBT_LEN TreeNode::sum_child_lengths() const {
698    if (is_leaf()) return 0.0;
699    return
700        leftlen +
701        rightlen +
702        get_leftson()->sum_child_lengths() +
703        get_rightson()->sum_child_lengths();
704}
705
706void TreeNode::bootstrap2branchlen() {
707    //! copy bootstraps to branchlengths
708    if (is_leaf()) {
709        set_branchlength_unrooted(DEFAULT_BRANCH_LENGTH);
710    }
711    else {
712        if (father) {
713            double         bootstrap;
714            GBT_RemarkType rtype = parse_bootstrap(bootstrap);
715
716            if (rtype == REMARK_BOOTSTRAP) {
717                double len = bootstrap/100.0;
718                set_branchlength_unrooted(len);
719            }
720            else {
721                set_branchlength_unrooted(1.0); // no bootstrap means "100%"
722            }
723        }
724        get_leftson()->bootstrap2branchlen();
725        get_rightson()->bootstrap2branchlen();
726    }
727}
728
729void TreeNode::branchlen2bootstrap() {
730    //! copy branchlengths to bootstraps
731    if (!is_leaf()) {
732        remove_remark();
733        if (!is_root_node()) {
734            set_bootstrap(get_branchlength_unrooted()*100.0);
735        }
736        get_leftson()->branchlen2bootstrap();
737        get_rightson()->branchlen2bootstrap();
738    }
739#if defined(ASSERTION_USED)
740    else {
741        rt_assert(has_no_remark());
742    }
743#endif
744}
745
746TreeNode *TreeNode::fixDeletedSon() {
747    // fix node after one son has been deleted
748    TreeNode *result = NULp;
749
750    if (leftson) {
751        gb_assert(!rightson);
752        result  = get_leftson();
753        leftson = NULp;
754    }
755    else {
756        gb_assert(!leftson);
757        gb_assert(rightson);
758
759        result   = get_rightson();
760        rightson = NULp;
761    }
762
763    // now 'result' contains the lasting tree
764    result->father = father;
765
766    // rescue remarks if possible
767    if (!is_leaf() && !result->is_leaf()) {
768        if (get_remark() && !result->get_remark()) {
769            result->use_as_remark(get_remark_ptr());
770            remove_remark();
771        }
772    }
773
774    if (gb_node && !result->gb_node) { // rescue group if possible
775        result->gb_node = gb_node;
776        gb_node         = NULp;
777    }
778
779    if (!result->father) {
780        get_tree_root()->change_root(this, result);
781    }
782
783    gb_assert(!is_root_node());
784
785    forget_origin();
786    forget_relatives();
787    delete this;
788
789    return result;
790}
791
792const TreeNode *TreeNode::ancestor_common_with(const TreeNode *other) const {
793    if (this == other) return this;
794    if (is_ancestor_of(other)) return this;
795    if (other->is_ancestor_of(this)) return other;
796    return get_father()->ancestor_common_with(other->get_father());
797}
798
799int TreeNode::count_clades() const {
800    if (is_leaf()) return is_clade();
801    return get_leftson()->count_clades() + get_rightson()->count_clades() + is_clade();
802}
803
804#if defined(ASSERTION_USED) || defined(PROVIDE_TREE_STRUCTURE_TESTS)
805bool TreeNode::has_valid_root_remarks() const {
806    // tests whether the root-edge has a valid remark:
807    // - if one son is a leaf, the other son may contain the remark for the root-edge
808    // - if no son is a leaf, both sons shall contain the same remark (or none)
809    rt_assert(is_root_node());
810    return implicated(!get_leftson()->is_leaf() && !get_rightson()->is_leaf(),
811                      ARB_strNULLcmp(get_leftson()->get_remark(), get_rightson()->get_remark()) == 0);
812}
813#endif
814
815// --------------------------------------------------------------------------------
816
817#ifdef UNIT_TESTS
818#ifndef TEST_UNIT_H
819#include <test_unit.h>
820#endif
821
822void TEST_tree_iterator() {
823    GB_shell  shell;
824    GBDATA   *gb_main = GB_open("TEST_trees.arb", "r");
825    {
826        GB_transaction  ta(gb_main);
827        TreeNode       *tree = GBT_read_tree(gb_main, "tree_removal", new SimpleRoot);
828
829        int leafs = GBT_count_leafs(tree);
830        TEST_EXPECT_EQUAL(leafs, 17);
831        TEST_EXPECT_EQUAL(leafs_2_edges(leafs, UNROOTED), 31);
832
833        int iter_steps = ARB_edge::iteration_count(leafs);
834        TEST_EXPECT_EQUAL(iter_steps, 62);
835
836        const ARB_edge start = rootEdge(tree->get_tree_root());
837
838        // iterate forward + count (until same edge reached)
839        int      count       = 0;
840        int      count_leafs = 0;
841        ARB_edge edge        = start;
842        do {
843            ARB_edge next = edge.next();
844            TEST_EXPECT(next.previous() == edge); // test reverse operation
845            edge = next;
846            ++count;
847            if (edge.is_edge_to_leaf()) ++count_leafs;
848        }
849        while (edge != start);
850        TEST_EXPECT_EQUAL(count, iter_steps);
851        TEST_EXPECT_EQUAL(count_leafs, leafs);
852
853        // iterate backward + count (until same edge reached)
854        count       = 0;
855        count_leafs = 0;
856        edge        = start;
857        do {
858            ARB_edge next = edge.previous();
859            TEST_EXPECT(next.next() == edge); // test reverse operation
860            edge = next;
861            ++count;
862            if (edge.is_edge_to_leaf()) ++count_leafs;
863        }
864        while (edge != start);
865        TEST_EXPECT_EQUAL(count, iter_steps);
866        TEST_EXPECT_EQUAL(count_leafs, leafs);
867
868        if (tree) {
869            gb_assert(tree->is_root_node());
870            destroy(tree);
871        }
872    }
873    GB_close(gb_main);
874}
875
876void TEST_tree_branch_modifications() {
877    GB_shell  shell;
878    GBDATA   *gb_main = GB_open("TEST_trees.arb", "r");
879    {
880        const char *left_newick       = "((((((CloTyro3:1.046,CloTyro4:0.061)'40%':0.026,CloTyro2:0.017)'0%':0.017,CloTyrob:0.009)'97%':0.274,CloInnoc:0.371)'0%':0.057,CloBifer:0.388)'53%':0.124,(((CloButy2:0.009,CloButyr:0.000):0.564,CloCarni:0.120)'33%':0.010,CloPaste:0.179)'97%':0.131):0.081;";
881        const char *left_newick_bs2bl = "((((((CloTyro3:0.100,CloTyro4:0.100):0.400,CloTyro2:0.100):0.000,CloTyrob:0.100):0.970,CloInnoc:0.100):0.000,CloBifer:0.100):0.530,(((CloButy2:0.100,CloButyr:0.100):1.000,CloCarni:0.100):0.330,CloPaste:0.100):0.970):0.500;"; // bootstrap2branchlen
882
883        const char *right_newick            = "((((CorAquat:0.084,CurCitre:0.058):0.103,CorGluta:0.522)'17%':0.053,CelBiazo:0.059)'40%':0.207,CytAquat:0.711):0.081;";
884        const char *right_newick_preserved1 = "((((CorAquat:0.084,CurCitre:0.058):0.103,CorGluta:0.522)'17%':0.060,CelBiazo:0.029)'40%':0.231,CytAquat:0.711):0.081;"; // set_branchlength_preserving to 0.029 at CelBiazo
885        const char *right_newick_preserved2 = "((((CorAquat:0.084,CurCitre:0.058):0.103,CorGluta:0.522)'17%':0.041,CelBiazo:0.117)'40%':0.161,CytAquat:0.711):0.081;"; // set_branchlength_preserving to 0.117 at CelBiazo
886        const char *right_newick_bl2bs      = "((((CorAquat,CurCitre)'10%',CorGluta)'5%',CelBiazo)'21%',CytAquat)'100%';"; // branchlen2bootstrap
887
888        NewickFormat BSLEN = NewickFormat(nREMARK|nLENGTH);
889
890        GB_transaction ta(gb_main);
891        {
892            TreeNode *tree = GBT_read_tree(gb_main, "tree_test", new SimpleRoot);
893
894            TreeNode *left  = tree->get_leftson();
895            TreeNode *right = tree->get_rightson();
896
897            TEST_EXPECT_NEWICK(BSLEN, left, left_newick);
898            TEST_EXPECT_NEWICK(BSLEN, right, right_newick);
899
900            left->bootstrap2branchlen();
901            right->branchlen2bootstrap();
902
903            TEST_EXPECT_NEWICK(nLENGTH, left,  left_newick_bs2bl);
904            TEST_EXPECT_NEWICK(nREMARK, right, right_newick_bl2bs);
905
906            destroy(tree);
907        }
908        {
909            TreeNode *tree = GBT_read_tree(gb_main, "tree_test", new SimpleRoot);
910
911            TreeNode *right    = tree->get_rightson();
912            TreeNode *CelBiazo = right->findLeafNamed("CelBiazo");
913
914            CelBiazo->set_branchlength_preserving(CelBiazo->get_branchlength() * 0.5);
915            TEST_EXPECT_NEWICK(BSLEN, right, right_newick_preserved1);
916
917            CelBiazo->set_branchlength_preserving(CelBiazo->get_branchlength() * 4.0);
918            TEST_EXPECT_NEWICK(BSLEN, right, right_newick_preserved2);
919
920            destroy(tree);
921        }
922    }
923    GB_close(gb_main);
924}
925
926TEST_PUBLISH(TEST_tree_branch_modifications);
927
928#endif // UNIT_TESTS
929
930// --------------------------------------------------------------------------------
Note: See TracBrowser for help on using the repository browser.