Browse code

facet_plot

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

Guangchuang Yu authored on 07/09/2016 01:36:05
Showing 15 changed files

... ...
@@ -1,7 +1,7 @@
1 1
 Package: ggtree
2 2
 Type: Package
3 3
 Title: an R package for visualization and annotation of phylogenetic trees with their covariates and other associated data
4
-Version: 1.5.12
4
+Version: 1.5.13
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 grammar of graphics.
... ...
@@ -22,6 +22,7 @@ S3method(fortify,r8s)
22 22
 S3method(fortify,raxml)
23 23
 S3method(identify,gg)
24 24
 S3method(print,beastList)
25
+export("%+>%")
25 26
 export("%<%")
26 27
 export("%<+%")
27 28
 export("%>%")
... ...
@@ -38,6 +39,7 @@ export(collapse)
38 39
 export(decimal2Date)
39 40
 export(download.phylopic)
40 41
 export(expand)
42
+export(facet_plot)
41 43
 export(flip)
42 44
 export(geom_aline)
43 45
 export(geom_balance)
... ...
@@ -182,6 +184,7 @@ importFrom(ggplot2,draw_key_text)
182 184
 importFrom(ggplot2,element_blank)
183 185
 importFrom(ggplot2,element_line)
184 186
 importFrom(ggplot2,element_rect)
187
+importFrom(ggplot2,facet_grid)
185 188
 importFrom(ggplot2,fortify)
186 189
 importFrom(ggplot2,geom_bar)
187 190
 importFrom(ggplot2,geom_rect)
... ...
@@ -1,5 +1,16 @@
1
+CHANGES IN VERSION 1.5.13
2
+------------------------
3
+ o facet_plot for plotting data with tree <2016-09-06, Tue>
4
+ o more parameters for column names in gheatmap <2016-09-06, Tue>
5
+   + colnames_angle
6
+   + colnames_offset_x
7
+   + colnames_offset_y
8
+   + hjust
9
+ o offset parameter in geom_tiplab and geom_tiplab2 <2016-09-05, Mon>
10
+ 
1 11
 CHANGES IN VERSION 1.5.12
2 12
 ------------------------
13
+ o use data in all layers instead of the base layer for coordination calculation in subview <2016-09-01, Thu>
3 14
  o bug fixed in subview, width & height should be width/2 & height/2 <2016-09-01, Thu>
4 15
  
5 16
 CHANGES IN VERSION 1.5.11
6 17
new file mode 100644
... ...
@@ -0,0 +1,29 @@
1
+##' plot tree associated data in an additional panel
2
+##'
3
+##' 
4
+##' @title facet_plot
5
+##' @param p tree view
6
+##' @param panel panel name for plot of input data
7
+##' @param data data to plot by 'geom', first column should be matched with tip label of tree
8
+##' @param geom geom function to plot the data
9
+##' @param mapping aes mapping for 'geom'
10
+##' @param ... additional parameters for 'geom'
11
+##' @return ggplot object
12
+##' @export
13
+##' @author Guangchuang Yu
14
+facet_plot <- function(p, panel, data, geom, mapping=NULL, ...) {
15
+    p <- add_panel(p, panel)
16
+    df <- p %+>% data
17
+    p + geom(data=df, mapping=mapping, ...)
18
+}
19
+
20
+##' @importFrom ggplot2 facet_grid
21
+add_panel <- function(p, panel) {
22
+    df <- p$data
23
+    if (is.null(df$panel)) {
24
+        df$panel <- factor("Tree")
25
+    }
26
+    levels(df$panel) %<>% c(., panel)
27
+    p$data <- df
28
+    p + facet_grid(.~panel, scales="free_x")
29
+}
... ...
@@ -4,6 +4,7 @@
4 4
 ##' @title geom_tiplab 
5 5
 ##' @param mapping aes mapping
6 6
 ##' @param hjust horizontal adjustment
7
+##' @param offset tiplab offset
7 8
 ##' @param align align tip lab or not, logical
8 9
 ##' @param linetype linetype for adding line if align = TRUE
9 10
 ##' @param linesize line size of line if align = TRUE
... ...
@@ -17,9 +18,13 @@
17 18
 ##' require(ape)
18 19
 ##' tr <- rtree(10)
19 20
 ##' ggtree(tr) + geom_tiplab()
