Browse code

better geom_tree/groupClade/groupOTU implementation & annotation_clade/annotation_clade2 functions

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

Guangchuang Yu authored on 31/07/2015 10:15:38
Showing 24 changed files

... ...
@@ -1,3 +1,5 @@
1 1
 TODO.md
2 2
 .travis.yml
3 3
 appveyor.yml
4
+.gitignore
5
+.svnignore
... ...
@@ -2,3 +2,4 @@
2 2
 R/.DS_Store
3 3
 vignettes/.DS_Store
4 4
 
5
+.svn
5 6
new file mode 100644
... ...
@@ -0,0 +1 @@
1
+.git
... ...
@@ -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.1.10
4
+Version: 1.1.12
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
... ...
@@ -17,6 +17,8 @@ export(.)
17 17
 export(add_colorbar)
18 18
 export(add_legend)
19 19
 export(aes)
20
+export(annotation_clade)
21
+export(annotation_clade2)
20 22
 export(as.binary)
21 23
 export(collapse)
22 24
 export(download.phylopic)
... ...
@@ -141,7 +143,9 @@ importFrom(ggplot2,xlim)
141 143
 importFrom(ggplot2,ylab)
142 144
 importFrom(grDevices,col2rgb)
143 145
 importFrom(grDevices,rgb)
146
+importFrom(grid,linesGrob)
144 147
 importFrom(grid,rasterGrob)
148
+importFrom(grid,textGrob)
145 149
 importFrom(grid,unit)
146 150
 importFrom(gridExtra,grid.arrange)
147 151
 importFrom(jsonlite,fromJSON)
... ...
@@ -1,3 +1,18 @@
1
+CHANGES IN VERSION 1.1.12
2
+------------------------
3
+ o update vignette according to the changes <2015-07-31, Fri>
4
+ o add mapping parameter in ggtree function <2015-07-31, Fri>
5
+ o extend groupClade to support operating on tree view <2015-07-31, Fri>
6
+ o extend groupOTU to support operating on tree view <2015-07-31, Fri>
7
+ o new implementation of groupClade & groupOTU <2015-07-31, Fri>
8
+ 
9
+CHANGES IN VERSION 1.1.11
10
+------------------------
11
+ o annotation_clade and annotation_clade2 functions. <2015-07-30, Thu>
12
+ o better add_legend implementation. <2015-07-30, Thu>
13
+ o add ... in theme_tree & theme_tree2 for accepting additional parameter. <2015-07-30, Thu>
14
+ o better geom_tree implementation. Now we can scale the tree with aes(color=numVar). <2015-07-30, Thu>
15
+ 
1 16
 CHANGES IN VERSION 1.1.10
2 17
 ------------------------
3 18
  o solve overlapping branches for layout = "fan" || "radial",
... ...
@@ -1,4 +1,6 @@
1 1
 setOldClass("phylo")
2
+setOldClass("gg")
3
+setOldClass("ggplot")
2 4
 
3 5
 
4 6
 ##' Class "hyphy"
... ...
@@ -3,6 +3,7 @@
3 3
 ##' 
4 4
 ##' @title ggtree
5 5
 ##' @param tr phylo object
6
+##' @param mapping aes mapping
6 7
 ##' @param showDistance add distance legend, logical
7 8
 ##' @param layout one of phylogram, dendrogram, cladogram, fan, radial and unrooted
8 9
 ##' @param yscale y scale
... ...
@@ -27,6 +28,7 @@
27 28
 ##' tr <- rtree(10)
28 29
 ##' ggtree(tr)
