Browse code

remove beast object support as read.beast output treedata object in treeio <2017-12-05, Tue>

guangchuang yu authored on 05/12/2017 11:05:11
Showing 22 changed files

... ...
@@ -13,17 +13,19 @@ Description: 'ggtree' extends the 'ggplot2' plotting system which implemented
13 13
     the grammar of graphics. 'ggtree' is designed for visualization and annotation
14 14
     of phylogenetic trees with their covariates and other associated data.
15 15
 Depends:
16
-    R (>= 3.3.2),
16
+    R (>= 3.4.0),
17 17
     ggplot2 (>= 2.2.0),
18
-    treeio
18
+    treeio (>= 1.3.2)
19 19
 Imports:
20 20
     ape,
21
+    dplyr,
21 22
     grDevices,
22 23
     grid,
23 24
     magrittr,
24 25
     methods,
25 26
     rvcheck,
26 27
     scales,
28
+    tibble,
27 29
     tidyr,
28 30
     utils
29 31
 Suggests:
... ...
@@ -43,4 +45,4 @@ BugReports: https://github.com/GuangchuangYu/ggtree/issues
43 45
 Packaged: 2014-12-03 08:16:14 UTC; root
44 46
 biocViews: Alignment, Annotation, Clustering, DataImport,
45 47
     MultipleSequenceAlignment, ReproducibleResearch, Software, Visualization
46
-RoxygenNote: 6.0.1.9000
48
+RoxygenNote: 6.0.1
... ...
@@ -2,8 +2,7 @@
2 2
 
3 3
 S3method(as.binary,phylo)
4 4
 S3method(as.data.frame,phylo)
5
-S3method(as.data.frame,treedata)
6
-S3method(fortify,beast)
5
+S3method(as_data_frame,treedata)
7 6
 S3method(fortify,codeml)
8 7
 S3method(fortify,codeml_mlc)
9 8
 S3method(fortify,hyphy)
... ...
@@ -81,6 +80,7 @@ export(nodeid)
81 80
 export(nodepie)
82 81
 export(open_tree)
83 82
 export(phylopic)
83
+export(range_format)
84 84
 export(reroot)
85 85
 export(rescale_tree)
86 86
 export(revts)
... ...
@@ -112,6 +112,7 @@ importFrom(ape,ladderize)
112 112
 importFrom(ape,read.tree)
113 113
 importFrom(ape,reorder.phylo)
114 114
 importFrom(ape,write.tree)
115
+importFrom(dplyr,full_join)
115 116
 importFrom(ggplot2,Geom)
116 117
 importFrom(ggplot2,GeomCurve)
117 118
 importFrom(ggplot2,GeomLabel)
... ...
@@ -190,6 +191,8 @@ importFrom(methods,setGeneric)
190 191
 importFrom(methods,setOldClass)
191 192
 importFrom(rvcheck,get_fun_from_pkg)
192 193
 importFrom(scales,alpha)
194
+importFrom(tibble,as_data_frame)
195
+importFrom(tibble,data_frame)
193 196
 importFrom(tidyr,gather)
194 197
 importFrom(treeio,as.phylo)
195 198
 importFrom(treeio,as.treedata)
... ...
@@ -1,5 +1,6 @@
1 1
 CHANGES IN VERSION 1.11.2
2 2
 ------------------------
3
+ o remove beast object support as read.beast output treedata object in treeio <2017-12-05, Tue>
3 4
  o deprecate subview, annotation_image and phylopic; remove theme_transparent <2017-12-04, Mon>
4 5
  o geom_tiplab now supports geom = "image" or geom = "phylopic" <2017-12-04, Mon>
5 6
  o A new layer geom_nodelab that equivalent to geom_tiplab but works for internal node <2017-12-04, Mon>
... ...
@@ -14,13 +14,14 @@ scaleX_by_time_from_mrsd <- function(df, mrsd, as.Date) {
14 14
     date <- Date2decimal(mrsd)
15 15
 
16 16
     df$x <- df$x + date - max(df$x)
17
-    df$branch <- (df[df$parent, "x"] + df[, "x"])/2
17
+    df$branch <- with(df, (x[match(parent, node)] + x)/2)
18
+    ## df$branch <- (df[df$parent, "x"] + df[, "x"])/2
18 19
 
19 20
     if (as.Date) {
20 21
         df$x <- decimal2Date(df$x)
21 22
         df$branch <- decimal2Date(df$branch)
22 23
     }
23
-    
24
+
24 25
     return(df)
25 26
 }
26 27
 
