Browse code

improved HeatmapAnnotation class

Zuguang Gu authored on 02/08/2018 12:43:21
Showing 14 changed files

... ...
@@ -52,3 +52,7 @@ setGeneric('draw_dend', function(object, ...) standardGeneric('draw_dend'))
52 52
 setGeneric('draw_heatmap_list', function(object, ...) standardGeneric('draw_heatmap_list'))
53 53
 
54 54
 setGeneric('row_dend', function(object, ...) standardGeneric('row_dend'))
55
+
56
+setGeneric('copy_all', function(object, ...) standardGeneric('copy_all'))
57
+setGeneric('resize', function(object, ...) standardGeneric('resize'))
58
+
55 59
similarity index 57%
56 60
rename from R/annotation_fun.R
57 61
rename to R/AnnotationFunction-class.R
... ...
@@ -8,25 +8,137 @@ AnnotationFunction = setClass("AnnotationFunction",
8 8
 		var_env = "environment",
9 9
 		fun = "function",
10 10
 		subset_rule = "list",
11
-		data_scale = "list"
11
+		subsetable = "logical",
12
+		data_scale = "numeric",
13
+		extended = "ANY"
12 14
 	),
13 15
 	prototype = list(
16
+		fun_name = "",
14 17
 		width = unit(1, "npc"),
15 18
 		height = unit(1, "npc"),
16 19
 		subset_rule = list(),
17
-		data_scale = list(x = NULL, y = NULL),
18
-		n = 0
20
+		subsetable = FALSE,
21
+		data_scale = c(0, 1),
22
+		n = 0,
23
+		extended = unit(c(0, 0, 0, 0), "mm")
19 24
 	)
20 25
 )
21 26
 
27
+anno_width_and_height = function(which, width = NULL, height = NULL, 
28
+	default = unit(1, "cm")) {
29
+
30
+	if(which == "column") {
31
+		if(is.null(height)) {
32
+			height = default
33
+		} else {
34
+			if(!is_abs_unit(height)) {
35
+				stop("height can only be an absolute unit.")
36
+			}
37
+		}
38
+		if(is.null(width)) {
39
+			width = unit(1, "npc")
40
+		}
41
+	}
42
+	if(which == "row") {
43
+		if(is.null(width)) {
44
+			width = default
45
+		} else {
46
+			if(!is_abs_unit(width)) {
47
+				stop("width can only be an absolute unit.")
48
+			}
49
+		}
50
+		if(is.null(height)) {
51
+			height = unit(1, "npc")
52
+		}
53
+	}
54
+	return(list(height = height, width = width))
55
+}
56
+
57
+
58
+AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), 
59
+	var_imported = list(), n = 0, data_scale = c(0, 1), subset_rule = list(), 
60
+	subsetable = FALSE, width = NULL, height = NULL) {
61
+
62
+	which = match.arg(which)[1]
63
+
64
+	anno = new("AnnotationFunction")
65
+
66
+	anno@which = which
67
+	anno@fun_name = fun_name
68
+
69
+	anno_size = anno_width_and_height(which, width, height, unit(1, "cm"))
70
+	anno@width = anno_size$width
71
+	anno@height = anno_size$height
72
+
73
+	anno@n = n
74
+	anno@data_scale = data_scale
75
+
76
+	anno@var_env = new.env()
77
+	if(is.character(var_imported)) {
78
+		for(nm in var_imported) {
79
+			anno@var_env[[nm]] = get(nm, envir = parent.frame())
80
+		}
81
+	} else if(inherits(var_imported, "list")) {
82
+		if(is.null(names(var_imported))) {
83
+			var_imported_nm = sapply(as.list(substitute(var_imported))[-1], as.character)
84
+			names(var_imported) = var_imported_nm
85
+		}
86
+
87
+		for(nm in names(var_imported)) {
88
+			anno@var_env[[nm]] = var_imported[[nm]]
89
+		}
90
+	} else {
91
+		stop_wrap("`var_import` needs to be a character vector which contains variable names or a list of variables")
92
+	}
93
+	
94
+	environment(fun) = anno@var_env
95
+	anno@fun = fun
96
+	
97
+	if(is.null(subset_rule)) {
98
+		for(nm in names(anno@var_env)) {
99
+			if(is.matrix(anno@var_env[[nm]])) {
100
+				anno@subset_rule[[nm]] = subset_matrix_by_row
101
+			} else if(inherits(anno@var_env[[nm]], "gpar")) {
102
+				anno@subset_rule[[nm]] = subset_gp
103
+			} else if(is.vector(anno@var_env[[nm]])) {
104
+				if(length(anno@var_env[[nm]]) > 1) {
105
+					anno@subset_rule[[nm]] = subset_vector
106
+				}
107
+			}
108
+		}
109
+	} else {
110
+		for(nm in names(subset_rule)) {
111
+			anno@subset_rule[[nm]] = subset_rule[[nm]]
112
+		}
113
+	}
114
+
115
+	if(missing(subsetable)) {
116
+		# is user defined subset rule
117
+		if(length(anno@subset_rule)) {
118
+			anno@subsetable = TRUE
119
+		}
120
+	} else {
121
+		anno@subsetable = subsetable
122
+	}
123
+
124
+	return(anno)
125
+}
126
+
22 127
 
