Browse code

update vignettes

git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/ggtree@112408 bc3139a8-67e5-0310-9ffc-ced21a209358

Guangchuang Yu authored on 11/01/2016 04:11:26
Showing 14 changed files

... ...
@@ -1,5 +1,6 @@
1 1
 CHANGES IN VERSION 1.3.8
2 2
 ------------------------
3
+ o update vignettes <2016-01-07, Thu>
3 4
  o 05 advance tree annotation vignette <2016-01-04, Mon>
4 5
  o export theme_inset <2016-01-04, Mon>
5 6
  o inset, nodebar, nodepie functions <2015-12-31, Thu>
... ...
@@ -77,7 +77,7 @@ ggtree <- function(tr,
77 77
                 branch.length = branch.length,
78 78
                 ndigits       = ndigits, ...)
79 79
     
80
-    p <- p + geom_tree(layout, ...) + xlab(NULL) + ylab(NULL) + theme_tree()
80
+    p <- p + geom_tree(layout, ...)  + theme_tree()
81 81
     
82 82
     if (type == "circular" || type == "radial") {
83 83
         p <- p + coord_polar(theta = "y")
... ...
@@ -9,6 +9,8 @@
9 9
 ##' @importFrom ggplot2 theme
10 10
 ##' @importFrom ggplot2 element_blank
11 11
 ##' @importFrom ggplot2 %+replace%
12
+##' @importFrom ggplot2 xlab
13
+##' @importFrom ggplot2 ylab
12 14
 ##' @export
13 15
 ##' @return updated ggplot object with new theme
14 16
 ##' @author Yu Guangchuang
... ...
@@ -17,12 +19,15 @@
17 19
 ##' tr <- rtree(10)
18 20
 ##' ggtree(tr) + theme_tree()
19 21
 theme_tree <- function(bgcolor="white", fgcolor="black", ...) {
20
-    theme_tree2() %+replace%
21
-    theme(panel.background=element_rect(fill=bgcolor, colour=bgcolor),
22
-          axis.line.x = element_blank(),
23
-          axis.text.x = element_blank(),
24
-          axis.ticks.x = element_blank(),
25
-          ...)
22
+    list(xlab(NULL),
23
+         ylab(NULL),
24
+	 theme_tree2_internal() %+replace%
25
+            theme(panel.background=element_rect(fill=bgcolor, colour=bgcolor),
26
+            axis.line.x = element_blank(),
27
+            axis.text.x = element_blank(),
28
+            axis.ticks.x = element_blank(),
29
+            ...)
30
+	 )
26 31
 }
27 32
 
28 33
 ##' tree2 theme
... ...
@@ -46,6 +51,13 @@ theme_tree <- function(bgcolor="white", fgcolor="black", ...) {
46 51
 ##' tr <- rtree(10)
47 52
 ##' ggtree(tr) + theme_tree2()
48 53
 theme_tree2 <- function(bgcolor="white", fgcolor="black", ...) {
54
+     list(xlab(NULL),
55
+          ylab(NULL),
56
+	  theme_tree2_internal(bgcolor, fgcolor, ...)
57
+	  )
58
+}
59
+
60
+theme_tree2_internal <- function(bgcolor="white", fgcolor="black", ...) {
49 61
     theme_bw() %+replace%
50 62
     theme(legend.position="none",
51 63
           panel.grid.minor=element_blank(),
... ...
@@ -42,23 +42,14 @@ To install:
42 42
 
43 43
 ## Documentation ##
44 44
 
45
-+ [viewing and annotating phylogenetic tree with ggtree](http://guangchuangyu.github.io/2014/12/viewing-and-annotating-phylogenetic-tree-with-ggtree/)
46
-+ [updating a tree view using %<% operator](http://guangchuangyu.github.io/2015/02/ggtree-updating-a-tree-view-using--operator/)
47
-+ [an example of drawing beast tree using ggtree](http://guangchuangyu.github.io/2015/04/an-example-of-drawing-beast-tree-using-ggtree/)
48
-+ [flip and rotate branches in ggtree](http://guangchuangyu.github.io/2015/07/flip-and-rotate-branches-in-ggtree/)
49
-+ [subsetting data in ggtree](http://guangchuangyu.github.io/2015/09/subsetting-data-in-ggtree/)
50
-+ [ggtree with funny fonts](http://guangchuangyu.github.io/2015/06/ggtree-with-funny-fonts/)
51
-+ [comic phylogenetic tree with ggtree and comicR](http://guangchuangyu.github.io/2015/09/comic-phylogenetic-tree-with-ggtree-and-comicr/)
52
-+ [embeding a subplot in ggplot via subview](http://guangchuangyu.github.io/2015/08/subview/)
53
-+ [annotate phylogenetic tree with local images](http://guangchuangyu.github.io/2015/08/ggtree-annotate-phylogenetic-tree-with-local-images/)
54
-+ [phylomoji with ggtree](http://guangchuangyu.github.io/2015/12/use-emoji-font-in-r/)
55
-
56
-
57 45
 To view the vignette of `ggtree` installed in your system, start `R` and enter:
58 46
 ```r
59 47
 vignette("ggtree", package = "ggtree")
60 48
 ```
61 49
 
50
+More documents can be found in <http://guangchuangyu.github.io/categories/ggtree>.
51
+
52
+
62 53
 ## Bugs/Feature requests ##
63 54
 
64 55
  - If you have any, [let me know](https://github.com/GuangchuangYu/ggtree/issues). Thx!
... ...
@@ -2,8 +2,8 @@
2 2
 	"tree": "(((((((A:4{1},B:4{2}):6{3},C:5{4}):8{5},D:6{6}):3{7},E:21{8}):10{9},((F:4{10},G:12{11}):14{12},H:8{13}):13{14}):13{15},((I:5{16},J:2{17}):30{18},(K:11{19},L:11{20}):2{21}):17{22}):4{23},M:56{24});",
3 3
 	"placements": [
4 4
 	{"p":[24, -61371.300778, 0.333344, 0.000003, 0.003887], "n":["AA"]},
5
-	{"p":[[1, -61312.210786, 0.333335, 0.000001, 0.000003],[2, -61312.210823, 0.333322, 0.000003, 0.000003],[550, -61312.210823, 0.333322, 0.000961, 0.000003]], "n":["BB"]},
6
-	{"p":[[8, -61312.229128, 0.200011, 0.000001, 0.000003],[9, -61312.229179, 0.200000, 0.000003, 0.000003],[10, -61312.229223, 0.199992, 0.000003, 0.000003]], "n":["CC"]}
5
+	{"p":[[1, -61312.210786, 0.333335, 0.000001, 0.000003],[2, -61322.210823, 0.333322, 0.000003, 0.000003],[550, -61352.210823, 0.333322, 0.000961, 0.000003]], "n":["BB"]},
6
+	{"p":[[8, -61312.229128, 0.200011, 0.000001, 0.000003],[9, -61322.229179, 0.200000, 0.000003, 0.000003],[10, -61342.229223, 0.199992, 0.000003, 0.000003]], "n":["CC"]}
7 7
 	],
8 8
 	"metadata": {"info": "sample file, without any meaning"},
9 9
 	"version" : 2,
... ...
@@ -35,8 +35,11 @@ library("ggtree")
35 35
 
36 36
 # Visualize tree with associated matrix
37 37
 
38
+<!--
38 39
 At first we implemented `gplot` function to visualize tree with heatmap but it has [an issue](https://github.com/GuangchuangYu/ggtree/issues/3) that it can't always guarantee the heatmap aligning to the tree properly, since the line up is between two figures and it's currently not supported internally by ggplot2. I have implemented another function `gheatmap` that can do the line up properly by creating a new layer above the tree.
40
+-->
39 41
 
42
+The `gheatmap` function is designed to visualize phylogenetic tree with heatmap of associated matrix.
40 43
 
41 44
 In the following example, we visualized a tree of H3 influenza viruses with their associated genotype.
42 45
 
... ...
@@ -51,12 +54,14 @@ p <- p + geom_tiplab(size=3)
51 54
 gheatmap(p, genotype, offset = 2, width=0.5)
52 55
 ```
53 56
 
54
-The _width_ parameter is to control the width of the heatmap. It supports another parameter _offset_ for controling the distance between the tree and the heatmap, for instance left space for tip labels.
57
+The _width_ parameter is to control the width of the heatmap. It supports another parameter _offset_ for controling the distance between the tree and the heatmap, for instance to allocate space for tip labels.
55 58
 
56 59
 
57
-For time scaled tree, as in this example, it's more often to use x axis by using `theme_tree2`. But with this solution, the heatmap is just another layer and will change the `x` axis. To overcome this issue, we implemented `scale_x_ggtree` to set the x axis more reasonable. User can also use `gplot` and tweak the positions of two plot to align properly.
60
+For time-scaled tree, as in this example, it's more often to use x axis by using `theme_tree2`. But with this solution, the heatmap is just another layer and will change the `x` axis. To overcome this issue, we implemented `scale_x_ggtree` to set the x axis more reasonable. 
58 61
 
59
-```{r fig.width=20, fig.height=16, fig.align="center"}
62
+<!-- User can also use `gplot` and tweak the positions of two plot to align properly. -->
63
+
64
+```{r fig.width=20, fig.height=16, fig.align="center", warning=FALSE}
60 65
 p <- ggtree(beast_tree, mrsd="2013-01-01") + geom_tiplab(size=3, align=TRUE) + theme_tree2()
61 66
 pp <- (p + scale_y_continuous(expand=c(0, 0.3))) %>%
62 67
     gheatmap(genotype, offset=4, width=0.5, colnames=FALSE) %>%
... ...
@@ -66,7 +71,7 @@ pp + theme(legend.position="right")
66 71
 
67 72
 # Visualize tree with multiple sequence alignment
68 73
 
69
-With `msaplot` function, user can visualizes multiple sequence alignment with phylogenetic tree, as demonstrated below:
74
+With `msaplot` function, user can visualize multiple sequence alignment with phylogenetic tree, as demonstrated below:
70 75
 ```{r fig.width=8, fig.height=12, fig.align='center'}
71 76
 fasta <- system.file("examples/FluA_H3_AA.fas", package="ggtree")
72 77
 msaplot(ggtree(beast_tree), fasta) 
... ...
@@ -74,10 +79,13 @@ msaplot(ggtree(beast_tree), fasta)
74 79
 
75 80
 A specific slice of the alignment can also be displayed by specific _window_ parameter.
76 81
 
82
+```{r fig.width=8, fig.height=12, fig.align='center'}
83
+msaplot(ggtree(beast_tree), fasta, window=c(150, 200)) 
84
+```
77 85
 
78 86
 # Annotate a phylogenetic with insets
79 87
 
80
-`ggtree` implemented a function, `subview`, that can add subplots into a ggplot2 object. It had successful applied to [plot pie graphs on map](http://stackoverflow.com/questions/10368180/plotting-pie-graphs-on-map-in-ggplot/32380396#32380396).
88
+`ggtree` implemented a function, `subview`, that can add subplots on a ggplot2 object. It had successful applied to [plot pie graphs on map](http://stackoverflow.com/questions/10368180/plotting-pie-graphs-on-map-in-ggplot/32380396#32380396).
81 89
 
82 90
 ```{r fig.width=8, fig.height=8, warning=F}
83 91
 set.seed(2016-01-04)
... ...
@@ -113,7 +121,7 @@ bars <- nodebar(dat, cols=1:4)
113 121
 inset(p, bars)
114 122
 ```
115 123
 
116
-The size of the inset can be ajusted by the paramter *width* and *height*.
124
+The sizes of the insets can be ajusted by the paramter *width* and *height*.
117 125
 
118 126
 ```{r}
119 127
 inset(p, bars, width=.03, height=.06)
... ...
@@ -190,8 +198,7 @@ d2$panel <- 'Stats'
190 198
 d1$panel <- factor(d1$panel, levels=c("Tree", "Stats"))
191 199
 d2$panel <- factor(d2$panel, levels=c("Tree", "Stats"))
192 200
 
193
-p <- ggplot(mapping=aes(x=x, y=y)) + facet_grid(.~panel, scale="free_x") +
194
-    xlab(NULL)+ylab(NULL)+theme_tree2()
201
+p <- ggplot(mapping=aes(x=x, y=y)) + facet_grid(.~panel, scale="free_x") + theme_tree2()
195 202
 p+geom_tree(data=d1) + geom_point(data=d2, aes(x=tipstats)) 
196 203
 ```
197 204
 
... ...
@@ -204,13 +211,13 @@ p+geom_tree(data=d1) + geom_point(data=d2, aes(x=tipstats))
204 211
 pp <- ggtree(tree) %>% phylopic("79ad5f09-cf21-4c89-8e7d-0c82a00ce728", color="steelblue", alpha = .3)
205 212
 print(pp)
206 213
 ```
207
-![](../inst/extdata/phylopic1.png)
214
+![](figures/phylopic1.png)
208 215
 
209 216
 ```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE, eval=FALSE}
210 217
 pp %>% phylopic("67382184-5135-4faa-8e98-eadff02c3e8a", color="#86B875", alpha=.8, node=4) %>%
211 218
      phylopic("d3563b54-780f-4711-a49a-7ea051e9dacc", color="darkcyan", alpha=.8, node=17, width=.2)
212 219
 ```
213
-![](../inst/extdata/phylopic2.png)
220
+![](figures/phylopic2.png)
214 221
 
215 222
 
216 223
 Annotate phylogenetic tree with local images is also supported, please refer to the [blog post](http://guangchuangyu.github.io/2015/08/ggtree-annotate-phylogenetic-tree-with-local-images/).
217 224
Binary files a/vignettes/figures/ggtree_objects.png and b/vignettes/figures/ggtree_objects.png differ
218 225
similarity index 100%
219 226
rename from inst/extdata/phylopic1.png
220 227
rename to vignettes/figures/phylopic1.png
221 228
similarity index 100%
222 229
rename from inst/extdata/phylopic2.png
223 230
rename to vignettes/figures/phylopic2.png
... ...
@@ -61,35 +61,15 @@ The `ggtree` is designed by extending the `ggplot2`[@wickham_ggplot2_2009] packa
61 61
 
62 62
 # Getting data into `R`
63 63
 
64
-Most of the tree viewer software (including `R` packages) focus on `Newick` and `Nexus` file format, while there are file formats from different evolution analysis software that contain supporting evidences within the file that are ready for annotating a phylogenetic tree.
65
-The `ggtree` package define several parser functions and `S4` classes to store statistical evidences inferred by commonly used software packages. It supports several file format, including:
66
-
67
-+ Newick (via `ape`)
68
-+ Nexus (via `ape`)
69
-+ New Hampshire eXtended format (NHX)
70
-+ Jplace
71
-
72
-and software output from:
73
-
74
-+ [BEAST](http://beast2.org/)[@bouckaert_beast_2014] 
75
-+ [EPA](http://sco.h-its.org/exelixis/web/software/epa/index.html)[@berger_EPA_2011]
76
-+ [HYPHY](http://hyphy.org/w/index.php/Main_Page)[@pond_hyphy_2005]
77
-+ [PAML](http://abacus.gene.ucl.ac.uk/software/paml.html)[@yang_paml_2007]
78
-+ [PHYLDOG](http://pbil.univ-lyon1.fr/software/phyldog/)[@boussau_genome-scale_2013]
79
-+ [pplacer](http://matsen.fhcrc.org/pplacer/)[@matsen_pplacer_2010]
80
-+ [r8s](http://loco.biosci.arizona.edu/r8s/)[@marazzi_locating_2012]
81
-+ [RAxML](http://sco.h-its.org/exelixis/web/software/raxml/)[@stamatakis_raxml_2014]
82
-+ [RevBayes](http://revbayes.github.io/intro.html)[@hohna_probabilistic_2014]
83
-
64
+Most of the tree viewer software (including `R` packages) focus on `Newick` and `Nexus` file format, while there are file formats from different evolution analysis software that contain supporting evidences within the file that are ready for annotating a phylogenetic tree. In addition to `Newick` and `Nexus`, ggtree supports `NHX` and `jplace` file formats. `ggtree` also supports software outputs from [BEAST](http://beast2.org/)[@bouckaert_beast_2014], [EPA](http://sco.h-its.org/exelixis/web/software/epa/index.html)[@berger_EPA_2011], [HYPHY](http://hyphy.org/w/index.php/Main_Page)[@pond_hyphy_2005], [PAML](http://abacus.gene.ucl.ac.uk/software/paml.html)[@yang_paml_2007], [PHYLDOG](http://pbil.univ-lyon1.fr/software/phyldog/)[@boussau_genome-scale_2013], [pplacer](http://matsen.fhcrc.org/pplacer/)[@matsen_pplacer_2010], [r8s](http://loco.biosci.arizona.edu/r8s/)[@marazzi_locating_2012], [RAxML](http://sco.h-its.org/exelixis/web/software/raxml/)[@stamatakis_raxml_2014] and [RevBayes](http://revbayes.github.io/intro.html)[@hohna_probabilistic_2014].
84 65
 
85 66
 Parsing data from a number of molecular evolution software is not only for visualization in `ggtree`, but also bring these data to `R` users for further analysis (e.g. summarization, visualization, comparision, test, _etc_).
86 67
 
87 68
 For more details, please refer to [Tree Data Import](treeImport.html) vignette.
88 69
 
89
-
90 70
 # Tree Visualization and Annotation
91 71
 
92
-Tree Visualization in `ggtree` is easy, with one line of command `ggtree(tree_object)`. It supports several layout, including `rectangular`, `slanted` and `circular` for `Phylogram` and `Cladogram`, `unrooted` layout, time-scaled and two dimentional phylogenies. [Tree Visualization](treeVisualization.html) vignette describe these feature in details.
72
+Tree Visualization in `ggtree` is easy, with one line of command `ggtree(tree_object)`. It supports several layouts, including `rectangular`, `slanted` and `circular` for `Phylogram` and `Cladogram`, `unrooted` layout, time-scaled and two dimentional phylogenies. [Tree Visualization](treeVisualization.html) vignette describes these feature in details.
93 73
 
94 74
 We implement several functions to manipulate a phylogenetic tree.
95 75
 
... ...
@@ -105,13 +85,13 @@ Details and examples can be found in [Tree Manipulation](treeManipulation.html)
105 85
 
106 86
 Most of the phylogenetic trees are scaled by evolutionary distance (substitution/site), in `ggtree` a phylogenetic tree can be re-scaled by any numerical variable inferred by evolutionary analysis (e.g. species divergence time, *dN/dS*, _etc_). Numerical and category variable can be used to color a phylogenetic tree.
107 87
 
108
-The `ggtree` package provides several layers to annotate a phylogenetic tree, including `geom_treescale` for adding a legend of tree scale, `geom_hilight` for highlighting selected clades and `geom_cladelabel` for labelling selected clades.
88
+The `ggtree` package provides several layers to annotate a phylogenetic tree, including `geom_tiplab` for adding tip labels, `geom_treescale` for adding a legend of tree scale, `geom_hilight` for highlighting selected clades and `geom_cladelabel` for labelling selected clades. 
109 89
 
110
-It supports annotating phylogenetic trees with analyses by R packages and other commonly used evolutionary software. User's specific annotation (e.g. experimental data) can be integrated to annotate phylogenetic tree. `ggtree` provides `write.jplace` function to combine Newick tree file and user's own data to a single `jplace` file that can be parsed and the data can be used to annotate the tree directly in `ggtree`.
90
+It supports annotating phylogenetic trees with analyses obtained from R packages and other commonly used evolutionary software. User's specific annotation (e.g. experimental data) can be integrated to annotate phylogenetic trees. `ggtree` provides `write.jplace` function to combine Newick tree file and user's own data to a single `jplace` file that can be parsed and the data can be used to annotate the tree directly in `ggtree`.
111 91
 
112 92
 `ggtree` integrates `phylopic` database and silhouette images of organisms can be downloaded and used to annotate phylogenetic directly. `ggtree` also supports using local images to annotate a phylogenetic tree.
113 93
 
114
-Visualizing an annotated phylogenetic tree with numerical matrix (e.g. genotype table) and multiple sequence alignment is also supported in `ggtree`. Examples of annotating phylogenetic trees can be found in the [Tree Annotation](treeAnnotation.html) vignette.
94
+Visualizing an annotated phylogenetic tree with numerical matrix (e.g. genotype table), multiple sequence alignment and subplots are also supported in `ggtree`. Examples of annotating phylogenetic trees can be found in the [Tree Annotation](treeAnnotation.html) and [Advance Tree Annotation](advanceTreeAnnotation.html) vignettes.
115 95
 
116 96
 
117 97
 # Vignette Entry
... ...
@@ -122,11 +102,12 @@ Visualizing an annotated phylogenetic tree with numerical matrix (e.g. genotype
122 102
 + [Tree Annotation](treeAnnotation.html)
123 103
 + [Advance Tree Annotation](advanceTreeAnnotation.html)
124 104
 
105
+More documents can be found in <http://guangchuangyu.github.io/categories/ggtree>.
106
+
125 107
 # Bugs/Feature requests
126 108
 
127 109
 If you have any, [let me know](https://github.com/GuangchuangYu/ggtree/issues). Thx!
128 110
 
129
-
130 111
 # Session info
131 112
 
132 113
 Here is the output of `sessionInfo()` on the system on which this document was compiled:
... ...
@@ -37,7 +37,7 @@ library("gridExtra")
37 37
 
38 38
 # Rescale tree
39 39
 
40
-Most of the phylogenetic trees are scaled by evolutionary distance (substitution/site), in `ggtree`, we can re-scale a phylogenetic tree by any numerical variable inferred by evolutionary analysis (e.g. *dN/dS*).
40
+Most of the phylogenetic trees are scaled by evolutionary distance (substitution/site), in `ggtree`, users can re-scale a phylogenetic tree by any numerical variable inferred by evolutionary analysis (e.g. *dN/dS*).
41 41
 
42 42
 
43 43
 ```{r fig.width=10, fig.height=5}
... ...
@@ -96,7 +96,8 @@ ggtree(beast_tree, aes(color=rate)) +
96 96
 User can use any feature (if available), including clade posterior and *dN/dS* _etc._, to scale the color of the tree.
97 97
 
98 98
 ## Annotate clades
99
-`ggtree` implements _`geom_cladelabel`_ layer to annotate a selected clade with a bar indicating that clade with a corresponding label.
99
+
100
+`ggtree` implements _`geom_cladelabel`_ layer to annotate a selected clade with a bar indicating the clade with a corresponding label.
100 101
 
101 102
 The _`geom_cladelabel`_ layer accepts a selected internal node number. To get the internal node number, please refer to [Tree Manipulation](treeManipulation.html#internal-node-number) vignette.
102 103
 
... ...
@@ -110,35 +111,35 @@ p+geom_cladelabel(node=45, label="test label") +
110 111
     geom_cladelabel(node=34, label="another clade") 
111 112
 ```
112 113
 
113
-We can set the parameter, `align = TRUE`, to align the clade label, and use the parameter, `offset`, to adjust the position.
114
+Users can set the parameter, `align = TRUE`, to align the clade label, and use the parameter, `offset`, to adjust the position.
114 115
 
115 116
 ```{r}
116 117
 p+geom_cladelabel(node=45, label="test label", align=TRUE, offset=.5) +
117 118
     geom_cladelabel(node=34, label="another clade", align=TRUE, offset=.5)
118 119
 ```
119 120
 
120
-We can change the color of the clade label via the parameter `color`.
121
+Users can change the color of the clade label via the parameter `color`.
121 122
 
122 123
 ```{r}
123 124
 p+geom_cladelabel(node=45, label="test label", align=T, color='red') +
124 125
     geom_cladelabel(node=34, label="another clade", align=T, color='blue')
125 126
 ```
126 127
 
127
-We can change the `angle` of the clade label text and the relative position from text to bar via the parameter `offset.text`.
128
+Users can change the `angle` of the clade label text and relative position from text to bar via the parameter `offset.text`.
128 129
 
129 130
 ```{r}
130 131
 p+geom_cladelabel(node=45, label="test label", align=T, angle=270, hjust='center', offset.text=.5) +
131 132
     geom_cladelabel(node=34, label="another clade", align=T, angle=45) 
132 133
 ```
133 134
 
134
-We can change the size of the bar and text via the parameters `barsize` and `fontsize` respectively.
135
+The size of the bar and text can be changed via the parameters `barsize` and `fontsize` respectively.
135 136
 
136 137
 ```{r}
137 138
 p+geom_cladelabel(node=45, label="test label", align=T, angle=270, hjust='center', offset.text=.5, barsize=1.5) +
138 139
     geom_cladelabel(node=34, label="another clade", align=T, angle=45, fontsize=8) 
139 140
 ```
140 141
 
141
-We can also use `geom_label` to label the text.
142
+Users can also use `geom_label` to label the text.
142 143
 
143 144
 ```{r}
144 145
 p+ geom_cladelabel(node=34, label="another clade", align=T, geom='label', fill='lightblue') 
... ...
@@ -146,7 +147,7 @@ p+ geom_cladelabel(node=34, label="another clade", align=T, geom='label', fill='
146 147
 
147 148
 # Highlight clades
148 149
 
149
-`ggtree` implements _`geom_hilight`_ layer, that an internal node number and add a layer of rectangle to highlight the selected clade.
150
+`ggtree` implements _`geom_hilight`_ layer, that accepts an internal node number and add a layer of rectangle to highlight the selected clade.
150 151
 
151 152
 ```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
152 153
 nwk <- system.file("extdata", "sample.nwk", package="ggtree")
... ...
@@ -214,18 +215,16 @@ In `ggtree`, we implemented several parser functions to parse output from common
214 215
 + [RAxML](http://sco.h-its.org/exelixis/web/software/raxml/)[@stamatakis_raxml_2014]
215 216
 + [RevBayes](http://revbayes.github.io/intro.html)[@hohna_probabilistic_2014]
216 217
 
217
-Evolutionary evidences inferred by these software packages can be used for further analysis in `R` and annotate phylogenetic tree directly in `ggtree`. For more details, please refer to the [Tree Data Import](treeImport.html) vignette.
218
+Evolutionary evidences inferred by these software packages can be used for further analysis in `R` and annotating phylogenetic tree directly in `ggtree`. For more details, please refer to the [Tree Data Import](treeImport.html) vignette.
218 219
 
219 220
 
220 221
 # Tree annotation with user specific annotation
221 222
 
222 223
 ## the `%<+%` operator
223 224
 
224
-We provides several functions to parse and store information from common software output.
225
-
226
-Here, we would like to demonstrate how to inject user specific annotation data in a tree.
225
+In addition to parse commonly used software output, `ggtree` also supports annotating a phylogenetic tree using user's own data.
227 226
 
228
-Suppose we have the following data that associated with the tree and would like to attach the data in the tree.
227
+Suppose we have the following data that associate with the tree and would like to attach the data in the tree.
229 228
 
230 229
 ```{r}
231 230
 nwk <- system.file("extdata", "sample.nwk", package="ggtree")
... ...
@@ -233,7 +232,7 @@ tree <- read.tree(nwk)
233 232
 p <- ggtree(tree)
234 233
 
235 234
 dd <- data.frame(taxa  = LETTERS[1:13], 
236
-      		 place = c(rep("GZ", 5), rep("HK", 3), rep("CZ", 4), NA),
235
+                 place = c(rep("GZ", 5), rep("HK", 3), rep("CZ", 4), NA),
237 236
                  value = round(abs(rnorm(13, mean=70, sd=10)), digits=1))
238 237
 ## you don't need to order the data
239 238
 ## data was reshuffled just for demonstration
... ...
@@ -248,38 +247,32 @@ print(dd)
248 247
 knitr::kable(dd)
249 248
 ```
250 249
 
251
-We can imaging that the _`place`_ column is the place we isolated the species and _`value`_ column stored numerical values for example bootstrap values.
250
+We can imaging that the _`place`_ column stores the location we isolated the species and _`value`_ column stores numerical values (e.g. bootstrap values).
252 251
 
253
-We have shown using the operator, _`%<%`_, to update a tree view with a new tree. Here, we will introduce another operator, _`%<+%`_, that attaches annotation data to a tree view. The only requirement of the input data is that its first column should be matched with the node/tip labels of the tree.
252
+We have demonstrated using the operator, _`%<%`_, to update a tree view with a new tree. Here, we will introduce another operator, _`%<+%`_, that attaches annotation data to a tree view. The only requirement of the input data is that its first column should be matched with the node/tip labels of the tree.
254 253
 
255
-After attaching the annotation data to the tree by _`%<+%`_, all the columns in the data are visible to _`ggplot2`_. As an example, here we attach the above annotation data to the tree view, _`p`_, and add a layer that showing the tip labels and colored them by the isolation site stored in _`place`_ column.
254
+After attaching the annotation data to the tree by _`%<+%`_, all the columns in the data are visible to _`ggtree`_. As an example, here we attach the above annotation data to the tree view, _`p`_, and add a layer that showing the tip labels and colored them by the isolation site stored in _`place`_ column.
256 255
 
257 256
 ```{r fig.width=6, fig.height=5, warning=FALSE, fig.align="center"}
258
-p <- p %<+% dd + geom_text(aes(color=place, label=label), hjust=-0.5) + 
257
+p <- p %<+% dd + geom_tiplab(aes(color=place)) + 
259 258
        geom_tippoint(aes(size=value, shape=place, color=place), alpha=0.25)
260 259
 p+theme(legend.position="right")
261 260
 ```
262 261
 
263
-Once the data was attached, it is always attached. So we can add another layer to display the isolation sites easily.
264
-```{r fig.width=6, fig.height=5, warning=FALSE, fig.align="center"}
265
-p <- p + geom_text(aes(color=place, label=place), hjust=1, vjust=-0.4, size=3)
266
-print(p)
267
-```
268
-
269
-And another layer showing numerical values:
262
+Once the data was attached, it is always attached. So that we can add other layers to display these information easily. 
270 263
 ```{r fig.width=6, fig.height=5, warning=FALSE, fig.align="center"}
271
-p <- p + geom_text(aes(color=place, label=value), hjust=1, vjust=1.4, size=3)
272
-print(p)
264
+p + geom_text(aes(color=place, label=place), hjust=1, vjust=-0.4, size=3) +
265
+  geom_text(aes(color=place, label=value), hjust=1, vjust=1.4, size=3)
273 266
 ```
274 267
 
275 268
 ## jplace file format
276 269
 
277
-In `ggtree`, we provide `write.jplace` function to store user's own data and associated newick tree to a single `jplace` file, which can be parsed directly in `ggtree` and user's data can be used to annotate the tree directly. For more detail, please refer to the [Tree Data Import](treeImport.html#jplace-file-format) vignette.
270
+`ggtree` provides `write.jplace()` function to store user's own data and associated newick tree to a single `jplace` file, which can be parsed directly in `ggtree` and user's data can be used to annotate the tree directly. For more detail, please refer to the [Tree Data Import](treeImport.html#jplace-file-format) vignette.
278 271
 
279 272
 
280 273
 # Advance tree annotation
281 274
 
282
-Advance tree annotation including visualizing tree with associated matrix, multiple sequence alignment, subplots and images (especially PhyloPic). For details and examples, please refer to the [Advance Tree Annotation](advanceTreeAnnotation.html) vignette.
275
+Advance tree annotation including visualizing phylogenetic tree with associated matrix and multiple sequence alignment; annotating tree with subplots and images (especially PhyloPic). For details and examples, please refer to the [Advance Tree Annotation](advanceTreeAnnotation.html) vignette.
283 276
 
284 277
 
285 278
 # References
... ...
@@ -33,7 +33,7 @@ library("ggtree")
33 33
 ```
34 34
 
35 35
 
36
-The `ggtree` package should not be viewed solely as a standalone software. While it is useful for viewing, annotating and manipulating phylogenetic trees, it is also an infrastructure that enables evolutionary evidences that inferred by commonly used software packages in the field to be used in `R`. For instance, *dN/dS* values or ancestral sequences inferred by [CODEML](http://abacus.gene.ucl.ac.uk/software/paml.html)[@yang_paml_2007], *clade support values (posterior)* inferred by [BEAST](http://beast2.org/)[@bouckaert_beast_2014] and short read placement by [EPA](http://sco.h-its.org/exelixis/web/software/epa/index.html)[@berger_EPA_2011] and [pplacer](http://matsen.fhcrc.org/pplacer/)[@matsen_pplacer_2010]. These evolutionary evidences are not only used in annotating phylogenetic tree in  `ggtree` but can also be further analyzed in `R`.
36
+The `ggtree` package should not be viewed solely as a standalone software. While it is useful for viewing, annotating and manipulating phylogenetic trees, it is also an infrastructure that enables evolutionary evidences that inferred by commonly used software packages in the field to be used in `R`. For instance, *dN/dS* values or ancestral sequences inferred by [CODEML](http://abacus.gene.ucl.ac.uk/software/paml.html)[@yang_paml_2007], clade support values (posterior) inferred by [BEAST](http://beast2.org/)[@bouckaert_beast_2014] and short read placement by [EPA](http://sco.h-its.org/exelixis/web/software/epa/index.html)[@berger_EPA_2011] and [pplacer](http://matsen.fhcrc.org/pplacer/)[@matsen_pplacer_2010]. These evolutionary evidences are not only used in annotating phylogenetic tree in  `ggtree` but can also be further analyzed in `R`.
37 37
 
38 38
 # Supported File Formats
39 39
 
... ...
@@ -66,14 +66,14 @@ The `ggtree` package implement several parser functions, including:
66 66
 + `read.codeml_mlc` for parsing `mlc` file (output of `CODEML`)
67 67
 + `read.hyphy` for parsing output of [HYPHY](http://hyphy.org/w/index.php/Main_Page)
68 68
 + `read.jplace` for parsing `jplace` file including output from [EPA](http://sco.h-its.org/exelixis/web/software/epa/index.html) and [pplacer](http://matsen.fhcrc.org/pplacer/)
69
-+ `read.nhx` for parsing `NHX` file including output from [PHYLODOG](http://pbil.univ-lyon1.fr/software/phyldog/) and RevBayes](http://revbayes.github.io/intro.html)
69
++ `read.nhx` for parsing `NHX` file including output from [PHYLODOG](http://pbil.univ-lyon1.fr/software/phyldog/) and [RevBayes](http://revbayes.github.io/intro.html)
70 70
 + `read.paml_rst` for parsing `rst` file (output of `BASEML` and `CODEML`)
71 71
 + `read.r8s` for parsing output of [r8s](loco.biosci.arizona.edu/r8s/)
72 72
 + `read.raxml` for parsing output of [RAxML](http://sco.h-its.org/exelixis/web/software/raxml/)
73 73
 
74 74
 # S4 classes
75 75
 
76
-Correspondingly, `ggtree` define several `S4` classes to store evolutionary evidences inferred by these software packages, including:
76
+Correspondingly, `ggtree` defines several `S4` classes to store evolutionary evidences inferred by these software packages, including:
77 77
 
78 78
 + _`apeBootstrap`_ for bootstrap analysis of `ape::boot.phylo()`[@paradis_ape_2004], output of `apeBoot()` defined in `ggtree`
79 79
 + _`beast`_ for storing output of `read.beast()`
... ...
@@ -82,7 +82,7 @@ Correspondingly, `ggtree` define several `S4` classes to store evolutionary evid
82 82
 + _`hyphy`_ for storing output of `read.hyphy()`
83 83
 + _`jplace`_ for storing output of `read.jplace()`
84 84
 + _`nhx`_ for storing output of `read.nhx()`
85
-+ _`paml_rst`_ for _`rst`_ file obtained by [PAML], including _`BASEML`_ and _`CODEML`_.
85
++ _`paml_rst`_ for _`rst`_ file obtained by [PAML](http://abacus.gene.ucl.ac.uk/software/paml.html), including _`BASEML`_ and _`CODEML`_.
86 86
 + _`phangorn`_ for storing ancestral sequences inferred by `R` package `phangorn`[@schliep_phangorn_2011], output of `phyPML()` defined in `ggtree`
87 87
 + _`r8s`_ for storing output of `read.r8s()`
88 88
 + _`raxml`_ for storing output of `read.raxml()`
... ...
@@ -95,7 +95,7 @@ Here is an overview of these `S4` classes:
95 95
 
96 96
 ![](figures/ggtree_objects.png)
97 97
 
98
-In addition, `ggtree` also supports _`phylo`_ (defined by `ape`[@paradis_ape_2004]) and _`phylo4`_ (defined by `phylobase`).
98
+In addition, `ggtree` also supports _`phylo`_, _`multiPhylo`_ (defined by `ape`[@paradis_ape_2004]) and _`phylo4`_ (defined by `phylobase`).
99 99
 
100 100
 
101 101
 In `ggtree`, tree objects can be merged and evidences inferred from different phylogenetic analyses can be combined or compared and visualized.
... ...
@@ -128,11 +128,11 @@ get.fields(beast)
128 128
 
129 129
 Users can use `ggtree(beast)` to visualize the tree and add layer to annotate it.
130 130
 
131
-```{r warning=FALSE}
131
+```{r warning=FALSE, fig.width=10, fig.height=10}
132 132
 ggtree(beast, ndigits=2, branch.length = 'none') + geom_text(aes(x=branch, label=length_0.95_HPD), vjust=-.5, color='firebrick')
133 133
 ```
134 134
 
135
-With `ggtree`, evolutionary evidences inferred by commonly used software packages (`BEAST` in this example) can be easily obtained in a tidy `data.frame` by `fortify` method.
135
+With `ggtree`, evolutionary evidences inferred by commonly used software packages (`BEAST` in this example) can be easily transformed to a tidy `data.frame` by `fortify` method.
136 136
 
137 137
 ```{r}
138 138
 beast_data <- fortify(beast)
... ...
@@ -145,7 +145,7 @@ head(beast_data)
145 145
 
146 146
 The _`read.paml_rst`_ function can parse `rst` file from `BASEML` and `CODEML`. The only difference is the space in the sequences. For `BASEML`, each ten bases are separated by one space, while for `CODEML`, each three bases (triplet) are separated by one space.
147 147
 
148
-```{r fig.width=8, width=60, warning=FALSE, fig.align="center"}
148
+```{r fig.width=12, fig.height=10, warning=FALSE, fig.align="center"}
149 149
 brstfile <- system.file("extdata/PAML_Baseml", "rst", package="ggtree")
150 150
 brst <- read.paml_rst(brstfile)
151 151
 brst
... ...
@@ -163,9 +163,9 @@ crst
163 163
 ```
164 164
 
165 165
 
166
-In `ggtree`, we define the `update` operator, `%<%`, that can update a tree view (applying the same pattern of visualization and annotation) with another tree object.
166
+`ggtree` defines the `update` operator, `%<%`, that can update a tree view (applying the same pattern of visualization and annotation) with another tree object.
167 167
 
168
-```{r fig.width=8, width=60, warning=FALSE, fig.align="center"}
168
+```{r fig.width=12, fig.height=10, warning=FALSE, fig.align="center"}
169 169
 p %<% crst
170 170
 ```
171 171
 
... ...
@@ -189,7 +189,7 @@ Please aware that _`/`_ and _`*`_ are not valid characters in _`names`_, they we
189 189
 So _`dN_vs_dS`_ is _`dN/dS`_, _`N_x_dN`_ is _`N*dN`_, and _`S_x_dS`_ is _`S*dS`_.
190 190
 
191 191
 
192
-```{r fig.width=8, width=60, warning=FALSE, fig.align="center"}
192
+```{r fig.width=8, fig.height=8, warning=FALSE, fig.align="center"}
193 193
 ggtree(mlc) + geom_text(aes(x=branch, label=dN_vs_dS), color='blue', vjust=-.2)
194 194
 ```
195 195
 
... ...
@@ -207,9 +207,7 @@ ggtree(mlc, branch.length = "dN_vs_dS", aes(color=dN_vs_dS)) +
207 207
     theme_tree2(legend.position=c(.9, .5))
208 208
 ```
209 209
 
210
-We can also plot the _`dN`_ or _`dS`_ tree and others. 
211
-
212
-#### rst and mlc files
210
+We can also plot the _`dN`_ or _`dS`_ tree and others. More examples (including evidences inferred by BEAST) can be found in the [Tree Annotation](treeAnnotation.html) vignette.  
213 211
 
214 212
 
215 213
 #### _`CODEML`_ output: rst and mlc files\
... ...
@@ -239,7 +237,7 @@ hy <- read.hyphy(nwk, ancseq, tipfas)
239 237
 hy
240 238
 ```
241 239
 
242
-```{r fig.width=12, fig.height=10, width=60, warning=FALSE, fig.align="center"}
240
+```{r fig.width=14, fig.height=10, warning=FALSE, fig.align="center"}
243 241
 ggtree(hy) + geom_text(aes(x=branch, label=AA_subs), vjust=-.5)
244 242
 ```
245 243
 
... ...
@@ -248,7 +246,7 @@ ggtree(hy) + geom_text(aes(x=branch, label=AA_subs), vjust=-.5)
248 246
 [r8s](http://loco.biosci.arizona.edu/r8s/) output contains 3 trees, namely `TREE`, `RATO` and `PHYLO` for time tree, rate tree and absolute substitution tree respectively.
249 247
 
250 248
 
251
-```{r fig.width=4, fig.height=6, width=60, warning=FALSE, fig.align="center")
249
+```{r fig.width=4, fig.height=6, width=60, warning=FALSE, fig.align="center"}
252 250
 r8s <- read.r8s(system.file("extdata/r8s", "H3_r8s_output.log", package="ggtree"))
253 251
 ggtree(r8s, branch.length="TREE", mrsd="2014-01-01") + theme_tree2()
254 252
 ```
... ...
@@ -259,7 +257,7 @@ ggtree(r8s, branch.length="TREE", mrsd="2014-01-01") + theme_tree2()
259 257
 User can also view 3 trees simultaneously.
260 258
 
261 259
 
262
-```{r fig.width=16, fig.height=10, width=60, warning=FALSE, fig.align="center")
260
+```{r fig.width=16, fig.height=10, width=60, warning=FALSE, fig.align="center"}
263 261
 ggtree(get.tree(r8s), aes(color=.id)) + facet_wrap(~.id, scales="free_x")
264 262
 ```
265 263
 
... ...
@@ -289,7 +287,7 @@ ggtree(nhx) + geom_tiplab() + geom_point(aes(color=S), size=5, alpha=.5) +
289 287
 
290 288
 ## Parsing EPA and pplacer output
291 289
 
292
-[EPA](http://sco.h-its.org/exelixis/web/software/epa/index.html)[@berger_EPA_2011] and [PPLACER](http://matsen.fhcrc.org/pplacer/)[@matsen_pplacer_2010] have common output file format, `jplace`. 
290
+[EPA](http://sco.h-its.org/exelixis/web/software/epa/index.html)[@berger_EPA_2011] and [PPLACER](http://matsen.fhcrc.org/pplacer/)[@matsen_pplacer_2010] have common output file format, `jplace`, which can be parse by `read.jplace()` function. 
293 291
 
294 292
 ```{r}
295 293
 jpf <- system.file("extdata/sample.jplace",  package="ggtree")
... ...
@@ -340,13 +338,13 @@ merged_tree
340 338
 head(fortify(merged_tree))
341 339
 ```
342 340
 
343
-After merging, all evidences inferred from different tools can be used to annotate the tree simultaneously. In this example, we used 'dN/dS' inferred by CodeML to color the tree and annotate the tree with 'posterior' inferred by BEAST.
341
+After merging, all evidences inferred from different tools can be used to annotate the tree simultaneously. In this example, we used `dN/dS` inferred by CodeML to color the tree and annotate the tree with `posterior` inferred by BEAST.
344 342
 
345 343
 ```{r fig.width=20, fig.height=26, warning=FALSE}
346
-ggtree(merged_tree, aes(color=dN), mrsd="2013-01-01", ndigits = 3) +
344
+ggtree(merged_tree, aes(color=dN_vs_dS), mrsd="2013-01-01", ndigits = 3) +
347 345
     geom_text(aes(label=posterior), vjust=.1, hjust=-.1, size=5, color="black") + 
348 346
     scale_color_continuous(name='dN/dS', limits=c(0, 1.5),
349
-                           oob=scales::squish, low="darkgreen", high="red")+
347
+                           oob=scales::squish, low="green", high="red")+
350 348
     theme_tree2(legend.position="right")
351 349
 ```	
352 350
 
... ...
@@ -370,13 +368,13 @@ outfile <- tempfile()
370 368
 write.jplace(tree, data, outfile)
371 369
 ```
372 370
 
373
-Then _`read.jplace`_ function was designed to read the _`jplace`_ file and store the information to a _`jplace`_ object.
371
+The _`read.jplace`_ function was designed to read the _`jplace`_ file and store the information to a _`jplace`_ object.
374 372
 ```{r}
375 373
 jp <- read.jplace(outfile)
376 374
 print(jp)
377 375
 ```
378 376
 
379
-Now we know the _`jp`_ object stored the tree and the associated amino acid substitution and GC content information, we can view the tree and display the associated annotation data on it directly by _`ggtree`_.
377
+Now we know the _`jp`_ object that stores the tree and the associated amino acid substitution and GC content information, we can view the tree and display the associated annotation data on it directly by _`ggtree`_.
380 378
 
381 379
 ```{r fig.width=12, fig.height=12, warning=FALSE, fig.align="center"}
382 380
 ggtree(jp) + 
... ...
@@ -37,7 +37,7 @@ expand <- ggtree::expand
37 37
 
38 38
 # Internal node number
39 39
 
40
-Some of the functions works with clade and accepts a parameter of internal node number. To get the internal node number, user can use `geom_text2` to display it:
40
+Some of the functions in `ggtree` works with clade and accepts a parameter of internal node number. To get the internal node number, user can use `geom_text2` to display it:
41 41
 
42 42
 ```{r}
43 43
 nwk <- system.file("extdata", "sample.nwk", package="ggtree")
... ...
@@ -56,7 +56,7 @@ p <- ggtree(tree)
56 56
 MRCA(p, tip=c('A', 'E'))
57 57
 ```
58 58
 
59
-# groupClade
59
+# group Clades
60 60
 
61 61
 The `ggtree` package defined several functions to manipulate tree view. _`groupClade`_ and _`groupOTU`_ methods for clustering clades or related OTUs. _`groupClade`_ accepts an internal node or a vector of internal nodes to cluster clade/clades.
62 62
 
... ...
@@ -78,7 +78,7 @@ With `groupClade` and `groupOTU`, it's easy to highlight selected taxa and easy
78 78
 
79 79
 ```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
80 80
 tree <- groupClade(tree, node=c(21, 17))
81
-ggtree(tree, aes(color=group, linetype=group)) + geom_text2(aes(subset=(group==2), label=label), hjust=-.5)
81
+ggtree(tree, aes(color=group, linetype=group)) + geom_tiplab(aes(subset=(group==2)))
82 82
 ```
83 83
 
84 84
 
... ...
@@ -104,16 +104,20 @@ cls <- list(c1=c("A", "B", "C", "D", "E"),
104 104
 
105 105
 tree <- groupOTU(tree, cls)
106 106
 library("colorspace")
107
-ggtree(tree, aes(color=group, linetype=group)) + geom_text(aes(label=label),  hjust=-.25) +
107
+ggtree(tree, aes(color=group, linetype=group)) + geom_tiplab() +
108 108
      scale_color_manual(values=c("black", rainbow_hcl(4))) + theme(legend.position="right")
109 109
 ```
110 110
 
111 111
 
112
+_`groupOTU`_ also work with graphic object.
113
+
112 114
 ```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
113 115
 p <- ggtree(tree)
114 116
 groupOTU(p, LETTERS[1:5]) + aes(color=group) + geom_tiplab() + scale_color_manual(values=c("black", "firebrick"))
115 117
 ```
116 118
 
119
+The following example use `groupOTU` to display taxa classification.
120
+
117 121
 ```{r fig.width=14, fig.height=14}
118 122
 library("ape")
119 123
 data(chiroptera)
... ...
@@ -179,7 +183,7 @@ grid.arrange(p1, p2, p3, p4, p5, ncol=5)
179 183
 # scale clade
180 184
 
181 185
 
182
-We have illustrated how to collapse selected clades. Another approach is to zoom out clade to a small scale.
186
+Collpase selected clades can save some space, another approach is to zoom out clade to a small scale.
183 187
 
184 188
 ```{r fig.width=12, fig.height=6, warning=F}
185 189
 grid.arrange(ggtree(tree) + geom_hilight(21, "steelblue"),
... ...
@@ -48,7 +48,7 @@ It implements _`geom_tree`_ layer for displaying phylogenetic trees, as shown be
48 48
 
49 49
 
50 50
 ```{r fig.width=3, fig.height=3, fig.align="center"}
51
-ggplot(tree, aes(x, y)) + geom_tree() + theme_tree() + xlab(NULL) + ylab(NULL)
51
+ggplot(tree, aes(x, y)) + geom_tree() + theme_tree()
52 52
 ```
53 53
 
54 54
 The function, _`ggtree`_, was implemented as a short cut to visualize a tree, and it works exactly the same as shown above.
... ...
@@ -58,12 +58,12 @@ _`ggtree`_ takes all the advantages of _`ggplot2`_. For example, we can change t
58 58
 ggtree(tree, color="firebrick", size=1, linetype="dotted")
59 59
 ```
60 60
 
61
-By default, the tree is viewing in ladderize form, user can set the parameter _`ladderize = FALSE`_ to disable it.
61
+By default, the tree is viewed in ladderize form, user can set the parameter _`ladderize = FALSE`_ to disable it.
62 62
 ```{r fig.width=3, fig.height=3, fig.align="center"}
63 63
 ggtree(tree, ladderize=FALSE)
64 64
 ```
65 65
 
66
-The _`branch.length`_ is used to scale the edge, user can set the parameter _`branch.length = "none"`_ to only viewing the tree topology (cladogram) or other numerical variable to scale the tree (e.g. _dN/dS_).
66
+The _`branch.length`_ is used to scale the edge, user can set the parameter _`branch.length = "none"`_ to only view the tree topology (cladogram) or other numerical variable to scale the tree (e.g. _dN/dS_, see also in [Tree Annotation](treeAnnotation.html) vignette).
67 67
 
68 68
 ```{r fig.width=3, fig.height=3, fig.align="center"}
69 69
 ggtree(tree, branch.length="none")
... ...
@@ -71,14 +71,14 @@ ggtree(tree, branch.length="none")
71 71
 
72 72
 # Layout
73 73
 
74
-Currently, _`ggtree`_ supports several layout, including:
74
+Currently, _`ggtree`_ supports several layouts, including:
75 75
 
76 76
 + `rectangular` (by default)
77 77
 + `slanted`
78 78
 + `fan` or `circular`
79 79
 
80
-for `Phylogram` (by default).
81
-`Cladogram` if user explicitly setting `branch.length='none'` and `unrooted` layout are also supported. 
80
+for `Phylogram` (by default) and `Cladogram` if user explicitly setting `branch.length='none'`.
81
+`ggtree` also supports `unrooted` layout.
82 82
 
83 83
 
84 84
 ## Phylogram
... ...
@@ -133,14 +133,14 @@ ggtree(tree, layout="unrooted") + ggtitle("unrooted layout")
133 133
 
134 134
 A phylogenetic tree can be scaled by time (time-scaled tree) by specifying the parameter, `mrsd` (most recent sampling date).
135 135
 
136
-```{r fig.width=9, fig.height=4, fig.align="center"}
136
+```{r fig.width=9, fig.height=9, fig.align="center"}
137 137
 tree2d <- read.beast(system.file("extdata", "twoD.tree", package="ggtree"))
138 138
 ggtree(tree2d, mrsd = "2014-05-01") + theme_tree2()
139 139
 ```
140 140
 
141 141
 ## Two dimensional tree
142 142
 
143
-`ggtree` implemented 2 dimensional tree. It accepts parameter _`yscale`_ to scale the y-axis based on the selected tree attribute. The attribute should be numerical variable. If it is *character*/*category* variable, user should provides a name vector of mapping the variable to numeric by passing it to parameter _`yscale_mapping`_.
143
+`ggtree` implemented two dimensional tree. It accepts parameter _`yscale`_ to scale the y-axis based on the selected tree attribute. The attribute should be numerical variable. If it is *character*/*category* variable, user should provides a name vector of mapping the variable to numeric by passing it to parameter _`yscale_mapping`_.
144 144
 
145 145
 
146 146
 ```{r fig.width=9, fig.height=4, fig.align="center"}
... ...
@@ -188,9 +188,12 @@ We can also use `theme_tree2()` to display the tree scale by adding `x axis`.
188 188
 ggtree(tree) + theme_tree2()
189 189
 ```
190 190
 
191
+Tree scale is not restricted to evolution distance, `ggtree` can re-scale the tree with other numerical variable. More details can be found in the [Tree Annotation](treeAnnotation.html) vignette.
192
+
193
+
191 194
 # Displaying nodes/tips
192 195
 
193
-Show all the internal nodes and tips in the tree can be done by adding a layer of points using _`geom_nodepoint`_,  _`geom_tippoint`_ or _`geom_point`_.
196
+Showing all the internal nodes and tips in the tree can be done by adding a layer of points using _`geom_nodepoint`_,  _`geom_tippoint`_ or _`geom_point`_.
194 197
 
195 198
 ```{r fig.width=3, fig.height=3, fig.align="center"}
196 199
 ggtree(tree)+geom_point(aes(shape=isTip, color=isTip), size=3)
... ...
@@ -223,9 +226,9 @@ p + geom_tiplab(aes(x=branch), size=3, color="purple", vjust=-0.3)
223 226
 
224 227
 Based on the middle of branch is very useful when annotating transition from parent node to child node.
225 228
 
226
-# update tree viewing with a new tree
229
+# update tree view with a new tree
227 230
 
228
-In previous example, we have a _`p`_ object that stored the tree viewing of 13 tips and internal nodes highlighted with specific colored big dots. If users want to applied this pattern (we can imaging a more complex one) to a new tree, you don't need to build the tree step by step. `ggtree` provides an operator, _`%<%`_, for applying the visualization pattern to a new tree.
231
+In previous example, we have a _`p`_ object that stored the tree viewing of 13 tips and internal nodes highlighted with specific colored big dots. If users want to apply this pattern (we can imaging a more complex one) to a new tree, you don't need to build the tree step by step. `ggtree` provides an operator, _`%<%`_, for applying the visualization pattern to a new tree.
229 232
 
230 233
 For example, the pattern in the _`p`_ object will be applied to a new tree with 50 tips as shown below:
231 234
 ```{r fig.width=3, fig.height=3, fig.align="center"}
... ...
@@ -236,7 +239,7 @@ Another example can be found in the [Tree Data Import](treeImport.html#rst-file)
236 239
 
237 240
 # theme
238 241
 
239
-`theme_tree()` defined a totally blank canvas, while _`theme_tree2()`_ add phylogenetic distance (via x-axis). These two themes all accept a parameter of _`bgcolor`_ that defined the background color.
242
+`theme_tree()` defined a totally blank canvas, while _`theme_tree2()`_ adds phylogenetic distance (via x-axis). These two themes all accept a parameter of _`bgcolor`_ that defined the background color.
240 243
 
241 244
 ```{r fig.width=6, fig.height=3, fig.align="center"}
242 245
 grid.arrange(