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 13 changed files

... ...
@@ -1,7 +1,7 @@
1 1
 Package: ggtree
2 2
 Type: Package
3 3
 Title: a phylogenetic tree viewer for different types of tree annotations
4
-Version: 1.5.0
4
+Version: 1.5.1
5 5
 Author: Guangchuang Yu and Tommy Tsan-Yuk Lam
6 6
 Maintainer: Guangchuang Yu <guangchuangyu@gmail.com>
7 7
 Description: ggtree extends the ggplot2 plotting system which implemented the
... ...
@@ -44,6 +44,7 @@ export(geom_point2)
44 44
 export(geom_range)
45 45
 export(geom_rootpoint)
46 46
 export(geom_segment2)
47
+export(geom_strip)
47 48
 export(geom_taxalink)
48 49
 export(geom_text2)
49 50
 export(geom_tiplab)
... ...
@@ -1,3 +1,19 @@
1
+CHANGES IN VERSION 1.5.1
2
+------------------------
3
+ o update vignettes <2016-05-10, Tue>
4
+   + add geom_range example in treeImport
5
+   + add geom_strip and geom_taxalink example in treeAnnotation
6
+   + add ggtreeUtilities vignette
7
+ o gheatmap now works with data.frame of only one column <2016-05-09, Mon>
8
+   + contributed by Justin Silverman <jsilve24@gmail.com>
9
+   + https://github.com/GuangchuangYu/ggtree/pull/57
10
+ o geom_strip for associated taxa <2016-05-09, Mon>
11
+   + https://github.com/GuangchuangYu/ggtree/issues/52
12
+ 
13
+CHANGES IN VERSION 1.4.0
14
+------------------------
15
+ o BioC 3.3 released <2016-05-05, Thu>
16
+ 
1 17
 CHANGES IN VERSION 1.3.16
2 18
 ------------------------
3 19
  o geom_treescale() supports family argument <2016-04-27, Wed>
