Browse code

update vignettes

guangchuang yu authored on 03/01/2018 09:55:53
Showing 1 changed files
1 1
deleted file mode 100644
... ...
@@ -1,196 +0,0 @@
1
-title: "Advance Tree Annotation"
2
-author: "Guangchuang Yu and Tommy Tsan-Yuk Lam\\
3
-
4
-        School of Public Health, The University of Hong Kong"
5
-date: "`r Sys.Date()`"
6
-bibliography: ggtree.bib
7
-biblio-style: apalike
8
-output:
9
-  prettydoc::html_pretty:
10
-    toc: true
11
-    theme: cayman
12
-    highlight: github
13
-  pdf_document:
14
-    toc: true
15
-vignette: >
16
-  %\VignetteIndexEntry{05 Advance Tree Annotation}
17
-  %\VignetteEngine{knitr::rmarkdown}
18
-  %\usepackage[utf8]{inputenc}
19
-
20
-```{r style, echo=FALSE, results="asis", message=FALSE}
21
-knitr::opts_chunk$set(tidy = FALSE,
22
-		   message = FALSE)
23
-```
24
-
25
-
26
-```{r echo=FALSE, results="hide", message=FALSE}
27
-library("ape")
28
-library("treeio")
29
-library("ggplot2")
30
-library("ggtree")
31
-```
32
-
33
-
34
-# Visualize tree with associated matrix
35
-
36
-<!--
37
-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.
38
-
39
-The `gheatmap` function is designed to visualize phylogenetic tree with heatmap of associated matrix.
40
-
41
-In the following example, we visualized a tree of H3 influenza viruses with their associated genotype.
42
-
43
-```{r fig.width=8, fig.height=6, fig.align="center", warning=FALSE, message=FALSE}
44
-beast_file <- system.file("examples/MCC_FluA_H3.tree", package="ggtree")
45
-beast_tree <- read.beast(beast_file)
46
-
47
-genotype_file <- system.file("examples/Genotype.txt", package="ggtree")
48
-genotype <- read.table(genotype_file, sep="\t", stringsAsFactor=F)
49
-colnames(genotype) <- sub("\\.$", "", colnames(genotype))
50
-p <- ggtree(beast_tree, mrsd="2013-01-01") + geom_treescale(x=2008, y=1, offset=2)
51
-p <- p + geom_tiplab(size=2)
52
-gheatmap(p, genotype, offset = 5, width=0.5, font.size=3, colnames_angle=-45, hjust=0) +
53
-    scale_fill_manual(breaks=c("HuH3N2", "pdm", "trig"), values=c("steelblue", "firebrick", "darkgreen"))
54
-```
55
-
56
-The _width_ parameter is to control the width of the heatmap. It supports another parameter _offset_ for controlling the distance between the tree and the heatmap, for instance to allocate space for tip labels.
57
-
58
-
59
-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.
60
-
61
-<!-- User can also use `gplot` and tweak the positions of two plot to align properly. -->
62
-
63
-
64
-
65
-```{r fig.width=8, fig.height=6, fig.align="center", warning=FALSE}
66
-p <- ggtree(beast_tree, mrsd="2013-01-01") + geom_tiplab(size=2, align=TRUE, linesize=.5) + theme_tree2()
67
-pp <- (p + scale_y_continuous(expand=c(0, 0.3))) %>%
68
-    gheatmap(genotype, offset=8, width=0.6, colnames=FALSE) %>%
69
-        scale_x_ggtree()
70
-pp + theme(legend.position="right")
71
-```
72
-
73
-
74
-# Visualize tree with multiple sequence alignment
75
-
76
-With `msaplot` function, user can visualize multiple sequence alignment with phylogenetic tree, as demonstrated below:
77
-```{r fig.width=8, fig.height=6, fig.align='center', warning=FALSE}
78
-fasta <- system.file("examples/FluA_H3_AA.fas", package="ggtree")
79
-msaplot(ggtree(beast_tree), fasta)
80
-```
81
-
82
-A specific slice of the alignment can also be displayed by specific _window_ parameter.
83
-
84
-```{r fig.width=7, fig.height=7, fig.align='center', warning=FALSE}
85
-msaplot(ggtree(beast_tree), fasta, window=c(150, 200)) + coord_polar(theta='y')
86
-```
87
-
88
-# Annotate a phylogenetic tree with insets
89
-
90
-`ggtree` provides a function, `inset`, for adding subplots to a phylogenetic tree. The input is a tree graphic object and a named list of ggplot graphic objects (can be any kind of charts), these objects should named by node numbers. To facilitate adding bar and pie charts (e.g. summarized stats of results from ancestral reconstruction) to phylogenetic tree, *ggtree* provides `nodepie` and `nodebar` functions to create a list of pie or bar charts.
91
-
92
-## Annotate with bar charts
93
-
94
-```{r}
95
-set.seed(2015-12-31)
96
-tr <- rtree(15)
97
-p <- ggtree(tr)
98
-
99
-a <- runif(14, 0, 0.33)
100
-b <- runif(14, 0, 0.33)
101
-c <- runif(14, 0, 0.33)
102
-d <- 1 - a - b - c
103
-dat <- data.frame(a=a, b=b, c=c, d=d)
104
-## input data should have a column of `node` that store the node number
105
-dat$node <- 15+1:14
106
-
107
-## cols parameter indicate which columns store stats (a, b, c and d in this example)
108
-bars <- nodebar(dat, cols=1:4)
109
-
110
-inset(p, bars)
111
-```
112
-
113
-The sizes of the insets can be ajusted by the paramter *width* and *height*.
114
-
115
-```{r}
116
-inset(p, bars, width=.06, height=.1)
117
-```
118
-
119
-Users can set the color via the parameter *color*. The *x* position can be one of 'node' or 'branch' and can be adjusted by the parameter *hjust* and *vjust* for horizontal and vertical adjustment respecitvely.
120
-
121
-
122
-```{r}
123
-bars2 <- nodebar(dat, cols=1:4, position='dodge',
124
-                 color=c(a='blue', b='red', c='green', d='cyan'))
125
-p2 <- inset(p, bars2, x='branch', width=.06, vjust=-.3)
126
-print(p2)
127
-```
128
-
129
-## Annotate with pie charts
130
-
131
-Similarly, users can use `nodepie` function to generate a list of pie charts and place these charts to annotate corresponding nodes. Both `nodebar` and `nodepie` accepts parameter *alpha* to allow transparency.
132
-
133
-```{r}
134
-pies <- nodepie(dat, cols=1:4, alpha=.6)
135
-inset(p, pies)
136
-```
137
-
138
-
139
-```{r}
140
-inset(p, pies, hjust=-.06)
141
-```
142
-
143
-## Annotate with other types of charts
144
-
145
-The `inset` function accepts a list of ggplot graphic objects and these input objects are not restricted to pie or bar charts. They can be any kinds of charts and hybrid of these charts.
146
-
147
-```{r}
148
-pies_and_bars <- bars2
149
-pies_and_bars[9:14] <- pies[9:14]
150
-inset(p, pies_and_bars)
151
-```
152
-
153
-```{r}
154
-d <- lapply(1:15, rnorm, n=100)
155
-ylim <- range(unlist(d))
156
-bx <- lapply(d, function(y) {
157
-    dd <- data.frame(y=y)
158
-    ggplot(dd, aes(x=1, y=y))+geom_boxplot() + ylim(ylim) + theme_inset()
159
-})
160
-names(bx) <- 1:15
161
-inset(p, bx, width=.06, height=.2, hjust=-.05)
162
-```
163
-
164
-
165
-After annotating with insets, users can further annotate the tree with another layer of insets.
166
-
167
-```{r fig.width=10, fig.height=7}
168
-p2 <- inset(p, bars2, x='branch', width=.06, vjust=-.4)
169
-p2 <- inset(p2, pies, x='branch', vjust=.4)
170
-bx2 <- lapply(bx, function(g) g+coord_flip())
171
-inset(p2, bx2, width=.4, height=.06, vjust=.04, hjust=p2$data$x[1:15]-4) + xlim(NA, 4.5)
172
-```
173
-
174
-# Plot tree with associated data
175
-
176
-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.
177
-
178
-```{r warning=F, fig.width=10, fig.height=6}
179
-tr <- rtree(30)
180
-
181
-d1 <- data.frame(id=tr$tip.label, val=rnorm(30, sd=3))
182
-p <- ggtree(tr)
183
-
184
-p2 <- facet_plot(p, panel="dot", data=d1, geom=geom_point, aes(x=val), color='firebrick')
185
-d2 <- data.frame(id=tr$tip.label, value = abs(rnorm(30, mean=100, sd=50)))
186
-
187
-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()
188
-```
189
-
190
-
191
-
192
-
193
-
Browse code

