Browse code

add more annotation functions

Zuguang Gu authored on 18/02/2022 19:51:49
Showing 16 changed files

... ...
@@ -6,6 +6,8 @@ CHANGES in VERSION 2.11.1
6 6
 * `anno_block()`: add `align_to` argument.
7 7
 * add `anno_text_box()` and `grid.text_box()`.
8 8
 * add `show_name` argument in `anno_empty()`.
9
+* the validation of annotations in `HeatmapAnnotation()` is simplified.
10
+* add `anno_numeric()`.
9 11
 
10 12
 =========================
11 13
 
... ...
@@ -1,32 +1,32 @@
1
-setGeneric('set_component_width', function(object, ...) standardGeneric('set_component_width'))
2
-setGeneric('annotation_legend_size', function(object, ...) standardGeneric('annotation_legend_size'))
1
+setGeneric('heatmap_legend_size', function(object, ...) standardGeneric('heatmap_legend_size'))
2
+setGeneric('draw_dend', function(object, ...) standardGeneric('draw_dend'))
3
+setGeneric('column_order', function(object, ...) standardGeneric('column_order'))
3 4
 setGeneric('re_size', function(object, ...) standardGeneric('re_size'))
4
-setGeneric('component_height', function(object, ...) standardGeneric('component_height'))
5
+setGeneric('component_width', function(object, ...) standardGeneric('component_width'))
6
+setGeneric('row_order', function(object, ...) standardGeneric('row_order'))
7
+setGeneric('draw_heatmap_body', function(object, ...) standardGeneric('draw_heatmap_body'))
8
+setGeneric('prepare', function(object, ...) standardGeneric('prepare'))
9
+setGeneric('get_legend_param_list', function(object, ...) standardGeneric('get_legend_param_list'))
5 10
 setGeneric('draw_heatmap_list', function(object, ...) standardGeneric('draw_heatmap_list'))
11
+setGeneric('set_component_width', function(object, ...) standardGeneric('set_component_width'))
6 12
 setGeneric('make_row_cluster', function(object, ...) standardGeneric('make_row_cluster'))
7
-setGeneric('draw', function(object, ...) standardGeneric('draw'))
8
-setGeneric('draw_annotation', function(object, ...) standardGeneric('draw_annotation'))
13
+setGeneric('draw_heatmap_legend', function(object, ...) standardGeneric('draw_heatmap_legend'))
9 14
 setGeneric('attach_annotation', function(object, ...) standardGeneric('attach_annotation'))
10
-setGeneric('add_heatmap', function(object, ...) standardGeneric('add_heatmap'))
11
-setGeneric('column_dend', function(object, ...) standardGeneric('column_dend'))
12
-setGeneric('get_color_mapping_list', function(object, ...) standardGeneric('get_color_mapping_list'))
15
+setGeneric('set_component_height', function(object, ...) standardGeneric('set_component_height'))
13 16
 setGeneric('map_to_colors', function(object, ...) standardGeneric('map_to_colors'))
14
-setGeneric('draw_dend', function(object, ...) standardGeneric('draw_dend'))
15
-setGeneric('make_layout', function(object, ...) standardGeneric('make_layout'))
16 17
 setGeneric('row_dend', function(object, ...) standardGeneric('row_dend'))
17
-setGeneric('draw_heatmap_body', function(object, ...) standardGeneric('draw_heatmap_body'))
18
-setGeneric('heatmap_legend_size', function(object, ...) standardGeneric('heatmap_legend_size'))
19
-setGeneric('component_width', function(object, ...) standardGeneric('component_width'))
20
-setGeneric('make_column_cluster', function(object, ...) standardGeneric('make_column_cluster'))
21
-setGeneric('draw_title', function(object, ...) standardGeneric('draw_title'))
22
-setGeneric('draw_annotation_legend', function(object, ...) standardGeneric('draw_annotation_legend'))
23
-setGeneric('prepare', function(object, ...) standardGeneric('prepare'))
24
-setGeneric('set_component_height', function(object, ...) standardGeneric('set_component_height'))
25
-setGeneric('column_order', function(object, ...) standardGeneric('column_order'))
26
-setGeneric('draw_dimnames', function(object, ...) standardGeneric('draw_dimnames'))
18
+setGeneric('add_heatmap', function(object, ...) standardGeneric('add_heatmap'))
27 19
 setGeneric('copy_all', function(object, ...) standardGeneric('copy_all'))