23 128
 "[.AnnotationFunction" = function(x, i) {
24 129
 	if(nargs() == 1) {
25 130
 		return(x)
26 131
 	} else {
132
+		if(!x@subsetable) {
133
+			stop("This object is not subsetable.")
134
+		}
27 135
 		x = copy_all(x)
28 136
 		for(var in names(x@subset_rule)) {
29
-			x@var_env[[var]] = x@subset_rule[[var]](x@var_env[[var]], i)
137
+			oe = try(x@var_env[[var]] <- x@subset_rule[[var]](x@var_env[[var]], i), silent = TRUE)
138
+			if(inherits(oe, "try-error")) {
139
+				message(paste0("An error when subsetting ", var))
140
+				stop(oe)
141
+			}
30 142
 		}
31 143
 		if(is.logical(i)) {
32 144
 			x@n = sum(i)
... ...
@@ -48,7 +160,7 @@ setMethod(f = "draw",
48 160
 	}
49 161
 	if(test2) {
50 162
         grid.newpage()
51
-        pushViewport(viewport(width = 0.9, height = 0.9))
163
+        pushViewport(viewport(width = 0.8, height = 0.8))
52 164
     }
53 165
 
54 166
     if(missing(index)) index = seq_len(object@n)
... ...
@@ -61,7 +173,21 @@ setMethod(f = "draw",
61 173
 	object@fun(index)
62 174
 	if(test2) {
63 175
 		grid.text(test, y = unit(1, "npc") + unit(2, "mm"), just = "bottom")
64
-		grid.rect(gp = gpar(fill = "transparent", col = "red"))
176
+
177
+		if(!identical(unit(0, "mm"), object@extended[1])) {
178
+			grid.rect(y = 1, height = unit(1, "npc") + object@extended[1], just = "top",
179
+				gp = gpar(fill = "transparent", col = "red", lty = 2))
180
+		} else if(!identical(unit(0, "mm"), object@extended[[2]])) {
181
+			grid.rect(x = 1, width = unit(1, "npc") + object@extended[2], just = "right",
182
+				gp = gpar(fill = "transparent", col = "red", lty = 2))
183
+		} else if(!identical(unit(0, "mm"), object@extended[[3]])) {
184
+			grid.rect(y = 0, height = unit(1, "npc") + object@extended[3], just = "bottom",
185
+				gp = gpar(fill = "transparent", col = "red", lty = 2))
186
+		} else if(!identical(unit(0, "mm"), object@extended[[4]])) {
187
+			grid.rect(x = 0, width = unit(1, "npc") + object@extended[4], just = "left",
188
+				gp = gpar(fill = "transparent", col = "red", lty = 2))
189
+		}
190
+		
65 191
 	}
66 192
 	popViewport()
67 193
 
... ...
@@ -71,7 +197,6 @@ setMethod(f = "draw",
71 197
 	
72 198
 })
73 199
 
74
-setGeneric('copy_all', function(object, ...) standardGeneric('copy_all'))
75 200
 setMethod(f = "copy_all",
76 201
 	signature = "AnnotationFunction",
77 202
 	definition = function(object, i) {
... ...
@@ -88,54 +213,58 @@ setMethod(f = "show",
88 213
 	signature = "AnnotationFunction",
89 214
 	definition = function(object) {
90 215
 
91
-	cat("An AnnotationFunction object generated by ", object@fun_name, "()\n", sep = "")
216
+	cat("An AnnotationFunction object\n")
217
+	if(object@fun_name == "") {
218
+		cat("  function: user-defined\n")
219
+	} else {
220
+		cat("  function: ", object@fun_name, "()\n", sep = "")
221
+	}
92 222
 	cat("  position:", object@which, "\n")
93 223
 	cat("  items:", ifelse(object@n == 0, "unknown", object@n), "\n")
224
+	cat("  width:", as.character(object@width), "\n")
225
+	cat("  height:", as.character(object@height), "\n")
226
+	var_imported = names(anno@var_env)
227
+	if(length(var_imported)) {
228
+		cat("  imported variable:", paste(var_imported, collapse = ", "), "\n")
229
+		var_subsetable = names(anno@subset_rule)
230
+		if(length(var_subsetable)) {
231
+			cat("  subsetable variable:", paste(var_subsetable, collapse = ", "), "\n")
232
+		}
233
+	}
234
+	cat("  this object is", ifelse(object@subsetable, "\b", "not"), "subsetable\n")
235
+	dirt = c("bottom", "left", "top", "right")
236
+	for(i in 1:4) {
237
+		if(!identical(unit(0, "mm"), object@extended[i])) {
238
+			cat(" ", as.character(object@extended[i]), "extension on the", dirt[i], "\n")
239
+		}
240
+	}
241
+	
94 242
 })
95 243
 
96 244
 anno_empty = function(which = c("column", "row"), border = TRUE, width = NULL, height = NULL) {
97 245
 	
98
-	if(exists(".__under_SingleAnnotation__", envir = parent.frame())) {
99
-		which = get("which", envir = parent.frame())
100
-	} else {
246
+	if(is.null(.ENV$current_annotation_which)) {
101 247
 		which = match.arg(which)[1]
248
+	} else {
249
+		which = .ENV$current_annotation_which
102 250
 	}
103 251
 
104
-	if(which == "column") {
105
-		if(missing(height)) {
106
-			height = unit(1, "cm")
107
-		}
108
-		if(missing(width)) {
109
-			width = unit(1, "npc")
110
-		}
111
-	}
112
-	if(which == "row") {
113
-		if(missing(width)) {
114
-			width = unit(1, "cm")
115
-		}
116
-		if(missing(height)) {
117
-			height = unit(1, "npc")
118
-		}
119
-	}
120
-
121
-	anno = AnnotationFunction()
122
-	anno@which = which
123
-	anno@fun_name = "anno_empty"
124
-	anno@width = width
125
-	anno@height = height
126
-
127
-	anno@var_env = new.env()
128
-	anno@var_env$border = border
129
-
252
+	anno_size = anno_width_and_height(which, width, height, unit(1, "cm"))
253
+	
130 254
 	fun = function(index) {
131 255
 		if(border) grid.rect()
132 256
 	}
133 257
 
134
-	environment(fun) = anno@var_env
135
-	anno@fun = fun
136
-		
137
-	anno@subset_rule = list()
138
-
258
+	anno = AnnotationFunction(
259
+		fun = fun,
260
+		fun_name = "anno_empty",
261
+		which = which,
262
+		var_import = list(border),
263
+		subset_rule = list(),
264
+		subsetable = TRUE,
265
+		height = anno_size$height,
266
+		width = anno_size$width
267
+	)
139 268
 	return(anno) 
140 269
 }
141 270
 
... ...
@@ -147,10 +276,10 @@ anno_simple = function(x, col, na_col = "grey",
147 276
 	pch = NULL, pt_size = unit(1, "snpc")*0.8, pt_gp = gpar(), 
148 277
 	width = NULL, height = NULL) {
149 278
 
150
-	if(exists(".__under_SingleAnnotation__", envir = parent.frame())) {
151
-		which = get("which", envir = parent.frame())
152
-	} else {
279
+	if(is.null(.ENV$current_annotation_which)) {
153 280
 		which = match.arg(which)[1]
281
+	} else {
282
+		which = .ENV$current_annotation_which
154 283
 	}
155 284
 
156 285
 	if(is.data.frame(x)) x = as.matrix(x)
... ...
@@ -161,23 +290,9 @@ anno_simple = function(x, col, na_col = "grey",
161 290
 	}
162 291
 	input_is_matrix = is.matrix(x)
163 292
 
164
-	if(which == "column") {
165
-		if(missing(height)) {
166
-			height = unit(5, "mm")*ifelse(input_is_matrix, ncol(x), 1)
167
-		}
168
-		if(missing(width)) {
169
-			width = unit(1, "npc")
170
-		}
171
-	}
172
-	if(which == "row") {
173
-		if(missing(width)) {
174
-			width = unit(5, "mm")*ifelse(input_is_matrix, ncol(x), 1)
175
-		}
176
-		if(missing(height)) {
177
-			height = unit(1, "npc")
178
-		}
179
-	}
180
-
293
+	anno_size = anno_width_and_height(which, width, height, 
294
+		unit(5, "mm")*ifelse(input_is_matrix, ncol(x), 1))
295
+	
181 296
 	if(missing(col)) {
182 297
 		col = default_col(x)
183 298
 	}
... ...
@@ -188,7 +303,7 @@ anno_simple = function(x, col, na_col = "grey",
188 303
     } else if(inherits(col, "ColorMapping")) {
189 304
     	color_mapping = col
190 305
     } else {
191
-    	stop("`col` should be a named vector/a color mapping function/a ColorMapping object.")
306
+    	stop_wrap("`col` should be a named vector/a color mapping function/a ColorMapping object.")
192 307
     }
193 308
 
194 309
     value = x
... ...
@@ -224,10 +339,12 @@ anno_simple = function(x, col, na_col = "grey",
224 339
             nc = ncol(value)
225 340
             for(i in seq_len(nc)) {
226 341
                 fill = map_to_colors(color_mapping, value[index, i])
227
-                grid.rect(x = (i-0.5)/nc, y, height = 1/n, width = 1/nc, gp = do.call("gpar", c(list(fill = fill), gp)))
342
+                grid.rect(x = (i-0.5)/nc, y, height = 1/n, width = 1/nc, 
343
+                	gp = do.call("gpar", c(list(fill = fill), gp)))
228 344
                 if(!is.null(pch)) {
229 345
 					l = !is.na(pch[, i])
230
-					grid.points(x = rep((i-0.5)/nc, sum(l)), y = y[l], pch = pch[l, i], size = pt_size, gp = pt_gp)
346
+					grid.points(x = rep((i-0.5)/nc, sum(l)), y = y[l], pch = pch[l, i], 
347
+						size = pt_size, gp = pt_gp)
231 348
 				}
232 349
             }
233 350
         } else {
... ...
@@ -235,11 +352,13 @@ anno_simple = function(x, col, na_col = "grey",
235 352
 			grid.rect(x = 0.5, y, height = 1/n, width = 1, gp = do.call("gpar", c(list(fill = fill), gp)))
236 353
 			if(!is.null(pch)) {
237 354
 				l = !is.na(pch)
238
-				grid.points(x = rep(0.5, sum(l)), y = y[l], pch = pch[l], size = pt_size[l], gp = subset_gp(pt_gp, which(l)))
355
+				grid.points(x = rep(0.5, sum(l)), y = y[l], pch = pch[l], size = pt_size[l], 
356
+					gp = subset_gp(pt_gp, which(l)))
239 357
 			}
240 358
         }
241 359
         if(border) grid.rect(gp = gpar(fill = "transparent"))
242 360
 	}
361
+
243 362
 	column_fun = function(index) {
244 363
 		n = length(index)
245 364
 		x = (seq_len(n) - 0.5) / n
... ...
@@ -270,43 +389,39 @@ anno_simple = function(x, col, na_col = "grey",
270 389
 		fun = column_fun
271 390
 	}
272 391
 
273
-	anno = AnnotationFunction()
274
-	anno@which = which
275
-	anno@fun_name = "anno_simple"
276
-	anno@width = width
277
-	anno@height = height
278
-	anno@n = n
279
-	if(which == "column") {
280
-		anno@data_scale = list(x = c(0.5, n + 0.5), y = c(0.5, nc + 0.5))
281
-	} else {
282
-		anno@data_scale = list(x = c(0.5, nc + 0.5), y = c(0.5, n + 0.5))
283
-	}
284
-
285
-	anno@var_env = new.env()
286
-	anno@var_env$value = value
287
-	anno@var_env$gp = gp
288
-	anno@var_env$border = border
289
-	anno@var_env$color_mapping = color_mapping
290
-	anno@var_env$pt_size = pt_size
291
-	anno@var_env$pch = pch
392
+	anno = AnnotationFunction(
393
+		fun = fun,
394
+		fun_name = "anno_simple",
395
+		which = which,
396
+		width = anno_size$width,
397
+		height = anno_size$height,
398
+		n = n,
399
+		data_scale = c(0.5, nc + 0.5),
400
+		var_import = list(value, gp, border, color_mapping, pt_gp, pt_size, pch)
401
+	)
292 402
 
293
-	environment(fun) = anno@var_env
294
-	anno@fun = fun
295
-		
296 403
 	anno@subset_rule = list()
297 404
 	if(input_is_matrix) {
298 405
 		anno@subset_rule$value = subset_matrix_by_row
299
-		anno@subset_rule$pch = subset_matrix_by_row
406
+		if(!is.null(pch)) {
407
+			anno@subset_rule$pch = subset_matrix_by_row
408
+		}
300 409
 	} else {
301 410
 		anno@subset_rule$value = subset_vector
302
-		anno@subset_rule$pch = subset_vector
411
+		if(!is.null(pch)) {
412
+			anno@subset_rule$pch = subset_vector
413
+			anno@subset_rule$pt_size = subset_vector
414
+			anno@subset_rule$pt_gp = subset_gp
415
+		}
303 416
 	}
304 417
 
418
+	anno@subsetable = TRUE
419
+
305 420
 	return(anno)      
306 421
 }
307 422
 
308
-anno_image = function(image, which = c("column", "row"), border = TRUE, gp = gpar(fill = NA, col = NA),
309
-	space = unit(1, "mm"), width = NULL, height = NULL) {
423
+anno_image = function(image, which = c("column", "row"), border = TRUE, 
424
+	gp = gpar(fill = NA, col = NA), space = unit(1, "mm"), width = NULL, height = NULL) {
310 425
 
311 426
 	allowed_image_type = c("png", "svg", "pdf", "eps", "jpeg", "jpg", "tiff")
312 427
 
... ...
@@ -372,30 +487,15 @@ anno_image = function(image, which = c("column", "row"), border = TRUE, gp = gpa
372 487
 		}
373 488
 	})
374 489
 
375
-	if(exists(".__under_SingleAnnotation__", envir = parent.frame())) {
376
-		which = get("which", envir = parent.frame())
377
-	} else {
490
+	if(is.null(.ENV$current_annotation_which)) {
378 491
 		which = match.arg(which)[1]
492
+	} else {
493
+		which = .ENV$current_annotation_which
379 494
 	}
380 495
 
381 496
 	space = space[1]
382 497
 
383
-	if(which == "column") {
384
-		if(missing(height)) {
385
-			height = unit(1, "cm")
386
-		}
387
-		if(missing(width)) {
388
-			width = unit(1, "npc")
389
-		}
390
-	}
391
-	if(which == "row") {
392
-		if(missing(width)) {
393
-			width = unit(1, "cm")
394
-		}
395
-		if(missing(height)) {
396
-			height = unit(1, "npc")
397
-		}
398
-	}
498
+	anno_size = anno_width_and_height(which, width, height, unit(1, "cm"))
399 499
 
400 500
 	gp = recycle_gp(gp, n_image)
401 501
 	
... ...
@@ -416,14 +516,17 @@ anno_image = function(image, which = c("column", "row"), border = TRUE, gp = gpa
416 516
 			if(image_class[ index[i] ] == "raster") {
417 517
 				grid.raster(image_list[[i]], x = (i-0.5)/n, width = width, height = height)
418 518
 			} else if(image_class[ index[i] ] == "grImport::Picture") {
419
-				getFromNamespace("grid.picture", ns = "grImport")(image_list[[i]], x = (i-0.5)/n, width = width, height = height)
519
+				grid.picture = getFromNamespace("grid.picture", ns = "grImport")
520
+				grid.picture(image_list[[i]], x = (i-0.5)/n, width = width, height = height)
420 521
 			} else if(image_class[ index[i] ] == "grImport2::Picture") {
421
-				getFromNamespace("grid.picture", ns = "grImport2")(image_list[[i]], x = (i-0.5)/n, width = width, height = height)
522
+				grid.picture = getFromNamespace("grid.picture", ns = "grImport2")
523
+				grid.picture(image_list[[i]], x = (i-0.5)/n, width = width, height = height)
422 524
 			}
423 525
 		}
424 526
 		if(border) grid.rect(gp = gpar(fill = "transparent"))
425
-		upViewport()
527
+		popViewport()
426 528
 	}
529
+
427 530
 	row_fun = function(index) {
428 531
 		n = length(index)
429 532
 
... ...
@@ -441,13 +544,15 @@ anno_image = function(image, which = c("column", "row"), border = TRUE, gp = gpa
441 544
 			if(image_class[ index[i] ] == "raster") {
442 545
 				grid.raster(image_list[[i]], y = (n - i + 0.5)/n, width = width, height = height)
443 546
 			} else if(image_class[ index[i] ] == "grImport::Picture") {
444
-				getFromNamespace("grid.picture", ns = "grImport")(image_list[[i]], y = (n - i + 0.5)/n, width = width, height = height)
547
+				grid.picture = getFromNamespace("grid.picture", ns = "grImport")
548
+				grid.picture(image_list[[i]], y = (n - i + 0.5)/n, width = width, height = height)
445 549
 			} else if(image_class[ index[i] ] == "grImport2::Picture") {
446
-				getFromNamespace("grid.picture", ns = "grImport2")(image_list[[i]], y = (n - i + 0.5)/n, width = width, height = height)
550
+				grid.picture = getFromNamespace("grid.picture", ns = "grImport2")
551
+				grid.picture(image_list[[i]], y = (n - i + 0.5)/n, width = width, height = height)
447 552
 			}
448 553
 		}
449 554
 		if(border) grid.rect(gp = gpar(fill = "transparent"))
450
-		upViewport()
555
+		popViewport()
451 556
 	}
452 557
 	
453 558
 	if(which == "row") {
... ...
@@ -456,38 +561,64 @@ anno_image = function(image, which = c("column", "row"), border = TRUE, gp = gpa
456 561
 		fun = column_fun
457 562
 	}
458 563
 
459
-	n = n_image
460
-	anno = AnnotationFunction()
461
-	anno@which = which
462
-	anno@fun_name = "anno_image"
463
-	anno@width = width
464
-	anno@height = height
465
-	anno@n = n
466
-	if(which == "column") {
467
-		anno@data_scale = list(x = c(0.5, n + 0.5), y = c(0.5, 1.5))
468
-	} else {
469
-		anno@data_scale = list(x = c(0.5, 1.5), y = c(0.5, n + 0.5))
470
-	}
471
-
472
-	anno@var_env = new.env()
473
-	anno@var_env$gp = gp
474
-	anno@var_env$border = border
475
-	anno@var_env$space = space
476
-	anno@var_env$yx_asp = yx_asp
477
-	anno@var_env$image_list = image_list
478
-	anno@var_env$image_class = image_class
564
+	anno = AnnotationFunction(
565
+		fun = fun,
566
+		fun_name = "anno_image",
567
+		which = which,
568
+		width = anno_size$width,
569
+		height = anno_size$height,
570
+		n = n_image,
571
+		data_scale = c(0.5, 1.5),
572
+		var_import = list(gp, border, space, yx_asp, image_list, image_class)
573
+	)
479 574
 
480
-	environment(fun) = anno@var_env
481
-	anno@fun = fun
482
-		
483
-	anno@subset_rule = list()
484 575
 	anno@subset_rule$gp = subset_vector
485 576
 	anno@subset_rule$image_list = subset_vector
486 577
 	anno@subset_rule$image_class = subset_vector
487 578
 
579
+	anno@subsetable = TRUE
580
+
488 581
 	return(anno)   
489 582
 }
490 583
 
584
+default_axis_param = function(which) {
585
+	list(
586
+		at = NULL, 
587
+		labels = NULL, 
588
+		labels_rot = ifelse(which == "column", 0, 90), 
589
+		gp = gpar(fontsize = 8), 
590
+		side = ifelse(which == "column", "left", "bottom"), 
591
+		facing = "outside"
592
+	)
593
+}
594
+
595
+validate_axis_param = function(axis_param, which) {
596
+	dft = default_axis_param(which)
597
+	for(nm in names(axis_param)) {
598
+		dft[[nm]] = axis_param[[nm]]
599
+	}
600
+	return(dft)
601
+}
602
+
603
+construct_axis_grob = function(axis_param, which, data_scale) {
604
+	axis_param_default = default_axis_param(which)
605
+
606
+	for(nm in setdiff(names(axis_param_default), names(axis_param))) {
607
+		axis_param[[nm]] = axis_param_default[[nm]]
608
+	}
609
+	
610
+	if(is.null(axis_param$at)) {
611
+		at = pretty_breaks(data_scale)
612
+		axis_param$at = at
613
+		axis_param$labels = at
614
+	}
615
+	if(is.null(axis_param$labels)) {
616
+		axis_param$labels = axis_param$at
617
+	}
618
+	axis_grob = do.call(annotation_axis_grob, axis_param)
619
+	
620
+	return(axis_grob)
621
+}
491 622
 
492 623
 # == title
493 624
 # Using points as annotation
... ...
@@ -514,16 +645,14 @@ anno_image = function(image, which = c("column", "row"), border = TRUE, gp = gpa
514 645
 # Zuguang Gu <z.gu@dkfz.de>
515 646
 #
516 647
 anno_points = function(x, which = c("column", "row"), border = TRUE, gp = gpar(), pch = 16, 
517
-	size = unit(2, "mm"), ylim = NULL, extend = 0.05, axis = TRUE, axis_side = NULL, 
518
-	axis_gp = gpar(fontsize = 8), axis_direction = c("normal", "reverse"),
648
+	size = unit(2, "mm"), ylim = NULL, extend = 0.05, axis = TRUE,
649
+	axis_param = default_axis_param(which),
519 650
 	width = NULL, height = NULL) {
520 651
 
521
-	axis_direction = match.arg(axis_direction)[1]
522
-
523
-	if(exists(".__under_SingleAnnotation__", envir = parent.frame())) {
524
-		which = get("which", envir = parent.frame())
525
-	} else {
652
+	if(is.null(.ENV$current_annotation_which)) {
526 653
 		which = match.arg(which)[1]
654
+	} else {
655
+		which = .ENV$current_annotation_which
527 656
 	}
528 657
 
529 658
 	if(is.data.frame(x)) x = as.matrix(x)
... ...
@@ -534,22 +663,7 @@ anno_points = function(x, which = c("column", "row"), border = TRUE, gp = gpar()
534 663
 	}
535 664
 	input_is_matrix = is.matrix(x)
536 665
 
537
-	if(which == "column") {
538
-		if(missing(height)) {
539
-			height = unit(1, "cm")
540
-		}
541
-		if(missing(width)) {
542
-			width = unit(1, "npc")
543
-		}
544
-	}
545
-	if(which == "row") {
546
-		if(missing(width)) {
547
-			width = unit(1, "cm")
548
-		}
549
-		if(missing(height)) {
550
-			height = unit(1, "npc")
551
-		}
552
-	}
666
+	anno_size = anno_width_and_height(which, width, height, unit(1, "cm"))
553 667
 
554 668
 	if(is.matrix(x)) {
555 669
 		n = nrow(x)
... ...
@@ -572,54 +686,39 @@ anno_points = function(x, which = c("column", "row"), border = TRUE, gp = gpar()
572 686
 	}
573 687
 	
574 688
 	if(is.null(ylim)) {
575
-		data_scale = pretty_scale(range(x, na.rm = TRUE))
689
+		data_scale = range(x, na.rm = TRUE)
576 690
 	} else {
577 691
 		data_scale = ylim
578 692
 	}
579 693
 	data_scale = data_scale + c(-extend, extend)*(data_scale[2] - data_scale[1])
580 694
 
581
-	if(which == "column") {
582
-		if(is.null(axis_side)) axis_side = "left"
583
-		if(axis_side == "top" || axis_side == "bottom") {
584
-			stop("`axis_side` can only be 'left' and 'right' for column annotations")
585
-		}
586
-	}
587
-	if(which == "row") {
588
-		if(is.null(axis_side)) axis_side = "bottom"
589
-		if(axis_side == "left" || axis_side == "right") {
590
-			stop("`axis_side` can only be 'top' and 'bottom' for row annotations")
591
-		}
592
-	}
593
-
594 695
 	value = x
595 696
 
697
+	axis_param = validate_axis_param(axis_param, which)
698
+	axis_grob = if(axis) construct_axis_grob(axis_param, which, data_scale) else NULL
699
+
596 700
 	row_fun = function(index) {
597 701
 		n = length(index)
598 702
 
599 703
 		pushViewport(viewport(xscale = data_scale, yscale = c(0.5, n+0.5)))
600
-		if(axis_direction == "reverse") x = data_scale[2] - x + data_scale[1]
601 704
 		if(is.matrix(value)) {
602 705
 			for(i in seq_len(ncol(value))) {
603
-				grid.points(value[index, i], n - seq_along(index) + 1, gp = subset_gp(gp, i), default.units = "native", pch = pch[i], size = size[i])
706
+				grid.points(value[index, i], n - seq_along(index) + 1, gp = subset_gp(gp, i), 
707
+					default.units = "native", pch = pch[i], size = size[i])
604 708
 			}
605 709
 		} else {
606
-			grid.points(value[index], n - seq_along(index) + 1, gp = gp, default.units = "native", pch = pch[index], size = size[index])
607
-		}
608
-		if(axis) {
609
-			if(axis_side == "top") {
610
-				grid.xaxis(main = FALSE, gp = axis_gp, axis_direction = axis_direction)
611
-			} else if(axis_side == "bottom") {
612
-				grid.xaxis(gp = axis_gp, axis_direction = axis_direction)
613
-			}
710
+			grid.points(value[index], n - seq_along(index) + 1, gp = gp, default.units = "native", 
711
+				pch = pch[index], size = size[index])
614 712
 		}
713
+		if(axis) grid.draw(axis_grob)
615 714
 		if(border) grid.rect(gp = gpar(fill = "transparent"))
616
-		upViewport()
715
+		popViewport()
617 716
 	}
717
+
618 718
 	column_fun = function(index) {
619 719
 		n = length(index)
620 720
 		
621 721
 		pushViewport(viewport(yscale = data_scale, xscale = c(0.5, n+0.5)))
622
-		if(axis_direction == "reverse") x = data_scale[2] - x + data_scale[1]
623 722
 		if(is.matrix(value)) {
624 723
 			for(i in seq_len(ncol(value))) {
625 724
 				grid.points(seq_along(index), value[index, i], gp = subset_gp(gp, i), default.units = "native", pch = pch[i], size = size[i])
... ...
@@ -627,15 +726,9 @@ anno_points = function(x, which = c("column", "row"), border = TRUE, gp = gpar()
627 726
 		} else {
628 727
 			grid.points(seq_along(index), value[index], gp = gp, default.units = "native", pch = pch[index], size = size[index])
629 728
 		}
630
-		if(axis) {
631
-			if(axis_side == "right") {
632
-				grid.yaxis(main = FALSE, gp = axis_gp)
633
-			} else if(axis_side == "left") {
634
-				grid.yaxis(gp = axis_gp)
635
-			}
636
-		}
729
+		if(axis) grid.draw(axis_grob)
637 730
 		if(border) grid.rect(gp = gpar(fill = "transparent"))
638
-		upViewport()
731
+		popViewport()
639 732
 	}
640 733
 
641 734
 	if(which == "row") {
... ...
@@ -644,34 +737,17 @@ anno_points = function(x, which = c("column", "row"), border = TRUE, gp = gpar()
644 737
 		fun = column_fun
645 738
 	}
646 739
 
647
-	anno = AnnotationFunction()
648
-	anno@which = which
649
-	anno@fun_name = "anno_points"
650
-	anno@width = width
651
-	anno@height = height
652
-	anno@n = n
653
-	if(which == "column") {
654
-		anno@data_scale = list(x = c(0.5, n + 0.5), y = data_scale)
655
-	} else {
656
-		anno@data_scale = list(x = data_scale, y = c(0.5, n + 0.5))
657
-	}
658
-
659
-	anno@var_env = new.env()
660
-	anno@var_env$value = value
661
-	anno@var_env$gp = gp
662
-	anno@var_env$border = border
663
-	anno@var_env$pch = pch
664
-	anno@var_env$size = size
665
-	anno@var_env$axis = axis
666
-	anno@var_env$axis_side = axis_side
667
-	anno@var_env$axis_gp = axis_gp
668
-	anno@var_env$axis_direction = axis_direction
669
-	anno@var_env$data_scale = data_scale
740
+	anno = AnnotationFunction(
741
+		fun = fun,
742
+		fun_name = "anno_points",
743
+		which = which,
744
+		width = anno_size$width,
745
+		height = anno_size$height,
746
+		n = n,
747
+		data_scale = data_scale,
748
+		var_import = list(value, gp, border, pch, size, axis, axis_param, axis_grob, data_scale)
749
+	)
670 750
 
671
-	environment(fun) = anno@var_env
672
-	anno@fun = fun
673
-		
674
-	anno@subset_rule = list()
675 751
 	anno@subset_rule$gp = subset_vector
676 752
 	if(input_is_matrix) {
677 753
 		anno@subset_rule$value = subset_matrix_by_row
... ...
@@ -681,10 +757,30 @@ anno_points = function(x, which = c("column", "row"), border = TRUE, gp = gpar()
681 757
 		anno@subset_rule$size = subset_vector
682 758
 		anno@subset_rule$pch = subset_vector
683 759
 	}
684
-	
760
+
761
+	anno@subsetable = TRUE
762
+
763
+	anno@extended = update_anno_extend(anno, axis_grob, axis_param)
764
+		
685 765
 	return(anno) 
686 766
 }
687 767
 
768
+update_anno_extend = function(anno, axis_grob, axis_param) {
769
+	extended = anno@extended
770
+	if(axis_param$facing == "outside") {
771
+		if(axis_param$side == "left") {
772
+			extended[[2]] = convertWidth(grobWidth(axis_grob), "mm", valueOnly = TRUE)
773
+		} else if(axis_param$side == "right") {
774
+			extended[[4]] = convertWidth(grobWidth(axis_grob), "mm", valueOnly = TRUE)
775
+		} else if(axis_param$side == "top") {
776
+			extended[[3]] = convertHeight(grobHeight(axis_grob), "mm", valueOnly = TRUE)
777
+		} else if(axis_param$side == "bottom") {
778
+			extended[[1]] = convertHeight(grobHeight(axis_grob), "mm", valueOnly = TRUE)
779
+		}
780
+	}
781
+	return(extended)
782
+}
783
+
688 784
 # == title
689 785
 # Using barplot as annotation
690 786
 #
... ...
@@ -713,8 +809,8 @@ anno_points = function(x, which = c("column", "row"), border = TRUE, gp = gpar()
713 809
 # Zuguang Gu <z.gu@dkfz.de>
714 810
 #
715 811
 anno_barplot = function(x, baseline = 0, which = c("column", "row"), border = TRUE, bar_width = 0.6,
716
-	gp = gpar(fill = "#CCCCCC"), ylim = NULL, extend = 0.05, axis = TRUE, axis_side = NULL, 
717
-	axis_gp = gpar(fontsize = 8), axis_direction = c("normal", "reverse"),
812
+	gp = gpar(fill = "#CCCCCC"), ylim = NULL, extend = 0.05, axis = TRUE, 
813
+	axis_param = default_axis_param(which),
718 814
 	width = NULL, height = NULL) {
719 815
 
720 816
 	if(inherits(x, "list")) x = do.call("cbind", x)
... ...
@@ -722,7 +818,7 @@ anno_barplot = function(x, baseline = 0, which = c("column", "row"), border = TR
722 818
 	if(inherits(x, "matrix")) {
723 819
 		sg = apply(x, 1, function(xx) all(sign(xx) %in% c(1, 0)) || all(sign(xx) %in% c(-1, 0)))
724 820
 		if(!all(sg)) {
725
-			stop("Since `x` is a matrix, the sign of each row should be either all positive or all negative.")
821
+			stop_wrap("Since `x` is a matrix, the sign of each row should be either all positive or all negative.")
726 822
 		}
727 823
 	}
728 824
 	# convert everything to matrix
... ...
@@ -752,43 +848,13 @@ anno_barplot = function(x, baseline = 0, which = c("column", "row"), border = TR
752 848
 		}
753 849
 	}
754 850
 
755
-	axis_direction = match.arg(axis_direction)[1]
756
-
757
-	if(exists(".__under_SingleAnnotation__", envir = parent.frame())) {
758
-		which = get("which", envir = parent.frame())
759
-	} else {
851
+	if(is.null(.ENV$current_annotation_which)) {
760 852
 		which = match.arg(which)[1]
853
+	} else {
854
+		which = .ENV$current_annotation_which
761 855
 	}
762 856
 
763
-	if(which == "column") {
764
-		if(missing(height)) {
765
-			height = unit(1, "cm")
766
-		}
767
-		if(missing(width)) {
768
-			width = unit(1, "npc")
769
-		}
770
-	}
771
-	if(which == "row") {
772
-		if(missing(width)) {
773
-			width = unit(1, "cm")
774
-		}
775
-		if(missing(height)) {
776
-			height = unit(1, "npc")
777
-		}
778
-	}
779
-
780
-	if(which == "column") {
781
-		if(is.null(axis_side)) axis_side = "left"
782
-		if(axis_side == "top" || axis_side == "bottom") {
783
-			stop("`axis_side` can only be 'left' and 'right' for column annotations")
784
-		}
785
-	}
786
-	if(which == "row") {
787
-		if(is.null(axis_side)) axis_side = "bottom"
788
-		if(axis_side == "left" || axis_side == "right") {
789
-			stop("`axis_side` can only be 'top' and 'bottom' for row annotations")
790
-		}
791
-	}
857
+	anno_size = anno_width_and_height(which, width, height, unit(1, "cm"))
792 858
 
793 859
 	if(nc == 1) {
794 860
 		gp = recycle_gp(gp, nrow(x))
... ...
@@ -797,14 +863,12 @@ anno_barplot = function(x, baseline = 0, which = c("column", "row"), border = TR
797 863
 	}
798 864
 
799 865
 	value = x
800
-	
866
+	axis_param = validate_axis_param(axis_param, which)
867
+	axis_grob = if(axis) construct_axis_grob(axis_param, which, data_scale) else NULL
868
+
801 869
 	row_fun = function(index) {
802 870
 		n = length(index)
803 871
 		
804
-		if(axis_direction == "reverse") {
805
-			value = data_scale[2] - value + data_scale[1]
806
-			baseline = data_scale[2] - baseline + data_scale[1]
807
-		}
808 872
 		pushViewport(viewport(xscale = data_scale, yscale = c(0.5, n+0.5)))
809 873
 		if(ncol(value) == 1) {
810 874
 			width = value[index] - baseline
... ...
@@ -817,15 +881,9 @@ anno_barplot = function(x, baseline = 0, which = c("column", "row"), border = TR
817 881
 				grid.rect(x = x_coor, y = n - seq_along(index) + 1, width = abs(width), height = 1*bar_width, default.units = "native", gp = subset_gp(gp, i))
818 882
 			}
819 883
 		}
820
-		if(axis) {
821
-			if(axis_side == "top") {
822
-				grid.xaxis(main = FALSE, gp = axis_gp, axis_direction = axis_direction)
823
-			} else if(axis_side == "bottom") {
824
-				grid.xaxis(gp = axis_gp, axis_direction = axis_direction)
825
-			}
826
-		}
884
+		if(axis) grid.draw(axis_grob)
827 885
 		if(border) grid.rect(gp = gpar(fill = "transparent"))
828
-		upViewport()
886
+		popViewport()
829 887
 	}
830 888
 	column_fun = function(index) {
831 889
 		n = length(index)
... ...
@@ -842,15 +900,9 @@ anno_barplot = function(x, baseline = 0, which = c("column", "row"), border = TR
842 900
 				grid.rect(y = y_coor, x = seq_along(index), height = abs(height), width = 1*bar_width, default.units = "native", gp = subset_gp(gp, i))
843 901
 			}
844 902
 		}
845
-		if(axis) {
846
-			if(axis_side == "right") {
847
-				grid.yaxis(main = FALSE, gp = axis_gp)
848
-			} else if(axis_side == "left") {
849
-				grid.yaxis(gp = axis_gp)
850
-			}
851
-		}
903
+		if(axis) grid.draw(axis_grob)
852 904
 		if(border) grid.rect(gp = gpar(fill = "transparent"))
853
-		upViewport()
905
+		popViewport()
854 906
 	}
855 907
 	
856 908
 	if(which == "row") {
... ...
@@ -860,40 +912,26 @@ anno_barplot = function(x, baseline = 0, which = c("column", "row"), border = TR
860 912
 	}
861 913
 	n = nrow(value)
862 914
 
863
-	anno = AnnotationFunction()
864
-	anno@which = which
865
-	anno@fun_name = "anno_barplot"
866
-	anno@width = width
867
-	anno@height = height
868
-	anno@n = n
869
-	if(which == "column") {
870
-		anno@data_scale = list(x = c(0.5, n + 0.5), y = data_scale)
871
-	} else {
872
-		anno@data_scale = list(x = data_scale, y = c(0.5, n + 0.5))
873
-	}
874
-
875
-	anno@var_env = new.env()
876
-	anno@var_env$value = value
877
-	anno@var_env$gp = gp
878
-	anno@var_env$border = border
879
-	anno@var_env$bar_width = bar_width
880
-	anno@var_env$baseline = baseline
881
-	anno@var_env$axis = axis
882
-	anno@var_env$axis_side = axis_side
883
-	anno@var_env$axis_gp = axis_gp
884
-	anno@var_env$axis_direction = axis_direction
885
-	anno@var_env$data_scale = data_scale
915
+	anno = AnnotationFunction(
916
+		fun = fun,
917
+		fun_name = "anno_barplot",
918
+		which = which,
919
+		width = anno_size$width,
920
+		height = anno_size$height,
921
+		n = n,
922
+		data_scale = data_scale,
923
+		var_import = list(value, gp, border, bar_width, baseline, axis, axis_param, axis_grob, data_scale)
924
+	)
886 925
 
887
-	environment(fun) = anno@var_env
888
-	anno@fun = fun
889
-		
890
-	anno@subset_rule = list()
891 926
 	anno@subset_rule$value = subset_matrix_by_row
892
-
893 927
 	if(ncol(value) == 1) {
894 928
 		anno@subset_rule$gp = subset_gp
895 929
 	}
896
-	
930
+		
931
+	anno@subsetable = TRUE
932
+
933
+	anno@extended = update_anno_extend(anno, axis_grob, axis_param)
934
+
897 935
 	return(anno) 
898 936
 }
899 937
 
... ...
@@ -924,47 +962,16 @@ anno_barplot = function(x, baseline = 0, which = c("column", "row"), border = TR
924 962
 #
925 963
 anno_boxplot = function(x, which = c("column", "row"), border = TRUE,
926 964
 	gp = gpar(fill = "#CCCCCC"), ylim = NULL, extend = 0.05, outline = TRUE, box_width = 0.6,
927
-	pch = 1, size = unit(2, "mm"), axis = TRUE, axis_side = NULL, 
928
-	axis_gp = gpar(fontsize = 8), axis_direction = c("normal", "reverse"),
965
+	pch = 1, size = unit(2, "mm"), axis = TRUE, axis_param = default_axis_param(which),
929 966
 	width = NULL, height = NULL) {
930 967
 
931
-	axis_direction = match.arg(axis_direction)[1]
932
-
933
-	if(exists(".__under_SingleAnnotation__", envir = parent.frame())) {
934
-		which = get("which", envir = parent.frame())
935
-	} else {
968
+	if(is.null(.ENV$current_annotation_which)) {
936 969
 		which = match.arg(which)[1]
970
+	} else {
971
+		which = .ENV$current_annotation_which
937 972
 	}
938 973
 
939
-	if(which == "column") {
940
-		if(missing(height)) {
941
-			height = unit(1, "cm")
942
-		}
943
-		if(missing(width)) {
944
-			width = unit(1, "npc")
945
-		}
946
-	}
947
-	if(which == "row") {
948
-		if(missing(width)) {
949
-			width = unit(1, "cm")
950
-		}
951
-		if(missing(height)) {
952
-			height = unit(1, "npc")
953
-		}
954
-	}
955
-
956
-	if(which == "column") {
957
-		if(is.null(axis_side)) axis_side = "left"
958
-		if(axis_side == "top" || axis_side == "bottom") {
959
-			stop("`axis_side` can only be 'left' and 'right' for column annotations")
960
-		}
961
-	}
962
-	if(which == "row") {
963
-		if(is.null(axis_side)) axis_side = "bottom"
964
-		if(axis_side == "left" || axis_side == "right") {
965
-			stop("`axis_side` can only be 'top' and 'bottom' for row annotations")
966
-		}
967
-	}
974
+	anno_size = anno_width_and_height(which, width, height, unit(2, "cm"))
968 975
 
969 976
 	## convert matrix all to list (or data frame)
970 977
 	if(is.matrix(x)) {
... ...
@@ -994,10 +1001,12 @@ anno_boxplot = function(x, which = c("column", "row"), border = TRUE,
994 1001
 	if(length(pch) == 1) pch = rep(pch, n)
995 1002
 	if(length(size) == 1) size = rep(size, n)
996 1003
 
1004
+	axis_param = validate_axis_param(axis_param, which)
1005
+	axis_grob = if(axis) construct_axis_grob(axis_param, which, data_scale) else NULL
1006
+
997 1007
 	row_fun = function(index) {
998 1008
 
999 1009
 		n_all = length(value)
1000
-		if(axis_direction == "reverse") value = lapply(value, function(y) data_scale[2] - y + data_scale[1])
1001 1010
 		value = value[index]
1002 1011
 		boxplot_stats = boxplot(value, plot = FALSE)$stats
1003 1012
 		
... ...
@@ -1011,36 +1020,32 @@ anno_boxplot = function(x, which = c("column", "row"), border = TRUE,
1011 1020
 
1012 1021
 		grid.segments(boxplot_stats[5, ], n - seq_along(index) + 1 - 0.5*box_width, 
1013 1022
 			          boxplot_stats[5, ], n - seq_along(index) + 1 + 0.5*box_width, 
1014
-			default.units = "native", gp = gp)
1023
+			          default.units = "native", gp = gp)
1015 1024
 		grid.segments(boxplot_stats[5, ], n - seq_along(index) + 1,
1016 1025
 			          boxplot_stats[4, ], n - seq_along(index) + 1, 
1017
-			default.units = "native", gp = gp)
1026
+			          default.units = "native", gp = gp)
1018 1027
 		grid.segments(boxplot_stats[1, ], n - seq_along(index) + 1, 
1019 1028
 			          boxplot_stats[2, ], n - seq_along(index) + 1, 
1020
-			default.units = "native", gp = gp)
1029
+			          default.units = "native", gp = gp)
1021 1030
 		grid.segments(boxplot_stats[1, ], n - seq_along(index) + 1 - 0.5*box_width, 
1022 1031
 			          boxplot_stats[1, ], n - seq_along(index) + 1 + 0.5*box_width, 
1023
-			default.units = "native", gp = gp)
1032
+			          default.units = "native", gp = gp)
1024 1033
 		grid.segments(boxplot_stats[3, ], n - seq_along(index) + 1 - 0.5*box_width, 
1025 1034
 			          boxplot_stats[3, ], n - seq_along(index) + 1 + 0.5*box_width, 
1026
-			default.units = "native", gp = gp)
1035
+			          default.units = "native", gp = gp)
1027 1036
 		if(outline) {
1028 1037
 			for(i in seq_along(value)) {
1029 1038
 				l1 = value[[i]] > boxplot_stats[5,i]
1030
-				if(sum(l1)) grid.points(y = rep(n - i + 1, sum(l1)), x = value[[i]][l1], default.units = "native", gp = subset_gp(gp, i), pch = pch[i], size = size[i])
1039
+				if(sum(l1)) grid.points(y = rep(n - i + 1, sum(l1)), x = value[[i]][l1], 
1040
+					default.units = "native", gp = subset_gp(gp, i), pch = pch[i], size = size[i])
1031 1041
 				l2 = value[[i]] < boxplot_stats[1,i]
1032
-				if(sum(l2)) grid.points(y = rep(n - i + 1, sum(l2)), x = value[[i]][l2], default.units = "native", gp = subset_gp(gp, i), pch = pch[i], size = size[i])
1033
-			}
1034
-		}
1035
-		if(axis) {
1036
-			if(axis_side == "top") {
1037
-				grid.xaxis(main = FALSE, gp = axis_gp, axis_direction = axis_direction)
1038
-			} else if(axis_side == "bottom") {
1039
-				grid.xaxis(gp = axis_gp, axis_direction = axis_direction)
1042
+				if(sum(l2)) grid.points(y = rep(n - i + 1, sum(l2)), x = value[[i]][l2], 
1043
+					default.units = "native", gp = subset_gp(gp, i), pch = pch[i], size = size[i])
1040 1044
 			}
1041 1045
 		}
1046
+		if(axis) grid.draw(axis_grob)
1042 1047
 		if(border) grid.rect(gp = gpar(fill = "transparent"))
1043
-		upViewport()
1048
+		popViewport()
1044 1049
 	}
1045 1050
 	column_fun = function(index) {
1046 1051
 		value = value[index]
... ...
@@ -1052,34 +1057,35 @@ anno_boxplot = function(x, which = c("column", "row"), border = TRUE,
1052 1057
 		grid.rect(x = seq_along(index), y = boxplot_stats[2, ], 
1053 1058
 			height = boxplot_stats[4, ] - boxplot_stats[2, ], width = 1*box_width, just = "bottom", 
1054 1059
 			default.units = "native", gp = gp)
1060
+		
1055 1061
 		grid.segments(seq_along(index) - 0.5*box_width, boxplot_stats[5, ],
1056
-			          seq_along(index) + 0.5*box_width, boxplot_stats[5, ], default.units = "native", gp = gp)
1062
+			          seq_along(index) + 0.5*box_width, boxplot_stats[5, ], 
1063
+			          default.units = "native", gp = gp)
1057 1064
 		grid.segments(seq_along(index), boxplot_stats[5, ],
1058
-			          seq_along(index), boxplot_stats[4, ], default.units = "native", gp = gp)
1065
+			          seq_along(index), boxplot_stats[4, ], 
1066
+			          default.units = "native", gp = gp)
1059 1067
 		grid.segments(seq_along(index), boxplot_stats[1, ],
1060
-			          seq_along(index), boxplot_stats[2, ], default.units = "native", gp = gp)
1068
+			          seq_along(index), boxplot_stats[2, ], 
1069
+			          default.units = "native", gp = gp)
1061 1070
 		grid.segments(seq_along(index) - 0.5*box_width, boxplot_stats[1, ],
1062
-			          seq_along(index) + 0.5*box_width, boxplot_stats[1, ], default.units = "native", gp = gp)
1071
+			          seq_along(index) + 0.5*box_width, boxplot_stats[1, ], 
1072
+			          default.units = "native", gp = gp)
1063 1073
 		grid.segments(seq_along(index) - 0.5*box_width, boxplot_stats[3, ],
1064 1074
 			          seq_along(index) + 0.5*box_width, boxplot_stats[3, ], 
1065
-			default.units = "native", gp = gp)
1075
+			          default.units = "native", gp = gp)
1066 1076
 		if(outline) {	
1067 1077
 			for(i in seq_along(value)) {
1068 1078
 				l1 = value[[i]] > boxplot_stats[5,i]
1069
-				if(sum(l1)) grid.points(x = rep(i, sum(l1)), y = value[[i]][l1], default.units = "native", gp = subset_gp(gp, i), pch = pch[i], size = size[i])
1079
+				if(sum(l1)) grid.points(x = rep(i, sum(l1)), y = value[[i]][l1], 
1080
+					default.units = "native", gp = subset_gp(gp, i), pch = pch[i], size = size[i])
1070 1081
 				l2 = value[[i]] < boxplot_stats[1,i]
1071
-				if(sum(l2)) grid.points(x = rep(i, sum(l2)), y = value[[i]][l2], default.units = "native", gp = subset_gp(gp, i), pch = pch[i], size = size[i])
1072
-			}
1073
-		}
1074
-		if(axis) {
1075
-			if(axis_side == "right") {
1076
-				grid.yaxis(main = FALSE, gp = axis_gp)
1077
-			} else if(axis_side == "left") {
1078
-				grid.yaxis(gp = axis_gp)
1082
+				if(sum(l2)) grid.points(x = rep(i, sum(l2)), y = value[[i]][l2], 
1083
+					default.units = "native", gp = subset_gp(gp, i), pch = pch[i], size = size[i])
1079 1084
 			}
1080 1085
 		}
1086
+		if(axis) grid.draw(axis_grob)
1081 1087
 		if(border) grid.rect(gp = gpar(fill = "transparent"))
1082
-		upViewport()
1088
+		popViewport()
1083 1089
 	}
1084 1090
 	
1085 1091
 	if(which == "row") {
... ...
@@ -1088,41 +1094,26 @@ anno_boxplot = function(x, which = c("column", "row"), border = TRUE,
1088 1094
 		fun = column_fun
1089 1095
 	}
1090 1096
 
1091
-	anno = AnnotationFunction()
1092
-	anno@which = which
1093
-	anno@fun_name = "anno_boxplot"
1094
-	anno@width = width
1095
-	anno@height = height
1096
-	anno@n = n
1097
-	if(which == "column") {
1098
-		anno@data_scale = list(x = c(0.5, n + 0.5), y = data_scale)
1099
-	} else {
1100
-		anno@data_scale = list(x = data_scale, y = c(0.5, n + 0.5))
1101
-	}
1102
-
1103
-	anno@var_env = new.env()
1104
-	anno@var_env$value = value
1105
-	anno@var_env$gp = gp
1106
-	anno@var_env$border = border
1107
-	anno@var_env$box_width = box_width
1108
-	anno@var_env$axis = axis
1109
-	anno@var_env$axis_side = axis_side
1110
-	anno@var_env$axis_gp = axis_gp
1111
-	anno@var_env$axis_direction = axis_direction
1112
-	anno@var_env$data_scale = data_scale
1113
-	anno@var_env$pch = pch
1114
-	anno@var_env$size = size
1115
-	anno@var_env$outline = outline
1097
+	anno = AnnotationFunction(
1098
+		fun = fun,
1099
+		fun_name = "anno_boxplot",
1100
+		which = which,
1101
+		n = n,
1102
+		width = anno_size$width,
1103
+		height = anno_size$height,
1104
+		data_scale = data_scale,
1105
+		var_import = list(value, gp, border, box_width, axis, axis_param, axis_grob, data_scale, pch, size, outline)
1106
+	)
1116 1107
 
1117
-	environment(fun) = anno@var_env
1118
-	anno@fun = fun
1119
-		
1120
-	anno@subset_rule = list()
1121 1108
 	anno@subset_rule$value = subset_vector
1122 1109
 	anno@subset_rule$gp = subset_gp
1123 1110
 	anno@subset_rule$pch = subset_vector
1124 1111
 	anno@subset_rule$size = subset_vector
1125 1112
 	
1113
+	anno@subsetable = TRUE
1114
+
1115
+	anno@extended = update_anno_extend(anno, axis_grob, axis_param)
1116
+
1126 1117
 	return(anno) 
1127 1118
 }
1128 1119
 
... ...
@@ -1144,44 +1135,16 @@ anno_boxplot = function(x, which = c("column", "row"), border = TRUE,
1144 1135
 #
1145 1136
 anno_histogram = function(x, which = c("column", "row"), n_breaks = 11, 
1146 1137
 	border = FALSE, gp = gpar(fill = "#CCCCCC"), 
1147
-	axis = TRUE, axis_side = NULL, axis_gp = gpar(fontsize = 8), 
1138
+	axis = TRUE, axis_param = default_axis_param(which), 
1148 1139
 	width = NULL, height = NULL) {
1149 1140
 	
1150
-	if(exists(".__under_SingleAnnotation__", envir = parent.frame())) {
1151
-		which = get("which", envir = parent.frame())
1152
-	} else {
1141
+	if(is.null(.ENV$current_annotation_which)) {
1153 1142
 		which = match.arg(which)[1]
1143
+	} else {
1144
+		which = .ENV$current_annotation_which
1154 1145
 	}
1155 1146
 
1156
-	if(which == "column") {
1157
-		if(missing(height)) {
1158
-			height = unit(4, "cm")
1159
-		}
1160
-		if(missing(width)) {
1161
-			width = unit(1, "npc")
1162
-		}
1163
-	}
1164
-	if(which == "row") {
1165
-		if(missing(width)) {
1166
-			width = unit(4, "cm")
1167
-		}
1168
-		if(missing(height)) {
1169
-			height = unit(1, "npc")
1170
-		}
1171
-	}
1172
-
1173
-	if(which == "column") {
1174
-		if(is.null(axis_side)) axis_side = "left"
1175
-		if(axis_side == "top" || axis_side == "bottom") {
1176
-			stop("`axis_side` can only be 'left' and 'right' for column annotations")
1177
-		}
1178
-	}
1179
-	if(which == "row") {
1180
-		if(is.null(axis_side)) axis_side = "bottom"
1181
-		if(axis_side == "left" || axis_side == "right") {
1182
-			stop("`axis_side` can only be 'top' and 'bottom' for row annotations")
1183
-		}
1184
-	}
1147
+	anno_size = anno_width_and_height(which, width, height, unit(4, "cm"))
1185 1148
 
1186 1149
 	## convert matrix all to list (or data frame)
1187 1150
 	if(is.matrix(x)) {
... ...
@@ -1204,8 +1167,10 @@ anno_histogram = function(x, which = c("column", "row"), n_breaks = 11,
1204 1167
 	xscale = xscale + c(0, 0.05)*(xscale[2] - xscale[1])
1205 1168
 	yscale = c(0, max(unlist(histogram_counts)))
1206 1169
 	yscale[2] = yscale[2]*1.05
1207
-	
1170
+
1208 1171
 	gp = recycle_gp(gp, n)
1172
+	axis_param = validate_axis_param(axis_param, which)
1173
+	axis_grob = if(axis) construct_axis_grob(axis_param, which, xscale) else NULL
1209 1174
 
1210 1175
 	row_fun = function(index) {
1211 1176
 		
... ...
@@ -1213,7 +1178,9 @@ anno_histogram = function(x, which = c("column", "row"), n_breaks = 11,
1213 1178
 		value = value[index]
1214 1179
 		
1215 1180
 		n = length(index)
1216
-		
1181
+		histogram_breaks = histogram_breaks[index]
1182
+		histogram_counts = histogram_counts[index]
1183
+
1217 1184
 		gp = subset_gp(gp, index)
1218 1185
 		for(i in seq_len(n)) {
1219 1186
 			n_breaks = length(histogram_breaks[[i]])
... ...
@@ -1222,13 +1189,7 @@ anno_histogram = function(x, which = c("column", "row"), n_breaks = 11,
1222 1189
 			popViewport()
1223 1190
 		}
1224 1191
 		pushViewport(viewport(xscale = xscale))
1225
-		if(axis) {
1226
-			if(axis_side == "top") {
1227
-				grid.xaxis(main = FALSE, gp = axis_gp)
1228
-			} else if(axis_side == "bottom") {
1229
-				grid.xaxis(gp = axis_gp)
1230
-			}
1231
-		}
1192
+		if(axis) grid.draw(axis_grob)
1232 1193
 		if(border) grid.rect(gp = gpar(fill = "transparent"))
1233 1194
 		popViewport()
1234 1195
 	}
... ...
@@ -1240,6 +1201,8 @@ anno_histogram = function(x, which = c("column", "row"), n_breaks = 11,
1240 1201
 		foo = yscale
1241 1202
 		yscale = xscale
1242 1203
 		xscale = foo
1204
+		histogram_breaks = histogram_breaks[index]
1205
+		histogram_counts = histogram_counts[index]
1243 1206
 
1244 1207
 		n = length(index)
1245 1208
 		
... ...
@@ -1253,13 +1216,7 @@ anno_histogram = function(x, which = c("column", "row"), n_breaks = 11,
1253 1216
 			popViewport()
1254 1217
 		}
1255 1218
 		pushViewport(viewport(yscale = yscale))
1256
-		if(axis) {
1257
-			if(axis_side == "right") {
1258
-				grid.yaxis(main = FALSE, gp = axis_gp)
1259
-			} else if(axis_side == "left") {
1260
-				grid.yaxis(gp = axis_gp)
1261
-			}
1262
-		}
1219
+		if(axis) grid.draw(axis_grob)
1263 1220
 		if(border) grid.rect(gp = gpar(fill = "transparent"))
1264 1221
 		popViewport()
1265 1222
 	}
... ...
@@ -1270,39 +1227,27 @@ anno_histogram = function(x, which = c("column", "row"), n_breaks = 11,
1270 1227
 		fun = column_fun
1271 1228
 	}
1272 1229
 
1273
-	anno = AnnotationFunction()
1274
-	anno@which = which
1275
-	anno@fun_name = "anno_histogram"
1276
-	anno@width = width
1277
-	anno@height = height
1278
-	anno@n = n
1279
-	if(which == "column") {
1280
-		anno@data_scale = list(x = c(0.5, n + 0.5), y = xscale)
1281
-	} else {
1282
-		anno@data_scale = list(x = xscale, y = c(0.5, n + 0.5))
1283
-	}
1284
-
1285
-	anno@var_env = new.env()
1286
-	anno@var_env$value = value
1287
-	anno@var_env$gp = gp
1288
-	anno@var_env$border = border
1289
-	anno@var_env$axis = axis
1290
-	anno@var_env$axis_side = axis_side
1291
-	anno@var_env$axis_gp = axis_gp
1292
-	anno@var_env$xscale = xscale
1293
-	anno@var_env$yscale = yscale
1294
-	anno@var_env$histogram_breaks = histogram_breaks
1295
-	anno@var_env$histogram_counts = histogram_counts
1230
+	anno = AnnotationFunction(
1231
+		fun = fun,
1232
+		fun_name = "anno_histogram",
1233
+		which = which,
1234
+		width = anno_size$width,
1235
+		height = anno_size$height,
1236
+		n = n,
1237
+		data_scale = xscale,
1238
+		var_import = list(value, gp, border, axis, axis_param, axis_grob, xscale, yscale,
1239
+			histogram_breaks, histogram_counts)
1240
+	)
1296 1241
 
1297
-	environment(fun) = anno@var_env
1298
-	anno@fun = fun
1299
-		
1300
-	anno@subset_rule = list()
1301 1242
 	anno@subset_rule$value = subset_vector
1302 1243
 	anno@subset_rule$gp = subset_gp
1303 1244
 	anno@subset_rule$histogram_breaks = subset_vector
1304 1245
 	anno@subset_rule$histogram_counts = subset_vector
1305 1246
 	
1247
+	anno@subsetable = TRUE
1248
+
1249
+	anno@extended = update_anno_extend(anno, axis_grob, axis_param)
1250
+
1306 1251
 	return(anno) 
1307 1252
 }
1308 1253
 
... ...
@@ -1325,59 +1270,19 @@ anno_histogram = function(x, which = c("column", "row"), n_breaks = 11,
1325 1270
 #
1326 1271
 anno_density = function(x, which = c("column", "row"), gp = gpar(fill = "#CCCCCC"),
1327 1272
 	type = c("lines", "violin", "heatmap"), 
1328
-	heatmap_color_schema = rev(brewer.pal(name = "RdYlBu", n = 11)), 
1329
-	joyplot_scale = 1, border = FALSE,
1330
-	axis = TRUE, axis_side = NULL, 
1331
-	axis_gp = gpar(fontsize = 8),
1273
+	heatmap_colors = rev(brewer.pal(name = "RdYlBu", n = 11)), 
1274
+	joyplot_scale = 1, border = TRUE,
1275
+	axis = TRUE, axis_param = default_axis_param(which),
1332 1276
 	width = NULL, height = NULL) {
1333 1277
 	
1334
-	if(exists(".__under_SingleAnnotation__", envir = parent.frame())) {
1335
-		which = get("which", envir = parent.frame())
1336
-	} else {
1278
+	if(is.null(.ENV$current_annotation_which)) {
1337 1279
 		which = match.arg(which)[1]
1338
-	}
1339
-
1340
-	if(which == "column") {
1341
-		if(missing(height)) {
1342
-			height = unit(4, "cm")
1343
-		}
1344
-		if(missing(width)) {
1345
-			width = unit(1, "npc")
1346
-		}
1347
-	}
1348
-	if(which == "row") {
1349
-		if(missing(width)) {
1350
-			width = unit(4, "cm")
1351
-		}
1352
-		if(missing(height)) {
1353
-			height = unit(1, "npc")
1354
-		}
1355
-	}
1356
-
1357
-	if(which == "column") {
1358
-		if(is.null(axis_side)) axis_side = "left"
1359
-		if(axis_side == "top" || axis_side == "bottom") {
1360
-			stop("`axis_side` can only be 'left' and 'right' for column annotations")
1361