... | ... |
@@ -186,6 +186,14 @@ AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), ce |
186 | 186 |
subsettable = TRUE |
187 | 187 |
} |
188 | 188 |
|
189 |
+ if(length(var_import) == 0) { |
|
190 |
+ global_vars = codetools::findGlobals(fun, merge = FALSE)$variables |
|
191 |
+ |
|
192 |
+ for(v in global_vars) { |
|
193 |
+ var_import[[v]] = get(v, envir = environment(fun)) |
|
194 |
+ } |
|
195 |
+ } |
|
196 |
+ |
|
189 | 197 |
if(length(var_import)) { |
190 | 198 |
anno@var_env = new.env() |
191 | 199 |
if(is.character(var_import)) { |
... | ... |
@@ -24,7 +24,7 @@ AnnotationFunction = setClass("AnnotationFunction", |
24 | 24 |
var_env = "environment", |
25 | 25 |
fun = "function", |
26 | 26 |
subset_rule = "list", |
27 |
- subsetable = "logical", |
|
27 |
+ subsettable = "logical", |
|
28 | 28 |
data_scale = "numeric", |
29 | 29 |
extended = "ANY", |
30 | 30 |
show_name = "logical" |
... | ... |
@@ -34,7 +34,7 @@ AnnotationFunction = setClass("AnnotationFunction", |
34 | 34 |
width = unit(1, "npc"), |
35 | 35 |
height = unit(1, "npc"), |
36 | 36 |
subset_rule = list(), |
37 |
- subsetable = FALSE, |
|
37 |
+ subsettable = FALSE, |
|
38 | 38 |
data_scale = c(0, 1), |
39 | 39 |
n = NA_integer_, |
40 | 40 |
extended = unit(c(0, 0, 0, 0), "mm"), |
... | ... |
@@ -92,8 +92,8 @@ anno_width_and_height = function(which, width = NULL, height = NULL, |
92 | 92 |
# -data_scale The data scale on the data axis (y-axis for column annotation and x-axis for row annotation). It is only used |
93 | 93 |
# when `decorate_annotation` is used with "native" unit coordinates. |
94 | 94 |
# -subset_rule The rule of subsetting variables in ``var_import``. It should be set when users want the final object to |
95 |
-# be subsetable. See **Details** section. |
|
96 |
-# -subsetable Whether the object is subsetable? |
|
95 |
+# be subsettable. See **Details** section. |
|
96 |
+# -subsettable Whether the object is subsettable? |
|
97 | 97 |
# -show_name It is used to turn off the drawing of annotation names in `HeatmapAnnotation`. Annotations always have names |
98 | 98 |
# associated and normally they will be drawn beside the annotation graphics to tell what the annotation is about. |
99 | 99 |
# e.g. the annotation names put beside the points annotation graphics. However, for some of the annotations, the names |
... | ... |
@@ -133,7 +133,7 @@ anno_width_and_height = function(which, width = NULL, height = NULL, |
133 | 133 |
# }, |
134 | 134 |
# var_import = list(x = x), |
135 | 135 |
# n = 10, |
136 |
-# subsetable = TRUE, |
|
136 |
+# subsettable = TRUE, |
|
137 | 137 |
# height = unit(2, "cm") |
138 | 138 |
# ) |
139 | 139 |
# m = rbind(1:10, 11:20) |
... | ... |
@@ -141,7 +141,7 @@ anno_width_and_height = function(which, width = NULL, height = NULL, |
141 | 141 |
# Heatmap(m, top_annotation = HeatmapAnnotation(foo = anno1), column_km = 2) |
142 | 142 |
AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), cell_fun = NULL, |
143 | 143 |
var_import = list(), n = NA, data_scale = c(0, 1), subset_rule = list(), |
144 |
- subsetable = length(subset_rule) > 0, show_name = TRUE, width = NULL, height = NULL) { |
|
144 |
+ subsettable = length(subset_rule) > 0, show_name = TRUE, width = NULL, height = NULL) { |
|
145 | 145 |
|
146 | 146 |
which = match.arg(which)[1] |
147 | 147 |
|
... | ... |
@@ -183,7 +183,7 @@ AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), ce |
183 | 183 |
} |
184 | 184 |
} |
185 | 185 |
} |
186 |
- subsetable = TRUE |
|
186 |
+ subsettable = TRUE |
|
187 | 187 |
} |
188 | 188 |
|
189 | 189 |
if(length(var_import)) { |
... | ... |
@@ -232,13 +232,13 @@ AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), ce |
232 | 232 |
} |
233 | 233 |
} |
234 | 234 |
|
235 |
- if(missing(subsetable)) { |
|
235 |
+ if(missing(subsettable)) { |
|
236 | 236 |
# is user defined subset rule |
237 | 237 |
if(length(anno@subset_rule)) { |
238 |
- anno@subsetable = TRUE |
|
238 |
+ anno@subsettable = TRUE |
|
239 | 239 |
} |
240 | 240 |
} else { |
241 |
- anno@subsetable = subsetable |
|
241 |
+ anno@subsettable = subsettable |
|
242 | 242 |
} |
243 | 243 |
|
244 | 244 |
return(anno) |
... | ... |
@@ -263,8 +263,8 @@ AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), ce |
263 | 263 |
if(nargs() == 1) { |
264 | 264 |
return(x) |
265 | 265 |
} else { |
266 |
- if(!x@subsetable) { |
|
267 |
- stop_wrap("This object is not subsetable.") |
|
266 |
+ if(!x@subsettable) { |
|
267 |
+ stop_wrap("This object is not subsettable.") |
|
268 | 268 |
} |
269 | 269 |
x = copy_all(x) |
270 | 270 |
if(x@fun_name == "anno_mark") { |
... | ... |
@@ -425,12 +425,12 @@ setMethod(f = "show", |
425 | 425 |
var_imported = names(object@var_env) |
426 | 426 |
if(length(var_imported)) { |
427 | 427 |
cat(" imported variable:", paste(var_imported, collapse = ", "), "\n") |
428 |
- var_subsetable = names(object@subset_rule) |
|
429 |
- if(length(var_subsetable)) { |
|
430 |
- cat(" subsetable variable:", paste(var_subsetable, collapse = ", "), "\n") |
|
428 |
+ var_subsettable = names(object@subset_rule) |
|
429 |
+ if(length(var_subsettable)) { |
|
430 |
+ cat(" subsettable variable:", paste(var_subsettable, collapse = ", "), "\n") |
|
431 | 431 |
} |
432 | 432 |
} |
433 |
- cat(" this object is ", ifelse(object@subsetable, "", "not "), "subsetable\n", sep = "") |
|
433 |
+ cat(" this object is ", ifelse(object@subsettable, "", "not "), "subsettable\n", sep = "") |
|
434 | 434 |
dirt = c("bottom", "left", "top", "right") |
435 | 435 |
for(i in 1:4) { |
436 | 436 |
if(!identical(unit(0, "mm"), object@extended[i])) { |
... | ... |
@@ -85,6 +85,7 @@ anno_width_and_height = function(which, width = NULL, height = NULL, |
85 | 85 |
# -fun A function which defines how to draw the annotation. See **Details** section. |
86 | 86 |
# -fun_name The name of the function. It is only used for printing the object. |
87 | 87 |
# -which Whether it is drawn as a column annotation or a row annotation? |
88 |
+# -cell_fun A simplified version of ``fun``. ``cell_fun`` only accepts one single index and it draws repeatedly in each annotation cell. |
|
88 | 89 |
# -var_import The names of the variables or the variable themselves that the annotation function depends on. See **Details** section. |
89 | 90 |
# -n Number of observations in the annotation. It is not mandatory, but it is better to provide this information |
90 | 91 |
# so that the higher order `HeatmapAnnotation` knows it and it can perform check on the consistency of annotations and heatmaps. |
... | ... |
@@ -138,7 +139,7 @@ anno_width_and_height = function(which, width = NULL, height = NULL, |
138 | 139 |
# m = rbind(1:10, 11:20) |
139 | 140 |
# Heatmap(m, top_annotation = HeatmapAnnotation(foo = anno1)) |
140 | 141 |
# Heatmap(m, top_annotation = HeatmapAnnotation(foo = anno1), column_km = 2) |
141 |
-AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), |
|
142 |
+AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), cell_fun = NULL, |
|
142 | 143 |
var_import = list(), n = NA, data_scale = c(0, 1), subset_rule = list(), |
143 | 144 |
subsetable = length(subset_rule) > 0, show_name = TRUE, width = NULL, height = NULL) { |
144 | 145 |
|
... | ... |
@@ -162,6 +163,29 @@ AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), |
162 | 163 |
anno@n = n |
163 | 164 |
anno@data_scale = data_scale |
164 | 165 |
|
166 |
+ if(!is.null(cell_fun)) { |
|
167 |
+ if(which == "column") { |
|
168 |
+ fun = function(index, k, n) { |
|
169 |
+ n = length(index) |
|
170 |
+ for(i in seq_along(index)) { |
|
171 |
+ pushViewport(viewport(x = i/n, width = 1/n, just = "right", default.units = "npc")) |
|
172 |
+ cell_fun(index[i]) |
|
173 |
+ popViewport() |
|
174 |
+ } |
|
175 |
+ } |
|
176 |
+ } else { |
|
177 |
+ fun = function(index, k, n) { |
|
178 |
+ n = length(index) |
|
179 |
+ for(i in seq_along(index)) { |
|
180 |
+ pushViewport(viewport(y = 1 - i/n, height = 1/n, just = "bottom", default.units = "npc")) |
|
181 |
+ cell_fun(index[i]) |
|
182 |
+ popViewport() |
|
183 |
+ } |
|
184 |
+ } |
|
185 |
+ } |
|
186 |
+ subsetable = TRUE |
|
187 |
+ } |
|
188 |
+ |
|
165 | 189 |
if(length(var_import)) { |
166 | 190 |
anno@var_env = new.env() |
167 | 191 |
if(is.character(var_import)) { |
... | ... |
@@ -245,9 +245,10 @@ AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), |
245 | 245 |
x = copy_all(x) |
246 | 246 |
if(x@fun_name == "anno_mark") { |
247 | 247 |
called_args = attr(x, "called_args") |
248 |
+ od = order(i) |
|
248 | 249 |
i = sort(i) |
249 | 250 |
l = called_args$at %in% i |
250 |
- called_args$at = which(i %in% called_args$at) |
|
251 |
+ called_args$at = od[which(i %in% called_args$at)] |
|
251 | 252 |
called_args$labels = called_args$labels[l] |
252 | 253 |
called_args$link_gp = subset_gp(called_args$link_gp, l) |
253 | 254 |
called_args$labels_gp = subset_gp(called_args$labels_gp, l) |
... | ... |
@@ -244,8 +244,17 @@ AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), |
244 | 244 |
} |
245 | 245 |
x = copy_all(x) |
246 | 246 |
if(x@fun_name == "anno_mark") { |
247 |
- ind_at = which(x@var_env[["at"]] %in% i) |
|
247 |
+ called_args = attr(x, "called_args") |
|
248 |
+ i = sort(i) |
|
249 |
+ l = called_args$at %in% i |
|
250 |
+ called_args$at = which(i %in% called_args$at) |
|
251 |
+ called_args$labels = called_args$labels[l] |
|
252 |
+ called_args$link_gp = subset_gp(called_args$link_gp, l) |
|
253 |
+ called_args$labels_gp = subset_gp(called_args$labels_gp, l) |
|
254 |
+ x2 = do.call(anno_mark, called_args) |
|
255 |
+ return(x2) |
|
248 | 256 |
} |
257 |
+ |
|
249 | 258 |
for(var in names(x@subset_rule)) { |
250 | 259 |
|
251 | 260 |
oe = try(x@var_env[[var]] <- x@subset_rule[[var]](x@var_env[[var]], i), silent = TRUE) |
... | ... |
@@ -243,12 +243,17 @@ AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), |
243 | 243 |
stop_wrap("This object is not subsetable.") |
244 | 244 |
} |
245 | 245 |
x = copy_all(x) |
246 |
+ if(x@fun_name == "anno_mark") { |
|
247 |
+ ind_at = which(x@var_env[["at"]] %in% i) |
|
248 |
+ } |
|
246 | 249 |
for(var in names(x@subset_rule)) { |
250 |
+ |
|
247 | 251 |
oe = try(x@var_env[[var]] <- x@subset_rule[[var]](x@var_env[[var]], i), silent = TRUE) |
248 | 252 |
if(inherits(oe, "try-error")) { |
249 | 253 |
message(paste0("An error when subsetting ", var)) |
250 | 254 |
stop_wrap(oe) |
251 | 255 |
} |
256 |
+ |
|
252 | 257 |
} |
253 | 258 |
if(is.logical(i)) { |
254 | 259 |
x@n = sum(i) |
... | ... |
@@ -312,13 +312,13 @@ setMethod(f = "draw", |
312 | 312 |
if(!identical(unit(0, "mm"), object@extended[1])) { |
313 | 313 |
grid.rect(y = 1, height = unit(1, "npc") + object@extended[1], just = "top", |
314 | 314 |
gp = gpar(fill = "transparent", col = "red", lty = 2)) |
315 |
- } else if(!identical(unit(0, "mm"), object@extended[[2]])) { |
|
315 |
+ } else if(!identical(unit(0, "mm"), object@extended[2])) { |
|
316 | 316 |
grid.rect(x = 1, width = unit(1, "npc") + object@extended[2], just = "right", |
317 | 317 |
gp = gpar(fill = "transparent", col = "red", lty = 2)) |
318 |
- } else if(!identical(unit(0, "mm"), object@extended[[3]])) { |
|
318 |
+ } else if(!identical(unit(0, "mm"), object@extended[3])) { |
|
319 | 319 |
grid.rect(y = 0, height = unit(1, "npc") + object@extended[3], just = "bottom", |
320 | 320 |
gp = gpar(fill = "transparent", col = "red", lty = 2)) |
321 |
- } else if(!identical(unit(0, "mm"), object@extended[[4]])) { |
|
321 |
+ } else if(!identical(unit(0, "mm"), object@extended[4])) { |
|
322 | 322 |
grid.rect(x = 0, width = unit(1, "npc") + object@extended[4], just = "left", |
323 | 323 |
gp = gpar(fill = "transparent", col = "red", lty = 2)) |
324 | 324 |
} |
... | ... |
@@ -391,7 +391,7 @@ setMethod(f = "show", |
391 | 391 |
cat(" subsetable variable:", paste(var_subsetable, collapse = ", "), "\n") |
392 | 392 |
} |
393 | 393 |
} |
394 |
- cat(" this object is ", ifelse(object@subsetable, "\b", "not "), "subsetable\n", sep = "") |
|
394 |
+ cat(" this object is ", ifelse(object@subsetable, "", "not "), "subsetable\n", sep = "") |
|
395 | 395 |
dirt = c("bottom", "left", "top", "right") |
396 | 396 |
for(i in 1:4) { |
397 | 397 |
if(!identical(unit(0, "mm"), object@extended[i])) { |
... | ... |
@@ -53,7 +53,7 @@ anno_width_and_height = function(which, width = NULL, height = NULL, |
53 | 53 |
if(!is_abs_unit(height)) { |
54 | 54 |
stop_wrap("height of the annotation can only be an absolute unit.") |
55 | 55 |
} else { |
56 |
- height = convertHeight(height, "mm") |
|
56 |
+ # height = convertHeight(height, "mm") |
|
57 | 57 |
} |
58 | 58 |
} |
59 | 59 |
if(is.null(width)) { |
... | ... |
@@ -67,7 +67,7 @@ anno_width_and_height = function(which, width = NULL, height = NULL, |
67 | 67 |
if(!is_abs_unit(width)) { |
68 | 68 |
stop_wrap("width of the annotation can only be an absolute unit.") |
69 | 69 |
} else { |
70 |
- width = convertWidth(width, "mm") |
|
70 |
+ # width = convertWidth(width, "mm") |
|
71 | 71 |
} |
72 | 72 |
} |
73 | 73 |
if(is.null(height)) { |
... | ... |
@@ -398,7 +398,6 @@ setMethod(f = "show", |
398 | 398 |
cat(" ", as.character(object@extended[i]), "extension on the", dirt[i], "\n") |
399 | 399 |
} |
400 | 400 |
} |
401 |
- |
|
402 | 401 |
}) |
403 | 402 |
|
404 | 403 |
# == title |
... | ... |
@@ -268,6 +268,7 @@ AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), |
268 | 268 |
# -k Current slice index. |
269 | 269 |
# -n Total number of slices. |
270 | 270 |
# -test Is it in test mode? The value can be logical or a text which is plotted as the title of plot. |
271 |
+# -... Pass to `grid::viewport`. |
|
271 | 272 |
# |
272 | 273 |
# == detail |
273 | 274 |
# Normally it is called internally by the `SingleAnnotation-class`. |
... | ... |
@@ -277,7 +278,7 @@ AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), |
277 | 278 |
# |
278 | 279 |
setMethod(f = "draw", |
279 | 280 |
signature = "AnnotationFunction", |
280 |
- definition = function(object, index, k = 1, n = 1, test = FALSE) { |
|
281 |
+ definition = function(object, index, k = 1, n = 1, test = FALSE, ...) { |
|
281 | 282 |
|
282 | 283 |
if(is.character(test)) { |
283 | 284 |
test2 = TRUE |
... | ... |
@@ -302,7 +303,7 @@ setMethod(f = "draw", |
302 | 303 |
anno_width = object@width |
303 | 304 |
|
304 | 305 |
# names should be passed to the data viewport |
305 |
- pushViewport(viewport(width = anno_width, height = anno_height)) |
|
306 |
+ pushViewport(viewport(width = anno_width, height = anno_height, ...)) |
|
306 | 307 |
vp_name1 = current.viewport()$name |
307 | 308 |
object@fun(index, k, n) |
308 | 309 |
if(test2) { |
... | ... |
@@ -390,7 +390,7 @@ setMethod(f = "show", |
390 | 390 |
cat(" subsetable variable:", paste(var_subsetable, collapse = ", "), "\n") |
391 | 391 |
} |
392 | 392 |
} |
393 |
- cat(" this object is", ifelse(object@subsetable, "\b", "not"), "subsetable\n") |
|
393 |
+ cat(" this object is ", ifelse(object@subsetable, "\b", "not "), "subsetable\n", sep = "") |
|
394 | 394 |
dirt = c("bottom", "left", "top", "right") |
395 | 395 |
for(i in 1:4) { |
396 | 396 |
if(!identical(unit(0, "mm"), object@extended[i])) { |
... | ... |
@@ -3,14 +3,13 @@ |
3 | 3 |
# The AnnotationFunction Class |
4 | 4 |
# |
5 | 5 |
# == details |
6 |
-# The heatmap annotation is basically graphics aligned to the heatmap columns |
|
7 |
-# if it is column annotation or heatmap rows if it is row annotation, while |
|
8 |
-# there is no restrictions for the graphic types, e.g. it can be heatmap-like |
|
6 |
+# The heatmap annotation is basically graphics aligned to the heatmap columns or rows. |
|
7 |
+# There is no restriction for the graphic types, e.g. it can be heatmap-like |
|
9 | 8 |
# annotation or points. Here the AnnotationFunction class is designed for |
10 | 9 |
# creating complex and flexible annotation graphics. As the main part of the class, it uses |
11 | 10 |
# a user-defined function to define the graphics. It also keeps information of |
12 | 11 |
# the size of the plotting regions of the annotation. And most importantly, it |
13 |
-# allows subsetting of the annotation to draw a subset of the graphics, which |
|
12 |
+# allows subsetting to the annotation to draw a subset of the graphics, which |
|
14 | 13 |
# is the base for the splitting of the annotations. |
15 | 14 |
# |
16 | 15 |
# See `AnnotationFunction` constructor for details. |
... | ... |
@@ -108,96 +107,37 @@ anno_width_and_height = function(which, width = NULL, height = NULL, |
108 | 107 |
# the width must be an absolute unit. |
109 | 108 |
# |
110 | 109 |
# == details |
111 |
-# We use a normal R function defines how to draw the annotation graphics. As |
|
112 |
-# expected, the main part of the AnnotationFunction class is this function. |
|
113 |
-# The function defines how to draw at specific positions which correspond to |
|
114 |
-# rows or columns in the heatmap. The function should have three arguments: |
|
115 |
-# ``index``, ``k`` and ``n`` (the names of the arguments can be arbitory) |
|
116 |
-# where ``k`` and ``n`` are optional. ``index`` corresponds to the indices of |
|
117 |
-# rows or columns of the heatmap. The value of ``index`` is not necessarily to |
|
118 |
-# be the whole row indices or column indices of the heatmap. It can be a |
|
119 |
-# subset of the indices if the annotation is split into slices according to |
|
120 |
-# the split of the heatmap. ``index`` is always reordered according to the |
|
121 |
-# reordering of heatmap rows or columns (e.g. by clustering). So, ``index`` |
|
122 |
-# actually contains a list of row or column indices for the current slice |
|
123 |
-# after row or column reordering. |
|
124 |
-# |
|
125 |
-# As mentioned, annotation can be split into slices. ``k`` corresponds to the |
|
126 |
-# current slice and ``n`` corresponds to the total number of slices. As you can image, |
|
127 |
-# when ``n > 1``, the annotation function will be executed for all ``k``s. The |
|
128 |
-# information of ``k`` and ``n`` sometimes can be useful, for example, we want |
|
129 |
-# to add axis ot the right side of a column annotation, if this column annotation |
|
130 |
-# is split into several slices, the axis is only drawn when``k == n``. |
|
131 |
-# |
|
132 |
-# Since the function only allows ``index``, ``k`` and ``n``, the function |
|
133 |
-# sometimes uses several external variables which can not be defined inside |
|
134 |
-# the function, e.g. the data points for the annotation. These variables |
|
135 |
-# should be imported into the AnnotationFunction class so that the function |
|
136 |
-# can correctly find these variables (by ``var_import`` argument). |
|
137 |
-# |
|
138 |
-# One important feature for AnnotationFunction class is it can be subsetable. |
|
139 |
-# To allow subsetting of the object, users need to define the rules for the |
|
140 |
-# imported variables. The rules are simple function which |
|
141 |
-# accpets the variable and indices, and returns the subset of the variable. |
|
142 |
-# The subset rule functions implemented in this package are `subset_gp`, |
|
143 |
-# `subset_matrix_by_row` and `subset_vector`. These three functions are enough |
|
144 |
-# for most of the cases. |
|
145 |
-# |
|
146 |
-# In following, we defined three AnnotationFunction objects: |
|
147 |
-# |
|
148 |
-# 1. It needs external variable and support subsetting |
|
149 |
-# |
|
150 |
-# x = 1:10 |
|
151 |
-# anno1 = AnnotationFunction( |
|
152 |
-# fun = function(index) { |
|
153 |
-# n = length(index) |
|
154 |
-# pushViewport(viewport()) |
|
155 |
-# grid.points(1:n, x[index]) |
|
156 |
-# popViewport() |
|
157 |
-# }, |
|
158 |
-# var_imported = list(x = x), |
|
159 |
-# n = 10, |
|
160 |
-# subset_rule = list(x = subset_vector), |
|
161 |
-# subsetable = TRUE |
|
162 |
-# ) |
|
163 |
-# |
|
164 |
-# 2. The data variable is defined inside the function and no need to import other variables. |
|
165 |
-# |
|
166 |
-# anno2 = AnnotationFunction( |
|
167 |
-# fun = function(index) { |
|
168 |
-# x = 1:10 |
|
169 |
-# n = length(index) |
|
170 |
-# pushViewport(viewport()) |
|
171 |
-# grid.points(1:n, x[index]) |
|
172 |
-# popViewport() |
|
173 |
-# }, |
|
174 |
-# n = 10, |
|
175 |
-# subsetable = TRUE |
|
176 |
-# ) |
|
177 |
-# |
|
178 |
-# 3. Only specify the function to the constructor. ``anno3`` is not subsettable. |
|
179 |
-# |
|
180 |
-# anno3 = AnnotationFunction( |
|
181 |
-# fun = function(index) { |
|
182 |
-# x = 1:10 |
|
183 |
-# n = length(index) |
|
184 |
-# pushViewport(viewport()) |
|
185 |
-# grid.points(1:n, x[index]) |
|
186 |
-# popViewport() |
|
187 |
-# } |
|
188 |
-# ) |
|
189 |
-# |
|
190 |
-# As you can see from the examples, you need to push a viewport for graphics and finally pop the viewport. |
|
191 |
-# |
|
192 |
-# In the package, we have implemted quite a lot annotation function by `AnnotationFunction` constructor: |
|
110 |
+# In the package, we have implemted quite a lot annotation functions by `AnnotationFunction` constructor: |
|
193 | 111 |
# `anno_empty`, `anno_image`, `anno_points`, `anno_lines`, `anno_barplot`, `anno_boxplot`, `anno_histogram`, |
194 | 112 |
# `anno_density`, `anno_joyplot`, `anno_horizon`, `anno_text` and `anno_mark`. These built-in annotation functions |
195 | 113 |
# support as both row annotations and column annotations and they are are all subsettable. |
196 | 114 |
# |
197 |
-# == seealso |
|
198 | 115 |
# The build-in annotation functions are already enough for most of the analysis, nevertheless, if users |
199 | 116 |
# want to know more about how to construct the AnnotationFunction class manually, they can refer to |
200 |
-# ComplexHeatmap Complete Reference (). |
|
117 |
+# https://jokergoo.github.io/ComplexHeatmap-reference/book/heatmap-annotations.html#implement-new-annotation-functions. |
|
118 |
+# |
|
119 |
+# == value |
|
120 |
+# A `AnnotationFunction-class` object which can be used in `HeatmapAnnotation`. |
|
121 |
+# |
|
122 |
+# == example |
|
123 |
+# x = 1:10 |
|
124 |
+# anno1 = AnnotationFunction( |
|
125 |
+# fun = function(index, k, n) { |
|
126 |
+# n = length(index) |
|
127 |
+# pushViewport(viewport(xscale = c(0.5, n + 0.5), yscale = c(0, 10))) |
|
128 |
+# grid.rect() |
|
129 |
+# grid.points(1:n, x[index], default.units = "native") |
|
130 |
+# if(k == 1) grid.yaxis() |
|
131 |
+# popViewport() |
|
132 |
+# }, |
|
133 |
+# var_import = list(x = x), |
|
134 |
+# n = 10, |
|
135 |
+# subsetable = TRUE, |
|
136 |
+# height = unit(2, "cm") |
|
137 |
+# ) |
|
138 |
+# m = rbind(1:10, 11:20) |
|
139 |
+# Heatmap(m, top_annotation = HeatmapAnnotation(foo = anno1)) |
|
140 |
+# Heatmap(m, top_annotation = HeatmapAnnotation(foo = anno1), column_km = 2) |
|
201 | 141 |
AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), |
202 | 142 |
var_import = list(), n = NA, data_scale = c(0, 1), subset_rule = list(), |
203 | 143 |
subsetable = length(subset_rule) > 0, show_name = TRUE, width = NULL, height = NULL) { |
... | ... |
@@ -325,12 +265,12 @@ AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), |
325 | 265 |
# == param |
326 | 266 |
# -object The `AnnotationFunction-class` object. |
327 | 267 |
# -index Index of observations. |
328 |
-# -k Current index of slice. |
|
268 |
+# -k Current slice index. |
|
329 | 269 |
# -n Total number of slices. |
330 | 270 |
# -test Is it in test mode? The value can be logical or a text which is plotted as the title of plot. |
331 | 271 |
# |
332 | 272 |
# == detail |
333 |
-# Normally it is called internally by the `SingleAnnotation` class. |
|
273 |
+# Normally it is called internally by the `SingleAnnotation-class`. |
|
334 | 274 |
# |
335 | 275 |
# When ``test`` is set to ``TRUE``, the annotation graphic is directly drawn, |
336 | 276 |
# which is generally for testing purpose. |
... | ... |
@@ -404,7 +344,7 @@ setMethod(f = "draw", |
404 | 344 |
# == detail |
405 | 345 |
# In `AnnotationFunction-class`, there is an environment which |
406 | 346 |
# stores some external variables for the annotation function (specified by the |
407 |
-# ``var_import`` argument by constructing the `AnnotationFunction-class` |
|
347 |
+# ``var_import`` argument when constructing the `AnnotationFunction-class` |
|
408 | 348 |
# object. This `copy_all,AnnotationFunction-method` hard copies all the |
409 | 349 |
# variables into a new isolated environment. |
410 | 350 |
# |
... | ... |
@@ -97,8 +97,8 @@ anno_width_and_height = function(which, width = NULL, height = NULL, |
97 | 97 |
# -show_name It is used to turn off the drawing of annotation names in `HeatmapAnnotation`. Annotations always have names |
98 | 98 |
# associated and normally they will be drawn beside the annotation graphics to tell what the annotation is about. |
99 | 99 |
# e.g. the annotation names put beside the points annotation graphics. However, for some of the annotations, the names |
100 |
-# are not necessarily to be drawn, such as text annotations drawn by `anno_text` or an empty annotation drawn by `anno_empty()`. |
|
101 |
-# In this case, when `show_names` is set to `FALSE`, there will be no annotation names drawn for the annotation. |
|
100 |
+# are not necessarily to be drawn, such as text annotations drawn by `anno_text` or an empty annotation drawn by `anno_empty`. |
|
101 |
+# In this case, when ``show_names`` is set to ``FALSE``, there will be no annotation names drawn for the annotation. |
|
102 | 102 |
# -width The width of the plotting region (the viewport) that the annotation is drawn. If it is a row annotation, |
103 | 103 |
# the width must be an absolute unit. Since the ``AnnotationFunction`` object is always contained by the `SingleAnnotation-class`object, |
104 | 104 |
# you can only set the width of row annotations or height of column annotations, while e.g. the height of the row annotation is always ``unit(1, "npc")`` |
... | ... |
@@ -348,6 +348,9 @@ setMethod(f = "draw", |
348 | 348 |
if(test2) { |
349 | 349 |
grid.newpage() |
350 | 350 |
pushViewport(viewport(width = 0.8, height = 0.8)) |
351 |
+ if(is.na(object@n)) { |
|
352 |
+ object@n = 1 |
|
353 |
+ } |
|
351 | 354 |
} |
352 | 355 |
|
353 | 356 |
verbose = ht_opt$verbose |
... | ... |
@@ -3,12 +3,14 @@ |
3 | 3 |
# The AnnotationFunction class |
4 | 4 |
# |
5 | 5 |
# == details |
6 |
-# The heatmap annotation is basically graphics aligned to the columns or heatmap if it is column annotation |
|
7 |
-# or heatmap rows if it is row annotation, while the type of the graphics can be arbitory, e.g. |
|
8 |
-# it can be heatmap-like or points. Here the AnnotationFunction class is designed for creating |
|
9 |
-# complex and flexible annotation graphics. As the main part, it uses a use-defined function |
|
10 |
-# to define the graphics. It also keeps information of the size of the plotting regions of the annotation. |
|
11 |
-# And most importantly, it allows subsetting of the annotation to draw a subset of the graphics, which |
|
6 |
+# The heatmap annotation is basically graphics aligned to the heatmap columns |
|
7 |
+# if it is column annotation or heatmap rows if it is row annotation, while |
|
8 |
+# there is no restrictions for the graphic types, e.g. it can be heatmap-like |
|
9 |
+# annotation or points. Here the AnnotationFunction class is designed for |
|
10 |
+# creating complex and flexible annotation graphics. As the main part of the class, it uses |
|
11 |
+# a user-defined function to define the graphics. It also keeps information of |
|
12 |
+# the size of the plotting regions of the annotation. And most importantly, it |
|
13 |
+# allows subsetting of the annotation to draw a subset of the graphics, which |
|
12 | 14 |
# is the base for the splitting of the annotations. |
13 | 15 |
# |
14 | 16 |
# See `AnnotationFunction` constructor for details. |
... | ... |
@@ -81,7 +83,7 @@ anno_width_and_height = function(which, width = NULL, height = NULL, |
81 | 83 |
# Constructor of AnnotationFunction Class |
82 | 84 |
# |
83 | 85 |
# == param |
84 |
-# -fun A function which defines how to draw this annotation. See **Details** section. |
|
86 |
+# -fun A function which defines how to draw the annotation. See **Details** section. |
|
85 | 87 |
# -fun_name The name of the function. It is only used for printing the object. |
86 | 88 |
# -which Whether it is drawn as a column annotation or a row annotation? |
87 | 89 |
# -var_import The names of the variables or the variable themselves that the annotation function depends on. See **Details** section. |
... | ... |
@@ -92,36 +94,54 @@ anno_width_and_height = function(which, width = NULL, height = NULL, |
92 | 94 |
# -subset_rule The rule of subsetting variables in ``var_import``. It should be set when users want the final object to |
93 | 95 |
# be subsetable. See **Details** section. |
94 | 96 |
# -subsetable Whether the object is subsetable? |
97 |
+# -show_name It is used to turn off the drawing of annotation names in `HeatmapAnnotation`. Annotations always have names |
|
98 |
+# associated and normally they will be drawn beside the annotation graphics to tell what the annotation is about. |
|
99 |
+# e.g. the annotation names put beside the points annotation graphics. However, for some of the annotations, the names |
|
100 |
+# are not necessarily to be drawn, such as text annotations drawn by `anno_text` or an empty annotation drawn by `anno_empty()`. |
|
101 |
+# In this case, when `show_names` is set to `FALSE`, there will be no annotation names drawn for the annotation. |
|
95 | 102 |
# -width The width of the plotting region (the viewport) that the annotation is drawn. If it is a row annotation, |
96 |
-# the width must be an absolute unit. |
|
103 |
+# the width must be an absolute unit. Since the ``AnnotationFunction`` object is always contained by the `SingleAnnotation-class`object, |
|
104 |
+# you can only set the width of row annotations or height of column annotations, while e.g. the height of the row annotation is always ``unit(1, "npc")`` |
|
105 |
+# which means it always fully filled in the parent ``SingleAnnotation`` and only in `SingleAnnotation` or even `HeatmapAnnotation` |
|
106 |
+# can adjust the height of the row annotations. |
|
97 | 107 |
# -height The height of the plotting region (the viewport) that the annotation is drawn. If it is a column annotation, |
98 | 108 |
# the width must be an absolute unit. |
99 | 109 |
# |
100 | 110 |
# == details |
101 |
-# A normal R function defines how to draw the annotation graphics. As expected, the main part of the AnnotationFunction |
|
102 |
-# class is this function. The function defines how to draw at specific positions which correspond to rows or columns |
|
103 |
-# in the heatmap. The function should have three arguments: ``index``, ``k`` and ``n`` (the names of the arguments can |
|
104 |
-# be arbitory) where ``k`` and ``n`` are optional. ``index`` corresponds to the indices of rows or columns of the heatmap. |
|
105 |
-# The value of ``index`` is not necessarily to be the whole row indices or column indices. It can also be a subset of |
|
106 |
-# the indices if the annotation is split into slices according to the split of the heatmap. The value in ``index`` is |
|
107 |
-# always sorted according to the reordering of heatmap rows or columns (e.g. by clustering). So, ``index`` actually contains |
|
108 |
-# a list of row or column indices for the current slice after row or column reordering. This type of design makes sure |
|
109 |
-# the annotation graphics are drawn at the correct positions and can be correctly corresponded to the heatmap rows or columns. |
|
111 |
+# We use a normal R function defines how to draw the annotation graphics. As |
|
112 |
+# expected, the main part of the AnnotationFunction class is this function. |
|
113 |
+# The function defines how to draw at specific positions which correspond to |
|
114 |
+# rows or columns in the heatmap. The function should have three arguments: |
|
115 |
+# ``index``, ``k`` and ``n`` (the names of the arguments can be arbitory) |
|
116 |
+# where ``k`` and ``n`` are optional. ``index`` corresponds to the indices of |
|
117 |
+# rows or columns of the heatmap. The value of ``index`` is not necessarily to |
|
118 |
+# be the whole row indices or column indices of the heatmap. It can be a |
|
119 |
+# subset of the indices if the annotation is split into slices according to |
|
120 |
+# the split of the heatmap. ``index`` is always reordered according to the |
|
121 |
+# reordering of heatmap rows or columns (e.g. by clustering). So, ``index`` |
|
122 |
+# actually contains a list of row or column indices for the current slice |
|
123 |
+# after row or column reordering. |
|
110 | 124 |
# |
111 |
-# As mentioned, annotation can be split into slices. ``k`` corresponds to the current slice and ``n`` corresponds to |
|
112 |
-# the total number of slices. The information of ``k`` and ``n`` sometimes can be useful, for example, we want to add axis |
|
113 |
-# in the annotation, and if it is a column annotation and axis is drawn on the very right of the annotation area, the axis |
|
114 |
-# is only drawn when ``k == n``. |
|
125 |
+# As mentioned, annotation can be split into slices. ``k`` corresponds to the |
|
126 |
+# current slice and ``n`` corresponds to the total number of slices. As you can image, |
|
127 |
+# when ``n > 1``, the annotation function will be executed for all ``k``s. The |
|
128 |
+# information of ``k`` and ``n`` sometimes can be useful, for example, we want |
|
129 |
+# to add axis ot the right side of a column annotation, if this column annotation |
|
130 |
+# is split into several slices, the axis is only drawn when``k == n``. |
|
115 | 131 |
# |
116 |
-# Since the function only allows ``index``, ``k`` and ``n``, the function sometimes uses several external variables which can |
|
117 |
-# not be defined inside the function, e.g. the data points for the annotation. These variables should be imported |
|
118 |
-# into the AnnotationFunction class so that the function can correctly find these variables. |
|
132 |
+# Since the function only allows ``index``, ``k`` and ``n``, the function |
|
133 |
+# sometimes uses several external variables which can not be defined inside |
|
134 |
+# the function, e.g. the data points for the annotation. These variables |
|
135 |
+# should be imported into the AnnotationFunction class so that the function |
|
136 |
+# can correctly find these variables (by ``var_import`` argument). |
|
119 | 137 |
# |
120 |
-# One important feature for AnnotationFunction class is it can be subsetable. To allow subsetting of the object, |
|
121 |
-# users need to define the rule for the imported variables if there is any. The rules are simple function which |
|
122 |
-# accpets the variable and indices, and returns the subset of the variable. The subset rule functions implemented |
|
123 |
-# in this package are `subset_gp`, `subset_matrix_by_row` and `subset_vector`. These three functions are enough for |
|
124 |
-# most of the cases. |
|
138 |
+# One important feature for AnnotationFunction class is it can be subsetable. |
|
139 |
+# To allow subsetting of the object, users need to define the rules for the |
|
140 |
+# imported variables. The rules are simple function which |
|
141 |
+# accpets the variable and indices, and returns the subset of the variable. |
|
142 |
+# The subset rule functions implemented in this package are `subset_gp`, |
|
143 |
+# `subset_matrix_by_row` and `subset_vector`. These three functions are enough |
|
144 |
+# for most of the cases. |
|
125 | 145 |
# |
126 | 146 |
# In following, we defined three AnnotationFunction objects: |
127 | 147 |
# |
... | ... |
@@ -155,7 +175,7 @@ anno_width_and_height = function(which, width = NULL, height = NULL, |
155 | 175 |
# subsetable = TRUE |
156 | 176 |
# ) |
157 | 177 |
# |
158 |
-# 3. The most compact way to only specify the function to the constructor. |
|
178 |
+# 3. Only specify the function to the constructor. ``anno3`` is not subsettable. |
|
159 | 179 |
# |
160 | 180 |
# anno3 = AnnotationFunction( |
161 | 181 |
# fun = function(index) { |
... | ... |
@@ -167,15 +187,20 @@ anno_width_and_height = function(which, width = NULL, height = NULL, |
167 | 187 |
# } |
168 | 188 |
# ) |
169 | 189 |
# |
170 |
-# Finally, you need to push a viewport for graphics and finally pop the viewport. |
|
190 |
+# As you can see from the examples, you need to push a viewport for graphics and finally pop the viewport. |
|
171 | 191 |
# |
172 |
-# In the package, quite a lot annotation function are constructed by `AnnotationFunction` constructor: |
|
192 |
+# In the package, we have implemted quite a lot annotation function by `AnnotationFunction` constructor: |
|
173 | 193 |
# `anno_empty`, `anno_image`, `anno_points`, `anno_lines`, `anno_barplot`, `anno_boxplot`, `anno_histogram`, |
174 |
-# `anno_density`, `anno_joyplot`, `anno_horizon`, `anno_text` and `anno_mark`. Thess built-in annotation functions |
|
175 |
-# are all subsettable. |
|
194 |
+# `anno_density`, `anno_joyplot`, `anno_horizon`, `anno_text` and `anno_mark`. These built-in annotation functions |
|
195 |
+# support as both row annotations and column annotations and they are are all subsettable. |
|
196 |
+# |
|
197 |
+# == seealso |
|
198 |
+# The build-in annotation functions are already enough for most of the analysis, nevertheless, if users |
|
199 |
+# want to know more about how to construct the AnnotationFunction class manually, they can refer to |
|
200 |
+# ComplexHeatmap Complete Reference (). |
|
176 | 201 |
AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), |
177 | 202 |
var_import = list(), n = NA, data_scale = c(0, 1), subset_rule = list(), |
178 |
- subsetable = FALSE, show_name = TRUE, width = NULL, height = NULL) { |
|
203 |
+ subsetable = length(subset_rule) > 0, show_name = TRUE, width = NULL, height = NULL) { |
|
179 | 204 |
|
180 | 205 |
which = match.arg(which)[1] |
181 | 206 |
|
... | ... |
@@ -263,7 +288,7 @@ AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), |
263 | 288 |
# -i A vector of indices. |
264 | 289 |
# |
265 | 290 |
# == details |
266 |
-# One good thing for designing the `AnnotationFunction-class` object is it can be subsetted, |
|
291 |
+# One good thing for designing the `AnnotationFunction-class` is it can be subsetted, |
|
267 | 292 |
# and this is the base for the splitting of the annotations. |
268 | 293 |
# |
269 | 294 |
# == example |
... | ... |
@@ -368,17 +393,20 @@ setMethod(f = "draw", |
368 | 393 |
}) |
369 | 394 |
|
370 | 395 |
# == title |
371 |
-# Copy the AnnotationFunction object |
|
396 |
+# Copy the AnnotationFunction Object |
|
372 | 397 |
# |
373 | 398 |
# == param |
374 | 399 |
# -object The `AnnotationFunction-class` object. |
375 | 400 |
# |
376 |
-# == detail |
|
377 |
-# In `AnnotationFunction-class`, there is an environment which stores some external variables |
|
378 |
-# for the annotation function. This `copy_all,AnnotationFunction-method` hard copy all the variables |
|
379 |
-# in that environment to a new environment. |
|
401 |
+# == detail |
|
402 |
+# In `AnnotationFunction-class`, there is an environment which |
|
403 |
+# stores some external variables for the annotation function (specified by the |
|
404 |
+# ``var_import`` argument by constructing the `AnnotationFunction-class` |
|
405 |
+# object. This `copy_all,AnnotationFunction-method` hard copies all the |
|
406 |
+# variables into a new isolated environment. |
|
380 | 407 |
# |
381 | 408 |
# The environment is at ``object@var_env``. |
409 |
+# |
|
382 | 410 |
setMethod(f = "copy_all", |
383 | 411 |
signature = "AnnotationFunction", |
384 | 412 |
definition = function(object) { |
... | ... |
@@ -392,7 +420,7 @@ setMethod(f = "copy_all", |
392 | 420 |
}) |
393 | 421 |
|
394 | 422 |
# == title |
395 |
-# Print the AnnotationFunction object |
|
423 |
+# Print the AnnotationFunction Object |
|
396 | 424 |
# |
397 | 425 |
# == param |
398 | 426 |
# -object The `AnnotationFunction-class` object. |
... | ... |
@@ -434,10 +462,10 @@ setMethod(f = "show", |
434 | 462 |
# |
435 | 463 |
# == param |
436 | 464 |
# -object The `AnnotationFunction-class` object. |
437 |
-# -... other arguments |
|
465 |
+# -... Other arguments. |
|
438 | 466 |
# |
439 |
-# == details |
|
440 |
-# It returns the ``n`` slot in the object. If there does not exist, it returns ``NA``. |
|
467 |
+# == details It returns the ``n`` slot in the object. If it does not exist, it |
|
468 |
+# returns ``NA``. |
|
441 | 469 |
# |
442 | 470 |
# == example |
443 | 471 |
# anno = anno_points(1:10) |
... | ... |
@@ -19,7 +19,7 @@ AnnotationFunction = setClass("AnnotationFunction", |
19 | 19 |
fun_name = "character", |
20 | 20 |
width = "ANY", |
21 | 21 |
height = "ANY", |
22 |
- n = "numeric", |
|
22 |
+ n = "ANY", |
|
23 | 23 |
var_env = "environment", |
24 | 24 |
fun = "function", |
25 | 25 |
subset_rule = "list", |
... | ... |
@@ -35,7 +35,7 @@ AnnotationFunction = setClass("AnnotationFunction", |
35 | 35 |
subset_rule = list(), |
36 | 36 |
subsetable = FALSE, |
37 | 37 |
data_scale = c(0, 1), |
38 |
- n = 0, |
|
38 |
+ n = NA_integer_, |
|
39 | 39 |
extended = unit(c(0, 0, 0, 0), "mm"), |
40 | 40 |
show_name = TRUE |
41 | 41 |
) |
... | ... |
@@ -50,7 +50,7 @@ anno_width_and_height = function(which, width = NULL, height = NULL, |
50 | 50 |
height = default |
51 | 51 |
} else { |
52 | 52 |
if(!is_abs_unit(height)) { |
53 |
- stop("height can only be an absolute unit.") |
|
53 |
+ stop_wrap("height of the annotation can only be an absolute unit.") |
|
54 | 54 |
} else { |
55 | 55 |
height = convertHeight(height, "mm") |
56 | 56 |
} |
... | ... |
@@ -64,7 +64,7 @@ anno_width_and_height = function(which, width = NULL, height = NULL, |
64 | 64 |
width = default |
65 | 65 |
} else { |
66 | 66 |
if(!is_abs_unit(width)) { |
67 |
- stop("width can only be an absolute unit.") |
|
67 |
+ stop_wrap("width of the annotation can only be an absolute unit.") |
|
68 | 68 |
} else { |
69 | 69 |
width = convertWidth(width, "mm") |
70 | 70 |
} |
... | ... |
@@ -174,7 +174,7 @@ anno_width_and_height = function(which, width = NULL, height = NULL, |
174 | 174 |
# `anno_density`, `anno_joyplot`, `anno_horizon`, `anno_text` and `anno_mark`. Thess built-in annotation functions |
175 | 175 |
# are all subsettable. |
176 | 176 |
AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), |
177 |
- var_import = list(), n = 0, data_scale = c(0, 1), subset_rule = list(), |
|
177 |
+ var_import = list(), n = NA, data_scale = c(0, 1), subset_rule = list(), |
|
178 | 178 |
subsetable = FALSE, show_name = TRUE, width = NULL, height = NULL) { |
179 | 179 |
|
180 | 180 |
which = match.arg(which)[1] |
... | ... |
@@ -213,7 +213,7 @@ AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), |
213 | 213 |
anno@var_env[[nm]] = var_import[[nm]] |
214 | 214 |
} |
215 | 215 |
} else { |
216 |
- stop_wrap("`var_import` needs to be a character vector which contains variable names or a list of variables") |
|
216 |
+ stop_wrap("`var_import` needs to be a character vector which contains variable names or a list of variables.") |
|
217 | 217 |
} |
218 | 218 |
environment(fun) = anno@var_env |
219 | 219 |
} else { |
... | ... |
@@ -275,14 +275,14 @@ AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), |
275 | 275 |
return(x) |
276 | 276 |
} else { |
277 | 277 |
if(!x@subsetable) { |
278 |
- stop("This object is not subsetable.") |
|
278 |
+ stop_wrap("This object is not subsetable.") |
|
279 | 279 |
} |
280 | 280 |
x = copy_all(x) |
281 | 281 |
for(var in names(x@subset_rule)) { |
282 | 282 |
oe = try(x@var_env[[var]] <- x@subset_rule[[var]](x@var_env[[var]], i), silent = TRUE) |
283 | 283 |
if(inherits(oe, "try-error")) { |
284 | 284 |
message(paste0("An error when subsetting ", var)) |
285 |
- stop(oe) |
|
285 |
+ stop_wrap(oe) |
|
286 | 286 |
} |
287 | 287 |
} |
288 | 288 |
if(is.logical(i)) { |
... | ... |
@@ -357,7 +357,7 @@ setMethod(f = "draw", |
357 | 357 |
} |
358 | 358 |
vp_name2 = current.viewport()$name |
359 | 359 |
if(vp_name1 != vp_name2) { |
360 |
- stop("Viewports are not the same before and after plotting the annotation graphics.") |
|
360 |
+ stop_wrap("Viewports should be the same before and after plotting the annotation graphics.") |
|
361 | 361 |
} |
362 | 362 |
popViewport() |
363 | 363 |
|
... | ... |
@@ -443,7 +443,9 @@ setMethod(f = "show", |
443 | 443 |
# anno = anno_points(1:10) |
444 | 444 |
# nobs(anno) |
445 | 445 |
nobs.AnnotationFunction = function(object, ...) { |
446 |
- if(object@n > 0) { |
|
446 |
+ if(is.na(object@n)) { |
|
447 |
+ return(NA) |
|
448 |
+ } else if(object@n > 0) { |
|
447 | 449 |
object@n |
448 | 450 |
} else { |
449 | 451 |
NA |
... | ... |
@@ -25,7 +25,8 @@ AnnotationFunction = setClass("AnnotationFunction", |
25 | 25 |
subset_rule = "list", |
26 | 26 |
subsetable = "logical", |
27 | 27 |
data_scale = "numeric", |
28 |
- extended = "ANY" |
|
28 |
+ extended = "ANY", |
|
29 |
+ show_name = "logical" |
|
29 | 30 |
), |
30 | 31 |
prototype = list( |
31 | 32 |
fun_name = "", |
... | ... |
@@ -35,7 +36,8 @@ AnnotationFunction = setClass("AnnotationFunction", |
35 | 36 |
subsetable = FALSE, |
36 | 37 |
data_scale = c(0, 1), |
37 | 38 |
n = 0, |
38 |
- extended = unit(c(0, 0, 0, 0), "mm") |
|
39 |
+ extended = unit(c(0, 0, 0, 0), "mm"), |
|
40 |
+ show_name = TRUE |
|
39 | 41 |
) |
40 | 42 |
) |
41 | 43 |
|
... | ... |
@@ -173,7 +175,7 @@ anno_width_and_height = function(which, width = NULL, height = NULL, |
173 | 175 |
# are all subsettable. |
174 | 176 |
AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), |
175 | 177 |
var_import = list(), n = 0, data_scale = c(0, 1), subset_rule = list(), |
176 |
- subsetable = FALSE, width = NULL, height = NULL) { |
|
178 |
+ subsetable = FALSE, show_name = TRUE, width = NULL, height = NULL) { |
|
177 | 179 |
|
178 | 180 |
which = match.arg(which)[1] |
179 | 181 |
|
... | ... |
@@ -190,6 +192,8 @@ AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"), |
190 | 192 |
anno@width = anno_size$width |
191 | 193 |
anno@height = anno_size$height |
192 | 194 |
|
195 |
+ anno@show_name = show_name |
|
196 |
+ |
|
193 | 197 |
anno@n = n |
194 | 198 |
anno@data_scale = data_scale |
195 | 199 |
|
... | ... |
@@ -1,10 +1,17 @@ |
1 | 1 |
|
2 | 2 |
# == title |
3 |
-# AnnotationFunction class |
|
3 |
+# The AnnotationFunction class |
|
4 | 4 |
# |
5 | 5 |
# == details |
6 |
-# THe AnnotationFunction class is a wrapper of user-defined annotation functions. |
|
7 |
-# See `AnnotationFunction` constructor for details |
|
6 |
+# The heatmap annotation is basically graphics aligned to the columns or heatmap if it is column annotation |
|
7 |
+# or heatmap rows if it is row annotation, while the type of the graphics can be arbitory, e.g. |
|
8 |
+# it can be heatmap-like or points. Here the AnnotationFunction class is designed for creating |
|
9 |
+# complex and flexible annotation graphics. As the main part, it uses a use-defined function |
|
10 |
+# to define the graphics. It also keeps information of the size of the plotting regions of the annotation. |
|
11 |
+# And most importantly, it allows subsetting of the annotation to draw a subset of the graphics, which |
|
12 |
+# is the base for the splitting of the annotations. |
|
13 |
+# |
|
14 |
+# See `AnnotationFunction` constructor for details. |
|
8 | 15 |
# |
9 | 16 |
AnnotationFunction = setClass("AnnotationFunction", |
10 | 17 |
slots = list( |
... | ... |
@@ -69,16 +76,17 @@ anno_width_and_height = function(which, width = NULL, height = NULL, |
69 | 76 |
|
70 | 77 |
|
71 | 78 |
# == title |
72 |
-# Constructor of AnnotationFunction class |
|
79 |
+# Constructor of AnnotationFunction Class |
|
73 | 80 |
# |
74 | 81 |
# == param |
75 |
-# -fun A function which defines how to draw annotation. See **Details** section. |
|
76 |
-# -fun_name The name of the function. It is only used for `show,AnnotationFunction-method`. |
|
82 |
+# -fun A function which defines how to draw this annotation. See **Details** section. |
|
83 |
+# -fun_name The name of the function. It is only used for printing the object. |
|
77 | 84 |
# -which Whether it is drawn as a column annotation or a row annotation? |
78 |
-# -var_imported The name of the object or the objects themselves that the annotation function depends on. See **Details** section. |
|
79 |
-# -n Number of observations in the annotation. It is not mandatory, but it is better to provide this information. |
|
85 |
+# -var_import The names of the variables or the variable themselves that the annotation function depends on. See **Details** section. |
|
86 |
+# -n Number of observations in the annotation. It is not mandatory, but it is better to provide this information |
|
87 |
+# so that the higher order `HeatmapAnnotation` knows it and it can perform check on the consistency of annotations and heatmaps. |
|
80 | 88 |
# -data_scale The data scale on the data axis (y-axis for column annotation and x-axis for row annotation). It is only used |
81 |
-# when `decoration_annotation` is used with "native" unit coordinates. |
|
89 |
+# when `decorate_annotation` is used with "native" unit coordinates. |
|
82 | 90 |
# -subset_rule The rule of subsetting variables in ``var_import``. It should be set when users want the final object to |
83 | 91 |
# be subsetable. See **Details** section. |
84 | 92 |
# -subsetable Whether the object is subsetable? |
... | ... |
@@ -88,12 +96,83 @@ anno_width_and_height = function(which, width = NULL, height = NULL, |
88 | 96 |
# the width must be an absolute unit. |
89 | 97 |
# |
90 | 98 |
# == details |
91 |
-# The AnnotationFunction class is a wrapper of the function which draws heatmap annotation. |
|
99 |
+# A normal R function defines how to draw the annotation graphics. As expected, the main part of the AnnotationFunction |
|
100 |
+# class is this function. The function defines how to draw at specific positions which correspond to rows or columns |
|
101 |
+# in the heatmap. The function should have three arguments: ``index``, ``k`` and ``n`` (the names of the arguments can |
|
102 |
+# be arbitory) where ``k`` and ``n`` are optional. ``index`` corresponds to the indices of rows or columns of the heatmap. |
|
103 |
+# The value of ``index`` is not necessarily to be the whole row indices or column indices. It can also be a subset of |
|
104 |
+# the indices if the annotation is split into slices according to the split of the heatmap. The value in ``index`` is |
|
105 |
+# always sorted according to the reordering of heatmap rows or columns (e.g. by clustering). So, ``index`` actually contains |
|
106 |
+# a list of row or column indices for the current slice after row or column reordering. This type of design makes sure |