unrooted layout

guangchuang yu authored on 21/12/2017 12:07:05
Showing 1 changed files
... ...
@@ -5,7 +5,7 @@ author: "Guangchuang Yu and Tommy Tsan-Yuk Lam\\
5 5
         School of Public Health, The University of Hong Kong"
6 6
 date: "`r Sys.Date()`"
7 7
 bibliography: ggtree.bib
8
-csl: nature.csl
8
+biblio-style: apalike
9 9
 output:
10 10
   prettydoc::html_pretty:
11 11
     toc: true
Browse code

update msaplot to use DNAbin/AAbin

guangchuang yu authored on 14/12/2017 10:29:44
Showing 1 changed files
... ...
@@ -16,7 +16,6 @@ output:
16 16
 vignette: >
17 17
   %\VignetteIndexEntry{05 Advance Tree Annotation}
18 18
   %\VignetteEngine{knitr::rmarkdown}
19
-  %\VignetteDepends{Biostrings}
20 19
   %\usepackage[utf8]{inputenc}
21 20
 ---
22 21
 
... ...
@@ -28,7 +27,6 @@ knitr::opts_chunk$set(tidy = FALSE,
28 27
 
29 28
 ```{r echo=FALSE, results="hide", message=FALSE}
30 29
 library("ape")
31
-library("Biostrings")
32 30
 library("treeio")
33 31
 library("ggplot2")
34 32
 library("ggtree")
Browse code

clean up code

guangchuang yu authored on 14/12/2017 08:47:21
Showing 1 changed files
... ...
@@ -29,6 +29,7 @@ knitr::opts_chunk$set(tidy = FALSE,
29 29
 ```{r echo=FALSE, results="hide", message=FALSE}
30 30
 library("ape")
31 31
 library("Biostrings")
32
+library("treeio")
32 33
 library("ggplot2")
33 34
 library("ggtree")
34 35
 ```
Browse code

ggtree with image files

guangchuang yu authored on 04/12/2017 11:45:07
Showing 1 changed files
... ...
@@ -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
-![](figures/inset_img.png)
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
-![](figures/phylopic1.png)
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
-![](figures/phylopic2.png)
222 194
 
223 195
 
224 196
 
Browse code

update docs

GuangchuangYu authored on 11/12/2016 16:17:02
Showing 1 changed files
... ...
@@ -1,8 +1,6 @@
1 1
 ---
2 2
 title: "Advance Tree Annotation"
3
-author: "\\
4
-
5
-	Guangchuang Yu (<guangchuangyu@gmail.com>) and Tommy Tsan-Yuk Lam (<ttylam@hku.hk>)\\
3
+author: "Guangchuang Yu and Tommy Tsan-Yuk Lam\\
6 4
 
7 5
         School of Public Health, The University of Hong Kong"
8 6
 date: "`r Sys.Date()`"
... ...
@@ -80,14 +78,14 @@ pp + theme(legend.position="right")
80 78
 # Visualize tree with multiple sequence alignment
81 79
 
82 80
 With `msaplot` function, user can visualize multiple sequence alignment with phylogenetic tree, as demonstrated below:
83
-```{r fig.width=8, fig.height=12, fig.align='center'}
81
+```{r fig.width=8, fig.height=6, fig.align='center', warning=FALSE}
84 82
 fasta <- system.file("examples/FluA_H3_AA.fas", package="ggtree")
85 83
 msaplot(ggtree(beast_tree), fasta)
86 84
 ```
87 85
 
88 86
 A specific slice of the alignment can also be displayed by specific _window_ parameter.
89 87
 
90
-```{r fig.width=16, fig.height=16, fig.align='center'}
88
+```{r fig.width=7, fig.height=7, fig.align='center', warning=FALSE}
91 89
 msaplot(ggtree(beast_tree), fasta, window=c(150, 200)) + coord_polar(theta='y')
92 90
 ```
93 91
 
... ...
@@ -171,7 +169,7 @@ inset(p, bx, width=.06, height=.2, hjust=-.05)
171 169
 After annotating with insets, users can further annotate the tree with another layer of insets.
172 170
 
173 171
 ```{r fig.width=10, fig.height=7}
174
-p2 <- inset(p, bars2, x='branch', width=.03, vjust=-.4)
172
+p2 <- inset(p, bars2, x='branch', width=.06, vjust=-.4)
175 173
 p2 <- inset(p2, pies, x='branch', vjust=.4)
176 174
 bx2 <- lapply(bx, function(g) g+coord_flip())
177 175
 inset(p2, bx2, width=.4, height=.06, vjust=.04, hjust=p2$data$x[1:15]-4) + xlim(NA, 4.5)
Browse code

prettydoc

guangchuang yu authored on 09/12/2016 08:46:05
Showing 1 changed files
... ...
@@ -8,9 +8,11 @@ author: "\\
8 8
 date: "`r Sys.Date()`"
9 9
 bibliography: ggtree.bib
10 10
 csl: nature.csl
11
-output: 
12
-  html_document:
11
+output:
12
+  prettydoc::html_pretty:
13 13
     toc: true
14
+    theme: cayman
15
+    highlight: github
14 16
   pdf_document:
15 17
     toc: true
16 18
 vignette: >
... ...
@@ -44,38 +46,43 @@ The `gheatmap` function is designed to visualize phylogenetic tree with heatmap
44 46
 
45 47
 In the following example, we visualized a tree of H3 influenza viruses with their associated genotype.
46 48
 
47
-```{r fig.width=20, fig.height=16, fig.align="center"}
49
+```{r fig.width=8, fig.height=6, fig.align="center", warning=FALSE, message=FALSE}
48 50
 beast_file <- system.file("examples/MCC_FluA_H3.tree", package="ggtree")
49 51
 beast_tree <- read.beast(beast_file)
50 52
 
51 53
 genotype_file <- system.file("examples/Genotype.txt", package="ggtree")
52 54
 genotype <- read.table(genotype_file, sep="\t", stringsAsFactor=F)
53
-p <- ggtree(beast_tree, mrsd="2013-01-01") + geom_treescale(x=2008, y=1)
54
-p <- p + geom_tiplab(size=3)
55
-gheatmap(p, genotype, offset = 2, width=0.5)
55
+colnames(genotype) <- sub("\\.$", "", colnames(genotype))
56
+p <- ggtree(beast_tree, mrsd="2013-01-01") + geom_treescale(x=2008, y=1, offset=2)
57
+p <- p + geom_tiplab(size=2)
58
+gheatmap(p, genotype, offset = 5, width=0.5, font.size=3, colnames_angle=-45, hjust=0) +
59
+    scale_fill_manual(breaks=c("HuH3N2", "pdm", "trig"), values=c("steelblue", "firebrick", "darkgreen"))
56 60
 ```
57 61
 
58 62
 The _width_ parameter is to control the width of the heatmap. It supports another parameter _offset_ for controlling the distance between the tree and the heatmap, for instance to allocate space for tip labels.
59 63
 
60 64
 
61
-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. 
65
+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.
62 66
 
63 67
 <!-- User can also use `gplot` and tweak the positions of two plot to align properly. -->
64 68
 
65
-```{r fig.width=20, fig.height=16, fig.align="center", warning=FALSE}
66
-p <- ggtree(beast_tree, mrsd="2013-01-01") + geom_tiplab(size=3, align=TRUE) + theme_tree2()
69
+
70
+
71
+```{r fig.width=8, fig.height=6, fig.align="center", warning=FALSE}
72
+p <- ggtree(beast_tree, mrsd="2013-01-01") + geom_tiplab(size=2, align=TRUE, linesize=.5) + theme_tree2()
67 73
 pp <- (p + scale_y_continuous(expand=c(0, 0.3))) %>%
68
-    gheatmap(genotype, offset=4, width=0.5, colnames=FALSE) %>%
74
+    gheatmap(genotype, offset=8, width=0.6, colnames=FALSE) %>%
69 75
         scale_x_ggtree()
70 76
 pp + theme(legend.position="right")
71 77
 ```
72 78
 
79
+
73 80
 # Visualize tree with multiple sequence alignment
74 81
 
75 82
 With `msaplot` function, user can visualize multiple sequence alignment with phylogenetic tree, as demonstrated below:
76 83
 ```{r fig.width=8, fig.height=12, fig.align='center'}
77 84
 fasta <- system.file("examples/FluA_H3_AA.fas", package="ggtree")
78
-msaplot(ggtree(beast_tree), fasta) 
85
+msaplot(ggtree(beast_tree), fasta)
79 86
 ```
80 87
 
81 88
 A specific slice of the alignment can also be displayed by specific _window_ parameter.
guangchuang yu authored on 24/10/2016 06:54:55
Showing 1 changed files
... ...
@@ -184,7 +184,7 @@ inset(p, img)
184 184
 
185 185
 # Plot tree with associated data
186 186
 
187
-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.
187
+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.
188 188
 
189 189
 ```{r warning=F, fig.width=10, fig.height=6}
190 190
 tr <- rtree(30)
Browse code

version 1.5.15

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

g.yu authored on 07/10/2016 05:18:29
Showing 1 changed files
... ...
@@ -112,7 +112,7 @@ inset(p, bars)
112 112
 The sizes of the insets can be ajusted by the paramter *width* and *height*.
113 113
 
114 114
 ```{r}
115
-inset(p, bars, width=.03, height=.06)
115
+inset(p, bars, width=.06, height=.1)
116 116
 ```
117 117
 
118 118
 Users can set the color via the parameter *color*. The *x* position can be one of 'node' or 'branch' and can be adjusted by the parameter *hjust* and *vjust* for horizontal and vertical adjustment respecitvely.
... ...
@@ -121,7 +121,7 @@ Users can set the color via the parameter *color*. The *x* position can be one o
121 121
 ```{r}
122 122
 bars2 <- nodebar(dat, cols=1:4, position='dodge',
123 123
                  color=c(a='blue', b='red', c='green', d='cyan'))
124
-p2 <- inset(p, bars2, x='branch', width=.03, vjust=-.3)
124
+p2 <- inset(p, bars2, x='branch', width=.06, vjust=-.3)
125 125
 print(p2)
126 126
 ```
127 127
 
... ...
@@ -157,7 +157,7 @@ bx <- lapply(d, function(y) {
157 157
     ggplot(dd, aes(x=1, y=y))+geom_boxplot() + ylim(ylim) + theme_inset()
158 158
 })
159 159
 names(bx) <- 1:15
160
-inset(p, bx, width=.03, height=.1, hjust=-.05)
160
+inset(p, bx, width=.06, height=.2, hjust=-.05)
161 161
 ```
162 162
 
163 163
 
... ...
@@ -167,7 +167,7 @@ After annotating with insets, users can further annotate the tree with another l
167 167
 p2 <- inset(p, bars2, x='branch', width=.03, vjust=-.4)
168 168
 p2 <- inset(p2, pies, x='branch', vjust=.4)
169 169
 bx2 <- lapply(bx, function(g) g+coord_flip())
170
-inset(p2, bx2, width=.2, height=.03, vjust=.04, hjust=p2$data$x[1:15]-4) + xlim(NA, 4.5)
170
+inset(p2, bx2, width=.4, height=.06, vjust=.04, hjust=p2$data$x[1:15]-4) + xlim(NA, 4.5)
171 171
 ```
172 172
 
173 173
 ## Annotate with image files
Browse code

facet_plot

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

g.yu authored on 07/09/2016 01:36:05
Showing 1 changed files
... ...
@@ -182,24 +182,20 @@ inset(p, img)
182 182
 
183 183
 ![](figures/inset_img.png)
184 184
 
185
-# Align tree with other plots on a page
185
+# Plot tree with associated data
186 186
 
187
-This is currently difficult to achieve in `ggplot2`. However, it is possible to obtain good results by creating a dummy faceting of data.
187
+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.
188 188
 
189 189
 ```{r warning=F, fig.width=10, fig.height=6}
190 190
 tr <- rtree(30)
191
-df <- fortify(tr)
192
-df$tipstats <- NA
193
-d1 <- df
194
-d2 <- df
195
-d2$tipstats[d2$isTip] <- abs(rnorm(30))
196
-d1$panel <- 'Tree'
197
-d2$panel <- 'Stats'
198
-d1$panel <- factor(d1$panel, levels=c("Tree", "Stats"))
199
-d2$panel <- factor(d2$panel, levels=c("Tree", "Stats"))
200
-
201
-p <- ggplot(mapping=aes(x=x, y=y)) + facet_grid(.~panel, scale="free_x") + theme_tree2()
202
-p+geom_tree(data=d1) + geom_point(data=d2, aes(x=tipstats)) 
191
+
192
+d1 <- data.frame(id=tr$tip.label, val=rnorm(30, sd=3))
193
+p <- ggtree(tr)
194
+
195
+p2 <- facet_plot(p, panel="dot", data=d1, geom=geom_point, aes(x=val), color='firebrick')
196
+d2 <- data.frame(id=tr$tip.label, value = abs(rnorm(30, mean=100, sd=50)))
197
+
198
+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()
203 199
 ```
204 200
 
205 201
 # Tree annotation with Phylopic
Browse code

clean dependencies

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

g.yu authored on 21/07/2016 13:16:38
Showing 1 changed files
... ...
@@ -16,6 +16,7 @@ output:
16 16
 vignette: >
17 17
   %\VignetteIndexEntry{05 Advance Tree Annotation}
18 18
   %\VignetteEngine{knitr::rmarkdown}
19
+  %\VignetteDepends{Biostrings}
19 20
   %\usepackage[utf8]{inputenc}
20 21
 ---
21 22
 
... ...
@@ -27,6 +28,7 @@ knitr::opts_chunk$set(tidy = FALSE,
27 28
 
28 29
 ```{r echo=FALSE, results="hide", message=FALSE}
29 30
 library("ape")
31
+library("Biostrings")
30 32
 library("ggplot2")
31 33
 library("ggtree")
32 34
 ```
Browse code

fixed R check

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

g.yu authored on 12/05/2016 07:25:06
Showing 1 changed files
... ...
@@ -170,7 +170,7 @@ inset(p2, bx2, width=.2, height=.03, vjust=.04, hjust=p2$data$x[1:15]-4) + xlim(
170 170
 
171 171
 ## Annotate with image files
172 172
 
173
-```{r}
173
+```{r eval=FALSE}
174 174
 imgfile <- tempfile(, fileext=".png")
175 175
 download.file("https://avatars1.githubusercontent.com/u/626539?v=3&u=e731426406dd3f45a73d96dd604bc45ae2e7c36f&s=140", destfile=imgfile, mode='wb')
176 176
 img <- list(imgfile, imgfile)
... ...
@@ -178,6 +178,7 @@ names(img) <- c("18", "22")
178 178
 inset(p, img)
179 179
 ```
180 180
 
181
+![](figures/inset_img.png)
181 182
 
182 183
 # Align tree with other plots on a page
183 184
 
Browse code

1.5.1: geom_strip, update vignettes

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

g.yu authored on 10/05/2016 07:50:46
Showing 1 changed files
... ...
@@ -84,19 +84,7 @@ msaplot(ggtree(beast_tree), fasta, window=c(150, 200)) + coord_polar(theta='y')
84 84
 
85 85
 # Annotate a phylogenetic tree with insets
86 86
 
87
-`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).
88
-
89
-```{r fig.width=8, fig.height=8, warning=F}
90
-set.seed(2016-01-04)
91
-tr <- rtree(30)
92
-tr <- groupClade(tr, node=45)
93
-p <- ggtree(tr, aes(color=group)) + geom_tippoint()
94
-p1 <- p + geom_hilight(node=45)
95
-p2 <- viewClade(p, node=45) + geom_tiplab()
96
-subview(p2, p1+theme_transparent(), x=2.3, y=28.5)
97
-```
98
-
99
-To make it more easy to use subview function for annotating taxa with subplots, *ggtree* provides a function, `inset`, for adding subplots to a phylogenetic tree. The input is a tree graphic object and a named list of ggplot graphic objects (can be any kind of charts), these objects should named by node numbers. To facilitate adding bar and pie charts (e.g. summarized stats of results from ancestral reconstruction) to phylogenetic tree, *ggtree* provides `nodepie` and `nodebar` functions to create a list of pie or bar charts.
87
+`ggtree` provides a function, `inset`, for adding subplots to a phylogenetic tree. The input is a tree graphic object and a named list of ggplot graphic objects (can be any kind of charts), these objects should named by node numbers. To facilitate adding bar and pie charts (e.g. summarized stats of results from ancestral reconstruction) to phylogenetic tree, *ggtree* provides `nodepie` and `nodebar` functions to create a list of pie or bar charts.
100 88
 
101 89
 ## Annotate with bar charts
102 90
 
Browse code

update docs

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

g.yu authored on 10/03/2016 11:55:44
Showing 1 changed files
... ...
@@ -53,7 +53,7 @@ p <- p + geom_tiplab(size=3)
53 53
 gheatmap(p, genotype, offset = 2, width=0.5)
54 54
 ```
55 55
 
56
-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.
56
+The _width_ parameter is to control the width of the heatmap. It supports another parameter _offset_ for controlling the distance between the tree and the heatmap, for instance to allocate space for tip labels.
57 57
 
58 58
 
59 59
 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. 
Browse code

fixed check

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

g.yu authored on 02/03/2016 09:54:31
Showing 1 changed files
... ...
@@ -28,7 +28,6 @@ knitr::opts_chunk$set(tidy = FALSE,
28 28
 ```{r echo=FALSE, results="hide", message=FALSE}
29 29
 library("ape")
30 30
 library("ggplot2")
31
-library("gridExtra")
32 31
 library("ggtree")
33 32
 ```
34 33
 
Browse code

inset with image files

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

g.yu authored on 23/02/2016 10:12:44
Showing 1 changed files
... ...
@@ -181,6 +181,17 @@ bx2 <- lapply(bx, function(g) g+coord_flip())
181 181
 inset(p2, bx2, width=.2, height=.03, vjust=.04, hjust=p2$data$x[1:15]-4) + xlim(NA, 4.5)
182 182
 ```
183 183
 
184
+## Annotate with image files
185
+
186
+```{r}
187
+imgfile <- tempfile(, fileext=".png")
188
+download.file("https://avatars1.githubusercontent.com/u/626539?v=3&u=e731426406dd3f45a73d96dd604bc45ae2e7c36f&s=140", destfile=imgfile, mode='wb')
189
+img <- list(imgfile, imgfile)
190
+names(img) <- c("18", "22")
191
+inset(p, img)
192
+```
193
+
194
+
184 195
 # Align tree with other plots on a page
185 196
 
186 197
 This is currently difficult to achieve in `ggplot2`. However, it is possible to obtain good results by creating a dummy faceting of data.
... ...
@@ -219,9 +230,5 @@ pp %>% phylopic("67382184-5135-4faa-8e98-eadff02c3e8a", color="#86B875", alpha=.
219 230
 ![](figures/phylopic2.png)
220 231
 
221 232
 
222
-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/).
223
-
224
-
225
-
226 233
 
227 234
 
Browse code

support phylip format

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

g.yu authored on 15/01/2016 04:55:05
Showing 1 changed files
... ...
@@ -79,8 +79,8 @@ msaplot(ggtree(beast_tree), fasta)
79 79
 
80 80
 A specific slice of the alignment can also be displayed by specific _window_ parameter.
81 81
 
82
-```{r fig.width=8, fig.height=12, fig.align='center'}
83
-msaplot(ggtree(beast_tree), fasta, window=c(150, 200)) 
82
+```{r fig.width=16, fig.height=16, fig.align='center'}
83
+msaplot(ggtree(beast_tree), fasta, window=c(150, 200)) + coord_polar(theta='y')
84 84
 ```
85 85
 
86 86
 # Annotate a phylogenetic tree with insets
Browse code

viewClade function

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

g.yu authored on 13/01/2016 02:57:51
Showing 1 changed files
... ...
@@ -83,7 +83,7 @@ A specific slice of the alignment can also be displayed by specific _window_ par
83 83
 msaplot(ggtree(beast_tree), fasta, window=c(150, 200)) 
84 84
 ```
85 85
 
86
-# Annotate a phylogenetic with insets
86
+# Annotate a phylogenetic tree with insets
87 87
 
88 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).
89 89
 
... ...
@@ -92,10 +92,9 @@ set.seed(2016-01-04)
92 92
 tr <- rtree(30)
93 93
 tr <- groupClade(tr, node=45)
94 94
 p <- ggtree(tr, aes(color=group)) + geom_tippoint()
95
-cpos <- get_clade_position(p, node=45)
96 95
 p1 <- p + geom_hilight(node=45)
97
-p2 <- with(cpos, p+xlim(xmin, xmax*1.01)+ylim(ymin, ymax))
98
-with(cpos, subview(p2+geom_tiplab(), p1+theme_transparent(), x=xmin+(xmax-xmin)*.15, y=ymin+(ymax-ymin)*.85))
96
+p2 <- viewClade(p, node=45) + geom_tiplab()
97
+subview(p2, p1+theme_transparent(), x=2.3, y=28.5)
99 98
 ```
100 99
 
101 100
 To make it more easy to use subview function for annotating taxa with subplots, *ggtree* provides a function, `inset`, for adding subplots to a phylogenetic tree. The input is a tree graphic object and a named list of ggplot graphic objects (can be any kind of charts), these objects should named by node numbers. To facilitate adding bar and pie charts (e.g. summarized stats of results from ancestral reconstruction) to phylogenetic tree, *ggtree* provides `nodepie` and `nodebar` functions to create a list of pie or bar charts.
Browse code

update vignettes

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

g.yu authored on 11/01/2016 04:11:26
Showing 1 changed files
... ...
@@ -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/).
Browse code

inset function and update vignette

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

g.yu authored on 04/01/2016 09:56:10
Showing 1 changed files
1 1
new file mode 100644
... ...
@@ -0,0 +1,221 @@
1
+---
2
+title: "Advance Tree Annotation"
3
+author: "\\
4
+
5
+	Guangchuang Yu (<guangchuangyu@gmail.com>) and Tommy Tsan-Yuk Lam (<ttylam@hku.hk>)\\
6
+
7
+        School of Public Health, The University of Hong Kong"
8
+date: "`r Sys.Date()`"
9
+bibliography: ggtree.bib
10
+csl: nature.csl
11
+output: 
12
+  html_document:
13
+    toc: true
14
+  pdf_document:
15
+    toc: true
16
+vignette: >
17
+  %\VignetteIndexEntry{05 Advance Tree Annotation}
18
+  %\VignetteEngine{knitr::rmarkdown}
19
+  %\usepackage[utf8]{inputenc}
20
+---
21
+
22
+```{r style, echo=FALSE, results="asis", message=FALSE}
23
+knitr::opts_chunk$set(tidy = FALSE,
24
+		   message = FALSE)
25
+```
26
+
27
+
28
+```{r echo=FALSE, results="hide", message=FALSE}
29
+library("ape")
30
+library("ggplot2")
31
+library("gridExtra")
32
+library("ggtree")
33
+```
34
+
35
+
36
+# Visualize tree with associated matrix
37
+
38
+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.
39
+
40
+
41
+In the following example, we visualized a tree of H3 influenza viruses with their associated genotype.
42
+
43
+```{r fig.width=20, fig.height=16, fig.align="center"}
44
+beast_file <- system.file("examples/MCC_FluA_H3.tree", package="ggtree")
45
+beast_tree <- read.beast(beast_file)
46
+
47
+genotype_file <- system.file("examples/Genotype.txt", package="ggtree")
48
+genotype <- read.table(genotype_file, sep="\t", stringsAsFactor=F)
49
+p <- ggtree(beast_tree, mrsd="2013-01-01") + geom_treescale(x=2008, y=1)
50
+p <- p + geom_tiplab(size=3)
51
+gheatmap(p, genotype, offset = 2, width=0.5)
52
+```
53
+
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.
55
+
56
+
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.
58
+
59
+```{r fig.width=20, fig.height=16, fig.align="center"}
60
+p <- ggtree(beast_tree, mrsd="2013-01-01") + geom_tiplab(size=3, align=TRUE) + theme_tree2()
61
+pp <- (p + scale_y_continuous(expand=c(0, 0.3))) %>%
62
+    gheatmap(genotype, offset=4, width=0.5, colnames=FALSE) %>%
63
+        scale_x_ggtree()
64
+pp + theme(legend.position="right")
65
+```
66
+
67
+# Visualize tree with multiple sequence alignment
68
+
69
+With `msaplot` function, user can visualizes multiple sequence alignment with phylogenetic tree, as demonstrated below:
70
+```{r fig.width=8, fig.height=12, fig.align='center'}
71
+fasta <- system.file("examples/FluA_H3_AA.fas", package="ggtree")
72
+msaplot(ggtree(beast_tree), fasta) 
73
+```
74
+
75
+A specific slice of the alignment can also be displayed by specific _window_ parameter.
76
+
77
+
78
+# Annotate a phylogenetic with insets
79
+
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).
81
+
82
+```{r fig.width=8, fig.height=8, warning=F}
83
+set.seed(2016-01-04)
84
+tr <- rtree(30)
85
+tr <- groupClade(tr, node=45)
86
+p <- ggtree(tr, aes(color=group)) + geom_tippoint()
87
+cpos <- get_clade_position(p, node=45)
88
+p1 <- p + geom_hilight(node=45)
89
+p2 <- with(cpos, p+xlim(xmin, xmax*1.01)+ylim(ymin, ymax))
90
+with(cpos, subview(p2+geom_tiplab(), p1+theme_transparent(), x=xmin+(xmax-xmin)*.15, y=ymin+(ymax-ymin)*.85))
91
+```
92
+
93
+To make it more easy to use subview function for annotating taxa with subplots, *ggtree* provides a function, `inset`, for adding subplots to a phylogenetic tree. The input is a tree graphic object and a named list of ggplot graphic objects (can be any kind of charts), these objects should named by node numbers. To facilitate adding bar and pie charts (e.g. summarized stats of results from ancestral reconstruction) to phylogenetic tree, *ggtree* provides `nodepie` and `nodebar` functions to create a list of pie or bar charts.
94
+
95
+## Annotate with bar charts
96
+
97
+```{r}
98
+set.seed(2015-12-31)
99
+tr <- rtree(15)
100
+p <- ggtree(tr)
101
+
102
+a <- runif(14, 0, 0.33)
103
+b <- runif(14, 0, 0.33)
104
+c <- runif(14, 0, 0.33)
105
+d <- 1 - a - b - c
106
+dat <- data.frame(a=a, b=b, c=c, d=d)
107
+## input data should have a column of `node` that store the node number
108
+dat$node <- 15+1:14
109
+
110
+## cols parameter indicate which columns store stats (a, b, c and d in this example)
111
+bars <- nodebar(dat, cols=1:4)
112
+
113
+inset(p, bars)
114
+```
115
+
116
+The size of the inset can be ajusted by the paramter *width* and *height*.
117
+
118
+```{r}
119
+inset(p, bars, width=.03, height=.06)
120
+```
121
+
122
+Users can set the color via the parameter *color*. The *x* position can be one of 'node' or 'branch' and can be adjusted by the parameter *hjust* and *vjust* for horizontal and vertical adjustment respecitvely.
123
+
124
+
125
+```{r}
126
+bars2 <- nodebar(dat, cols=1:4, position='dodge',
127
+                 color=c(a='blue', b='red', c='green', d='cyan'))
128
+p2 <- inset(p, bars2, x='branch', width=.03, vjust=-.3)
129
+print(p2)
130
+```
131
+
132
+## Annotate with pie charts
133
+
134
+Similarly, users can use `nodepie` function to generate a list of pie charts and place these charts to annotate corresponding nodes. Both `nodebar` and `nodepie` accepts parameter *alpha* to allow transparency.
135
+
136
+```{r}
137
+pies <- nodepie(dat, cols=1:4, alpha=.6)
138
+inset(p, pies)
139
+```
140
+
141
+
142
+```{r}
143
+inset(p, pies, hjust=-.06)
144
+```
145
+
146
+## Annotate with other types of charts
147
+
148
+The `inset` function accepts a list of ggplot graphic objects and these input objects are not restricted to pie or bar charts. They can be any kinds of charts and hybrid of these charts.
149
+
150
+```{r}
151
+pies_and_bars <- bars2
152
+pies_and_bars[9:14] <- pies[9:14]
153
+inset(p, pies_and_bars)
154
+```
155
+
156
+```{r}
157
+d <- lapply(1:15, rnorm, n=100)
158
+ylim <- range(unlist(d))
159
+bx <- lapply(d, function(y) {
160
+    dd <- data.frame(y=y)
161
+    ggplot(dd, aes(x=1, y=y))+geom_boxplot() + ylim(ylim) + theme_inset()
162
+})
163
+names(bx) <- 1:15
164
+inset(p, bx, width=.03, height=.1, hjust=-.05)
165
+```
166
+
167
+
168
+After annotating with insets, users can further annotate the tree with another layer of insets.
169
+
170
+```{r fig.width=10, fig.height=7}
171
+p2 <- inset(p, bars2, x='branch', width=.03, vjust=-.4)
172
+p2 <- inset(p2, pies, x='branch', vjust=.4)
173
+bx2 <- lapply(bx, function(g) g+coord_flip())
174
+inset(p2, bx2, width=.2, height=.03, vjust=.04, hjust=p2$data$x[1:15]-4) + xlim(NA, 4.5)
175
+```
176
+
177
+# Align tree with other plots on a page
178
+
179
+This is currently difficult to achieve in `ggplot2`. However, it is possible to obtain good results by creating a dummy faceting of data.
180
+
181
+```{r warning=F, fig.width=10, fig.height=6}
182
+tr <- rtree(30)
183
+df <- fortify(tr)
184
+df$tipstats <- NA
185
+d1 <- df
186
+d2 <- df
187
+d2$tipstats[d2$isTip] <- abs(rnorm(30))
188
+d1$panel <- 'Tree'
189
+d2$panel <- 'Stats'
190
+d1$panel <- factor(d1$panel, levels=c("Tree", "Stats"))
191
+d2$panel <- factor(d2$panel, levels=c("Tree", "Stats"))
192
+
193
+p <- ggplot(mapping=aes(x=x, y=y)) + facet_grid(.~panel, scale="free_x") +
194
+    xlab(NULL)+ylab(NULL)+theme_tree2()
195
+p+geom_tree(data=d1) + geom_point(data=d2, aes(x=tipstats)) 
196
+```
197
+
198
+# Tree annotation with Phylopic
199
+
200
+
201
+[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.
202
+
203
+```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE, eval=FALSE}