28
-setGeneric('get_legend_param_list', function(object, ...) standardGeneric('get_legend_param_list'))
29
-setGeneric('row_order', function(object, ...) standardGeneric('row_order'))
20
+setGeneric('component_height', function(object, ...) standardGeneric('component_height'))
21
+setGeneric('make_column_cluster', function(object, ...) standardGeneric('make_column_cluster'))
30 22
 setGeneric('adjust_heatmap_list', function(object, ...) standardGeneric('adjust_heatmap_list'))
31
-setGeneric('draw_heatmap_legend', function(object, ...) standardGeneric('draw_heatmap_legend'))
23
+setGeneric('annotation_legend_size', function(object, ...) standardGeneric('annotation_legend_size'))
32 24
 setGeneric('color_mapping_legend', function(object, ...) standardGeneric('color_mapping_legend'))
25
+setGeneric('draw_annotation', function(object, ...) standardGeneric('draw_annotation'))
26
+setGeneric('get_color_mapping_list', function(object, ...) standardGeneric('get_color_mapping_list'))
27
+setGeneric('draw_annotation_legend', function(object, ...) standardGeneric('draw_annotation_legend'))
28
+setGeneric('draw_title', function(object, ...) standardGeneric('draw_title'))
29
+setGeneric('draw_dimnames', function(object, ...) standardGeneric('draw_dimnames'))
30
+setGeneric('make_layout', function(object, ...) standardGeneric('make_layout'))
31
+setGeneric('column_dend', function(object, ...) standardGeneric('column_dend'))
32
+setGeneric('draw', function(object, ...) standardGeneric('draw'))
... ...
@@ -1300,18 +1300,18 @@ anno_barplot = function(x, baseline = 0, which = c("column", "row"), border = TR
1300 1300
 		data_scale = range(rowSums(x, na.rm = TRUE), na.rm = TRUE)
1301 1301
 	}
1302 1302
 
1303
-	if(data_scale[1] == data_scale[2]) data_scale[2] = data_scale[1] + 1
1303
+	if(data_scale[1] == data_scale[2]) data_scale[2] = data_scale[1] + .Machine$double.eps*1.1
1304 1304
 
1305 1305
 	if(!is.null(ylim)) data_scale = ylim
