Browse code

revert to previous version for compatible with CRAN version of ggplot2

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

Guangchuang Yu authored on 31/08/2015 03:34:32
Showing 15 changed files

... ...
@@ -1,7 +1,7 @@
1 1
 Package: ggtree
2 2
 Type: Package
3 3
 Title: a phylogenetic tree viewer for different types of tree annotations
4
-Version: 1.1.18
4
+Version: 1.1.19
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
... ...
@@ -27,11 +27,8 @@ export(expand)
27 27
 export(flip)
28 28
 export(geom_aline)
29 29
 export(geom_nodepoint)
30
-export(geom_point2)
31 30
 export(geom_rootpoint)
32
-export(geom_segment2)
33 31
 export(geom_text)
34
-export(geom_text2)
35 32
 export(geom_tiplab)
36 33
 export(geom_tippoint)
37 34
 export(geom_tree)
... ...
@@ -118,35 +115,27 @@ importFrom(ape,which.edge)
118 115
 importFrom(ape,write.tree)
119 116
 importFrom(colorspace,rainbow_hcl)
120 117
 importFrom(ggplot2,"%+replace%")
121
-importFrom(ggplot2,GeomPoint)
122
-importFrom(ggplot2,GeomSegment)
123
-importFrom(ggplot2,GeomText)
124 118
 importFrom(ggplot2,aes)
125 119
 importFrom(ggplot2,aes_string)
126 120
 importFrom(ggplot2,annotate)
127 121
 importFrom(ggplot2,annotation_custom)
128 122
 importFrom(ggplot2,coord_flip)
129 123
 importFrom(ggplot2,coord_polar)
130
-importFrom(ggplot2,draw_key_path)
131
-importFrom(ggplot2,draw_key_point)
132
-importFrom(ggplot2,draw_key_text)
133 124
 importFrom(ggplot2,element_blank)
134 125
 importFrom(ggplot2,element_line)
135 126
 importFrom(ggplot2,element_rect)
136 127
 importFrom(ggplot2,element_text)
137 128
 importFrom(ggplot2,fortify)
129
+importFrom(ggplot2,geom_point)
138 130
 importFrom(ggplot2,geom_rect)
139 131
 importFrom(ggplot2,geom_segment)
140 132
 importFrom(ggplot2,geom_text)
141 133
 importFrom(ggplot2,geom_tile)
142 134
 importFrom(ggplot2,ggplot)
143 135
 importFrom(ggplot2,ggplotGrob)
144
-importFrom(ggplot2,ggproto)
145 136
 importFrom(ggplot2,guide_legend)
146 137
 importFrom(ggplot2,guides)
147 138
 importFrom(ggplot2,labs)
148
-importFrom(ggplot2,layer)
149
-importFrom(ggplot2,position_nudge)
150 139
 importFrom(ggplot2,scale_color_manual)
151 140
 importFrom(ggplot2,scale_fill_discrete)
152 141
 importFrom(ggplot2,scale_fill_gradient)
... ...
@@ -162,6 +151,7 @@ importFrom(ggplot2,ylab)
162 151
 importFrom(ggplot2,ylim)
163 152
 importFrom(grDevices,col2rgb)
164 153
 importFrom(grDevices,rgb)
154
+importFrom(grid,editGrob)
165 155
 importFrom(grid,gpar)
166 156
 importFrom(grid,linesGrob)
167 157
 importFrom(grid,rasterGrob)
... ...
@@ -1,120 +1,46 @@
1
-
2 1
 ##' add tip point
3 2
 ##'
4 3
 ##' 
5 4
 ##' @title geom_tippoint
6
-##' @inheritParams geom_point2
5
+##' @param mapping aes mapping
6
+##' @param ... additional parameter
7 7
 ##' @return tip point layer
8 8
 ##' @export
9 9
 ##' @author Guangchuang Yu
