Document update
... | ... |
@@ -12,15 +12,20 @@ vexpand <- function(ratio, direction = 1) { |
12 | 12 |
ggexpand(ratio, direction, side = 'v') |
13 | 13 |
} |
14 | 14 |
|
15 |
-##' expand xlim (ylim) by ratio of x (y) range |
|
15 |
+##' expand xlim (ylim) by ratio of x (y) axis range |
|
16 | 16 |
##' |
17 | 17 |
##' |
18 | 18 |
##' @rdname ggexpand |
19 |
-##' @param ratio expand x (y) limits by amount of xrange (yrange) * ratio |
|
20 |
-##' @param direction expand x limit at right hand side if direction is 1, or left hand side if direction is -1 |
|
21 |
-##' @param side one of 'h' for horizontal and 'v' for vertical or 'hv' for both. |
|
19 |
+##' @param ratio expand x (y) axis limits by amount of xrange (yrange) * ratio |
|
20 |
+##' @param direction expand x axis limit at right hand side if direction is 1 (default), or left hand side if direction is -1 |
|
21 |
+##' @param side one of 'h' for horizontal and 'v' for vertical or 'hv' for both (default). |
|
22 | 22 |
##' @return ggexpand object |
23 | 23 |
##' @export |
24 |
+##' @examples |
|
25 |
+##' x <- rtree(20) |
|
26 |
+##' x$tip.label <- paste0('RRRRREEEEEAAAAALLLLLYYYYY_Long_Lable_', x$tip.label) |
|
27 |
+##' p1 <- ggtree(x) + geom_tiplab() |
|
28 |
+##' p1 + ggexpand(1.5, side = "h") |
|
24 | 29 |
##' @author Guangchuang Yu |
25 | 30 |
ggexpand <- function(ratio, direction = 1, side = 'hv') { |
26 | 31 |
side <- match.arg(side, c('h', 'v', 'hv')) |
... | ... |
@@ -30,13 +35,21 @@ ggexpand <- function(ratio, direction = 1, side = 'hv') { |
30 | 35 |
} |
31 | 36 |
|
32 | 37 |
|
33 |
-##' set x axis limits for Tree panel |
|
38 |
+##' set x axis limits specially for Tree panel |
|
34 | 39 |
##' |
35 | 40 |
##' |
36 | 41 |
##' @title xlim_tree |
37 |
-##' @param xlim xlim |
|
42 |
+##' @param xlim x axis limits |
|
38 | 43 |
##' @return updated tree view |
39 | 44 |
##' @export |
45 |
+##' @examples |
|
46 |
+##' x <- rtree(30) |
|
47 |
+##' p <- ggtree(x) + geom_tiplab() |
|
48 |
+##' d <- data.frame(label = x$tip.label, |
|
49 |
+##' value = rnorm(30)) |
|
50 |
+##' p2 <- p + geom_facet(panel = "Dot", data = d, |
|
51 |
+##' geom = geom_point, mapping = aes(x = value)) |
|
52 |
+##' p2 + xlim_tree(6) |
|
40 | 53 |
##' @author Guangchuang Yu |
41 | 54 |
xlim_tree <- function(xlim) { |
42 | 55 |
xlim_expand(xlim, panel='Tree') |
... | ... |
@@ -47,11 +60,19 @@ xlim_tree <- function(xlim) { |
47 | 60 |
##' |
48 | 61 |
##' |
49 | 62 |
##' @title xlim_expand |
50 |
-##' @param xlim xlim |
|
51 |
-##' @param panel panel |
|
63 |
+##' @param xlim x axis limits |
|
64 |
+##' @param panel name of the panel to expand |
|
52 | 65 |
##' @return updated tree view |
53 | 66 |
##' @importFrom ggplot2 geom_blank |
54 | 67 |
##' @export |
68 |
+##' @examples |
|
69 |
+##' x <- rtree(30) |
|
70 |
+##' p <- ggtree(x) + geom_tiplab() |
|
71 |
+##' d <- data.frame(label = x$tip.label, |
|
72 |
+##' value = rnorm(30)) |
|
73 |
+##' p2 <- p + geom_facet(panel = "Dot", data = d, |
|
74 |
+##' geom = geom_point, mapping = aes(x = value)) |
|
75 |
+##' p2 + xlim_expand(c(-10, 10), 'Dot') |
|
55 | 76 |
##' @author Guangchuang Yu |
56 | 77 |
xlim_expand <- function(xlim, panel) { |
57 | 78 |
structure(list(x = xlim, panel = panel), class = "facet_xlim") |
... | ... |
@@ -61,23 +82,36 @@ xlim_expand <- function(xlim, panel) { |
61 | 82 |
|
62 | 83 |
##' add second x-axis for geom_range |
63 | 84 |
##' |
85 |
+##' notice that the first axis is disabled in the default theme thus users need to enable it first before using scale_x_range |
|
64 | 86 |
##' |
65 | 87 |
##' @title scale_x_range |
66 | 88 |
##' @return ggtree object |
67 | 89 |
##' @export |
90 |
+##' @references |
|
91 |
+##' For demonstration of this function ,please refer to chapter 5.2.4 of |
|
92 |
+##' *Data Integration, Manipulation and Visualization of Phylogenetic Trees* |
|
93 |
+##' <http://yulab-smu.top/treedata-book/index.html> by Guangchuang Yu. |
|
68 | 94 |
##' @author Guangchuang Yu |
69 | 95 |
scale_x_range <- function() { |
70 | 96 |
structure(list(), class = "range_xaxis") |
71 | 97 |
} |
72 | 98 |
|
73 | 99 |
|
74 |
-##' reverse timescle x-axis |
|
100 |
+##' reverse timescle x-axis by setting the most recent tip to 0 |
|
101 |
+##' |
|
102 |
+##' 'scale_x_continuous(labels=abs)' is required if users want to set the x-axis lable to absolute value |
|
75 | 103 |
##' |
76 | 104 |
##' |
77 | 105 |
##' @title revts |
78 |
-##' @param treeview treeview |
|
79 |
-##' @return updated treeview |
|
106 |
+##' @param treeview original tree view |
|
107 |
+##' @return updated tree view |
|
80 | 108 |
##' @export |
109 |
+##' @examples |
|
110 |
+##' tr <- rtree(10) |
|
111 |
+##' p <- ggtree(tr) + theme_tree2() |
|
112 |
+##' p2 <- revts(p) |
|
113 |
+##' p3 <- p2 + scale_x_continuous(labels=abs) |
|
114 |
+##' plot_list(p, p2, p3, ncol=3, tag_levels="A") |
|
81 | 115 |
##' @author Guangchuang Yu |
82 | 116 |
revts <- function(treeview) { |
83 | 117 |
x <- treeview$data$x |
... | ... |
@@ -4,7 +4,7 @@ |
4 | 4 |
##' This function extract an ordered vector of the tips from selected clade or the whole tree |
5 | 5 |
##' based on the ggtree() plot. |
6 | 6 |
##' @title get_taxa_name |
7 |
-##' @param tree_view tree view (i.e. the ggtree object). If tree_view is NULL, the last ggplot will be used. |
|
7 |
+##' @param tree_view tree view (i.e. the ggtree object). If tree_view is NULL, the last ggplot object will be used. |
|
8 | 8 |
##' @param node internal node number to specify a clade. If NULL, using the whole tree |
9 | 9 |
##' @return ordered taxa name vector |
10 | 10 |
##' @importFrom tidytree offspring |
... | ... |
@@ -35,17 +35,22 @@ get_taxa_name <- function(tree_view=NULL, node=NULL) { |
35 | 35 |
} |
36 | 36 |
|
37 | 37 |
|
38 |
-##' view a clade of tree |
|
38 |
+##' view a selected clade of tree, clade can be selected by specifying a node number or |
|
39 |
+##' determined by the most recent common ancestor of selected tips |
|
39 | 40 |
##' |
40 | 41 |
##' |
41 | 42 |
##' @title viewClade |
42 | 43 |
##' @inheritParams get_taxa_name |
43 |
-##' @param xmax_adjust adjust xmax |
|
44 |
+##' @param xmax_adjust adjust the max range of x axis |
|
44 | 45 |
##' @return clade plot |
45 | 46 |
##' @importFrom ggplot2 ggplot_build |
46 | 47 |
##' @importFrom ggplot2 coord_cartesian |
47 | 48 |
##' @importFrom aplot xrange |
48 | 49 |
##' @export |
50 |
+##' @examples |
|
51 |
+##' x <- rtree(15) |
|
52 |
+##' p <- ggtree(x) + geom_tiplab() |
|
53 |
+##' viewClade(p, 18, xmax_adjust = 0.) |
|
49 | 54 |
##' @author Guangchuang Yu |
50 | 55 |
viewClade <- function(tree_view=NULL, node, xmax_adjust=0) { |
51 | 56 |
tree_view %<>% get_tree_view |
... | ... |
@@ -70,20 +75,26 @@ is.viewClade <- function(tree_view) { |
70 | 75 |
|
71 | 76 |
|
72 | 77 |
|
73 |
-##' collapse a clade |
|
78 |
+##' collapse a selected clade, which can later be expanded with the 'expand()' fuction if necessary |
|
74 | 79 |
##' |
75 | 80 |
##' |
76 | 81 |
##' @title collapse-ggtree |
77 | 82 |
##' @rdname collapse |
78 | 83 |
##' @param x tree view (i.e. the ggtree object). If tree_view is NULL, the last ggplot will be used. |
79 | 84 |
##' @param node internal node number |
80 |
-##' @param mode one of 'none', 'max', 'min' and 'mixed' |
|
81 |
-##' @param clade_name set clade name. If clade_name = NULL, do nothing |
|
82 |
-##' @param ... additional parameters |
|
85 |
+##' @param mode one of 'none'(default), 'max', 'min' and 'mixed'. 'none' would simply collapse the clade as 'tip' and |
|
86 |
+##' the rest will display a triangle, whose shape is determined by the farest/closest tip of the collapsed clade to indicate it |
|
87 |
+##' @param clade_name set a name for the collapsed clade. If clade_name = NULL, do nothing |
|
88 |
+##' @param ... additional parameters to set the color or transparency of the triangle |
|
83 | 89 |
##' @return tree view |
84 | 90 |
##' @method collapse ggtree |
85 | 91 |
##' @importFrom ggplot2 geom_polygon |
86 | 92 |
##' @export |
93 |
+##' @examples |
|
94 |
+##' x <- rtree(15) |
|
95 |
+##' p <- ggtree(x) + geom_tiplab() |
|
96 |
+##' p |
|
97 |
+##' p1 <- collapse(p, node = 17, mode = "mixed", clade_name = "cclade", alpha = 0.8, color = "grey", fill = "light blue") |
|
87 | 98 |
##' @seealso expand |
88 | 99 |
##' @author Guangchuang Yu |
89 | 100 |
collapse.ggtree <- function(x=NULL, node, mode = "none", clade_name = NULL, ...) { |
... | ... |
@@ -173,13 +184,18 @@ collapse.ggtree <- function(x=NULL, node, mode = "none", clade_name = NULL, ...) |
173 | 184 |
tree_view |
174 | 185 |
} |
175 | 186 |
|
176 |
-##' expand collased clade |
|
187 |
+##' expand collapsed clade |
|
177 | 188 |
##' |
178 | 189 |
##' |
179 | 190 |
##' @title expand |
180 | 191 |
##' @inheritParams get_taxa_name |
181 | 192 |
##' @return tree view |
182 | 193 |
##' @export |
194 |
+##' examples |
|
195 |
+##' x <- rtree(15) |
|
196 |
+##' p <- ggtree(x) + geom_tiplab() |
|
197 |
+##' p1 <- collapse(p, 17) |
|
198 |
+##' expand(p1, 17) |
|
183 | 199 |
##' @seealso collapse |
184 | 200 |
##' @author Guangchuang Yu |
185 | 201 |
expand <- function(tree_view=NULL, node) { |
... | ... |
@@ -230,13 +246,17 @@ expand <- function(tree_view=NULL, node) { |
230 | 246 |
return(tree_view) |
231 | 247 |
} |
232 | 248 |
|
233 |
-##' rotate 180 degree of a selected branch |
|
249 |
+##' rotate selected clade by 180 degree |
|
234 | 250 |
##' |
235 | 251 |
##' |
236 | 252 |
##' @title rotate |
237 | 253 |
##' @inheritParams get_taxa_name |
238 | 254 |
##' @return ggplot2 object |
239 | 255 |
##' @export |
256 |
+##' @examples |
|
257 |
+##' x <- rtree(15) |
|
258 |
+##' p <- ggtree(x) + geom_tiplab() |
|
259 |
+##' rotate(p, 17) |
|
240 | 260 |
##' @author Guangchuang Yu |
241 | 261 |
rotate <- function(tree_view=NULL, node) { |
242 | 262 |
tree_view %<>% get_tree_view |
... | ... |
@@ -271,15 +291,19 @@ rotate <- function(tree_view=NULL, node) { |
271 | 291 |
|
272 | 292 |
|
273 | 293 |
|
274 |
-##' flip position of two selected branches |
|
294 |
+##' exchange the position of 2 clades |
|
275 | 295 |
##' |
276 | 296 |
##' |
277 | 297 |
##' @title flip |
278 | 298 |
##' @param tree_view tree view (i.e. the ggtree object). If tree_view is NULL, the last ggplot will be used. |
279 |
-##' @param node1 node number of branch 1 |
|
280 |
-##' @param node2 node number of branch 2 |
|
281 |
-##' @return ggplot2 object |
|
299 |
+##' @param node1 node number of clade 1. It should share a same parent node with node2 |
|
300 |
+##' @param node2 node number of clade 2. It should share a same parent node with node1 |
|
301 |
+##' @return ggplot object |
|
282 | 302 |
##' @export |
303 |
+##' x <- rtree(15) |
|
304 |
+##' p <- ggtree(x) + geom_tiplab() + |
|
305 |
+##' geom_nodelab(aes(subset=!isTip, label=node), hjust = -.1, color = "red") |
|
306 |
+##' flip(p, 19, 20) ## Depends on the condition of your tree |
|
283 | 307 |
##' @author Guangchuang Yu |
284 | 308 |
flip <- function(tree_view=NULL, node1, node2) { |
285 | 309 |
tree_view %<>% get_tree_view |
... | ... |
@@ -342,17 +366,22 @@ flip <- function(tree_view=NULL, node1, node2) { |
342 | 366 |
} |
343 | 367 |
|
344 | 368 |
|
345 |
-##' scale clade |
|
369 |
+##' zoom out/in a selected clade to emphasize or de-emphasize it |
|
346 | 370 |
##' |
347 | 371 |
##' |
348 | 372 |
##' @title scaleClade |
349 | 373 |
##' @inheritParams get_taxa_name |
350 |
-##' @param scale scale |
|
351 |
-##' @param vertical_only logical. If TRUE, only vertical will be scaled. |
|
374 |
+##' @param scale the scale of the selected clade. The clade will be zoom in when scale > 1, |
|
375 |
+##' and will be zoom out when scale < 1 |
|
376 |
+##' @param vertical_only logical. If TRUE (default), only vertical will be scaled. |
|
352 | 377 |
##' If FALSE, the clade will be scaled vertical and horizontally. |
353 |
-##' TRUE by default. |
|
354 | 378 |
##' @return tree view |
355 | 379 |
##' @export |
380 |
+##' @examples |
|
381 |
+##' x <- rtree(15) |
|
382 |
+##' p <- ggtree(x) + geom_tiplab() + |
|
383 |
+##' geom_nodelab(aes(subset=!isTip, label=node), hjust = -.1, color = "red") |
|
384 |
+##' scaleClade(p, 24, scale = .1) |
|
356 | 385 |
##' @author Guangchuang Yu |
357 | 386 |
scaleClade <- function(tree_view=NULL, node, scale=1, vertical_only=TRUE) { |
358 | 387 |
tree_view %<>% get_tree_view |
... | ... |
@@ -431,15 +460,20 @@ reassign_y_from_node_to_root <- function(df, node) { |
431 | 460 |
} |
432 | 461 |
|
433 | 462 |
|
434 |
-##' zoom selected clade of a tree |
|
463 |
+##' zoom in on a selected clade of a tree, while showing its on the full view of tree as a seperated panel for reference |
|
435 | 464 |
##' |
436 | 465 |
##' |
437 | 466 |
##' @title zoomClade |
438 | 467 |
##' @inheritParams get_taxa_name |
439 |
-##' @param xexpand numeric, extend x, meaning the ratio of range of original x, |
|
468 |
+##' @param xexpand numeric, expend the xlim of the zoom area. |
|
440 | 469 |
##' default is NULL. |
441 | 470 |
##' @return full tree with zoom in clade |
442 | 471 |
##' @author Guangchuang Yu |
472 |
+##' @examples |
|
473 |
+##' x <- rtree(15) |
|
474 |
+##' p <- ggtree(x) + geom_tiplab() + |
|
475 |
+##' geom_nodelab(aes(subset=!isTip, label=node), hjust = -.1, color = "red") |
|
476 |
+##' zoomClade(p, 21, xexpand = .2) |
|
443 | 477 |
##' @export |
444 | 478 |
zoomClade <- function(tree_view = NULL, node, xexpand=NULL) { |
445 | 479 |
p <- get_tree_view(tree_view) |
... | ... |
@@ -1,9 +1,9 @@ |
1 |
-##' label facet_plot output |
|
1 |
+##' function to relable selected panels created by 'geom_facet' or 'facet-plot' |
|
2 | 2 |
##' |
3 | 3 |
##' |
4 | 4 |
##' @title facet_labeller |
5 | 5 |
##' @param p facet_plot output |
6 |
-##' @param label labels of facet panels |
|
6 |
+##' @param label new labels of facet panels |
|
7 | 7 |
##' @return ggplot object |
8 | 8 |
##' @importFrom ggplot2 as_labeller |
9 | 9 |
##' @export |
... | ... |
@@ -2,11 +2,13 @@ |
2 | 2 |
|
3 | 3 |
##' zoom selected clade of a tree |
4 | 4 |
##' |
5 |
+##' 'geom_zoom_clade' zooms in on a selected clade of a tree, |
|
6 |
+##' while showing its on the full view of tree as a seperated panel for reference |
|
5 | 7 |
##' |
6 | 8 |
##' @title geom_zoom_clade |
7 |
-##' @param node internal node number |
|
8 |
-##' @param xexpand numeric, extend x, meaning the ratio of range of original x, |
|
9 |
-##' default is NULL. |
|
9 |
+##' @param node internal node number to zoom in its corresponding clade |
|
10 |
+##' @param xexpand numeric, extend x, meaning the ratio of range of the xlim of the original tree, |
|
11 |
+##' defaults to NULL. |
|
10 | 12 |
##' @return updated tree view |
11 | 13 |
##' @author Guangchuang Yu |
12 | 14 |
##' @export |
... | ... |
@@ -4,20 +4,32 @@ |
4 | 4 |
#' correspond to multichotomies will not be displayed. |
5 | 5 |
#' |
6 | 6 |
#' @title geom_balance |
7 |
-#' @param node selected node (balance) to highlight |
|
8 |
-#' @param fill color fill |
|
9 |
-#' @param color color to outline highlights and divide balance |
|
10 |
-#' @param alpha alpha (transparency) |
|
11 |
-#' @param extend extend xmax of the rectangle |
|
12 |
-#' @param extendto extend xmax to extendto |
|
7 |
+#' @param node selected node (balance) to highlight its two direct descendant |
|
8 |
+#' @param fill color to fill in the highlight rectangle, default to "steelblue" |
|
9 |
+#' @param color color to outline highlight rectangle and divide balance, defaults to "white" |
|
10 |
+#' @param alpha alpha (transparency) for the highlight rectangle, defaults to 0.5 |
|
11 |
+#' @param extend extend xmax of the highlight rectangle by the value of extend |
|
12 |
+#' @param extendto extend xmax of the highlight rectangle to the value of extendto |
|
13 | 13 |
#' @return ggplot2 |
14 | 14 |
#' @export |
15 | 15 |
#' @importFrom ggplot2 aes_ |
16 | 16 |
#' @importFrom ggplot2 GeomRect |
17 | 17 |
#' @importFrom utils packageVersion |
18 | 18 |
#' @author Justin Silverman and modified by Guangchuang Yu |
19 |
-#' @references J. Silverman, et al. *A phylogenetic transform enhances |
|
20 |
-#' analysis of compositional microbiota data*. (in preparation) |
|
19 |
+#' @examples |
|
20 |
+#' library(ggtree) |
|
21 |
+#' set.seed(123) |
|
22 |
+#' tr<- rtree(15) |
|
23 |
+#' x <- ggtree(tr) |
|
24 |
+#' x + geom_balance(17) |
|
25 |
+#' |
|
26 |
+#' @references |
|
27 |
+#' J. Silverman, et al. *A phylogenetic transform enhances |
|
28 |
+#' analysis of compositional microbiota data*. (in preparation) |
|
29 |
+#' |
|
30 |
+#' For more detailed demonstration, please refer to chapter 5.2.2 of |
|
31 |
+#' *Data Integration, Manipulation and Visualization of Phylogenetic Trees* |
|
32 |
+#' <http://yulab-smu.top/treedata-book/index.html> by Guangchuang Yu. |
|
21 | 33 |
geom_balance <- function(node, fill="steelblue", color='white', alpha=.5, extend=0, extendto=NULL) { |
22 | 34 |
|
23 | 35 |
data = NULL |
... | ... |
@@ -3,30 +3,30 @@ |
3 | 3 |
##' @title geom_cladelab |
4 | 4 |
##' @param node selected node to annotate, when data and mapping is NULL, it is required. |
5 | 5 |
##' @param label character, character to be showed, when data and mapping is NULL, it is required. |
6 |
-##' @param data data.frame, the data to be displayed in the annotation, default is NULL. |
|
7 |
-##' @param mapping Set of aesthetic mappings, default is NULL. The detail see the following explanation. |
|
6 |
+##' @param data data.frame, the data to be displayed in the annotation, defaults to NULL. |
|
7 |
+##' @param mapping Set of aesthetic mappings, defaults to NULL. The detail see the following explanation. |
|
8 | 8 |
##' @param geom character, one of 'text', 'label', 'shadowtext', 'image' and 'phylopic', |
9 |
-##' default is 'text', and the parameter see the Aesthetics For Specified Geom. |
|
10 |
-##' @param parse logical, whether parse label to emoji font, default is FALSE. |
|
9 |
+##' defaults to 'text', and the parameter see the Aesthetics For Specified Geom. |
|
10 |
+##' @param parse logical, whether parse label to emoji font, defaults to FALSE. |
|
11 | 11 |
##' @param ... additional parameters, see also following section. |
12 | 12 |
##' |
13 | 13 |
##' additional parameters can refer the following parameters. |
14 | 14 |
##' \itemize{ |
15 | 15 |
##' \item \code{offset} distance bar and tree, offset of bar and text from |
16 |
-##' the clade, default is 0. |
|
16 |
+##' the clade, defaults to 0. |
|
17 | 17 |
##' \item \code{offset.text} distance bar and text, offset of text from bar, |
18 |
-##' default is 0. |
|
19 |
-##' \item \code{align} logical, whether align clade lab, default is FALSE. |
|
20 |
-##' \item \code{extend} numeric, extend the length of bar, default is 0. |
|
18 |
+##' defaults to 0. |
|
19 |
+##' \item \code{align} logical, whether align clade lab, defaults to FALSE. |
|
20 |
+##' \item \code{extend} numeric, extend the length of bar, defaults to 0. |
|
21 | 21 |
##' \item \code{angle} numeric or 'auto', if angle is auto, the angle of text will |
22 |
-##' be calculated automatically, which is useful for the circular etc layout, default is 0. |
|
23 |
-##' \item \code{horizontal} logical, whether set label to horizontal, default is TRUE. |
|
24 |
-##' \item \code{barsize} the width of line, default is 0.5. |
|
25 |
-##' \item \code{barcolour} the colour of line, default is 'black'. |
|
26 |
-##' \item \code{fontsize} the size of text, default is 3.88. |
|
27 |
-##' \item \code{textcolour} the colour of text, default is 'black'. |
|
28 |
-##' \item \code{imagesize} the size of image, default is 0.05. |
|
29 |
-##' \item \code{imagecolor} the colour of image, default is NULL, when |
|
22 |
+##' be calculated automatically, which is useful for the circular etc layout, defaults to 0. |
|
23 |
+##' \item \code{horizontal} logical, whether set label to horizontal, defaults to TRUE. |
|
24 |
+##' \item \code{barsize} the width of line, defaults to 0.5. |
|
25 |
+##' \item \code{barcolour} the colour of line, defaults to 'black'. |
|
26 |
+##' \item \code{fontsize} the size of text, defaults to 3.88. |
|
27 |
+##' \item \code{textcolour} the colour of text, defaults to 'black'. |
|
28 |
+##' \item \code{imagesize} the size of image, defaults to 0.05. |
|
29 |
+##' \item \code{imagecolor} the colour of image, defaults to NULL, when |
|
30 | 30 |
##' geom="phylopic", it should be required. |
31 | 31 |
##' } |
32 | 32 |
##' The parameters also can be set in mapping, when data is provided. Note: the barsize, barcolour, |
... | ... |
@@ -40,16 +40,16 @@ |
40 | 40 |
##' \itemize{ |
41 | 41 |
##' \item \strong{\code{node}} selected node to hight light, it is required. |
42 | 42 |
##' \item \strong{\code{label}} labels showed, it is required. |
43 |
-##' \item \code{colour} the colour of text, default is "black". |
|
44 |
-##' \item \code{size} the size of text, default is 3.88. |
|
45 |
-##' \item \code{angle} the angle of text, default is 0. |
|
46 |
-##' \item \code{hjust} A numeric vector specifying horizontal justification, default is 0. |
|
47 |
-##' \item \code{vjust} A numeric vector specifying vertical justification, default is 0.5. |
|
48 |
-##' \item \code{alpha} the transparency of text, default is NA. |
|
49 |
-##' \item \code{family} the family of text, default is 'sans'. |
|
50 |
-##' \item \code{fontface} the font face of text, default is 1 (plain), others are |
|
43 |
+##' \item \code{colour} the colour of text, defaults to "black". |
|
44 |
+##' \item \code{size} the size of text, defaults to 3.88. |
|
45 |
+##' \item \code{angle} the angle of text, defaults to 0. |
|
46 |
+##' \item \code{hjust} A numeric vector specifying horizontal justification, defaults to 0. |
|
47 |
+##' \item \code{vjust} A numeric vector specifying vertical justification, defaults to 0.5. |
|
48 |
+##' \item \code{alpha} the transparency of text, defaults to NA. |
|
49 |
+##' \item \code{family} the family of text, defaults to 'sans'. |
|
50 |
+##' \item \code{fontface} the font face of text, defaults to 1 (plain), others are |
|
51 | 51 |
##' 2 (bold), 3 (italic), 4 (bold.italic). |
52 |
-##' \item \code{lineheight} The height of a line as a multiple of the size of text, default is 1.2 . |
|
52 |
+##' \item \code{lineheight} The height of a line as a multiple of the size of text, defaults to 1.2 . |
|
53 | 53 |
##' } |
54 | 54 |
##' when the colour, size are not be set in mapping, and user want to modify the colour of text, |
55 | 55 |
##' they should use textcolour, fontsize to avoid the confusion with bar layer annotation. |
... | ... |
@@ -59,17 +59,17 @@ |
59 | 59 |
##' \itemize{ |
60 | 60 |
##' \item \strong{\code{node}} selected node to hight light, it is required. |
61 | 61 |
##' \item \strong{\code{label}} labels to be showed, it is required. |
62 |
-##' \item \code{colour} the colour of text, default is "black". |
|
63 |
-##' \item \code{fill} the background colour of the label, default is "white". |
|
64 |
-##' \item \code{size} the size of text, default is 3.88. |
|
65 |
-##' \item \code{angle} the angle of text, default is 0. |
|
66 |
-##' \item \code{hjust} A numeric vector specifying horizontal justification, default is 0. |
|
67 |
-##' \item \code{vjust} A numeric vector specifying vertical justification, default is 0.5. |
|
68 |
-##' \item \code{alpha} the transparency of text, default is NA. |
|
69 |
-##' \item \code{family} the family of text, default is 'sans'. |
|
70 |
-##' \item \code{fontface} the font face of text, default is 1 (plain), others are |
|
62 |
+##' \item \code{colour} the colour of text, defaults to "black". |
|
63 |
+##' \item \code{fill} the background colour of the label, defaults to "white". |
|
64 |
+##' \item \code{size} the size of text, defaults to 3.88. |
|
65 |
+##' \item \code{angle} the angle of text, defaults to 0. |
|
66 |
+##' \item \code{hjust} A numeric vector specifying horizontal justification, defaults to 0. |
|
67 |
+##' \item \code{vjust} A numeric vector specifying vertical justification, defaults to 0.5. |
|
68 |
+##' \item \code{alpha} the transparency of text, defaults to NA. |
|
69 |
+##' \item \code{family} the family of text, defaults to 'sans'. |
|
70 |
+##' \item \code{fontface} the font face of text, defaults to 1 (plain), others are |
|
71 | 71 |
##' 2 (bold), 3 (italic), 4 (bold.italic). |
72 |
-##' \item \code{lineheight} The height of a line as a multiple of the size of text, default is 1.2 . |
|
72 |
+##' \item \code{lineheight} The height of a line as a multiple of the size of text, defaults to 1.2 . |
|
73 | 73 |
##' } |
74 | 74 |
##' when the colour, size are not be set in mapping, and user want to modify the colour of text, |
75 | 75 |
##' they should use textcolour, fontsize to avoid the confusion with bar layer annotation. |
... | ... |
@@ -79,18 +79,18 @@ |
79 | 79 |
##' \itemize{ |
80 | 80 |
##' \item \strong{\code{node}} selected node to hight light, it is required. |
81 | 81 |
##' \item \strong{\code{label}} labels to be showed, it is required. |
82 |
-##' \item \code{colour} the colour of text, default is "black". |
|
83 |
-##' \item \code{bg.colour} the background colour of text, default is 'black'. |
|
84 |
-##' \item \code{bg.r} the width of background text, default is 0.1. |
|
85 |
-##' \item \code{size} the size of text, default is 3.88. |
|
86 |
-##' \item \code{angle} the angle of text, default is 0. |
|
87 |
-##' \item \code{hjust} A numeric vector specifying horizontal justification, default is 0. |
|
88 |
-##' \item \code{vjust} A numeric vector specifying vertical justification, default is 0.5. |
|
89 |
-##' \item \code{alpha} the transparency of text, default is NA. |
|
90 |
-##' \item \code{family} the family of text, default is 'sans'. |
|
91 |
-##' \item \code{fontface} the font face of text, default is 1 (plain), others are |
|
82 |
+##' \item \code{colour} the colour of text, defaults to "black". |
|
83 |
+##' \item \code{bg.colour} the background colour of text, defaults to 'black'. |
|
84 |
+##' \item \code{bg.r} the width of background text, defaults to 0.1. |
|
85 |
+##' \item \code{size} the size of text, defaults to 3.88. |
|
86 |
+##' \item \code{angle} the angle of text, defaults to 0. |
|
87 |
+##' \item \code{hjust} A numeric vector specifying horizontal justification, defaults to 0. |
|
88 |
+##' \item \code{vjust} A numeric vector specifying vertical justification, defaults to 0.5. |
|
89 |
+##' \item \code{alpha} the transparency of text, defaults to NA. |
|
90 |
+##' \item \code{family} the family of text, defaults to 'sans'. |
|
91 |
+##' \item \code{fontface} the font face of text, defaults to 1 (plain), others are |
|
92 | 92 |
##' 2 (bold), 3 (italic), 4 (bold.italic). |
93 |
-##' \item \code{lineheight} The height of a line as a multiple of the size of text, default is 1.2 . |
|
93 |
+##' \item \code{lineheight} The height of a line as a multiple of the size of text, defaults to 1.2 . |
|
94 | 94 |
##' } |
95 | 95 |
##' when the colour, size are not be set in mapping, and user want to modify the colour of text, |
96 | 96 |
##' they should use textcolour, fontsize to avoid the confusion with bar layer annotation. |
... | ... |
@@ -102,9 +102,9 @@ |
102 | 102 |
##' \item \strong{\code{label}} labels to be showed, it is required. |
103 | 103 |
##' \item \strong{\code{image}} the image to be annotated, when geom="phylopic", |
104 | 104 |
##' the uid of phylopic databases, it is required. |
105 |
-##' \item \code{colour} the color of image, default is NULL. |
|
106 |
-##' \item \code{size} the size of image, default is 0.05. |
|
107 |
-##' \item \code{alpha} the alpha of image, default is 0.8. |
|
105 |
+##' \item \code{colour} the color of image, defaults to NULL. |
|
106 |
+##' \item \code{size} the size of image, defaults to 0.05. |
|
107 |
+##' \item \code{alpha} the alpha of image, defaults to 0.8. |
|
108 | 108 |
##' } |
109 | 109 |
##' when the colour, size are not be set in mapping, and user want to modify the colour of image, |
110 | 110 |
##' they should use imagecolour, imagesize to avoid the confusion with bar layer annotation. |
... | ... |
@@ -18,7 +18,7 @@ |
18 | 18 |
##' @param family sans by default, can be any supported font |
19 | 19 |
##' @param parse logical, whether parse label |
20 | 20 |
##' @param horizontal logical, whether set label to horizontal, |
21 |
-##' default is TRUE. |
|
21 |
+##' defaults to TRUE. |
|
22 | 22 |
##' @param ... additional parameter |
23 | 23 |
##' @return ggplot layers |
24 | 24 |
##' @export |
... | ... |
@@ -5,10 +5,10 @@ |
5 | 5 |
#' |
6 | 6 |
#' @title geom_hilight |
7 | 7 |
#' @rdname geom-hilight |
8 |
-#' @param data data.frame, The data to be displayed in this layer, default is NULL. |
|
9 |
-#' @param mapping Set of aesthetic mappings, default is NULL. |
|
8 |
+#' @param data data.frame, The data to be displayed in this layer, defaults to NULL. |
|
9 |
+#' @param mapping Set of aesthetic mappings, defaults to NULL. |
|
10 | 10 |
#' @param node selected node to hilight, when data and mapping is NULL, it is required. |
11 |
-#' @param type the type of layer, default is `auto`, meaning rectangular, circular, |
|
11 |
+#' @param type the type of layer, defaults to `auto`, meaning rectangular, circular, |
|
12 | 12 |
#' slanted, fan, inward_circular, radial, equal_angle, ape layout tree will use rectangular layer, |
13 | 13 |
#' unrooted and daylight layout tree use will use encircle layer. You can specify this parameter to |
14 | 14 |
#' `rect` (rectangular layer) or `encircle` (encircle layer), 'gradient' (gradient color), |
... | ... |
@@ -18,39 +18,39 @@ |
18 | 18 |
#' \item \code{align} control the align direction of the edge of high light rectangular. |
19 | 19 |
#' Options is 'none' (default), 'left', 'right', 'both'. This argument only work when the |
20 | 20 |
#' 'geom_hilight' is plotting using geom_hilight(mapping=aes(...)). |
21 |
-#' \item \code{gradient.direction} character, the direction of gradient color, default is 'rt' |
|
21 |
+#' \item \code{gradient.direction} character, the direction of gradient color, defaults to 'rt' |
|
22 | 22 |
#' meaning the locations of gradient color is from root to tip, options are 'rt' and 'tr'. |
23 | 23 |
#' \item \code{gradient.length.out} integer, desired length of the sequence of gradient color, |
24 |
-#' default is 2. |
|
24 |
+#' defaults to 2. |
|
25 | 25 |
#' \item \code{roundrect.r} numeric, the radius of the rounded corners, when \code{roundrect=TRUE}, |
26 |
-#' default is 0.05. |
|
26 |
+#' defaults to 0.05. |
|
27 | 27 |
#' } |
28 | 28 |
#' @section Aesthetics: |
29 | 29 |
#' \code{geom_hilight()} understands the following aesthetics for rectangular layer (required |
30 | 30 |
#' aesthetics are in bold): |
31 | 31 |
#' \itemize{ |
32 | 32 |
#' \item \strong{\code{node}} selected node to hight light, it is required. |
33 |
-#' \item \code{colour} the colour of margin, default is NA. |
|
34 |
-#' \item \code{fill} the colour of fill, default is 'steelblue'. |
|
35 |
-#' \item \code{alpha} the transparency of fill, default is 0.5. |
|
36 |
-#' \item \code{extend} extend xmax of the rectangle, default is 0. |
|
37 |
-#' \item \code{extendto} specify a value, meaning the rectangle extend to, default is NULL. |
|
38 |
-#' \item \code{linetype} the line type of margin, default is 1. |
|
39 |
-#' \item \code{size} the width of line of margin, default is 0.5. |
|
33 |
+#' \item \code{colour} the colour of margin, defaults to NA. |
|
34 |
+#' \item \code{fill} the colour of fill, defaults to 'steelblue'. |
|
35 |
+#' \item \code{alpha} the transparency of fill, defaults to 0.5. |
|
36 |
+#' \item \code{extend} extend xmax of the rectangle, defaults to 0. |
|
37 |
+#' \item \code{extendto} specify a value, meaning the rectangle extend to, defaults to NULL. |
|
38 |
+#' \item \code{linetype} the line type of margin, defaults to 1. |
|
39 |
+#' \item \code{size} the width of line of margin, defaults to 0.5. |
|
40 | 40 |
#' } |
41 | 41 |
#' \code{geom_hilight()} understands the following aesthethics for encircle layer (required |
42 | 42 |
#' aesthetics are in bold): |
43 | 43 |
#' \itemize{ |
44 | 44 |
#' \item \strong{\code{node}} selected node to hight light, it is required. |
45 |
-#' \item \code{colour} the colour of margin, default is 'black'. |
|
46 |
-#' \item \code{fill} the colour of fill, default is 'steelblue'. |
|
47 |
-#' \item \code{alpha} the transparency of fill, default is 0.5. |
|
48 |
-#' \item \code{expand} expands the xspline clade region, default is 0. |
|
45 |
+#' \item \code{colour} the colour of margin, defaults to 'black'. |
|
46 |
+#' \item \code{fill} the colour of fill, defaults to 'steelblue'. |
|
47 |
+#' \item \code{alpha} the transparency of fill, defaults to 0.5. |
|
48 |
+#' \item \code{expand} expands the xspline clade region, defaults to 0. |
|
49 | 49 |
#' \item \code{spread} control the size, when only one point. |
50 |
-#' \item \code{size} the width of line of margin, default is 0.5. |
|
51 |
-#' \item \code{linetype} the line type of margin, default is 1. |
|
52 |
-#' \item \code{s_shape} the shape of the spline relative to the control points, default is 0.5. |
|
53 |
-#' \item \code{s_open} whether the spline is a line or a closed shape, default is FALSE. |
|
50 |
+#' \item \code{size} the width of line of margin, defaults to 0.5. |
|
51 |
+#' \item \code{linetype} the line type of margin, defaults to 1. |
|
52 |
+#' \item \code{s_shape} the shape of the spline relative to the control points, defaults to 0.5. |
|
53 |
+#' \item \code{s_open} whether the spline is a line or a closed shape, defaults to FALSE. |
|
54 | 54 |
#' } |
55 | 55 |
#' @return a list object. |
56 | 56 |
#' @author Guangchuang Yu and Shuangbin Xu |
... | ... |
@@ -74,6 +74,10 @@ |
74 | 74 |
#' # display the high light layer with round rectangular. |
75 | 75 |
#' p8 <- p + geom_hilight(data=dat, mapping=aes(node=id, fill=type), type = "roundrect", alpha=0.68) |
76 | 76 |
#' p2/ p3/ p4/ p5 / p6/ p7/ p8 |
77 |
+#' @references |
|
78 |
+#' For more detailed demonstration, please refer to chapter 5.2.2 of |
|
79 |
+#' *Data Integration, Manipulation and Visualization of Phylogenetic Trees* |
|
80 |
+#' <http://yulab-smu.top/treedata-book/index.html> by Guangchuang Yu. |
|
77 | 81 |
geom_hilight <- function(data=NULL, |
78 | 82 |
mapping=NULL, |
79 | 83 |
node=NULL, |
... | ... |
@@ -1,30 +1,41 @@ |
1 | 1 |
##' geom_label2 support aes(subset) via setup_data |
2 | 2 |
##' |
3 |
+##' 'geom_label2' is a modified version of geom_label, with subset aesthetic supported |
|
3 | 4 |
##' |
4 | 5 |
##' @title geom_label2 |
5 |
-##' @param mapping the aesthetic mapping |
|
6 |
+##' @param mapping Set of aesthetic mappings, defaults to NULL. |
|
6 | 7 |
##' @param data A layer specific dataset - |
7 | 8 |
##' only needed if you want to override the plot defaults. |
8 |
-##' @param ... other arguments passed on to 'layer' |
|
9 |
-##' @param stat Name of stat to modify data |
|
10 |
-##' @param position The position adjustment to use for overlapping points on this layer |
|
11 |
-##' @param family sans by default, can be any supported font |
|
12 |
-##' @param parse if TRUE, the labels will be parsed as expressions |
|
13 |
-##' @param nudge_x horizontal adjustment |
|
14 |
-##' @param nudge_y vertical adjustment |
|
15 |
-##' @param label.padding Amount of padding around label. |
|
16 |
-##' @param label.r Radius of rounded corners. |
|
17 |
-##' @param label.size Size of label border, in mm |
|
18 |
-##' @param na.rm logical |
|
19 |
-##' @param show.legend logical |
|
20 |
-##' @param inherit.aes logical |
|
9 |
+##' @param ... other arguments passed on to 'layer'. |
|
10 |
+##' @param stat Name of the stat to modify data. |
|
11 |
+##' @param position The position adjustment to use for overlapping points on this layer. |
|
12 |
+##' @param family "sans" by default, can be any supported font. |
|
13 |
+##' @param parse if 'TRUE', the labels will be parsed as expressions, defaults to 'FALSE'. |
|
14 |
+##' @param nudge_x adjust the horizontal position of the labels. |
|
15 |
+##' @param nudge_y adjust the vertical position of the labels. |
|
16 |
+##' @param label.padding Amount of padding around label, defaults to 'unit(0.25, "lines")'. |
|
17 |
+##' @param label.r Use to set the radius of rounded corners of the label, defaults to 'unit(0.15, "lines")'. |
|
18 |
+##' @param label.size Size of label border, in mm, defaults to 0.25. |
|
19 |
+##' @param na.rm If "FALSE" (default), missing values are removed with a warning. If "TRUE", missing values are silently removed, logical. |
|
20 |
+##' @param show.legend Whether to show legend, logical, defaults to "NA". |
|
21 |
+##' @param inherit.aes Whether to inherit aesthetic mappings, logical, defaults to "TRUE". |
|
21 | 22 |
##' @return label layer |
22 | 23 |
##' @importFrom ggplot2 layer |
23 | 24 |
##' @importFrom ggplot2 position_nudge |
25 |
+##' @examples |
|
26 |
+##' library(ggtree) |
|
27 |
+##' set.seed(123) |
|
28 |
+##' tr<- rtree(15) |
|
29 |
+##' x <- ggtree(tr) |
|
30 |
+##' x + geom_label2(aes(label = node, subset = isTip == FALSE)) |
|
24 | 31 |
##' @export |
25 | 32 |
##' @seealso |
26 | 33 |
##' [geom_label][ggplot2::geom_label] |
27 | 34 |
##' @author Guangchuang Yu |
35 |
+##' @references |
|
36 |
+##' For more detailed demonstration of this function, please refer to chapter A.4.5 of |
|
37 |
+##' *Data Integration, Manipulation and Visualization of Phylogenetic Trees* |
|
38 |
+##' <http://yulab-smu.top/treedata-book/index.html> by Guangchuang Yu. |
|
28 | 39 |
geom_label2 <- function(mapping = NULL, data = NULL, |
29 | 40 |
..., |
30 | 41 |
stat = "identity", |
... | ... |
@@ -1,12 +1,12 @@ |
1 |
-##' add node label layer |
|
1 |
+##' add node label layer for a tree |
|
2 | 2 |
##' |
3 | 3 |
##' |
4 | 4 |
##' @title geom_nodelab |
5 |
-##' @param mapping aes mapping |
|
6 |
-##' @param nudge_x horizontal adjustment to nudge label |
|
7 |
-##' @param nudge_y vertical adjustment to nudge label |
|
5 |
+##' @param mapping aesthetic mappings, defaults to NULL |
|
6 |
+##' @param nudge_x horizontal adjustment to nudge labels, defaults to 0 |
|
7 |
+##' @param nudge_y vertical adjustment to nudge labels, defaults to 0 |
|
8 | 8 |
##' @param geom one of 'text', "shadowtext", 'label', 'image' and 'phylopic' |
9 |
-##' @param hjust horizontal alignment, one of 0, 0.5 or 1 |
|
9 |
+##' @param hjust horizontal alignment, defaults to 0.5 |
|
10 | 10 |
##' @param node a character indicating which node labels will be displayed, |
11 | 11 |
##' it should be one of 'internal', 'external' and 'all'. If it is set to 'internal' |
12 | 12 |
##' will display internal node labels, 'external' will display the tip labels, |
... | ... |
@@ -17,6 +17,10 @@ |
17 | 17 |
##' @return geom layer |
18 | 18 |
##' @export |
19 | 19 |
##' @author Guangchuang Yu |
20 |
+##' @references |
|
21 |
+##' For demonstration of this function, please refer to chapter A.4.5 of |
|
22 |
+##' *Data Integration, Manipulation and Visualization of Phylogenetic Trees* |
|
23 |
+##' <http://yulab-smu.top/treedata-book/index.html> by Guangchuang Yu. |
|
20 | 24 |
geom_nodelab <- function(mapping = NULL, nudge_x = 0, nudge_y = 0, geom = "text", hjust = 0.5, node="internal",...) { |
21 | 25 |
|
22 | 26 |
p <- geom_tiplab(mapping, offset = nudge_x, nudge_y = nudge_y, geom = geom, hjust = hjust, ...) |
... | ... |
@@ -1,5 +1,5 @@ |
1 | 1 |
|
2 |
-##' add tip point |
|
2 |
+##' add tip point layer for a tree |
|
3 | 3 |
##' |
4 | 4 |
##' |
5 | 5 |
##' @title geom_tippoint |
... | ... |
@@ -7,6 +7,15 @@ |
7 | 7 |
##' @return tip point layer |
8 | 8 |
##' @export |
9 | 9 |
##' @author Guangchuang Yu |
10 |
+##' @examples |
|
11 |
+##' library(ggtree) |
|
12 |
+##' tr<- rtree(15) |
|
13 |
+##' x <- ggtree(tr) |
|
14 |
+##' x + geom_tippoint() |
|
15 |
+##' @references |
|
16 |
+##' For more detailed demonstration, please refer to chapter 4.3.2 of |
|
17 |
+##' *Data Integration, Manipulation and Visualization of Phylogenetic Trees* |
|
18 |
+##' <http://yulab-smu.top/treedata-book/index.html> by Guangchuang Yu. |
|
10 | 19 |
geom_tippoint <- function(mapping = NULL, data = NULL, |
11 | 20 |
position = "identity", na.rm = FALSE, |
12 | 21 |
show.legend = NA, inherit.aes = TRUE, ...) { |
... | ... |
@@ -49,7 +58,7 @@ geom_tippoint <- function(mapping = NULL, data = NULL, |
49 | 58 |
## } |
50 | 59 |
|
51 | 60 |
|
52 |
-##' add node point |
|
61 |
+##' add node point layer to a tree |
|
53 | 62 |
##' |
54 | 63 |
##' |
55 | 64 |
##' @title geom_nodepoint |
... | ... |
@@ -58,6 +67,14 @@ geom_tippoint <- function(mapping = NULL, data = NULL, |
58 | 67 |
##' @importFrom ggplot2 aes_string |
59 | 68 |
##' @export |
60 | 69 |
##' @author Guangchuang Yu |
70 |
+##' library(ggtree) |
|
71 |
+##' tr<- rtree(15) |
|
72 |
+##' x <- ggtree(tr) |
|
73 |
+##' x + geom_nodepoint() |
|
74 |
+##' @references |
|
75 |
+##' For more detailed demonstration, please refer to chapter 4.3.2 of |
|
76 |
+##' *Data Integration, Manipulation and Visualization of Phylogenetic Trees* |
|
77 |
+##' <http://yulab-smu.top/treedata-book/index.html> by Guangchuang Yu. |
|
61 | 78 |
geom_nodepoint <- function(mapping = NULL, data = NULL, |
62 | 79 |
position = "identity", na.rm = FALSE, |
63 | 80 |
show.legend = NA, inherit.aes = TRUE, ...) { |
... | ... |
@@ -80,9 +97,9 @@ geom_nodepoint <- function(mapping = NULL, data = NULL, |
80 | 97 |
} |
81 | 98 |
|
82 | 99 |
|
83 |
-##' geom_rootpoint is used to add root point |
|
100 |
+##' geom_rootpoint is used to add root point layer to a tree |
|
84 | 101 |
##' |
85 |
-##' geom_rootpoint inherit from geom_point2, it is used to display and customize the points on the root |
|
102 |
+##' geom_rootpoint inherit from geom_point2, and it is used to display and customize the points on the root |
|
86 | 103 |
##' |
87 | 104 |
##' @title geom_rootpoint |
88 | 105 |
##' @inheritParams geom_point2 |
... | ... |
@@ -136,13 +153,13 @@ geom_rootpoint <- function(mapping = NULL, data = NULL, |
136 | 153 |
#' If `inherit.aes = TRUE`, the mapping can be inherited from the plot mapping as |
137 | 154 |
#' specified in the call to `ggplot()`. |
138 | 155 |
#' @param data The data to be displayed in this layer. If 'NULL' (the default), |
139 |
-#' the data is inherited from the plot data as specified in the call to 'ggplot()', |
|
156 |
+#' the data is inherited from the plot data as specified in the call to `ggplot()`. |
|
140 | 157 |
#' @param stat Name of the statistical transformation to be used on the data for this layer. |
141 | 158 |
#' @param position Position adjustment. |
142 |
-#' @param na.rm logical. If 'FALSE' (the default), missing values are removed with a warning. If 'TRUE', missing values are silently removed. |
|
159 |
+#' @param na.rm logical. If 'FALSE' (default), missing values are removed with a warning. If 'TRUE', missing values are silently removed. |
|
143 | 160 |
#' @param show.legend logical. Should this layer be included in the legends? |
144 | 161 |
#' 'NA', the default, includes if any aesthetics are mapped. 'FALSE' never includes, and 'TRUE' always includes. |
145 |
-#' @param inherit.aes logical (default is 'TRUE'). If 'FALSE', overrides the default aesthetics, |
|
162 |
+#' @param inherit.aes logical (defaults to 'TRUE'). If 'FALSE', overrides the default aesthetics, |
|
146 | 163 |
#' rather then combining with them. |
147 | 164 |
#' @param ... addtional parameters that passed on to this layer. These are often aesthetics, used to set an aesthetic to a fixed value, like `colour = "red"` or `size = 3`. |
148 | 165 |
#' @importFrom ggplot2 layer |
... | ... |
@@ -150,12 +167,12 @@ geom_rootpoint <- function(mapping = NULL, data = NULL, |
150 | 167 |
#' \code{geom_point2()} understands the following aesthetics |
151 | 168 |
#' \itemize{ |
152 | 169 |
#' \item \code{subset} logical expression indicating elements or rows to keep: missing values are taken as false; should be in aes(). |
153 |
-#' \item \code{colour} the colour of point, default is black. |
|
154 |
-#' \item \code{fill} the colour of fill, default is black. |
|
155 |
-#' \item \code{alpha} the transparency of fill, default is 1. |
|
156 |
-#' \item \code{size} the size of point, default is 1.5. |
|
157 |
-#' \item \code{shape} specify a shape, default is 19. |
|
158 |
-#' \item \code{stroke} control point border thickness of point, default is 0.5. |
|
170 |
+#' \item \code{colour} the colour of point, defaults to "black". |
|
171 |
+#' \item \code{fill} the colour of fill, defaults to "black". |
|
172 |
+#' \item \code{alpha} the transparency of fill, defaults to 1. |
|
173 |
+#' \item \code{size} the size of point, defaults to 1.5. |
|
174 |
+#' \item \code{shape} specify a shape, defaults to 19. |
|
175 |
+#' \item \code{stroke} control point border thickness of point, defaults to 0.5. |
|
159 | 176 |
#' } |
160 | 177 |
#' @seealso |
161 | 178 |
#' [geom_point][ggplot2::geom_point]; |
... | ... |
@@ -1,14 +1,18 @@ |
1 |
-##' bar of range (HPD, range etc) to present uncertainty of evolutionary inference |
|
1 |
+##' horizontal bar of range (HPD, range etc) on nodes to present uncertainty of evolutionary inference |
|
2 | 2 |
##' |
3 | 3 |
##' |
4 | 4 |
##' @title geom_range |
5 |
-##' @param range range, e.g. "height_0.95_HPD" |
|
5 |
+##' @param range range(interval) to be displayed, e.g. "height_0.95_HPD" |
|
6 | 6 |
##' @param center center of the range, mean, median or auto (default, the center of the range) |
7 | 7 |
##' @param ... additional parameter, e.g. color, size, alpha |
8 | 8 |
##' @return ggplot layer |
9 | 9 |
##' @importFrom ggplot2 aes_string |
10 | 10 |
##' @export |
11 | 11 |
##' @author Guangchuang Yu |
12 |
+##' @references |
|
13 |
+##' For demonstration of this function, please refer to chapter 5.2.4 of |
|
14 |
+##' *Data Integration, Manipulation and Visualization of Phylogenetic Trees* |
|
15 |
+##' <http://yulab-smu.top/treedata-book/index.html> by Guangchuang Yu. |
|
12 | 16 |
geom_range <- function(range, center = "auto", ...) { |
13 | 17 |
structure(list(range = range, center = center, ...), class = "geom_range") |
14 | 18 |
} |
... | ... |
@@ -1,17 +1,17 @@ |
1 |
-#' display root edge |
|
1 |
+#' display root edge layer for a tree |
|
2 | 2 |
#' |
3 |
-#' `geom_rootedge` is used to create a rootedge. |
|
3 |
+#' `geom_rootedge` is used to create a rootedge as ggtree doesn’t plot the root edge by default. |
|
4 | 4 |
#' |
5 | 5 |
#' @title geom_rootedge |
6 |
-#' @param rootedge length of rootedge; use phylo$root.edge if rootedge = NULL (by default). |
|
6 |
+#' @param rootedge length of rootedge; use phylo$root.edge if rootedge = NULL (default). |
|
7 | 7 |
#' @param ... additional parameters |
8 | 8 |
#' |
9 | 9 |
#' Additional parameters can be referred to the following parameters: |
10 | 10 |
#' \itemize{ |
11 |
-#' \item \code{size} control the width of rootedge, default is 0.5. |
|
12 |
-#' \item \code{colour} color of rootedge, default is black. |
|
13 |
-#' \item \code{linetype} the type of line, default is 1. |
|
14 |
-#' \item \code{alpha} modify colour transparency, default is 1. |
|
11 |
+#' \item \code{size} control the width of rootedge, defaults to 0.5. |
|
12 |
+#' \item \code{colour} color of rootedge, defaults to black. |
|
13 |
+#' \item \code{linetype} the type of line, defaults to 1. |
|
14 |
+#' \item \code{alpha} modify colour transparency, defaults to 1. |
|
15 | 15 |
#' } |
16 | 16 |
# |
17 | 17 |
#' @return ggtree rootedge layer |
... | ... |
@@ -22,6 +22,7 @@ |
22 | 22 |
#' visualization and annotation of phylogenetic trees with their covariates and |
23 | 23 |
#' other associated data. Methods in Ecology and Evolution, 8(1):28-36. |
24 | 24 |
#' <https://doi.org/10.1111/2041-210X.12628> |
25 |
+#' |
|
25 | 26 |
#' @export |
26 | 27 |
#' @examples |
27 | 28 |
#' |
... | ... |
@@ -43,8 +44,10 @@ |
43 | 44 |
#' ## this will ignore tree$root.edge |
44 | 45 |
#' ggtree(tree2) + geom_tiplab() + geom_rootedge(rootedge = 3) |
45 | 46 |
#' |
46 |
-#' ## For more information about tree visualization, please refer to the online book |
|
47 |
-#' ## https://yulab-smu.top/treedata-book/chapter4.html |
|
47 |
+#' |
|
48 |
+#' ## For more detailed demonstration of this function, please refer to chapter A.4.5 of |
|
49 |
+#' ## *Data Integration, Manipulation and Visualization of Phylogenetic Trees* |
|
50 |
+#' ## <http://yulab-smu.top/treedata-book/index.html> by Guangchuang Yu. |
|
48 | 51 |
#' |
49 | 52 |
geom_rootedge <- function(rootedge = NULL, ...) { |
50 | 53 |
# add isTip for checking whether the x of tree is reversed. |
... | ... |
@@ -1,10 +1,13 @@ |
1 |
-##' add horizontal align lines |
|
1 |
+##' add horizontal align lines layer to a tree |
|
2 |
+##' |
|
3 |
+##' 'geom_aline'align all tips to the longest one by adding |
|
4 |
+##' padding characters to the right side of the tip. |
|
2 | 5 |
##' |
3 | 6 |
##' |
4 | 7 |
##' @title geom_aline |
5 | 8 |
##' @param mapping aes mapping |
6 |
-##' @param linetype line type |
|
7 |
-##' @param size line size |
|
9 |
+##' @param linetype set line type of the line, defaults to "dotted" |
|
10 |
+##' @param size set line size of the line, defaults to 1 |
|
8 | 11 |
##' @param ... additional parameter |
9 | 12 |
##' @return aline layer |
10 | 13 |
##' @export |
... | ... |
@@ -25,17 +28,19 @@ geom_aline <- function(mapping=NULL, linetype="dotted", size=1, ...) { |
25 | 28 |
|
26 | 29 |
##' geom_segment2 support aes(subset) via setup_data |
27 | 30 |
##' |
31 |
+##' 'geom_segment2' is a modified version of geom_segment, with subset aesthetic supported |
|
28 | 32 |
##' |
29 | 33 |
##' @title geom_segment2 |
30 |
-##' @param mapping aes mapping |
|
31 |
-##' @param data data |
|
32 |
-##' @param stat Name of stat to modify data |
|
33 |
-##' @param position position |
|
34 |
-##' @param lineend lineend |
|
35 |
-##' @param na.rm logical |
|
36 |
-##' @param show.legend logical |
|
37 |
-##' @param inherit.aes logical |
|
38 |
-##' @param nudge_x horizontal adjustment of x |
|
34 |
+##' @param mapping Set of aesthetic mappings, defaults to NULL |
|
35 |
+##' @param data A layer specific dataset - |
|
36 |
+##' only needed if you want to override the plot defaults. |
|
37 |
+##' @param stat Name of stat to modify data. |
|
38 |
+##' @param position The position adjustment to use for overlapping points on this layer. |
|
39 |
+##' @param lineend Line end style, one of butt (default), round and square. |
|
40 |
+##' @param na.rm If "FALSE" (default), missing values are removed with a warning. If "TRUE", missing values are silently removed, logical. |
|
41 |
+##' @param show.legend Whether to show legend, logical. |
|
42 |
+##' @param inherit.aes Whether to inherit aesthetic mappings, logical, defaults to "TRUE". |
|
43 |
+##' @param nudge_x adjust the horizontal position of the segments. |
|
39 | 44 |
##' @param arrow specification for arrow heads, as created by arrow(). |
40 | 45 |
##' @param arrow.fill fill color to usse for the arrow head (if closed). `NULL` means use `colour` aesthetic. |
41 | 46 |
##' @param ... additional parameter |
... | ... |
@@ -4,24 +4,34 @@ |
4 | 4 |
##' @title geom_strip |
5 | 5 |
##' @param taxa1 taxa1 |
6 | 6 |
##' @param taxa2 taxa2 |
7 |
-##' @param label optional label |
|
7 |
+##' @param label add label alongside the bar (optional) |
|
8 | 8 |
##' @param offset offset of bar and text from the clade |
9 | 9 |
##' @param offset.text offset of text from bar |
10 |
-##' @param align logical |
|
11 |
-##' @param barsize size of bar |
|
12 |
-##' @param extend extend bar vertically |
|
13 |
-##' @param fontsize size of text |
|
14 |
-##' @param angle angle of text |
|
10 |
+##' @param align logical, whether to align bars to the most distant bar ,defaults to "TRUE" |
|
11 |
+##' Note that if "FALSE", the bars might cross the tree |
|
12 |
+##' @param barsize set size of the bar |
|
13 |
+##' @param extend extend bar length vertically |
|
14 |
+##' @param fontsize set size of the text |
|
15 |
+##' @param angle set the angle of text |
|
15 | 16 |
##' @param geom one of 'text' or 'label' |
16 |
-##' @param hjust hjust |
|
17 |
-##' @param color color for bar and label |
|
18 |
-##' @param fill fill label background, only work with geom='label' |
|
19 |
-##' @param family sans by default, can be any supported font |
|
20 |
-##' @param parse logical, whether parse label |
|
17 |
+##' @param hjust adjust the horizonal position of the bar |
|
18 |
+##' @param color set color for bar and label |
|
19 |
+##' @param fill set color to fill label background, only work with geom='label' |
|
20 |
+##' @param family "sans" by default, can be any supported font |
|
21 |
+##' @param parse logical, whether to parse labels, if "TRUE", the labels will be parsed into expressions, defaults to "FALSE" |
|
21 | 22 |
##' @param ... additional parameter |
22 | 23 |
##' @return ggplot layers |
23 | 24 |
##' @export |
24 | 25 |
##' @author Guangchuang Yu |
26 |
+##' @examples |
|
27 |
+##' library(ggtree) |
|
28 |
+##' tr<- rtree(15) |
|
29 |
+##' x <- ggtree(tr) |
|
30 |
+##' x + geom_strip(13, 1, color = "red") + geom_strip(3, 7, color = "blue") |
|
31 |
+##' @references |
|
32 |
+##' For more detailed demonstration of this function, please refer to chapter 5.2.1 of |
|
33 |
+##' *Data Integration, Manipulation and Visualization of Phylogenetic Trees* |
|
34 |
+##' <http://yulab-smu.top/treedata-book/index.html> by Guangchuang Yu. |
|
25 | 35 |
geom_strip <- function(taxa1, taxa2, label, offset=0, offset.text=0, |
26 | 36 |
align=TRUE, barsize=0.5, extend=0, fontsize=3.88, |
27 | 37 |
angle=0, geom="text", hjust=0, color = 'black', fill=NA, family="sans", |
... | ... |
@@ -1,33 +1,43 @@ |
1 |
-##' add tip label layer |
|
1 |
+##' add tip label layer for a tree |
|
2 |
+##' |
|
3 |
+##' 'geom_tiplab' not only supports using text or label geom to display tip labels, |
|
4 |
+##' but also supports image geom to label tip with image files or phylopics. |
|
5 |
+##' |
|
6 |
+##' For adding tip labels to a tree with circular layout, 'geom_tiplab' will |
|
7 |
+##' automatically adjust the angle of the tip labels to the tree by |
|
8 |
+##' internally calling 'geom_tiplab2'. |
|
2 | 9 |
##' |
3 | 10 |
##' |
4 | 11 |
##' @title geom_tiplab |
5 | 12 |
##' @param mapping aes mapping |
6 |
-##' @param hjust horizontal adjustment |
|
13 |
+##' @param hjust horizontal adjustment, defaults to 0 |
|
7 | 14 |
##' @param offset tiplab offset, horizontal |
8 |
-##' adjustment to nudge tip labels, default is 0. |
|
9 |
-##' @param align align tip lab or not, logical |
|
10 |
-##' @param linetype linetype for adding line if align = TRUE |
|
11 |
-##' @param linesize line size of line if align = TRUE |
|
15 |
+##' adjustment to nudge tip labels, defaults to 0 |
|
16 |
+##' @param align if TRUE, align all tip labels to the longest tip by adding padding characters |
|
17 |
+##' to the left side of tip labels, defaults to "FALSE" |
|
18 |
+##' with a line connecting each tip and its corresponding label, defaults to "FALSE" |
|
19 |
+##' @param linetype set linetype of the line if align = TRUE, defaults to "dotted" |
|
20 |
+##' @param linesize set line size of the line if align = TRUE, defaults to 0.5 |
|
12 | 21 |
##' @param geom one of 'text', 'label', 'shadowtext', 'image' and 'phylopic' |
13 |
-##' @param as_ylab display tip labels as y-axis label, only works for rectangular and dendrogram layouts |
|
22 |
+##' @param as_ylab display tip labels as y-axis label, |
|
23 |
+##' only works for rectangular and dendrogram layouts, defaults to "FALSE" |
|
14 | 24 |
##' @param ... additional parameter |
15 | 25 |
##' |
16 | 26 |
##' additional parameters can refer the following parameters. |
17 | 27 |
##' |
18 | 28 |
##' The following parameters for geom="text". |
19 | 29 |
##' \itemize{ |
20 |
-##' \item \code{size} control the size of tip labels, default is 3.88. |
|
21 |
-##' \item \code{colour} control the colour of tip labels, default is "black". |
|
22 |
-##' \item \code{angle} control the angle of tip labels, default is 0. |
|
23 |
-##' \item \code{vjust} A numeric vector specifying vertical justification, default is 0.5. |
|
24 |
-##' \item \code{alpha} the transparency of text, default is NA. |
|
25 |
-##' \item \code{family} the family of text, default is 'sans'. |
|
26 |
-##' \item \code{fontface} the font face of text, default is 1 (plain), others are |
|
30 |
+##' \item \code{size} control the size of tip labels, defaults to 3.88. |
|
31 |
+##' \item \code{colour} control the colour of tip labels, defaults to "black". |
|
32 |
+##' \item \code{angle} control the angle of tip labels, defaults to 0. |
|
33 |
+##' \item \code{vjust} A numeric vector specifying vertical justification, defaults to 0.5. |
|
34 |
+##' \item \code{alpha} the transparency of text, defaults to NA. |
|
35 |
+##' \item \code{family} the family of text, defaults to 'sans'. |
|
36 |
+##' \item \code{fontface} the font face of text, defaults to 1 (plain), others are |
|
27 | 37 |
##' 2 (bold), 3 (italic), 4 (bold.italic). |
28 |
-##' \item \code{lineheight} The height of a line as a multiple of the size of text, default is 1.2 . |
|
29 |
-##' \item \code{nudge_x} horizontal adjustment to nudge labels, default is 0. |
|
30 |
-##' \item \code{nudge_y} vertical adjustment to nudge labels, default is 0. |
|
38 |
+##' \item \code{lineheight} The height of a line as a multiple of the size of text, defaults to 1.2 . |
|
39 |
+##' \item \code{nudge_x} horizontal adjustment to nudge labels, defaults to 0. |
|
40 |
+##' \item \code{nudge_y} vertical adjustment to nudge labels, defaults to 0. |
|
31 | 41 |
##' \item \code{check.overlap} if TRUE, text that overlaps previous text in the same layer |
32 | 42 |
##' will not be plotted. |
33 | 43 |
##' \item \code{parse} if TRUE, the labels will be parsed into expressions, if it is 'emoji', the labels |
... | ... |
@@ -36,49 +46,49 @@ |
36 | 46 |
##' |
37 | 47 |
##' The following parameters for geom="label". |
38 | 48 |
##' \itemize{ |
39 |
-##' \item \code{size} the size of tip labels, default is 3.88. |
|
40 |
-##' \item \code{colour} the colour of tip labels, default is "black". |
|
41 |
-##' \item \code{fill} the colour of rectangular box of labels, default is "white". |
|
42 |
-##' \item \code{vjust} numeric vector specifying vertical justification, default is 0.5. |
|
43 |
-##' \item \code{alpha} the transparency of labels, default is NA. |
|
44 |
-##' \item \code{family} the family of text, default is 'sans'. |
|
45 |
-##' \item \code{fontface} the font face of text, default is 1 (plain), others are |
|
49 |
+##' \item \code{size} the size of tip labels, defaults to 3.88. |
|
50 |
+##' \item \code{colour} the colour of tip labels, defaults to "black". |
|
51 |
+##' \item \code{fill} the colour of rectangular box of labels, defaults to "white". |
|
52 |
+##' \item \code{vjust} numeric vector specifying vertical justification, defaults to 0.5. |
|
53 |
+##' \item \code{alpha} the transparency of labels, defaults to NA. |
|
54 |
+##' \item \code{family} the family of text, defaults to 'sans'. |
|
55 |
+##' \item \code{fontface} the font face of text, defaults to 1 (plain), others are |
|
46 | 56 |
##' 2 (bold), 3 (italic), 4 (bold.italic). |
47 |
-##' \item \code{lineheight} The height of a line as a multiple of the size of text, default is 1.2. |
|
48 |
-##' \item \code{nudge_x} horizontal adjustment to nudge labels, default is 0. |
|
49 |
-##' \item \code{nudge_y} vertical adjustment, default is 0. |
|
57 |
+##' \item \code{lineheight} The height of a line as a multiple of the size of text, defaults to 1.2. |
|
58 |
+##' \item \code{nudge_x} horizontal adjustment to nudge labels, defaults to 0. |
|
59 |
+##' \item \code{nudge_y} vertical adjustment, defaults to 0. |
|
50 | 60 |
##' \item \code{check.overlap} if TRUE, text that overlaps previous text in the same layer |
51 | 61 |
##' will not be plotted. |
52 | 62 |
##' \item \code{parse} if TRUE, the labels will be parsed into expressions, if it is 'emoji', the labels |
53 | 63 |
##' will be parsed into emojifont. |
54 |
-##' \item \code{label.padding} Amount of padding around label, default is 'unit(0.25, "lines")'. |
|
55 |
-##' \item \code{label.r} Radius of rounded corners, default is 'unit(0.15, "lines")'. |
|
56 |
-##' \item \code{label.size} Size of label border, in mm, default is 0.25. |
|
64 |
+##' \item \code{label.padding} Amount of padding around label, defaults to 'unit(0.25, "lines")'. |
|
65 |
+##' \item \code{label.r} Radius of rounded corners, defaults to 'unit(0.15, "lines")'. |
|
66 |
+##' \item \code{label.size} Size of label border, in mm, defaults to 0.25. |
|
57 | 67 |
##' } |
58 | 68 |
##' |
59 | 69 |
##' The following parameters for geom="shadowtext", some parameters are like to geom="text". |
60 | 70 |
##' \itemize{ |
61 |
-##' \item \code{bg.colour} the background colour of text, default is "black". |
|
62 |
-##' \item \code{bg.r} the width of background of text, default is 0.1 . |
|
71 |
+##' \item \code{bg.colour} the background colour of text, defaults to "black". |
|
72 |
+##' \item \code{bg.r} the width of background of text, defaults to 0.1 . |
|
63 | 73 |
##' } |
64 | 74 |
##' |
65 | 75 |
##' The following parameters for geom="image" or geom="phylopic". |
66 | 76 |
##' \itemize{ |
67 | 77 |
##' \item \code{image} the image file path for geom='image', but when geom='phylopic', |
68 | 78 |
##' it should be the uid of phylopic databases. |
69 |
-##' \item \code{size} the image size, default is 0.05. |
|
70 |
-##' \item \code{colour} the color of image, default is NULL. |
|
71 |
-##' \item \code{alpha} the transparency of image, default is 0.8. |
|
79 |
+##' \item \code{size} the image size, defaults to 0.05. |
|
80 |
+##' \item \code{colour} the color of image, defaults to NULL. |
|
81 |
+##' \item \code{alpha} the transparency of image, defaults to 0.8. |
|
72 | 82 |
##' } |
73 | 83 |
##' |
74 | 84 |
##' The following parameters for the line when align = TRUE. |
75 | 85 |
##' \itemize{ |
76 |
-##' \item \code{colour} the colour of line, default is 'black'. |
|
77 |
-##' \item \code{alpha} the transparency of line, default is NA. |
|
86 |
+##' \item \code{colour} the colour of line, defaults to 'black'. |
|
87 |
+##' \item \code{alpha} the transparency of line, defaults to NA. |
|
78 | 88 |
##' \item \code{arrow} specification for arrow heads, |
79 |
-##' as created by arrow(), default is NULL. |
|
89 |
+##' as created by arrow(), defaults to NULL. |
|
80 | 90 |
##' \item \code{arrow.fill} fill color to usse for the arrow head (if closed), |
81 |
-##' default is 'NULL', meaning use 'colour' aesthetic. |
|
91 |
+##' defaults to 'NULL', meaning use 'colour' aesthetic. |
|
82 | 92 |
##' } |
83 | 93 |
##' @return tip label layer |
84 | 94 |
##' @importFrom ggplot2 geom_text |
... | ... |
@@ -89,6 +99,10 @@ |
89 | 99 |
##' require(ape) |
90 | 100 |
##' tr <- rtree(10) |
91 | 101 |
##' ggtree(tr) + geom_tiplab() |
102 |
+##' @references |
|
103 |
+##' For more detailed demonstration, please refer to chapter 4.3.3 of |
|
104 |
+##' *Data Integration, Manipulation and Visualization of Phylogenetic Trees* |
|
105 |
+##' <http://yulab-smu.top/treedata-book/index.html> by Guangchuang Yu. |
|
92 | 106 |
geom_tiplab <- function(mapping=NULL, hjust = 0, align = FALSE, linetype = "dotted", |
93 | 107 |
linesize=0.5, geom="text", offset=0, as_ylab = FALSE, ...) { |
94 | 108 |
structure(list(mapping = mapping, |
... | ... |
@@ -210,14 +224,21 @@ geom_tiplab_rectangular <- function(mapping=NULL, hjust = 0, align = FALSE, |
210 | 224 |
|
211 | 225 |
##' add tip label for circular layout |
212 | 226 |
##' |
227 |
+##' 'geom_tiplab2' will automatically adjust the angle of the tip labels |
|
228 |
+##' to the tree with circular layout |
|
213 | 229 |
##' |
214 | 230 |
##' @title geom_tiplab2 |
215 | 231 |
##' @param mapping aes mapping |
216 |
-##' @param hjust horizontal adjustment |
|
232 |
+##' @param hjust horizontal adjustment, defaults to 0 |
|
217 | 233 |
##' @param ... additional parameter, see geom_tiplab |
218 | 234 |
##' @return tip label layer |
219 | 235 |
##' @export |
220 | 236 |
##' @author Guangchuang Yu |
237 |
+##' @examples |
|
238 |
+##' library(ggtree) |
|
239 |
+##' set.seed(123) |
|
240 |
+##' tr <- rtree(10) |
|
241 |
+##' ggtree(tr, layout = "circular") + geom_tiplab2() |
|
221 | 242 |
##' @references <https://groups.google.com/forum/#!topic/bioc-ggtree/o35PV3iHO-0> |
222 | 243 |
##' @seealso [geom_tiplab] |
223 | 244 |
geom_tiplab2 <- function(mapping=NULL, hjust=0, ...) { |
... | ... |
@@ -263,10 +284,10 @@ geom_tiplab_circular <- geom_tiplab2 |
263 | 284 |
|
264 | 285 |
#' Padding taxa labels |
265 | 286 |
#' |
266 |
-#' This function add padding character to the left side of taxa labels. |
|
287 |
+#' This function adds padding characters to the left side of taxa labels, adjust their length to the longest label. |
|
267 | 288 |
#' @param label taxa label |
268 |
-#' @param justify should a character vector be left-justified, right-justified (default), centred or left alone. |
|
269 |
-#' @param pad padding character (default is a dot) |
|
289 |
+#' @param justify should a character vector be right-justified (default), left-justified, centred or left alone. |
|
290 |
+#' @param pad padding character (defaults to dots) |
|
270 | 291 |
#' |
271 | 292 |
#' @return Taxa labels with padding characters added |
272 | 293 |
#' @export |
... | ... |
@@ -3,10 +3,10 @@ |
3 | 3 |
##' |
4 | 4 |
##' @title geom_tree |
5 | 5 |
##' @param mapping aesthetic mapping |
6 |
-##' @param data data |
|
6 |
+##' @param data data of the tree |
|
7 | 7 |
##' @param layout one of 'rectangular', 'dendrogram', 'slanted', 'ellipse', 'roundrect', |
8 | 8 |
##' 'fan', 'circular', 'inward_circular', 'radial', 'equal_angle', 'daylight' or 'ape' |
9 |
-##' @param multiPhylo logical, whether input data contains multiple phylo class. |
|
9 |
+##' @param multiPhylo logical, whether input data contains multiple phylo class, defaults to "FALSE". |
|
10 | 10 |
##' @param continuous character, continuous transition for selected aesthethic ('size' |
11 | 11 |
##' or 'color'('colour')). It should be one of 'color' (or 'colour'), 'size', 'all' |
12 | 12 |
##' and 'none', default is 'none' |
... | ... |
@@ -30,6 +30,11 @@ |
30 | 30 |
##' @importFrom ggplot2 aes |
31 | 31 |
##' @export |
32 | 32 |
##' @author Yu Guangchuang |
33 |
+##' @examples |
|
34 |
+##' @references |
|
35 |
+##' For demonstration of this function, please refer to chapter 4.2.1 of |
|
36 |
+##' *Data Integration, Manipulation and Visualization of Phylogenetic Trees* |
|
37 |
+##' <http://yulab-smu.top/treedata-book/index.html> by Guangchuang Yu. |
|
33 | 38 |
geom_tree <- function(mapping=NULL, data=NULL, layout="rectangular", multiPhylo=FALSE, continuous="none", position="identity", ...) { |
34 | 39 |
if (is.logical(continuous)){ |
35 | 40 |
warning_wrap('The type of "continuous" argument was changed (v>=2.5.2). Now, |
... | ... |
@@ -1,20 +1,26 @@ |
1 |
-##' add tree scale |
|
1 |
+##' add tree scale to a tree |
|
2 |
+##' |
|
3 |
+##' 'geom_treescale' automatically adds a scale bar for evolutionary distance |
|
2 | 4 |
##' |
3 | 5 |
##' |
4 | 6 |
##' @title geom_treescale |
5 |
-##' @param x x position |
|
6 |
-##' @param y y position |
|
7 |
-##' @param width width of scale |
|
8 |
-##' @param offset offset of text to line |
|
9 |
-##' @param label the title of tree scale, default is NULL. |
|
10 |
-##' @param offset.label offset of scale title to line. |
|
11 |
-##' @param color color |
|
12 |
-##' @param linesize size of line |
|
13 |
-##' @param fontsize size of text |
|
14 |
-##' @param family sans by default, can be any supported font |
|
7 |
+##' @param x set x position of the scale |
|
8 |
+##' @param y set y position of the scale |
|
9 |
+##' @param width set the length of the tree scale |
|
10 |
+##' @param offset set offset of text to line, defaults to NULL |
|
11 |
+##' @param label set the title of tree scale, defaults to NULL. |
|
12 |
+##' @param offset.label set offset of the scale title to line. |
|
13 |
+##' @param color set color of the scale |
|
14 |
+##' @param linesize set size of line |
|
15 |
+##' @param fontsize set size of text |
|
16 |
+##' @param family 'sans' by default, can be any supported font |
|
15 | 17 |
##' @return ggplot layers |
16 | 18 |
##' @export |
17 | 19 |
##' @author Guangchuang Yu |
20 |
+##' @references |
|
21 |
+##' For demonstration of this function, please refer to chapter 4.3.1 of |
|
22 |
+##' *Data Integration, Manipulation and Visualization of Phylogenetic Trees* |
|
23 |
+##' <http://yulab-smu.top/treedata-book/index.html> by Guangchuang Yu. |
|
18 | 24 |
geom_treescale <- function(x=NULL, y=NULL, width=NULL, offset=NULL, |
19 | 25 |
offset.label=NULL, label=NULL, color="black", |
20 | 26 |
linesize=0.5, fontsize=3.88, family="sans") { |
... | ... |
@@ -1,11 +1,14 @@ |
1 | 1 |
##' drawing phylogenetic trees from list of phylo objects |
2 |
+##' |
|
3 |
+##' The trees plotted by 'ggdensitree()' will be stacked on top of each other and the |
|
4 |
+##' structures of the trees will be rotated to ensure the consistency of the tip order. |
|
2 | 5 |
##' |
3 | 6 |
##' @title ggdensitree |
4 | 7 |
##' @param data a list of phylo objects or any object with an as.phylo and fortify method |
5 | 8 |
##' @param mapping aesthetic mapping |
6 | 9 |
##' @param layout one of 'slanted', 'rectangluar', 'fan', 'circular' or 'radial' (default: 'slanted') |
7 | 10 |
##' @param tip.order the order of the tips by a character vector of taxa names; or an integer, N, to order the tips by the order of the tips in the Nth tree; 'mode' to order the tips by the most common order; 'mds' to order the tips based on MDS of the path length between the tips; or 'mds_dist' to order the tips based on MDS of the distance between the tips (default: 'mode') |
8 |
-##' @param align.tips TRUE to align trees by their tips and FALSE to align trees by their root (default: TRUE) |
|
11 |
+##' @param align.tips TRUE (default) to align trees by their tips and FALSE to align trees by their root |
|
9 | 12 |
##' @param jitter deviation to jitter tips |
10 | 13 |
##' @param ... additional parameters passed to fortify, ggtree and geom_tree |
11 | 14 |
##' @return tree layer |
... | ... |
@@ -13,6 +16,10 @@ |
13 | 16 |
##' @importFrom magrittr add |
14 | 17 |
##' @export |
15 | 18 |
##' @author Yu Guangchuang, Bradley R. Jones |
19 |
+##' @references |
|
20 |
+##' For more detailed demonstration of this function, please refer to chapter 4.4.2 of |
|
21 |
+##' *Data Integration, Manipulation and Visualization of Phylogenetic Trees* |
|
22 |
+##' <http://yulab-smu.top/treedata-book/index.html> by Guangchuang Yu. |
|
16 | 23 |
##' @examples |
17 | 24 |
##' require(ape) |
18 | 25 |
##' require(dplyr) |
... | ... |
@@ -37,6 +37,10 @@ |
37 | 37 |
##' visualization and annotation of phylogenetic trees with their covariates and |
38 | 38 |
##' other associated data. Methods in Ecology and Evolution, 8(1):28-36. |
39 | 39 |
##' <https://doi.org/10.1111/2041-210X.12628> |
40 |
+##' |
|
41 |
+##' For more information, please refer to |
|
42 |
+##' *Data Integration, Manipulation and Visualization of Phylogenetic Trees* |
|
43 |
+##' <http://yulab-smu.top/treedata-book/index.html> by Guangchuang Yu. |
|
40 | 44 |
##' @examples |
41 | 45 |
##' require(ape) |
42 | 46 |
##' tr <- rtree(10) |
... | ... |
@@ -1,25 +1,27 @@ |
1 |
-##' append a heatmap of a matrix to right side of phylogenetic tree |
|
1 |
+##' append a heatmap of a matrix to the right side of a phylogenetic tree |
|
2 | 2 |
##' |
3 | 3 |
##' |
4 | 4 |
##' @title gheatmap |
5 | 5 |
##' @param p tree view |
6 | 6 |
##' @param data matrix or data.frame |
7 |
-##' @param offset offset of heatmap to tree |
|
8 |
-##' @param width total width of heatmap, compare to width of tree |
|
9 |
-##' @param low color of lowest value |
|
10 |
-##' @param high color of highest value |
|
11 |
-##' @param color color of heatmap cell border |
|
12 |
-##' @param colnames logical, add matrix colnames or not |
|
13 |
-##' @param colnames_position one of 'bottom' or 'top' |
|
14 |
-##' @param colnames_angle angle of column names |
|
15 |
-##' @param colnames_level levels of colnames |
|
16 |
-##' @param colnames_offset_x x offset for column names |
|
17 |
-##' @param colnames_offset_y y offset for column names |
|
18 |
-##' @param font.size font size of matrix colnames |
|
19 |
-##' @param family font of matrix colnames |
|
20 |
-##' @param hjust hjust for column names (0: align left, 0.5: align center, 1: align righ) |
|
7 |
+##' @param offset set offset of the heatmap to tree |
|
8 |
+##' @param width total width of heatmap, compare to width of tree, defaults to 1, |
|
9 |
+##' which means they are of the same length |
|
10 |
+##' @param low set color of the lowest value, defaults to "green" |
|
11 |
+##' @param high set color of the highest value, defaults to "red" |
|
12 |
+##' @param color set color of heatmap cell border, defaults to "white" |
|
13 |
+##' @param colnames logical, whether to add matrix colnames, defaults to "TRUE" |
|
14 |
+##' @param colnames_position set the position of the colnames, one of 'bottom' (default) or 'top' |
|
15 |
+##' @param colnames_angle set the angle of colnames |
|
16 |
+##' @param colnames_level set levels of colnames |
|
17 |
+##' @param colnames_offset_x set x offset for colnames |
|
18 |
+##' @param colnames_offset_y set y offset for colnames |
|
19 |
+##' @param font.size set font size of matrix colnames |
|
20 |
+##' @param family font of matrix colnames, can be any supported font |
|
21 |
+##' @param hjust adjust horizonal position of column names (0: align left, 0.5: align center (default), 1: align righ) |
|
21 | 22 |
##' @param legend_title title of fill legend |
22 |
-##' @param custom_column_labels instead of the column names from a matrix, input a custom vector of column labels |
|
23 |
+##' @param custom_column_labels instead of using the colnames from the input matrix/data.frame, |
|
24 |
+##' input a custom vector to be set as column labels |
|
23 | 25 |
##' @return tree view |
24 | 26 |
##' @importFrom ggplot2 geom_tile |
25 | 27 |
##' @importFrom ggplot2 geom_text |
... | ... |
@@ -34,6 +36,10 @@ |
34 | 36 |
##' @importFrom dplyr select |
35 | 37 |
##' @export |
36 | 38 |
##' @author Guangchuang Yu |
39 |
+##' @references |
|
40 |
+##' For demonstration of this function, please refer to chapter 7.3 of |
|
41 |
+##' *Data Integration, Manipulation and Visualization of Phylogenetic Trees* |
|
42 |
+##' <http://yulab-smu.top/treedata-book/index.html> by Guangchuang Yu. |
|
37 | 43 |
gheatmap <- function(p, data, offset=0, width=1, low="green", high="red", color="white", |
38 | 44 |
colnames=TRUE, colnames_position="bottom", colnames_angle=0, colnames_level=NULL, |
39 | 45 |
colnames_offset_x = 0, colnames_offset_y = 0, font.size=4, family="", |
... | ... |
@@ -1,19 +1,29 @@ |
1 |
-##' add subplots to tree |
|
2 |
-##' |
|
1 |
+##' gemo_inset can add subplots to tree by accepting a list of ggplot objects that are ancestral |
|
2 |
+##' stats or data associated with selected nodes in the tree. These ggplot objects can be any |
|
3 |
+##' kind of charts or hybrid of of these charts. |
|
4 |
+##' |
|
5 |
+##' Users can also use |
|
6 |
+##' |
|
3 | 7 |
##' |
4 | 8 |
##' @title geom_inset |
5 | 9 |
##' @rdname inset |
6 | 10 |
##' @param insets a list of ggplot objects, named by node number |
7 |
-##' @param width width of inset, relative to the range of x-axis |
|
8 |
-##' @param height height of inset, relative to the range of y-axis |
|
9 |
-##' @param hjust horizontal adjustment |
|
10 |
-##' @param vjust vertical adjustment |
|
11 |
-##' @param x x position, one of 'node' and 'branch' |
|
12 |
-##' @param reverse_x whether x axis was reversed by scale_x_reverse |
|
13 |
-##' @param reverse_y whether y axis was reversed by scale_y_reverse |
|
11 |
+##' @param width width of the inset, relative to the range of x-axis, defaults to .1 |
|
12 |
+##' @param height height of the inset, relative to the range of y-axis, defaults to .1 |
|
13 |
+##' @param hjust adjust the horizontal position of the charts, charts will go left if hjust > 0 |
|
14 |
+##' @param vjust adjust the vertical position of the charts, charts will go down if vjust > 0 |
|
15 |
+##' @param x the position where users want to place the charts, one of 'node' (default) and 'branch' |
|
16 |
+##' @param reverse_x whether to reverse x axis of the charts by 'ggplot2::scale_x_reverse', defaults to 'FALSE' |
|
17 |
+##' @param reverse_y whether to reverse y axis of the charts by 'ggplot2::scale_y_reverse', defaults to 'FALSE' |
|
14 | 18 |
##' @return inset layer |
15 | 19 |
##' @export |
16 | 20 |
##' @author Guangchuang Yu |
21 |
+##' @references |
|
22 |
+##' For demonstration of this function, please refer to chapter 8.3 of |
|
23 |
+##' *Data Integration, Manipulation and Visualization of Phylogenetic Trees* |
|
24 |
+##' <http://yulab-smu.top/treedata-book/index.html> by Guangchuang Yu. |
|
25 |
+##' |
|
26 |
+ |
|
17 | 27 |
geom_inset <- function(insets, width = .1, height = .1, hjust = 0, vjust = 0, |
18 | 28 |
x = "node", reverse_x = FALSE, reverse_y = FALSE) { |
19 | 29 |
structure(list(insets = insets, width = width, height = height, |
... | ... |
@@ -21,13 +31,13 @@ geom_inset <- function(insets, width = .1, height = .1, hjust = 0, vjust = 0, |
21 | 31 |
reverse_x = reverse_x, reverse_y = reverse_y), class = "tree_inset") |
22 | 32 |
} |
23 | 33 |
|
24 |
-##' add insets in a tree |
|
34 |
+##' add subplots as insets in a tree |
|
25 | 35 |
##' |
26 | 36 |
##' |
27 | 37 |
##' @title inset |
28 | 38 |
##' @rdname inset |
29 |
-##' @param tree_view tree view |
|
30 |
-## @inheritParams geom_inset |
|
39 |
+##' @param tree_view tree view |
|
40 |
+##' @inheritParams geom_inset |
|
31 | 41 |
##' @return tree view with insets |
32 | 42 |
##' @importFrom yulab.utils get_fun_from_pkg |
33 | 43 |
##' @export |
... | ... |
@@ -74,7 +84,7 @@ inset <- function(tree_view, insets, width, height, hjust=0, vjust=0, |
74 | 84 |
##' |
75 | 85 |
##' |
76 | 86 |
##' @title nodebar |
77 |
-##' @param position position of bar, one of 'stack' and 'dodge' |
|
87 |
+##' @param position position of bars, if 'stack' (default) make bars stacked atop one another, 'dodge' make them dodged side-to-side |
|
78 | 88 |
##' @inheritParams nodepie |
79 | 89 |
##' @return list of ggplot objects |
80 | 90 |
##' @export |
... | ... |
@@ -105,10 +115,10 @@ nodebar <- function(data, cols, color, alpha=1, position="stack") { |
105 | 115 |
##' |
106 | 116 |
##' |
107 | 117 |
##' @title nodepie |
108 |
-##' @param data a data.frame of stats with an additional column of node number |
|
109 |
-##' @param cols column of stats |
|
110 |
-##' @param color color of bar |
|
111 |
-##' @param alpha alpha |
|
118 |
+##' @param data a data.frame of stats with an additional column of node number named "node" |
|
119 |
+##' @param cols columns of the data.frame that store the stats |
|
120 |
+##' @param color set color of bars |
|
121 |
+##' @param alpha set transparency of the charts |
|
112 | 122 |
##' @return list of ggplot objects |
113 | 123 |
##' @export |
114 | 124 |
##' @author Guangchuang Yu |
... | ... |
@@ -1,8 +1,8 @@ |
1 |
-##' rotate circular tree |
|
1 |
+##' rotate circular tree in a certain angle |
|
2 | 2 |
##' |
3 | 3 |
##' |
4 | 4 |
##' @title rotate_tree |
5 |
-##' @param treeview tree view |
|
5 |
+##' @param treeview tree view in circular layout |
|
6 | 6 |
##' @param angle the angle of rotation |
7 | 7 |
##' @return updated tree view |
8 | 8 |
##' @export |
... | ... |
@@ -10,8 +10,7 @@ |
10 | 10 |
##' tree <- rtree(15) |
11 | 11 |
##' p <- ggtree(tree) + geom_tiplab() |
12 | 12 |
##' p2 <- open_tree(p, 180) |
13 |