... | ... |
@@ -43,4 +43,4 @@ BugReports: https://github.com/GuangchuangYu/ggtree/issues |
43 | 43 |
Packaged: 2014-12-03 08:16:14 UTC; root |
44 | 44 |
biocViews: Alignment, Annotation, Clustering, DataImport, |
45 | 45 |
MultipleSequenceAlignment, ReproducibleResearch, Software, Visualization |
46 |
-RoxygenNote: 5.0.1 |
|
46 |
+RoxygenNote: 6.0.1 |
... | ... |
@@ -1,5 +1,7 @@ |
1 | 1 |
CHANGES IN VERSION 1.9.2 |
2 | 2 |
------------------------ |
3 |
+ o extend parameter in geom_cladebar <2017-07-26, Wed> |
|
4 |
+ + https://github.com/GuangchuangYu/ggtree/issues/142#issuecomment-317817995 |
|
3 | 5 |
o scaleClade works after calling viewClade <2017-07-20, Thu> |
4 | 6 |
+ https://groups.google.com/forum/?utm_medium=email&utm_source=footer#!topic/bioc-ggtree/QVSryszPaFY |
5 | 7 |
o gheatmap support handling collapsed tree <2017-06-29, Thu> |
... | ... |
@@ -6,6 +6,7 @@ |
6 | 6 |
##' @param label clade label |
7 | 7 |
##' @param offset offset of bar and text from the clade |
8 | 8 |
##' @param offset.text offset of text from bar |
9 |
+##' @param extend extend bar height |
|
9 | 10 |
##' @param align logical |
10 | 11 |
##' @param barsize size of bar |
11 | 12 |
##' @param fontsize size of text |
... | ... |
@@ -20,11 +21,21 @@ |
20 | 21 |
##' @return ggplot layers |
21 | 22 |
##' @export |
22 | 23 |
##' @author Guangchuang Yu |
23 |
-geom_cladelabel <- function(node, label, offset=0, offset.text=0, |
|
24 |
- align=FALSE, barsize=0.5, fontsize=3.88, |
|
25 |
- angle=0, geom="text", hjust = 0, |
|
26 |
- color = NULL, fill=NA, |
|
27 |
- family="sans", parse=FALSE, ...) { |
|
24 |
+geom_cladelabel <- function(node, label, |
|
25 |
+ offset = 0, |
|
26 |
+ offset.text = 0, |
|
27 |
+ extend = 0, |
|
28 |
+ align = FALSE, |
|
29 |
+ barsize = 0.5, |
|
30 |
+ fontsize = 3.88, |
|
31 |
+ angle = 0, |
|
32 |
+ geom = "text", |
|
33 |
+ hjust = 0, |
|
34 |
+ color = NULL, |
|
35 |
+ fill = NA, |
|
36 |
+ family = "sans", |
|
37 |
+ parse = FALSE, |
|
38 |
+ ...) { |
|
28 | 39 |
mapping <- NULL |
29 | 40 |
data <- NULL |
30 | 41 |
position <- "identity" |
... | ... |
@@ -73,7 +84,7 @@ geom_cladelabel <- function(node, label, offset=0, offset.text=0, |
73 | 84 |
} |
74 | 85 |
|
75 | 86 |
layer_bar <- stat_cladeBar(node=node, offset=offset, align=align, |
76 |
- size=barsize, |
|
87 |
+ size=barsize, extend = extend, |
|
77 | 88 |
mapping=mapping, data=data, |
78 | 89 |
position=position, show.legend = show.legend, |
79 | 90 |
inherit.aes = inherit.aes, na.rm=na.rm, ...) |
... | ... |
@@ -95,11 +106,18 @@ geom_cladelabel <- function(node, label, offset=0, offset.text=0, |
95 | 106 |
parse = parse, ...) |
96 | 107 |
} |
97 | 108 |
|
98 |
- layer_bar <- stat_cladeBar(node=node, offset=offset, align=align, |
|
99 |
- size=barsize, color = barcolor, |
|
100 |
- mapping=mapping, data=data, |
|
101 |
- position=position, show.legend = show.legend, |
|
102 |
- inherit.aes = inherit.aes, na.rm=na.rm, ...) |
|
109 |
+ layer_bar <- stat_cladeBar(node = node, |
|
110 |
+ offset = offset, |
|
111 |
+ align = align, |
|
112 |
+ size = barsize, |
|
113 |
+ color = barcolor, |
|
114 |
+ extend = extend, |
|
115 |
+ mapping = mapping, |
|
116 |
+ data = data, |
|
117 |
+ position = position, |
|
118 |
+ show.legend = show.legend, |
|
119 |
+ inherit.aes = inherit.aes, |
|
120 |
+ na.rm = na.rm, ...) |
|
103 | 121 |
|
104 | 122 |
} |
105 | 123 |
|
... | ... |
@@ -110,11 +128,11 @@ geom_cladelabel <- function(node, label, offset=0, offset.text=0, |
110 | 128 |
} |
111 | 129 |
|
112 | 130 |
|
113 |
-stat_cladeText <- function(mapping=NULL, data=NULL, |
|
114 |
- geom="text", position="identity", |
|
131 |
+stat_cladeText <- function(mapping = NULL, data = NULL, |
|
132 |
+ geom = "text", position = "identity", |
|
115 | 133 |
node, label, offset, align, ..., angle, |
116 |
- show.legend=NA, inherit.aes=FALSE, |
|
117 |
- na.rm=FALSE, parse=FALSE) { |
|
134 |
+ show.legend = NA, inherit.aes = FALSE, |
|
135 |
+ na.rm = FALSE, parse = FALSE) { |
|
118 | 136 |
default_aes <- aes_(x=~x, y=~y, node=~node, parent=~parent, angle=~angle) |
119 | 137 |
if (is.null(mapping)) { |
120 | 138 |
mapping <- default_aes |
... | ... |
@@ -122,14 +140,14 @@ stat_cladeText <- function(mapping=NULL, data=NULL, |
122 | 140 |
mapping <- modifyList(mapping, default_aes) |
123 | 141 |
} |
124 | 142 |
|
125 |
- layer(stat=StatCladeText, |
|
126 |
- data=data, |
|
127 |
- mapping=mapping, |
|
128 |
- geom=geom, |
|
129 |
- position=position, |
|
143 |
+ layer(stat = StatCladeText, |
|
144 |
+ data = data, |
|
145 |
+ mapping = mapping, |
|
146 |
+ geom = geom, |
|
147 |
+ position = position, |
|
130 | 148 |
show.legend = show.legend, |
131 | 149 |
inherit.aes = inherit.aes, |
132 |
- params=list(node=node, |
|
150 |
+ params=list(node = node, |
|
133 | 151 |
label = label, |
134 | 152 |
offset = offset, |
135 | 153 |
align = align, |
... | ... |
@@ -144,7 +162,7 @@ stat_cladeText <- function(mapping=NULL, data=NULL, |
144 | 162 |
|
145 | 163 |
stat_cladeBar <- function(mapping=NULL, data=NULL, |
146 | 164 |
geom="segment", position="identity", |
147 |
- node, offset, align, ..., |
|
165 |
+ node, offset, align, extend, ..., |
|
148 | 166 |
show.legend=NA, inherit.aes=FALSE, na.rm=FALSE) { |
149 | 167 |
default_aes <- aes_(x=~x, y=~y, node=~node, parent=~parent, xend=~x, yend=~y) |
150 | 168 |
if (is.null(mapping)) { |
... | ... |
@@ -153,17 +171,18 @@ stat_cladeBar <- function(mapping=NULL, data=NULL, |
153 | 171 |
mapping <- modifyList(mapping, default_aes) |
154 | 172 |
} |
155 | 173 |
|
156 |
- layer(stat=StatCladeBar, |
|
157 |
- data=data, |
|
158 |
- mapping=mapping, |
|
159 |
- geom=geom, |
|
160 |
- position=position, |
|
174 |
+ layer(stat = StatCladeBar, |
|
175 |
+ data = data, |
|
176 |
+ mapping = mapping, |
|
177 |
+ geom = geom, |
|
178 |
+ position = position, |
|
161 | 179 |
show.legend = show.legend, |
162 | 180 |
inherit.aes = inherit.aes, |
163 |
- params=list(node=node, |
|
164 |
- offset=offset, |
|
165 |
- align=align, |
|
166 |
- na.rm=na.rm, |
|
181 |
+ params = list(node = node, |
|
182 |
+ offset = offset, |
|
183 |
+ extend = extend, |
|
184 |
+ align = align, |
|
185 |
+ na.rm = na.rm, |
|
167 | 186 |
...), |
168 | 187 |
check.aes = FALSE |
169 | 188 |
) |
... | ... |
@@ -182,15 +201,15 @@ StatCladeText <- ggproto("StatCladeText", Stat, |
182 | 201 |
|
183 | 202 |
|
184 | 203 |
StatCladeBar <- ggproto("StatCladBar", Stat, |
185 |
- compute_group = function(self, data, scales, params, node, offset, align) { |
|
186 |
- get_cladelabel_position(data, node, offset, align, adjustRatio=1.02, angle=0) |
|
204 |
+ compute_group = function(self, data, scales, params, node, offset, align, extend) { |
|
205 |
+ get_cladelabel_position(data, node, offset, align, adjustRatio=1.02, angle=0, extend=extend) |
|
187 | 206 |
}, |
188 | 207 |
required_aes = c("x", "y", "xend", "yend") |
189 | 208 |
) |
190 | 209 |
|
191 | 210 |
|
192 |
-get_cladelabel_position <- function(data, node, offset, align, adjustRatio, angle="auto") { |
|
193 |
- df <- get_cladelabel_position_(data, node, angle) |
|
211 |
+get_cladelabel_position <- function(data, node, offset, align, adjustRatio, angle="auto", extend=0) { |
|
212 |
+ df <- get_cladelabel_position_(data, node, angle, extend) |
|
194 | 213 |
if (align) { |
195 | 214 |
mx <- max(data$x, na.rm=TRUE) |
196 | 215 |
} else { |
... | ... |
@@ -203,12 +222,12 @@ get_cladelabel_position <- function(data, node, offset, align, adjustRatio, angl |
203 | 222 |
## } |
204 | 223 |
|
205 | 224 |
mx <- mx * adjustRatio + offset |
206 |
- |
|
225 |
+ |
|
207 | 226 |
data.frame(x=mx, xend=mx, y=df$y, yend=df$yend, angle=angle) |
208 | 227 |
} |
209 | 228 |
|
210 | 229 |
|
211 |
-get_cladelabel_position_ <- function(data, node, angle="auto") { |
|
230 |
+get_cladelabel_position_ <- function(data, node, angle = "auto", extend = 0) { |
|
212 | 231 |
sp <- get.offspring.df(data, node) |
213 | 232 |
sp2 <- c(sp, node) |
214 | 233 |
sp.df <- data[match(sp2, data$node),] |
... | ... |
@@ -217,7 +236,7 @@ get_cladelabel_position_ <- function(data, node, angle="auto") { |
217 | 236 |
y <- y[!is.na(y)] |
218 | 237 |
mx <- max(sp.df$x, na.rm=TRUE) |
219 | 238 |
|
220 |
- d <- data.frame(x=mx, y=min(y), yend=max(y)) |
|
239 |
+ d <- data.frame(x=mx, y=min(y) - extend, yend=max(y) + extend) |
|
221 | 240 |
if (missing(angle)) |
222 | 241 |
return(d) |
223 | 242 |
|
... | ... |
@@ -226,6 +245,7 @@ get_cladelabel_position_ <- function(data, node, angle="auto") { |
226 | 245 |
} else { |
227 | 246 |
d$angle <- angle |
228 | 247 |
} |
248 |
+ |
|
229 | 249 |
return(d) |
230 | 250 |
} |
231 | 251 |
|
... | ... |
@@ -6,7 +6,7 @@ ggtree: an R package for visualization and annotation of phylogenetic trees with |
6 | 6 |
|
7 | 7 |
[](https://bioconductor.org/packages/ggtree) [](https://github.com/guangchuangyu/ggtree) [](https://www.bioconductor.org/packages/devel/bioc/html/ggtree.html#since) [](https://bioconductor.org/packages/stats/bioc/ggtree) [](https://bioconductor.org/packages/stats/bioc/ggtree) |
8 | 8 |
|
9 |
-[](http://www.repostatus.org/#active) [](https://codecov.io/gh/GuangchuangYu/ggtree) [](https://github.com/GuangchuangYu/ggtree/commits/master) [](https://github.com/GuangchuangYu/ggtree/network) [](https://github.com/GuangchuangYu/ggtree/stargazers) [](https://awesome-r.com/#awesome-r-graphic-displays) |
|
9 |
+[](http://www.repostatus.org/#active) [](https://codecov.io/gh/GuangchuangYu/ggtree) [](https://github.com/GuangchuangYu/ggtree/commits/master) [](https://github.com/GuangchuangYu/ggtree/network) [](https://github.com/GuangchuangYu/ggtree/stargazers) [](https://awesome-r.com/#awesome-r-graphic-displays) |
|
10 | 10 |
|
11 | 11 |
[](https://www.bioconductor.org/packages/devel/bioc/html/ggtree.html#archives) [](https://bioconductor.org/checkResults/devel/bioc-LATEST/ggtree/) [](https://travis-ci.org/GuangchuangYu/ggtree) [](https://ci.appveyor.com/project/GuangchuangYu/ggtree) [](#backers) [](#sponsors) |
12 | 12 |
|
... | ... |
@@ -27,7 +27,7 @@ Please cite the following article when using `ggtree`: |
27 | 27 |
|
28 | 28 |
**G Yu**, DK Smith, H Zhu, Y Guan, TTY Lam<sup>\*</sup>. ggtree: an R package for visualization and annotation of phylogenetic trees with their covariates and other associated data. ***Methods in Ecology and Evolution***. 2017, 8(1):28-36. |
29 | 29 |
|
30 |
-[](http://dx.doi.org/10.1111/2041-210X.12628) [](https://www.altmetric.com/details/10533079) [](https://scholar.google.com.hk/scholar?oi=bibs&hl=en&cites=7268358477862164627) |
|
30 |
+[](http://dx.doi.org/10.1111/2041-210X.12628) [](https://www.altmetric.com/details/10533079) [](https://scholar.google.com.hk/scholar?oi=bibs&hl=en&cites=7268358477862164627) |
|
31 | 31 |
|
32 | 32 |
------------------------------------------------------------------------ |
33 | 33 |
|
... | ... |
@@ -30,11 +30,10 @@ highlights the two direct descendant clades of an internal node |
30 | 30 |
Particularly useful when studying neighboring clades. Note that balances that |
31 | 31 |
correspond to multichotomies will not be displayed. |
32 | 32 |
} |
33 |
-\author{ |
|
34 |
-Justin Silverman |
|
35 |
-} |
|
36 | 33 |
\references{ |
37 | 34 |
J. Silverman, et al. \emph{A phylogenetic transform enhances |
38 | 35 |
analysis of compositional microbiota data}. (in preparation) |
39 | 36 |
} |
40 |
- |
|
37 |
+\author{ |
|
38 |
+Justin Silverman |
|
39 |
+} |
... | ... |
@@ -4,9 +4,10 @@ |
4 | 4 |
\alias{geom_cladelabel} |
5 | 5 |
\title{geom_cladelabel} |
6 | 6 |
\usage{ |
7 |
-geom_cladelabel(node, label, offset = 0, offset.text = 0, align = FALSE, |
|
8 |
- barsize = 0.5, fontsize = 3.88, angle = 0, geom = "text", hjust = 0, |
|
9 |
- color = NULL, fill = NA, family = "sans", parse = FALSE, ...) |
|
7 |
+geom_cladelabel(node, label, offset = 0, offset.text = 0, extend = 0, |
|
8 |
+ align = FALSE, barsize = 0.5, fontsize = 3.88, angle = 0, |
|
9 |
+ geom = "text", hjust = 0, color = NULL, fill = NA, family = "sans", |
|
10 |
+ parse = FALSE, ...) |
|
10 | 11 |
} |
11 | 12 |
\arguments{ |
12 | 13 |
\item{node}{selected node} |
... | ... |
@@ -17,6 +18,8 @@ geom_cladelabel(node, label, offset = 0, offset.text = 0, align = FALSE, |
17 | 18 |
|
18 | 19 |
\item{offset.text}{offset of text from bar} |
19 | 20 |
|
21 |
+\item{extend}{extend bar height} |
|
22 |
+ |
|
20 | 23 |
\item{align}{logical} |
21 | 24 |
|
22 | 25 |
\item{barsize}{size of bar} |
... | ... |
@@ -48,4 +51,3 @@ annotate a clade with bar and text label |
48 | 51 |
\author{ |
49 | 52 |
Guangchuang Yu |
50 | 53 |
} |
51 |
- |
... | ... |
@@ -18,4 +18,3 @@ named list of subtrees with the root id of subtree and list of node id's making |
18 | 18 |
Get all subtrees of node, as well as remaining branches of parent (ie, rest of tree structure as subtree) |
19 | 19 |
return named list of subtrees with list name as starting node id. |
20 | 20 |
} |
21 |
- |
... | ... |
@@ -3,8 +3,9 @@ |
3 | 3 |
\docType{package} |
4 | 4 |
\name{ggtree} |
5 | 5 |
\alias{ggtree} |
6 |
-\alias{ggtree-package} |
|
7 | 6 |
\alias{package-ggtree} |
7 |
+\alias{ggtree-package} |
|
8 |
+\alias{ggtree} |
|
8 | 9 |
\title{visualizing phylogenetic tree and heterogenous associated data based on grammar of graphics |
9 | 10 |
\code{ggtree} provides functions for visualizing phylogenetic tree and its associated data in R.} |
10 | 11 |
\usage{ |
... | ... |
@@ -57,4 +58,3 @@ ggtree(tr) |
57 | 58 |
\author{ |
58 | 59 |
Yu Guangchuang |
59 | 60 |
} |
60 |
- |
... | ... |
@@ -3,12 +3,13 @@ |
3 | 3 |
\docType{methods} |
4 | 4 |
\name{gzoom} |
5 | 5 |
\alias{gzoom} |
6 |
+\alias{gzoom} |
|
7 |
+\alias{gzoom,ggtree-method} |
|
6 | 8 |
\alias{gzoom,beast-method} |
7 | 9 |
\alias{gzoom,codeml-method} |
8 |
-\alias{gzoom,ggtree-method} |
|
10 |
+\alias{gzoom,treedata-method} |
|
9 | 11 |
\alias{gzoom,paml_rst-method} |
10 | 12 |
\alias{gzoom,phylo-method} |
11 |
-\alias{gzoom,treedata-method} |
|
12 | 13 |
\title{gzoom method} |
13 | 14 |
\usage{ |
14 | 15 |
gzoom(object, focus, subtree = FALSE, widths = c(0.3, 0.7), ...) |
... | ... |
@@ -50,4 +51,3 @@ figure |
50 | 51 |
\description{ |
51 | 52 |
zoom selected subtree |
52 | 53 |
} |
53 |
- |
... | ... |
@@ -4,9 +4,9 @@ |
4 | 4 |
\name{scale_color} |
5 | 5 |
\alias{scale_color} |
6 | 6 |
\alias{scale_color,beast-method} |
7 |
+\alias{scale_color,treedata-method} |
|
7 | 8 |
\alias{scale_color,paml_rst-method} |
8 | 9 |
\alias{scale_color,phylo-method} |
9 |
-\alias{scale_color,treedata-method} |
|
10 | 10 |
\title{scale_color method} |
11 | 11 |
\usage{ |
12 | 12 |
scale_color(object, by, ...) |
... | ... |
@@ -33,4 +33,3 @@ color vector |
33 | 33 |
\description{ |
34 | 34 |
scale color by a numerical tree attribute |
35 | 35 |
} |
36 |
- |