10
-geom_tippoint <- function(mapping = NULL, data = NULL, stat = "identity",
11
-                       position = "identity", na.rm = FALSE,
12
-                          show.legend = NA, inherit.aes = TRUE, ...) {
10
+geom_tippoint <- function(mapping = NULL, ...) {
13 11
     isTip <- NULL
14
-    self_mapping <- aes(subset = isTip)
15
-    if (is.null(mapping)) {
16
-        mapping <- self_mapping
17
-    } else {
18
-        mapping %<>% modifyList(self_mapping)
19
-    }
20
-    geom_point2(mapping, data, stat, position, na.rm, show.legend, inherit.aes, ...)    
12
+    geom_point(mapping, subset=.(isTip), ...)
21 13
 }
22 14
 
23 15
 ##' add node point
24 16
 ##'
25 17
 ##' 
26 18
 ##' @title geom_nodepoint
27
-##' @inheritParams geom_point2
19
+##' @param mapping aes mapping
20
+##' @param ... additional parameter
28 21
 ##' @return node point layer
29 22
 ##' @export
30 23
 ##' @author Guangchuang Yu
31
-geom_nodepoint <- function(mapping = NULL, data = NULL, stat = "identity",
32
-                       position = "identity", na.rm = FALSE,
33
-                       show.legend = NA, inherit.aes = TRUE, ...) {
24
+geom_nodepoint <- function(mapping = NULL,  ...) {
34 25
     isTip <- NULL
35
-    self_mapping <- aes(subset = !isTip)
36
-    if (is.null(mapping)) {
37
-        mapping <- self_mapping
38
-    } else {
39
-        mapping %<>% modifyList(self_mapping)
40
-    }
41
-    geom_point2(mapping, data, stat, position, na.rm, show.legend, inherit.aes, ...)    
26
+    geom_point(mapping, subset=.(!isTip), ...)
42 27
 }
43 28
 
44 29
 
30
+
45 31
 ##' add root point
46 32
 ##'
47 33
 ##' 
48 34
 ##' @title geom_rootpoint
49
-##' @inheritParams geom_point2
35
+##' @param mapping aes mapping
36
+##' @param ... additional parameter
50 37
 ##' @return root point layer
38
+##' @importFrom ggplot2 geom_point
51 39
 ##' @export
52 40
 ##' @author Guangchuang Yu
53
-geom_rootpoint <- function(mapping = NULL, data = NULL, stat = "identity",
54
-                           position = "identity", na.rm = FALSE,
55
-                           show.legend = NA, inherit.aes = TRUE, ...) {
41
+geom_rootpoint <- function(mapping = NULL,  ...) {
56 42
     isTip <- node <- parent <- NULL
57
-    self_mapping <- aes(subset = (node == parent))
58
-    if (is.null(mapping)) {
59
-        mapping <- self_mapping
60
-    } else {
61
-        mapping %<>% modifyList(self_mapping)
62
-    }
63
-    geom_point2(mapping, data, stat, position, na.rm, show.legend, inherit.aes, ...)
43
+    geom_point(mapping, subset=.(node == parent), ...)
64 44
 }
65 45
 
66 46
 
67
-##' geom_point2 support aes(subset) via setup_data
68
-##'
69
-##' 
70
-##' @title geom_point2
71
-##' @param mapping aes mapping
72
-##' @param data data
73
-##' @param stat stat
74
-##' @param position position
75
-##' @param na.rm logical
76
-##' @param show.legend logical
77
-##' @param inherit.aes logical
78
-##' @param ... addktional parameter
79
-##' @importFrom ggplot2 layer
80
-##' @export
81
-##' @seealso
82
-##' \link[ggplot2]{geom_point}
83
-##' @return point layer
84
-##' @author Guangchuang Yu
85
-geom_point2 <- function(mapping = NULL, data = NULL, stat = "identity",
86
-                       position = "identity", na.rm = FALSE,
87
-                       show.legend = NA, inherit.aes = TRUE, ...) {
88
-  layer(
89
-    data = data,
90
-    mapping = mapping,
91
-    stat = stat,
92
-    geom = GeomPointGGtree,
93
-    position = position,
94
-    show.legend = show.legend,
95
-    inherit.aes = inherit.aes,
96
-    params = list(
97
-      na.rm = na.rm,
98
-      ...
99
-    )
100
-  )
101
-}
102
-
103
-##' @importFrom ggplot2 ggproto
104
-##' @importFrom ggplot2 GeomPoint
105
-##' @importFrom ggplot2 draw_key_point
106
-GeomPointGGtree <- ggproto("GeomPointGGtree", GeomPoint,
107
-                           setup_data = function(data, params) {
108
-                               data[data$subset,]
109
-                           },
110
-                           
111
-                           draw_panel = function(data, panel_scales, coord, na.rm = FALSE){
112
-                               GeomPoint$draw_panel(data, panel_scales, coord, na.rm)
113
-                           },
114
-                           
115
-                           draw_key = draw_key_point,
116
-                           
117
-                           required_aes = c("x", "y"),
118
-                           default_aes = aes(shape = 19, colour = "black", size = 1.5, fill = NA,
119
-                               alpha = NA, stroke = 0.5)
120
-                           )
... ...
@@ -11,75 +11,14 @@
11 11
 ##' @author Yu Guangchuang
12 12
 geom_aline <- function(mapping=NULL, linetype="dotted", size=1, ...) {
13 13
     x <- y <- isTip <- NULL
14
-    dot_mapping <- aes(xend=x+diff(range(x))/200, x=max(x), yend=y, subset=isTip)
14
+    dot_mapping <- aes(xend=x+diff(range(x))/200, x=max(x), yend=y)
15 15
     if (!is.null(mapping)) {
16 16
         dot_mapping <- modifyList(dot_mapping, mapping)
17 17
     }
18 18
     
19
-    geom_segment2(dot_mapping,
20
-                  linetype=linetype,
21
-                  size=size, ...)
19
+    geom_segment(mapping,
20
+                 subset=.(isTip),
21
+                 linetype=linetype,
22
+                 size=size, ...)
22 23
 }
23 24
 
24
-
25
-
26
-##' geom_segment2 support aes(subset) via setup_data
27
-##'
28
-##' 
29
-##' @title geom_segment2
30
-##' @param mapping aes mapping 
31
-##' @param data data
32
-##' @param stat stat
33
-##' @param position position
34
-##' @param arrow arrow
35
-##' @param lineend lineend
36
-##' @param na.rm logical
37
-##' @param show.legend logical
38
-##' @param inherit.aes logical
39
-##' @param ... additional parameter
40
-##' @importFrom ggplot2 layer
41
-##' @export
42
-##' @seealso
43
-##' \link[ggplot2]{geom_segment}
44
-##' @return add segment layer
45
-##' @author Guangchuang Yu
46
-geom_segment2 <- function(mapping = NULL, data = NULL, stat = "identity",
47
-                         position = "identity", arrow = NULL, lineend = "butt",
48
-                         na.rm = FALSE, show.legend = NA, inherit.aes = TRUE,
49
-                         ...) {
50
-  layer(
51
-    data = data,
52
-    mapping = mapping,
53
-    stat = stat,
54
-    geom = GeomSegmentGGtree,
55
-    position = position,
56
-    show.legend = show.legend,
57
-    inherit.aes = inherit.aes,
58
-    params = list(
59
-      arrow = arrow,
60
-      lineend = lineend,
61
-      na.rm = na.rm,
62
-      ...
63
-    )
64
-  )
65
-}
66
-
67
-##' @importFrom ggplot2 GeomSegment
68
-##' @importFrom ggplot2 draw_key_path
69
-GeomSegmentGGtree <- ggproto("GeomSegmentGGtree", GeomSegment,
70
-                          setup_data = function(data, params) {
71
-                              data[data$subset,]
72
-                          },
73
-                          
74
-                          draw_panel = function(data, panel_scales, coord, arrow = NULL,
75
-                              lineend = "butt", na.rm = FALSE) {
76
-
77
-                              GeomSegment$draw_panel(data, panel_scales, coord, arrow,
78
-                                                     lineend, na.rm)
79
-                          },
80
-                          
81
-                          required_aes = c("x", "y", "xend", "yend"),
82
-                          default_aes = aes(colour = "black", size = 0.5, linetype = 1, alpha = NA),
83
-                          
84
-                          draw_key = draw_key_path
85
-                          )
... ...
@@ -1,42 +1,3 @@
1
-##' geom_text2 support aes(subset) via setup_data
2
-##'
3
-##' 
4
-##' @title geom_text2
5
-##' @inheritParams geom_text
6
-##' @return text layer
7
-##' @importFrom ggplot2 layer
8
-##' @importFrom ggplot2 position_nudge
9
-##' @export
10
-##' @seealso
11
-##' \link[ggplot2]{geom_text}
12
-##' @author Guangchuang Yu
13
-geom_text2 <- function(mapping = NULL, data = NULL, stat = "identity",
14
-  position = "identity", parse = FALSE, show.legend = NA, inherit.aes = TRUE,
15
-  ..., nudge_x = 0, nudge_y = 0, check_overlap = FALSE)
16
-{
17
-  if (!missing(nudge_x) || !missing(nudge_y)) {
18
-    if (!missing(position)) {
19
-      stop("Specify either `position` or `nudge_x`/`nudge_y`", call. = FALSE)
20
-    }
21
-
22
-    position <- position_nudge(nudge_x, nudge_y)
23
-  }
24
-
25
-  layer(
26
-    data = data,
27
-    mapping = mapping,
28
-    stat = stat,
29
-    geom = GeomTextGGtree,
30
-    position = position,
31
-    show.legend = show.legend,
32
-    inherit.aes = inherit.aes,
33
-    params = list(
34
-      parse = parse,
35
-      check_overlap = check_overlap,
36
-      ...
37
-    )
38
-  )
39
-}
40 1
 
41 2
 ##' text annotations
42 3
 ##' @export
... ...
@@ -47,12 +8,7 @@ geom_text2 <- function(mapping = NULL, data = NULL, stat = "identity",
47 8
 ##' @param stat The statistical transformation to use on the data for this layer
48 9
 ##' @param position The position adjustment to use for overlapping points on this layer
49 10
 ##' @param parse if TRUE, the labels will be passd into expressions
50
-##' @param show.legend logical
51
-##' @param inherit.aes logical
52 11
 ##' @param ... other arguments passed on to 'layer'
53
-##' @param nudge_x horizontal adjustment
54
-##' @param nudge_y vertical adjustment
55
-##' @param check_overlap if TRUE, text that overlaps previous text in the same layer will not be plotted
56 12
 ##' @source
57 13
 ##' This is just the imported function
58 14
 ##' from the ggplot2 package. The documentation you should
... ...
@@ -62,24 +18,3 @@ geom_text2 <- function(mapping = NULL, data = NULL, stat = "identity",
62 18
 ##' \link[ggplot2]{geom_text}
63 19
 geom_text <- ggplot2::geom_text
64 20
 
65
-
66
-##' @importFrom ggplot2 GeomText
67
-##' @importFrom ggplot2 draw_key_text
68
-GeomTextGGtree <- ggproto("GeomTextGGtree", GeomText,
69
-                          setup_data = function(data, params) {
70
-                              data[data$subset,]
71
-                          },
72
-                          
73
-                          draw_panel = function(data, panel_scales, coord, parse = FALSE,
74
-                              na.rm = FALSE, check_overlap = FALSE) {
75
-                              GeomText$draw_panel(data, panel_scales, coord, parse,
76
-                                                  na.rm, check_overlap)
77
-                          },
78
-
79
-                          required_aes = c("x", "y", "label"),
80
-                          
81
-                          default_aes = aes(colour = "black", size = 3.88, angle = 0, hjust = 0.5,
82
-                              vjust = 0.5, alpha = NA, family = "", fontface = 1, lineheight = 1.2),
83
-                          
84
-                          draw_key = draw_key_text
85
-                          )
... ...
@@ -40,10 +40,12 @@ geom_tiplab <- function(mapping=NULL, hjust = 0, align = FALSE, linetype = "dott
40 40
     } 
41 41
     
42 42
     list(
43
-        geom_text2(mapping=text_mapping, 
44
-                   hjust = hjust, ...),
43
+        geom_text(mapping=text_mapping,
44
+                  subset=.(isTip),
45
+                  hjust = hjust, ...),
45 46
         if (!is.null(dot_mapping))
46
-            geom_segment2(mapping=dot_mapping,
47
+            geom_segment(mapping=dot_mapping,
48
+                         subset=.(isTip),
47 49
                           linetype = linetype,
48 50
                           size = linesize, ...)
49 51
         )
... ...
@@ -9,6 +9,7 @@
9 9
 ##' @param width width of subview, [0,1]
10 10
 ##' @param height height of subview, [0,1]
11 11
 ##' @return ggplot object
12
+##' @importFrom grid editGrob
12 13
 ##' @importFrom ggplot2 annotation_custom
13 14
 ##' @importFrom ggplot2 ggplotGrob
14 15
 ##' @export
... ...
@@ -16,11 +17,20 @@
16 17
 subview <- function(mainview, subview, x, y, width=.1, height=.1) {
17 18
     xrng <- mainview$data$x %>% range %>% diff
18 19
     yrng <- mainview$data$y %>% range %>% diff
19
-   
20
+
21
+    grob <- ggplotGrob(subview)
20 22
     mainview + annotation_custom(
21
-        ggplotGrob(subview),
23
+        editGrob(grob, name=paste(grob$name, annotation_id())),
22 24
         xmin = x - width*xrng,
23 25
         xmax = x + width*xrng,
24 26
         ymin = y - height*yrng,
25 27
         ymax = y + height*yrng)
26 28
 }
29
+
30
+annotation_id <- local({
31
+  i <- 1
32
+  function() {
33
+    i <<- i + 1
34
+    i
35
+  }
36
+})
... ...
@@ -4,26 +4,12 @@
4 4
 \alias{geom_nodepoint}
5 5
 \title{geom_nodepoint}
6 6
 \usage{
7
-geom_nodepoint(mapping = NULL, data = NULL, stat = "identity",
8
-  position = "identity", na.rm = FALSE, show.legend = NA,
9
-  inherit.aes = TRUE, ...)
7
+geom_nodepoint(mapping = NULL, ...)
10 8
 }
11 9
 \arguments{
12 10
 \item{mapping}{aes mapping}
13 11
 
14
-\item{data}{data}
15
-
16
-\item{stat}{stat}
17
-
18
-\item{position}{position}
19
-
20
-\item{na.rm}{logical}
21
-
22
-\item{show.legend}{logical}
23
-
24
-\item{inherit.aes}{logical}
25
-
26
-\item{...}{addktional parameter}
12
+\item{...}{additional parameter}
27 13
 }
28 14
 \value{
29 15
 node point layer
30 16
deleted file mode 100644
... ...
@@ -1,40 +0,0 @@
1
-% Generated by roxygen2 (4.1.1): do not edit by hand
2
-% Please edit documentation in R/geom_point.R
3
-\name{geom_point2}
4
-\alias{geom_point2}
5
-\title{geom_point2}
6
-\usage{
7
-geom_point2(mapping = NULL, data = NULL, stat = "identity",
8
-  position = "identity", na.rm = FALSE, show.legend = NA,
9
-  inherit.aes = TRUE, ...)
10
-}
11
-\arguments{
12
-\item{mapping}{aes mapping}
13
-
14
-\item{data}{data}
15
-
16
-\item{stat}{stat}
17
-
18
-\item{position}{position}
19
-
20
-\item{na.rm}{logical}
21
-
22
-\item{show.legend}{logical}
23
-
24
-\item{inherit.aes}{logical}
25
-
26
-\item{...}{addktional parameter}
27
-}
28
-\value{
29
-point layer
30
-}
31
-\description{
32
-geom_point2 support aes(subset) via setup_data
33
-}
34
-\author{
35
-Guangchuang Yu
36
-}
37
-\seealso{
38
-\link[ggplot2]{geom_point}
39
-}
40
-
... ...
@@ -4,26 +4,12 @@
4 4
 \alias{geom_rootpoint}
5 5
 \title{geom_rootpoint}
6 6
 \usage{
7
-geom_rootpoint(mapping = NULL, data = NULL, stat = "identity",
8
-  position = "identity", na.rm = FALSE, show.legend = NA,
9
-  inherit.aes = TRUE, ...)
7
+geom_rootpoint(mapping = NULL, ...)
10 8
 }
11 9
 \arguments{
12 10
 \item{mapping}{aes mapping}
13 11
 
14
-\item{data}{data}
15
-
16
-\item{stat}{stat}
17
-
18
-\item{position}{position}
19
-
20
-\item{na.rm}{logical}
21
-
22
-\item{show.legend}{logical}
23
-
24
-\item{inherit.aes}{logical}
25
-
26
-\item{...}{addktional parameter}
12
+\item{...}{additional parameter}
27 13
 }
28 14
 \value{
29 15
 root point layer
30 16
deleted file mode 100644
... ...
@@ -1,44 +0,0 @@
1
-% Generated by roxygen2 (4.1.1): do not edit by hand
2
-% Please edit documentation in R/geom_segment.R
3
-\name{geom_segment2}
4
-\alias{geom_segment2}
5
-\title{geom_segment2}
6
-\usage{
7
-geom_segment2(mapping = NULL, data = NULL, stat = "identity",
8
-  position = "identity", arrow = NULL, lineend = "butt", na.rm = FALSE,
9
-  show.legend = NA, inherit.aes = TRUE, ...)
10
-}
11
-\arguments{
12
-\item{mapping}{aes mapping}
13
-
14
-\item{data}{data}
15
-
16
-\item{stat}{stat}
17
-
18
-\item{position}{position}
19
-
20
-\item{arrow}{arrow}
21
-
22
-\item{lineend}{lineend}
23
-
24
-\item{na.rm}{logical}
25
-
26
-\item{show.legend}{logical}
27
-
28
-\item{inherit.aes}{logical}
29
-
30
-\item{...}{additional parameter}
31
-}
32
-\value{
33
-add segment layer
34
-}
35
-\description{
36
-geom_segment2 support aes(subset) via setup_data
37
-}
38
-\author{
39
-Guangchuang Yu
40
-}
41
-\seealso{
42
-\link[ggplot2]{geom_segment}
43
-}
44
-
... ...
@@ -10,9 +10,7 @@ read for the geom_text function can be found here: \link[ggplot2]{geom_text}
10 10
 }
11 11
 \usage{
12 12
 geom_text(mapping = NULL, data = NULL, stat = "identity",
13
-  position = "identity", parse = FALSE, show.legend = NA,
14
-  inherit.aes = TRUE, ..., nudge_x = 0, nudge_y = 0,
15
-  check_overlap = FALSE)
13
+  position = "identity", parse = FALSE, ...)
16 14
 }
17 15
 \arguments{
18 16
 \item{mapping}{the aesthetic mapping}
... ...
@@ -26,17 +24,7 @@ only needed if you want to override he plot defaults.}
26 24
 
27 25
 \item{parse}{if TRUE, the labels will be passd into expressions}
28 26
 
29
-\item{show.legend}{logical}
30
-
31
-\item{inherit.aes}{logical}
32
-
33 27
 \item{...}{other arguments passed on to 'layer'}
34
-
35
-\item{nudge_x}{horizontal adjustment}
36
-
37
-\item{nudge_y}{vertical adjustment}
38
-
39
-\item{check_overlap}{if TRUE, text that overlaps previous text in the same layer will not be plotted}
40 28
 }
41 29
 \description{
42 30
 text annotations
43 31
deleted file mode 100644
... ...
@@ -1,48 +0,0 @@
1
-% Generated by roxygen2 (4.1.1): do not edit by hand
2
-% Please edit documentation in R/geom_text.R
3
-\name{geom_text2}
4
-\alias{geom_text2}
5
-\title{geom_text2}
6
-\usage{
7
-geom_text2(mapping = NULL, data = NULL, stat = "identity",
8
-  position = "identity", parse = FALSE, show.legend = NA,
9
-  inherit.aes = TRUE, ..., nudge_x = 0, nudge_y = 0,
10
-  check_overlap = FALSE)
11
-}
12
-\arguments{
13
-\item{mapping}{the aesthetic mapping}
14
-
15
-\item{data}{A layer specific dataset -
16
-only needed if you want to override he plot defaults.}
17
-
18
-\item{stat}{The statistical transformation to use on the data for this layer}
19
-
20
-\item{position}{The position adjustment to use for overlapping points on this layer}
21
-
22
-\item{parse}{if TRUE, the labels will be passd into expressions}
23
-
24
-\item{show.legend}{logical}
25
-
26
-\item{inherit.aes}{logical}
27
-
28
-\item{...}{other arguments passed on to 'layer'}
29
-
30
-\item{nudge_x}{horizontal adjustment}
31
-
32
-\item{nudge_y}{vertical adjustment}
33
-
34
-\item{check_overlap}{if TRUE, text that overlaps previous text in the same layer will not be plotted}
35
-}
36
-\value{
37
-text layer
38
-}
39
-\description{
40
-geom_text2 support aes(subset) via setup_data
41
-}
42
-\author{
43
-Guangchuang Yu
44
-}
45
-\seealso{
46
-\link[ggplot2]{geom_text}
47
-}
48
-
... ...
@@ -4,26 +4,12 @@
4 4
 \alias{geom_tippoint}
5 5
 \title{geom_tippoint}
6 6
 \usage{
7
-geom_tippoint(mapping = NULL, data = NULL, stat = "identity",
8
-  position = "identity", na.rm = FALSE, show.legend = NA,
9
-  inherit.aes = TRUE, ...)
7
+geom_tippoint(mapping = NULL, ...)
10 8
 }
11 9
 \arguments{
12 10
 \item{mapping}{aes mapping}
13 11
 
14
-\item{data}{data}
15
-
16
-\item{stat}{stat}
17
-
18
-\item{position}{position}
19
-
20
-\item{na.rm}{logical}
21
-
22
-\item{show.legend}{logical}
23
-
24
-\item{inherit.aes}{logical}
25
-
26
-\item{...}{addktional parameter}
12
+\item{...}{additional parameter}
27 13
 }
28 14
 \value{
29 15
 tip point layer
... ...
@@ -289,7 +289,7 @@ With _`collapse`_ function, user can collapse a selected clade.
289 289
 
290 290
 ```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
291 291
 cp <- ggtree(tree) %>% collapse(node=21)
292
-cp + geom_point2(aes(subset=(node == 21)), size=5, shape=23, fill="steelblue")
292
+cp + geom_point(subset=.(node == 21), size=5, shape=23, fill="steelblue")
293 293
 ```
294 294
 
295 295
 ## expand collapsed clade
... ...
@@ -401,8 +401,8 @@ With _`groupOTU`_ and _`groupClade`_, it's easy to highlight selected taxa and e
401 401
 
402 402
 ```{r fig.width=5, fig.height=5, fig.align="center", warning=FALSE}
403 403
 ggtree(tree, aes(color=group, linetype=group)) +
404
-    geom_text2(aes(label=label, subset=(group==2)), hjust = -.5) +
405
-        geom_text2(aes(label=label, subset=(group==1)), hjust = -.5, color="blue")
404
+    geom_text(aes(label=label), subset=.(group==2), hjust = -.5) +
405
+        geom_text(aes(label=label), subset=.(group==1), hjust = -.5, color="blue")
406 406
 ```
407 407
 
408 408