1306 1306
 	if(baseline == "min") {
1307 1307
 		data_scale = data_scale + c(0, extend)*(data_scale[2] - data_scale[1])
1308
-		baseline = min(x)
1308
+		baseline = min(x, na.rm = TRUE)
1309 1309
 	} else if(baseline == "max") {
1310 1310
 		data_scale = data_scale + c(-extend, 0)*(data_scale[2] - data_scale[1])
1311
-		baseline = max(x)
1311
+		baseline = max(x, na.rm = TRUE)
1312 1312
 	} else {
1313 1313
 		if(is.numeric(baseline)) {
1314
-			if(baseline == 0 && all(abs(rowSums(x) - 1) < 1e-6) && !beside) {
1314
+			if(baseline == 0 && all(abs(rowSums(x, na.rm = TRUE) - 1) < 1e-6) && !beside) {
1315 1315
 				data_scale = c(0, 1)
1316 1316
 			} else if(baseline <= data_scale[1]) {
1317 1317
 				data_scale = c(baseline, extend*(data_scale[2] - baseline) + data_scale[2])
... ...
@@ -4314,8 +4314,8 @@ anno_customize = function(x, graphics = list(), which = c("column", "row"),
4314 4314
 # == param
4315 4315
 # -x A vector of numeric values.
4316 4316
 # -rg Range. A numeric vector of length two.
4317
-# -labels_gp. Graphics parameters for labels.
4318
-# -x_convert. A function applied on ``x``. E.g. when ``x`` contains p-values, to map ``x`` to the heights of bars, a transformation of ``-log10(x)`` 
4317
+# -labels_gp Graphics parameters for labels.
4318
+# -x_convert A function applied on ``x``. E.g. when ``x`` contains p-values, to map ``x`` to the heights of bars, a transformation of ``-log10(x)`` 
4319 4319
 #      is normally applied.
4320 4320
 # -labels_format A function applied on ``x``. E.g., when ``x`` is a numeric, ``labels_format`` can be set to ``function(x) sprintf("\%.2f", x)``.
4321 4321
 # -labels_offset Offset of labels to the left or right of bars.
... ...
@@ -4330,7 +4330,7 @@ anno_customize = function(x, graphics = list(), which = c("column", "row"),
4330 4330
 #
4331 4331
 # == example
4332 4332
 # m = matrix(rnorm(100), 10)
4333
-# x = numeric(10)
4333
+# x = rnorm(10)
4334 4334
 # Heatmap(m, right_annotation = rowAnnotation(numeric = anno_numeric(x)))
4335 4335
 anno_numeric = function(x, rg = range(x), labels_gp = gpar(), x_convert = NULL, 
4336 4336
 	labels_format = NULL, labels_offset = unit(4, "pt"),
... ...
@@ -4359,6 +4359,10 @@ anno_numeric = function(x, rg = range(x), labels_gp = gpar(), x_convert = NULL,
4359 4359
 		rg = range(x_convert(rg))
4360 4360
 	}
4361 4361
 
4362
+	if(rg[1] == rg[2]) {
4363
+		rg[2] = rg[2] + .Machine$double.eps*1.1
4364
+	}
4365
+
4362 4366
     x[x < rg[1]] = rg[1]
4363 4367
     x[x > rg[2]] = rg[2]
4364 4368
 
... ...
@@ -95,7 +95,7 @@ HeatmapAnnotation = setClass("HeatmapAnnotation",
95 95
 # Zuguang Gu <z.gu@dkfz.de>
96 96
 #
97 97
 HeatmapAnnotation = function(..., 
98
-	df, name, col, na_col = "grey",
98
+	df = NULL, name, col, na_col = "grey",
99 99
 	annotation_legend_param = list(), 
100 100
 	show_legend = TRUE, 
101 101
 	which = c("column", "row"), 
... ...
@@ -150,53 +150,8 @@ HeatmapAnnotation = function(...,
150 150
 	.Object@name = name
151 151
 	n_anno = 0
152 152
 
153
-	#### check system calls ####
154
-	# HeatmapAnnotation is either called by `HeatmapAnnotation()` or by `rowAnnotation()`/`columnAnnotation()`
155
-	sc = sys.calls()
156
-	nsc = length(sc)
157
-	if(nsc == 1) {  # HeatmapAnnotation(...)
158
-		scl = as.list(sc[[1]])
159
-		arg_list = scl[-1]
160
-	} else {
161
-		
162
-		scl = as.list(sc[[nsc-1]])
163
-		if(is.function(scl[[1]])) {
164
-			if(identical(scl[[1]], pheatmap)) {
165
-				scl = as.list(sc[[nsc]])
166
-				arg_list = scl[-1]
167
-			} else if(identical(scl[[1]], heatmap)) {
168
-				scl = as.list(sc[[nsc]])
169
-				arg_list = scl[-1]
170
-			} else if(identical(scl[[1]], heatmap.2)) {
171
-				scl = as.list(sc[[nsc]])
172
-				arg_list = scl[-1]
173
-			} else {
174
-				# do.call(rowAnnotation, list(...))
175
-				# do.call(columnAnnotation, list(...))
176
-				arg_list = scl[-1]
177
-			}
178
-		} else if(any(as.character(scl[[1]]) %in% c("HeatmapAnnotation", "rowAnnotation", "columnAnnotation"))) { 
179
-			# columnAnnotation(...), rowAnnotation(...)
180
-			# do.call("columnAnnotation", list(...))
181
-			# do.call("rowAnnotation", list(...))
182
-			arg_list = scl[-1]
183
-		} else {
184
-			# do.call("HeatmapAnnotation", list(...))
185
-			# do.call(HeatmapAnnotation, list(...))
186
-			scl = as.list(sc[[nsc]])
187
-			arg_list = scl[-1]
188
-		}
189
-	}
190
-
191
-    called_args = names(arg_list)
192
-    anno_args = setdiff(called_args, fun_args)
193
-    if(any(anno_args == "")) stop_wrap("annotations should have names.")
194
-    if(is.null(called_args)) {
195
-    	stop_wrap("It seems you are putting only one argument to the function. If it is a simple vector annotation or a function annotation (e.g. anno_*()), specify it as HeatmapAnnotation(name = value). If it is a data frame annotation, specify it as HeatmapAnnotation(df = value)")
196
-    }
197
-
198 153
     ##### pull all annotation to `anno_value_list`####
199
-    if("df" %in% called_args) {
154
+    if(!is.null(df)) {
200 155
     	if(is.matrix(df)) {
201 156
     		warning_wrap("`df` should be a data frame while not a matrix. Convert it to data frame.")
202 157
     		df = as.data.frame(df)
... ...
@@ -209,23 +164,35 @@ HeatmapAnnotation = function(...,
209 164
     }
210 165
 
211 166
     anno_arg_list = list(...)
212
-	if("df" %in% called_args && length(anno_arg_list)) {
213
-		if(any(duplicated(c(names(df), names(anno_arg_list))))) {
214
-			stop_wrap("Annotation names are duplicated. Check the column names of `df`.")
167
+    anno_arg_names = names(anno_arg_list)
168
+	if(any(anno_arg_names == "")) {
169
+		stop_wrap("Annotations should have names.")
170
+	}
171
+	if(is.null(anno_arg_names)) {
172
+		if(length(anno_arg_list) == 1) {
173
+			stop_wrap("The annotation should be specified as name-value pairs or via argument `df` with a data frame.")
174
+		}
175
+		if(length(anno_arg_list) > 1) {
176
+			stop_wrap("Annotations should have names.")
177
+		}
178
+	}
179
+
180
+	if(!is.null(df) && length(anno_arg_list)) {
181
+		if(any(duplicated(c(names(df), anno_arg_names)))) {
182
+			stop_wrap("Annotation names are duplicated to those in `df`. Check the column names of `df`.")
215 183
 		}
216 184
 	}
217 185
 
218 186
 	anno_value_list = list()
219
-	for(nm in called_args) {
220
-		if(nm %in% names(anno_arg_list)) {
221
-			anno_value_list[[nm]] = anno_arg_list[[nm]]
222
-		} else if(nm == "df") {
223
-			for(nm2 in colnames(df)) {
224
-				if(is.null(rownames(df))) {
225
-					anno_value_list[[nm2]] = df[, nm2]
226
-				} else {
227
-					anno_value_list[[nm2]] = structure(df[, nm2], names = rownames(df))
228
-				}
187
+	for(nm in anno_arg_names) {
188
+		anno_value_list[[nm]] = anno_arg_list[[nm]]
189
+	}
190
+	if(!is.null(df)) {
191
+		for(nm2 in colnames(df)) {
192
+			if(is.null(rownames(df))) {
193
+				anno_value_list[[nm2]] = df[, nm2]
194
+			} else {
195
+				anno_value_list[[nm2]] = structure(df[, nm2], names = rownames(df))
229 196
 			}
230 197
 		}
231 198
 	}
... ...
@@ -12,7 +12,7 @@
12 12
 # -round_corners Whether to draw round corners for the box.
13 13
 # -r Radius of the round corners.
14 14
 # -line_space Space between lines. The value can be a `grid::unit` object or a numeric scalar which is measured in mm.
15
-# -word_space Space between texts The value can be a `grid::unit` object or a numeric scalar which is measured in mm.
15
+# -text_space Space between texts The value can be a `grid::unit` object or a numeric scalar which is measured in mm.
16 16
 # -max_width The maximal width of the viewport to put the word cloud. The value can be a `grid::unit` object or a numeric scalar which is measured in mm.
17 17
 #        Note this might be larger than the final width of the returned grob object.
18 18
 # -padding Padding of the box, i.e. space between text and the four box borders. The value should be a `grid::unit` object with length 1, 2 or 4. If 
... ...
@@ -213,7 +213,7 @@ text_box_grob = function(text, x = unit(0.5, "npc"), y = unit(0.5, "npc"), just
213 213
 # Width for text_box grob
214 214
 #
215 215
 # == param
216
-# -x The ``text_box`` grob returned by `text_boxd_grob`.
216
+# -x The ``text_box`` grob returned by `text_box_grob`.
217 217
 #
218 218
 # == value
219 219
 # A `grid::unit` object.
... ...
@@ -8,7 +8,7 @@ Constructor Method for HeatmapAnnotation class
8 8
 }
9 9
 \usage{
10 10
 HeatmapAnnotation(...,
11
-    df, name, col, na_col = "grey",
11
+    df = NULL, name, col, na_col = "grey",
12 12
     annotation_legend_param = list(),
13 13
     show_legend = TRUE,
14 14
     which = c("column", "row"),
... ...
@@ -10,9 +10,9 @@ Method dispatch page for \code{add_heatmap}.
10 10
 \code{add_heatmap} can be dispatched on following classes:
11 11
 
12 12
 \itemize{
13
+\item \code{\link{add_heatmap,HeatmapAnnotation-method}}, \code{\link{HeatmapAnnotation-class}} class method
13 14
 \item \code{\link{add_heatmap,Heatmap-method}}, \code{\link{Heatmap-class}} class method
14 15
 \item \code{\link{add_heatmap,HeatmapList-method}}, \code{\link{HeatmapList-class}} class method
15
-\item \code{\link{add_heatmap,HeatmapAnnotation-method}}, \code{\link{HeatmapAnnotation-class}} class method
16 16
 }
17 17
 }
18 18
 \examples{
... ...
@@ -18,8 +18,8 @@ anno_numeric(x, rg = range(x), labels_gp = gpar(), x_convert = NULL,
18 18
 
19 19
   \item{x}{A vector of numeric values.}
20 20
   \item{rg}{Range. A numeric vector of length two.}
21
-  \item{labels_gp.}{Graphics parameters for labels.}
22
-  \item{x_convert.}{A function applied on \code{x}. E.g. when \code{x} contains p-values, to map \code{x} to the heights of bars, a transformation of \code{-log10(x)}  is normally applied.}
21
+  \item{labels_gp}{Graphics parameters for labels.}
22
+  \item{x_convert}{A function applied on \code{x}. E.g. when \code{x} contains p-values, to map \code{x} to the heights of bars, a transformation of \code{-log10(x)}  is normally applied.}
23 23
   \item{labels_format}{A function applied on \code{x}. E.g., when \code{x} is a numeric, \code{labels_format} can be set to \code{function(x) sprintf("\%.2f", x)}.}
24 24
   \item{labels_offset}{Offset of labels to the left or right of bars.}
25 25
   \item{bg_gp}{Graphics parameters for the background bars.}
... ...
@@ -10,8 +10,8 @@ Method dispatch page for \code{column_order}.
10 10
 \code{column_order} can be dispatched on following classes:
11 11
 
12 12
 \itemize{
13
-\item \code{\link{column_order,Heatmap-method}}, \code{\link{Heatmap-class}} class method
14 13
 \item \code{\link{column_order,HeatmapList-method}}, \code{\link{HeatmapList-class}} class method
14
+\item \code{\link{column_order,Heatmap-method}}, \code{\link{Heatmap-class}} class method
15 15
 }
16 16
 }
17 17
 \examples{
... ...
@@ -10,8 +10,8 @@ Method dispatch page for \code{component_height}.
10 10
 \code{component_height} can be dispatched on following classes:
11 11
 
12 12
 \itemize{
13
-\item \code{\link{component_height,Heatmap-method}}, \code{\link{Heatmap-class}} class method
14 13
 \item \code{\link{component_height,HeatmapList-method}}, \code{\link{HeatmapList-class}} class method
14
+\item \code{\link{component_height,Heatmap-method}}, \code{\link{Heatmap-class}} class method
15 15
 }
16 16
 }
17 17
 \examples{
... ...
@@ -10,12 +10,12 @@ Method dispatch page for \code{draw}.
10 10
 \code{draw} can be dispatched on following classes:
11 11
 
12 12
 \itemize{
13
-\item \code{\link{draw,SingleAnnotation-method}}, \code{\link{SingleAnnotation-class}} class method
14 13
 \item \code{\link{draw,AnnotationFunction-method}}, \code{\link{AnnotationFunction-class}} class method
15
-\item \code{\link{draw,Heatmap-method}}, \code{\link{Heatmap-class}} class method
14
+\item \code{\link{draw,SingleAnnotation-method}}, \code{\link{SingleAnnotation-class}} class method
16 15
 \item \code{\link{draw,Legends-method}}, \code{\link{Legends-class}} class method
17 16
 \item \code{\link{draw,HeatmapAnnotation-method}}, \code{\link{HeatmapAnnotation-class}} class method
18 17
 \item \code{\link{draw,HeatmapList-method}}, \code{\link{HeatmapList-class}} class method
18
+\item \code{\link{draw,Heatmap-method}}, \code{\link{Heatmap-class}} class method
19 19
 }
20 20
 }
21 21
 \examples{
... ...
@@ -10,8 +10,8 @@ Method dispatch page for \code{draw_title}.
10 10
 \code{draw_title} can be dispatched on following classes:
11 11
 
12 12
 \itemize{
13
-\item \code{\link{draw_title,Heatmap-method}}, \code{\link{Heatmap-class}} class method
14 13
 \item \code{\link{draw_title,HeatmapList-method}}, \code{\link{HeatmapList-class}} class method
14
+\item \code{\link{draw_title,Heatmap-method}}, \code{\link{Heatmap-class}} class method
15 15
 }
16 16
 }
17 17
 \examples{
... ...
@@ -10,12 +10,12 @@ Method dispatch page for \code{show}.
10 10
 \code{show} can be dispatched on following classes:
11 11
 
12 12
 \itemize{
13
+\item \code{\link{show,SingleAnnotation-method}}, \code{\link{SingleAnnotation-class}} class method
13 14
 \item \code{\link{show,HeatmapAnnotation-method}}, \code{\link{HeatmapAnnotation-class}} class method
15
+\item \code{\link{show,Heatmap-method}}, \code{\link{Heatmap-class}} class method
14 16
 \item \code{\link{show,HeatmapList-method}}, \code{\link{HeatmapList-class}} class method
15
-\item \code{\link{show,ColorMapping-method}}, \code{\link{ColorMapping-class}} class method
16 17
 \item \code{\link{show,AnnotationFunction-method}}, \code{\link{AnnotationFunction-class}} class method
17
-\item \code{\link{show,SingleAnnotation-method}}, \code{\link{SingleAnnotation-class}} class method
18
-\item \code{\link{show,Heatmap-method}}, \code{\link{Heatmap-class}} class method
18
+\item \code{\link{show,ColorMapping-method}}, \code{\link{ColorMapping-class}} class method
19 19
 }
20 20
 }
21 21
 \examples{
... ...
@@ -23,7 +23,7 @@ text_box_grob(text, x = unit(0.5, "npc"), y = unit(0.5, "npc"), just = "centre",
23 23
   \item{round_corners}{Whether to draw round corners for the box.}
24 24
   \item{r}{Radius of the round corners.}
25 25
   \item{line_space}{Space between lines. The value can be a \code{\link[grid]{unit}} object or a numeric scalar which is measured in mm.}
26
-  \item{word_space}{Space between texts The value can be a \code{\link[grid]{unit}} object or a numeric scalar which is measured in mm.}
26
+  \item{text_space}{Space between texts The value can be a \code{\link[grid]{unit}} object or a numeric scalar which is measured in mm.}
27 27
   \item{max_width}{The maximal width of the viewport to put the word cloud. The value can be a \code{\link[grid]{unit}} object or a numeric scalar which is measured in mm. Note this might be larger than the final width of the returned grob object.}
28 28
   \item{padding}{Padding of the box, i.e. space between text and the four box borders. The value should be a \code{\link[grid]{unit}} object with length 1, 2 or 4. If  length of the input unit is 2, the first value is the padding both to the top and to the bottom, and the second value is the padding to the left and right. If length of the input unit is 4, the four values correspond to paddings to the bottom, left, top and right of the box.}
29 29
   \item{first_text_from}{Should the texts be added from the top of the box or from the bottom? Value should be either "top" or "bottom".}
... ...
@@ -11,7 +11,7 @@ Width for text_box grob
11 11
 }
12 12
 \arguments{
13 13
 
14
-  \item{x}{The \code{text_box} grob returned by \code{\link{text_boxd_grob}}.}
14
+  \item{x}{The \code{text_box} grob returned by \code{\link{text_box_grob}}.}
15 15
 
16 16
 }
17 17
 \value{
... ...
@@ -270,3 +270,36 @@ ha = HeatmapAnnotation(foo = 1:10, bar = letters[1:10],
270 270
 		foo = gt_render("foo", gp = gpar(box_fill = "red")),
271 271
 		bar = gt_render("bar", gp = gpar(box_fill = "blue"))))
272 272
 draw(ha, test = TRUE)
273
+
274
+
275
+### test whether arguments can be captured
276
+HeatmapAnnotation(a = 1:10)
277
+rowAnnotation(a = 1:10)
278
+columnAnnotation(a = 1:10)
279
+do.call(HeatmapAnnotation, list(a = 1:10))
280
+do.call(rowAnnotation, list(a = 1:10))
281
+do.call(columnAnnotation, list(a = 1:10))
282
+do.call("HeatmapAnnotation", list(a = 1:10))
283
+do.call("rowAnnotation", list(a = 1:10))
284
+do.call("columnAnnotation", list(a = 1:10))
285
+
286
+f = function() HeatmapAnnotation(a = 1:10)
287
+f()
288
+f = function() rowAnnotation(a = 1:10)
289
+f()
290
+f = function() columnAnnotation(a = 1:10)
291
+f()
292
+
293
+sapply(1, function(x) HeatmapAnnotation(a = 1:10))
294
+sapply(1, function(x) rowAnnotation(a = 1:10))
295
+sapply(1, function(x) columnAnnotation(a = 1:10))
296
+
297
+mapply(function(x, y) HeatmapAnnotation(a = 1:10), list(1), list(1))
298
+mapply(function(x, y) rowAnnotation(a = 1:10), list(1), list(1))
299
+mapply(function(x, y) columnAnnotation(a = 1:10), list(1), list(1))
300
+
301
+
302
+try({
303
+	HeatmapAnnotation(1:10)
304
+	HeatmapAnnotation(df = data.frame(a = 1:10), a = 1:10)
305
+})