Browse code

Commit made by the Bioconductor Git-SVN bridge. Consists of 4 commits.

Commit information:

Commit id: 84b61073b62e8e9019f2069bdd428cddfe6de923

update vignette

Committed by: GuangchuangYu
Author Name: GuangchuangYu
Commit date: 2015-02-04 14:07:37 +0800
Author date: 2015-02-04 14:07:37 +0800

Commit id: a433cb7834aac21b3286bfcb0f1fdb9f636438c4

scale_color

Committed by: GuangchuangYu
Author Name: GuangchuangYu
Commit date: 2015-02-04 13:53:21 +0800
Author date: 2015-02-04 13:53:21 +0800

Commit id: 4529f53a366b6e0c8bdb6cddb7e8d97e7c1f3624

groupOTU

Committed by: GuangchuangYu
Author Name: GuangchuangYu
Commit date: 2015-02-04 12:30:20 +0800
Author date: 2015-02-04 12:30:20 +0800

Commit id: 36eca359ebb41930375c9d1a8e41bcb632dd8252

scale color prototye

Committed by: GuangchuangYu
Author Name: GuangchuangYu
Commit date: 2015-02-04 11:22:26 +0800
Author date: 2015-02-04 11:22:26 +0800


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

g.yu authored on 04/02/2015 06:08:11
Showing 17 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: 0.99.10
4
+Version: 0.99.11
5 5
 Author: Guangchuang Yu
6 6
 Maintainer: Guangchuang Yu <guangchuangyu@gmail.com>
7 7
 Description: ggtree extends the ggplot2 plotting system which implemented the
... ...
@@ -12,6 +12,7 @@ Depends:
12 12
 Imports:
13 13
     ape,
14 14
     Biostrings,
15
+    colorspace,
15 16
     ggplot2,
16 17
     grid,
17 18
     gridExtra,
... ...
@@ -25,7 +26,6 @@ Imports:
25 26
 Suggests:
26 27
     phylobase,
27 28
     BiocStyle,
28
-    colorspace,
29 29
     knitr,
30 30
     testthat,
31 31
     rmarkdown
... ...
@@ -44,6 +44,7 @@ export(read.jplace)
44 44
 export(read.paml_rst)
45 45
 export(read.tree)
46 46
 export(rtree)
47
+export(scale_color)
47 48
 export(theme_tree)
48 49
 export(theme_tree2)
49 50
 export(write.jplace)
... ...
@@ -62,6 +63,7 @@ exportMethods(get.treeinfo)
62 63
 exportMethods(get.treetext)
63 64
 exportMethods(groupOTU)
64 65
 exportMethods(plot)
66
+exportMethods(scale_color)
65 67
 exportMethods(show)
66 68
 importFrom(Biostrings,GENETIC_CODE)
67 69
 importFrom(Biostrings,readBStringSet)
... ...
@@ -78,6 +80,7 @@ importFrom(ape,read.tree)
78 80
 importFrom(ape,reorder.phylo)
79 81
 importFrom(ape,which.edge)
80 82
 importFrom(ape,write.tree)
83
+importFrom(colorspace,rainbow_hcl)
81 84
 importFrom(ggplot2,"%+replace%")
82 85
 importFrom(ggplot2,aes)
83 86
 importFrom(ggplot2,aes_string)
... ...
@@ -1,5 +1,11 @@
1
+CHANGES IN VERSION 0.99.11
2
+------------------------
3
+ o add scale_color to support colored lines and text based on numerical values and update vignette <2015-02-04, Wed>
4
+ o revised groupOTU that output index can be used in geom_text and update vignette <2015-02-04, Wed>
5
+
1 6
 CHANGES IN VERSION 0.99.10
2 7
 ------------------------
8
+ o support y scale by category variable <2015-02-03, Tue>
3 9
  o support order nodes by yscale <2015-02-03, Tue>
4 10
 
5 11
 CHANGES IN VERSION 0.99.9
... ...
@@ -114,3 +114,15 @@ setGeneric("get.tipseq", function(object, ...) standardGeneric("get.tipseq"))
114 114
 ##' @export
