Browse code

now geom_text2, geom_label2, geom_point2 and geom_segment2 work with ggplot2

guangchuang yu authored on 01/08/2017 12:22:46
Showing 11 changed files

... ...
@@ -1,5 +1,6 @@
1 1
 CHANGES IN VERSION 1.9.3
2 2
 ------------------------
3
+ o now geom_text2, geom_label2, geom_point2 and geom_segment2 work with ggplot2 <2017-08-01, Tue>
3 4
  o update fortify.jplace to support number of placement (nplace) <2017-07-27, Thu>
4 5
 
5 6
 CHANGES IN VERSION 1.9.2
... ...
@@ -6,6 +6,7 @@
6 6
 ##' @param data A layer specific dataset -
7 7
 ##'             only needed if you want to override he plot defaults.
8 8
 ##' @param ... other arguments passed on to 'layer'
9
+##' @param stat Name of stat to modify data
9 10
 ##' @param position The position adjustment to use for overlapping points on this layer
10 11
 ##' @param family sans by default, can be any supported font
11 12
 ##' @param parse if TRUE, the labels will be passd into expressions
... ...
@@ -26,6 +27,7 @@
26 27
 ##' @author Guangchuang Yu
27 28
 geom_label2 <- function(mapping = NULL, data = NULL,
28 29
                         ...,
30
+                        stat = "identity",
29 31
                         position = "identity",
30 32
                         family = "sans",
31 33
                         parse = FALSE,
... ...
@@ -46,7 +48,7 @@ geom_label2 <- function(mapping = NULL, data = NULL,
46 48
         position <- position_nudge(nudge_x, nudge_y)
47 49
     }
48 50
 
49
-    default_aes <- aes_(node=~node)
51
+    default_aes <- aes_() #node=~node)
50 52
     if (is.null(mapping)) {
51 53
         mapping <- default_aes
52 54
     } else {
... ...
@@ -65,7 +67,7 @@ geom_label2 <- function(mapping = NULL, data = NULL,
65 67
     layer(
66 68
         data = data,
67 69
         mapping = mapping,
68
-        stat = StatTreeData,
70
+        stat = stat,
69 71
         geom = GeomLabelGGtree,
70 72
         position = position,
71 73
         show.legend = show.legend,
... ...
@@ -91,24 +93,24 @@ GeomLabelGGtree <- ggproto("GeomLabelGGtree", GeomLabel,
91 93
                                if (is.null(data$subset))
92 94
                                    return(data)
93 95
                                data[which(data$subset),]
94
-                           },
95
-                           draw_panel = function(self, data, panel_scales, coord, parse = FALSE,
96
-                                                 na.rm = FALSE,
97
-                                                 label.padding = unit(0.25, "lines"),
98
-                                                 label.r = unit(0.15, "lines"),
99
-                                                 label.size = 0.25) {
100
-                               GeomLabel$draw_panel(data, panel_scales, coord, parse,
101
-                                                   na.rm, label.padding, label.r, label.size)
102
-                           },
103
-                           required_aes = c("node", "x", "y", "label"),
96
+                           }## ,
97
+                           ## draw_panel = function(self, data, panel_scales, coord, parse = FALSE,
98
+                           ##                       na.rm = FALSE,
99
+                           ##                       label.padding = unit(0.25, "lines"),
100
+                           ##                       label.r = unit(0.15, "lines"),
101
+                           ##                       label.size = 0.25) {
102
+                           ##     GeomLabel$draw_panel(data, panel_scales, coord, parse,
103
+                           ##                         na.rm, label.padding, label.r, label.size)
104
+                           ## },
105
+                           ## required_aes = c("x", "y", "label"),
104 106
 
105
-                           default_aes = aes(
106
-                               colour = "black", fill = "white", size = 3.88, angle = 0,
107
-                               hjust = 0.5, vjust = 0.5, alpha = NA, family = "", fontface = 1,
108
-                               lineheight = 1.2
109
-                           ),
107
+                           ## default_aes = aes(
108
+                           ##     colour = "black", fill = "white", size = 3.88, angle = 0,
109
+                           ##     hjust = 0.5, vjust = 0.5, alpha = NA, family = "", fontface = 1,
110
+                           ##     lineheight = 1.2
111
+                           ## ),
110 112
 
111
-                           draw_key = draw_key_label
113
+                           ## draw_key = draw_key_label
112 114
                            )
113 115
 
114 116
 
... ...
@@ -10,14 +10,13 @@
10 10
 geom_tippoint <- function(mapping = NULL, data = NULL,
11 11
                        position = "identity", na.rm = FALSE,
12 12
                           show.legend = NA, inherit.aes = TRUE, ...) {
13
-    isTip <- NULL
14
-    self_mapping <- aes(subset = isTip)
13
+    self_mapping <- aes_(node = ~node, subset = ~isTip)
15 14
     if (is.null(mapping)) {
16 15
         mapping <- self_mapping
17 16
     } else {
18 17
         mapping <- modifyList(self_mapping, mapping)
19 18
     }
20
-    geom_point2(mapping, data, position, na.rm, show.legend, inherit.aes, ...)
19
+    geom_point2(mapping, data, position, na.rm, show.legend, inherit.aes, stat = StatTreeData, ...)
21 20
 }
22 21
 
23 22
 ## angle is not supported,
... ...
@@ -52,14 +51,14 @@ geom_tippoint <- function(mapping = NULL, data = NULL,
52 51
 geom_nodepoint <- function(mapping = NULL, data = NULL,
53 52
                        position = "identity", na.rm = FALSE,
54 53
                        show.legend = NA, inherit.aes = TRUE, ...) {
55
-    isTip <- NULL
56
-    self_mapping <- aes(subset = !isTip)
54
+    node <- isTip <- NULL
55
+    self_mapping <- aes(node = node, subset = !isTip)
57 56
     if (is.null(mapping)) {
58 57
         mapping <- self_mapping
59 58
     } else {
60 59
         mapping %<>% modifyList(self_mapping)
61 60
     }
62
-    geom_point2(mapping, data, position, na.rm, show.legend, inherit.aes, ...)
61
+    geom_point2(mapping, data, position, na.rm, show.legend, inherit.aes, stat = StatTreeData, ...)
63 62
 }
64 63
 
65 64
 
... ...
@@ -75,13 +74,13 @@ geom_rootpoint <- function(mapping = NULL, data = NULL,
75 74
                            position = "identity", na.rm = FALSE,
76 75
                            show.legend = NA, inherit.aes = TRUE, ...) {
77 76
     isTip <- node <- parent <- NULL
78
-    self_mapping <- aes(subset = (node == parent))
77
+    self_mapping <- aes(node = node, subset = (node == parent))
79 78
     if (is.null(mapping)) {
80 79
         mapping <- self_mapping
81 80
     } else {
82 81
         mapping %<>% modifyList(self_mapping)
83 82
     }
84
-    geom_point2(mapping, data, position, na.rm, show.legend, inherit.aes, ...)
83
+    geom_point2(mapping, data, position, na.rm, show.legend, inherit.aes, stat = StatTreeData, ...)
85 84
 }
86 85
 
87 86
 
... ...
@@ -91,6 +90,7 @@ geom_rootpoint <- function(mapping = NULL, data = NULL,
91 90
 ##' @title geom_point2
92 91
 ##' @param mapping aes mapping
93 92
 ##' @param data data
93
+##' @param stat Name of stat to modify data
94 94
 ##' @param position position
95 95
 ##' @param na.rm logical
96 96
 ##' @param show.legend logical
... ...
@@ -102,12 +102,12 @@ geom_rootpoint <- function(mapping = NULL, data = NULL,
102 102
 ##' \link[ggplot2]{geom_point}
103 103
 ##' @return point layer
104 104
 ##' @author Guangchuang Yu
105
-geom_point2 <- function(mapping = NULL, data = NULL,
105
+geom_point2 <- function(mapping = NULL, data = NULL, stat = "identity",
106 106
                        position = "identity", na.rm = FALSE,
107 107
                        show.legend = NA, inherit.aes = TRUE, ...) {
108 108
 
109 109
 
110
-    default_aes <- aes_(node=~node)
110
+    default_aes <- aes_() # node=~node)
111 111
     if (is.null(mapping)) {
112 112
         mapping <- default_aes
113 113
     } else {
... ...
@@ -117,7 +117,7 @@ geom_point2 <- function(mapping = NULL, data = NULL,
117 117
     layer(
118 118
         data = data,
119 119
         mapping = mapping,
120
-        stat = StatTreeData,
120
+        stat = stat,
121 121
         geom = GeomPointGGtree,
122 122
         position = position,
123 123
         show.legend = show.legend,
... ...
@@ -18,7 +18,7 @@ geom_aline <- function(mapping=NULL, linetype="dotted", size=1, ...) {
18 18
 
19 19
     geom_segment2(dot_mapping,
20 20
                   linetype=linetype,
21
-                  size=size, ...)
21
+                  size=size, stat = StatTreeData, ...)
22 22
 }
23 23
 
24 24
 
... ...
@@ -29,6 +29,7 @@ geom_aline <- function(mapping=NULL, linetype="dotted", size=1, ...) {
29 29
 ##' @title geom_segment2
30 30
 ##' @param mapping aes mapping
31 31
 ##' @param data data
32
+##' @param stat Name of stat to modify data
32 33
 ##' @param position position
33 34
 ##' @param arrow arrow
34 35
 ##' @param lineend lineend
... ...
@@ -42,7 +43,7 @@ geom_aline <- function(mapping=NULL, linetype="dotted", size=1, ...) {
42 43
 ##' \link[ggplot2]{geom_segment}
43 44
 ##' @return add segment layer
44 45
 ##' @author Guangchuang Yu
45
-geom_segment2 <- function(mapping = NULL, data = NULL,
46
+geom_segment2 <- function(mapping = NULL, data = NULL, stat = "identity",
46 47
                          position = "identity", arrow = NULL, lineend = "butt",
47 48
                          na.rm = FALSE, show.legend = NA, inherit.aes = TRUE,
48 49
                          ...) {
... ...
@@ -57,7 +58,7 @@ geom_segment2 <- function(mapping = NULL, data = NULL,
57 58
     layer(
58 59
         data = data,
59 60
         mapping = mapping,
60
-        stat = StatTreeData,
61
+        stat = stat,
61 62
         geom = GeomSegmentGGtree,
62 63
         position = position,
63 64
         show.legend = show.legend,
... ...
@@ -79,19 +80,21 @@ GeomSegmentGGtree <- ggproto("GeomSegmentGGtree", GeomSegment,
79 80
                                  if (is.null(data$subset))
80 81
                                      return(data)
81 82
                                  data[which(data$subset),]
82
-                             },
83
+                             }
83 84
 
84
-                             draw_panel = function(data, panel_scales, coord, arrow = NULL,
85
-                                                   lineend = "butt", na.rm = FALSE) {
85
+                            ## ,
86 86
 
87
-                                 GeomSegment$draw_panel(data, panel_scales, coord, arrow,
88
-                                                        lineend, na.rm)
89
-                             },
87
+                            ##  draw_panel = function(data, panel_scales, coord, arrow = NULL,
88
+                            ##                        lineend = "butt", na.rm = FALSE) {
90 89
 
91
-                             required_aes = c("x", "y", "xend", "yend"),
92
-                             default_aes = aes(colour = "black", size = 0.5, linetype = 1, alpha = NA),
90
+                            ##      GeomSegment$draw_panel(data, panel_scales, coord, arrow,
91
+                            ##                             lineend, na.rm)
92
+                            ##  },
93 93
 
94
-                             draw_key = draw_key_path
94
+                            ##  required_aes = c("x", "y", "xend", "yend"),
95
+                            ##  default_aes = aes(colour = "black", size = 0.5, linetype = 1, alpha = NA),
96
+
97
+                            ##  draw_key = draw_key_path
95 98
                              )
96 99
 
97 100
 
... ...
@@ -6,6 +6,7 @@
6 6
 ##' @param data A layer specific dataset -
7 7
 ##'             only needed if you want to override he plot defaults.
8 8
 ##' @param ... other arguments passed on to 'layer'
9
+##' @param stat Name of stat to modify data
9 10
 ##' @param position The position adjustment to use for overlapping points on this layer
10 11
 ##' @param family sans by default, can be any supported font
11 12
 ##' @param parse if TRUE, the labels will be passd into expressions
... ...
@@ -25,6 +26,7 @@
25 26
 ##' @author Guangchuang Yu
26 27
 geom_text2 <- function(mapping = NULL, data = NULL,
27 28
                        ...,
29
+                       stat = "identity",
28 30
                        position = "identity",
29 31
                        family="sans",
30 32
                        parse = FALSE,
... ...
@@ -43,7 +45,7 @@ geom_text2 <- function(mapping = NULL, data = NULL,
43 45
         position <- position_nudge(nudge_x, nudge_y)
44 46
     }
45 47
 
46
-    default_aes <- aes_(node=~node)
48
+    default_aes <- aes_() #node=~node)
47 49
     if (is.null(mapping)) {
48 50
         mapping <- default_aes
49 51
     } else {
... ...
@@ -61,7 +63,7 @@ geom_text2 <- function(mapping = NULL, data = NULL,
61 63
     layer(
62 64
         data = data,
63 65
         mapping = mapping,
64
-        stat = StatTreeData,
66
+        stat = stat, #StatTreeData,
65 67
         geom = GeomTextGGtree,
66 68
         position = position,
67 69
         show.legend = show.legend,
... ...
@@ -94,7 +96,7 @@ GeomTextGGtree <- ggproto("GeomTextGGtree", GeomText,
94 96
                               GeomText$draw_panel(data, panel_scales, coord, parse,
95 97
                                                   na.rm, check_overlap)
96 98
                           },
97
-                          required_aes = c("node", "x", "y", "label"),
99
+                          required_aes = c("x", "y", "label"),
98 100
 
99 101
                           default_aes = aes(colour = "black", size = 3.88, angle = 0, hjust = 0.5,
100 102
                               vjust = 0.5, alpha = NA, family = "", fontface = 1, lineheight = 1.2),
... ...
@@ -25,12 +25,12 @@ geom_tiplab <- function(mapping=NULL, hjust = 0,  align = FALSE, linetype = "dot
25 25
     } else {
26 26
         text_geom <- geom_label2
27 27
     }
28
-    x <- y <- label <- isTip <- NULL
28
+    x <- y <- label <- isTip <- node <- NULL
29 29
     if (align == TRUE) {
30
-        self_mapping <- aes(x = max(x, na.rm=TRUE) + diff(range(x, na.rm=TRUE))/200, y = y, label = label, subset= isTip)
30
+        self_mapping <- aes(x = max(x, na.rm=TRUE) + diff(range(x, na.rm=TRUE))/200, y = y, label = label, node = node, subset = isTip)
31 31
     }
32 32
     else {
33
-        self_mapping <- aes(x = x + diff(range(x, na.rm=TRUE))/200, y= y, label = label, subset= isTip)
33
+        self_mapping <- aes(x = x + diff(range(x, na.rm=TRUE))/200, y= y, label = label, node = node, subset = isTip)
34 34
     }
35 35
 
36 36
     if (is.null(mapping)) {
... ...
@@ -46,19 +46,20 @@ geom_tiplab <- function(mapping=NULL, hjust = 0,  align = FALSE, linetype = "dot
46 46
         segment_mapping <- aes(x = max(x, na.rm=TRUE),
47 47
                                xend = x + diff(range(x, na.rm=TRUE))/200,
48 48
                                y = y, yend = y,
49
-                               subset=isTip)
49
+                               node = node,
50
+                               subset = isTip)
50 51
         if (!is.null(mapping))
51 52
             segment_mapping <- modifyList(segment_mapping, mapping)
52 53
     }
53 54
 
54 55
     list(
55 56
         text_geom(mapping=text_mapping,
56
-                  hjust = hjust, nudge_x = offset, ...)
57
+                  hjust = hjust, nudge_x = offset, stat = StatTreeData, ...)
57 58
         ,
58 59
         if (show_segment)
59 60
             geom_segment2(mapping = segment_mapping,
60 61
                           linetype = linetype,
61
-                          size = linesize, ...)
62
+                          size = linesize, stat = StatTreeData, ...)
62 63
 
63 64
             ## geom_tipsegment(mapping = segment_mapping,
64 65
             ##                 offset = offset,
... ...
@@ -81,12 +82,12 @@ geom_tiplab <- function(mapping=NULL, hjust = 0,  align = FALSE, linetype = "dot
81 82
 ##' @references \url{https://groups.google.com/forum/#!topic/bioc-ggtree/o35PV3iHO-0}
82 83
 geom_tiplab2 <- function(mapping=NULL, hjust=0, ...) {
83 84
 
84
-    angle <- NULL
85
-    isTip <- NULL
85
+    angle <- isTip <- node <- NULL
86
+
86 87
     ## m1 <- aes(subset=(abs(angle) < 90), angle=angle)
87 88
     ## m2 <- aes(subset=(abs(angle) >= 90), angle=angle+180)
88
-    m1 <- aes(subset=(isTip & (angle < 90 | angle > 270)), angle=angle)
89
-    m2 <- aes(subset=(isTip & (angle >= 90 & angle <=270)), angle=angle+180)
89
+    m1 <- aes(subset=(isTip & (angle < 90 | angle > 270)), angle=angle, node = node)
90
+    m2 <- aes(subset=(isTip & (angle >= 90 & angle <=270)), angle=angle+180, node = node)
90 91
 
91 92
     if (!is.null(mapping)) {
92 93
         m1 <- modifyList(mapping, m1)
... ...
@@ -6,7 +6,7 @@ ggtree: an R package for visualization and annotation of phylogenetic trees with
6 6
 
7 7
 [![](https://img.shields.io/badge/release%20version-1.8.1-green.svg?style=flat)](https://bioconductor.org/packages/ggtree) [![](https://img.shields.io/badge/devel%20version-1.9.3-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) [![](https://img.shields.io/badge/download-17269/total-blue.svg?style=flat)](https://bioconductor.org/packages/stats/bioc/ggtree) [![](https://img.shields.io/badge/download-885/month-blue.svg?style=flat)](https://bioconductor.org/packages/stats/bioc/ggtree)
8 8
 
9
-[![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-2017--07--31-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)
9
+[![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-2017--08--01-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)
10 10
 
11 11
 [![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) [![Backers on Open Collective](https://opencollective.com/ggtree/backers/badge.svg)](#backers) [![Sponsors on Open Collective](https://opencollective.com/ggtree/sponsors/badge.svg)](#sponsors)
12 12
 
... ...
@@ -4,10 +4,11 @@
4 4
 \alias{geom_label2}
5 5
 \title{geom_label2}
6 6
 \usage{
7
-geom_label2(mapping = NULL, data = NULL, ..., position = "identity",
8
-  family = "sans", parse = FALSE, nudge_x = 0, nudge_y = 0,
9
-  label.padding = unit(0.25, "lines"), label.r = unit(0.15, "lines"),
10
-  label.size = 0.25, na.rm = TRUE, show.legend = NA, inherit.aes = TRUE)
7
+geom_label2(mapping = NULL, data = NULL, ..., stat = "identity",
8
+  position = "identity", family = "sans", parse = FALSE, nudge_x = 0,
9
+  nudge_y = 0, label.padding = unit(0.25, "lines"), label.r = unit(0.15,
10
+  "lines"), label.size = 0.25, na.rm = TRUE, show.legend = NA,
11
+  inherit.aes = TRUE)
11 12
 }
12 13
 \arguments{
13 14
 \item{mapping}{the aesthetic mapping}
... ...
@@ -17,6 +18,8 @@ only needed if you want to override he plot defaults.}
17 18
 
18 19
 \item{...}{other arguments passed on to 'layer'}
19 20
 
21
+\item{stat}{Name of stat to modify data}
22
+
20 23
 \item{position}{The position adjustment to use for overlapping points on this layer}
21 24
 
22 25
 \item{family}{sans by default, can be any supported font}
... ...
@@ -4,14 +4,17 @@
4 4
 \alias{geom_point2}
5 5
 \title{geom_point2}
6 6
 \usage{
7
-geom_point2(mapping = NULL, data = NULL, position = "identity",
8
-  na.rm = FALSE, show.legend = NA, inherit.aes = TRUE, ...)
7
+geom_point2(mapping = NULL, data = NULL, stat = "identity",
8
+  position = "identity", na.rm = FALSE, show.legend = NA,
9
+  inherit.aes = TRUE, ...)
9 10
 }
10 11
 \arguments{
11 12
 \item{mapping}{aes mapping}
12 13
 
13 14
 \item{data}{data}
14 15
 
16
+\item{stat}{Name of stat to modify data}
17
+
15 18
 \item{position}{position}
16 19
 
17 20
 \item{na.rm}{logical}
... ...
@@ -4,15 +4,17 @@
4 4
 \alias{geom_segment2}
5 5
 \title{geom_segment2}
6 6
 \usage{
7
-geom_segment2(mapping = NULL, data = NULL, position = "identity",
8
-  arrow = NULL, lineend = "butt", na.rm = FALSE, show.legend = NA,
9
-  inherit.aes = TRUE, ...)
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 10
 }
11 11
 \arguments{
12 12
 \item{mapping}{aes mapping}
13 13
 
14 14
 \item{data}{data}
15 15
 
16
+\item{stat}{Name of stat to modify data}
17
+
16 18
 \item{position}{position}
17 19
 
18 20
 \item{arrow}{arrow}
... ...
@@ -4,9 +4,10 @@
4 4
 \alias{geom_text2}
5 5
 \title{geom_text2}
6 6
 \usage{
7
-geom_text2(mapping = NULL, data = NULL, ..., position = "identity",
8
-  family = "sans", parse = FALSE, na.rm = TRUE, show.legend = NA,
9
-  inherit.aes = TRUE, nudge_x = 0, nudge_y = 0, check_overlap = FALSE)
7
+geom_text2(mapping = NULL, data = NULL, ..., stat = "identity",
8
+  position = "identity", family = "sans", parse = FALSE, na.rm = TRUE,
9
+  show.legend = NA, inherit.aes = TRUE, nudge_x = 0, nudge_y = 0,
10
+  check_overlap = FALSE)
10 11
 }
11 12
 \arguments{
12 13
 \item{mapping}{the aesthetic mapping}
... ...
@@ -16,6 +17,8 @@ only needed if you want to override he plot defaults.}
16 17
 
17 18
 \item{...}{other arguments passed on to 'layer'}
18 19
 
20
+\item{stat}{Name of stat to modify data}
21
+
19 22
 \item{position}{The position adjustment to use for overlapping points on this layer}
20 23
 
21 24
 \item{family}{sans by default, can be any supported font}