...
|
...
|
@@ -194,7 +194,7 @@ layoutEqualAngle <- function(tree, branch.length ){
|
194
|
194
|
df$y <- NA
|
195
|
195
|
df$start <- NA # Start angle of segment of subtree.
|
196
|
196
|
df$end <- NA # End angle of segment of subtree
|
197
|
|
- df$angle <- NA # Orthogonal angle to beta ... for labels??
|
|
197
|
+ df$angle <- NA # Orthogonal angle to beta for tip labels.
|
198
|
198
|
## Initialize root node position and angles.
|
199
|
199
|
df[root, "x"] <- 0
|
200
|
200
|
df[root, "y"] <- 0
|
...
|
...
|
@@ -246,7 +246,7 @@ layoutEqualAngle <- function(tree, branch.length ){
|
246
|
246
|
## Calculate (x,y) position of the i-th child node from current node.
|
247
|
247
|
df[child, "x"] <- df[curNode, "x"] + cospi(beta) * length.child
|
248
|
248
|
df[child, "y"] <- df[curNode, "y"] + sinpi(beta) * length.child
|
249
|
|
- ## Calculate orthogonal angle to beta.
|
|
249
|
+ ## Calculate orthogonal angle to beta for tip label.
|
250
|
250
|
df[child, "angle"] <- -90 - 180 * beta * sign(beta - 1)
|
251
|
251
|
## Update the start and end angles of the childs segment.
|
252
|
252
|
df[child, "start"] <- start
|
...
|
...
|
@@ -641,6 +641,10 @@ rotateTreePoints.df <- function(df, pivot_node, nodes, angle){
|
641
|
641
|
df[node, 'x'] <- cospitheta * delta_x - sinpitheta * delta_y + df[pivot_node, 'x']
|
642
|
642
|
df[node, 'y'] <- sinpitheta * delta_x + cospitheta * delta_y + df[pivot_node, 'y']
|
643
|
643
|
|
|
644
|
+ }
|
|
645
|
+
|
|
646
|
+ # Now update labels of rotated tree.
|
|
647
|
+ for(node in nodes){
|
644
|
648
|
# Update label angle if not root node.
|
645
|
649
|
# get parent
|
646
|
650
|
parent_id <- getParent.df(df, node)
|
...
|
...
|
@@ -648,12 +652,14 @@ rotateTreePoints.df <- function(df, pivot_node, nodes, angle){
|
648
|
652
|
if( parent_id != 0){
|
649
|
653
|
theta_parent_child <- getNodeAngle.df(df, parent_id, node)
|
650
|
654
|
if(!is.na(theta_parent_child)){
|
651
|
|
- # Update label angle
|
652
|
|
- df[node, 'angle'] <- -90 - 180 * theta_parent_child * sign(theta_parent_child - 1)
|
|
655
|
+ # Update tip label angle, that is parallel to edge.
|
|
656
|
+ #df[node, 'angle'] <- -90 - 180 * theta_parent_child * sign(theta_parent_child - 1)
|
|
657
|
+ df[node, 'angle'] <- 180 * theta_parent_child
|
653
|
658
|
}
|
654
|
659
|
}
|
655
|
|
-
|
656
|
660
|
}
|
|
661
|
+
|
|
662
|
+
|
657
|
663
|
return(df)
|
658
|
664
|
}
|
659
|
665
|
|