20
-geom_tiplab <- function(mapping=NULL, hjust = 0, align = FALSE, linetype = "dotted", linesize=1, geom="text", ...) {
21
+geom_tiplab <- function(mapping=NULL, hjust = 0,  align = FALSE, linetype = "dotted", linesize=1, geom="text", offset = 0, ...) {
21 22
     geom <- match.arg(geom, c("text", "label"))
22
-
23
+    if (geom == "text") {
24
+        text_geom <- geom_text2
25
+    } else {
26
+        text_geom <- geom_label2
27
+    }
23 28
     x <- y <- label <- isTip <- NULL
24 29
     if (align == TRUE) {
25 30
         self_mapping <- aes(x = max(x, na.rm=TRUE) + diff(range(x, na.rm=TRUE))/200, y = y, label = label, subset= isTip)
... ...
@@ -34,26 +39,21 @@ geom_tiplab <- function(mapping=NULL, hjust = 0, align = FALSE, linetype = "dott
34 39
         text_mapping <- modifyList(self_mapping, mapping)
35 40
     }
36 41
 
37
-    dot_mapping <- NULL
38
-    if (align && (!is.na(linetype) && !is.null(linetype))) {
39
-        dot_mapping <- aes(xend=x+diff(range(x, na.rm=TRUE))/200, x=max(x, na.rm=TRUE), y=y, yend=y, subset=isTip)
40
-        if (!is.null(mapping)) {
41
-            dot_mapping <- modifyList(dot_mapping, mapping)
42
-        }
43
-    } 
44 42
     
43
+    show_segment <- FALSE
44
+    if (align && (!is.na(linetype) && !is.null(linetype))) {
45
+        show_segment <- TRUE
46
+    }  
47
+
45 48
     list(
46
-        if (geom == "text") {
47
-            geom_text2(mapping=text_mapping, 
48
-                       hjust = hjust, ...)
49
-        } else {
50
-            geom_label2(mapping=text_mapping, 
51
-                        hjust = hjust, ...)
52
-        },
53
-        if (!is.null(dot_mapping))
54
-            geom_segment2(mapping=dot_mapping,
55
-                          linetype = linetype,
56
-                          size = linesize, ...)
49
+        text_geom(mapping=text_mapping, 
50
+                  hjust = hjust, nudge_x = offset, ...)
51
+        ,
52
+        if (show_segment)
53
+            geom_tipsegment(mapping = aes(subset=isTip),
54
+                            offset = offset,
55
+                            linetype = linetype,
56
+                            size = linesize, ...)
57 57
     )
58 58
 }
59 59
 
... ...
@@ -86,3 +86,46 @@ geom_tiplab2 <- function(mapping=NULL, hjust=0, ...) {
86 86
          geom_tiplab(m2, hjust=1-hjust, ...)
87 87
          )
88 88
 }
89
+
90
+geom_tipsegment <- function(mapping=NULL, data=NULL,
91
+                            geom=GeomSegmentGGtree, position = "identity",
92
+                            offset,  ...,
93
+                            show.legend=NA, inherit.aes=FALSE, na.rm=TRUE) {
94
+    
95
+    default_aes <- aes_(x=~x, y=~y)
96
+    if (is.null(mapping)) {
97
+        mapping <- default_aes
98
+    } else {
99
+        mapping <- modifyList(default_aes, mapping)
100
+    }
101
+    
102
+    layer(stat=StatTipSegment,
103
+          data = data,
104
+          mapping = mapping,
105
+          geom = geom,
106
+          position = position,
107
+          show.legend = show.legend,
108
+          inherit.aes = inherit.aes,
109
+          params = list(offset = offset,
110
+                        na.rm = na.rm,
111
+                        ...)
112
+          )
113
+}
114
+
115
+StatTipSegment <- ggproto("StatTipSegment", Stat,
116
+                        compute_group = function(self, data, scales, params, offset) {
117
+                            get_tipsegment_position(data, offset)
118
+                        },
119
+                        required_aes = c("x", "y")
120
+                        )
121
+
122
+
123
+get_tipsegment_position <- function(data, offset, adjustRatio=1/200) {
124
+    adjust <- diff(range(data$x, na.rm=TRUE)) * adjustRatio
125
+    xend <- data$x + adjust
126
+    x <- max(data$x, na.rm = TRUE)  + offset
127
+    y <- data$y
128
+    data.frame(x=x, xend=xend, y=y, yend=y)
129
+}
130
+
131
+
... ...
@@ -11,8 +11,12 @@
11 11
 ##' @param color color of heatmap cell border
12 12
 ##' @param colnames logical, add matrix colnames or not
13 13
 ##' @param colnames_position one of 'bottom' or 'top'
14
+##' @param colnames_angle angle of column names
14 15
 ##' @param colnames_level levels of colnames
16
+##' @param colnames_offset_x x offset for column names
17
+##' @param colnames_offset_y y offset for column names
15 18
 ##' @param font.size font size of matrix colnames
19
+##' @param hjust hjust for column names (0: align left, 0.5: align center, 1: align righ)
16 20
 ##' @return tree view
17 21
 ##' @importFrom ggplot2 geom_tile
18 22
 ##' @importFrom ggplot2 geom_text
... ...
@@ -25,7 +29,8 @@
25 29
 ##' @export
26 30
 ##' @author Guangchuang Yu
27 31
 gheatmap <- function(p, data, offset=0, width=1, low="green", high="red", color="white",
28
-                     colnames=TRUE, colnames_position="bottom", colnames_level=NULL, font.size=4) {
32
+                     colnames=TRUE, colnames_position="bottom", colnames_angle=0, colnames_level=NULL,
33
+                     colnames_offset_x = 0, colnames_offset_y = 0, font.size=4, hjust=0.5) {
29 34
     
30 35
     colnames_position %<>% match.arg(c("bottom", "top"))
31 36
     variable <- value <- lab <- y <- NULL
... ...
@@ -85,7 +90,9 @@ gheatmap <- function(p, data, offset=0, width=1, low="green", high="red", color=
85 90
         } else {
86 91
             y <- max(p$data$y) + 1
87 92
         }
88
-        p2 <- p2 + geom_text(data=mapping, aes(x=to, label=from), y=y, size=font.size, inherit.aes = FALSE)
93
+        mapping$y <- y
94
+        p2 <- p2 + geom_text(data=mapping, aes(x=to, y = y, label=from), size=font.size, inherit.aes = FALSE,
95
+                             angle=colnames_angle, nudge_x=colnames_offset_x, nudge_y = colnames_offset_y, hjust=hjust)
89 96
     }
90 97
     
91 98
     p2 <- p2 + theme(legend.position="right", legend.title=element_blank())
... ...
@@ -88,6 +88,25 @@
88 88
     return(dd)
89 89
 }
