... | ... |
@@ -5,11 +5,7 @@ Version: 1.7.4 |
5 | 5 |
Authors@R: c( |
6 | 6 |
person("Guangchuang", "Yu", email = "guangchuangyu@gmail.com", role = c("aut", "cre", "cph")), |
7 | 7 |
person("Tommy Tsan-Yuk", "Lam", email = "tylam.tommy@gmail.com", rol = c("aut", "ths")), |
8 |
- person("Justin", "Silverman", email = "jsilve24@gmail.com", rol = "ctb", comment = "geom_balance"), |
|
9 |
- person("Casey", "Dunn", email = "casey_dunn@brown.edu", rol = "ctb", |
|
10 |
- comment = "NHX"), |
|
11 |
- person("Bradley", "Jones", email="brj1@sfu.ca", rol = "ctb", |
|
12 |
- comment="get.tree method for data.frame") |
|
8 |
+ person("Justin", "Silverman", email = "jsilve24@gmail.com", rol = "ctb") |
|
13 | 9 |
) |
14 | 10 |
Maintainer: Guangchuang Yu <guangchuangyu@gmail.com> |
15 | 11 |
Description: 'ggtree' extends the 'ggplot2' plotting system which implemented the grammar of graphics. |
... | ... |
@@ -6,7 +6,7 @@ setMethod("show", signature(object = "beast"), |
6 | 6 |
cat("'beast' S4 object that stored information of\n\t", |
7 | 7 |
paste0("'", object@file, "'.\n\n")) |
8 | 8 |
cat("...@ tree: ") |
9 |
- print.phylo(get.tree(object)) |
|
9 |
+ print.phylo(get.tree(object)) |
|
10 | 10 |
cat("\nwith the following features available:\n") |
11 | 11 |
print_fields(object) |
12 | 12 |
}) |
... | ... |
@@ -20,7 +20,7 @@ setMethod("show", signature(object = "codeml"), |
20 | 20 |
object@mlc@mlcfile, "'."), |
21 | 21 |
"\n\n") |
22 | 22 |
cat("...@ tree:") |
23 |
- print.phylo(get.tree(object)) |
|
23 |
+ print.phylo(get.tree(object)) |
|
24 | 24 |
cat("\nwith the following features available:\n") |
25 | 25 |
print_fields(object, len=4) |
26 | 26 |
}) |
... | ... |
@@ -32,10 +32,10 @@ setMethod("show", signature(object = "codeml_mlc"), |
32 | 32 |
cat("'codeml_mlc' S4 object that stored information of\n\t", |
33 | 33 |
paste0("'", object@mlcfile, "'."), |
34 | 34 |
"\n\n") |
35 |
- |
|
35 |
+ |
|
36 | 36 |
cat("...@ tree:") |
37 |
- print.phylo(get.tree(object)) |
|
38 |
- |
|
37 |
+ print.phylo(get.tree(object)) |
|
38 |
+ |
|
39 | 39 |
cat("\nwith the following features available:\n") |
40 | 40 |
cat("\t", paste0("'", |
41 | 41 |
paste(get.fields(object), collapse="',\t'"), |
... | ... |
@@ -46,7 +46,7 @@ setMethod("show", signature(object = "codeml_mlc"), |
46 | 46 |
|
47 | 47 |
##' show method for \code{jplace} instance |
48 | 48 |
##' |
49 |
-##' |
|
49 |
+##' |
|
50 | 50 |
##' @name show |
51 | 51 |
##' @docType methods |
52 | 52 |
##' @rdname show-methods |
... | ... |
@@ -72,8 +72,8 @@ setMethod("show", signature(object = "jplace"), |
72 | 72 |
|
73 | 73 |
phylo <- get.tree(object) |
74 | 74 |
phylo$node.label <- NULL |
75 |
- phylo$tip.label %<>% gsub("\\@\\d+", "", .) |
|
76 |
- |
|
75 |
+ phylo$tip.label %<>% gsub("\\@\\d+", "", .) |
|
76 |
+ |
|
77 | 77 |
print.phylo(phylo) |
78 | 78 |
|
79 | 79 |
cat("\nwith the following features availables:\n") |
... | ... |
@@ -92,7 +92,7 @@ setMethod("show", signature(object = "nhx"), |
92 | 92 |
cat("'nhx' S4 object that stored information of\n\t", |
93 | 93 |
paste0("'", object@file, "'.\n\n")) |
94 | 94 |
cat("...@ tree: ") |
95 |
- print.phylo(get.tree(object)) |
|
95 |
+ print.phylo(get.tree(object)) |
|
96 | 96 |
cat("\nwith the following features available:\n") |
97 | 97 |
print_fields(object) |
98 | 98 |
}) |
... | ... |
@@ -105,7 +105,7 @@ setMethod("show", signature(object = "phylip"), |
105 | 105 |
cat("'phylip' S4 object that stored information of\n\t", |
106 | 106 |
paste0("'", object@file, "'.\n\n")) |
107 | 107 |
cat("...@ tree: ") |
108 |
- print.phylo(get.tree(object)) |
|
108 |
+ print.phylo(get.tree(object)) |
|
109 | 109 |
msg <- paste0("\nwith sequence alignment available (", length(object@sequence), |
110 | 110 |
" sequences of length ", nchar(object@sequence)[1], ")\n") |
111 | 111 |
cat(msg) |
... | ... |
@@ -132,9 +132,9 @@ setMethod("show", signature(object = "paml_rst"), |
132 | 132 |
fields <- fields[fields != "joint_subs"] |
133 | 133 |
fields <- fields[fields != "joint_AA_subs"] |
134 | 134 |
} |
135 |
- |
|
135 |
+ |
|
136 | 136 |
cat("...@ tree:") |
137 |
- print.phylo(get.tree(object)) |
|
137 |
+ print.phylo(get.tree(object)) |
|
138 | 138 |
cat("\nwith the following features available:\n") |
139 | 139 |
cat("\t", paste0("'", |
140 | 140 |
paste(fields, collapse="',\t'"), |
... | ... |
@@ -152,7 +152,24 @@ setMethod("show", signature(object = "r8s"), |
152 | 152 |
cat("'r8s' S4 object that stored information of\n\t", |
153 | 153 |
paste0("'", object@file, "'.\n\n")) |
154 | 154 |
cat("...@ tree: ") |
155 |
- print.phylo(get.tree(object)) |
|
155 |
+ print.phylo(get.tree(object)) |
|
156 | 156 |
## cat("\nwith the following features available:\n") |
157 | 157 |
## print_fields(object) |
158 | 158 |
}) |
159 |
+ |
|
160 |
+ |
|
161 |
+##' @rdname show-methods |
|
162 |
+##' @importFrom ape print.phylo |
|
163 |
+##' @exportMethod show |
|
164 |
+setMethod("show", signature(object = "phangorn"), |
|
165 |
+ function(object) { |
|
166 |
+ cat("'phangorn' S4 object that stored ancestral sequences inferred by 'phangorn::ancestral.pml'", ".\n\n") |
|
167 |
+ cat("...@ tree: ") |
|
168 |
+ print.phylo(get.tree(object)) |
|
169 |
+ fields <- get.fields(object) |
|
170 |
+ cat("\nwith the following features available:\n") |
|
171 |
+ cat("\t", paste0("'", |
|
172 |
+ paste(fields, collapse="',\t'"), |
|
173 |
+ "'."), |
|
174 |
+ "\n") |
|
175 |
+ }) |
... | ... |
@@ -1,8 +1,8 @@ |
1 | 1 |
##' tree annotation of sequence substitution by comparing to parent node |
2 | 2 |
##' |
3 |
-##' |
|
3 |
+##' |
|
4 | 4 |
##' @title treeAnno.pml |
5 |
-##' @param pmlTree tree in pml object, output of phangorn::optim.pml |
|
5 |
+##' @param pmlTree tree in pml object, output of phangorn::optim.pml |
|
6 | 6 |
##' @param type one of 'ml' and 'bayes' for inferring ancestral sequences |
7 | 7 |
##' @return phangorn object |
8 | 8 |
##' @importFrom ape read.tree |
... | ... |
@@ -13,7 +13,7 @@ phyPML <- function(pmlTree, type = "ml") { |
13 | 13 |
sequences <- pmlToSeqString(pmlTree, type, includeAncestor=TRUE) |
14 | 14 |
tr <- pmlTree$tree |
15 | 15 |
tr <- reorder.phylo(tr) |
16 |
- |
|
16 |
+ |
|
17 | 17 |
if (is.null(tr$node.label)) { |
18 | 18 |
n <- length(tr$tip.label) |
19 | 19 |
nl <- (n+1):(2*n-2) |
... | ... |
@@ -21,14 +21,14 @@ phyPML <- function(pmlTree, type = "ml") { |
21 | 21 |
} else { |
22 | 22 |
names(sequences) <- c(tr$tip.label, tr$node.label) |
23 | 23 |
} |
24 |
- |
|
24 |
+ |
|
25 | 25 |
seq_type <- get_seqtype(sequences) |
26 | 26 |
res <- new("phangorn", |
27 | 27 |
phylo = tr, |
28 | 28 |
fields = "subs", |
29 | 29 |
seq_type = seq_type, |
30 | 30 |
ancseq = sequences) |
31 |
- |
|
31 |
+ |
|
32 | 32 |
|
33 | 33 |
res@tip_seq <- sequences[names(sequences) %in% tr$tip.label] |
34 | 34 |
|
... | ... |
@@ -37,28 +37,12 @@ phyPML <- function(pmlTree, type = "ml") { |
37 | 37 |
res@AA_subs <- get.subs_(res@phylo, sequences, translate=TRUE) |
38 | 38 |
res@fields %<>% c("AA_subs") |
39 | 39 |
} |
40 |
- |
|
40 |
+ |
|
41 | 41 |
return(res) |
42 | 42 |
} |
43 | 43 |
|
44 | 44 |
|
45 | 45 |
|
46 |
-##' @rdname show-methods |
|
47 |
-##' @importFrom ape print.phylo |
|
48 |
-##' @exportMethod show |
|
49 |
-setMethod("show", signature(object = "phangorn"), |
|
50 |
- function(object) { |
|
51 |
- cat("'phangorn' S4 object that stored ancestral sequences inferred by 'phangorn::ancestral.pml'", ".\n\n") |
|
52 |
- cat("...@ tree: ") |
|
53 |
- print.phylo(get.tree(object)) |
|
54 |
- fields <- get.fields(object) |
|
55 |
- cat("\nwith the following features available:\n") |
|
56 |
- cat("\t", paste0("'", |
|
57 |
- paste(fields, collapse="',\t'"), |
|
58 |
- "'."), |
|
59 |
- "\n") |
|
60 |
- }) |
|
61 |
- |
|
62 | 46 |
|
63 | 47 |
##' @rdname get.subs-methods |
64 | 48 |
##' @exportMethod get.subs |
... | ... |
@@ -114,17 +98,18 @@ setMethod("get.fields", signature(object="phangorn"), |
114 | 98 |
|
115 | 99 |
##' convert pml object to XStringSet object |
116 | 100 |
##' |
117 |
-##' |
|
118 |
-##' @title pmlToSeq |
|
101 |
+##' |
|
102 |
+##' @title pmlToSeq |
|
119 | 103 |
##' @param pml pml object |
120 |
-##' @param includeAncestor logical |
|
104 |
+##' @param includeAncestor logical |
|
105 |
+##' @param type one of "marginal", "ml", "bayes" |
|
121 | 106 |
##' @return XStringSet |
122 | 107 |
## @importFrom Biostrings DNAStringSet |
123 | 108 |
##' @export |
124 | 109 |
##' @author ygc |
125 |
-pmlToSeq <- function(pml, includeAncestor=TRUE) { |
|
110 |
+pmlToSeq <- function(pml, type="ml", includeAncestor=TRUE) { |
|
126 | 111 |
DNAStringSet <- get_fun_from_pkg("Biostrings", "DNAStringSet") |
127 |
- pmlToSeqString(pml, includeAncestor) %>% |
|
112 |
+ pmlToSeqString(pml, type, includeAncestor) %>% |
|
128 | 113 |
DNAStringSet |
129 | 114 |
} |
130 | 115 |
|
... | ... |
@@ -136,15 +121,15 @@ pmlToSeqString <- function(pml, type, includeAncestor=TRUE) { |
136 | 121 |
ancestral.pml <- get_fun_from_pkg("phangorn", "ancestral.pml") |
137 | 122 |
phyDat <- ancestral.pml(pml, type) |
138 | 123 |
} |
139 |
- |
|
124 |
+ |
|
140 | 125 |
phyDat <- matrix2vector.phyDat(phyDat) |
141 | 126 |
## defined by phangorn |
142 |
- labels <- c("a", "c", "g", "t", "u", "m", "r", "w", "s", |
|
127 |
+ labels <- c("a", "c", "g", "t", "u", "m", "r", "w", "s", |
|
143 | 128 |
"y", "k", "v", "h", "d", "b", "n", "?", "-") |
144 | 129 |
labels <- toupper(labels) |
145 | 130 |
|
146 | 131 |
index <- attr(phyDat, "index") |
147 |
- |
|
132 |
+ |
|
148 | 133 |
result <- do.call(rbind, phyDat) |
149 | 134 |
result <- result[, index, drop=FALSE] |
150 | 135 |
|
... | ... |
@@ -177,7 +162,7 @@ matrix2vector.phyDat.item <- function(y) { |
177 | 162 |
## cat("insertion found...\n") |
178 | 163 |
} |
179 | 164 |
## 18 is the gap(-) index of base character defined in phangorn |
180 |
- ## c("a", "c", "g", "t", "u", "m", "r", "w", "s", |
|
165 |
+ ## c("a", "c", "g", "t", "u", "m", "r", "w", "s", |
|
181 | 166 |
## "y", "k", "v", "h", "d", "b", "n", "?", "-") |
182 | 167 |
18 |
183 | 168 |
} else { |
... | ... |
@@ -2,9 +2,9 @@ |
2 | 2 |
ggtree: an R package for visualization and annotation of phylogenetic trees with their covariates and other associated data |
3 | 3 |
=========================================================================================================================== |
4 | 4 |
|
5 |
-[](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) <img src="logo.png" align="right" /> |
|
5 |
+[](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) <img src="logo.png" align="right" /> |
|
6 | 6 |
|
7 |
-[](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) |
|
7 |
+[](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) |
|
8 | 8 |
|
9 | 9 |
[](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) [](http://bioconda.github.io/recipes/bioconductor-ggtree/README.html) |
10 | 10 |
|
... | ... |
@@ -18,7 +18,7 @@ Please cite the following article when using `ggtree`: |
18 | 18 |
|
19 | 19 |
**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***. *accepted* |
20 | 20 |
|
21 |
-[](http://dx.doi.org/10.1111/2041-210X.12628) [](https://scholar.google.com.hk/scholar?oi=bibs&hl=en&cites=7268358477862164627) [](https://www.altmetric.com/details/10533079) |
|
21 |
+[](http://dx.doi.org/10.1111/2041-210X.12628) [](https://scholar.google.com.hk/scholar?oi=bibs&hl=en&cites=7268358477862164627) [](https://www.altmetric.com/details/10533079) |
|
22 | 22 |
|
23 | 23 |
------------------------------------------------------------------------ |
24 | 24 |
|
... | ... |
@@ -51,7 +51,7 @@ For details, please visit our project website, <https://guangchuangyu.github.io/ |
51 | 51 |
|
52 | 52 |
### Download stats |
53 | 53 |
|
54 |
-[](https://bioconductor.org/packages/stats/bioc/ggtree) [](https://bioconductor.org/packages/stats/bioc/ggtree) [](https://bioconductor.org/packages/stats/bioc/ggtree) |
|
54 |
+[](https://bioconductor.org/packages/stats/bioc/ggtree) [](https://bioconductor.org/packages/stats/bioc/ggtree) [](https://bioconductor.org/packages/stats/bioc/ggtree) |
|
55 | 55 |
|
56 | 56 |
+----------------------+----------------------+----------------------+----------------------+-+ |
57 | 57 |
| * | |
... | ... |
@@ -4,11 +4,13 @@ |
4 | 4 |
\alias{pmlToSeq} |
5 | 5 |
\title{pmlToSeq} |
6 | 6 |
\usage{ |
7 |
-pmlToSeq(pml, includeAncestor = TRUE) |
|
7 |
+pmlToSeq(pml, type = "ml", includeAncestor = TRUE) |
|
8 | 8 |
} |
9 | 9 |
\arguments{ |
10 | 10 |
\item{pml}{pml object} |
11 | 11 |
|
12 |
+\item{type}{one of "marginal", "ml", "bayes"} |
|
13 |
+ |
|
12 | 14 |
\item{includeAncestor}{logical} |
13 | 15 |
} |
14 | 16 |
\value{ |
... | ... |
@@ -1,5 +1,5 @@ |
1 | 1 |
% Generated by roxygen2: do not edit by hand |
2 |
-% Please edit documentation in R/RAxML.R, R/ape.R, R/hyphy.R, R/method-show.R, R/phangorn.R |
|
2 |
+% Please edit documentation in R/RAxML.R, R/ape.R, R/hyphy.R, R/method-show.R |
|
3 | 3 |
\docType{methods} |
4 | 4 |
\name{show,raxml-method} |
5 | 5 |
\alias{show} |