115 115
 setGeneric("groupOTU", function(object, focus) standardGeneric("groupOTU"))
116 116
 
117
+##' @docType methods
118
+##' @name scale_color
119
+##' @rdname scale_color-methods
120
+##' @title scale_color method
121
+##' @param object supported objects, including phylo, paml_rst,
122
+##'               codeml_mlc, codeml, jplace, beast, hyphy
123
+##' @param by one of numerical attributes
124
+##' @param ... additional parameter
125
+##' @return color vector
126
+##' @export
127
+setGeneric("scale_color", function(object, by, ...) standardGeneric("scale_color"))
128
+
... ...
@@ -89,6 +89,14 @@ setMethod("groupOTU", signature(object="beast"),
89 89
           }
90 90
           )
91 91
 
92
+##' @rdname scale_color-methods
93
+##' @exportMethod scale_color
94
+setMethod("scale_color", signature(object="beast"),
95
+          function(object, by, ...) {
96
+              scale_color_(object, by, ...)
97
+          })
98
+
99
+
92 100
 ##' get.tree method
93 101
 ##'
94 102
 ##'
... ...
@@ -30,6 +30,14 @@ setMethod("groupOTU", signature(object="codeml"),
30 30
           }
31 31
           )
32 32
 
33
+##' @rdname scale_color-methods
34
+##' @exportMethod scale_color
35
+setMethod("scale_color", signature(object="codeml"),
36
+          function(object, by, ...) {
37
+              scale_color_(object, by, ...)
38
+          })
39
+
40
+
33 41
 ##' @rdname show-methods
34 42
 ##' @exportMethod show
35 43
 setMethod("show", signature(object = "codeml"),
... ...
@@ -31,6 +31,13 @@ setMethod("groupOTU", signature(object="codeml_mlc"),
31 31
           }
32 32
           )
33 33
 
34
+##' @rdname scale_color-methods
35
+##' @exportMethod scale_color
36
+setMethod("scale_color", signature(object="codeml_mlc"),
37
+          function(object, by, ...) {
38
+              scale_color_(object, by, ...)
39
+          })
40
+
34 41
 ##' @rdname show-methods
35 42
 ##' @exportMethod show