90 90
 
91
+##' update data with tree info (y coordination and panel)
92
+##'
93
+##'
94
+##' @rdname add_TREEINFO
95
+##' @title \%+>\%
96
+##' @param p tree view 
97
+##' @param data data.frame
98
+##' @return updated data.frame
99
+##' @export
100
+##' @author Guangchuang Yu
101
+`%+>%` <- function(p, data) {
102
+    df <- p$data
103
+    res <- merge(df[, c('label', 'y')], data, by.x='label', by.y=1, all.x=TRUE)
104
+    lv <- levels(df$panel)
105
+    res$panel <- factor(lv[length(lv)], levels=lv)
106
+    return(res)
107
+}
108
+
109
+
91 110
 ##' pipe
92 111
 ##' @importFrom magrittr %>%
93 112
 ##' @name %>%
... ...
@@ -18,8 +18,46 @@ subview <- function(mainview, subview, x, y, width=.1, height=.1) {
18 18
     aes_x <- mapping["x"]
19 19
     aes_y <- mapping["y"]
20 20
     
21
-    xrng <- mainview$data[, aes_x] %>% range %>% diff
22
-    yrng <- mainview$data[, aes_y] %>% range %>% diff
21
+    xrng <- mainview$data[, aes_x] %>% range 
22
+    yrng <- mainview$data[, aes_y] %>% range
23
+
24
+    for (i in seq_along(mainview$layers)) {
25
+        layer <- mainview$layers[[i]]
26
+        dd <- layer$data
27
+        if (is(dd, "data.frame")) {
28
+            mapping <- as.character(layer$mapping)
29
+            mn <- names(mapping)
30
+            if ('x' %in% mn) {
31
+                aes_x <- mapping["x"]
32
+                xrng <- c(xrng, layer$data[, aes_x])
33
+            }
34
+            if ('xmin' %in% mn) {
35
+                aes_x <- mapping["xmin"]
36
+                xrng <- c(xrng, layer$data[, aes_x])
37
+            }
38
+            if ('xmax' %in% mn) {
39
+                aes_x <- mapping["xmax"]
40
+                xrng <- c(xrng, layer$data[, aes_x])
41
+            }
42
+            if ('y' %in% mn) {
43
+                aes_y <- mapping["y"]
44
+                yrng <- c(yrng, layer$data[, aes_y])
45
+            }
46
+            if ('ymin' %in% mn) {
47
+                aes_y <- mapping["ymin"]
48
+                yrng <- c(yrng, layer$data[, aes_y])
49
+            }
50
+            if ('ymax' %in% mn) {
51
+                aes_y <- mapping["ymax"]
52
+                yrng <- c(yrng, layer$data[, aes_y])
53
+            }
54
+            xrng <- range(xrng)
55
+            yrng <- range(yrng)
56
+        }
57
+    }
58
+
59
+    xrng <- diff(xrng)
60
+    yrng <- diff(yrng)
23 61
     
24 62
     if (!any(class(subview) %in% c("ggplot", "grob", "character"))) {
25 63
         stop("subview should be a ggplot or grob object, or an image file...")
... ...
@@ -382,6 +382,7 @@ is.tree <- function(x) {
382 382
                         "baseml",
383 383
                         "paml_rst",
384 384
                         "baseml_mlc",
385
+                        "codeml_mlc",
385 386
                         "codeml",
386 387
                         "hyphy",
387 388
                         "beast")
... ...
@@ -1,11 +1,11 @@
1 1
 ggtree: an R package for visualization and annotation of phylogenetic trees with their covariates and other associated data
2 2
 ===========================================================================================================================
3 3
 
4
-[![platform](http://www.bioconductor.org/shields/availability/devel/ggtree.svg)](https://www.bioconductor.org/packages/devel/bioc/html/ggtree.html#archives) [![Build Status](http://www.bioconductor.org/shields/build/devel/bioc/ggtree.svg)](https://bioconductor.org/checkResults/devel/bioc-LATEST/ggtree/) [![Linux/Mac Travis Build Status](https://img.shields.io/travis/GuangchuangYu/ggtree/master.svg?label=Mac%20OSX%20%26%20Linux)](https://travis-ci.org/GuangchuangYu/ggtree) [![AppVeyor Build Status](https://img.shields.io/appveyor/ci/Guangchuangyu/ggtree/master.svg?label=Windows)](https://ci.appveyor.com/project/GuangchuangYu/ggtree) [![install with bioconda](https://img.shields.io/badge/install%20with-bioconda-green.svg?style=flat)](http://bioconda.github.io/recipes/bioconductor-ggtree/README.html)
4
+[![releaseVersion](https://img.shields.io/badge/release%20version-1.4.20-green.svg?style=flat)](https://bioconductor.org/packages/ggtree) [![develVersion](https://img.shields.io/badge/devel%20version-1.5.13-green.svg?style=flat)](https://github.com/GuangchuangYu/ggtree) [![Bioc](http://www.bioconductor.org/shields/years-in-bioc/ggtree.svg)](https://www.bioconductor.org/packages/devel/bioc/html/ggtree.html#since) [![total](https://img.shields.io/badge/downloads-12850/total-blue.svg?style=flat)](https://bioconductor.org/packages/stats/bioc/ggtree) [![month](https://img.shields.io/badge/downloads-1122/month-blue.svg?style=flat)](https://bioconductor.org/packages/stats/bioc/ggtree)
5 5
 
6
-[![Project Status: Active - The project has reached a stable, usable state and is being actively developed.](http://www.repostatus.org/badges/latest/active.svg)](http://www.repostatus.org/#active) [![codecov](https://codecov.io/gh/GuangchuangYu/ggtree/branch/master/graph/badge.svg)](https://codecov.io/gh/GuangchuangYu/ggtree) [![Last-changedate](https://img.shields.io/badge/last%20change-2016--09--01-green.svg)](https://github.com/GuangchuangYu/ggtree/commits/master) [![commit](http://www.bioconductor.org/shields/commits/bioc/ggtree.svg)](https://www.bioconductor.org/packages/devel/bioc/html/ggtree.html#svn_source) [![GitHub forks](https://img.shields.io/github/forks/GuangchuangYu/ggtree.svg)](https://github.com/GuangchuangYu/ggtree/network) [![GitHub stars](https://img.shields.io/github/stars/GuangchuangYu/ggtree.svg)](https://github.com/GuangchuangYu/ggtree/stargazers)
6
+[![Project Status: Active - The project has reached a stable, usable state and is being actively developed.](http://www.repostatus.org/badges/latest/active.svg)](http://www.repostatus.org/#active) [![codecov](https://codecov.io/gh/GuangchuangYu/ggtree/branch/master/graph/badge.svg)](https://codecov.io/gh/GuangchuangYu/ggtree) [![Last-changedate](https://img.shields.io/badge/last%20change-2016--09--07-green.svg)](https://github.com/GuangchuangYu/ggtree/commits/master) [![GitHub forks](https://img.shields.io/github/forks/GuangchuangYu/ggtree.svg)](https://github.com/GuangchuangYu/ggtree/network) [![GitHub stars](https://img.shields.io/github/stars/GuangchuangYu/ggtree.svg)](https://github.com/GuangchuangYu/ggtree/stargazers) [![Awesome](https://cdn.rawgit.com/sindresorhus/awesome/d7305f38d29fed78fa85652e3a63e154dd8e8829/media/badge.svg)](https://awesome-r.com/#awesome-r-graphic-displays)
7 7
 
8
-[![releaseVersion](https://img.shields.io/badge/release%20version-1.4.18-green.svg?style=flat)](https://bioconductor.org/packages/ggtree) [![develVersion](https://img.shields.io/badge/devel%20version-1.5.12-green.svg?style=flat)](https://github.com/GuangchuangYu/ggtree) [![Bioc](http://www.bioconductor.org/shields/years-in-bioc/ggtree.svg)](https://www.bioconductor.org/packages/devel/bioc/html/ggtree.html#since) [![post](http://www.bioconductor.org/shields/posts/ggtree.svg)](https://support.bioconductor.org/t/ggtree/) [![download](http://www.bioconductor.org/shields/downloads/ggtree.svg)](https://bioconductor.org/packages/stats/bioc/ggtree/)
8
+[![platform](http://www.bioconductor.org/shields/availability/devel/ggtree.svg)](https://www.bioconductor.org/packages/devel/bioc/html/ggtree.html#archives) [![Build Status](http://www.bioconductor.org/shields/build/devel/bioc/ggtree.svg)](https://bioconductor.org/checkResults/devel/bioc-LATEST/ggtree/) [![Linux/Mac Travis Build Status](https://img.shields.io/travis/GuangchuangYu/ggtree/master.svg?label=Mac%20OSX%20%26%20Linux)](https://travis-ci.org/GuangchuangYu/ggtree) [![AppVeyor Build Status](https://img.shields.io/appveyor/ci/Guangchuangyu/ggtree/master.svg?label=Windows)](https://ci.appveyor.com/project/GuangchuangYu/ggtree) [![install with bioconda](https://img.shields.io/badge/install%20with-bioconda-green.svg?style=flat)](http://bioconda.github.io/recipes/bioconductor-ggtree/README.html)
9 9
 
10 10
 The `ggtree` package extending the `ggplot2` package. It based on grammar of graphics and takes all the good parts of `ggplot2`. `ggtree` is designed for not only viewing phylogenetic tree but also displaying annotation data on the tree.
11 11
 
... ...
@@ -17,7 +17,7 @@ Please cite the following article when using `ggtree`:
17 17
 
18 18
 **G Yu**, DK Smith, H Zhu, Y Guan, TTY Lam<sup>\*</sup>. ggtree: an R package for visualization and annotation of phylogenetic trees with their covariates and other associated data. ***Methods in Ecology and Evolution***. *accepted*
19 19
 
20
-[![doi](https://img.shields.io/badge/doi-10.1111/2041--210X.12628-green.svg?style=flat)](http://dx.doi.org/10.1111/2041-210X.12628) [![Altmetric](https://img.shields.io/badge/Altmetric-128-green.svg?style=flat)](https://www.altmetric.com/details/10533079)
20
+[![doi](https://img.shields.io/badge/doi-10.1111/2041--210X.12628-green.svg?style=flat)](http://dx.doi.org/10.1111/2041-210X.12628) [![Altmetric](https://img.shields.io/badge/Altmetric-140-green.svg?style=flat)](https://www.altmetric.com/details/10533079)
21 21
 
22 22
 ------------------------------------------------------------------------
23 23
 
... ...
@@ -30,30 +30,30 @@ For details, please visit our project website, <https://guangchuangyu.github.io/
30 30
 
31 31
 ### Download stats
32 32
 
33
-[![download](http://www.bioconductor.org/shields/downloads/ggtree.svg)](https://bioconductor.org/packages/stats/bioc/ggtree/) [![total](https://img.shields.io/badge/downloads-12736/total-blue.svg?style=flat)](https://bioconductor.org/packages/stats/bioc/ggtree) [![month](https://img.shields.io/badge/downloads-1091/month-blue.svg?style=flat)](https://bioconductor.org/packages/stats/bioc/ggtree)
33
+[![download](http://www.bioconductor.org/shields/downloads/ggtree.svg)](https://bioconductor.org/packages/stats/bioc/ggtree/) [![total](https://img.shields.io/badge/downloads-12850/total-blue.svg?style=flat)](https://bioconductor.org/packages/stats/bioc/ggtree) [![month](https://img.shields.io/badge/downloads-1122/month-blue.svg?style=flat)](https://bioconductor.org/packages/stats/bioc/ggtree)
34 34
 
35
-         +---------------------------+---------------------------+----------------------------+--------+
36
-         |                                                                                    *        |
35
+         +--------------------------+--------------------------+--------------------------+------------+
36
+         |                                                                               *             |
37 37
     1200 +                                                                                             +
38
-         |                                                                      *                      |
39
-         |                                                                                         *   |
40
-    1000 +                                                                          *    *             +
38
+         |                                                                  *                      *   |
39
+         |                                                                                    *        |
40
+    1000 +                                                                      *    *                 +
41 41
          |                                                                                             |
42 42
          |                                                                                             |
43 43
          |                                                                                             |
44
-     800 +                                                  *         *                                +
45
-         |                                                                 *                           |
46
-         |                                              *        *                                     |
47
-     600 +                                         *                                                   +
44
+     800 +                                                *        *                                   +
45
+         |                                                             *                               |
46
+         |                                            *        *                                       |
47
+     600 +                                       *                                                     +
48 48
          |                                                                                             |
49 49
          |                                                                                             |
50
-         |                                    *                                                        |
51
-     400 +                           *   *                                                             +
52
-         |                      *                                                                      |
50
+         |                                   *                                                         |
51
+     400 +                         *    *                                                              +
52
+         |                     *                                                                       |
53 53
          |                                                                                             |
54
-     200 +                 *                                                                           +
54
+     200 +                *                                                                            +
55 55
          |                                                                                             |
56 56
          |                                                                                             |
57
-         |   *    *   *                                                                                |
58
-       0 +---------------------------+---------------------------+----------------------------+--------+
59
-                                  2015.5                       2016                        2016.5
57
+         |   *   *    *                                                                                |
58
+       0 +--------------------------+--------------------------+--------------------------+------------+
59
+                                 2015.5                      2016                      2016.5
60 60
new file mode 100644
... ...
@@ -0,0 +1,23 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/operator.R
3
+\name{\%+>\%}
4
+\alias{\%+>\%}
5
+\title{\%+>\%}
6
+\usage{
7
+p \%+>\% data
8
+}
9
+\arguments{
10
+\item{p}{tree view}
11
+
12
+\item{data}{data.frame}
13
+}
14
+\value{
15
+updated data.frame
16
+}
17
+\description{
18
+update data with tree info (y coordination and panel)
19
+}
20
+\author{
21
+Guangchuang Yu
22
+}
23
+
0 24
new file mode 100644
... ...
@@ -0,0 +1,31 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/facet_plot.R
3
+\name{facet_plot}
4
+\alias{facet_plot}
5
+\title{facet_plot}
6
+\usage{
7
+facet_plot(p, panel, data, geom, mapping = NULL, ...)
8
+}
9
+\arguments{
10
+\item{p}{tree view}
11
+
12
+\item{panel}{panel name for plot of input data}
13
+
14
+\item{data}{data to plot by 'geom', first column should be matched with tip label of tree}
15
+
16
+\item{geom}{geom function to plot the data}
17
+
18
+\item{mapping}{aes mapping for 'geom'}
19
+
20
+\item{...}{additional parameters for 'geom'}
21
+}
22
+\value{
23
+ggplot object
24
+}
25
+\description{
26
+plot tree associated data in an additional panel
27
+}
28
+\author{
29
+Guangchuang Yu
30
+}
31
+
... ...
@@ -5,7 +5,7 @@
5 5
 \title{geom_tiplab}
6 6
 \usage{
7 7
 geom_tiplab(mapping = NULL, hjust = 0, align = FALSE,
8
-  linetype = "dotted", linesize = 1, geom = "text", ...)
8
+  linetype = "dotted", linesize = 1, geom = "text", offset = 0, ...)
9 9
 }
10 10
 \arguments{
11 11
 \item{mapping}{aes mapping}
... ...
@@ -20,6 +20,8 @@ geom_tiplab(mapping = NULL, hjust = 0, align = FALSE,
20 20
 
21 21
 \item{geom}{one of 'text' and 'label'}
22 22
 
23
+\item{offset}{tiplab offset}
24
+
23 25
 \item{...}{additional parameter}
24 26
 }
25 27
 \value{
... ...
@@ -6,7 +6,8 @@
6 6
 \usage{
7 7
 gheatmap(p, data, offset = 0, width = 1, low = "green", high = "red",
8 8
   color = "white", colnames = TRUE, colnames_position = "bottom",
9
-  colnames_level = NULL, font.size = 4)
9
+  colnames_angle = 0, colnames_level = NULL, colnames_offset_x = 0,
10
+  colnames_offset_y = 0, font.size = 4, hjust = 0.5)
10 11
 }
11 12
 \arguments{
12 13
 \item{p}{tree view}
... ...
@@ -27,9 +28,17 @@ gheatmap(p, data, offset = 0, width = 1, low = "green", high = "red",
27 28
 
28 29
 \item{colnames_position}{one of 'bottom' or 'top'}
29 30
 
31
+\item{colnames_angle}{angle of column names}
32
+
30 33
 \item{colnames_level}{levels of colnames}
31 34
 
35
+\item{colnames_offset_x}{x offset for column names}
36
+
37
+\item{colnames_offset_y}{y offset for column names}
38
+
32 39
 \item{font.size}{font size of matrix colnames}
40
+
41
+\item{hjust}{hjust for column names (0: align left, 0.5: align center, 1: align righ)}
33 42
 }
34 43
 \value{
35 44
 tree view
... ...
@@ -182,24 +182,20 @@ inset(p, img)
182 182
 
183 183
 ![](figures/inset_img.png)
184 184
 
185
-# Align tree with other plots on a page
185
+# Plot tree with associated data
186 186
 
187
-This is currently difficult to achieve in `ggplot2`. However, it is possible to obtain good results by creating a dummy faceting of data.
187
+For associating phylogenetic tree with different type of plot produced by user's data, `ggtree` provides `facet_plot` function which accepts an input `data.frame` and a 'geom' function to draw the input data. The data will be displayed in an additional panel of the plot.
188 188
 
189 189
 ```{r warning=F, fig.width=10, fig.height=6}
190 190
 tr <- rtree(30)
191
-df <- fortify(tr)
192
-df$tipstats <- NA
193
-d1 <- df
194
-d2 <- df
195
-d2$tipstats[d2$isTip] <- abs(rnorm(30))
196
-d1$panel <- 'Tree'
197
-d2$panel <- 'Stats'
198
-d1$panel <- factor(d1$panel, levels=c("Tree", "Stats"))
199
-d2$panel <- factor(d2$panel, levels=c("Tree", "Stats"))
200
-
201
-p <- ggplot(mapping=aes(x=x, y=y)) + facet_grid(.~panel, scale="free_x") + theme_tree2()
202
-p+geom_tree(data=d1) + geom_point(data=d2, aes(x=tipstats)) 
191
+
192
+d1 <- data.frame(id=tr$tip.label, val=rnorm(30, sd=3))
193
+p <- ggtree(tr)
194
+
195
+p2 <- facet_plot(p, panel="dot", data=d1, geom=geom_point, aes(x=val), color='firebrick')
196
+d2 <- data.frame(id=tr$tip.label, value = abs(rnorm(30, mean=100, sd=50)))
197
+
198
+facet_plot(p2, panel='bar', data=d2, geom=geom_segment, aes(x=0, xend=value, y=y, yend=y), size=3, color='steelblue') + theme_tree2()
203 199
 ```
204 200
 
205 201
 # Tree annotation with Phylopic