... | ... |
@@ -30,7 +30,7 @@ fortify.phylo <- function(model, data, |
30 | 30 |
} |
31 | 31 |
|
32 | 32 |
if (layout %in% c("equal_angle", "daylight")) { |
33 |
- res <- layout.unrooted(x, layout.method = layout, branch.length = branch.length, ...) |
|
33 |
+ res <- layout.unrooted(model, layout.method = layout, branch.length = branch.length, ...) |
|
34 | 34 |
} else { |
35 | 35 |
if (is.null(x$edge.length) || branch.length == "none") { |
36 | 36 |
xpos <- getXcoord_no_length(x) |
... | ... |
@@ -1,11 +1,11 @@ |
1 | 1 |
|
2 | 2 |
|
3 | 3 |
##' @importFrom ape reorder.phylo |
4 |
-layout.unrooted <- function(tree, branch.length="branch.length", layout.method="equal_angle", ...) { |
|
4 |
+layout.unrooted <- function(model, branch.length="branch.length", layout.method="equal_angle", ...) { |
|
5 | 5 |
|
6 | 6 |
df <- switch(layout.method, |
7 |
- equal_angle = layoutEqualAngle(tree, branch.length), |
|
8 |
- daylight = layoutDaylight(tree, branch.length) |
|
7 |
+ equal_angle = layoutEqualAngle(model, branch.length), |
|
8 |
+ daylight = layoutDaylight(model, branch.length) |
|
9 | 9 |
) |
10 | 10 |
|
11 | 11 |
return(df) |
... | ... |
@@ -36,7 +36,9 @@ set_branch_length_cladogram <- function(tree) { |
36 | 36 |
##' @param tree phylo object |
37 | 37 |
##' @param branch.length set to 'none' for edge length of 1. Otherwise the phylogenetic tree edge length is used. |
38 | 38 |
##' @return tree as data.frame with equal angle layout. |
39 |
-layoutEqualAngle <- function(tree, branch.length ){ |
|
39 |
+layoutEqualAngle <- function(model, branch.length ){ |
|
40 |
+ tree <- as.phylo(model) |
|
41 |
+ |
|
40 | 42 |
if (branch.length == "none") { |
41 | 43 |
tree <- set_branch_length_cladogram(tree) |
42 | 44 |
} |
... | ... |
@@ -44,7 +46,7 @@ layoutEqualAngle <- function(tree, branch.length ){ |
44 | 46 |
root <- getRoot(tree) |
45 | 47 |
## Convert Phylo tree to data.frame. |
46 | 48 |
## df <- as.data.frame.phylo_(tree) |
47 |
- df <- as_data_frame(tree) %>% |
|
49 |
+ df <- as_data_frame(model) %>% |
|
48 | 50 |
mutate_(isTip = ~(! node %in% parent)) |
49 | 51 |
|
50 | 52 |
## NOTE: Angles (start, end, angle) are in half-rotation units (radians/pi or degrees/180) |
... | ... |
@@ -127,15 +129,16 @@ layoutEqualAngle <- function(tree, branch.length ){ |
127 | 129 |
##' nodes = remove tip nodes. |
128 | 130 |
##' |
129 | 131 |
##' ``` |
130 |
-layoutDaylight <- function( tree, branch.length ){ |
|
131 |
- |
|
132 |
+layoutDaylight <- function(model, branch.length ){ |
|
133 |
+ tree <- as.phylo(model) |
|
134 |
+ |
|
132 | 135 |
## How to set optimal |
133 | 136 |
MAX_COUNT <- 5 |
134 | 137 |
MINIMUM_AVERAGE_ANGLE_CHANGE <- 0.05 |
135 | 138 |
|
136 | 139 |
|
137 | 140 |
## Initialize tree. |
138 |
- tree_df <- layoutEqualAngle(tree, branch.length) |
|
141 |
+ tree_df <- layoutEqualAngle(model, branch.length) |
|
139 | 142 |
|
140 | 143 |
## nodes = get list of nodes in tree_df |
141 | 144 |
## Get list of node id's. |