36 43
 setMethod("show", signature(object = "codeml_mlc"),
... ...
@@ -34,8 +34,10 @@ ggtree <- function(tr, showDistance=FALSE, layout="phylogram", ...) {
34 34
     } else {
35 35
         type <- "none"
36 36
     }
37
-    p <- ggplot(tr, aes(x, y), layout=layout, ...) + geom_tree(layout, ...) + xlab("") + ylab("") + theme_tree2()
37
+    p <- ggplot(tr, aes(x, y), layout=layout, ...)
38 38
 
39
+    p <- p + geom_tree(layout, ...) + xlab("") + ylab("") + theme_tree2()
40
+    
39 41
     if (type == "dendrogram") {
40 42
         p <- p + scale_x_reverse() + coord_flip()
41 43
     } else if (type == "fan" || type == "radial") {
... ...
@@ -53,6 +55,9 @@ ggtree <- function(tr, showDistance=FALSE, layout="phylogram", ...) {
53 55
 ##' 
54 56
 ##' @title geom_tree
55 57
 ##' @param layout one of phylogram, cladogram
58
+##' @param color color
59
+##' @param linetype line type
60
+##' @param size line size
56 61
 ##' @param ... additional parameter
57 62
 ##' @return tree layer
58 63
 ##' @importFrom ggplot2 geom_segment
... ...
@@ -64,19 +69,32 @@ ggtree <- function(tr, showDistance=FALSE, layout="phylogram", ...) {
64 69
 ##' tr <- rtree(10)
65 70
 ##' require(ggplot2)
66 71
 ##' ggplot(tr) + geom_tree()
67
-geom_tree <- function(layout="phylogram", ...) {
72
+geom_tree <- function(layout="phylogram", color="black", linetype="solid", size=1, ...) {
68 73
     x <- y <- parent <- NULL
69 74
     if (layout == "phylogram" || layout == "fan") {
70
-        geom_segment(aes(x=c(x[parent], x[parent]),
71
-                         xend=c(x, x[parent]),
72
-                         y=c(y, y[parent]),
73
-                         yend=c(y, y)),...)
75
+        if (length(color) != 1) {
76
+            color <- c(color, color)
77
+        }
78
+        if (length(linetype) != 1) {
79
+            linetype <- c(linetype, linetype)
80
+        }
81
+        if (length(size) != 1) {
82
+            size <- c(size, size)
83
+        }
84
+        geom_segment(aes(x    = c(x[parent], x[parent]),
85
+                         xend = c(x,         x[parent]),
86
+                         y    = c(y,         y[parent]),
87
+                         yend = c(y,         y)),
88
+                     color = color,
89
+                     linetype = linetype, ...)
74 90
     } else if (layout == "cladogram" || layout == "unrooted") {
75
-        geom_segment(aes(x=x[parent],
76
-                         xend=x,
77
-                         y=y[parent],
78
-                         yend=y))
79
-    } 
91
+        geom_segment(aes(x    = x[parent],
92
+                         xend = x,
93
+                         y    = y[parent],
94
+                         yend = y),
95
+                     color = color,
96
+                     linetype = linetype, ...)
97
+    }
80 98
 }
81 99
 
82 100
 ##' add tip label layer
... ...
@@ -97,6 +97,13 @@ setMethod("groupOTU", signature(object="hyphy"),
97 97
           }
98 98
           )
99 99
 
100
+##' @rdname scale_color-methods
101
+##' @exportMethod scale_color
102
+setMethod("scale_color", signature(object="hyphy"),
103
+          function(object, by, ...) {
104
+              scale_color_(object, by, ...)
105
+          })
106
+
100 107
 ##' @rdname show-methods
101 108
 ##' @exportMethod show
102 109
 setMethod("show", signature(object = "hyphy"),
... ...
@@ -34,6 +34,14 @@ setMethod("groupOTU", signature(object="jplace"),
34 34
           }
35 35
           )
36 36
 
37
+##' @rdname scale_color-methods
38
+##' @exportMethod scale_color
39
+setMethod("scale_color", signature(object="jplace"),
40
+          function(object, by, ...) {
41
+              scale_color_(object, by, ...)
42
+          })
43
+
44
+
37 45
 ##' @rdname get.tree-methods
38 46
 ##' @exportMethod get.tree
39 47
 setMethod("get.tree", signature(object="jplace"),
... ...
@@ -68,6 +68,12 @@ setMethod("groupOTU", signature(object="paml_rst"),
68 68
           }
69 69
           )
70 70
 
71
+##' @rdname scale_color-methods
72
+##' @exportMethod scale_color
73
+setMethod("scale_color", signature(object="paml_rst"),
74
+          function(object, by, ...) {
75
+              scale_color_(object, by, ...)
76
+          })
71 77
 
72 78
 ##' @rdname get.tipseq-methods
73 79
 ##' @exportMethod get.tipseq
... ...
@@ -1,3 +1,57 @@
1
+##' @rdname scale_color-methods
2
+##' @exportMethod scale_color
3
+setMethod("scale_color", signature(object="phylo"),
4
+          function(object, by, ...) {
5
+              scale_color_(object, by, ...)
6
+          })
7
+
8
+##' @importFrom colorspace rainbow_hcl
9
+scale_color_ <- function(phylo, by, low=NULL, high=NULL, na.color=NULL, default.color="grey") {
10
+    if (!is.null(low) & ! is.null(high)) {
11
+        cols <- color_scale(c(low, high))
12
+    } else {
13
+        cols <- rainbow_hcl(100)
14
+    }
15
+    df <- fortify(phylo)
16
+    
17
+    vals <- df[, by]
18
+    idx <- sapply(vals, getIdx, min(vals, na.rm=TRUE), max(vals, na.rm=TRUE))
19
+    df$color <- cols[idx]
20
+
21
+    if ( is(phylo, "phylo")) {
22
+        tree <- phylo
23
+    } else {
24
+        tree <- get.tree(phylo)
25
+    }
26
+
27
+    if (is.null(na.color)) {
28
+        nodes <- getNodes_by_postorder(tree)
29
+        for (curNode in nodes) {
30
+            children <- getChild(tree, curNode)
31
+            if (length(children) == 0) {
32
+                next
33
+            }
34
+            idx <- which(is.na(df[children, "color"]))
35
+            if (length(idx) > 0) {
36
+                df[children[idx], "color"] <- df[curNode, "color"]
37
+            }
38
+        }
39
+        ii <- which(is.na(df[, "color"]))
40
+        if (length(ii) > 0) {
41
+            df[ii, "color"] <- default.color
42
+        }
43
+    } else {
44
+        ii <- which(is.na(df[, "color"]))
45
+        if (length(ii) > 0) {
46
+            df[ii, "color"] <- na.color
47
+        }
48
+    }
49
+
50
+    ## cols[is.na(cols)] <- "grey"
51
+    return(df$color)
52
+}
53
+
54
+
1 55
 ##' @rdname groupOTU-methods
2 56
 ##' @exportMethod groupOTU
3 57
 setMethod("groupOTU", signature(object="phylo"),
... ...
@@ -37,14 +91,15 @@ gfocus <- function(phy, focus) {
37 91
     
38 92
     n <- getNodeNum(phy)
39 93
     if (is.null(attr(phy, "focus"))) {
40
-        foc <- rep(1, 2*n)
94
+        ## foc <- rep(1, 2*n)
95
+        foc <- rep(1, n)
41 96
     } else {
42 97
         foc <- attr(phy, "focus")
43 98
     }
44 99
     i <- max(foc) + 1
45 100
     sn <- phy$edge[which.edge(phy, focus),] %>% as.vector %>% unique
46 101
     foc[sn] <- i
47
-    foc[sn+n] <- i
102
+    ## foc[sn+n] <- i
48 103
     attr(phy, "focus") <- foc
49 104
 
50 105
     ## sn <- which(df$focus != 1)
... ...
@@ -581,3 +636,12 @@ getYcoord_scale2 <- function(tr, df, yscale) {
581 636
     }
582 637
     return(y)
583 638
 }
639
+
640
+getYcoord_scale_category <- function(tr, df, yscale) {
641
+    y <- as.numeric(factor(df[, yscale]))
642
+    if (any(is.na(y))) {
643
+        warning("NA found in y scale mapping")
644
+        y[is.na(y)] <- 0
645
+    }
646
+    return(y)
647
+}
... ...
@@ -185,7 +185,9 @@ fortify.beast <- function(model, data,
185 185
     stats <- stats[,colnames(stats) != "node"]
186 186
     
187 187
     df <- cbind(df, stats)
188
-    scaleY(phylo, df, yscale, ...)
188
+    df <- scaleY(phylo, df, yscale, ...)
189
+
190
+    return(df)
189 191
 }
190 192
 
191 193
 
... ...
@@ -340,15 +342,14 @@ scaleY <- function(phylo, df, yscale, order.y = TRUE, ...) {
340 342
         warning("yscale is not available...\n")
341 343
         return(df)
342 344
     }
343
-    if (! is.numeric(df[, yscale])) {
344
-        warning("yscale should be numeric...\n")
345
-        return(df)
346
-    }
347
-
348
-    if (order.y) {
349
-        y <- getYcoord_scale2(phylo, df, yscale)
345
+    if (is.numeric(df[, yscale])) {
346
+        if (order.y) {
347
+            y <- getYcoord_scale2(phylo, df, yscale)
348
+        } else {
349
+            y <- getYcoord_scale(phylo, df, yscale)
350
+        }
350 351
     } else {
351
-        y <- getYcoord_scale(phylo, df, yscale)
352
+        y <- getYcoord_scale_category(phylo, df, yscale)
352 353
     }
353 354
     
354 355
     df[, "y"] <- y
... ...
@@ -275,3 +275,37 @@ roundDigit <- function(d) {
275 275
 }
276 276
 
277 277
 
278
+color_scale <- function(c1="grey", c2="red") {
279
+    pal <- colorRampPalette(c(c1, c2))
280
+    colors <- pal(100)
281
+    return(colors)
282
+}
283
+
284
+getIdx <- function(v, MIN, MAX) {
285
+    if (is.na(v)) {
286
+        return(NA)
287
+    }
288
+    if ( MIN == MAX ) {
289
+        return(100)
290
+    }
291
+    intervals <- seq(MIN, MAX, length.out=100)
292
+    max(which(intervals <= v))
293
+}
294
+
295
+
296
+get_color_attribute <- function(p) {
297
+    p$data[, "color"]
298
+}
299
+
300
+is.tree_attribute <- function(df, var) {
301
+    if(length(var) == 1 &&
302
+       !is.null(var)    &&
303
+       var %in% colnames(df)) {
304
+        return(TRUE)
305
+    } 
306
+    return(FALSE)
307
+}
308
+
309
+is.tree_attribute_ <- function(p, var) {
310
+    is.tree_attribute(p$data, var)
311
+}
... ...
@@ -4,11 +4,18 @@
4 4
 \alias{geom_tree}
5 5
 \title{geom_tree}
6 6
 \usage{
7
-geom_tree(layout = "phylogram", ...)
7
+geom_tree(layout = "phylogram", color = "black", linetype = "solid",
8
+  size = 1, ...)
8 9
 }
9 10
 \arguments{
10 11
 \item{layout}{one of phylogram, cladogram}
11 12
 
13
+\item{color}{color}
14
+
15
+\item{linetype}{line type}
16
+
17
+\item{size}{line size}
18
+
12 19
 \item{...}{additional parameter}
13 20
 }
14 21
 \value{
15 22
new file mode 100644
... ...
@@ -0,0 +1,45 @@
1
+% Generated by roxygen2 (4.1.0): do not edit by hand
2
+% Please edit documentation in R/AllGenerics.R, R/beast.R, R/codeml.R, R/codeml_mlc.R, R/hyphy.R, R/jplace.R, R/paml_rst.R, R/tree.R
3
+\docType{methods}
4
+\name{scale_color}
5
+\alias{scale_color}
6
+\alias{scale_color,beast-method}
7
+\alias{scale_color,codeml-method}
8
+\alias{scale_color,codeml_mlc-method}
9
+\alias{scale_color,hyphy-method}
10
+\alias{scale_color,jplace-method}
11
+\alias{scale_color,paml_rst-method}
12
+\alias{scale_color,phylo-method}
13
+\title{scale_color method}
14
+\usage{
15
+scale_color(object, by, ...)
16
+
17
+\S4method{scale_color}{beast}(object, by, ...)
18
+
19
+\S4method{scale_color}{codeml}(object, by, ...)
20
+
21
+\S4method{scale_color}{codeml_mlc}(object, by, ...)
22
+
23
+\S4method{scale_color}{hyphy}(object, by, ...)
24
+
25
+\S4method{scale_color}{jplace}(object, by, ...)
26
+
27
+\S4method{scale_color}{paml_rst}(object, by, ...)
28
+
29
+\S4method{scale_color}{phylo}(object, by, ...)
30
+}
31
+\arguments{
32
+\item{object}{supported objects, including phylo, paml_rst,
33
+codeml_mlc, codeml, jplace, beast, hyphy}
34
+
35
+\item{by}{one of numerical attributes}
36
+
37
+\item{...}{additional parameter}
38
+}
39
+\value{
40
+color vector
41
+}
42
+\description{
43
+scale_color method
44
+}
45
+
... ...
@@ -23,6 +23,8 @@ vignette: >
23 23
 
24 24
 ```{r style, echo=FALSE, results="hide", message=FALSE}
25 25
 BiocStyle::markdown()
26
+knitr::opts_chunk$set(tidy = FALSE,
27
+		   message = FALSE)
26 28
 ```
27 29
 
28 30
 
... ...
@@ -51,7 +53,7 @@ The `r Githubpkg("GuangchuangYu/ggtree")` is designed by extending the `r CRANpk
51 53
 # Tree visualization
52 54
 ## viewing tree with `ggtree`
53 55
 `r Githubpkg("GuangchuangYu/ggtree")` extend _`ggplot`_ to support viewing phylogenetic tree. It implements _`geom_tree`_ layer for displaying phylogenetic trees, as shown below:
54
-```{r fig.width=3, fig.height=3, tidy=TRUE, fig.align="center"}
56
+```{r fig.width=3, fig.height=3, fig.align="center"}
55 57
 nwk <- system.file("extdata", "sample.nwk", package="ggtree")
56 58
 x <- readLines(nwk)
57 59
 cat(substring(x, 1, 56), "\n", substring(x, 57), "\n")
... ...
@@ -227,13 +229,13 @@ beast
227 229
 ```
228 230
 Since _`%`_ is not a valid character in _`names`_, all the feature names that contain _`x%`_ will convert to _`0.x`_. For example, _`length_95%_HPD`_ will be changed to _`length_0.95_HPD`_.
229 231
 
230
-```{r fig.width=8, tidy=TRUE, width=60, warning=FALSE, fig.align="center"}
232
+```{r fig.width=8, width=60, warning=FALSE, fig.align="center"}
231 233
 plot(beast, annotation="length_0.95_HPD", branch.length="none") + theme_tree()
232 234
 ```
233 235
 
234 236
 User can round the digits by setting the parameter _`ndigits`_. The default value is 2.
235 237
 
236
-```{r fig.width=8, tidy=TRUE, width=60, warning=FALSE, fig.align="center"}
238
+```{r fig.width=8, width=60, warning=FALSE, fig.align="center"}
237 239
 plot(beast, annotation="height", ndigits=3, annotation.color="red")
238 240
 ```
239 241
 
... ...
@@ -268,7 +270,7 @@ baseml <- read.baseml(rstfile, mlbfile)
268 270
 baseml
269 271
 ```
270 272
 
271
-```{r fig.width=10, fig.height=8, tidy=TRUE, width=60, warning=FALSE}
273
+```{r fig.width=10, fig.height=8, width=60, warning=FALSE}
272 274
 p <- plot(rst, annotation="marginal_AA_subs", annotation.color="steelblue")
273 275
 print(p)
274 276
 ```
... ...
@@ -289,7 +291,7 @@ _`rst`_ file from _`CODEML`_ is similar to _`BASEML`_, and also parsed by _`read
289 291
 If you remember the _`%<%`_ operator introduced in [`update tree viewing with a new tree`](#update-tree-viewing-with-a-new-tree) session, you can use it to update a tree view with a new object.
290 292
 
291 293
 In last session, we use _`rstfile`_ of _`BASEML`_ to build a tree view with amino acid substitution annotated. The following example use another _`rstfile`_ from _`CODEML`_ to update the tree view.
292
-```{r fig.width=8, tidy=TRUE, width=60, warning=FALSE, fig.align="center"}
294
+```{r fig.width=8, width=60, warning=FALSE, fig.align="center"}
293 295
 rstfile <- system.file("extdata/PAML_Codeml", "rst", package="ggtree")
294 296
 rst <- read.paml_rst(rstfile, tipfas)
295 297
 p %<% rst
... ...
@@ -314,7 +316,7 @@ Please aware that _`/`_ and _`*`_ are not valid characters in _`names`_, they we
314 316
 So _`dN_vs_dS`_ is _`dN/dS`_, _`N_x_dN`_ is _`N*dN`_, and _`S_x_dS`_ is _`S*dS`_.
315 317
 
316 318
 
317
-```{r fig.width=8, tidy=TRUE, width=60, warning=FALSE, fig.align="center"}
319
+```{r fig.width=8, width=60, warning=FALSE, fig.align="center"}
318 320
 plot(mlc, branch.length="branch.length", annotation="dN_vs_dS", annotation.color="blue", ndigits=3)
319 321
 ```
320 322
 
... ...
@@ -324,7 +326,7 @@ get.fields(mlc)
324 326
 ```
325 327
 
326 328
 For example, if we set _`branch.length`_ to _`dN_vs_dS`_, it will plot the $\omega$ (_`dN/dS`_) tree:
327
-```{r fig.width=8, tidy=TRUE, width=60, warning=FALSE, fig.align="center"}
329
+```{r fig.width=8, width=60, warning=FALSE, fig.align="center"}
328 330
 plot(mlc, branch.length="dN_vs_dS", annotation="dN_vs_dS", ndigits=3)
329 331
 ```
330 332
 
... ...
@@ -346,7 +348,7 @@ ml
346 348
 
347 349
 So we can annotate _`dN/dS`_ with the tree in _`rstfile`_ and amino acid substitutions with the tree in _`mlcfile`_.
348 350
 
349
-```{r fig.width=12, fig.height=8, tidy=TRUE, width=60, warning=FALSE, fig.align="center"}
351
+```{r fig.width=12, fig.height=8, width=60, warning=FALSE, fig.align="center"}
350 352
 plot(ml, branch.length="rst.branch.length", annotation="dN_vs_dS")
351 353
 plot(ml, branch.length="mlc.branch.length", annotation="marginal_AA_subs")
352 354
 plot(ml, branch.length="dN", annotation="joint_AA_subs", annotation.color="darkgreen")
... ...
@@ -360,7 +362,7 @@ hy <- read.hyphy(nwk, ancseq, tipfas)
360 362
 hy
361 363
 ```
362 364
 
363
-```{r fig.width=12, fig.height=10, tidy=TRUE, width=60, warning=FALSE, fig.align="center"}
365
+```{r fig.width=12, fig.height=10, width=60, warning=FALSE, fig.align="center"}
364 366
 plot(hy, annotation="AA_subs")
365 367
 ```
366 368
 
... ...
@@ -393,7 +395,7 @@ We may, for example, count the number of placement and annotate this information
393 395
 We implemented several _`plot`_ methods for easily viewing annotation data. Users are not restricted to _`plot`_ methods provided. They can use _`geom_text`_ to add annotation layer. All annotation data are visible to _`ggplot2`_.
394 396
 
395 397
 In the following example, we use the _`codeml`_ object to visualize the $\omega$ (_`dN/dS`_) tree, and annotate the tree with _`dN`_ and _`dS`_.
396
-```{r fig.width=12, fig.height=10, tidy=TRUE, width=60, warning=FALSE, fig.align="center"}
398
+```{r fig.width=12, fig.height=10, width=60, warning=FALSE, fig.align="center"}
397 399
 ggtree(ml, branch.length="dN_vs_dS") + 
398 400
 	   geom_text(aes(x=branch, label=dN), 
399 401
 	   	     size=3, vjust=-0.5, color="red") +
... ...
@@ -531,6 +533,20 @@ library("ggtree")
531 533
 gzoom(chiroptera, grep("Plecotus", chiroptera$tip.label))
532 534
 ```
533 535
 
536
+## scale color based on numerical attribute
537
+
538
+`r Githubpkg("GuangchuangYu/ggtree")` provides _`scale_color`_ to calculate colors based on numerical attribute of the tree. The output can be used to color lines and annotation text.
539
+```{r fig.width=12, fig.height=6, fig.align="center", warning=FALSE}
540
+cols = scale_color(ml, by="dN")
541
+ggtree(ml, color=cols) + geom_text(aes(label=label), color=cols, hjust=.25)
542
+```
543
+
544
+_`scale_color`_ will auto determine the color. User can also provide parameter _`low`_ and _`high`_ to speicify the color scale.
545
+
546
+```{r fig.width=12, fig.height=6, fig.align="center", warning=FALSE}
547
+cols = scale_color(ml, by="dN", low="green", high="red")
548
+ggtree(ml, color=cols) + geom_text(aes(label=label), color=cols, hjust=.25)
549
+```
534 550
 
535 551
 ## group OTUs
536 552
 
... ...
@@ -544,7 +560,7 @@ tree <- read.tree(nwk)
544 560
 cluster_index <- groupOTU(tree, focus=c("A", "B", "C", "D", "E"))
545 561
 cluster_index
546 562
 ```
547
-In the _`cluster_index`_, _`1`_ represent the cluster that not selected, while other number represent the corresponding selected group(s).
563
+In the _`cluster_index`_, **1** represent the cluster that not selected, while other number represent the corresponding selected group(s).
548 564
 
549 565
 ```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
550 566
 ggtree(tree, color=c("black", "red")[cluster_index])
... ...
@@ -562,19 +578,21 @@ cls_ind <- groupOTU(tree, cls)
562 578
 library("colorspace")
563 579
 cols <- rainbow_hcl(4)
564 580
 cols <- c("black", cols)
565
-ggtree(tree, color=cols[cls_ind]) + geom_tiplab()
581
+ggtree(tree, color=cols[cls_ind]) + geom_text(aes(label=label), color=cols[cls_ind], hjust=-.25)
566 582
 ```
567 583
 
568 584
 We can change the linetype either:
569 585
 ```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
570 586
 linetype <- c("solid", "dotted", "dashed", "dotdash", "longdash")
571
-ggtree(tree, color=cols[cls_ind], linetype=linetype[cls_ind]) + geom_tiplab()
587
+ggtree(tree, color=cols[cls_ind], linetype=linetype[cls_ind]) +
588
+      geom_text(aes(label=label), color=cols[cls_ind], hjust=-.25)
572 589
 ```
573 590
 
574 591
 And also size:
575 592
 ```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
576 593
 size <- 1:5
577
-ggtree(tree, color=cols[cls_ind], linetype=linetype[cls_ind], size=size[cls_ind]) + geom_tiplab()
594
+ggtree(tree, color=cols[cls_ind], linetype=linetype[cls_ind], size=size[cls_ind]) +
595
+      geom_text(aes(label=label), color=cols[cls_ind], hjust=-.25)
578 596
 ```
579 597
 
580 598
 All the tree classes defined in `r Githubpkg("GuangchuangYu/ggtree")`, including _`beast`_, _`paml_rst`_, _`codeml_mlc`_, _`codeml`_, _`hyphy`_ and _`jplace`_ are all supported.
... ...
@@ -588,16 +606,26 @@ ggtree(ml, color=cols[ind])
588 606
 
589 607
 ### iris example
590 608
 
591
-In this example, we first build a tree based on the iris data.
609
+In this example, we first build a tree based on the iris data, then grouping the tree based on different spacies.
592 610
 ```{r fig.width=20, fig.height=20, fig.align="center", warning=FALSE}
593 611
 data(iris)
594
-rownames(iris) <- paste0(iris[,5], "_", 1:150)
612
+rn <- paste0(iris[,5], "_", 1:150)
613
+rownames(iris) <- rn
595 614
 d_iris <- dist(iris[,-5], method="man")
596 615
 
597 616
 tree_iris <- bionj(d_iris)
598
-ggtree(tree_iris) + geom_text(aes(label=node))
617
+cls_ind <- groupOTU(tree_iris, list(setosa    = rn[1:50],
618
+				versicolor    = rn[51:100],
619
+				virginica_145 = rn[101:150]))
620
+cols <- rainbow_hcl(4)
621
+ggtree(tree_iris, color=cols[cls_ind]) +
622
+     geom_text(aes(label=label), color=cols[cls_ind], hjust=-.1)
599 623
 ```
600 624
 
625
+<!--
626
+```
627
+ggtree(tree_iris) + geom_text(aes(label=node))
628
+```
601 629
 By adding a layer of internal node number, we can easily extract tip labels of a particular clade by the _`get.offspring.tip`_ function.
602 630
 ```{r}
603 631
 cl1 <- get.offspring.tip(tree_iris, 242)
... ...
@@ -618,6 +646,8 @@ ggtree(tree_iris, color=cols[cls_ind]) %<+% species +
618 646
      geom_text(aes(label=label, color=species), hjust=-0.1) +
619 647
          scale_color_manual(values=cols[2:4])
620 648
 ```
649
+-->
650
+
621 651
 
622 652
 This example demonstrates how the separation of the _`bionj`_ is very good with the _`setosa`_ species, but misses in labeling several _`versicolor`_ and _`virginica`_ species.
623 653