4 20
new file mode 100644
... ...
@@ -0,0 +1,177 @@
1
+##' annotate associated taxa (from taxa1 to taxa2, can be Monophyletic, Polyphyletic or Paraphyletc Taxa) with bar and (optional) text label
2
+##'
3
+##' 
4
+##' @title geom_strip
5
+##' @param taxa1 taxa1
6
+##' @param taxa2 taxa2
7
+##' @param label optional label
8
+##' @param offset offset of bar and text from the clade
9
+##' @param offset.text offset of text from bar
10
+##' @param align logical
11
+##' @param barsize size of bar
12
+##' @param barextend extend bar vertically
13
+##' @param fontsize size of text
14
+##' @param angle angle of text
15
+##' @param geom one of 'text' or 'label'
16
+##' @param hjust hjust
17
+##' @param fill fill label background, only work with geom='label'
18
+##' @param family sans by default, can be any supported font
19
+##' @param ... additional parameter
20
+##' @return ggplot layers
21
+##' @export
22
+##' @author Guangchuang Yu
23
+geom_strip <- function(taxa1, taxa2, label=NA, offset=0, offset.text=0,
24
+                       align=TRUE, barsize=0.5, barextend=0, fontsize=3.88,
25
+                       angle=0, geom="text", hjust=0, fill=NA, family="sans", ...) {
26
+    mapping <- NULL
27
+    data <- NULL
28
+    position <- "identity"
29
+    show.legend <- NA
30
+    na.rm <- TRUE
31
+    inherit.aes <- FALSE
32
+
33
+    layer_bar <- stat_stripBar(taxa1=taxa1, taxa2=taxa2, offset=offset, align=align,
34
+                               size=barsize, barextend=barextend,
35
+                               mapping=mapping, data=data, 
36
+                               position=position, show.legend = show.legend,
37
+                               inherit.aes = inherit.aes, na.rm=na.rm, ...)
38
+
39
+    if (is.na(label) || is.null(label)) {
40
+        return(layer_bar)
41
+    }
42
+    
43
+    if (geom == "text") {
44
+        ## no fill parameter
45
+        layer_text <- stat_stripText(taxa1=taxa1, taxa2=taxa2, label=label, offset=offset+offset.text,
46
+                                    align=align, size=fontsize, angle=angle, family=family,
47
+                                    mapping=mapping, data=data, geom=geom, hjust=hjust,
48
+                                    position=position, show.legend = show.legend,
49
+                                    inherit.aes = inherit.aes, na.rm=na.rm, ...)
50
+        
51
+    } else {
52
+        layer_text <- stat_stripText(taxa1=taxa1, taxa2=taxa2, label=label, offset=offset+offset.text,
53
+                                    align=align, size=fontsize, angle=angle, fill=fill,family=family,
54
+                                    mapping=mapping, data=data, geom=geom, hjust=hjust,
55
+                                    position=position, show.legend = show.legend,
56
+                                    inherit.aes = inherit.aes, na.rm=na.rm, ...)
57
+    }
58
+    
59
+    list(
60
+        layer_bar,
61
+        layer_text
62
+    )
63
+}
64
+
65
+
66
+stat_stripText <- function(mapping=NULL, data=NULL,
67
+                           geom="text", position="identity",
68
+                           taxa1, taxa2, label, offset, align, ...,
69
+                           show.legend=NA, inherit.aes=FALSE, na.rm=FALSE) {
70
+    default_aes <- aes_(x=~x, y=~y, node=~node, parent=~parent,label=~label)
71
+    if (is.null(mapping)) {
72
+        mapping <- default_aes
73
+    } else {
74
+        mapping <- modifyList(mapping, default_aes)
75
+    }
76
+    
77
+    layer(stat=StatStripText,
78
+          data=data,
79
+          mapping=mapping,
80
+          geom=geom,
81
+          position=position,
82
+          show.legend = show.legend,
83
+          inherit.aes = inherit.aes,
84
+          params=list(taxa1=taxa1,
85
+                      taxa2=taxa2,
86
+                      label=label,
87
+                      offset=offset,
88
+                      align=align,
89
+                      na.rm=na.rm,
90
+                      ...)
91
+          )
92
+    
93
+}
94
+
95
+stat_stripBar <- function(mapping=NULL, data=NULL,
96
+                          geom="segment", position="identity",
97
+                          taxa1, taxa2, offset, align, barextend, ...,
98
+                          show.legend=NA, inherit.aes=FALSE, na.rm=FALSE) {
99
+    default_aes <- aes_(x=~x, y=~y, node=~node, parent=~parent, label=~label)
100
+    if (is.null(mapping)) {
101
+        mapping <- default_aes
102
+    } else {
103
+        mapping <- modifyList(mapping, default_aes)
104
+    }
105
+    
106
+    layer(stat=StatStripBar,
107
+          data=data,
108
+          mapping=mapping,
109
+          geom=geom,
110
+          position=position,
111
+          show.legend = show.legend,
112
+          inherit.aes = inherit.aes,
113
+          params=list(taxa1=taxa1,
114
+                      taxa2=taxa2,
115
+                      offset=offset,
116
+                      align=align,
117
+                      barextend=barextend,
118
+                      na.rm=na.rm,
119
+                      ...)
120
+          )
121
+
122
+}
123
+
124
+StatStripText <- ggproto("StatStripText", Stat,
125
+                         compute_group = function(self, data, scales, params, taxa1, taxa2,
126
+                                                  label, offset, align) {
127
+                             df <- get_striplabel_position(data, taxa1, taxa2, offset, align, adjustRatio = 1.03)
128
+                             df$y <- mean(c(df$y, df$yend))
129
+                             df$label <- label
130
+                             return(df)
131
+                         },
132
+                         required_aes = c("x", "y", "label")
133
+                         )
134
+
135
+                         
136
+                          
137
+StatStripBar <- ggproto("StatStripBar", Stat,
138
+                        compute_group = function(self, data, scales, params,
139
+                                                 taxa1, taxa2, offset, align, barextend) {
140
+                            get_striplabel_position(data, taxa1, taxa2, offset, align, barextend, adjustRatio=1.02)
141
+                        },
142
+                        required_aes = c("x", "y", "xend", "yend")
143
+                        )
144
+
145
+
146
+get_striplabel_position <- function(data, taxa1, taxa2, offset, align, barextend, adjustRatio) {
147
+    df <- get_striplabel_position_(data, taxa1, taxa2, barextend)
148
+    if (align) {
149
+        mx <- max(data$x, na.rm=TRUE)
150
+    } else {
151
+        mx <- df$x
152
+    }
153
+    mx <- mx * adjustRatio + offset
154
+    data.frame(x=mx, xend=mx, y=df$y, yend=df$yend)
155
+}
156
+
157
+
158
+get_striplabel_position_ <- function(data, taxa1, taxa2, barextend=0) {
159
+    node1 <- taxa2node(data, taxa1)
160
+    node2 <- taxa2node(data, taxa2)
161
+
162
+    xx <- with(data, c(x[node == node1], x[node == node2]))
163
+    yy <- with(data, c(y[node == node1], y[node == node2]))
164
+
165
+    data.frame(x=max(xx), y=min(yy)-barextend, yend=max(yy)+barextend)
166
+}
167
+
168
+## used in geom_strip, geom_taxalink
169
+taxa2node <- function(data, taxa) {
170
+    idx <- with(data, which(taxa == label | taxa == node))
171
+
172
+    if (length(idx) == 0) {
173
+        stop("input taxa is not valid...")
174
+    }
175
+    
176
+    return(data$node[idx])
177
+}
... ...
@@ -37,10 +37,8 @@ geom_taxalink <- function(taxa1, taxa2, curvature=0.5, ...) {
37 37
 
38 38
 StatTaxalink <- ggproto("StatTaxalink", Stat,
39 39
                         compute_group = function(self, data, scales, params, taxa1, taxa2) {
40
-                            node <- data$node
41
-                            label <- data$label
42
-                            node1 <- which(taxa1 == label | taxa1 == node)
43
-                            node2 <- which(taxa2 == label | taxa2 == node)
40
+                            node1 <- taxa2node(data, taxa1)
41
+                            node2 <- taxa2node(data, taxa2)
44 42
                             x <- data$x
45 43
                             y <- data$y
46 44
                             
... ...
@@ -26,27 +26,28 @@
26 26
 ##' @author Guangchuang Yu
27 27
 gheatmap <- function(p, data, offset=0, width=1, low="green", high="red", color="white",
28 28
                      colnames=TRUE, colnames_position="bottom", colnames_level=NULL, font.size=4) {
29
-
29
+    
30 30
     colnames_position %<>% match.arg(c("bottom", "top"))
31 31
     variable <- value <- lab <- y <- NULL
32 32
     
33 33
     ## if (is.null(width)) {
34 34
     ##     width <- (p$data$x %>% range %>% diff)/30
35 35
     ## }
36
-
36
+    
37 37
     ## convert width to width of each cell
38 38
     width <- width * (p$data$x %>% range %>% diff) / ncol(data)
39 39
     
40 40
     isTip <- x <- y <- variable <- value <- from <- to <- NULL
41
- 
41
+    
42 42
     df <- p$data
43 43
     df <- df[df$isTip,]
44 44
     start <- max(df$x) + offset
45
-
46
-    dd <- data[df$label[order(df$y)],]
47
-    dd$y <- sort(df$y)
48
-
45
+    
46
+    dd <- data
49 47
     dd$lab <- rownames(dd)
48
+    dd <- dd[df$label[order(df$y)],]
49
+    dd$y <- sort(df$y)
50
+    
50 51
     ## dd <- melt(dd, id=c("lab", "y"))
51 52
     dd <- gather(dd, variable, value, -c(lab, y))
52 53
     
... ...
@@ -61,13 +62,14 @@ gheatmap <- function(p, data, offset=0, width=1, low="green", high="red", color=
61 62
     V2 <- start + as.numeric(dd$variable) * width
62 63
     mapping <- data.frame(from=dd$variable, to=V2)
63 64
     mapping <- unique(mapping)
64
-
65
+    
65 66
     dd$x <- V2
66
-
67
+    dd$width <- width
68
+    
67 69
     if (is.null(color)) {
68
-        p2 <- p + geom_tile(data=dd, aes(x, y, fill=value), inherit.aes=FALSE)
70
+        p2 <- p + geom_tile(data=dd, aes(x, y, fill=value, width=width), inherit.aes=FALSE)
69 71
     } else {
70
-        p2 <- p + geom_tile(data=dd, aes(x, y, fill=value), color=color, inherit.aes=FALSE)
72
+        p2 <- p + geom_tile(data=dd, aes(x, y, fill=value, width=width), color=color, inherit.aes=FALSE)
71 73
     }
72 74
     if (is(dd$value,"numeric")) {
73 75
         p2 <- p2 + scale_fill_gradient(low=low, high=high, na.value="white")
... ...
@@ -83,7 +85,7 @@ gheatmap <- function(p, data, offset=0, width=1, low="green", high="red", color=
83 85
         }
84 86
         p2 <- p2 + geom_text(data=mapping, aes(x=to, label=from), y=y, size=font.size, inherit.aes = FALSE)
85 87
     }
86
-
88
+    
87 89
     p2 <- p2 + theme(legend.position="right", legend.title=element_blank())
88 90
     p2 <- p2 + guides(fill = guide_legend(override.aes = list(colour = NULL)))
89 91
     
90 92
new file mode 100644
... ...
@@ -0,0 +1,52 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/geom_strip.R
3
+\name{geom_strip}
4
+\alias{geom_strip}
5
+\title{geom_strip}
6
+\usage{
7
+geom_strip(taxa1, taxa2, label = NA, offset = 0, offset.text = 0,
8
+  align = TRUE, barsize = 0.5, barextend = 0, fontsize = 3.88,
9
+  angle = 0, geom = "text", hjust = 0, fill = NA, family = "sans",
10
+  ...)
11
+}
12
+\arguments{
13
+\item{taxa1}{taxa1}
14
+
15
+\item{taxa2}{taxa2}
16
+
17
+\item{label}{optional label}
18
+
19
+\item{offset}{offset of bar and text from the clade}
20
+
21
+\item{offset.text}{offset of text from bar}
22
+
23
+\item{align}{logical}
24
+
25
+\item{barsize}{size of bar}
26
+
27
+\item{barextend}{extend bar vertically}
28
+
29
+\item{fontsize}{size of text}
30
+
31
+\item{angle}{angle of text}
32
+
33
+\item{geom}{one of 'text' or 'label'}
34
+
35
+\item{hjust}{hjust}
36
+
37
+\item{fill}{fill label background, only work with geom='label'}
38
+
39
+\item{family}{sans by default, can be any supported font}
40
+
41
+\item{...}{additional parameter}
42
+}
43
+\value{
44
+ggplot layers
45
+}
46
+\description{
47
+annotate associated taxa (from taxa1 to taxa2, can be Monophyletic, Polyphyletic or Paraphyletc Taxa) with bar and (optional) text label
48
+}
49
+\author{
50
+Guangchuang Yu
51
+}
52
+
... ...
@@ -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
 
... ...
@@ -84,7 +84,16 @@ Details and examples can be found in [Tree Manipulation](treeManipulation.html)
84 84
 
85 85
 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.
86 86
 
87
-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. 
87
+The `ggtree` package provides several layers to annotate a phylogenetic tree, including:
88
+
89
++ `geom_cladelabel` for labelling selected clades
90
++ `geom_hilight` for highlighting selected clades 
91
++ `geom_range` to indicate uncertainty of branch lengths
92
++ `geom_strip` for adding strip/bar to label associated taxa (with optional label)
93
++ `geom_taxalink` for connecting related taxa
94
++ `geom_tiplab` for adding tip labels
95
++ `geom_treescale` for adding a legend of tree scale
96
+
88 97
 
89 98
 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`.
90 99
 
... ...
@@ -100,8 +109,10 @@ Visualizing an annotated phylogenetic tree with numerical matrix (e.g. genotype
100 109
 + [Tree Manipulation](treeManipulation.html)
101 110
 + [Tree Annotation](treeAnnotation.html)
102 111
 + [Advance Tree Annotation](advanceTreeAnnotation.html)
112
++ [ggtree utilities](ggtreeUtilities.html)
113
+
103 114
 
104
-More documents can be found in <http://guangchuangyu.github.io/tags/ggtree>.
115
+More documents can be found in <http://guangchuangyu.github.io/ggtree>.
105 116
 
106 117
 # Bugs/Feature requests
107 118
 
108 119
new file mode 100644
... ...
@@ -0,0 +1,85 @@
1
+---
2
+title: "ggtree utilities"
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{00 ggtree introduction}
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("ggtree")
32
+```
33
+
34
+
35
+# Layers that allows subsetting
36
+
37
+`Subsetting` is not supported in layers defined in `ggplot2`, while it is quite useful in phylogenetic annotation since it allows us to annotate at specific node(s). 
38
+
39
+In `ggtree`, we provides modified version of layers defined in `ggplot2` to support `subsetting`, including:
40
+
41
++ geom_segment2
42
++ geom_point2
43
++ geom_text2
44
++ geom_label2
45
+
46
+```{r fig.width=5, fig.height=5}
47
+file <- system.file("extdata/BEAST", "beast_mcc.tree", package="ggtree")
48
+beast <- read.beast(file)
49
+ggtree(beast) + geom_point2(aes(subset=!is.na(posterior) & posterior > 0.75), color='firebrick')
50
+```
51
+
52
+# subplots in ggplot object
53
+
54
+`ggtree` implemented a function, `subview`, that can add subplots on a ggplot2 object. 
55
+
56
+```{r fig.width=8, fig.height=8, warning=F}
57
+set.seed(2016-01-04)
58
+tr <- rtree(30)
59
+tr <- groupClade(tr, node=45)
60
+p <- ggtree(tr, aes(color=group)) + geom_tippoint()
61
+p1 <- p + geom_hilight(node=45)
62
+p2 <- viewClade(p, node=45) + geom_tiplab()
63
+subview(p2, p1+theme_transparent(), x=2.3, y=28.5)
64
+```
65
+
66
+This is the backend of the [inset](advanceTreeAnnotation.html) function.
67
+
68
+This `subview` function works with any `ggplot` objects and it had successful applied to [plot pie graphs on map](http://stackoverflow.com/questions/10368180/plotting-pie-graphs-on-map-in-ggplot/32380396#32380396).
69
+
70
+```{r fig.show='animate', interval=.1}
71
+library(ggtree)
72
+dd <- data.frame(x=LETTERS[1:3], y=1:3)
73
+pie <- ggplot(dd, aes(x=1, y, fill=x)) + geom_bar(stat="identity", width=1) + coord_polar(theta="y") + theme_inset()
74
+x <- sample(2:9)
75
+y <- sample(2:9)
76
+width <- sample(seq(0.05, 0.15, length.out=length(x)))
77
+height <- width
78
+p <- ggplot(data=data.frame(x=c(0, 10), y=c(0, 10)), aes(x, y))+geom_blank()
79
+for (i in seq_along(x)) {
80
+    p <- subview(p, pie, x[i], y[i], width[i], height[i])
81
+    print(p)
82
+}
83
+```
84
+
85
+
... ...
@@ -99,7 +99,7 @@ ggtree(beast_tree, aes(color=rate)) +
99 99
 
100 100
 User can use any feature (if available), including clade posterior and *dN/dS* _etc._, to scale the color of the tree.
101 101
 
102
-## Annotate clades
102
+# Annotate clades
103 103
 
104 104
 `ggtree` implements _`geom_cladelabel`_ layer to annotate a selected clade with a bar indicating the clade with a corresponding label.
105 105
 
... ...
@@ -169,6 +169,23 @@ ggtree(tree, layout="circular") + geom_hilight(node=21, fill="steelblue", alpha=
169 169
 Another way to highlight selected clades is setting the clades with different colors and/or line types as demonstrated in [Tree Manipulation](treeManipulation.html#groupclade) vignette.
170 170
 
171 171
 
172
+# labelling associated taxa (Monophyletic, Polyphyletic or Paraphyletic)
173
+
174
+`geom_cladelabel` is designed to labelling Monophyletic (Clade) while there are related taxa that are not form a clade. `ggtree` provides `geom_strip` to add a strip/bar to indicate the association with optional label (see [the issue](https://github.com/GuangchuangYu/ggtree/issues/52)).
175
+
176
+```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
177
+ggtree(tree) + geom_tiplab() + geom_strip('E', 'G', barsize=2, color='red') + geom_strip('F', 'L', barsize=2, color='blue')
178
+```
179
+
180
+# taxa connection
181
+
182
+Some evolutionary events (e.g. reassortment, horizontal gene transfer) can be modeled by a simple tree. `ggtree` provides `geom_taxalink` layer that allows drawing straight or curved lines between any of two nodes in the tree, allow it to represent evolutionary events by connecting taxa.
183
+
184
+```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
185
+ggtree(tree) + geom_tiplab() + geom_taxalink('A', 'E') + geom_taxalink('F', 'K', color='red', arrow=grid::arrow(length = grid::unit(0.02, "npc")))
186
+```
187
+
188
+
172 189
 # Tree annotation with analysis of R packages
173 190
 
174 191
 ## annotating tree with ape bootstraping analysis
... ...
@@ -136,6 +136,18 @@ Users can use `ggtree(beast)` to visualize the tree and add layer to annotate it
136 136
 ggtree(beast, ndigits=2, branch.length = 'none') + geom_text(aes(x=branch, label=length_0.95_HPD), vjust=-.5, color='firebrick')
137 137
 ```
138 138
 
139
+`ggtree` provides `geom_range` layer to display uncertainty of branch length.
140
+
141
+```{r warning=FALSE, fig.width=10, fig.height=10}
142
+ggtree(beast) + geom_range(range='height_0.95_HPD', color='red', alpha=.6, size=2)
143
+```
144
+
145
+In `FigTree`, only `heigh_0.95_HPD` is meaningful since the branch is scaled by `height`. In `ggtree` we can display HPD of `rate`, `height` or other variable if available since `ggtree` can rescale a tree using `rescale_tree` function or by specifing `branch.length` in `ggtree` function.
146
+
147
+```{r warning=FALSE, fig.width=10, fig.height=10}
148
+ggtree(beast, branch.length = 'rate') + geom_range(range='rate_0.95_HPD', color='red', alpha=.6, size=2)
149
+```
150
+
139 151
 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.
140 152
 
141 153
 ```{r}
... ...
@@ -217,6 +217,12 @@ For _`circular`_ and _`unrooted`_ layout, `ggtree` supports rotating node labels
217 217
 ggtree(tree, layout="circular") + geom_tiplab(aes(angle=angle), color='blue')
218 218
 ```
219 219
 
220
+To make it more readable for human eye, `ggtree` provides a `geom_tiplab2` for `circular` layout (see post [1](https://groups.google.com/forum/?utm_medium=email&utm_source=footer#!topic/bioc-ggtree/o35PV3iHO-0) and [2](https://groups.google.com/forum/#!topic/bioc-ggtree/p42R5l8J-14)).
221
+
222
+```{r fig.width=6, fig.height=6, warning=FALSE, fig.align="center"}
223
+ggtree(tree, layout="circular") + geom_tiplab2(color='blue')
224
+```
225
+
220 226
 By default, the positions are based on the node positions, we can change them to based on the middle of the branch/edge.
221 227
 
222 228
 ```{r fig.width=4, fig.height=3, warning=FALSE, fig.align="center"}