... | ... |
@@ -2,9 +2,9 @@ Package: ggtree |
2 | 2 |
Type: Package |
3 | 3 |
Title: an R package for visualization and annotation of phylogenetic trees with |
4 | 4 |
their covariates and other associated data |
5 |
-Version: 1.11.1 |
|
5 |
+Version: 1.11.2 |
|
6 | 6 |
Authors@R: c( |
7 |
- person("Guangchuang", "Yu", email = "guangchuangyu@gmail.com", role = c("aut", "cre", "cph")), |
|
7 |
+ person("Guangchuang", "Yu", email = "guangchuangyu@gmail.com", role = c("aut", "cre", "cph"), comment = c(ORCID = "0000-0002-6485-8781")), |
|
8 | 8 |
person("Tommy Tsan-Yuk", "Lam", email = "tylam.tommy@gmail.com", role = c("aut", "ths")), |
9 | 9 |
person("Justin", "Silverman", email = "jsilve24@gmail.com", role = "ctb") |
10 | 10 |
) |
... | ... |
@@ -29,8 +29,8 @@ Imports: |
29 | 29 |
Suggests: |
30 | 30 |
Biostrings, |
31 | 31 |
colorspace, |
32 |
- EBImage, |
|
33 | 32 |
emojifont, |
33 |
+ ggimage, |
|
34 | 34 |
knitr, |
35 | 35 |
prettydoc, |
36 | 36 |
rmarkdown, |
... | ... |
@@ -38,7 +38,6 @@ export(as.binary) |
38 | 38 |
export(as.polytomy) |
39 | 39 |
export(collapse) |
40 | 40 |
export(decimal2Date) |
41 |
-export(download.phylopic) |
|
42 | 41 |
export(expand) |
43 | 42 |
export(facet_plot) |
44 | 43 |
export(flip) |
... | ... |
@@ -50,6 +49,7 @@ export(geom_hilight) |
50 | 49 |
export(geom_hilight_encircle) |
51 | 50 |
export(geom_label2) |
52 | 51 |
export(geom_motif) |
52 |
+export(geom_nodelab) |
|
53 | 53 |
export(geom_nodepoint) |
54 | 54 |
export(geom_point2) |
55 | 55 |
export(geom_range) |
... | ... |
@@ -66,7 +66,6 @@ export(geom_tree2) |
66 | 66 |
export(geom_treescale) |
67 | 67 |
export(get.offspring.tip) |
68 | 68 |
export(get.path) |
69 |
-export(get.phylopic) |
|
70 | 69 |
export(get_balance_position) |
71 | 70 |
export(get_clade_position) |
72 | 71 |
export(get_heatmap_column_position) |
... | ... |
@@ -167,9 +166,7 @@ importFrom(ggplot2,xlab) |
167 | 166 |
importFrom(ggplot2,xlim) |
168 | 167 |
importFrom(ggplot2,ylab) |
169 | 168 |
importFrom(ggplot2,ylim) |
170 |
-importFrom(grDevices,col2rgb) |
|
171 | 169 |
importFrom(grDevices,colorRampPalette) |
172 |
-importFrom(grDevices,rgb) |
|
173 | 170 |
importFrom(graphics,identify) |
174 | 171 |
importFrom(grid,convertX) |
175 | 172 |
importFrom(grid,convertY) |
... | ... |
@@ -200,7 +197,6 @@ importFrom(treeio,as.treedata) |
200 | 197 |
importFrom(treeio,get.placements) |
201 | 198 |
importFrom(treeio,groupClade) |
202 | 199 |
importFrom(treeio,groupOTU) |
203 |
-importFrom(utils,download.file) |
|
204 | 200 |
importFrom(utils,modifyList) |
205 | 201 |
importFrom(utils,packageDescription) |
206 | 202 |
importFrom(utils,packageVersion) |
... | ... |
@@ -1,3 +1,9 @@ |
1 |
+CHANGES IN VERSION 1.11.2 |
|
2 |
+------------------------ |
|
3 |
+ o deprecate subview, annotation_image and phylopic <2017-12-04, Mon> |
|
4 |
+ o geom_tiplab now supports geom = "image" or geom = "phylopic" <2017-12-04, Mon> |
|
5 |
+ o A new layer geom_nodelab that equivalent to geom_tiplab but works for internal node <2017-12-04, Mon> |
|
6 |
+ |
|
1 | 7 |
CHANGES IN VERSION 1.11.1 |
2 | 8 |
------------------------ |
3 | 9 |
o bug fixed in geom_tiplab, now `offset` parameter works with `align=TRUE`. <2017-11-20, Mon> |
4 | 10 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,65 @@ |
1 |
+ |
|
2 |
+##' annotation taxa with images |
|
3 |
+##' |
|
4 |
+##' |
|
5 |
+##' @title annotation_image |
|
6 |
+##' @param tree_view tree view |
|
7 |
+##' @param img_info data.frame with first column of taxa name and second column of image names |
|
8 |
+##' @param width width of the image to be plotted in image |
|
9 |
+##' @param align logical |
|
10 |
+##' @param linetype line type if align = TRUE |
|
11 |
+##' @param linesize line size if align = TRUE |
|
12 |
+##' @param offset offset of image from the tree view |
|
13 |
+##' @return tree view |
|
14 |
+##' @export |
|
15 |
+##' @author Guangchuang Yu |
|
16 |
+annotation_image <- function(tree_view, img_info, width=0.1, align=TRUE, linetype="dotted", linesize =1, offset=0) { |
|
17 |
+ stop('the `annotation_image` function was deprecated...\nplease use `geom_tiplab(geom="image")`') |
|
18 |
+} |
|
19 |
+ |
|
20 |
+ |
|
21 |
+##' add phylopic layer |
|
22 |
+##' |
|
23 |
+##' |
|
24 |
+##' @title phylopic |
|
25 |
+##' @param tree_view tree view |
|
26 |
+##' @param phylopic_id phylopic id |
|
27 |
+##' @param size size of phylopic to download |
|
28 |
+##' @param color color |
|
29 |
+##' @param alpha alpha |
|
30 |
+##' @param node selected node |
|
31 |
+##' @param x x position |
|
32 |
+##' @param y y position |
|
33 |
+##' @param width width of phylopic |
|
34 |
+##' @return phylopic layer |
|
35 |
+##' @export |
|
36 |
+##' @importFrom ggplot2 annotation_custom |
|
37 |
+##' @importFrom grid rasterGrob |
|
38 |
+##' @author Guangchuang Yu |
|
39 |
+phylopic <- function(tree_view, phylopic_id, |
|
40 |
+ size=512, color="black", alpha=0.5, |
|
41 |
+ node=NULL, x=NULL, y=NULL, width=.1) { |
|
42 |
+ |
|
43 |
+ stop('the `phylopic` function was deprecated...\nplease use `geom_tiplab(geom="phylopic")` or `geom_nodelab(geom="phylopic")`') |
|
44 |
+} |
|
45 |
+ |
|
46 |
+ |
|
47 |
+##' add subview to mainview for ggplot2 objects |
|
48 |
+##' |
|
49 |
+##' |
|
50 |
+##' @title subview |
|
51 |
+##' @param mainview main view |
|
52 |
+##' @param subview a ggplot or grob object |
|
53 |
+##' @param x x position |
|
54 |
+##' @param y y position |
|
55 |
+##' @param width width of subview, [0,1] |
|
56 |
+##' @param height height of subview, [0,1] |
|
57 |
+##' @return ggplot object |
|
58 |
+##' @importFrom ggplot2 annotation_custom |
|
59 |
+##' @importFrom ggplot2 ggplotGrob |
|
60 |
+##' @importFrom ggplot2 ggplot_build |
|
61 |
+##' @export |
|
62 |
+##' @author Guangchuang Yu |
|
63 |
+subview <- function(mainview, subview, x, y, width=.1, height=.1) { |
|
64 |
+ stop("The subview function was deprecated, please use ggimage::geom_subview() instead.") |
|
65 |
+} |
0 | 66 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,23 @@ |
1 |
+##' add node label layer |
|
2 |
+##' |
|
3 |
+##' |
|
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 |
|
8 |
+##' @param geom one of 'text', 'label', 'image' and 'phylopic' |
|
9 |
+##' @param hjust horizontal alignment, one of 0, 0.5 or 1 |
|
10 |
+##' @param ... additional parameters |
|
11 |
+##' @return geom layer |
|
12 |
+##' @export |
|
13 |
+##' @author guangchuang yu |
|
14 |
+geom_nodelab <- function(mapping = NULL, nudge_x = 0, nudge_y = 0, geom = "text", hjust = 0.5, ...) { |
|
15 |
+ self_mapping <- aes_(subset = ~!isTip) |
|
16 |
+ if (is.null(mapping)) { |
|
17 |
+ mapping <- self_mapping |
|
18 |
+ } else { |
|
19 |
+ mapping <- modifyList(self_mapping, mapping) |
|
20 |
+ } |
|
21 |
+ |
|
22 |
+ geom_tiplab(mapping, offset = nudge_x, nudge_y = nudge_y, geom = geom, hjust = hjust, ...) |
|
23 |
+} |
... | ... |
@@ -8,10 +8,11 @@ |
8 | 8 |
##' @param align align tip lab or not, logical |
9 | 9 |
##' @param linetype linetype for adding line if align = TRUE |
10 | 10 |
##' @param linesize line size of line if align = TRUE |
11 |
-##' @param geom one of 'text' and 'label' |
|
11 |
+##' @param geom one of 'text', 'label', 'image' and 'phylopic' |
|
12 | 12 |
##' @param ... additional parameter |
13 | 13 |
##' @return tip label layer |
14 | 14 |
##' @importFrom ggplot2 geom_text |
15 |
+##' @importFrom utils modifyList |
|
15 | 16 |
##' @export |
16 | 17 |
##' @author Yu Guangchuang |
17 | 18 |
##' @examples |
... | ... |
@@ -19,12 +20,18 @@ |
19 | 20 |
##' tr <- rtree(10) |
20 | 21 |
##' ggtree(tr) + geom_tiplab() |
21 | 22 |
geom_tiplab <- function(mapping=NULL, hjust = 0, align = FALSE, linetype = "dotted", linesize=0.5, geom="text", offset=0, ...) { |
22 |
- geom <- match.arg(geom, c("text", "label")) |
|
23 |
+ geom <- match.arg(geom, c("text", "label", "image", "phylopic")) |
|
23 | 24 |
if (geom == "text") { |
24 |
- text_geom <- geom_text2 |
|
25 |
- } else { |
|
26 |
- text_geom <- geom_label2 |
|
25 |
+ label_geom <- geom_text2 |
|
26 |
+ } else if (geom == "label") { |
|
27 |
+ label_geom <- geom_label2 |
|
28 |
+ } else if (geom == "image") { |
|
29 |
+ label_geom <- get_fun_from_pkg("ggimage", "geom_image") |
|
30 |
+ } else if (geom == "phylopic") { |
|
31 |
+ label_geom <- get_fun_from_pkg("ggimage", "geom_phylopic") |
|
27 | 32 |
} |
33 |
+ |
|
34 |
+ |
|
28 | 35 |
x <- y <- label <- isTip <- node <- NULL |
29 | 36 |
if (align == TRUE) { |
30 | 37 |
self_mapping <- aes(x = max(x, na.rm=TRUE) + diff(range(x, na.rm=TRUE))/200, y = y, label = label, node = node, subset = isTip) |
... | ... |
@@ -54,13 +61,14 @@ geom_tiplab <- function(mapping=NULL, hjust = 0, align = FALSE, linetype = "dot |
54 | 61 |
} |
55 | 62 |
|
56 | 63 |
list( |
57 |
- text_geom(mapping=text_mapping, |
|
58 |
- hjust = hjust, nudge_x = offset, stat = StatTreeData, ...) |
|
59 |
- , |
|
60 | 64 |
if (show_segment) |
61 | 65 |
geom_segment2(mapping = segment_mapping, |
62 | 66 |
linetype = linetype, nudge_x = offset, |
63 | 67 |
size = linesize, stat = StatTreeData, ...) |
68 |
+ , |
|
69 |
+ label_geom(mapping=text_mapping, |
|
70 |
+ hjust = hjust, nudge_x = offset, stat = StatTreeData, ...) |
|
71 |
+ |
|
64 | 72 |
) |
65 | 73 |
} |
66 | 74 |
|
... | ... |
@@ -36,14 +36,13 @@ inset <- function(tree_view, insets, width=0.1, height=0.1, hjust=0, vjust=0, |
36 | 36 |
if (reverse_y) |
37 | 37 |
yy <- -yy |
38 | 38 |
|
39 |
- for (i in seq_along(insets)) { |
|
40 |
- tree_view %<>% subview(insets[[i]], |
|
41 |
- x = xx[i], |
|
42 |
- y = yy[i], |
|
43 |
- width = width, |
|
44 |
- height = height) |
|
45 |
- } |
|
46 |
- return(tree_view) |
|
39 |
+ geom_subview <- get_fun_from_pkg("ggimage", "geom_subview") |
|
40 |
+ |
|
41 |
+ tree_view + geom_subview(subview = insets, |
|
42 |
+ width = width, |
|
43 |
+ height = height, |
|
44 |
+ x = xx, |
|
45 |
+ y = yy) |
|
47 | 46 |
} |
48 | 47 |
|
49 | 48 |
##' generate a list of bar charts for results of ancestral state reconstruction |
50 | 49 |
deleted file mode 100644 |
... | ... |
@@ -1,43 +0,0 @@ |
1 |
-## ##' parsing phylip tree format |
|
2 |
-## ##' |
|
3 |
-## ##' |
|
4 |
-## ##' @title read.phylip |
|
5 |
-## ##' @param file phylip file |
|
6 |
-## ##' @return an instance of 'phylip' |
|
7 |
-## ##' @export |
|
8 |
-## ## @importFrom Biostrings BStringSet |
|
9 |
-## ##' @author Guangchuang Yu |
|
10 |
-## read.phylip <- function(file) { |
|
11 |
-## phylip <- readLines(file) |
|
12 |
-## i <- grep("^\\d+$", phylip) |
|
13 |
-## if (length(i) != 1) { |
|
14 |
-## stop("input file is not phylip tree format...") |
|
15 |
-## } |
|
16 |
-## n <- length(phylip) |
|
17 |
-## ntree <- as.numeric(phylip[i]) |
|
18 |
-## trees <- read.tree(text=phylip[(i+1):n]) |
|
19 |
- |
|
20 |
-## phylipInfo <- strsplit(phylip[1], split="\\s") %>% unlist |
|
21 |
-## nseq <- phylipInfo[1] |
|
22 |
-## seqLen <- phylipInfo[2] |
|
23 |
-## if (nseq != i-2) { |
|
24 |
-## stop("only sequential format is supported...\n-> see http://evolution.genetics.washington.edu/phylip/doc/sequence.html") |
|
25 |
-## } |
|
26 |
-## seqlines <- phylip[2:(i-1)] |
|
27 |
-## seq_with_name <- lapply(seqlines, function(x) unlist(strsplit(x, "\\s+"))) |
|
28 |
-## seqs <- sapply(seq_with_name, function(x) x[2]) |
|
29 |
-## names(seqs) <- sapply(seq_with_name, function(x) x[1]) |
|
30 |
- |
|
31 |
-## if (any(nchar(seqs) != seqLen)) { |
|
32 |
-## stop(paste("sequence length not consistent...\n->", paste0(nchar(seqs), collapse=" "))) |
|
33 |
-## } |
|
34 |
- |
|
35 |
-## new("phylip", |
|
36 |
-## file = filename(file), |
|
37 |
-## phylo = trees, |
|
38 |
-## ntree = ntree, |
|
39 |
-## sequence = seqs |
|
40 |
-## ) |
|
41 |
-## } |
|
42 |
- |
|
43 |
- |
44 | 0 |
deleted file mode 100644 |
... | ... |
@@ -1,173 +0,0 @@ |
1 |
-##' download phylopic and convert to grob object |
|
2 |
-##' |
|
3 |
-##' |
|
4 |
-##' @title get.phylopic |
|
5 |
-##' @param id phylopic id |
|
6 |
-##' @param size size of the phylopic |
|
7 |
-##' @param color color |
|
8 |
-##' @param alpha alpha |
|
9 |
-##' @return grob object |
|
10 |
-##' @importFrom grid rasterGrob |
|
11 |
-##' @export |
|
12 |
-##' @author Guangchuang Yu |
|
13 |
-get.phylopic <- function(id, size=512, color="black", alpha=1) { |
|
14 |
- download.phylopic(id, size, color, alpha) %>% rasterGrob |
|
15 |
-} |
|
16 |
- |
|
17 |
-##' download phylopic |
|
18 |
-##' |
|
19 |
-##' @title download.phylopic |
|
20 |
-##' @param id phyopic id |
|
21 |
-##' @param size size of phylopic |
|
22 |
-##' @param color color |
|
23 |
-##' @param alpha alpha |
|
24 |
-##' @return matrix |
|
25 |
-##' @importFrom grDevices rgb |
|
26 |
-##' @importFrom grDevices col2rgb |
|
27 |
-## @importFrom EBImage readImage |
|
28 |
-## @importFrom EBImage channel |
|
29 |
-##' @export |
|
30 |
-##' @author Guangchuang Yu |
|
31 |
-download.phylopic <- function(id, size=512, color="black", alpha=1) { |
|
32 |
- imgfile <- tempfile(fileext = ".png") |
|
33 |
- download.phylopic_internal(id, size, imgfile) |
|
34 |
- |
|
35 |
- channel <- get_fun_from_pkg("EBImage", "channel") |
|
36 |
- readImage <- get_fun_from_pkg("EBImage", "readImage") |
|
37 |
- |
|
38 |
- img <- readImage(imgfile) |
|
39 |
- |
|
40 |
- color <- col2rgb(color) / 255 |
|
41 |
- |
|
42 |
- img <- channel(img, 'rgb') |
|
43 |
- img[,,1] <- color[1] |
|
44 |
- img[,,2] <- color[2] |
|
45 |
- img[,,3] <- color[3] |
|
46 |
- img[,,4] <- img[,,4]*alpha |
|
47 |
- |
|
48 |
- return(img) |
|
49 |
-} |
|
50 |
- |
|
51 |
-##' @importFrom utils download.file |
|
52 |
-##' @importFrom utils modifyList |
|
53 |
-download.phylopic_internal <- function(id, size=512, outfile=NULL) { |
|
54 |
- size %<>% as.character %>% |
|
55 |
- match.arg(c("64", "128", "256", "512", "1024")) |
|
56 |
- |
|
57 |
- imgurl <- paste0("http://phylopic.org/assets/images/submissions/", id, ".", size, ".png") |
|
58 |
- if (is.null(outfile)) { |
|
59 |
- outfile <- sub(".*/", "", imgurl) |
|
60 |
- } |
|
61 |
- ## mode = "wb" for Windows platform |
|
62 |
- download.file(imgurl, outfile, mode="wb", quiet = TRUE) |
|
63 |
-} |
|
64 |
- |
|
65 |
- |
|
66 |
-##' add phylopic layer |
|
67 |
-##' |
|
68 |
-##' |
|
69 |
-##' @title phylopic |
|
70 |
-##' @param tree_view tree view |
|
71 |
-##' @param phylopic_id phylopic id |
|
72 |
-##' @param size size of phylopic to download |
|
73 |
-##' @param color color |
|
74 |
-##' @param alpha alpha |
|
75 |
-##' @param node selected node |
|
76 |
-##' @param x x position |
|
77 |
-##' @param y y position |
|
78 |
-##' @param width width of phylopic |
|
79 |
-##' @return phylopic layer |
|
80 |
-##' @export |
|
81 |
-##' @importFrom ggplot2 annotation_custom |
|
82 |
-##' @importFrom grid rasterGrob |
|
83 |
-##' @author Guangchuang Yu |
|
84 |
-phylopic <- function(tree_view, phylopic_id, |
|
85 |
- size=512, color="black", alpha=0.5, |
|
86 |
- node=NULL, x=NULL, y=NULL, width=.1) { |
|
87 |
- |
|
88 |
- message("The phylopic function will be defunct in next release, please use ggimage::geom_phylopic() instead.") |
|
89 |
- |
|
90 |
- width <- diff(range(tree_view$data$x)) * width |
|
91 |
- img <- download.phylopic(phylopic_id, size, color, alpha) |
|
92 |
- if ( is.null(node) ) { |
|
93 |
- xmin <- ymin <- -Inf |
|
94 |
- xmax <- ymax <- Inf |
|
95 |
- } else { |
|
96 |
- if (is.null(x) || is.null(y)) { |
|
97 |
- if (is.null(node)) { |
|
98 |
- stop("node or x and y should not be NULL...") |
|
99 |
- } |
|
100 |
- df <- tree_view$data |
|
101 |
- x <- df[match(node, df$node), "x"] |
|
102 |
- y <- df[match(node, df$node), "y"] |
|
103 |
- } |
|
104 |
- AR <- getAR(img) |
|
105 |
- xmin <- x - width/2 |
|
106 |
- xmax <- x + width/2 |
|
107 |
- ymin <- y - AR * width/2 |
|
108 |
- ymax <- y + AR * width/2 |
|
109 |
- } |
|
110 |
- |
|
111 |
- tree_view + annotation_custom(xmin=xmin, ymin=ymin, |
|
112 |
- xmax=xmax, ymax=ymax, |
|
113 |
- rasterGrob(img)) |
|
114 |
-} |
|
115 |
- |
|
116 |
-getAR <- function(img) { |
|
117 |
- dims <- dim(img)[1:2] |
|
118 |
- dims[1]/dims[2] |
|
119 |
-} |
|
120 |
- |
|
121 |
- |
|
122 |
-##' annotation taxa with images |
|
123 |
-##' |
|
124 |
-##' |
|
125 |
-##' @title annotation_image |
|
126 |
-##' @param tree_view tree view |
|
127 |
-##' @param img_info data.frame with first column of taxa name and second column of image names |
|
128 |
-##' @param width width of the image to be plotted in image |
|
129 |
-##' @param align logical |
|
130 |
-##' @param linetype line type if align = TRUE |
|
131 |
-##' @param linesize line size if align = TRUE |
|
132 |
-##' @param offset offset of image from the tree view |
|
133 |
-##' @return tree view |
|
134 |
-##' @export |
|
135 |
-##' @author Guangchuang Yu |
|
136 |
-annotation_image <- function(tree_view, img_info, width=0.1, align=TRUE, linetype="dotted", linesize =1, offset=0) { |
|
137 |
- df <- tree_view$data |
|
138 |
- idx <- match(img_info[,1], df$label) |
|
139 |
- x <- df[idx, "x"] |
|
140 |
- y <- df[idx, "y"] |
|
141 |
- |
|
142 |
- readImage <- get_fun_from_pkg("EBImage", "readImage") |
|
143 |
- images <- lapply(img_info[,2], readImage) |
|
144 |
- |
|
145 |
- ARs <- sapply(images, getAR) |
|
146 |
- |
|
147 |
- width <- width * diff(range(df$x)) |
|
148 |
- if (align) { |
|
149 |
- xmin <- max(df$x) + offset |
|
150 |
- xmin <- rep(xmin, length(x)) |
|
151 |
- } else { |
|
152 |
- xmin <- x - width/2 + offset |
|
153 |
- } |
|
154 |
- xmax <- xmin + width |
|
155 |
- |
|
156 |
- ymin <- y - ARs * width/2 |
|
157 |
- ymax <- y + ARs * width/2 |
|
158 |
- image_layers <- lapply(1:length(xmin), function(i) { |
|
159 |
- annotation_custom(xmin=xmin[i], ymin=ymin[i], |
|
160 |
- xmax=xmax[i], ymax=ymax[i], |
|
161 |
- rasterGrob(images[[i]])) |
|
162 |
- }) |
|
163 |
- |
|
164 |
- tree_view <- tree_view + image_layers |
|
165 |
- |
|
166 |
- if (align && (!is.null(linetype) && !is.na(linetype))) { |
|
167 |
- tree_view <- tree_view + geom_segment(data=df[idx,], |
|
168 |
- x=xmin, xend = x*1.01, |
|
169 |
- y = y, yend = y, |
|
170 |
- linetype=linetype, size=linesize) |
|
171 |
- } |
|
172 |
- tree_view |
|
173 |
-} |
174 | 0 |
deleted file mode 100644 |
... | ... |
@@ -1,97 +0,0 @@ |
1 |
-##' add subview to mainview for ggplot2 objects |
|
2 |
-##' |
|
3 |
-##' |
|
4 |
-##' @title subview |
|
5 |
-##' @param mainview main view |
|
6 |
-##' @param subview a ggplot or grob object |
|
7 |
-##' @param x x position |
|
8 |
-##' @param y y position |
|
9 |
-##' @param width width of subview, [0,1] |
|
10 |
-##' @param height height of subview, [0,1] |
|
11 |
-##' @return ggplot object |
|
12 |
-##' @importFrom ggplot2 annotation_custom |
|
13 |
-##' @importFrom ggplot2 ggplotGrob |
|
14 |
-##' @importFrom ggplot2 ggplot_build |
|
15 |
-##' @export |
|
16 |
-##' @author Guangchuang Yu |
|
17 |
-subview <- function(mainview, subview, x, y, width=.1, height=.1) { |
|
18 |
- message("The subview function will be defunct in next release, please use ggimage::geom_subview() instead.") |
|
19 |
- |
|
20 |
- mapping <- mainview$mapping %>% as.character |
|
21 |
- aes_x <- mapping["x"] |
|
22 |
- aes_y <- mapping["y"] |
|
23 |
- |
|
24 |
- if (is.na(aes_x) || is.na(aes_y)) { |
|
25 |
- obj <- ggplot_build(mainview) |
|
26 |
- xrng <- obj$layout$panel_ranges[[1]]$x.range |
|
27 |
- yrng <- obj$layout$panel_ranges[[1]]$y.range |
|
28 |
- } else { |
|
29 |
- xrng <- mainview$data[, aes_x] %>% range |
|
30 |
- yrng <- mainview$data[, aes_y] %>% range |
|
31 |
- } |
|
32 |
- |
|
33 |
- for (i in seq_along(mainview$layers)) { |
|
34 |
- layer <- mainview$layers[[i]] |
|
35 |
- dd <- layer$data |
|
36 |
- if (is(dd, "data.frame")) { |
|
37 |
- mapping <- as.character(layer$mapping) |
|
38 |
- mn <- names(mapping) |
|
39 |
- if ('x' %in% mn) { |
|
40 |
- aes_x <- mapping["x"] |
|
41 |
- xrng <- c(xrng, layer$data[, aes_x]) |
|
42 |
- } |
|
43 |
- if ('xmin' %in% mn) { |
|
44 |
- aes_x <- mapping["xmin"] |
|
45 |
- xrng <- c(xrng, layer$data[, aes_x]) |
|
46 |
- } |
|
47 |
- if ('xmax' %in% mn) { |
|
48 |
- aes_x <- mapping["xmax"] |
|
49 |
- xrng <- c(xrng, layer$data[, aes_x]) |
|
50 |
- } |
|
51 |
- if ('y' %in% mn) { |
|
52 |
- aes_y <- mapping["y"] |
|
53 |
- yrng <- c(yrng, layer$data[, aes_y]) |
|
54 |
- } |
|
55 |
- if ('ymin' %in% mn) { |
|
56 |
- aes_y <- mapping["ymin"] |
|
57 |
- yrng <- c(yrng, layer$data[, aes_y]) |
|
58 |
- } |
|
59 |
- if ('ymax' %in% mn) { |
|
60 |
- aes_y <- mapping["ymax"] |
|
61 |
- yrng <- c(yrng, layer$data[, aes_y]) |
|
62 |
- } |
|
63 |
- xrng <- range(xrng) |
|
64 |
- yrng <- range(yrng) |
|
65 |
- } |
|
66 |
- } |
|
67 |
- |
|
68 |
- xrng <- diff(xrng) |
|
69 |
- yrng <- diff(yrng) |
|
70 |
- |
|
71 |
- if (!any(class(subview) %in% c("ggplot", "trellis", "grob", "character"))) { |
|
72 |
- stop("subview should be a ggplot or grob object, or an image file...") |
|
73 |
- } |
|
74 |
- |
|
75 |
- if (is(subview, "ggplot")) { |
|
76 |
- sv <- ggplotGrob(subview) |
|
77 |
- } else if (is(subview, "trellis")) { |
|
78 |
- sv <- grid::grid.grabExpr(print(subview)) |
|
79 |
- } else if (is(subview, "grob")) { |
|
80 |
- sv <- subview |
|
81 |
- } else if (file.exists(subview)) { |
|
82 |
- readImage <- get_fun_from_pkg("EBImage", "readImage") |
|
83 |
- sv <- rasterGrob(readImage(subview)) |
|
84 |
- } else { |
|
85 |
- stop("subview should be a ggplot or grob object, or an image file...") |
|
86 |
- } |
|
87 |
- |
|
88 |
- width <- width/2 |
|
89 |
- height <- height/2 |
|
90 |
- |
|
91 |
- mainview + annotation_custom( |
|
92 |
- sv, |
|
93 |
- xmin = x - width*xrng, |
|
94 |
- xmax = x + width*xrng, |
|
95 |
- ymin = y - height*yrng, |
|
96 |
- ymax = y + height*yrng) |
|
97 |
-} |
... | ... |
@@ -1,6 +1,6 @@ |
1 | 1 |
<!-- README.md is generated from README.Rmd. Please edit that file --> |
2 |
-ggtree: an R package for visualization and annotation of phylogenetic trees with their covariates and other associated data |
|
3 |
-=========================================================================================================================== |
|
2 |
+ |
|
3 |
+# ggtree: an R package for visualization and annotation of phylogenetic trees with their covariates and other associated data |
|
4 | 4 |
|
5 | 5 |
<img src="https://raw.githubusercontent.com/Bioconductor/BiocStickers/master/ggtree/ggtree.png" height="200" align="right" /> |
6 | 6 |
|
... | ... |
@@ -36,33 +36,35 @@ Collective](https://opencollective.com/ggtree/sponsors/badge.svg)](#sponsors) |
36 | 36 |
The `ggtree` package extending the `ggplot2` package. It based on |
37 | 37 |
grammar of graphics and takes all the good parts of `ggplot2`. `ggtree` |
38 | 38 |
is designed for not only viewing phylogenetic tree but also displaying |
39 |
-annotation data on the tree. |
|
39 |
+annotation data on the |
|
40 |
+tree. |
|
40 | 41 |
|
41 | 42 |
[](https://twitter.com/intent/tweet?hashtags=ggtree&url=http://onlinelibrary.wiley.com/doi/10.1111/2041-210X.12628/abstract&screen_name=guangchuangyu) |
42 | 43 |
|
43 | 44 |
For details, please visit our project website, |
44 | 45 |
<https://guangchuangyu.github.io/ggtree>. |
45 | 46 |
|
46 |
-- [Documentation](https://guangchuangyu.github.io/ggtree/documentation/) |
|
47 |
-- [FAQ](https://guangchuangyu.github.io/ggtree/faq/) |
|
48 |
-- [Featured |
|
47 |
+ - [Documentation](https://guangchuangyu.github.io/ggtree/documentation/) |
|
48 |
+ - [FAQ](https://guangchuangyu.github.io/ggtree/faq/) |
|
49 |
+ - [Featured |
|
49 | 50 |
Articles](https://guangchuangyu.github.io/ggtree/featuredArticles/) |
50 |
-- [Feedback](https://guangchuangyu.github.io/ggtree/#feedback) |
|
51 |
+ - [Feedback](https://guangchuangyu.github.io/ggtree/#feedback) |
|
51 | 52 |
|
53 |
+----- |
|
52 | 54 |
|
53 | 55 |
Please cite the following article when using `ggtree`: |
54 | 56 |
|
55 | 57 |
**G Yu**, DK Smith, H Zhu, Y Guan, TTY Lam<sup>\*</sup>. ggtree: an R |
56 | 58 |
package for visualization and annotation of phylogenetic trees with |
57 | 59 |
their covariates and other associated data. ***Methods in Ecology and |
58 |
-Evolution***. 2017, 8(1):28-36. |
|
60 |
+Evolution***. 2017, |
|
61 |
+8(1):28-36. |
|
59 | 62 |
|
60 | 63 |
[](http://dx.doi.org/10.1111/2041-210X.12628) |
61 | 64 |
[](https://www.altmetric.com/details/10533079) |
62 | 65 |
[](https://scholar.google.com.hk/scholar?oi=bibs&hl=en&cites=7268358477862164627) |
63 | 66 |
|
67 |
+----- |
|
64 | 68 |
|
65 | 69 |
### Citation |
66 | 70 |
|
... | ... |
@@ -76,23 +78,20 @@ Evolution***. 2017, 8(1):28-36. |
76 | 78 |
|
77 | 79 |
<img src="docs/images/dlstats.png" width="890"/> |
78 | 80 |
|
79 |
-Contributors |
|
81 |
+## Contributors |
|
80 | 82 |
|
81 | 83 |
This project exists thanks to all the people who contribute. |
82 | 84 |
[\[Contribute\]](CONTRIBUTING.md). |
83 | 85 |
<a href="https://github.com/GuangchuangYu/ggtree/graphs/contributors"><img src="https://opencollective.com/ggtree/contributors.svg?width=890" /></a> |
84 | 86 |
|
85 |
-Backers |
|
87 |
+## Backers |
|
86 | 88 |
|
87 |
-Thank you to all our backers! 🙏 \[[Become a |
|
89 |
+Thank you to all our backers\! 🙏 \[[Become a |
|
88 | 90 |
backer](https://opencollective.com/ggtree#backer)\] |
89 | 91 |
|
90 | 92 |
<a href="https://opencollective.com/ggtree#backers" target="_blank"><img src="https://opencollective.com/ggtree/backers.svg?width=890"></a> |
91 | 93 |
|
92 |
-Sponsors |
|
94 |
+## Sponsors |
|
93 | 95 |
|
94 | 96 |
Support this project by becoming a sponsor. Your logo will show up here |
95 | 97 |
with a link to your website. \[[Become a |
6 | 6 |
deleted file mode 100644 |
... | ... |
@@ -1,26 +0,0 @@ |
1 |
-% Generated by roxygen2: do not edit by hand |
|
2 |
-% Please edit documentation in R/phylopic.R |
|
3 |
-\name{download.phylopic} |
|
4 |
-\alias{download.phylopic} |
|
5 |
-\title{download.phylopic} |
|
6 |
-\usage{ |
|
7 |
-download.phylopic(id, size = 512, color = "black", alpha = 1) |
|
8 |
-} |
|
9 |
-\arguments{ |
|
10 |
-\item{id}{phyopic id} |
|
11 |
- |
|
12 |
-\item{size}{size of phylopic} |
|
13 |
- |
|
14 |
-\item{color}{color} |
|
15 |
- |
|
16 |
-\item{alpha}{alpha} |
|
17 |
-} |
|
18 |
-\value{ |
|
19 |
-matrix |
|
20 |
-} |
|
21 |
-\description{ |
|
22 |
-download phylopic |
|
23 |
-} |
|
24 |
-\author{ |
|
25 |
-Guangchuang Yu |
|
26 |
-} |
27 | 0 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,31 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/geom_nodelab.R |
|
3 |
+\name{geom_nodelab} |
|
4 |
+\alias{geom_nodelab} |
|
5 |
+\title{geom_nodelab} |
|
6 |
+\usage{ |
|
7 |
+geom_nodelab(mapping = NULL, nudge_x = 0, nudge_y = 0, geom = "text", |
|
8 |
+ hjust = 0.5, ...) |
|
9 |
+} |
|
10 |
+\arguments{ |
|
11 |
+\item{mapping}{aes mapping} |
|
12 |
+ |
|
13 |
+\item{nudge_x}{horizontal adjustment to nudge label} |
|
14 |
+ |
|
15 |
+\item{nudge_y}{vertical adjustment to nudge label} |
|
16 |
+ |
|
17 |
+\item{geom}{one of 'text', 'label', 'image' and 'phylopic'} |
|
18 |
+ |
|
19 |
+\item{hjust}{horizontal alignment, one of 0, 0.5 or 1} |
|
20 |
+ |
|
21 |
+\item{...}{additional parameters} |
|
22 |
+} |
|
23 |
+\value{ |
|
24 |
+geom layer |
|
25 |
+} |
|
26 |
+\description{ |
|
27 |
+add node label layer |
|
28 |
+} |
|
29 |
+\author{ |
|
30 |
+guangchuang yu |
|
31 |
+} |
... | ... |
@@ -18,7 +18,7 @@ geom_tiplab(mapping = NULL, hjust = 0, align = FALSE, |
18 | 18 |
|
19 | 19 |
\item{linesize}{line size of line if align = TRUE} |
20 | 20 |
|
21 |
-\item{geom}{one of 'text' and 'label'} |
|
21 |
+\item{geom}{one of 'text', 'label', 'image' and 'phylopic'} |
|
22 | 22 |
|
23 | 23 |
\item{offset}{tiplab offset} |
24 | 24 |
|
25 | 25 |
deleted file mode 100644 |
... | ... |
@@ -1,26 +0,0 @@ |
1 |
-% Generated by roxygen2: do not edit by hand |
|
2 |
-% Please edit documentation in R/phylopic.R |
|
3 |
-\name{get.phylopic} |
|
4 |
-\alias{get.phylopic} |
|
5 |
-\title{get.phylopic} |
|
6 |
-\usage{ |
|
7 |
-get.phylopic(id, size = 512, color = "black", alpha = 1) |
|
8 |
-} |
|
9 |
-\arguments{ |
|
10 |
-\item{id}{phylopic id} |
|
11 |
- |
|
12 |
-\item{size}{size of the phylopic} |
|
13 |
- |
|
14 |
-\item{color}{color} |
|
15 |
- |
|
16 |
-\item{alpha}{alpha} |
|
17 |
-} |
|
18 |
-\value{ |
|
19 |
-grob object |
|
20 |
-} |
|
21 |
-\description{ |
|
22 |
-download phylopic and convert to grob object |
|
23 |
-} |
|
24 |
-\author{ |
|
25 |
-Guangchuang Yu |
|
26 |
-} |
... | ... |
@@ -175,18 +175,6 @@ bx2 <- lapply(bx, function(g) g+coord_flip()) |
175 | 175 |
inset(p2, bx2, width=.4, height=.06, vjust=.04, hjust=p2$data$x[1:15]-4) + xlim(NA, 4.5) |
176 | 176 |
``` |
177 | 177 |
|
178 |
-## Annotate with image files |
|
179 |
- |
|
180 |
-```{r eval=FALSE} |
|
181 |
-imgfile <- tempfile(, fileext=".png") |
|
182 |
-download.file("https://avatars1.githubusercontent.com/u/626539?v=3&u=e731426406dd3f45a73d96dd604bc45ae2e7c36f&s=140", destfile=imgfile, mode='wb') |
|
183 |
-img <- list(imgfile, imgfile) |
|
184 |
-names(img) <- c("18", "22") |
|
185 |
-inset(p, img) |
|
186 |
-``` |
|
187 |
- |
|
188 |
- |
|
189 |
- |
|
190 | 178 |
# Plot tree with associated data |
191 | 179 |
|
192 | 180 |
For associating phylogenetic tree with different type of plot produced by user's data, `ggtree` provides `facet_plot` function which accepts an input `data.frame` and a `geom` function to draw the input data. The data will be displayed in an additional panel of the plot. |
... | ... |
@@ -203,22 +191,6 @@ d2 <- data.frame(id=tr$tip.label, value = abs(rnorm(30, mean=100, sd=50))) |
203 | 191 |
facet_plot(p2, panel='bar', data=d2, geom=geom_segment, aes(x=0, xend=value, y=y, yend=y), size=3, color='steelblue') + theme_tree2() |
204 | 192 |
``` |
205 | 193 |
|
206 |
-# Tree annotation with Phylopic |
|
207 |
- |
|
208 |
- |
|
209 |
-[PhyloPic](http://phylopic.org/) is a database that stores reusable silhouette images of organisms. `ggtree` supports downloading images from [PhyloPic](http://phylopic.org/) and annotating phylogenetic tree with the downloaded images. |
|
210 |
- |
|
211 |
-```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE, eval=FALSE} |
|
212 |
-pp <- ggtree(tree) %>% phylopic("79ad5f09-cf21-4c89-8e7d-0c82a00ce728", color="steelblue", alpha = .3) |
|
213 |
-print(pp) |
|
214 |
-``` |
|
215 |
- |
|
216 |
- |
|
217 |
-```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE, eval=FALSE} |
|
218 |
-pp %>% phylopic("67382184-5135-4faa-8e98-eadff02c3e8a", color="#86B875", alpha=.8, node=4) %>% |
|
219 |
- phylopic("d3563b54-780f-4711-a49a-7ea051e9dacc", color="darkcyan", alpha=.8, node=17, width=.2) |
|
220 |
-``` |
|
221 |
- |
|
222 | 194 |
|
223 | 195 |
|
224 | 196 |
|
... | ... |
@@ -53,15 +53,16 @@ ggtree(beast) + geom_point2(aes(subset=!is.na(posterior) & posterior > 0.75), co |
53 | 53 |
To support viewing multiple plots, ggtree provides `multiplot` function that similar to `gridExtra::grid.arrange` with extra feature of labeling the plots. |
54 | 54 |
|
55 | 55 |
|
56 |
-```{r fig.width=8, fig.height=4, warning=FALSE} |
|
56 |
+``` {r fig.width=8, fig.height=4, warning=FALSE} |
|
57 | 57 |
multiplot(ggtree(rtree(30)), ggtree(rtree(40)), ncol=2, labels=c('A', 'B')) |
58 | 58 |
``` |
59 | 59 |
|
60 |
+<!-- |
|
60 | 61 |
# subplots in ggplot object |
61 | 62 |
|
62 | 63 |
`ggtree` implemented a function, `subview`, that can add subplots on a ggplot2 object. |
63 | 64 |
|
64 |
-```{r fig.width=8, fig.height=8, warning=F} |
|
65 |
+#``` {r fig.width=8, fig.height=8, warning=F} |
|
65 | 66 |
set.seed(2016-01-04) |
66 | 67 |
tr <- rtree(30) |
67 | 68 |
tr <- groupClade(tr, node=45) |
... | ... |
@@ -69,13 +70,13 @@ p <- ggtree(tr, aes(color=group)) + geom_tippoint() |
69 | 70 |
p1 <- p + geom_hilight(node=45) |
70 | 71 |
p2 <- viewClade(p, node=45) + geom_tiplab() |
71 | 72 |
subview(p2, p1+theme_transparent(), x=2.3, y=28.5) |
72 |
-``` |
|
73 |
+#``` |
|
73 | 74 |
|
74 | 75 |
This is the backend of the [inset](advanceTreeAnnotation.html) function. |
75 | 76 |
|
76 | 77 |
This `subview` function works with any `ggplot` objects and it had successful applied to [plot pie graphs on map](http://stackoverflow.com/questions/10368180/plotting-pie-graphs-on-map-in-ggplot/32380396#32380396). |
77 | 78 |
|
78 |
-```{r eval=FALSE} |
|
79 |
+#``` {r eval=FALSE} |
|
79 | 80 |
library(ggtree) |
80 | 81 |
dd <- data.frame(x=LETTERS[1:3], y=1:3) |
81 | 82 |
pie <- ggplot(dd, aes(x=1, y, fill=x)) + geom_bar(stat="identity", width=1) + coord_polar(theta="y") + theme_inset() |
... | ... |
@@ -88,7 +89,8 @@ for (i in seq_along(x)) { |
88 | 89 |
p <- subview(p, pie, x[i], y[i], width[i], height[i]) |
89 | 90 |
print(p) |
90 | 91 |
} |
91 |
-``` |
|
92 |
+#``` |
|
92 | 93 |
 |
93 | 94 |
|
94 | 95 |
|
96 |
+--> |