... ...
@@ -28,7 +29,7 @@ scaleX_by_time_from_mrsd <- function(df, mrsd, as.Date) {
28 29
 
29 30
 ##' convert Date to decimal format, eg "2014-05-05" to "2014.34"
30 31
 ##'
31
-##' 
32
+##'
32 33
 ##' @title Date2decimal
33 34
 ##' @param x Date
34 35
 ##' @return numeric
... ...
@@ -38,7 +39,7 @@ Date2decimal <- function(x) {
38 39
     if (is(x, "numeric")) {
39 40
         return(x)
40 41
     }
41
-    
42
+
42 43
     if (is(x, "character")) {
43 44
         x <- as.Date(x)
44 45
     }
... ...
@@ -49,7 +50,7 @@ Date2decimal <- function(x) {
49 50
 
50 51
 ##' convert decimal format to Date, eg "2014.34" to "2014-05-05"
51 52
 ##'
52
-##' 
53
+##'
53 54
 ##' @title decimal2Date
54 55
 ##' @param x numerical number, eg 2014.34
55 56
 ##' @return Date
... ...
@@ -1,31 +1,3 @@
1
-
2
-## ##' @export
3
-## ape::read.tree
4
-
5
-
6
-## ##' generate random tree
7
-## ##' @export
8
-## ##' @rdname rtree
9
-## ##' @param n number of tips in the tree
10
-## ##' @param rooted logcial
11
-## ##' @param tip.label tip label
12
-## ##' @param br one of the following: (i) an R function used to generate the
13
-## ##'           branch lengths ('rtree'; use 'NULL' to simulate only a
14
-## ##'           topology), or the coalescence times ('rcoal'); (ii) a
15
-## ##'           character to simulate a genuine coalescent tree for 'rcoal'
16
-## ##'           (the default); or (iii) a numeric vector for the branch
17
-## ##'           lengths or the coalescence times.
18
-## ##' @param ... additional parameters to be passed to 'br'
19
-## ##' @source
20
-## ##' This is just the imported function
21
-## ##' from the ape package. The documentation you should
22
-## ##' read for the rtree function can be found here: \link[ape]{rtree}
23
-## ##'
24
-## ##' @seealso
25
-## ##' \link[ape]{rtree}
26
-## rtree <- ape::rtree
27
-
28
-
29 1
 ##' merge phylo and output of boot.phylo to 'apeBootstrap' object
30 2
 ##'
31 3
 ##'
... ...
@@ -41,49 +13,3 @@ apeBoot <- function(phylo, boot) {
41 13
     as.treedata(phylo, boot)
42 14
 }
43 15
 
44
-## apeBoot <- function(phylo, boot) {
45
-##     ## phylo is a phylo object
46
-##     ## boot is output from boot.phylo
47
-##     new("apeBootstrap",
48
-##         phylo=phylo,
49
-##         bootstrap=data.frame(node=(1:Nnode(phylo)) + Ntip(phylo), bootstrap=boot)
50
-##         )
51
-## }
52
-
53
-
54
-## ##' @rdname show-methods
55
-## ##' @importFrom ape print.phylo
56
-## ##' @exportMethod show
57
-## setMethod("show", signature(object = "apeBootstrap"),
58
-##           function(object) {
59
-##               cat("'apeBoot' S4 object that stored bootstrap value generated by 'ape::boot.phylo'", ".\n\n")
60
-##               cat("...@ tree: ")
61
-##               print.phylo(get.tree(object))
62
-##           })
63
-
64
-
65
-
66
-
67
-## ##' @rdname groupClade-methods
68
-## ##' @exportMethod groupClade
69
-## setMethod("groupClade", signature(object="apeBootstrap"),
70
-##           function(object, node, group_name="group") {
71
-##               groupClade_(object, node, group_name)
72
-##           })
73
-
74
-## ##' @rdname scale_color-methods
75
-## ##' @exportMethod scale_color
76
-## setMethod("scale_color", signature(object="apeBootstrap"),
77
-##           function(object, by="bootstrap", ...) {
78
-##               scale_color_(object, by, ...)
79
-##           })
80
-
81
-
82
-## ##' @rdname get.fields-methods
83
-## ##' @exportMethod get.fields
84
-## setMethod("get.fields", signature(object="apeBootstrap"),
85
-##           function(object, ...) {
86
-##               get.fields.tree(object)
87
-##           }
88
-##           )
89
-
90 16
new file mode 100644
... ...
@@ -0,0 +1,20 @@
1
+##' format a list of range (HPD, CI, etc that has length of 2)
2
+##'
3
+##'
4
+##' @title range_format
5
+##' @param x input list
6
+##' @param trans transformation function
7
+##' @return character vector of '[lower, upper]'
8
+##' @export
9
+##' @author guangchuang yu
10
+range_format <- function(x, trans = NULL) {
11
+    sapply(x, function(y) {
12
+        if(length(y) == 1 && is.na(y)) {
13
+            return(NA)
14
+        } else {
15
+            if (!is.null(trans) && is(trans, 'function'))
16
+                y <- trans(y)
17
+            return(sprintf("[%f, %f]", y[1], y[2]))
18
+        }
19
+    })
20
+}
... ...
@@ -3,12 +3,13 @@
3 3
 ##'
4 4
 ##' @title geom_range
5 5
 ##' @param range range, e.g. "height_0.95_HPD"
6
+##' @param branch.length corresponding branch.length
6 7
 ##' @param ... additional parameter, e.g. color, size, alpha
7 8
 ##' @return ggplot layer
8 9
 ##' @importFrom ggplot2 aes_string
9 10
 ##' @export
10 11
 ##' @author Guangchuang Yu
11
-geom_range <- function(range="height_0.95_HPD", ...) {
12
+geom_range <- function(range = "length_0.95_HPD", branch.length = "branch.length", ...) {
12 13
     position = "identity"
13 14
     show.legend = NA
14 15
     na.rm = TRUE
... ...
@@ -16,11 +17,10 @@ geom_range <- function(range="height_0.95_HPD", ...) {
16 17
 
17 18
     default_aes <- aes_(x=~x, y=~y, xend=~x, yend=~y)
18 19
 
19
-    if (grepl("^height", range)) {
20
-        mapping <- modifyList(default_aes, aes_string(branch.length="height", label=range))
21
-    } else {
22
-        mapping <- modifyList(default_aes, aes_string(branch.length="branch.length", label=range))
23
-    }
20
+    lower <- paste0('range_lower(', range, ')')
21
+    upper <- paste0('range_upper(', range, ')')
22
+
23
+    mapping <- modifyList(default_aes, aes_string(branch.length=branch.length, lower=lower, upper=upper))
24 24
 
25 25
     layer(
26 26
         stat = StatRange,
... ...
@@ -39,21 +39,28 @@ geom_range <- function(range="height_0.95_HPD", ...) {
39 39
 
40 40
 StatRange <- ggproto("StatRange", Stat,
41 41
                      compute_group = function(self, data, scales, params) {
42
-                         ## label is actually the range
43
-
44
-                         df <- data[!is.na(data[,"label"]),]
45
-                         rr <- gsub("\\[", "", df[,"label"])
46
-                         rr <- gsub("\\]", "", rr)
47
-                         rr2 <- strsplit(rr, split=',') %>% do.call('rbind', .)
48
-                         rr2 <- matrix(as.numeric(rr2), ncol=2, byrow=FALSE)
49
-                         rr2 <- rr2 + df$x - df$branch
50
-
51
-                         data.frame(x = rr2[,1],
52
-                                    xend = rr2[,2],
53
-                                    y = df$y,
54
-                                    yend = df$y)
42
+                         df <- data[!is.na(data[["lower"]]),]
43
+                         df[["lower"]] <- df[["lower"]] + df[["x"]] - df[["branch.length"]]
44
+                         df[["upper"]] <- df[["upper"]] + df[["x"]] - df[["branch.length"]]
45
+
46
+                         data.frame(x = df[["lower"]],
47
+                                    xend = df[["upper"]],
48
+                                    y = df[["y"]],
49
+                                    yend = df[["y"]])
55 50
                      },
56 51
                      required_aes = c("x", "y", "xend", "yend")
57 52
                      )
58 53
 
59 54
 
55
+range_lower <- function(range) {
56
+    sapply(range, function(x) as.numeric(x[1]))
57
+}
58
+
59
+range_upper <- function(range) {
60
+    sapply(range, function(x) {
61
+        if (length(x) == 1 && is.na(x))
62
+            return(NA)
63
+        as.numeric(x[2])
64
+    })
65
+}
66
+
... ...
@@ -106,118 +106,118 @@ rm.singleton.newick <- function(nwk, outfile = NULL) {
106 106
     invisible(tree)
107 107
 }
108 108
 
109
-##' @method fortify beast
110
-##' @export
111
-fortify.beast <- function(model, data,
112
-                          layout        = "rectangular",
113
-                          yscale        = "none",
114
-                          ladderize     = TRUE,
115
-                          right         = FALSE,
116
-                          branch.length = "branch.length",
117
-                          ndigits       = NULL,
118
-                          mrsd = NULL, ...) {
119
-
120
-    model <- set_branch_length(model, branch.length)
121
-    phylo <- model@phylo
122
-    df    <- fortify(phylo,
123
-                     layout = layout,
124
-                     branch.length = branch.length,
125
-                     ladderize = ladderize,
126
-                     right = right,
127
-                     mrsd = mrsd, ...)
128
-
129
-    stats <- model@stats
130
-
131
-    scn <- colnames(stats)
132
-    scn <- scn[scn != 'node']
133
-
134
-    for (cn in scn) {
135
-        if (cn %in% colnames(df)) {
136
-            colnames(stats)[colnames(stats) == cn] <- paste0(cn, "_")
137
-            msg <- paste("feature", cn, "was renamed to", paste0(cn, "_"), "due to name conflict...")
138
-            warning(msg)
139
-        }
140
-    }
141
-
142
-    idx <- which(colnames(stats) != "node")
143
-    for (ii in idx) {
144
-        if (is.character_beast(stats, ii)) {
145
-            len <- sapply(stats[,ii], length)
146
-            if (any(len > 1)) {
147
-                stats[,ii] %<>% sapply(., function(x) {
148
-                    y <- unlist(x) %>% as.character %>%
149
-                        gsub("\"", "", .) %>% gsub("'", "", .)
150
-                    if (length(y) == 1) {
151
-                        return(y)
152
-                    } else {
153
-                        return(paste0('{', paste0(y, collapse = ','), '}'))
154
-                    }
155
-                })
156
-            } else {
157
-                stats[,ii] %<>% unlist %>% as.character %>%
158
-                    gsub("\"", "", .) %>% gsub("'", "", .)
159
-            }
160
-            next
161
-        }
162
-
163
-        len <- sapply(stats[,ii], length)
164
-        if ( all(len == 1) ) {
165
-            stats[, ii] %<>% unlist %>% as.character %>% as.numeric
166
-            if (!is.null(ndigits)) {
167
-                stats[, ii] %<>% round(., ndigits)
168
-            }
169
-        } else if (all(len <= 2)) {
170
-            stats[, ii] %<>% sapply(., function(x) {
171
-                y <- unlist(x) %>% as.character %>% as.numeric
172
-                if (!is.null(ndigits)) {
173
-                    y %<>% round(., ndigits)
174
-                }
175
-                if (length(y) == 1) {
176
-                    return(y)
177
-                } else {
178
-                    return(paste0('[', paste0(y, collapse = ','), ']'))
179
-                }
180
-            })
181
-        } else {
182
-            stats[,ii] %<>% sapply(., function(x) {
183
-                y <- unlist(x) %>% as.character %>% as.numeric
184
-                if (!is.null(ndigits)) {
185
-                    y %<>% round(., ndigits)
186
-                }
187
-                if (length(y) == 1) {
188
-                    return(y)
189
-                } else {
190
-                    return(paste0('{', paste0(y, collapse = ','), '}'))
191
-                }
192
-            })
193
-        }
194
-    }
195
-
196
-
197
-    cn <- colnames(stats)
198
-    lo <- cn[grep("_lower", cn)]
199
-    hi <- gsub("lower$", "upper", lo)
200
-    rid <- gsub("_lower$", "", lo)
201
-
202
-    for (i in seq_along(rid)) {
203
-        stats[, rid[i]] <- paste0("[", stats[, lo[i]], ",", stats[, hi[i]], "]")
204
-        stats[is.na(stats[, lo[i]]), rid[i]] <- NA
205
-    }
206
-
207
-    idx   <- match(df$node, stats$node)
208
-    stats <- stats[idx,]
209
-    cn_stats <- colnames(stats)
210
-    stats <- stats[, cn_stats != "node"]
211
-
212
-    df <- cbind(df, stats)
213
-    if (is(stats, "data.frame") == FALSE) {
214
-        colnames(df)[colnames(df) == "stats"] <- cn_stats[cn_stats != "node"]
215
-    }
216
-
217
-    df <- scaleY(phylo, df, yscale, layout, ...)
109
+## ##' @method fortify beast
110
+## ##' @export
111
+## fortify.beast <- function(model, data,
112
+##                           layout        = "rectangular",
113
+##                           yscale        = "none",
114
+##                           ladderize     = TRUE,
115
+##                           right         = FALSE,
116
+##                           branch.length = "branch.length",
117
+##                           ndigits       = NULL,
118
+##                           mrsd = NULL, ...) {
119
+
120
+##     model <- set_branch_length(model, branch.length)
121
+##     phylo <- model@phylo
122
+##     df    <- fortify(phylo,
123
+##                      layout = layout,
124
+##                      branch.length = branch.length,
125
+##                      ladderize = ladderize,
126
+##                      right = right,
127
+##                      mrsd = mrsd, ...)
128
+
129
+##     stats <- model@stats
130
+
131
+##     scn <- colnames(stats)
132
+##     scn <- scn[scn != 'node']
133
+
134
+##     for (cn in scn) {
135
+##         if (cn %in% colnames(df)) {
136
+##             colnames(stats)[colnames(stats) == cn] <- paste0(cn, "_")
137
+##             msg <- paste("feature", cn, "was renamed to", paste0(cn, "_"), "due to name conflict...")
138
+##             warning(msg)
139
+##         }
140
+##     }
141
+
142
+##     idx <- which(colnames(stats) != "node")
143
+##     for (ii in idx) {
144
+##         if (is.character_beast(stats, ii)) {
145
+##             len <- sapply(stats[,ii], length)
146
+##             if (any(len > 1)) {
147
+##                 stats[,ii] %<>% sapply(., function(x) {
148
+##                     y <- unlist(x) %>% as.character %>%
149
+##                         gsub("\"", "", .) %>% gsub("'", "", .)
150
+##                     if (length(y) == 1) {
151
+##                         return(y)
152
+##                     } else {
153
+##                         return(paste0('{', paste0(y, collapse = ','), '}'))
154
+##                     }
155
+##                 })
156
+##             } else {
157
+##                 stats[,ii] %<>% unlist %>% as.character %>%
158
+##                     gsub("\"", "", .) %>% gsub("'", "", .)
159
+##             }
160
+##             next
161
+##         }
162
+
163
+##         len <- sapply(stats[,ii], length)
164
+##         if ( all(len == 1) ) {
165
+##             stats[, ii] %<>% unlist %>% as.character %>% as.numeric
166
+##             if (!is.null(ndigits)) {
167
+##                 stats[, ii] %<>% round(., ndigits)
168
+##             }
169
+##         } else if (all(len <= 2)) {
170
+##             stats[, ii] %<>% sapply(., function(x) {
171
+##                 y <- unlist(x) %>% as.character %>% as.numeric
172
+##                 if (!is.null(ndigits)) {
173
+##                     y %<>% round(., ndigits)
174
+##                 }
175
+##                 if (length(y) == 1) {
176
+##                     return(y)
177
+##                 } else {
178
+##                     return(paste0('[', paste0(y, collapse = ','), ']'))
179
+##                 }
180
+##             })
181
+##         } else {
182
+##             stats[,ii] %<>% sapply(., function(x) {
183
+##                 y <- unlist(x) %>% as.character %>% as.numeric
184
+##                 if (!is.null(ndigits)) {
185
+##                     y %<>% round(., ndigits)
186
+##                 }
187
+##                 if (length(y) == 1) {
188
+##                     return(y)
189
+##                 } else {
190
+##                     return(paste0('{', paste0(y, collapse = ','), '}'))
191
+##                 }
192
+##             })
193
+##         }
194
+##     }
195
+
196
+
197
+##     cn <- colnames(stats)
198
+##     lo <- cn[grep("_lower", cn)]
199
+##     hi <- gsub("lower$", "upper", lo)
200
+##     rid <- gsub("_lower$", "", lo)
201
+
202
+##     for (i in seq_along(rid)) {
203
+##         stats[, rid[i]] <- paste0("[", stats[, lo[i]], ",", stats[, hi[i]], "]")
204
+##         stats[is.na(stats[, lo[i]]), rid[i]] <- NA
205
+##     }
206
+
207
+##     idx   <- match(df$node, stats$node)
208
+##     stats <- stats[idx,]
209
+##     cn_stats <- colnames(stats)
210
+##     stats <- stats[, cn_stats != "node"]
211
+
212
+##     df <- cbind(df, stats)
213
+##     if (is(stats, "data.frame") == FALSE) {
214
+##         colnames(df)[colnames(df) == "stats"] <- cn_stats[cn_stats != "node"]
215
+##     }
216
+
217
+##     df <- scaleY(phylo, df, yscale, layout, ...)
218 218
 
219
-    append_extraInfo(df, model)
220
-}
219
+##     append_extraInfo(df, model)
220
+## }
221 221
 
222 222
 
223 223
 ##' @method fortify codeml
... ...
@@ -392,7 +392,7 @@ scaleY <- function(phylo, df, yscale, layout, ...) {
392 392
         warning("yscale is not available...\n")
393 393
         return(df)
394 394
     }
395
-    if (is.numeric(df[, yscale])) {
395
+    if (is.numeric(df[[yscale]])) {
396 396
         y <- getYcoord_scale_numeric(phylo, df, yscale, ...)
397 397
         ## if (order.y) {
398 398
         ##     y <- getYcoord_scale2(phylo, df, yscale)
... ...
@@ -68,15 +68,15 @@ setMethod("gzoom", signature(object="ggtree"),
68 68
 ##           })
69 69
 
70 70
 
71
-##' zoom selected subtree
72
-##'
73
-##'
74
-##' @rdname gzoom-methods
75
-##' @exportMethod gzoom
76
-setMethod("gzoom", signature(object="beast"),
77
-          function(object, focus, subtree=FALSE, widths=c(.3, .7)) {
78
-              gzoom.phylo(get.tree(object), focus, subtree, widths)
79
-          })
71
+## ##' zoom selected subtree
72
+## ##'
73
+## ##'
74
+## ##' @rdname gzoom-methods
75
+## ##' @exportMethod gzoom
76
+## setMethod("gzoom", signature(object="beast"),
77
+##           function(object, focus, subtree=FALSE, widths=c(.3, .7)) {
78
+##               gzoom.phylo(get.tree(object), focus, subtree, widths)
79
+##           })
80 80
 
81 81
 ##' @rdname gzoom-methods
82 82
 ##' @exportMethod gzoom
... ...
@@ -85,7 +85,9 @@ setMethod("gzoom", signature(object="codeml"),
85 85
               gzoom.phylo(get.tree(object), focus, subtree, widths)
86 86
           })
87 87
 
88
-
88
+##' zoom selected subtree
89
+##'
90
+##'
89 91
 ##' @rdname gzoom-methods
90 92
 ##' @exportMethod gzoom
91 93
 setMethod("gzoom", signature(object="treedata"),
... ...
@@ -1,16 +1,16 @@
1 1
 
2
-##' @rdname reroot-methods
3
-##' @exportMethod reroot
4
-setMethod("reroot", signature(object="beast"),
5
-          function(object, node, ...) {
6
-              object@phylo <- reroot(object@phylo, node, ...)
2
+## ##' @rdname reroot-methods
3
+## ##' @exportMethod reroot
4
+## setMethod("reroot", signature(object="beast"),
5
+##           function(object, node, ...) {
6
+##               object@phylo <- reroot(object@phylo, node, ...)
7 7
 
8
-              node_map <- attr(object@phylo, "node_map")
9
-              idx <- match(object@stats$node, node_map[,1])
10
-              object@stats$node <- node_map[idx, 2]
8
+##               node_map <- attr(object@phylo, "node_map")
9
+##               idx <- match(object@stats$node, node_map[,1])
10
+##               object@stats$node <- node_map[idx, 2]
11 11
 
12
-              return(object)
13
-          })
12
+##               return(object)
13
+##           })
14 14
 
15 15
 ## ##' @rdname reroot-methods
16 16
 ## ##' @exportMethod reroot
... ...
@@ -1,14 +1,16 @@
1
+## ##' scale color by a numerical tree attribute
2
+## ##'
3
+## ##'
4
+## ##' @rdname scale_color-methods
5
+## ##' @exportMethod scale_color
6
+## setMethod("scale_color", signature(object="beast"),
7
+##           function(object, by, ...) {
8
+##               scale_color_(object, by, ...)
9
+##           })
10
+
1 11
 ##' scale color by a numerical tree attribute
2 12
 ##'
3 13
 ##'
4
-##' @rdname scale_color-methods
5
-##' @exportMethod scale_color
6
-setMethod("scale_color", signature(object="beast"),
7
-          function(object, by, ...) {
8
-              scale_color_(object, by, ...)
9
-          })
10
-
11
-
12 14
 ##' @rdname scale_color-methods
13 15
 ##' @exportMethod scale_color
14 16
 setMethod("scale_color", signature(object="treedata"),
... ...
@@ -18,14 +18,12 @@ fortify.treedata <- function(model, data, layout="rectangular", yscale="none",
18 18
     }
19 19
     ypos <- getYcoord(x)
20 20
     N <- Nnode(x, internal.only=FALSE)
21
-    xypos <- data.frame(node=1:N, x=xpos, y=ypos)
21
+    xypos <- data_frame(node=1:N, x=xpos, y=ypos)
22 22
 
23
-    df <- as.data.frame(model, branch.length="branch.length") # already set by set_branch_length
24
-    idx <- is.na(df$parent)
25
-    df$parent[idx] <- df$node[idx]
26
-    rownames(df) <- df$node
23
+    df <- as_data_frame(model, branch.length="branch.length") # already set by set_branch_length
24
+    ##rownames(df) <- as.character(df$node)
27 25
 
28
-    res <- merge(df, xypos, by='node', all.y=TRUE)
26
+    res <- full_join(df, xypos, by = "node")
29 27
 
30 28
     ## add branch mid position
31 29
     res <- calculate_branch_mid(res)
... ...
@@ -39,31 +37,41 @@ fortify.treedata <- function(model, data, layout="rectangular", yscale="none",
39 37
     scaleY(as.phylo(model), res, yscale, layout, ...)
40 38
 }
41 39
 
42
-##' @method as.data.frame treedata
40
+##' @method as_data_frame treedata
41
+##' @importFrom tibble as_data_frame
43 42
 ##' @export
44 43
 ## @importFrom treeio Nnode
45 44
 ## @importFrom treeio Ntip
46
-as.data.frame.treedata <- function(x, row.names, optional, branch.length = "branch.length", ...) {
45
+as_data_frame.treedata <- function(x, row.names, optional, branch.length = "branch.length", ...) {
47 46
     tree <- set_branch_length(x, branch.length)
48 47
 
49 48
     ## res <- as.data.frame(tree@phylo)
50
-    res <- as.data.frame_(tree@phylo)
51
-    tree_anno <- get_tree_data(x)
49
+    res <- as_data_frame_(tree@phylo)
50
+    tree_anno <- as_data_frame(get_tree_data(x))
52 51
     if (nrow(tree_anno) > 0) {
53
-        res <- merge(res, tree_anno, by="node", all.x=TRUE)
52
+        by <- "node"
53
+        tree_anno$node <- as.integer(tree_anno$node)
54
+        if ("parent" %in% colnames(tree_anno)) {
55
+            by <- c(by, "parent")
56
+            tree_anno$parent <- as.integer(tree_anno$parent)
57
+        }
58
+
59
+        res <- full_join(res, tree_anno, by=by)
54 60
     }
55 61
     return(res)
56 62
 }
57 63
 
58 64
 ##@method as.data.frame phylo
59 65
 ##@export
60
-as.data.frame_ <- function(x, row.names, optional, branch.length = "branch.length", ...) {
66
+##' @importFrom tibble data_frame
67
+##' @importFrom dplyr full_join
68
+as_data_frame_ <- function(x, row.names, optional, branch.length = "branch.length", ...) {
61 69
     phylo <- x
62 70
     ntip <- Ntip(phylo)
63 71
     N <- Nnode(phylo, internal.only=FALSE)
64 72
 
65 73
     tip.label <- phylo[["tip.label"]]
66
-    res <- as.data.frame(phylo[["edge"]])
74
+    res <- as_data_frame(phylo[["edge"]])
67 75
     colnames(res) <- c("parent", "node")
68 76
     if (!is.null(phylo$edge.length))
69 77
         res$branch.length <- phylo$edge.length
... ...
@@ -73,11 +81,14 @@ as.data.frame_ <- function(x, row.names, optional, branch.length = "branch.lengt
73 81
     if ( !is.null(phylo$node.label) ) {
74 82
         label[(ntip+1):N] <- phylo$node.label
75 83
     }
76
-    label.df <- data.frame(node=1:N, label=label)
77
-    res <- merge(res, label.df, by='node', all.y=TRUE)
78 84
     isTip <- rep(FALSE, N)
79 85
     isTip[1:ntip] <- TRUE
80
-    res$isTip <- isTip
86
+
87
+    label.df <- data_frame(node=1:N, label=label, isTip = isTip)
88
+    res <- full_join(res, label.df, by='node')
89
+
90
+    idx <- is.na(res$parent)
91
+    res$parent[idx] <- res$node[idx]
81 92
 
82 93
     return(res)
83 94
 }
... ...
@@ -1449,7 +1460,7 @@ getYcoord_scale_numeric <- function(tr, df, yscale, ...) {
1449 1460
 }
1450 1461
 
1451 1462
 .assign_parent_status <- function(tr, df, variable) {
1452
-    yy <- df[, variable]
1463
+    yy <- df[[variable]]
1453 1464
     na.idx <- which(is.na(yy))
1454 1465
     if (length(na.idx) > 0) {
1455 1466
         tree <- get.tree(tr)
... ...
@@ -1470,7 +1481,7 @@ getYcoord_scale_numeric <- function(tr, df, yscale, ...) {
1470 1481
 }
1471 1482
 
1472 1483
 .assign_child_status <- function(tr, df, variable, yscale_mapping=NULL) {
1473
-    yy <- df[, variable]
1484
+    yy <- df[[variable]]
1474 1485
     if (!is.null(yscale_mapping)) {
1475 1486
         yy <- yscale_mapping[yy]
1476 1487
     }
... ...
@@ -1507,7 +1518,7 @@ getYcoord_scale_category <- function(tr, df, yscale, yscale_mapping=NULL, ...) {
1507 1518
     }
1508 1519
 
1509 1520
     if (yscale == "label") {
1510
-        yy <- df[, yscale]
1521
+        yy <- df[[yscale]]
1511 1522
         ii <- which(is.na(yy))
1512 1523
         if (length(ii)) {
1513 1524
             df[ii, yscale] <- df[ii, "node"]
... ...
@@ -1518,7 +1529,7 @@ getYcoord_scale_category <- function(tr, df, yscale, yscale_mapping=NULL, ...) {
1518 1529
     df <- .assign_parent_status(tr, df, yscale)
1519 1530
     df <- .assign_child_status(tr, df, yscale, yscale_mapping)
1520 1531
 
1521
-    y <- df[, yscale]
1532
+    y <- df[[yscale]]
1522 1533
 
1523 1534
     if (anyNA(y)) {
1524 1535
         warning("NA found in y scale mapping, all were setting to 0")
... ...
@@ -1543,7 +1554,8 @@ add_angle_slanted <- function(res) {
1543 1554
 }
1544 1555
 
1545 1556
 calculate_branch_mid <- function(res) {
1546
-    res$branch <- (res[res$parent, "x"] + res[, "x"])/2
1557
+    res$branch <- with(res, (x[match(parent, node)] + x)/2)
1558
+    ## res$branch <- (res[match(res$parent, res$node), "x"] + res[, "x"])/2
1547 1559
     if (!is.null(res$length)) {
1548 1560
         res$length[is.na(res$length)] <- 0
1549 1561
     }
... ...
@@ -1566,6 +1578,9 @@ set_branch_length <- function(tree_object, branch.length) {
1566 1578
 
1567 1579
     tree_anno <- get_tree_data(tree_object)
1568 1580
 
1581
+    if (is(tree_anno, "matrix"))
1582
+        tree_anno <- as.data.frame(tree_anno)
1583
+
1569 1584
     phylo <- get.tree(tree_object)
1570 1585
 
1571 1586
     cn <- colnames(tree_anno)
... ...
@@ -1573,7 +1588,7 @@ set_branch_length <- function(tree_object, branch.length) {
1573 1588
 
1574 1589
     length <- match.arg(branch.length, cn)
1575 1590
 
1576
-    if (all(is.na(as.numeric(tree_anno[, length])))) {
1591
+    if (all(is.na(as.numeric(tree_anno[[length]])))) {
1577 1592
         stop("branch.length should be numerical attributes...")
1578 1593
     }
1579 1594
 
... ...
@@ -1584,7 +1599,7 @@ set_branch_length <- function(tree_object, branch.length) {
1584 1599
                 by  = "node",
1585 1600
                 all.x = TRUE)
1586 1601
     dd <- dd[match(edge$node, dd$node),]
1587
-    len <- unlist(dd[, length])
1602
+    len <- unlist(dd[[length]])
1588 1603
     len <- as.numeric(len)
1589 1604
     len[is.na(len)] <- 0
1590 1605
 
... ...
@@ -1,7 +1,7 @@
1 1
 ---
2 2
 output:
3 3
   md_document:
4
-    variant: gfm
4
+    variant: markdown_github
5 5
 html_preview: false
6 6
 ---
7 7
 
... ...
@@ -1,70 +1,35 @@
1 1
 <!-- README.md is generated from README.Rmd. Please edit that file -->
2
-
3
-# ggtree: an R package for visualization and annotation of phylogenetic trees with their covariates and other associated data
2
+ggtree: an R package for visualization and annotation of phylogenetic trees with their covariates and other associated data
3
+===========================================================================================================================
4 4
 
5 5
 <img src="https://raw.githubusercontent.com/Bioconductor/BiocStickers/master/ggtree/ggtree.png" height="200" align="right" />
6 6
 
7
-[![releaseVersion](https://img.shields.io/badge/release%20version-1.10.0-green.svg?style=flat)](https://bioconductor.org/packages/ggtree)
8
-[![develVersion](https://img.shields.io/badge/devel%20version-1.11.1-green.svg?style=flat)](https://github.com/guangchuangyu/ggtree)
9
-[![Bioc](http://www.bioconductor.org/shields/years-in-bioc/ggtree.svg)](https://www.bioconductor.org/packages/devel/bioc/html/ggtree.html#since)
10
-[![total](https://img.shields.io/badge/downloads-21911/total-blue.svg?style=flat)](https://bioconductor.org/packages/stats/bioc/ggtree)
11
-[![month](https://img.shields.io/badge/downloads-1156/month-blue.svg?style=flat)](https://bioconductor.org/packages/stats/bioc/ggtree)
12
-
13
-[![Project Status: Active - The project has reached a stable, usable
14
-state and is being actively
15
-developed.](http://www.repostatus.org/badges/latest/active.svg)](http://www.repostatus.org/#active)
16
-[![codecov](https://codecov.io/gh/GuangchuangYu/ggtree/branch/master/graph/badge.svg)](https://codecov.io/gh/GuangchuangYu/ggtree)
17
-[![Last-changedate](https://img.shields.io/badge/last%20change-2017--12--04-green.svg)](https://github.com/GuangchuangYu/ggtree/commits/master)
18
-[![GitHub
19
-forks](https://img.shields.io/github/forks/GuangchuangYu/ggtree.svg)](https://github.com/GuangchuangYu/ggtree/network)
20
-[![GitHub
21
-stars](https://img.shields.io/github/stars/GuangchuangYu/ggtree.svg)](https://github.com/GuangchuangYu/ggtree/stargazers)
22
-[![Awesome](https://cdn.rawgit.com/sindresorhus/awesome/d7305f38d29fed78fa85652e3a63e154dd8e8829/media/badge.svg)](https://awesome-r.com/#awesome-r-graphic-displays)
23
-
24
-[![platform](http://www.bioconductor.org/shields/availability/devel/ggtree.svg)](https://www.bioconductor.org/packages/devel/bioc/html/ggtree.html#archives)
25
-[![Build
26
-Status](http://www.bioconductor.org/shields/build/devel/bioc/ggtree.svg)](https://bioconductor.org/checkResults/devel/bioc-LATEST/ggtree/)
27
-[![Linux/Mac Travis Build
28
-Status](https://img.shields.io/travis/GuangchuangYu/ggtree/master.svg?label=Mac%20OSX%20%26%20Linux)](https://travis-ci.org/GuangchuangYu/ggtree)
29
-[![AppVeyor Build
30
-Status](https://img.shields.io/appveyor/ci/Guangchuangyu/ggtree/master.svg?label=Windows)](https://ci.appveyor.com/project/GuangchuangYu/ggtree)
31
-[![Backers on Open
32
-Collective](https://opencollective.com/ggtree/backers/badge.svg)](#backers)
33
-[![Sponsors on Open
34
-Collective](https://opencollective.com/ggtree/sponsors/badge.svg)](#sponsors)
35
-
36
-The `ggtree` package extending the `ggplot2` package. It based on
37
-grammar of graphics and takes all the good parts of `ggplot2`. `ggtree`
38
-is designed for not only viewing phylogenetic tree but also displaying
39
-annotation data on the
40
-tree.
7
+[![releaseVersion](https://img.shields.io/badge/release%20version-1.10.0-green.svg?style=flat)](https://bioconductor.org/packages/ggtree) [![develVersion](https://img.shields.io/badge/devel%20version-1.11.2-green.svg?style=flat)](https://github.com/guangchuangyu/ggtree) [![Bioc](http://www.bioconductor.org/shields/years-in-bioc/ggtree.svg)](https://www.bioconductor.org/packages/devel/bioc/html/ggtree.html#since) [![total](https://img.shields.io/badge/downloads-21911/total-blue.svg?style=flat)](https://bioconductor.org/packages/stats/bioc/ggtree) [![month](https://img.shields.io/badge/downloads-1156/month-blue.svg?style=flat)](https://bioconductor.org/packages/stats/bioc/ggtree)
8
+
9
+[![Project Status: Active - The project has reached a stable, usable state and is being actively developed.](http://www.repostatus.org/badges/latest/active.svg)](http://www.repostatus.org/#active) [![codecov](https://codecov.io/gh/GuangchuangYu/ggtree/branch/master/graph/badge.svg)](https://codecov.io/gh/GuangchuangYu/ggtree) [![Last-changedate](https://img.shields.io/badge/last%20change-2017--12--05-green.svg)](https://github.com/GuangchuangYu/ggtree/commits/master) [![GitHub forks](https://img.shields.io/github/forks/GuangchuangYu/ggtree.svg)](https://github.com/GuangchuangYu/ggtree/network) [![GitHub stars](https://img.shields.io/github/stars/GuangchuangYu/ggtree.svg)](https://github.com/GuangchuangYu/ggtree/stargazers) [![Awesome](https://cdn.rawgit.com/sindresorhus/awesome/d7305f38d29fed78fa85652e3a63e154dd8e8829/media/badge.svg)](https://awesome-r.com/#awesome-r-graphic-displays)
10
+
11
+[![platform](http://www.bioconductor.org/shields/availability/devel/ggtree.svg)](https://www.bioconductor.org/packages/devel/bioc/html/ggtree.html#archives) [![Build Status](http://www.bioconductor.org/shields/build/devel/bioc/ggtree.svg)](https://bioconductor.org/checkResults/devel/bioc-LATEST/ggtree/) [![Linux/Mac Travis Build Status](https://img.shields.io/travis/GuangchuangYu/ggtree/master.svg?label=Mac%20OSX%20%26%20Linux)](https://travis-ci.org/GuangchuangYu/ggtree) [![AppVeyor Build Status](https://img.shields.io/appveyor/ci/Guangchuangyu/ggtree/master.svg?label=Windows)](https://ci.appveyor.com/project/GuangchuangYu/ggtree) [![Backers on Open Collective](https://opencollective.com/ggtree/backers/badge.svg)](#backers) [![Sponsors on Open Collective](https://opencollective.com/ggtree/sponsors/badge.svg)](#sponsors)
12
+
13
+The `ggtree` package extending the `ggplot2` package. It based on grammar of graphics and takes all the good parts of `ggplot2`. `ggtree` is designed for not only viewing phylogenetic tree but also displaying annotation data on the tree.
41 14
 
42 15
 [![Twitter](https://img.shields.io/twitter/url/https/github.com/GuangchuangYu/ggtree.svg?style=social)](https://twitter.com/intent/tweet?hashtags=ggtree&url=http://onlinelibrary.wiley.com/doi/10.1111/2041-210X.12628/abstract&screen_name=guangchuangyu)
43 16
 
44
-For details, please visit our project website,
45
-<https://guangchuangyu.github.io/ggtree>.
17
+For details, please visit our project website, <https://guangchuangyu.github.io/ggtree>.
46 18
 
47
-  - [Documentation](https://guangchuangyu.github.io/ggtree/documentation/)
48
-  - [FAQ](https://guangchuangyu.github.io/ggtree/faq/)
49
-  - [Featured
50
-    Articles](https://guangchuangyu.github.io/ggtree/featuredArticles/)
51
-  - [Feedback](https://guangchuangyu.github.io/ggtree/#feedback)
19
+-   [Documentation](https://guangchuangyu.github.io/ggtree/documentation/)
20
+-   [FAQ](https://guangchuangyu.github.io/ggtree/faq/)
21
+-   [Featured Articles](https://guangchuangyu.github.io/ggtree/featuredArticles/)
22
+-   [Feedback](https://guangchuangyu.github.io/ggtree/#feedback)
52 23
 
24
+------------------------------------------------------------------------
53 25
 
54 26
 Please cite the following article when using `ggtree`:
55 27
 
56
-**G Yu**, DK Smith, H Zhu, Y Guan, TTY Lam<sup>\*</sup>. ggtree: an R
57
-package for visualization and annotation of phylogenetic trees with
58
-their covariates and other associated data. ***Methods in Ecology and
59
-Evolution***. 2017,
60
-8(1):28-36.
28
+**G Yu**, DK Smith, H Zhu, Y Guan, TTY Lam<sup>\*</sup>. ggtree: an R package for visualization and annotation of phylogenetic trees with their covariates and other associated data. ***Methods in Ecology and Evolution***. 2017, 8(1):28-36.
61 29
 
62
-[![doi](https://img.shields.io/badge/doi-10.1111/2041--210X.12628-green.svg?style=flat)](http://dx.doi.org/10.1111/2041-210X.12628)
63
-[![Altmetric](https://img.shields.io/badge/Altmetric-333-green.svg?style=flat)](https://www.altmetric.com/details/10533079)
64
-[![citation](https://img.shields.io/badge/cited%20by-51-green.svg?style=flat)](https://scholar.google.com.hk/scholar?oi=bibs&hl=en&cites=7268358477862164627)
30
+[![doi](https://img.shields.io/badge/doi-10.1111/2041--210X.12628-green.svg?style=flat)](http://dx.doi.org/10.1111/2041-210X.12628) [![Altmetric](https://img.shields.io/badge/Altmetric-333-green.svg?style=flat)](https://www.altmetric.com/details/10533079) [![citation](https://img.shields.io/badge/cited%20by-52-green.svg?style=flat)](https://scholar.google.com.hk/scholar?oi=bibs&hl=en&cites=7268358477862164627)
65 31
 
32
+------------------------------------------------------------------------
66 33
 
67 34
 ### Citation
68 35
 
... ...
@@ -72,38 +37,25 @@ Evolution***. 2017,
72 37
 
73 38
 ### Download stats
74 39
 
75
-[![download](http://www.bioconductor.org/shields/downloads/ggtree.svg)](https://bioconductor.org/packages/stats/bioc/ggtree)
76
-[![total](https://img.shields.io/badge/downloads-21911/total-blue.svg?style=flat)](https://bioconductor.org/packages/stats/bioc/ggtree)
77
-[![month](https://img.shields.io/badge/downloads-1156/month-blue.svg?style=flat)](https://bioconductor.org/packages/stats/bioc/ggtree)
40
+[![download](http://www.bioconductor.org/shields/downloads/ggtree.svg)](https://bioconductor.org/packages/stats/bioc/ggtree) [![total](https://img.shields.io/badge/downloads-21911/total-blue.svg?style=flat)](https://bioconductor.org/packages/stats/bioc/ggtree) [![month](https://img.shields.io/badge/downloads-1156/month-blue.svg?style=flat)](https://bioconductor.org/packages/stats/bioc/ggtree)
78 41
 
79 42
 <img src="docs/images/dlstats.png" width="890"/>
80 43
 
81
-## Contributors
44
+Contributors
45
+------------
82 46
 
83
-This project exists thanks to all the people who contribute.
84
-[\[Contribute\]](CONTRIBUTING.md).
85
-<a href="https://github.com/GuangchuangYu/ggtree/graphs/contributors"><img src="https://opencollective.com/ggtree/contributors.svg?width=890" /></a>
47
+This project exists thanks to all the people who contribute. [\[Contribute\]](CONTRIBUTING.md). <a href="https://github.com/GuangchuangYu/ggtree/graphs/contributors"><img src="https://opencollective.com/ggtree/contributors.svg?width=890" /></a>
86 48
 
87
-## Backers
49
+Backers
50
+-------
88 51
 
89
-Thank you to all our backers\! 🙏 \[[Become a
90
-backer](https://opencollective.com/ggtree#backer)\]
52
+Thank you to all our backers! 🙏 \[[Become a backer](https://opencollective.com/ggtree#backer)\]
91 53
 
92 54
 <a href="https://opencollective.com/ggtree#backers" target="_blank"><img src="https://opencollective.com/ggtree/backers.svg?width=890"></a>
93 55
 
94
-## Sponsors
95
-
96
-Support this project by becoming a sponsor. Your logo will show up here
97
-with a link to your website. \[[Become a
98
-sponsor](https://opencollective.com/ggtree#sponsor)\]
99
-
100
-<a href="https://opencollective.com/ggtree/sponsor/0/website" target="_blank"><img src="https://opencollective.com/ggtree/sponsor/0/avatar.svg"></a>
101
-<a href="https://opencollective.com/ggtree/sponsor/1/website" target="_blank"><img src="https://opencollective.com/ggtree/sponsor/1/avatar.svg"></a>
102
-<a href="https://opencollective.com/ggtree/sponsor/2/website" target="_blank"><img src="https://opencollective.com/ggtree/sponsor/2/avatar.svg"></a>
103
-<a href="https://opencollective.com/ggtree/sponsor/3/website" target="_blank"><img src="https://opencollective.com/ggtree/sponsor/3/avatar.svg"></a>
104
-<a href="https://opencollective.com/ggtree/sponsor/4/website" target="_blank"><img src="https://opencollective.com/ggtree/sponsor/4/avatar.svg"></a>
105
-<a href="https://opencollective.com/ggtree/sponsor/5/website" target="_blank"><img src="https://opencollective.com/ggtree/sponsor/5/avatar.svg"></a>
106
-<a href="https://opencollective.com/ggtree/sponsor/6/website" target="_blank"><img src="https://opencollective.com/ggtree/sponsor/6/avatar.svg"></a>
107
-<a href="https://opencollective.com/ggtree/sponsor/7/website" target="_blank"><img src="https://opencollective.com/ggtree/sponsor/7/avatar.svg"></a>
108
-<a href="https://opencollective.com/ggtree/sponsor/8/website" target="_blank"><img src="https://opencollective.com/ggtree/sponsor/8/avatar.svg"></a>
109
-<a href="https://opencollective.com/ggtree/sponsor/9/website" target="_blank"><img src="https://opencollective.com/ggtree/sponsor/9/avatar.svg"></a>
56
+Sponsors
57
+--------
58
+
59
+Support this project by becoming a sponsor. Your logo will show up here with a link to your website. \[[Become a sponsor](https://opencollective.com/ggtree#sponsor)\]
60
+
61
+<a href="https://opencollective.com/ggtree/sponsor/0/website" target="_blank"><img src="https://opencollective.com/ggtree/sponsor/0/avatar.svg"></a> <a href="https://opencollective.com/ggtree/sponsor/1/website" target="_blank"><img src="https://opencollective.com/ggtree/sponsor/1/avatar.svg"></a> <a href="https://opencollective.com/ggtree/sponsor/2/website" target="_blank"><img src="https://opencollective.com/ggtree/sponsor/2/avatar.svg"></a> <a href="https://opencollective.com/ggtree/sponsor/3/website" target="_blank"><img src="https://opencollective.com/ggtree/sponsor/3/avatar.svg"></a> <a href="https://opencollective.com/ggtree/sponsor/4/website" target="_blank"><img src="https://opencollective.com/ggtree/sponsor/4/avatar.svg"></a> <a href="https://opencollective.com/ggtree/sponsor/5/website" target="_blank"><img src="https://opencollective.com/ggtree/sponsor/5/avatar.svg"></a> <a href="https://opencollective.com/ggtree/sponsor/6/website" target="_blank"><img src="https://opencollective.com/ggtree/sponsor/6/avatar.svg"></a> <a href="https://opencollective.com/ggtree/sponsor/7/website" target="_blank"><img src="https://opencollective.com/ggtree/sponsor/7/avatar.svg"></a> <a href="https://opencollective.com/ggtree/sponsor/8/website" target="_blank"><img src="https://opencollective.com/ggtree/sponsor/8/avatar.svg"></a> <a href="https://opencollective.com/ggtree/sponsor/9/website" target="_blank"><img src="https://opencollective.com/ggtree/sponsor/9/avatar.svg"></a>
110 62
Binary files a/docs/images/citation.png and b/docs/images/citation.png differ
... ...
@@ -4,11 +4,13 @@
4 4
 \alias{geom_range}
5 5
 \title{geom_range}
6 6
 \usage{
7
-geom_range(range = "height_0.95_HPD", ...)
7
+geom_range(range = "length_0.95_HPD", branch.length = "branch.length", ...)
8 8
 }
9 9
 \arguments{
10 10
 \item{range}{range, e.g. "height_0.95_HPD"}
11 11
 
12
+\item{branch.length}{corresponding branch.length}
13
+
12 14
 \item{...}{additional parameter, e.g. color, size, alpha}
13 15
 }
14 16
 \value{
... ...
@@ -5,7 +5,6 @@
5 5
 \alias{gzoom}
6 6
 \alias{gzoom}
7 7
 \alias{gzoom,ggtree-method}
8
-\alias{gzoom,beast-method}
9 8
 \alias{gzoom,codeml-method}
10 9
 \alias{gzoom,treedata-method}
11 10
 \alias{gzoom,paml_rst-method}
... ...
@@ -17,9 +16,6 @@ gzoom(object, focus, subtree = FALSE, widths = c(0.3, 0.7), ...)
17 16
 \S4method{gzoom}{ggtree}(object, focus, widths = c(0.3, 0.7),
18 17
   xmax_adjust = 0)
19 18
 
20
-\S4method{gzoom}{beast}(object, focus, subtree = FALSE, widths = c(0.3,
21
-  0.7))
22
-
23 19
 \S4method{gzoom}{codeml}(object, focus, subtree = FALSE, widths = c(0.3,
24 20
   0.7))
25 21
 
26 22
new file mode 100644
... ...
@@ -0,0 +1,22 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/format.R
3
+\name{range_format}
4
+\alias{range_format}
5
+\title{range_format}
6
+\usage{
7
+range_format(x, trans = NULL)
8
+}
9
+\arguments{
10
+\item{x}{input list}
11
+
12
+\item{trans}{transformation function}
13
+}
14
+\value{
15
+character vector of '[lower, upper]'
16
+}
17
+\description{
18
+format a list of range (HPD, CI, etc that has length of 2)
19
+}
20
+\author{
21
+guangchuang yu
22
+}
... ...
@@ -3,14 +3,11 @@
3 3
 \docType{methods}
4 4
 \name{reroot}
5 5
 \alias{reroot}
6
-\alias{reroot,beast-method}
7 6
 \alias{reroot,phylo-method}
8 7
 \title{reroot method}
9 8
 \usage{
10 9
 reroot(object, node, ...)
11 10
 
12
-\S4method{reroot}{beast}(object, node, ...)
13
-
14 11
 \S4method{reroot}{phylo}(object, node, ...)
15 12
 }
16 13
 \arguments{
... ...
@@ -3,7 +3,6 @@
3 3
 \docType{methods}
4 4
 \name{scale_color}
5 5
 \alias{scale_color}
6
-\alias{scale_color,beast-method}
7 6
 \alias{scale_color,treedata-method}
8 7
 \alias{scale_color,paml_rst-method}
9 8
 \alias{scale_color,phylo-method}
... ...
@@ -11,8 +10,6 @@
11 10
 \usage{
12 11
 scale_color(object, by, ...)
13 12
 
14
-\S4method{scale_color}{beast}(object, by, ...)
15
-
16 13
 \S4method{scale_color}{treedata}(object, by, ...)
17 14
 
18 15
 \S4method{scale_color}{paml_rst}(object, by, ...)
... ...
@@ -43,7 +43,7 @@ library("ggtree")
43 43
 
44 44
 If you use `ggtree` in published research, please cite:
45 45
 
46
-__G Yu__, DK Smith, H Zhu, Y Guan, TTY Lam^\*^. ggtree: an R package for visualization and annotation of phylogenetic trees with their covariates and other associated data. __*Methods in Ecology and Evolution*__. 2017, 8(1):28-36. doi:[10.1111/2041-210X.12628](http://dx.doi.org/10.1111/2041-210X.12628)
46
+__G Yu__, DK Smith, H Zhu, Y Guan, TTY Lam^\*^. ggtree: an R package for visualization and annotation of phylogenetic trees with their covariates and other associated data. __*Methods in Ecology and Evolution*__. 2017, 8(1):28-36. doi:[10.1111/2041-210X.12628](http://dx.doi.org/10.1111/2041-210X.12628).
47 47
 
48 48
 
49 49
 # Introduction
... ...
@@ -135,7 +135,7 @@ get.fields(beast)
135 135
 Users can use `ggtree(beast)` to visualize the tree and add layer to annotate it.
136 136
 
137 137
 ```{r warning=FALSE, fig.width=10, fig.height=10}
138
-ggtree(beast, ndigits=2, branch.length = 'none') + geom_text(aes(x=branch, label=length_0.95_HPD), vjust=-.5, color='firebrick')
138
+ggtree(beast, branch.length = 'none') + geom_text(aes(x=branch, label=range_format(length_0.95_HPD)), vjust=-.5, color='firebrick')
139 139
 ```
140 140
 
141 141
 `ggtree` provides `geom_range` layer to display uncertainty of branch length.