29 30
 ggtree <- function(tr,
31
+                   mapping = NULL,
30 32
                    showDistance=FALSE,
31 33
                    layout="phylogram",
32 34
                    yscale="none",
... ...
@@ -34,6 +36,10 @@ ggtree <- function(tr,
34 36
                    branch.length="branch.length",
35 37
                    ndigits = NULL, ...) {
36 38
     d <- x <- y <- NULL
39
+    if(yscale != "none") {
40
+        ## for 2d tree
41
+        layout <- "cladogram"
42
+    }
37 43
     if (layout == "fan") {
38 44
         ## layout <- "phylogram"
39 45
         type <- "fan"
... ...
@@ -46,7 +52,12 @@ ggtree <- function(tr,
46 52
     } else {
47 53
         type <- "none"
48 54
     }
49
-    p <- ggplot(tr, aes(x, y),
55
+    if (is.null(mapping)) {
56
+        mapping <- aes(x, y)
57
+    } else {
58
+        mapping <- modifyList(aes(x, y), mapping)
59
+    }
60
+    p <- ggplot(tr, mapping=mapping,
50 61
                 layout        = layout,
51 62
                 yscale        = yscale,
52 63
                 ladderize     = ladderize,
... ...
@@ -81,9 +92,6 @@ ggtree <- function(tr,
81 92
 ##' 
82 93
 ##' @title geom_tree
83 94
 ##' @param layout one of phylogram, cladogram
84
-##' @param color color
85
-##' @param linetype line type
86
-##' @param size line size
87 95
 ##' @param ... additional parameter
88 96
 ##' @return tree layer
89 97
 ##' @importFrom ggplot2 geom_segment
... ...
@@ -95,35 +103,28 @@ ggtree <- function(tr,
95 103
 ##' tr <- rtree(10)
96 104
 ##' require(ggplot2)
97 105
 ##' ggplot(tr) + geom_tree()
98
-geom_tree <- function(layout="phylogram", color="black", linetype="solid", size=0.5, ...) {
106
+geom_tree <- function(layout="phylogram", ...) {
99 107
     x <- y <- parent <- NULL
100 108
     lineend  = "round"
101 109
     if (layout == "phylogram" || layout == "fan") {
102
-        if (length(color) != 1) {
103
-            color <- rep(color, 2) ## c(color, color)
104
-        }
105
-        if (length(linetype) != 1) {
106
-            linetype <- rep(linetype, 2) ## c(linetype, linetype)
107
-        }
108
-        if (length(size) != 1) {
109
-            size <- rep(size, 2) ## c(size, size)
110
-        }
111
-        geom_segment(aes(x    = c(x[parent], x[parent]),
112
-                         xend = c(x,         x[parent]),
113
-                         y    = c(y,         y[parent]),
114
-                         yend = c(y,         y)),
115
-                     color    = color,
116
-                     linetype = linetype,
117
-                     size     = size,
118
-                     lineend  = lineend, ...)
110
+        list(
111
+            geom_segment(aes(x    = x[parent],
112
+                             xend = x,
113
+                             y    = y,
114
+                             yend = y),
115
+                         lineend  = lineend, ...),
116
+            
117
+            geom_segment(aes(x    = x[parent],
118
+                             xend = x[parent],
119
+                             y    = y[parent],
120
+                             yend = y),
121
+                         lineend  = lineend, ...)
122
+            )
119 123
     } else if (layout == "cladogram" || layout == "unrooted") {
120 124
         geom_segment(aes(x    = x[parent],
121 125
                          xend = x,
122 126
                          y    = y[parent],
123 127
                          yend = y),
124
-                     color    = color,
125
-                     linetype = linetype,
126
-                     size     = size,
127 128
                      lineend  = lineend, ...)
128 129
     }
129 130
 }
... ...
@@ -222,6 +223,7 @@ geom_tippoint <- function(...) {
222 223
 ##' @title theme_tree
223 224
 ##' @param bgcolor background color
224 225
 ##' @param fgcolor foreground color
226
+##' @param ... additional parameter
225 227
 ##' @importFrom ggplot2 theme_bw
226 228
 ##' @importFrom ggplot2 theme
227 229
 ##' @importFrom ggplot2 element_blank
... ...
@@ -233,13 +235,13 @@ geom_tippoint <- function(...) {
233 235
 ##' require(ape)
234 236
 ##' tr <- rtree(10)
235 237
 ##' ggtree(tr) + theme_tree()
236
-theme_tree <- function(bgcolor="white", fgcolor="black") {
238
+theme_tree <- function(bgcolor="white", fgcolor="black", ...) {
237 239
     theme_tree2() %+replace%
238 240
     theme(panel.background=element_rect(fill=bgcolor, colour=bgcolor),
239 241
           axis.line.x = element_line(color=bgcolor),
240 242
           axis.text.x = element_blank(),
241
-          axis.ticks.x = element_blank()
242
-          )
243
+          axis.ticks.x = element_blank(),
244
+          ...)
243 245
 }
244 246
 
245 247
 ##' tree2 theme
... ...
@@ -248,6 +250,7 @@ theme_tree <- function(bgcolor="white", fgcolor="black") {
248 250
 ##' @title theme_tree2
249 251
 ##' @param bgcolor background color
250 252
 ##' @param fgcolor foreground color
253
+##' @param ... additional parameter
251 254
 ##' @importFrom ggplot2 theme_bw
252 255
 ##' @importFrom ggplot2 theme
253 256
 ##' @importFrom ggplot2 element_blank
... ...
@@ -261,7 +264,7 @@ theme_tree <- function(bgcolor="white", fgcolor="black") {
261 264
 ##' require(ape)
262 265
 ##' tr <- rtree(10)
263 266
 ##' ggtree(tr) + theme_tree2()
264
-theme_tree2 <- function(bgcolor="white", fgcolor="black") {
267
+theme_tree2 <- function(bgcolor="white", fgcolor="black", ...) {
265 268
     theme_bw() %+replace%
266 269
     theme(legend.position="none",
267 270
           panel.grid.minor=element_blank(),
... ...
@@ -271,8 +274,8 @@ theme_tree2 <- function(bgcolor="white", fgcolor="black") {
271 274
           axis.line=element_line(color=fgcolor),
272 275
           axis.line.y=element_line(color=bgcolor),
273 276
           axis.ticks.y=element_blank(),
274
-          axis.text.y=element_blank()
275
-          )
277
+          axis.text.y=element_blank(),
278
+          ...)
276 279
 }
277 280
 
278 281
 ##' hilight clade with rectangle
... ...
@@ -616,18 +619,24 @@ add_colorbar <- function(p, color, x=NULL, ymin=NULL, ymax=NULL, font.size=4) {
616 619
 ##' @param font.size font size
617 620
 ##' @param ... additional parameter
618 621
 ##' @return tree view
622
+##' @importFrom grid linesGrob
623
+##' @importFrom grid textGrob
619 624
 ##' @export
620 625
 ##' @author Guangchuang Yu
621 626
 add_legend <- function(p, x=NULL, y=NULL, offset=NULL, font.size=4, ...) {
627
+    dx <- p$data$x %>% range %>% diff
628
+    
622 629
     if (is.null(x)) {
623
-        x <- min(p$data$x)
630
+        ## x <- min(p$data$x)
631
+        x <- dx/2
624 632
     }
625 633
     if (is.null(y)) {
626
-        y <- -0.5
634
+        y <- 0
635
+        p <- p + ylim(0, max(p$data$y))
627 636
     }
628 637
 
629
-    d <- p$data$x %>% range %>% diff
630
-    d <- d/20 
638
+
639
+    d <- dx/10 
631 640
     n <- 0
632 641
     while (d < 1) {
633 642
         d <- d*10
... ...
@@ -635,13 +644,10 @@ add_legend <- function(p, x=NULL, y=NULL, offset=NULL, font.size=4, ...) {
635 644
     }
636 645
     d <- floor(d)/(10^n)
637 646
     if (is.null(offset)) {
638
-        offset <- p$data$y %>% range %>% diff
639
-        offset <- offset / 100
647
+        offset <- 0.4
640 648
     }
641
-    p <- p + geom_segment(x=x, y=y, xend=x+d, yend=y, ...) +
642
-        geom_text(x=x+d/2, y=y-offset, label=d, size=font.size, ...) +
643
-            geom_segment(x=x, y=y-offset/2, xend=x, yend=y+offset/2, ...) +
644
-                geom_segment(x=x+d, y=y-offset/2, xend=x+d, yend=y+offset/2, ...)
649
+    p <- p + annotation_custom(linesGrob(), xmin=x, xmax=x+d, ymin=y, ymax=y) +
650
+        annotation_custom(textGrob(label=d), xmin=x+d/2, xmax=x+d/2, ymin=y+offset, ymax=y+offset)
645 651
     return(p)
646 652
 }
647 653
 
... ...
@@ -660,3 +666,116 @@ get_taxa_name <- function(tree_view, node) {
660 666
     res <- df[sp, "label"]
661 667
     return(res[df[sp, "isTip"]])
662 668
 }
669
+
670
+##' annotate a selected clade with internal node number
671
+##'
672
+##' 
673
+##' @title annotation_clade
674
+##' @param tree_view tree view
675
+##' @param node node number
676
+##' @param label clade label
677
+##' @param bar.size bar size
678
+##' @param font.size font size
679
+##' @param offset offset of bar from the tree
680
+##' @param offset.text offset of label from bar
681
+##' @param ... additional parameter
682
+##' @export
683
+##' @return ggplot2
684
+##' @author Guangchuang Yu
685
+annotation_clade <- function(tree_view, node, label, bar.size=2, font.size=4, offset=0, offset.text=NULL, ...) {
686
+    df <- tree_view$data
687
+    sp <- get.offspring.df(df, node)
688
+    sp.df <- df[c(sp, node), ]
689
+    y <- sp.df$y
690
+
691
+    mx <- max(p$data$x) + offset
692
+    annotation_clade_internal(tree_view, mx, y, label, bar.size, font.size, offset.text, ...)
693
+}
694
+
695
+
696
+##' annotate a clade with selected upper and lower tips
697
+##'
698
+##' 
699
+##' @title annotation_clade2
700
+##' @param tree_view tree view
701
+##' @param tip1 tip1 label or id
702
+##' @param tip2 tip2 label or id
703
+##' @param label clade label
704
+##' @param bar.size bar size
705
+##' @param font.size font size
706
+##' @param offset offset of bar from the tree
707
+##' @param offset.text offset of label from bar
708
+##' @param ... additional parameter
709
+##' @export
710
+##' @return ggplot2
711
+##' @author Guangchuang Yu
712
+annotation_clade2 <- function(tree_view, tip1, tip2, label, bar.size=2, font.size=4, offset=0, offset.text=NULL, ...) {
713
+    df <- tree_view$data
714
+    
715
+    y <- c(df[which(tip1 == df$label | tip1 == df$node), "y"],
716
+           df[which(tip2 == df$label | tip2 == df$node), "y"])
717
+    
718
+    mx <- max(p$data$x) + offset
719
+    annotation_clade_internal(tree_view, mx, y, label, bar.size, font.size, offset.text, ...)
720
+}
721
+
722
+
723
+annotation_clade_internal <- function(tree_view, x, y, label, bar.size, font.size, offset.text, ...) {
724
+    mx <- x
725
+    if (is.null(offset.text)) {
726
+        offset.text <- mx * 0.02
727
+    }
728
+    tree_view + geom_segment(x=mx, xend=mx, y=min(y), yend=max(y), size=bar.size, ...) +
729
+        annotate("text", label=label, x=mx+offset.text, y=mean(y), angle=270, size=font.size, ...)
730
+}
731
+
732
+##' @rdname groupOTU-methods
733
+##' @exportMethod groupOTU
734
+setMethod("groupOTU", signature(object="ggplot"),
735
+          function(object, focus) {
736
+              groupOTU.ggplot(object, focus)
737
+          })
738
+
739
+
740
+##' @rdname groupOTU-methods
741
+##' @exportMethod groupOTU
742
+setMethod("groupOTU", signature(object="gg"),
743
+          function(object, focus) {
744
+              groupOTU.ggplot(object, focus)
745
+          })
746
+
747
+
748
+##' @rdname groupClade-methods
749
+##' @exportMethod groupClade
750
+setMethod("groupClade", signature(object="ggplot"),
751
+          function(object, node) {
752
+              groupClade.ggplot(object, node)
753
+          })
754
+
755
+
756
+##' @rdname groupClade-methods
757
+##' @exportMethod groupClade
758
+setMethod("groupClade", signature(object="gg"),
759
+          function(object, node) {
760
+              groupClade.ggplot(object, node)
761
+          })
762
+
763
+
764
+groupClade.ggplot <- function(object, nodes) {
765
+    df <- object$data
766
+    group_name <- "group"
767
+    df[, group_name] <- 0
768
+    for (node in nodes) {
769
+        df <- groupClade.df(df, node, group_name)
770
+    }
771
+    df$group <- factor(df$group)
772
+    object$data <- df
773
+    return(object)
774
+}
775
+
776
+groupClade.df <- function(df, node, group_name) {
777
+    foc <- c(node, get.offspring.df(df, node))
778
+    idx <- match(foc, df$node)
779
+    df[idx, group_name] <- max(df$group) + 1
780
+    return(df)
781
+}
... ...
@@ -27,17 +27,19 @@ setMethod("groupOTU", signature(object="phylo"),
27 27
 ##' @title groupOTU.phylo
28 28
 ##' @param phy tree object
29 29
 ##' @param focus tip list
30
-##' @return cluster index
30
+##' @return phylo object
31 31
 ##' @author ygc
32
-groupOTU.phylo <- function(phy, focus) {
32
+groupOTU.phylo <- function(phy, focus, group_name="group") {
33
+    attr(phy, group_name) <- NULL
33 34
     if ( is(focus, "list") ) {
34 35
         for (i in 1:length(focus)) {
35
-            phy <- gfocus(phy, focus[[i]])
36
+            phy <- gfocus(phy, focus[[i]], group_name)
36 37
         } 
37 38
     } else {
38
-        phy <- gfocus(phy, focus)
39
+        phy <- gfocus(phy, focus, group_name)
39 40
     }
40
-    attr(phy, "focus")
41
+    attr(phy, group_name) <- factor(attr(phy, group_name))
42
+    return(phy)
41 43
 }
42 44
 
43 45
 ##' @rdname groupClade-methods
... ...
@@ -58,7 +60,7 @@ groupClade.phylo <- function(object, node) {
58 60
         })
59 61
     }
60 62
     
61
-    groupOTU.phylo(object, tips)
63
+    groupOTU.phylo(object, tips, "group")
62 64
 }
63 65
 
64 66
 
... ...
@@ -56,36 +56,39 @@ scale_color_ <- function(phylo, by, low=NULL, high=NULL, na.color=NULL, default.
56 56
 }
57 57
 
58 58
 groupClade_ <- function(object, node) {
59
-    groupClade.phylo(get.tree(object), node)
59
+    if (is(object, "phylo")) {
60
+        object <- groupClade.phylo(object, node)
61
+    } else {
62
+        object@phylo <- groupClade.phylo(get.tree(object), node)
63
+    }
64
+    return(object)
60 65
 }
61 66
 
62 67
 groupOTU_ <- function(object, focus) {
63
-    groupOTU.phylo(get.tree(object), focus)
68
+    if (is(object, "phylo")) {
69
+        object <- groupOTU.phylo(object, focus)
70
+    } else {
71
+        object@phylo <- groupOTU.phylo(get.tree(object), focus)
72
+    }
73
+    return(object)
64 74
 }
65 75
 
66 76
 ##' @importFrom ape which.edge
67
-gfocus <- function(phy, focus) {
77
+gfocus <- function(phy, focus, group_name) {
68 78
     if (is.character(focus)) {
69 79
         focus <- which(phy$tip.label %in% focus)
70 80
     }
71 81
     
72 82
     n <- getNodeNum(phy)
73
-    if (is.null(attr(phy, "focus"))) {
74
-        ## foc <- rep(1, 2*n)
75
-        foc <- rep(1, n)
83
+    if (is.null(attr(phy, group_name))) {
84
+        foc <- rep(0, n)
76 85
     } else {
77
-        foc <- attr(phy, "focus")
86
+        foc <- attr(phy, group_name)
78 87
     }
79 88
     i <- max(foc) + 1
80 89
     sn <- phy$edge[which.edge(phy, focus),] %>% as.vector %>% unique
81 90
     foc[sn] <- i
82
-    ## foc[sn+n] <- i
83
-    attr(phy, "focus") <- foc
84
-
85
-    ## sn <- which(df$focus != 1)
86
-    ## df$focus[df$parent] -> f2
87
-    ## f2[-sn] <- 1
88
-
91
+    attr(phy, group_name) <- foc
89 92
     phy
90 93
 }
91 94
 
... ...
@@ -111,10 +114,12 @@ gzoom.phylo <- function(phy, focus, subtree=FALSE, widths=c(.3, .7)) {
111 114
         focus <- which(phy$tip.label %in% focus)
112 115
     }
113 116
 
114
-    phy <- gfocus(phy, focus)
117
+    group_name <- "focus"
118
+    phy <- gfocus(phy, focus, group_name)
115 119
 
116
-    foc <- attr(phy, "focus")
117
-    cols <- c("black", "red")[foc]
120
+    foc <- attr(phy, group_name)
121
+    ## foc should +1 since the group index start from 0
122
+    cols <- c("black", "red")[foc+1]
118 123
 
119 124
     p1 <- ggtree(phy, color=cols)
120 125
     
... ...
@@ -454,6 +454,9 @@ fortify.phylo <- function(model, data, layout="phylogram",
454 454
     if(layout == "cladogram") {
455 455
         df <- add_angle_cladogram(df)
456 456
     }
457
+    if (!is.null(attr(tree, "group"))) {
458
+        df$group <- attr(tree, "group")
459
+    }
457 460
     return(df)
458 461
 }
459 462
 
... ...
@@ -524,7 +527,7 @@ as.data.frame.phylo_ <- function(x, layout="phylogram",
524 527
     
525 528
     if (layout == "fan") {
526 529
         idx <- match(1:N, order(res$y))
527
-        angle <- -360/N * 1:N
530
+        angle <- -360/(N+1) * (1:N + 1)
528 531
         angle <- angle[idx]
529 532
         res$angle <- angle
530 533
     } 
... ...
@@ -469,3 +469,47 @@ getCols <- function (n) {
469 469
               "#ffff99", "#b15928")
470 470
     colorRampPalette(col3)(n)
471 471
 }
472
+
473
+
474
+groupOTU.ggplot <- function(object, focus) {
475
+    df <- object$data
476
+    group_name <- "group"
477
+    df[, group_name] <- 0
478
+    object$data <- groupOTU.df(df, focus, group_name)
479
+    return(object)     
480
+}
481
+
482
+
483
+groupOTU.df <- function(df, focus, group_name) {    
484
+    if (is(focus, "list")) {
485
+        for (i in 1:length(focus)) {
486
+            df <- gfocus.df(df, focus[[i]], group_name)
487
+        }
488
+    } else {
489
+        df <- gfocus.df(df, focus, group_name)
490
+    }
491
+    df$group <- factor(df$group)
492
+    return(df)
493
+}
494
+
495
+gfocus.df <- function(df, focus, group_name) {
496
+    focus <- df$node[which(df$label %in% focus)]
497
+    if (length(focus) == 1) {
498
+        df[match(focus, df$node), group_name] <- max(df(df$group)) + 1
499
+        return(df)
500
+    }
501
+    
502
+    anc <- getAncestor.df(df, focus[1])
503
+    foc <- c(focus[1], anc)
504
+    for (j in 2:length(focus)) {
505
+        anc2 <- getAncestor.df(df, focus[j])
506
+        comAnc <- intersect(anc, anc2)
507
+        foc <- c(foc, focus[j], anc2)
508
+        foc <- foc[! foc %in% comAnc]
509
+        foc <- c(foc, comAnc[1])
510
+    }
511
+    idx <- match(foc, df$node)
512
+    df[idx, group_name] <- max(df$group) + 1
513
+    return(df)
514
+}
515
+
... ...
@@ -34,6 +34,7 @@ To install:
34 34
 + [viewing and annotating phylogenetic tree with ggtree](http://ygc.name/2014/12/21/ggtree/)
35 35
 + [updating a tree view using %<% operator](http://ygc.name/2015/02/10/ggtree-updating-a-tree-view/)
36 36
 + [an example of drawing beast tree using ggtree](http://ygc.name/2015/04/01/an-example-of-drawing-beast-tree-using-ggtree/)
37
++ [flip and rotate branches in ggtree](http://ygc.name/2015/07/01/flip-and-rotate-branches-in-ggtree/)
37 38
 
38 39
 To view the vignette of `ggtree` installed in your system, start `R` and enter:
39 40
 ```r
40 41
new file mode 100644
... ...
@@ -0,0 +1,5 @@
1
+
2
+as.phylo.igraph(x) {
3
+    edge <- get.edgelist(x)
4
+    
5
+}
0 6
new file mode 100644
... ...
@@ -0,0 +1,36 @@
1
+% Generated by roxygen2 (4.1.1): do not edit by hand
2
+% Please edit documentation in R/ggtree.R
3
+\name{annotation_clade}
4
+\alias{annotation_clade}
5
+\title{annotation_clade}
6
+\usage{
7
+annotation_clade(tree_view, node, label, bar.size = 2, font.size = 4,
8
+  offset = 0, offset.text = NULL, ...)
9
+}
10
+\arguments{
11
+\item{tree_view}{tree view}
12
+
13
+\item{node}{node number}
14
+
15
+\item{label}{clade label}
16
+
17
+\item{bar.size}{bar size}
18
+
19
+\item{font.size}{font size}
20
+
21
+\item{offset}{offset of bar from the tree}
22
+
23
+\item{offset.text}{offset of label from bar}
24
+
25
+\item{...}{additional parameter}
26
+}
27
+\value{
28
+ggplot2
29
+}
30
+\description{
31
+annotate a selected clade with internal node number
32
+}
33
+\author{
34
+Guangchuang Yu
35
+}
36
+
0 37
new file mode 100644
... ...
@@ -0,0 +1,38 @@
1
+% Generated by roxygen2 (4.1.1): do not edit by hand
2
+% Please edit documentation in R/ggtree.R
3
+\name{annotation_clade2}
4
+\alias{annotation_clade2}
5
+\title{annotation_clade2}
6
+\usage{
7
+annotation_clade2(tree_view, tip1, tip2, label, bar.size = 2, font.size = 4,
8
+  offset = 0, offset.text = NULL, ...)
9
+}
10
+\arguments{
11
+\item{tree_view}{tree view}
12
+
13
+\item{tip1}{tip1 label or id}
14
+
15
+\item{tip2}{tip2 label or id}
16
+
17
+\item{label}{clade label}
18
+
19
+\item{bar.size}{bar size}
20
+
21
+\item{font.size}{font size}
22
+
23
+\item{offset}{offset of bar from the tree}
24
+
25
+\item{offset.text}{offset of label from bar}
26
+
27
+\item{...}{additional parameter}
28
+}
29
+\value{
30
+ggplot2
31
+}
32
+\description{
33
+annotate a clade with selected upper and lower tips
34
+}
35
+\author{
36
+Guangchuang Yu
37
+}
38
+
... ...
@@ -4,18 +4,11 @@
4 4
 \alias{geom_tree}
5 5
 \title{geom_tree}
6 6
 \usage{
7
-geom_tree(layout = "phylogram", color = "black", linetype = "solid",
8
-  size = 0.5, ...)
7
+geom_tree(layout = "phylogram", ...)
9 8
 }
10 9
 \arguments{
11 10
 \item{layout}{one of phylogram, cladogram}
12 11
 
13
-\item{color}{color}
14
-
15
-\item{linetype}{line type}
16
-
17
-\item{size}{line size}
18
-
19 12
 \item{...}{additional parameter}
20 13
 }
21 14
 \value{
... ...
@@ -8,13 +8,15 @@
8 8
 \title{visualizing phylogenetic tree and heterogenous associated data based on grammar of graphics
9 9
 \code{ggtree} provides functions for visualizing phylogenetic tree and its associated data in R.}
10 10
 \usage{
11
-ggtree(tr, showDistance = FALSE, layout = "phylogram", yscale = "none",
12
-  ladderize = TRUE, right = FALSE, branch.length = "branch.length",
13
-  ndigits = NULL, ...)
11
+ggtree(tr, mapping = NULL, showDistance = FALSE, layout = "phylogram",
12
+  yscale = "none", ladderize = TRUE, right = FALSE,
13
+  branch.length = "branch.length", ndigits = NULL, ...)
14 14
 }
15 15
 \arguments{
16 16
 \item{tr}{phylo object}
17 17
 
18
+\item{mapping}{aes mapping}
19
+
18 20
 \item{showDistance}{add distance legend, logical}
19 21
 
20 22
 \item{layout}{one of phylogram, dendrogram, cladogram, fan, radial and unrooted}
... ...
@@ -1,11 +1,13 @@
1 1
 % Generated by roxygen2 (4.1.1): 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/phylo.R
2
+% Please edit documentation in R/AllGenerics.R, R/beast.R, R/codeml.R, R/codeml_mlc.R, R/ggtree.R, R/hyphy.R, R/jplace.R, R/paml_rst.R, R/phylo.R
3 3
 \docType{methods}
4 4
 \name{groupClade}
5 5
 \alias{groupClade}
6 6
 \alias{groupClade,beast-method}
7 7
 \alias{groupClade,codeml-method}
8 8
 \alias{groupClade,codeml_mlc-method}
9
+\alias{groupClade,gg-method}
10
+\alias{groupClade,ggplot-method}
9 11
 \alias{groupClade,hyphy-method}
10 12
 \alias{groupClade,jplace-method}
11 13
 \alias{groupClade,paml_rst-method}
... ...
@@ -20,6 +22,10 @@ groupClade(object, node)
20 22
 
21 23
 \S4method{groupClade}{codeml_mlc}(object, node)
22 24
 
25
+\S4method{groupClade}{ggplot}(object, node)
26
+
27
+\S4method{groupClade}{gg}(object, node)
28
+
23 29
 \S4method{groupClade}{hyphy}(object, node)
24 30
 
25 31
 \S4method{groupClade}{jplace}(object, node)
... ...
@@ -1,11 +1,13 @@
1 1
 % Generated by roxygen2 (4.1.1): 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/phylo.R
2
+% Please edit documentation in R/AllGenerics.R, R/beast.R, R/codeml.R, R/codeml_mlc.R, R/ggtree.R, R/hyphy.R, R/jplace.R, R/paml_rst.R, R/phylo.R
3 3
 \docType{methods}
4 4
 \name{groupOTU}
5 5
 \alias{groupOTU}
6 6
 \alias{groupOTU,beast-method}
7 7
 \alias{groupOTU,codeml-method}
8 8
 \alias{groupOTU,codeml_mlc-method}
9
+\alias{groupOTU,gg-method}
10
+\alias{groupOTU,ggplot-method}
9 11
 \alias{groupOTU,hyphy-method}
10 12
 \alias{groupOTU,jplace-method}
11 13
 \alias{groupOTU,paml_rst-method}
... ...
@@ -20,6 +22,10 @@ groupOTU(object, focus)
20 22
 
21 23
 \S4method{groupOTU}{codeml_mlc}(object, focus)
22 24
 
25
+\S4method{groupOTU}{ggplot}(object, focus)
26
+
27
+\S4method{groupOTU}{gg}(object, focus)
28
+
23 29
 \S4method{groupOTU}{hyphy}(object, focus)
24 30
 
25 31
 \S4method{groupOTU}{jplace}(object, focus)
... ...
@@ -4,7 +4,7 @@
4 4
 \alias{groupOTU.phylo}
5 5
 \title{groupOTU.phylo}
6 6
 \usage{
7
-groupOTU.phylo(phy, focus)
7
+groupOTU.phylo(phy, focus, group_name = "group")
8 8
 }
9 9
 \arguments{
10 10
 \item{phy}{tree object}
... ...
@@ -12,7 +12,7 @@ groupOTU.phylo(phy, focus)
12 12
 \item{focus}{tip list}
13 13
 }
14 14
 \value{
15
-cluster index
15
+phylo object
16 16
 }
17 17
 \description{
18 18
 group OTU
... ...
@@ -4,12 +4,14 @@
4 4
 \alias{theme_tree}
5 5
 \title{theme_tree}
6 6
 \usage{
7
-theme_tree(bgcolor = "white", fgcolor = "black")
7
+theme_tree(bgcolor = "white", fgcolor = "black", ...)
8 8
 }
9 9
 \arguments{
10 10
 \item{bgcolor}{background color}
11 11
 
12 12
 \item{fgcolor}{foreground color}
13
+
14
+\item{...}{additional parameter}
13 15
 }
14 16
 \value{
15 17
 updated ggplot object with new theme
... ...
@@ -4,12 +4,14 @@
4 4
 \alias{theme_tree2}
5 5
 \title{theme_tree2}
6 6
 \usage{
7
-theme_tree2(bgcolor = "white", fgcolor = "black")
7
+theme_tree2(bgcolor = "white", fgcolor = "black", ...)
8 8
 }
9 9
 \arguments{
10 10
 \item{bgcolor}{background color}
11 11
 
12 12
 \item{fgcolor}{foreground color}
13
+
14
+\item{...}{additional parameter}
13 15
 }
14 16
 \value{
15 17
 updated ggplot object with new theme
... ...
@@ -82,6 +82,22 @@ The _`branch.length`_ is used to scale the edge, user can set the parameter _`br
82 82
 ggtree(tree, branch.length="none")
83 83
 ```
84 84
 
85
+## support multiple phylogenetic classes
86
+
87
+`r Githubpkg("GuangchuangYu/ggtree")` defined several S4 classes to store phylogenetic object and its associated annotation, including:
88
+
89
++ `jplace`
90
++ `paml_rst`
91
++ `codeml_mlc`
92
++ `codeml`
93
++ `hyphy`
94
++ `beast`
95
+
96
+In addition, it also supports _`phylo`_ (defined by `r CRANpkg("ape")`[@paradis_ape_2004]), and _`phylo4`_ (defined by `r CRANpkg("phylobase")`)
97
+
98
+User can use _`ggtree(object)`_ command to view the phylogenetic tree directly, and annotation data stored in these objects can be added as demonstrated in __[`Tree annotation with output from evolution software`](#tree-annotation-with-output-from-evolution-software)__ session.
99
+
100
+
85 101
 ## layout
86 102
 
87 103
 Currently, _`ggtree`_ supports several layout, including:
... ...
@@ -113,7 +129,7 @@ grid.arrange(ggtree(tree) + ggtitle("phylogram layout"),
113 129
 
114 130
 ```{r fig.width=9, fig.height=4, fig.align="center"}
115 131
 tree2d <- read.beast(system.file("extdata", "twoD.tree", package="ggtree"))
116
-ggtree(tree2d, layout="cladogram", time_scale=TRUE,
132
+ggtree(tree2d, time_scale=TRUE,
117 133
        yscale="NGS", yscale_mapping=c(N2=2, N3=3, N4=4, N5=5, N6=6, N7=7)) +
118 134
            theme_classic() + scale_x_continuous(breaks=seq(1965, 2015, 5)) +
119 135
                theme(panel.grid.major=element_line(color="grey20", linetype="dotted", size=.3),
... ...
@@ -124,46 +140,20 @@ ggtree(tree2d, layout="cladogram", time_scale=TRUE,
124 140
 In this example, the figure demonstrates the quantity of y increase along the trunk. User can highlight the trunk with different line size or color using the functions we described below.
125 141
 
126 142
 
127
-## support multiple phylogenetic classes
128
-
129
-`r Githubpkg("GuangchuangYu/ggtree")` defined several S4 classes to store phylogenetic object and its associated annotation, including:
130
-
131
-+ `jplace`
132
-+ `paml_rst`
133
-+ `codeml_mlc`
134
-+ `codeml`
135
-+ `hyphy`
136
-+ `beast`
137
-
138
-In addition, it also supports _`phylo`_ (defined by `r CRANpkg("ape")`[@paradis_ape_2004]), and _`phylo4`_ (defined by `r CRANpkg("phylobase")`)
139
-
140
-User can use _`ggtree(object)`_ command to view the phylogenetic tree directly, and annotation data stored in these objects can be added as demonstrated in __[`Tree annotation`](#tree-annotation)__ session.
141
- 
142 143
 ## display evolution distance
143 144
 
144 145
 To show evolution distance, user can use `add_legend` function.
145 146
 
146 147
 ```{r fig.width=3, fig.height=3, fig.align="center"}
147
-ggtree(tree) %>% add_legend(x=0, y=10, offset=0.5, font.size=3)
148
+ggtree(tree) %>% add_legend()
148 149
 ```
149 150
 
150
-User can specific the position and offset of distance from text to line segment.
151
-
152 151
 We can also use `theme_tree2()` or `ggtree(showDistance=TRUE)`
153 152
 
154 153
 ```{r fig.width=3, fig.height=3, fig.align="center"}
155 154
 ggtree(tree) + theme_tree2()
156 155
 ```
157 156
 
158
-Another way is to show the edge length of the tree. Besides, the scale of branch length can be specify via _`scale_x_continuous()`_. 
159
-```{r fig.width=3, fig.height=3, warning=FALSE, fig.align="center"}
160
-ggtree(tree, showDistance=TRUE) +
161
-    geom_text(aes(label=branch.length, x=branch), size = 3, 
162
-              vjust=-0.5, color="#F06C45") +
163
-      scale_x_continuous(breaks=seq(0, 60, 5))
164
-```
165
-
166
-
167 157
 ## display nodes/tips
168 158
 
169 159
 Show all the internal nodes and tips in the tree can be done by adding a layer of points using _`geom_point`_.
... ...
@@ -221,8 +211,216 @@ p %<% rtree(50)
221 211
 
222 212
 Another example can be found in [`CODEML`](#codeml) session.
223 213
 
224
-
225 214
 # Tree annotation
215
+
216
+## zoom on a portion of tree
217
+
218
+`r Githubpkg("GuangchuangYu/ggtree")` provides _`gzoom`_ function that similar to _`zoom`_ function provided in `r CRANpkg("ape")`. This function plots simultaneously a whole phylogenetic tree and a portion of it. It aims at exploring very large trees.
219
+
220
+```{r fig.width=18, fig.height=10, fig.align="center"}
221
+library("ape")
222
+data(chiroptera)
223
+library("ggtree")
224
+gzoom(chiroptera, grep("Plecotus", chiroptera$tip.label))
225
+```
226
+
227
+## annotate clade
228
+`r Githubpkg("GuangchuangYu/ggtree")` implements _`annotation_clade`_ and _`annotation_clade2`_ functions to annotate a selected clade with a bar indicating that clade with a corresponding label.
229
+
230
+The _`annotation_clade`_ function accepts a selected internal node number and annotates that selected clade, while _`annotation_clade2`_ functions accepts two tip labels (upper one and lower one) to annotate the clade.
231
+
232
+User can use _`geom_text`_ to display all the node numbers, and select interesting clade to annotate.
233
+```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
234
+ggtree(tree) + geom_text(aes(label=node))
235
+```
236
+
237
+```{r fig.width=5, fig.height=5}
238
+p <- ggtree(tree) + geom_tiplab()
239
+annotation_clade(p, node=17, "selected clade", offset.text=2)
240
+```
241
+
242
+```{r fig.width=5, fig.height=5}
243
+annotation_clade2(p, "B", "E", "Clade X", offset.text=2) %>%
244
+    annotation_clade2("G", "H", "Clade Y", bar.size=4, font.size=8, offset=5, offset.text=4, color="steelblue")
245
+```
246
+The parameter `bar.size` is used to control the width of the bar and the `font.size` parameter is to control the font size of the clade lable. The parameter `offset` is used to control the distance from the annotation to the tree, while `offset.text` to control the distance from clade label to bar.
247
+
248
+
249
+## highlight clades
250
+
251
+`r Githubpkg("GuangchuangYu/ggtree")` implements _`hilight`_ function, that accepts tree view and internal node number and add a layer of rectangle to highlight the selected clade.
252
+
253
+```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
254
+ggtree(tree) %>% hilight(node=21, fill="steelblue", alpha=.6) %>%
255
+    hilight(node=17, fill="darkgreen", alpha=.6)
256
+```
257
+
258
+
259
+```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
260
+ggtree(tree, layout="fan") %>% hilight(node=21, fill="steelblue", alpha=.6) %>%
261
+     hilight(node=23, fill="darkgreen", alpha=.6)
262
+```
263
+
264
+Another way to highlight selected clades is setting the clades with different colors and/or line types as demonstrated in __[`group clades`](#group-clades)__ section.
265
+
266
+## collapse clade
267
+
268
+With _`collapse`_ function, user can collapse a selected clade.
269
+
270
+```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
271
+cp <- ggtree(tree) %>% collapse(node=21)
272
+cp + geom_point(subset=.(node == 21), size=5, shape=23, fill="steelblue")
273
+```
274
+
275
+## expand collapsed clade
276
+
277
+The collapsed clade can be expanded via _`expand`_ function.
278
+
279
+```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
280
+cp %>% expand(node=21)
281
+```
282
+
283
+## flip clades
284
+
285
+The positions of two selected branches can be flip over using __*flip*__ function.
286
+
287
+```{r fig.width=20, fig.height=7, warning=FALSE}
288
+set.seed(2015-06-30)
289
+p1 <- ggtree(rtree(30)) + geom_text(aes(label=node))
290
+p2 <- flip(p1, node1=45, node2=33)
291
+p3 <- flip(p2, 32, 58)
292
+grid.arrange(p1, p2, p3, ncol=3)
293
+```
294
+
295
+## rotate clade
296
+
297
+A selected clade can be rotated by 180 degree using __*rotate*__ function.
298
+
299
+```{r fig.width=16, fig.height=8, warning=FALSE}
300
+set.seed(2015-07-01)
301
+p1 <- ggtree(rtree(30)) + geom_text(aes(label=node))
302
+p1 <- hilight(p1, 33)
303
+p2 <- rotate(p1, 33)
304
+grid.arrange(p1, p2, ncol=2)
305
+```
306
+
307
+## group OTUs
308
+
309
+`r Githubpkg("GuangchuangYu/ggtree")` provides _`groupOTU`_ function to group tips and all their related ancestors. 
310
+
311
+```{r}
312
+tree <- groupOTU(tree, focus=c("A", "B", "C", "D", "E"))
313
+```
314
+
315
+```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
316
+ggtree(tree, aes(color=group)) + geom_tiplab()
317
+```
318
+
319
+_`groupOTU`_ can also input a list of tip groups.
320
+
321
+```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
322
+cls <- list(c1=c("A", "B", "C", "D", "E"),
323
+            c2=c("F", "G", "H"),
324
+            c3=c("L", "K", "I", "J"),
325
+            c4="M")
326
+
327
+tree <- groupOTU(tree, cls)
328
+library("colorspace")
329
+ggtree(tree, aes(color=group, linetype=group)) + geom_text(aes(label=label),  hjust=-.25) +
330
+     scale_color_manual(values=c("black", rainbow_hcl(4))) + theme(legend.position="right")
331
+```
332
+
333
+_`groupOTU`_ also work with tree view (ggplot2 object).
334
+
335
+
336
+```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
337
+p <- ggtree(tree)
338
+groupOTU(p, LETTERS[1:5]) + aes(color=group) + geom_tiplab() + scale_color_manual(values=c("black", "firebrick"))
339
+```
340
+
341
+### iris example
342
+
343
+In this example, we first build a tree based on the iris data, then grouping the tree based on different spacies.
344
+```{r fig.width=20, fig.height=20, fig.align="center", warning=FALSE}
345
+data(iris)
346
+rn <- paste0(iris[,5], "_", 1:150)
347
+rownames(iris) <- rn
348
+d_iris <- dist(iris[,-5], method="man")
349
+
350
+tree_iris <- bionj(d_iris)
351
+tree_iris <- groupOTU(tree_iris, list(setosa    = rn[1:50],
352
+				versicolor    = rn[51:100],
353
+				virginica_145 = rn[101:150]))
354
+cols <- rainbow_hcl(4)
355
+ggtree(tree_iris, aes(color=group)) +
356
+    geom_text(aes(label=label), hjust=-.1) +
357
+        scale_color_manual(values=cols, breaks=1:3,
358
+                           labels=c("Setosa", "Versicolor", "Virginica")) +
359
+                               theme(legend.position="right")
360
+```
361
+
362
+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.
363
+
364
+## group clades
365
+
366
+As demonstrated above, _`groupOTU`_ is used for clustering related OTUs. Related OTUs are not necessarily within a clade, they can be distantly related as demonstrated in __[`iris example`](#iris-example)__. _`groupOTU`_ works fine for monophyletic (clade), polyphyletic and paraphyletic. If user wants to hilight a specific clade, we provides a more friendly function _`groupClade`_ that accept an internal node or a vector of internal nodes to cluster clade/clades that works similar to _`groupOTU`_. User can also use _`hilight`_ function demonstrated in __[`hilight clades`](#hilight-clades)__ section for highlighting selected clades.
367
+
368
+```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
369
+tree <- groupClade(tree, node=21)
370
+ggtree(tree, aes(color=group, linetype=group))
371
+```
372
+
373
+```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
374
+tree <- groupClade(tree, node=c(21, 17))
375
+ggtree(tree, aes(color=group, linetype=group))
376
+```
377
+
378
+It also works with tree view, just like _`groupOTU`_.
379
+
380
+With _`groupOTU`_ and _`groupClade`_, it's easy to highlight selected taxa and easy to selecte taxa to display related feature.
381
+
382
+```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
383
+ggtree(tree, aes(color=group, linetype=group)) +
384
+    geom_text(subset=.(group==2), aes(label=label), hjust = -.5) +
385
+        geom_text(subset=.(group==1), aes(label=label), hjust = -.5, color="blue")
386
+```
387
+
388
+
389
+## scale clade
390
+In __[`collapse clade`](#collapse-clade)__, we have illustrated how to collapse selected clades. Another approach is to zoom out clade to a small scale.
391
+
392
+```{r fig.width=12, fig.height=6, warning=F}
393
+grid.arrange(ggtree(tree) %>% hilight(21, "steelblue"),
394
+             ggtree(tree) %>% scaleClade(21, scale=0.3) %>% hilight(21, "steelblue"),
395
+             ncol=2)
396
+```
397
+
398
+Of course, _`scaleClade`_ can accept `scale` larger than 1 and zoom in the selected portion.
399
+
400
+```{r fig.width=12, fig.height=6, warning=F}
401
+grid.arrange(ggtree(tree) %>% hilight(17, fill="steelblue") %>%
402
+                 hilight(21, fill="darkgreen"),
403
+             ggtree(tree) %>% scaleClade(17, scale=2) %>% scaleClade(21, scale=0.3) %>%
404
+                 hilight(17, "steelblue") %>% hilight(21, fill="darkgreen"),
405
+             ncol=2)
406
+```
407
+
408
+# Tree annotation with phylopic
409
+
410
+[PhyloPic](http://phylopic.org/) is a database that stores reusable silhouette images of organisms. `r Githubpkg("GuangchuangYu/ggtree")` supports downloading images from [PhyloPic](http://phylopic.org/) and annotating phylogenetic tree with the downloaded images.
411
+
412
+```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
413
+pp <- ggtree(tree) %>% phylopic("79ad5f09-cf21-4c89-8e7d-0c82a00ce728", color="steelblue", alpha = .3)
414
+pp
415
+```
416
+
417
+```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
418
+pp %>% phylopic("67382184-5135-4faa-8e98-eadff02c3e8a", color="#86B875", alpha=.8, node=4, width=4) %>%
419
+    phylopic("d3563b54-780f-4711-a49a-7ea051e9dacc", color="darkcyan", alpha=.8, node=17, width=8)
420
+```
421
+
422
+
423
+# Tree annotation with output from evolution software
226 424
 In `r Githubpkg("GuangchuangYu/ggtree")`, we implemented several functions to parse the output from [PAML](http://abacus.gene.ucl.ac.uk/software/paml.html)[@yang_paml_2007], [HYPHY](http://hyphy.org/w/index.php/Main_Page)[@pond_hyphy_2005], [EPA](http://sco.h-its.org/exelixis/web/software/epa/index.html)[@berger_EPA_2011], [PPLACER](http://matsen.fhcrc.org/pplacer/)[@matsen_pplacer_2010] and [BEAST](http://beast2.org/)[@bouckaert_beast_2014] and defined several classes to store phylogenetic object and associated annotation.
227 425
 
228 426
 Classes include:
... ...
@@ -266,7 +464,6 @@ plot(beast, annotation="height", ndigits=3, annotation.color="red")
266 464
 #### _`rst`_ file\
267 465
 
268 466
 
269
-
270 467
 _`rst`_ file from _`baseml`_ is similar to _`codeml`_ output. The only difference is the space in the sequences. For _`baseml`_, each ten bases are separated by one space, while for _`codeml`_, each three bases (triplet) are separated by one space. We defined a _`read.paml_rst`_ to parse _`rst`_ file. It supports _`baseml`_ and _`codeml`_ output. The information will be stored in _`paml_rst`_ S4 object.
271 468
 
272 469
 ```{r}
... ...
@@ -287,7 +484,6 @@ print(p)
287 484
 #### rst file\
288 485
 
289 486
 
290
-
291 487
 _`rst`_ file from _`CODEML`_ is similar to _`BASEML`_, and also parsed by _`read.paml_rst`_ function. The _`plot`_ method works also in the same way.
292 488
 
293 489
 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.
... ...
@@ -340,7 +536,7 @@ We can also plot the _`dN`_ or _`dS`_ tree and others. The parameter _`annotatio
340 536
 
341 537
 We annotate the tree with information presented in _`rstfile`_ and _`mlcfile`_ separately as demonstrated in previous sessions.
342 538
 
343
-We can also use both of them and it's highly recommended. User don't need to provide tip sequences, as it's already available in _`mlcfile`_. All the features in both files are available for annotation.
539
+We can also use both of them and it's highly recommended. All the features in both files are available for annotation.
344 540
 
345 541
 
346 542
 ```{r}
... ...
@@ -395,6 +591,8 @@ We may, for example, count the number of placement and annotate this information
395 591
 
396 592
 
397 593
 ## mergine tree objects
594
+
595
+
398 596
 In ggtree, objects can be merged and evidences inferred from different phylogenetic analyses can be combined or compared and visualized.
399 597
 
400 598
 User can use the command like:
... ...
@@ -422,9 +620,9 @@ merged_tree
422 620
 After merging, all evidences inferred from different tools can be used to annotate the tree simultaneously. In this example, we used 'dN/dS' inferred by CodeML to color the tree and annotate the tree with 'posterior' inferred by BEAST.
423 621
 
424 622
 ```{r fig.width=20, fig.height=26, warning=FALSE}
425
-cols <- scale_color(merged_tree, "dN_vs_dS", interval=seq(0, 1.5))
426
-ggtree(merged_tree, time_scale=TRUE, ndigits = 3, color=cols) +
427
-    geom_text(aes(label=posterior), vjust=.1, hjust=-.1, size=5) + theme_tree2()
623
+ggtree(merged_tree, aes(color=dN_vs_dS), time_scale=TRUE, ndigits = 3) +
624
+    geom_text(aes(label=posterior), vjust=.1, hjust=-.1, size=5) + theme_tree2() +
625
+        scale_color_continuous(low="steelblue", high="red")
428 626
 ```
429 627
 
430 628
 
... ...
@@ -441,7 +639,9 @@ ggtree(ml, branch.length="dN_vs_dS") +
441 639
 ```	
442 640
 
443 641
 
444
-## user specific annotation
642
+# Tree annotation with user specific annotation
643
+
644
+## the `%<+%` operator
445 645
 We provides several functions to parse and store information from common software output, and corresponding _`plot`_ methods for visualizing annotation in the tree.
446 646
 
447 647
 Here, we would like to demonstrate how to inject user specific annotation data in a tree.
... ...
@@ -478,7 +678,7 @@ After attaching the annotation data to the tree by _`%<+%`_, all the columns in
478 678
 ```{r fig.width=6, fig.height=5, warning=FALSE, fig.align="center"}
479 679
 p <- p %<+% dd + geom_text(aes(color=place, label=label), hjust=-0.5) + 
480 680
        geom_point(aes(size=value, shape=place, color=place), alpha=0.25, subset=.(isTip))
481
-print(p)
681
+p+theme(legend.position="right")
482 682
 ```
483 683
 
484 684
 Once the data was attached, it is always attached. So we can add another layer to display the isolation sites easily.
... ...
@@ -525,269 +725,26 @@ ggtree(jp, showDistance=TRUE) +
525 725
 	   geom_text(aes(label=label), hjust=-.5)
526 726
 ```
527 727
 
528
-## zoom on a portion of tree
529
-
530
-`r Githubpkg("GuangchuangYu/ggtree")` provides _`gzoom`_ function that similar to _`zoom`_ function provided in `r CRANpkg("ape")`. This function plots simultaneously a whole phylogenetic tree and a portion of it. It aims at exploring very large trees.
531
-
532
-```{r fig.width=18, fig.height=10, fig.align="center"}
533
-library("ape")
534
-data(chiroptera)
535
-library("ggtree")
536
-gzoom(chiroptera, grep("Plecotus", chiroptera$tip.label))
537
-```
538
-
539
-## highlight clades
540
-
541
-`r Githubpkg("GuangchuangYu/ggtree")` implements _`hilight`_ function, that accepts tree view and internal node number and add a layer of rectangle to highlight the selected clade.
542
-
543
-```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
544
-nwk <- system.file("extdata", "sample.nwk", package="ggtree")
545
-tree <- read.tree(nwk)
546
-
547
-ggtree(tree) + geom_text(aes(label=node))
548
-```
549
-
550
-User can use _`geom_text`_ to display all the node numbers, and select interesting clade to highlight.
551
-
552
-```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
553
-ggtree(tree) %>% hilight(node=21, fill="steelblue", alpha=.6) %>%
554
-    hilight(node=17, fill="darkgreen", alpha=.6)
555
-```
556
-
557
-
558
-```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
559
-ggtree(tree, layout="fan") %>% hilight(node=21, fill="steelblue", alpha=.6) %>%
560
-     hilight(node=17, fill="darkgreen", alpha=.6)
561
-```
562
-
563
-Another way to highlight selected clades is setting the clades with different colors and/or line types as demonstrated in __[`group clades`](#group-clades)__ section.
564
-
565
-## collapse clade
566
-
567
-With _`collapse`_ function, user can collapse a selected clade.
568
-
569
-```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
570
-cp <- ggtree(tree) %>% collapse(node=21)
571
-cp + geom_point(subset=.(node == 21), size=5, shape=23, fill="steelblue")
572
-```
573
-
574
-## expand collapsed clade
575
-
576
-The collapsed clade can be expanded via _`expand`_ function.
577
-
578
-```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
579
-cp %>% expand(node=21)
580
-```
581
-
582
-## flip clades
583
-
584
-The positions of two selected branches can be flip over using __*flip*__ function.
585
-
586
-```{r fig.width=20, fig.height=7, warning=FALSE}
587
-set.seed(2015-06-30)
588
-p1 <- ggtree(rtree(30)) + geom_text(aes(label=node))
589
-p2 <- flip(p1, node1=45, node2=33)
590
-p3 <- flip(p2, 32, 58)
591
-grid.arrange(p1, p2, p3, ncol=3)
592
-```
593
-
594
-## rotate clade
595
-
596
-A selected clade can be rotated by 180 degree using __*rotate*__ function.
597
-
598
-```{r fig.width=16, fig.height=8, warning=FALSE}
599
-set.seed(2015-07-01)
600
-p1 <- ggtree(rtree(30)) + geom_text(aes(label=node))
601
-p1 <- hilight(p1, 33)
602
-p2 <- rotate(p1, 33)
603
-grid.arrange(p1, p2, ncol=2)
604
-```
605
-
606
-## phylopic
607
-
608
-[PhyloPic](http://phylopic.org/) is a database that stores reusable silhouette images of organisms. `r Githubpkg("GuangchuangYu/ggtree")` supports downloading images from [PhyloPic](http://phylopic.org/) and annotating phylogenetic tree with the downloaded images.
609
-
610
-```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
611
-pp <- ggtree(tree) %>% phylopic("79ad5f09-cf21-4c89-8e7d-0c82a00ce728", color="steelblue", alpha = .3)
612
-pp
613
-```
614
-
615
-```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
616
-pp %>% phylopic("67382184-5135-4faa-8e98-eadff02c3e8a", color="#86B875", alpha=.8, node=21, width=4) %>%
617
-    phylopic("d3563b54-780f-4711-a49a-7ea051e9dacc", color="darkcyan", alpha=.8, node=17, width=8)
618
-```
619
-
620
-## scale color based on numerical attribute
621
-
622
-`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.
623
-```{r fig.width=12, fig.height=6, fig.align="center", warning=FALSE}
624
-cols = scale_color(ml, by="dN")
625
-ggtree(ml, color=cols) + geom_text(aes(label=label), color=cols, hjust=.25)
626
-```
627
-
628
-_`scale_color`_ will auto determine the color. User can also provide parameter _`low`_ and _`high`_ to speicify the color scale.
629
-
630
-```{r fig.width=12, fig.height=6, fig.align="center", warning=FALSE}
631
-cols = scale_color(ml, by="dN", low="green", high="red")
632
-ggtree(ml, color=cols) + geom_text(aes(label=label), color=cols, hjust=.25)
633
-```
634
-
635
-## group OTUs
636
-
637
-`r Githubpkg("GuangchuangYu/ggtree")` provides _`groupOTU`_ function to group tips and all their related ancestors. It return a cluster index of each line segment in the tree view.
638
-
639
-```{r}
640
-cluster_index <- groupOTU(tree, focus=c("A", "B", "C", "D", "E"))
641
-cluster_index
642
-```
643
-In the _`cluster_index`_, **1** represent the cluster that not selected, while other number represent the corresponding selected group(s).
644
-
645
-```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
646
-ggtree(tree, color=c("black", "red")[cluster_index])
647
-```
648
-
649
-_`groupOTU`_ can also input a list of tip groups.
650
-
651
-```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
652
-cls <- list(c1=c("A", "B", "C", "D", "E"),
653
-            c2=c("F", "G", "H"),
654
-            c3=c("L", "K", "I", "J"),
655
-            c4="M")
656
-
657
-cls_ind <- groupOTU(tree, cls)
658
-library("colorspace")
659
-cols <- rainbow_hcl(4)
660
-cols <- c("black", cols)
661
-ggtree(tree, color=cols[cls_ind]) + geom_text(aes(label=label), color=cols[cls_ind], hjust=-.25) +
662
-    annotate("point", x=1, y=seq(14, 12, length.out=4), color=cols[2:5], size=6) +
663
-                 annotate("text", x=4, y=seq(14,12, length.out=4), label=names(cls))
664
-```
665
-
666
-We can change the linetype either:
667
-```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
668
-linetype <- c("solid", "dotted", "dashed", "dotdash", "longdash")
669
-ggtree(tree, color=cols[cls_ind], linetype=linetype[cls_ind]) +
670
-      geom_text(aes(label=label), color=cols[cls_ind], hjust=-.25)
671
-```
672
-
673
-And also size:
674
-```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
675
-size <- seq(1, 3, length.out=5)
676
-ggtree(tree, color=cols[cls_ind], linetype=linetype[cls_ind], size=size[cls_ind]) +
677
-      geom_text(aes(label=label), color=cols[cls_ind], hjust=-.25)
678
-```
679
-
680
-All the tree classes defined in `r Githubpkg("GuangchuangYu/ggtree")`, including _`beast`_, _`paml_rst`_, _`codeml_mlc`_, _`codeml`_, _`hyphy`_ and _`jplace`_ are all supported.
681
-
682
-
683
-### iris example
684
-
685
-In this example, we first build a tree based on the iris data, then grouping the tree based on different spacies.
686
-```{r fig.width=20, fig.height=20, fig.align="center", warning=FALSE}
687
-data(iris)
688
-rn <- paste0(iris[,5], "_", 1:150)
689
-rownames(iris) <- rn
690
-d_iris <- dist(iris[,-5], method="man")
691
-
692
-tree_iris <- bionj(d_iris)
693
-cls_ind <- groupOTU(tree_iris, list(setosa    = rn[1:50],
694
-				versicolor    = rn[51:100],
695
-				virginica_145 = rn[101:150]))
696
-cols <- rainbow_hcl(4)
697
-ggtree(tree_iris, color=cols[cls_ind]) +
698
-     geom_text(aes(label=label), color=cols[cls_ind], hjust=-.1)
699
-```
700 728
 
701
-<!--
702
-By adding a layer of internal node number, we can easily extract tip labels of a particular clade by the _`get.offspring.tip`_ function.
703
-```{r}
704
-ggtree(tree_iris) + geom_text(aes(label=node))
705
-cl1 <- get.offspring.tip(tree_iris, 242)
706
-cl2 <- get.offspring.tip(tree_iris, 152) 
707
-cl2 <- cl2[!cl2 %in% cl1]
708
-cl3 <- get.offspring.tip(tree_iris, 158)
709
-cl4 <- get.offspring.tip(tree_iris, 157)
710
-
711
-cls_ind <- groupOTU(tree_iris, list(cl1, cl2, cl3, cl4))
712
-```
713
-
714
-```{r fig.width=20, fig.height=24, fig.align="center", warning=FALSE}
715
-cols <- rainbow_hcl(3)
716
-cols <- c("black", cols, cols[2])
717
-species <- data.frame(otu=row.names(iris), species=iris[,5])
718
-
719
-ggtree(tree_iris, color=cols[cls_ind]) %<+% species + 
720
-     geom_text(aes(label=label, color=species), hjust=-0.1) +
721
-         scale_color_manual(values=cols[2:4])
722
-```
723
-
724
-
725
-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.
726
-
727
-## group clades
728
-
729
-As demonstrated above, _`groupOTU`_ is used for clustering related OTUs. Related OTUs are not necessarily within a clade, they can be distantly related as demonstrated in __[`iris example`](#iris-example)__. _`groupOTU`_ works fine for monophyletic (clade), polyphyletic and paraphyletic. If user wants to hilight a specific clade, we provides a more friendly function _`groupClade`_ that accept an internal node or a vector of internal nodes and return cluster index just exactly like _`groupOTU`_. User can also use _`hilight`_ function demonstrated in __[`hilight clades`](#hilight-clades)__ section for highlighting selected clades.
730
-
731
-```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
732
-idx <- groupClade(tree, node=21)
733
-cols <- c("black", "darkgreen")[idx]
734
-lty <- c("solid", "dashed")[idx]
735
-ggtree(tree, color=cols, linetype=lty)
736
-```
737
-
738
-```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
739
-idx <- groupClade(tree, node=c(21, 17))
740
-cols <- c("black", "darkgreen", "firebrick")[idx]
741
-lty <- c("solid", "dashed", "dotted")[idx]
742
-ggtree(tree, color=cols, linetype=lty)
743
-```
744
-
745
-## scale clade
746
-In __[`collapse clade`](#collapse-clade)__, we have illustrated how to collapse selected clades. Another approach is to zoom out clade to a small scale.
747
-
748
-```{r fig.width=12, fig.height=6, warning=F}
749
-grid.arrange(ggtree(tree) %>% hilight(21, "steelblue"),
750
-             ggtree(tree) %>% scaleClade(21, scale=0.3) %>% hilight(21, "steelblue"),
751
-             ncol=2)
752
-```
753
-
754
-Of calse, _`scaleClade`_ can accept `scale` larger than 1 and zoom in the selected portion.
755
-
756
-```{r fig.width=12, fig.height=6, warning=F}
757
-grid.arrange(ggtree(tree) %>% hilight(17, fill="steelblue") %>%
758
-                 hilight(21, fill="darkgreen"),
759
-             ggtree(tree) %>% scaleClade(17, scale=2) %>% scaleClade(21, scale=0.3) %>%
760
-                 hilight(17, "steelblue") %>% hilight(21, fill="darkgreen"),
761
-             ncol=2)
762
-```
729
+## visualize tree with associated matrix
763 730
 
731
+At first I 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.
764 732
 
765