... | ... |
@@ -211,6 +211,9 @@ HeatmapAnnotation = function(..., |
211 | 211 |
if(length(show_legend) == 1) { |
212 | 212 |
show_legend = recycle_param(show_legend, simple_anno_name, TRUE) |
213 | 213 |
} |
214 |
+ if(length(show_legend) < length(anno_value_list) && length(show_legend) > 1) { |
|
215 |
+ show_legend = recycle_param(show_legend, simple_anno_name, TRUE) |
|
216 |
+ } |
|
214 | 217 |
# check length of show_legend |
215 | 218 |
if(length(show_legend) == length(anno_value_list) && !all(l_simple_anno)) { |
216 | 219 |
show_legend = show_legend[l_simple_anno] |
... | ... |
@@ -1051,6 +1051,9 @@ anno_type = function(ha) { |
1051 | 1051 |
size(x2) = sum(x2@anno_size) + sum(x2@gap) - x2@gap[length(x2@gap)] |
1052 | 1052 |
|
1053 | 1053 |
} else if(nargs() == 2) { # ha[1:4] |
1054 |
+ if(is.character(i) && all(i %in% names(x2@anno_list))) { |
|
1055 |
+ warning_wrap("It seems you want to obtain a subset of annotations. You should set in a form of `anno[, names]`.") |
|
1056 |
+ } |
|
1054 | 1057 |
x2 = x |
1055 | 1058 |
for(nm in names(x2@anno_list)) { |
1056 | 1059 |
x2@anno_list[[nm]] = x2@anno_list[[nm]][i] |
... | ... |
@@ -95,7 +95,7 @@ HeatmapAnnotation = setClass("HeatmapAnnotation", |
95 | 95 |
# Zuguang Gu <z.gu@dkfz.de> |
96 | 96 |
# |
97 | 97 |
HeatmapAnnotation = function(..., |
98 |
- df, name, col, na_col = "grey", |
|
98 |
+ df = NULL, name, col, na_col = "grey", |
|
99 | 99 |
annotation_legend_param = list(), |
100 | 100 |
show_legend = TRUE, |
101 | 101 |
which = c("column", "row"), |
... | ... |
@@ -150,53 +150,8 @@ HeatmapAnnotation = function(..., |
150 | 150 |
.Object@name = name |
151 | 151 |
n_anno = 0 |
152 | 152 |
|
153 |
- #### check system calls #### |
|
154 |
- # HeatmapAnnotation is either called by `HeatmapAnnotation()` or by `rowAnnotation()`/`columnAnnotation()` |
|
155 |
- sc = sys.calls() |
|
156 |
- nsc = length(sc) |
|
157 |
- if(nsc == 1) { # HeatmapAnnotation(...) |
|
158 |
- scl = as.list(sc[[1]]) |
|
159 |
- arg_list = scl[-1] |
|
160 |
- } else { |
|
161 |
- |
|
162 |
- scl = as.list(sc[[nsc-1]]) |
|
163 |
- if(is.function(scl[[1]])) { |
|
164 |
- if(identical(scl[[1]], pheatmap)) { |
|
165 |
- scl = as.list(sc[[nsc]]) |
|
166 |
- arg_list = scl[-1] |
|
167 |
- } else if(identical(scl[[1]], heatmap)) { |
|
168 |
- scl = as.list(sc[[nsc]]) |
|
169 |
- arg_list = scl[-1] |
|
170 |
- } else if(identical(scl[[1]], heatmap.2)) { |
|
171 |
- scl = as.list(sc[[nsc]]) |
|
172 |
- arg_list = scl[-1] |
|
173 |
- } else { |
|
174 |
- # do.call(rowAnnotation, list(...)) |
|
175 |
- # do.call(columnAnnotation, list(...)) |
|
176 |
- arg_list = scl[-1] |
|
177 |
- } |
|
178 |
- } else if(any(as.character(scl[[1]]) %in% c("HeatmapAnnotation", "rowAnnotation", "columnAnnotation"))) { |
|
179 |
- # columnAnnotation(...), rowAnnotation(...) |
|
180 |
- # do.call("columnAnnotation", list(...)) |
|
181 |
- # do.call("rowAnnotation", list(...)) |
|
182 |
- arg_list = scl[-1] |
|
183 |
- } else { |
|
184 |
- # do.call("HeatmapAnnotation", list(...)) |
|
185 |
- # do.call(HeatmapAnnotation, list(...)) |
|
186 |
- scl = as.list(sc[[nsc]]) |
|
187 |
- arg_list = scl[-1] |
|
188 |
- } |
|
189 |
- } |
|
190 |
- |
|
191 |
- called_args = names(arg_list) |
|
192 |
- anno_args = setdiff(called_args, fun_args) |
|
193 |
- if(any(anno_args == "")) stop_wrap("annotations should have names.") |
|
194 |
- if(is.null(called_args)) { |
|
195 |
- stop_wrap("It seems you are putting only one argument to the function. If it is a simple vector annotation or a function annotation (e.g. anno_*()), specify it as HeatmapAnnotation(name = value). If it is a data frame annotation, specify it as HeatmapAnnotation(df = value)") |
|
196 |
- } |
|
197 |
- |
|
198 | 153 |
##### pull all annotation to `anno_value_list`#### |
199 |
- if("df" %in% called_args) { |
|
154 |
+ if(!is.null(df)) { |
|
200 | 155 |
if(is.matrix(df)) { |
201 | 156 |
warning_wrap("`df` should be a data frame while not a matrix. Convert it to data frame.") |
202 | 157 |
df = as.data.frame(df) |
... | ... |
@@ -209,23 +164,35 @@ HeatmapAnnotation = function(..., |
209 | 164 |
} |
210 | 165 |
|
211 | 166 |
anno_arg_list = list(...) |
212 |
- if("df" %in% called_args && length(anno_arg_list)) { |
|
213 |
- if(any(duplicated(c(names(df), names(anno_arg_list))))) { |
|
214 |
- stop_wrap("Annotation names are duplicated. Check the column names of `df`.") |
|
167 |
+ anno_arg_names = names(anno_arg_list) |
|
168 |
+ if(any(anno_arg_names == "")) { |
|
169 |
+ stop_wrap("Annotations should have names.") |
|
170 |
+ } |
|
171 |
+ if(is.null(anno_arg_names)) { |
|
172 |
+ if(length(anno_arg_list) == 1) { |
|
173 |
+ stop_wrap("The annotation should be specified as name-value pairs or via argument `df` with a data frame.") |
|
174 |
+ } |
|
175 |
+ if(length(anno_arg_list) > 1) { |
|
176 |
+ stop_wrap("Annotations should have names.") |
|
177 |
+ } |
|
178 |
+ } |
|
179 |
+ |
|
180 |
+ if(!is.null(df) && length(anno_arg_list)) { |
|
181 |
+ if(any(duplicated(c(names(df), anno_arg_names)))) { |
|
182 |
+ stop_wrap("Annotation names are duplicated to those in `df`. Check the column names of `df`.") |
|
215 | 183 |
} |
216 | 184 |
} |
217 | 185 |
|
218 | 186 |
anno_value_list = list() |
219 |
- for(nm in called_args) { |
|
220 |
- if(nm %in% names(anno_arg_list)) { |
|
221 |
- anno_value_list[[nm]] = anno_arg_list[[nm]] |
|
222 |
- } else if(nm == "df") { |
|
223 |
- for(nm2 in colnames(df)) { |
|
224 |
- if(is.null(rownames(df))) { |
|
225 |
- anno_value_list[[nm2]] = df[, nm2] |
|
226 |
- } else { |
|
227 |
- anno_value_list[[nm2]] = structure(df[, nm2], names = rownames(df)) |
|
228 |
- } |
|
187 |
+ for(nm in anno_arg_names) { |
|
188 |
+ anno_value_list[[nm]] = anno_arg_list[[nm]] |
|
189 |
+ } |
|
190 |
+ if(!is.null(df)) { |
|
191 |
+ for(nm2 in colnames(df)) { |
|
192 |
+ if(is.null(rownames(df))) { |
|
193 |
+ anno_value_list[[nm2]] = df[, nm2] |
|
194 |
+ } else { |
|
195 |
+ anno_value_list[[nm2]] = structure(df[, nm2], names = rownames(df)) |
|
229 | 196 |
} |
230 | 197 |
} |
231 | 198 |
} |
... | ... |
@@ -25,7 +25,7 @@ HeatmapAnnotation = setClass("HeatmapAnnotation", |
25 | 25 |
width = "ANY", |
26 | 26 |
height = "ANY", |
27 | 27 |
gap = "ANY", |
28 |
- subsetable = "logical", |
|
28 |
+ subsettable = "logical", |
|
29 | 29 |
extended = "ANY", |
30 | 30 |
param = "list" |
31 | 31 |
), |
... | ... |
@@ -33,7 +33,7 @@ HeatmapAnnotation = setClass("HeatmapAnnotation", |
33 | 33 |
anno_list = list(), |
34 | 34 |
which = "column", |
35 | 35 |
gap = unit(0, "mm"), |
36 |
- subsetable = FALSE, |
|
36 |
+ subsettable = FALSE, |
|
37 | 37 |
extended = unit(c(0, 0, 0, 0), "mm"), |
38 | 38 |
param = list() |
39 | 39 |
), |
... | ... |
@@ -526,7 +526,7 @@ HeatmapAnnotation = function(..., |
526 | 526 |
.Object@width = width |
527 | 527 |
.Object@height = height |
528 | 528 |
|
529 |
- .Object@subsetable = all(sapply(anno_list, function(x) x@subsetable)) |
|
529 |
+ .Object@subsettable = all(sapply(anno_list, function(x) x@subsettable)) |
|
530 | 530 |
extended = unit(c(0, 0, 0, 0), "mm") |
531 | 531 |
for(i in 1:4) { |
532 | 532 |
extended[i] = unit(max(sapply(anno_list, function(anno) { |
... | ... |
@@ -795,7 +795,7 @@ setMethod(f = "show", |
795 | 795 |
cat(" items:", ifelse(length(len), len[1], "unknown"), "\n") |
796 | 796 |
cat(" width:", as.character(object@width), "\n") |
797 | 797 |
cat(" height:", as.character(object@height), "\n") |
798 |
- cat(" this object is ", ifelse(object@subsetable, "", "not "), "subsetable\n", sep = "") |
|
798 |
+ cat(" this object is ", ifelse(object@subsettable, "", "not "), "subsettable\n", sep = "") |
|
799 | 799 |
dirt = c("bottom", "left", "top", "right") |
800 | 800 |
for(i in 1:4) { |
801 | 801 |
if(!identical(unit(0, "mm"), object@extended[i])) { |
... | ... |
@@ -220,8 +220,13 @@ HeatmapAnnotation = function(..., |
220 | 220 |
if(nm %in% names(anno_arg_list)) { |
221 | 221 |
anno_value_list[[nm]] = anno_arg_list[[nm]] |
222 | 222 |
} else if(nm == "df") { |
223 |
- for(nm2 in colnames(df)) |
|
224 |
- anno_value_list[[nm2]] = df[, nm2] |
|
223 |
+ for(nm2 in colnames(df)) { |
|
224 |
+ if(is.null(rownames(df))) { |
|
225 |
+ anno_value_list[[nm2]] = df[, nm2] |
|
226 |
+ } else { |
|
227 |
+ anno_value_list[[nm2]] = structure(df[, nm2], names = rownames(df)) |
|
228 |
+ } |
|
229 |
+ } |
|
225 | 230 |
} |
226 | 231 |
} |
227 | 232 |
|
... | ... |
@@ -151,7 +151,6 @@ HeatmapAnnotation = function(..., |
151 | 151 |
n_anno = 0 |
152 | 152 |
|
153 | 153 |
#### check system calls #### |
154 |
- |
|
155 | 154 |
# HeatmapAnnotation is either called by `HeatmapAnnotation()` or by `rowAnnotation()`/`columnAnnotation()` |
156 | 155 |
sc = sys.calls() |
157 | 156 |
nsc = length(sc) |
... | ... |
@@ -159,11 +158,23 @@ HeatmapAnnotation = function(..., |
159 | 158 |
scl = as.list(sc[[1]]) |
160 | 159 |
arg_list = scl[-1] |
161 | 160 |
} else { |
162 |
- # do.call(rowAnnotation, list(...)) |
|
163 |
- # do.call(columnAnnotation, list(...)) |
|
161 |
+ |
|
164 | 162 |
scl = as.list(sc[[nsc-1]]) |
165 | 163 |
if(is.function(scl[[1]])) { |
166 |
- arg_list = scl[-1] |
|
164 |
+ if(identical(scl[[1]], pheatmap)) { |
|
165 |
+ scl = as.list(sc[[nsc]]) |
|
166 |
+ arg_list = scl[-1] |
|
167 |
+ } else if(identical(scl[[1]], heatmap)) { |
|
168 |
+ scl = as.list(sc[[nsc]]) |
|
169 |
+ arg_list = scl[-1] |
|
170 |
+ } else if(identical(scl[[1]], heatmap.2)) { |
|
171 |
+ scl = as.list(sc[[nsc]]) |
|
172 |
+ arg_list = scl[-1] |
|
173 |
+ } else { |
|
174 |
+ # do.call(rowAnnotation, list(...)) |
|
175 |
+ # do.call(columnAnnotation, list(...)) |
|
176 |
+ arg_list = scl[-1] |
|
177 |
+ } |
|
167 | 178 |
} else if(any(as.character(scl[[1]]) %in% c("HeatmapAnnotation", "rowAnnotation", "columnAnnotation"))) { |
168 | 179 |
# columnAnnotation(...), rowAnnotation(...) |
169 | 180 |
# do.call("columnAnnotation", list(...)) |
... | ... |
@@ -155,17 +155,23 @@ HeatmapAnnotation = function(..., |
155 | 155 |
# HeatmapAnnotation is either called by `HeatmapAnnotation()` or by `rowAnnotation()`/`columnAnnotation()` |
156 | 156 |
sc = sys.calls() |
157 | 157 |
nsc = length(sc) |
158 |
- if(nsc == 1) { |
|
158 |
+ if(nsc == 1) { # HeatmapAnnotation(...) |
|
159 | 159 |
scl = as.list(sc[[1]]) |
160 | 160 |
arg_list = scl[-1] |
161 | 161 |
} else { |
162 |
+ # do.call(rowAnnotation, list(...)) |
|
163 |
+ # do.call(columnAnnotation, list(...)) |
|
162 | 164 |
scl = as.list(sc[[nsc-1]]) |
163 | 165 |
if(is.function(scl[[1]])) { |
164 |
- scl = as.list(sc[[nsc]]) |
|
165 | 166 |
arg_list = scl[-1] |
166 |
- } else if(any(as.character(scl[[1]]) %in% c("HeatmapAnnotation", "rowAnnotation", "columnAnnotation"))) { |
|
167 |
+ } else if(any(as.character(scl[[1]]) %in% c("HeatmapAnnotation", "rowAnnotation", "columnAnnotation"))) { |
|
168 |
+ # columnAnnotation(...), rowAnnotation(...) |
|
169 |
+ # do.call("columnAnnotation", list(...)) |
|
170 |
+ # do.call("rowAnnotation", list(...)) |
|
167 | 171 |
arg_list = scl[-1] |
168 | 172 |
} else { |
173 |
+ # do.call("HeatmapAnnotation", list(...)) |
|
174 |
+ # do.call(HeatmapAnnotation, list(...)) |
|
169 | 175 |
scl = as.list(sc[[nsc]]) |
170 | 176 |
arg_list = scl[-1] |
171 | 177 |
} |
... | ... |
@@ -1058,12 +1058,16 @@ anno_type = function(ha) { |
1058 | 1058 |
for(nm in names(x2@anno_list)) { |
1059 | 1059 |
x2@anno_list[[nm]] = x2@anno_list[[nm]][i] |
1060 | 1060 |
} |
1061 |
+ x2@anno_size = do.call(unit.c, lapply(x2@anno_list, size)) |
|
1062 |
+ size(x2) = sum(x2@anno_size) + sum(x2@gap) - x2@gap[length(x2@gap)] |
|
1061 | 1063 |
|
1062 | 1064 |
} else if(nargs() == 2) { # ha[1:4] |
1063 | 1065 |
x2 = x |
1064 | 1066 |
for(nm in names(x2@anno_list)) { |
1065 | 1067 |
x2@anno_list[[nm]] = x2@anno_list[[nm]][i] |
1066 | 1068 |
} |
1069 |
+ x2@anno_size = do.call(unit.c, lapply(x2@anno_list, size)) |
|
1070 |
+ size(x2) = sum(x2@anno_size) + sum(x2@gap) - x2@gap[length(x2@gap)] |
|
1067 | 1071 |
|
1068 | 1072 |
} else if (!missing(i) && !missing(j)) { # ha[1:4, "foo"] |
1069 | 1073 |
x2 = x |
... | ... |
@@ -1075,6 +1079,7 @@ anno_type = function(ha) { |
1075 | 1079 |
x2@gap = x@gap[j] |
1076 | 1080 |
x2@gap[length(x2@gap)] = unit(0, "mm") |
1077 | 1081 |
|
1082 |
+ x2@anno_size = do.call(unit.c, lapply(x2@anno_list, size)) |
|
1078 | 1083 |
size(x2) = sum(x2@anno_size) + sum(x2@gap) - x2@gap[length(x2@gap)] |
1079 | 1084 |
} |
1080 | 1085 |
|
... | ... |
@@ -273,13 +273,17 @@ HeatmapAnnotation = function(..., |
273 | 273 |
} |
274 | 274 |
border = recycle_param(border, an, FALSE) |
275 | 275 |
annotation_name_gp = recycle_gp(annotation_name_gp, n_total_anno) |
276 |
- if(length(annotation_label) > 0) { |
|
277 |
- if(length(annotation_label) != length(an)) { |
|
278 |
- stop_wrap("Length of `annotation_label` should be the same as number of annotations.") |
|
276 |
+ if(length(annotation_label)) { |
|
277 |
+ if(inherits(annotation_label, "gridtext")) { |
|
278 |
+ annotation_label = lapply(seq_along(annotation_label), function(i) annotation_label[i]) |
|
279 |
+ names(annotation_label) = an |
|
279 | 280 |
} |
280 |
- annotation_label = lapply(seq_along(annotation_label), function(i) annotation_label[i]) |
|
281 |
- names(annotation_label) == an |
|
282 | 281 |
} |
282 |
+ annotation_label = recycle_list(annotation_label, an, NULL) |
|
283 |
+ # if(length(annotation_label) > 0) { |
|
284 |
+ # annotation_label = lapply(seq_along(annotation_label), function(i) annotation_label[i]) |
|
285 |
+ # names(annotation_label) == an |
|
286 |
+ # } |
|
283 | 287 |
|
284 | 288 |
if(!missing(col)) { |
285 | 289 |
if(length(col) >= 1) { |
... | ... |
@@ -328,7 +332,7 @@ HeatmapAnnotation = function(..., |
328 | 332 |
i_anno = i_anno + 1 |
329 | 333 |
arg_list = list(name = ag, which = which, |
330 | 334 |
label = annotation_label[[i_anno]], |
331 |
- show_name = show_annotation_name[i_anno], |
|
335 |
+ show_name = show_annotation_name[[i_anno]], |
|
332 | 336 |
name_gp = subset_gp(annotation_name_gp, i_anno), |
333 | 337 |
name_offset = annotation_name_offset[[i_anno]], |
334 | 338 |
name_side = annotation_name_side[i_anno], |
... | ... |
@@ -273,8 +273,12 @@ HeatmapAnnotation = function(..., |
273 | 273 |
} |
274 | 274 |
border = recycle_param(border, an, FALSE) |
275 | 275 |
annotation_name_gp = recycle_gp(annotation_name_gp, n_total_anno) |
276 |
- if(length(annotation_label) != length(an)) { |
|
277 |
- stop_wrap("Length of `annotation_label` should be the same as number of annotations.") |
|
276 |
+ if(length(annotation_label) > 0) { |
|
277 |
+ if(length(annotation_label) != length(an)) { |
|
278 |
+ stop_wrap("Length of `annotation_label` should be the same as number of annotations.") |
|
279 |
+ } |
|
280 |
+ annotation_label = lapply(seq_along(annotation_label), function(i) annotation_label[i]) |
|
281 |
+ names(annotation_label) == an |
|
278 | 282 |
} |
279 | 283 |
|
280 | 284 |
if(!missing(col)) { |
... | ... |
@@ -323,7 +327,7 @@ HeatmapAnnotation = function(..., |
323 | 327 |
|
324 | 328 |
i_anno = i_anno + 1 |
325 | 329 |
arg_list = list(name = ag, which = which, |
326 |
- label = annotation_label[i_anno], |
|
330 |
+ label = annotation_label[[i_anno]], |
|
327 | 331 |
show_name = show_annotation_name[i_anno], |
328 | 332 |
name_gp = subset_gp(annotation_name_gp, i_anno), |
329 | 333 |
name_offset = annotation_name_offset[[i_anno]], |
... | ... |
@@ -273,7 +273,9 @@ HeatmapAnnotation = function(..., |
273 | 273 |
} |
274 | 274 |
border = recycle_param(border, an, FALSE) |
275 | 275 |
annotation_name_gp = recycle_gp(annotation_name_gp, n_total_anno) |
276 |
- annotation_label = recycle_list(annotation_label, an, NULL) |
|
276 |
+ if(length(annotation_label) != length(an)) { |
|
277 |
+ stop_wrap("Length of `annotation_label` should be the same as number of annotations.") |
|
278 |
+ } |
|
277 | 279 |
|
278 | 280 |
if(!missing(col)) { |
279 | 281 |
if(length(col) >= 1) { |
... | ... |
@@ -321,7 +323,7 @@ HeatmapAnnotation = function(..., |
321 | 323 |
|
322 | 324 |
i_anno = i_anno + 1 |
323 | 325 |
arg_list = list(name = ag, which = which, |
324 |
- label = annotation_label[[i_anno]], |
|
326 |
+ label = annotation_label[i_anno], |
|
325 | 327 |
show_name = show_annotation_name[i_anno], |
326 | 328 |
name_gp = subset_gp(annotation_name_gp, i_anno), |
327 | 329 |
name_offset = annotation_name_offset[[i_anno]], |
... | ... |
@@ -663,8 +663,8 @@ setMethod(f = "draw", |
663 | 663 |
|
664 | 664 |
if(test2) { |
665 | 665 |
grid.newpage() |
666 |
- if(which == "column") pushViewport(viewport(width = unit(1, "npc") - unit(3, "cm"), height = object@height)) |
|
667 |
- if(which == "row") pushViewport(viewport(height = unit(1, "npc") - unit(3, "cm"), width = object@width)) |
|
666 |
+ if(which == "column") pushViewport(viewport(width = unit(1, "npc") - unit(3, "cm") - sum(object@extended[c(2,4)]), height = object@height)) |
|
667 |
+ if(which == "row") pushViewport(viewport(height = unit(1, "npc") - unit(3, "cm") - sum(object@extended[c(1,3)]), width = object@width)) |
|
668 | 668 |
} else { |
669 | 669 |
pushViewport(do.call(viewport, vp_param)) |
670 | 670 |
} |
... | ... |
@@ -63,7 +63,7 @@ HeatmapAnnotation = setClass("HeatmapAnnotation", |
63 | 63 |
# -annotation_name_gp Graphic parameters for anntation names. Graphic paramters can be vectors. |
64 | 64 |
# -annotation_name_offset Offset to the annotation names, a `grid::unit` object. The value can be a vector. |
65 | 65 |
# -annotation_name_side Side of the annotation names. |
66 |
-# -annotation_name_rot Rotation of the annotation names, it can only take values in ``c(00, 90, 180, 270)``. The value can be a vector. |
|
66 |
+# -annotation_name_rot Rotation of the annotation names. The value can be a vector. |
|
67 | 67 |
# -annotation_name_align Whether to align the annotation names. |
68 | 68 |
# -annotation_height Height of each annotation if annotations are column annotations. |
69 | 69 |
# -annotation_width Width of each annotation if annotations are row annotations. |
... | ... |
@@ -900,7 +900,7 @@ setMethod(f = "add_heatmap", |
900 | 900 |
# ha3 = HeatmapAnnotation(sth = cbind(1:10, 10:1)) |
901 | 901 |
# ha = c(ha1, ha2, ha3, gap = unit(c(1, 4), "mm")) |
902 | 902 |
# ha |
903 |
-c.HeatmapAnnotation = function(..., gap = unit(0, "mm")) { |
|
903 |
+c.HeatmapAnnotation = function(..., gap = unit(1, "points")) { |
|
904 | 904 |
anno_list = list(...) |
905 | 905 |
if(length(anno_list) == 1) { |
906 | 906 |
return(anno_list[[1]]) |
... | ... |
@@ -1410,3 +1410,90 @@ has_zoomed_anno_empty = function(ha) { |
1410 | 1410 |
} |
1411 | 1411 |
return(FALSE) |
1412 | 1412 |
} |
1413 |
+ |
|
1414 |
+# == title |
|
1415 |
+# Attach heatmap annotations to the heatmap |
|
1416 |
+# |
|
1417 |
+# == param |
|
1418 |
+# -object A `Heatmap-class` object. |
|
1419 |
+# -ha A `HeatmapAnnotation-class` object. |
|
1420 |
+# -side Which side of the heatmap. Value should be in "top", "bottom", "left", "right". |
|
1421 |
+# -gap Space between the two heatmap annotations. |
|
1422 |
+# |
|
1423 |
+# == example |
|
1424 |
+# m = matrix(rnorm(100), 10) |
|
1425 |
+# ht = Heatmap(m) |
|
1426 |
+# ha = HeatmapAnnotation(foo = 1:10) |
|
1427 |
+# ht = attach_annotation(ht, ha) |
|
1428 |
+# ht |
|
1429 |
+# ha2 = HeatmapAnnotation(bar = letters[1:10]) |
|
1430 |
+# ht = attach_annotation(ht, ha2) |
|
1431 |
+# ht |
|
1432 |
+setMethod(f = "attach_annotation", |
|
1433 |
+ signature = "Heatmap", |
|
1434 |
+ definition = function(object, ha, side = c("top", "bottom", "left", "right"), |
|
1435 |
+ gap = unit(1, "points")) { |
|
1436 |
+ |
|
1437 |
+ if(missing(side)) { |
|
1438 |
+ side = ifelse(ha@which == "column", "top", "left") |
|
1439 |
+ } else { |
|
1440 |
+ side = match.arg(side)[1] |
|
1441 |
+ } |
|
1442 |
+ ha_which = ha@which |
|
1443 |
+ if(ha_which == "column" && side %in% c("left", "right")) { |
|
1444 |
+ stop_wrap("Column annotations can only be attached to the top/bottom side of the heatmap.") |
|
1445 |
+ } else if(ha_which == "row" && side %in% c("top", "bottom")) { |
|
1446 |
+ stop_wrap("Row annotations can only be attached to the left/right side of the heatmap.") |
|
1447 |
+ } |
|
1448 |
+ |
|
1449 |
+ if(side == "top") { |
|
1450 |
+ if(is.null(object@top_annotation)) { |
|
1451 |
+ object@top_annotation = ha |
|
1452 |
+ h = height(ha) + ht_opt$COLUMN_ANNO_PADDING |
|
1453 |
+ h = convertHeight(h, "mm") |
|
1454 |
+ object@top_annotation_param = list(height = h) |
|
1455 |
+ } else { |
|
1456 |
+ object@top_annotation = c(object@top_annotation, ha, gap = gap) |
|
1457 |
+ h = height(object@top_annotation) + height(ha) + gap |
|
1458 |
+ h = convertHeight(h, "mm") |
|
1459 |
+ object@top_annotation_param = list(height = h) |
|
1460 |
+ } |
|
1461 |
+ } else if(side == "bottom") { |
|
1462 |
+ if(is.null(object@bottom_annotation)) { |
|
1463 |
+ object@bottom_annotation = ha |
|
1464 |
+ h = height(ha) + ht_opt$COLUMN_ANNO_PADDING |
|
1465 |
+ h = convertHeight(h, "mm") |
|
1466 |
+ object@bottom_annotation_param = list(height = h) |
|
1467 |
+ } else { |
|
1468 |
+ object@bottom_annotation = c(object@bottom_annotation, ha, gap = gap) |
|
1469 |
+ h = height(object@bottom_annotation) + height(ha) + gap |
|
1470 |
+ h = convertHeight(h, "mm") |
|
1471 |
+ object@bottom_annotation_param = list(height = h) |
|
1472 |
+ } |
|
1473 |
+ } else if(side == "left") { |
|
1474 |
+ if(is.null(object@left_annotation)) { |
|
1475 |
+ object@left_annotation = ha |
|
1476 |
+ w = width(ha) + ht_opt$ROW_ANNO_PADDING |
|
1477 |
+ w = convertWidth(w, "mm") |
|
1478 |
+ object@left_annotation_param = list(width = w) |
|
1479 |
+ } else { |
|
1480 |
+ object@left_annotation = c(object@left_annotation, ha, gap = gap) |
|
1481 |
+ w = width(object@left_annotation) + width(ha) + gap |
|
1482 |
+ w = convertWidth(w, "mm") |
|
1483 |
+ object@left_annotation_param = list(width = w) |
|
1484 |
+ } |
|
1485 |
+ } else if(side == "right") { |
|
1486 |
+ if(is.null(object@right_annotation)) { |
|
1487 |
+ object@right_annotation = ha |
|
1488 |
+ w = width(ha) + ht_opt$ROW_ANNO_PADDING |
|
1489 |
+ w = convertWidth(w, "mm") |
|
1490 |
+ object@right_annotation_param = list(width = w) |
|
1491 |
+ } else { |
|
1492 |
+ object@right_annotation = c(object@right_annotation, ha, gap = gap) |
|
1493 |
+ w = width(object@right_annotation) + width(ha) + gap |
|
1494 |
+ w = convertWidth(w, "mm") |
|
1495 |
+ object@right_annotation_param = list(height = w) |
|
1496 |
+ } |
|
1497 |
+ } |
|
1498 |
+ object |
|
1499 |
+}) |
... | ... |
@@ -64,6 +64,7 @@ HeatmapAnnotation = setClass("HeatmapAnnotation", |
64 | 64 |
# -annotation_name_offset Offset to the annotation names, a `grid::unit` object. The value can be a vector. |
65 | 65 |
# -annotation_name_side Side of the annotation names. |
66 | 66 |
# -annotation_name_rot Rotation of the annotation names, it can only take values in ``c(00, 90, 180, 270)``. The value can be a vector. |
67 |
+# -annotation_name_align Whether to align the annotation names. |
|
67 | 68 |
# -annotation_height Height of each annotation if annotations are column annotations. |
68 | 69 |
# -annotation_width Width of each annotation if annotations are row annotations. |
69 | 70 |
# -height Height of the whole column annotations. |
... | ... |
@@ -108,6 +109,7 @@ HeatmapAnnotation = function(..., |
108 | 109 |
annotation_name_offset = NULL, |
109 | 110 |
annotation_name_side = ifelse(which == "column", "right", "bottom"), |
110 | 111 |
annotation_name_rot = NULL, |
112 |
+ annotation_name_align = FALSE, |
|
111 | 113 |
|
112 | 114 |
annotation_height = NULL, |
113 | 115 |
annotation_width = NULL, |
... | ... |
@@ -441,6 +443,51 @@ HeatmapAnnotation = function(..., |
441 | 443 |
anno_size = convertWidth(anno_size, "mm") |
442 | 444 |
|
443 | 445 |
names(anno_list) = sapply(anno_list, function(x) x@name) |
446 |
+ |
|
447 |
+ if(annotation_name_align) { |
|
448 |
+ # adjust x, y, offset slot in SingleAnnotation objects |
|
449 |
+ l_bottom = sapply(anno_list, function(x) x@name_param$side == "bottom" & x@name_param$show & x@fun@fun_name != "anno_simple") |
|
450 |
+ if(sum(l_bottom) > 1) { |
|
451 |
+ max_offset = unit(max(sapply(anno_list[l_bottom], function(anno) { |
|
452 |
+ unit_to_numeric(anno@name_param$offset) |
|
453 |
+ })), "mm") |
|
454 |
+ for(i in which(l_bottom)) { |
|
455 |
+ anno_list[[i]]@name_param$offset = max_offset |
|
456 |
+ anno_list[[i]]@name_param$y = unit(0, "npc") - max_offset |
|
457 |
+ } |
|
458 |
+ } |
|
459 |
+ l_top = sapply(anno_list, function(x) x@name_param$side == "top" & x@name_param$show & x@fun@fun_name != "anno_simple") |
|
460 |
+ if(sum(l_top) > 1) { |
|
461 |
+ max_offset = unit(max(sapply(anno_list[l_top], function(anno) { |
|
462 |
+ unit_to_numeric(anno@name_param$offset) |
|
463 |
+ })), "mm") |
|
464 |
+ for(i in which(l_bottom)) { |
|
465 |
+ anno_list[[i]]@name_param$offset = max_offset |
|
466 |
+ anno_list[[i]]@name_param$y = unit(1, "npc") + max_offset |
|
467 |
+ } |
|
468 |
+ } |
|
469 |
+ l_left = sapply(anno_list, function(x) x@name_param$side == "left" & x@name_param$show & x@fun@fun_name != "anno_simple") |
|
470 |
+ if(sum(l_left) > 1) { |
|
471 |
+ max_offset = unit(max(sapply(anno_list[l_left], function(anno) { |
|
472 |
+ unit_to_numeric(anno@name_param$offset) |
|
473 |
+ })), "mm") |
|
474 |
+ for(i in which(l_left)) { |
|
475 |
+ anno_list[[i]]@name_param$offset = max_offset |
|
476 |
+ anno_list[[i]]@name_param$x = unit(0, "npc") - max_offset |
|
477 |
+ } |
|
478 |
+ } |
|
479 |
+ l_right = sapply(anno_list, function(x) x@name_param$side == "right" & x@name_param$show & x@fun@fun_name != "anno_simple") |
|
480 |
+ if(sum(l_right) > 1) { |
|
481 |
+ max_offset = unit(max(sapply(anno_list[l_right], function(anno) { |
|
482 |
+ unit_to_numeric(anno@name_param$offset) |
|
483 |
+ })), "mm") |
|
484 |
+ for(i in which(l_right)) { |
|
485 |
+ anno_list[[i]]@name_param$offset = max_offset |
|
486 |
+ anno_list[[i]]@name_param$x = unit(1, "npc") + max_offset |
|
487 |
+ } |
|
488 |
+ } |
|
489 |
+ } |
|
490 |
+ |
|
444 | 491 |
.Object@anno_list = anno_list |
445 | 492 |
.Object@anno_size = anno_size |
446 | 493 |
.Object@which = which |
... | ... |
@@ -455,6 +502,7 @@ HeatmapAnnotation = function(..., |
455 | 502 |
})), "mm") |
456 | 503 |
} |
457 | 504 |
.Object@extended = extended |
505 |
+ |
|
458 | 506 |
.Object@param = list( |
459 | 507 |
simple_anno_size = simple_anno_size, |
460 | 508 |
simple_anno_size_adjust = simple_anno_size_adjust, |
... | ... |
@@ -281,6 +281,7 @@ HeatmapAnnotation = function(..., |
281 | 281 |
if(any(is.na(names(col)))) { |
282 | 282 |
stop_wrap("`col` should be a named list.") |
283 | 283 |
} |
284 |
+ col = col[intersect(simple_anno_name, names(col))] |
|
284 | 285 |
if(any(sapply(col, function(x) if(is.function(x)) FALSE else is.null(names(x))))) { |
285 | 286 |
stop_wrap("elements in `col` should be named vectors.") |
286 | 287 |
} |
... | ... |
@@ -158,7 +158,10 @@ HeatmapAnnotation = function(..., |
158 | 158 |
arg_list = scl[-1] |
159 | 159 |
} else { |
160 | 160 |
scl = as.list(sc[[nsc-1]]) |
161 |
- if(any(as.character(scl[[1]]) %in% c("HeatmapAnnotation", "rowAnnotation", "columnAnnotation"))) { |
|
161 |
+ if(is.function(scl[[1]])) { |
|
162 |
+ scl = as.list(sc[[nsc]]) |
|
163 |
+ arg_list = scl[-1] |
|
164 |
+ } else if(any(as.character(scl[[1]]) %in% c("HeatmapAnnotation", "rowAnnotation", "columnAnnotation"))) { |
|
162 | 165 |
arg_list = scl[-1] |
163 | 166 |
} else { |
164 | 167 |
scl = as.list(sc[[nsc]]) |
... | ... |
@@ -942,6 +942,9 @@ names.HeatmapAnnotation = function(x) { |
942 | 942 |
names(x@anno_list) = value |
943 | 943 |
for(i in seq_along(value)) { |
944 | 944 |
x@anno_list[[i]]@name = value[i] |
945 |
+ if(!is.null(x@anno_list[[i]]@color_mapping)) { |
|
946 |
+ x@anno_list[[i]]@color_mapping@name = value[i] |
|
947 |
+ } |
|
945 | 948 |
} |
946 | 949 |
return(x) |
947 | 950 |
} |
... | ... |
@@ -271,18 +271,20 @@ HeatmapAnnotation = function(..., |
271 | 271 |
annotation_label = recycle_list(annotation_label, an, NULL) |
272 | 272 |
|
273 | 273 |
if(!missing(col)) { |
274 |
- if(is.null(names(col))) { |
|
275 |
- stop_wrap("`col` should be a named list.") |
|
276 |
- } |
|
277 |
- if(any(is.na(names(col)))) { |
|
278 |
- stop_wrap("`col` should be a named list.") |
|
279 |
- } |
|
280 |
- if(any(sapply(col, function(x) if(is.function(x)) FALSE else is.null(names(x))))) { |
|
281 |
- stop_wrap("elements in `col` should be named vectors.") |
|
282 |
- } |
|
283 |
- if(any(sapply(col, function(x) if(is.function(x)) FALSE else any(is.na(names(x)))))) { |
|
284 |
- stop_wrap("elements in `col` should be named vectors.") |
|
285 |
- } |
|
274 |
+ if(length(col) >= 1) { |
|
275 |
+ if(is.null(names(col))) { |
|
276 |
+ stop_wrap("`col` should be a named list.") |
|
277 |
+ } |
|
278 |
+ if(any(is.na(names(col)))) { |
|
279 |
+ stop_wrap("`col` should be a named list.") |
|
280 |
+ } |
|
281 |
+ if(any(sapply(col, function(x) if(is.function(x)) FALSE else is.null(names(x))))) { |
|
282 |
+ stop_wrap("elements in `col` should be named vectors.") |
|
283 |
+ } |
|
284 |
+ if(any(sapply(col, function(x) if(is.function(x)) FALSE else any(is.na(names(x)))))) { |
|
285 |
+ stop_wrap("elements in `col` should be named vectors.") |
|
286 |
+ } |
|
287 |
+ } |
|
286 | 288 |
} |
287 | 289 |
|
288 | 290 |
### check the length of annotations |
... | ... |
@@ -59,6 +59,7 @@ HeatmapAnnotation = setClass("HeatmapAnnotation", |
59 | 59 |
# -gap Gap between annotations. It can be a single value or a vector of `grid::unit` objects. |
60 | 60 |
# -show_annotation_name Whether show annotation names? For column annotation, annotation names are drawn either on the left |
61 | 61 |
# or the right, and for row annotations, names are draw either on top or at the bottom. The value can be a vector. |
62 |
+# -annotation_label Labels for the annotations. By default it is the same as individual annotation names. |
|
62 | 63 |
# -annotation_name_gp Graphic parameters for anntation names. Graphic paramters can be vectors. |
63 | 64 |
# -annotation_name_offset Offset to the annotation names, a `grid::unit` object. The value can be a vector. |
64 | 65 |
# -annotation_name_side Side of the annotation names. |
... | ... |
@@ -102,6 +103,7 @@ HeatmapAnnotation = function(..., |
102 | 103 |
gap = unit(1, "points"), |
103 | 104 |
|
104 | 105 |
show_annotation_name = TRUE, |
106 |
+ annotation_label = NULL, |
|
105 | 107 |
annotation_name_gp = gpar(), |
106 | 108 |
annotation_name_offset = NULL, |
107 | 109 |
annotation_name_side = ifelse(which == "column", "right", "bottom"), |
... | ... |
@@ -266,6 +268,7 @@ HeatmapAnnotation = function(..., |
266 | 268 |
} |
267 | 269 |
border = recycle_param(border, an, FALSE) |
268 | 270 |
annotation_name_gp = recycle_gp(annotation_name_gp, n_total_anno) |
271 |
+ annotation_label = recycle_list(annotation_label, an, NULL) |
|
269 | 272 |
|
270 | 273 |
if(!missing(col)) { |
271 | 274 |
if(is.null(names(col))) { |
... | ... |
@@ -310,6 +313,7 @@ HeatmapAnnotation = function(..., |
310 | 313 |
|
311 | 314 |
i_anno = i_anno + 1 |
312 | 315 |
arg_list = list(name = ag, which = which, |
316 |
+ label = annotation_label[[i_anno]], |
|
313 | 317 |
show_name = show_annotation_name[i_anno], |
314 | 318 |
name_gp = subset_gp(annotation_name_gp, i_anno), |
315 | 319 |
name_offset = annotation_name_offset[[i_anno]], |
... | ... |
@@ -961,6 +961,7 @@ anno_type = function(ha) { |
961 | 961 |
# ha[, 1:2] |
962 | 962 |
# ha[1:5, c("foo", "sth")] |
963 | 963 |
"[.HeatmapAnnotation" = function(x, i, j) { |
964 |
+ |
|
964 | 965 |
if(!missing(j)) { |
965 | 966 |
if(is.character(j)) { |
966 | 967 |
j = which(names(x@anno_list) %in% j) |
... | ... |
@@ -1004,7 +1005,6 @@ anno_type = function(ha) { |
1004 | 1005 |
x2@gap[length(x2@gap)] = unit(0, "mm") |
1005 | 1006 |
|
1006 | 1007 |
size(x2) = sum(x2@anno_size) + sum(x2@gap) - x2@gap[length(x2@gap)] |
1007 |
- |
|
1008 | 1008 |
} |
1009 | 1009 |
|
1010 | 1010 |
extended = unit(c(0, 0, 0, 0), "mm") |
... | ... |
@@ -1237,7 +1237,7 @@ setMethod(f = "re_size", |
1237 | 1237 |
if(is_size_set) { |
1238 | 1238 |
if(is_abs_unit(size_adjusted)) { |
1239 | 1239 |
rel_num = sapply(which(l_rel_unit), function(i) { |
1240 |
- if(identical(class(annotation_size_adjusted[i]), "unit")) { |
|
1240 |
+ if(inherits(annotation_size_adjusted[i], "unit")) { |
|
1241 | 1241 |
if(unitType(annotation_size_adjusted[i]) != "null") { |
1242 | 1242 |
stop_wrap("relative unit should be defined as `unit(..., 'null')") |
1243 | 1243 |
} |
... | ... |
@@ -1238,7 +1238,7 @@ setMethod(f = "re_size", |
1238 | 1238 |
if(is_abs_unit(size_adjusted)) { |
1239 | 1239 |
rel_num = sapply(which(l_rel_unit), function(i) { |
1240 | 1240 |
if(identical(class(annotation_size_adjusted[i]), "unit")) { |
1241 |
- if(attr(annotation_size_adjusted[i], "unit") != "null") { |
|
1241 |
+ if(unitType(annotation_size_adjusted[i]) != "null") { |
|
1242 | 1242 |
stop_wrap("relative unit should be defined as `unit(..., 'null')") |
1243 | 1243 |
} |
1244 | 1244 |
} else { |
... | ... |
@@ -440,9 +440,9 @@ HeatmapAnnotation = function(..., |
440 | 440 |
.Object@subsetable = all(sapply(anno_list, function(x) x@subsetable)) |
441 | 441 |
extended = unit(c(0, 0, 0, 0), "mm") |
442 | 442 |
for(i in 1:4) { |
443 |
- extended[[i]] = max(sapply(anno_list, function(anno) { |
|
444 |
- anno@extended[[i]] |
|
445 |
- })) |
|
443 |
+ extended[i] = unit(max(sapply(anno_list, function(anno) { |
|
444 |
+ unit_to_numeric(anno@extended[i]) |
|
445 |
+ })), "mm") |
|
446 | 446 |
} |
447 | 447 |
.Object@extended = extended |
448 | 448 |
.Object@param = list( |
... | ... |
@@ -893,9 +893,9 @@ c.HeatmapAnnotation = function(..., gap = unit(0, "mm")) { |
893 | 893 |
|
894 | 894 |
extended = unit(c(0, 0, 0, 0), "mm") |
895 | 895 |
for(i in 1:4) { |
896 |
- extended[[i]] = max(sapply(x@anno_list, function(anno) { |
|
897 |
- anno@extended[[i]] |
|
898 |
- })) |
|
896 |
+ extended[i] = unit(max(sapply(x@anno_list, function(anno) { |
|
897 |
+ unit_to_numeric(anno@extended[i]) |
|
898 |
+ })), "mm") |
|
899 | 899 |
} |
900 | 900 |
x@extended = extended |
901 | 901 |
|
... | ... |
@@ -1009,9 +1009,9 @@ anno_type = function(ha) { |
1009 | 1009 |
|
1010 | 1010 |
extended = unit(c(0, 0, 0, 0), "mm") |
1011 | 1011 |
for(i in 1:4) { |
1012 |
- extended[[i]] = max(sapply(x2@anno_list, function(anno) { |
|
1013 |
- anno@extended[[i]] |
|
1014 |
- })) |
|
1012 |
+ extended[[i]] = unit(max(sapply(x2@anno_list, function(anno) { |
|
1013 |
+ unit_to_numeric(anno@extended[i]) |
|
1014 |
+ })), "mm") |
|
1015 | 1015 |
} |
1016 | 1016 |
x2@extended = extended |
1017 | 1017 |
|
... | ... |
@@ -1202,7 +1202,11 @@ setMethod(f = "re_size", |
1202 | 1202 |
anno_size = object@anno_size |
1203 | 1203 |
size = slot(object, size_name) |
1204 | 1204 |
gap = object@gap |
1205 |
- gap = gap[-length(gap)] |
|
1205 |
+ if(length(gap) == 1) { |
|
1206 |
+ gap = unit(0, "mm") |
|
1207 |
+ } else { |
|
1208 |
+ gap = gap[-length(gap)] |
|
1209 |
+ } |
|
1206 | 1210 |
n = length(object@anno_list) |
1207 | 1211 |
|
1208 | 1212 |
# the basic rule is |
... | ... |
@@ -1240,7 +1244,7 @@ setMethod(f = "re_size", |
1240 | 1244 |
} else { |
1241 | 1245 |
stop_wrap("relative unit should be defined as `unit(..., 'null')") |
1242 | 1246 |
} |
1243 |
- annotation_size_adjusted[i][[1]] |
|
1247 |
+ unit_to_numeric(annotation_size_adjusted[i][[1]]) |
|
1244 | 1248 |
}) |
1245 | 1249 |
rel_num = rel_num/sum(rel_num) |
1246 | 1250 |
if(any(!l_rel_unit)) { |
... | ... |
@@ -52,7 +52,7 @@ HeatmapAnnotation = setClass("HeatmapAnnotation", |
52 | 52 |
# See `SingleAnnotation` for how to set colors. |
53 | 53 |
# -na_col Color for ``NA`` values in simple annotations. |
54 | 54 |
# -annotation_legend_param A list which contains parameters for annotation legends. See `color_mapping_legend,ColorMapping-method` for all possible options. |
55 |
-# -show_legend Whether show annotation legends. The value can be one single value or a vector which corresponds to simple annotations. |
|
55 |
+# -show_legend Whether show annotation legends. The value can be one single value or a vector. |
|
56 | 56 |
# -which Are these row annotations or column annotations? |
57 | 57 |
# -gp Graphic parameters for simple annotations (with ``fill`` parameter ignored). |
58 | 58 |
# -border border of single annotations. |
... | ... |
@@ -215,6 +215,10 @@ HeatmapAnnotation = function(..., |
215 | 215 |
if(length(show_legend) == 1) { |
216 | 216 |
show_legend = recycle_param(show_legend, simple_anno_name, TRUE) |
217 | 217 |
} |
218 |
+ # check length of show_legend |
|
219 |
+ if(length(show_legend) == length(anno_value_list) && !all(l_simple_anno)) { |
|
220 |
+ show_legend = show_legend[l_simple_anno] |
|
221 |
+ } |
|
218 | 222 |
|
219 | 223 |
###### normalize `heatmap_legend_param` ####### |
220 | 224 |
if(length(annotation_legend_param) == 0) { |
... | ... |
@@ -26,14 +26,16 @@ HeatmapAnnotation = setClass("HeatmapAnnotation", |
26 | 26 |
height = "ANY", |
27 | 27 |
gap = "ANY", |
28 | 28 |
subsetable = "logical", |
29 |
- extended = "ANY" |
|
29 |
+ extended = "ANY", |
|
30 |
+ param = "list" |
|
30 | 31 |
), |
31 | 32 |
prototype = list( |
32 | 33 |
anno_list = list(), |
33 | 34 |
which = "column", |
34 | 35 |
gap = unit(0, "mm"), |
35 | 36 |
subsetable = FALSE, |
36 |
- extended = unit(c(0, 0, 0, 0), "mm") |
|
37 |
+ extended = unit(c(0, 0, 0, 0), "mm"), |
|
38 |
+ param = list() |
|
37 | 39 |
), |
38 | 40 |
contains = "AdditiveUnit" |
39 | 41 |
) |
... | ... |
@@ -65,7 +67,7 @@ HeatmapAnnotation = setClass("HeatmapAnnotation", |
65 | 67 |
# -annotation_width Width of each annotation if annotations are row annotations. |
66 | 68 |
# -height Height of the whole column annotations. |
67 | 69 |
# -width Width of the whole heatmap annotations. |
68 |
-# -anno_simple_size Size of the simple annotation. |
|
70 |
+# -simple_anno_size Size of the simple annotation. |
|
69 | 71 |
# -simple_anno_size_adjust Whether also adjust the size of simple annotations when adjusting the whole heatmap annotation. |
70 | 72 |
# |
71 | 73 |
# == details |
... | ... |
@@ -109,12 +111,17 @@ HeatmapAnnotation = function(..., |
109 | 111 |
annotation_width = NULL, |
110 | 112 |
height = NULL, |
111 | 113 |
width = NULL, |
112 |
- anno_simple_size = ht_opt$anno_simple_size, |
|
114 |
+ simple_anno_size = ht_opt$simple_anno_size, |
|
113 | 115 |
simple_anno_size_adjust = FALSE |
114 | 116 |
) { |
115 | 117 |
|
116 | 118 |
dev.null() |
117 | 119 |
|
120 |
+ is_height_set = !missing(height) |
|
121 |
+ is_width_set = !missing(width) |
|
122 |
+ is_annotation_height_set = !missing(annotation_height) |
|
123 |
+ is_annotation_width_set = !missing(annotation_width) |
|
124 |
+ |
|
118 | 125 |
.ENV$current_annotation_which = NULL |
119 | 126 |
which = match.arg(which)[1] |
120 | 127 |
.ENV$current_annotation_which = which |
... | ... |
@@ -198,6 +205,10 @@ HeatmapAnnotation = function(..., |
198 | 205 |
n_simple_anno = sum(l_simple_anno) |
199 | 206 |
simple_anno_name = names(anno_value_list[l_simple_anno]) |
200 | 207 |
|
208 |
+ if("anno_simple_size" %in% names(anno_value_list)) { |
|
209 |
+ stop_wrap("Please use `simple_anno_size` as the argument.") |
|
210 |
+ } |
|
211 |
+ |
|
201 | 212 |
if(verbose) qqcat("in total there are @{length(anno_value_list)} annotations (@{n_simple_anno} simple annotations)\n") |
202 | 213 |
|
203 | 214 |
# normalize `show_legend` |
... | ... |
@@ -318,7 +329,7 @@ HeatmapAnnotation = function(..., |
318 | 329 |
arg_list$legend_param = annotation_legend_param[[i_simple + 1]] |
319 | 330 |
arg_list$value = anno_value_list[[ag]] |
320 | 331 |
arg_list$na_col = na_col |
321 |
- # arg_list$anno_simple_size = anno_simple_size |
|
332 |
+ arg_list$simple_anno_size = simple_anno_size |
|
322 | 333 |
if(missing(col)) { |
323 | 334 |
anno_list[[ag]] = do.call(SingleAnnotation, arg_list) |
324 | 335 |
} else { |
... | ... |
@@ -361,6 +372,8 @@ HeatmapAnnotation = function(..., |
361 | 372 |
|
362 | 373 |
|
363 | 374 |
if(is.null(gap)) gap = unit(0, "mm") |
375 |
+ if(identical(gap, 0)) gap = unit(0, "mm") |
|
376 |
+ if(!inherits(gap, "unit")) stop_wrap("`gap` needs to be a unit object.") |
|
364 | 377 |
|
365 | 378 |
# the nth gap does not really matter |
366 | 379 |
if(length(gap) == 1) { |
... | ... |
@@ -428,14 +441,20 @@ HeatmapAnnotation = function(..., |
428 | 441 |
})) |
429 | 442 |
} |
430 | 443 |
.Object@extended = extended |
444 |
+ .Object@param = list( |
|
445 |
+ simple_anno_size = simple_anno_size, |
|
446 |
+ simple_anno_size_adjust = simple_anno_size_adjust, |
|
447 |
+ is_height_set = is_height_set, |
|
448 |
+ is_width_set = is_width_set, |
|
449 |
+ is_annotation_height_set = is_annotation_height_set, |
|
450 |
+ is_annotation_width_set = is_annotation_width_set |
|
451 |
+ ) |
|
431 | 452 |
|
432 | 453 |
## adjust height/width if `width`/`annotation_width` is set |
433 | 454 |
if(which == "column") { |
434 |
- .Object = re_size(.Object, height = height, annotation_height = annotation_height, |
|
435 |
- anno_simple_size = anno_simple_size, simple_anno_size_adjust = simple_anno_size_adjust) |
|
455 |
+ .Object = re_size(.Object, height = height, annotation_height = annotation_height) |
|
436 | 456 |
} else { |
437 |
- .Object = re_size(.Object, width = width, annotation_width = annotation_width, |
|
438 |
- anno_simple_size = anno_simple_size, simple_anno_size_adjust = simple_anno_size_adjust) |
|
457 |
+ .Object = re_size(.Object, width = width, annotation_width = annotation_width) |
|
439 | 458 |
} |
440 | 459 |
|
441 | 460 |
return(.Object) |
... | ... |
@@ -1015,7 +1034,7 @@ length.HeatmapAnnotation = function(x) { |
1015 | 1034 |
# -annotation_width A vector of of annotation widths in `grid::unit` class. |
1016 | 1035 |
# -height The height of the complete heatmap annotation. |
1017 | 1036 |
# -width The width of the complete heatmap annotation. |
1018 |
-# -anno_simple_size The size of one line of the simple annotation. |
|
1037 |
+# -simple_anno_size The size of one line of the simple annotation. |
|
1019 | 1038 |
# -simple_anno_size_adjust Whether adjust the size of the simple annotation? |
1020 | 1039 |
# |
1021 | 1040 |
# == details |
... | ... |
@@ -1027,10 +1046,10 @@ length.HeatmapAnnotation = function(x) { |
1027 | 1046 |
# ``annotation_height`` are absolute units, ``height`` is ignored. |
1028 | 1047 |
# 2. If ``annotation_height`` contains non-absolute units, ``height`` also need to be set and the |
1029 | 1048 |
# non-absolute units should be set in a simple form such as 1:10 or ``unit(1, "null")``. |
1030 |
-# 3. ``anno_simple_size`` is only used when ``annotation_height`` is NULL. |
|
1049 |
+# 3. ``simple_anno_size`` is only used when ``annotation_height`` is NULL. |
|
1031 | 1050 |
# 4. If only ``height`` is set, non-simple annotation is adjusted while keeps simple anntation unchanged. |
1032 | 1051 |
# 5. If only ``height`` is set and all annotations are simple annotations, all anntations are adjusted, |
1033 |
-# and ``anno_simple_size`` is disabled. |
|
1052 |
+# and ``simple_anno_size`` is disabled. |
|
1034 | 1053 |
# 6. If ``simple_anno_size_adjust`` is ``FALSE``, the size of the simple annotations will not change. |
1035 | 1054 |
# |
1036 | 1055 |
setMethod(f = "re_size", |
... | ... |
@@ -1040,17 +1059,17 @@ setMethod(f = "re_size", |
1040 | 1059 |
annotation_width = NULL, |
1041 | 1060 |
height = NULL, |
1042 | 1061 |
width = NULL, |
1043 |
- anno_simple_size = ht_opt$anno_simple_size, |
|
1044 |
- simple_anno_size_adjust = NULL) { |
|
1062 |
+ simple_anno_size = object@param$simple_anno_size, |
|
1063 |
+ simple_anno_size_adjust = object@param$simple_anno_size_adjust) { |
|
1045 | 1064 |
|
1046 | 1065 |
if(object@which == "column") { |
1047 | 1066 |
if(!missing(width) || !missing(annotation_width)) { |
1048 |
- stop_wrap("Please use ComplexHeatmap:::width() directly") |
|
1067 |
+ stop_wrap("You cannot set the width of the column annotations.") |
|
1049 | 1068 |
} |
1050 | 1069 |
} |
1051 | 1070 |
if(object@which == "colrowumn") { |
1052 | 1071 |
if(!missing(height) || !missing(annotation_height)) { |
1053 |
- stop_wrap("Please use ComplexHeatmap:::height() directly") |
|
1072 |
+ stop_wrap("You cannot set the height of the row annotations.") |
|
1054 | 1073 |
} |
1055 | 1074 |
} |
1056 | 1075 |
|
... | ... |
@@ -1078,7 +1097,6 @@ setMethod(f = "re_size", |
1078 | 1097 |
return(object) |
1079 | 1098 |
} |
1080 | 1099 |
} |
1081 |
- |
|
1082 | 1100 |
if(which == "column") { |
1083 | 1101 |
if(is.null(height)) { |
1084 | 1102 |
is_size_set = FALSE |
... | ... |
@@ -1106,7 +1124,7 @@ setMethod(f = "re_size", |
1106 | 1124 |
if(length(object@anno_list) == 1 && !inherits(annotation_height, "unit")) { |
1107 | 1125 |
stop_wrap("When there is only one annotation, `annotation_height` should be set as a unit object.") |
1108 | 1126 |
} |
1109 |
- if(!inherits(height, "unit")) { |
|
1127 |
+ if(!inherits(height, "unit") || !object@param$is_height_set) { |
|
1110 | 1128 |
height = annotation_height[1] |
1111 | 1129 |
} |
1112 | 1130 |
if(!inherits(height, "unit")) { |
... | ... |
@@ -1151,7 +1169,7 @@ setMethod(f = "re_size", |
1151 | 1169 |
if(length(object@anno_list) == 1 && !inherits(annotation_width, "unit")) { |
1152 | 1170 |
stop_wrap("When there is only one annotation, `annotation_width` should be set as a unit object.") |
1153 | 1171 |
} |
1154 |
- if(!inherits(width, "unit")) { |
|
1172 |
+ if(!inherits(width, "unit") || !object@param$is_width_set) { |
|
1155 | 1173 |
width = annotation_width[1] |
1156 | 1174 |
} |
1157 | 1175 |
if(!inherits(width, "unit")) { |
... | ... |
@@ -1260,10 +1278,14 @@ setMethod(f = "re_size", |
1260 | 1278 |
} else { |
1261 | 1279 |
size = convertUnitFun(size, "mm", valueOnly = TRUE) |
1262 | 1280 |
anno_size = convertUnitFun(anno_size, "mm", valueOnly = TRUE) |
1263 |
- |
|
1264 |
- l_simple_anno = sapply(seq_len(n), function(i) { |
|
1265 |
- !is.null(object@anno_list[[i]]@color_mapping) |
|
1266 |
- }) |
|
1281 |
+ |
|
1282 |
+ if(simple_anno_size_adjust) { |
|
1283 |
+ l_simple_anno = rep(FALSE, n) |
|
1284 |
+ } else { |
|
1285 |
+ l_simple_anno = sapply(seq_len(n), function(i) { |
|
1286 |
+ !is.null(object@anno_list[[i]]@color_mapping) |
|
1287 |
+ }) |
|
1288 |
+ } |
|
1267 | 1289 |
|
1268 | 1290 |
if(all(l_simple_anno)) { |
1269 | 1291 |
anno_size2 = anno_size/sum(anno_size) * (size_adjusted - sum(gap)) |
... | ... |
@@ -1273,22 +1295,21 @@ setMethod(f = "re_size", |
1273 | 1295 |
|
1274 | 1296 |
anno_size2 = anno_size |
1275 | 1297 |
# size_adjusted = convertUnitFun(size_adjusted, "mm", valueOnly = TRUE) |
1276 |
- if(is.null(anno_simple_size)) { |
|
1277 |
- anno_simple_size = 5 |
|
1298 |
+ if(is.null(simple_anno_size)) { |
|
1299 |
+ simple_anno_size = 5 |
|
1278 | 1300 |
} else { |
1279 |
- anno_simple_size = convertUnitFun(anno_simple_size, "mm", valueOnly = TRUE) |
|
1301 |
+ simple_anno_size = convertUnitFun(simple_anno_size, "mm", valueOnly = TRUE) |
|
1280 | 1302 |
} |
1281 | 1303 |
if(size_adjusted <= sum(gap)) { |
1282 | 1304 |
stop_wrap(paste0(size_name, " you set is smaller than sum of gaps.")) |
1283 | 1305 |
} |
1284 | 1306 |
|
1285 | 1307 |
## fix the size of simple annotation and zoom function annotations |
1286 |
- ts = size_adjusted - sum(gap) - sum(anno_size[l_simple_anno]*anno_simple_size/5) |
|
1308 |
+ ts = size_adjusted - sum(gap) - sum(anno_size[l_simple_anno]) # total size excluding simple annotations and gap |
|
1287 | 1309 |
if(ts < 0) { |
1288 | 1310 |
stop_wrap(paste0(size_name, " you set is too small.")) |
1289 | 1311 |
} |
1290 | 1312 |
anno_size2[!l_simple_anno] = anno_size[!l_simple_anno]/sum(anno_size[!l_simple_anno]) * ts |
1291 |
- anno_size2[l_simple_anno] = anno_size[l_simple_anno]*anno_simple_size/5 |
|
1292 | 1313 |
|
1293 | 1314 |
size_adjusted = unit(size_adjusted, "mm") |
1294 | 1315 |
anno_size2 = unit(anno_size2, "mm") |
... | ... |
@@ -1041,7 +1041,7 @@ setMethod(f = "re_size", |
1041 | 1041 |
height = NULL, |
1042 | 1042 |
width = NULL, |
1043 | 1043 |
anno_simple_size = ht_opt$anno_simple_size, |
1044 |
- simple_anno_size_adjust = FALSE) { |
|
1044 |
+ simple_anno_size_adjust = NULL) { |
|
1045 | 1045 |
|
1046 | 1046 |
if(object@which == "column") { |
1047 | 1047 |
if(!missing(width) || !missing(annotation_width)) { |
... | ... |
@@ -1054,9 +1054,17 @@ setMethod(f = "re_size", |
1054 | 1054 |
} |
1055 | 1055 |
} |
1056 | 1056 |
|
1057 |
+ all_simple_annotation = all(sapply(object@anno_list, function(x) is_simple_annotation(x) || is_matrix_annotation(x))) |
|
1058 |
+ if(is.null(simple_anno_size_adjust)) { |
|
1059 |
+ if(all_simple_annotation) { |
|
1060 |
+ simple_anno_size_adjust = TRUE |
|
1061 |
+ } else { |
|
1062 |
+ simple_anno_size_adjust = FALSE |
|
1063 |
+ } |
|
1064 |
+ } |
|
1057 | 1065 |
which = object@which |
1058 | 1066 |
if(!simple_anno_size_adjust) { |
1059 |
- if(all(sapply(object@anno_list, function(x) is_simple_annotation(x) || is_matrix_annotation(x)))) { |
|
1067 |
+ if(all_simple_annotation) { |
|
1060 | 1068 |
if(which == "column") { |
1061 | 1069 |
height = sum(object@anno_size) + sum(object@gap) - object@gap[length(object@gap)] |
1062 | 1070 |
object@height = convertHeight(height, "mm") |
... | ... |
@@ -1064,6 +1072,9 @@ setMethod(f = "re_size", |
1064 | 1072 |
width = sum(object@anno_size) + sum(object@gap) - object@gap[length(object@gap)] |
1065 | 1073 |
object@width = convertWidth(width, "mm") |
1066 | 1074 |
} |
1075 |
+ if(ht_opt$verbose) { |
|
1076 |
+ message_wrap("`simple_anno_size_adjust` is set to FALSE and all annotations are simple annotations or matrix annotations, the heights of all annotations are not adjusted.") |
|
1077 |
+ } |
|
1067 | 1078 |
return(object) |
1068 | 1079 |
} |
1069 | 1080 |
} |
... | ... |
@@ -1083,6 +1094,11 @@ setMethod(f = "re_size", |
1083 | 1094 |
if(is.null(annotation_height)) { |
1084 | 1095 |
is_annotation_size_set = FALSE |
1085 | 1096 |
} else { |
1097 |
+ if(length(annotation_height) == 1) { |
|
1098 |
+ if(!inherits(annotation_height, "unit")) { |
|
1099 |
+ annotation_height = rep(annotation_height, length(object@anno_list)) |
|
1100 |
+ } |
|
1101 |
+ } |
|
1086 | 1102 |
if(length(annotation_height) == 1) { |
1087 | 1103 |
if(length(object@anno_list) > 1) { |
1088 | 1104 |
warning_wrap("`annotation_height` is set with length of one while with multiple annotations, `annotation_height` is treated as `height`.") |
... | ... |
@@ -1090,7 +1106,9 @@ setMethod(f = "re_size", |
1090 | 1106 |
if(length(object@anno_list) == 1 && !inherits(annotation_height, "unit")) { |
1091 | 1107 |
stop_wrap("When there is only one annotation, `annotation_height` should be set as a unit object.") |
1092 | 1108 |
} |
1093 |
- height = annotation_height[1] |
|
1109 |
+ if(!inherits(height, "unit")) { |
|
1110 |
+ height = annotation_height[1] |
|
1111 |
+ } |
|
1094 | 1112 |
if(!inherits(height, "unit")) { |
1095 | 1113 |
stop_wrap("`height` should be a `unit` object") |
1096 | 1114 |
} |
... | ... |
@@ -1121,6 +1139,11 @@ setMethod(f = "re_size", |
1121 | 1139 |
if(is.null(annotation_width)) { |
1122 | 1140 |
is_annotation_size_set = FALSE |
1123 | 1141 |
} else { |
1142 |
+ if(length(annotation_width) == 1) { |
|
1143 |
+ if(!inherits(annotation_width, "unit")) { |
|
1144 |
+ annotation_width = rep(annotation_width, length(object@anno_list)) |
|
1145 |
+ } |
|
1146 |
+ } |
|
1124 | 1147 |
if(length(annotation_width) == 1) { |
1125 | 1148 |
if(length(object@anno_list) > 1) { |
1126 | 1149 |
warning_wrap("`annotation_width` is set with length of one while with multiple annotations, `annotation_width` is treated as `width`.") |
... | ... |
@@ -1128,7 +1151,9 @@ setMethod(f = "re_size", |
1128 | 1151 |
if(length(object@anno_list) == 1 && !inherits(annotation_width, "unit")) { |
1129 | 1152 |
stop_wrap("When there is only one annotation, `annotation_width` should be set as a unit object.") |
1130 | 1153 |
} |
1131 |
- width = annotation_width[1] |
|
1154 |
+ if(!inherits(width, "unit")) { |
|
1155 |
+ width = annotation_width[1] |
|
1156 |
+ } |
|
1132 | 1157 |
if(!inherits(width, "unit")) { |
1133 | 1158 |
stop_wrap("`width` should be a `unit` object") |
1134 | 1159 |
} |
... | ... |
@@ -58,7 +58,7 @@ HeatmapAnnotation = setClass("HeatmapAnnotation", |
58 | 58 |
# -show_annotation_name Whether show annotation names? For column annotation, annotation names are drawn either on the left |
59 | 59 |
# or the right, and for row annotations, names are draw either on top or at the bottom. The value can be a vector. |
60 | 60 |
# -annotation_name_gp Graphic parameters for anntation names. Graphic paramters can be vectors. |
61 |
-# -annotation_name_offset Offset to the annotations, `grid::unit` object. The value can be a vector. |
|
61 |
+# -annotation_name_offset Offset to the annotation names, a `grid::unit` object. The value can be a vector. |
|
62 | 62 |
# -annotation_name_side Side of the annotation names. |
63 | 63 |
# -annotation_name_rot Rotation of the annotation names, it can only take values in ``c(00, 90, 180, 270)``. The value can be a vector. |
64 | 64 |
# -annotation_height Height of each annotation if annotations are column annotations. |
... | ... |
@@ -1085,7 +1085,10 @@ setMethod(f = "re_size", |
1085 | 1085 |
} else { |
1086 | 1086 |
if(length(annotation_height) == 1) { |
1087 | 1087 |
if(length(object@anno_list) > 1) { |
1088 |
- warning_wrap("`annotation_height` is set with length of one while with multiplt annotations, `annotation_height` is treated as `height`.") |
|
1088 |
+ warning_wrap("`annotation_height` is set with length of one while with multiple annotations, `annotation_height` is treated as `height`.") |
|
1089 |
+ } |
|
1090 |
+ if(length(object@anno_list) == 1 && !inherits(annotation_height, "unit")) { |
|
1091 |
+ stop_wrap("When there is only one annotation, `annotation_height` should be set as a unit object.") |
|
1089 | 1092 |
} |
1090 | 1093 |
height = annotation_height[1] |
1091 | 1094 |
if(!inherits(height, "unit")) { |
... | ... |
@@ -1120,7 +1123,10 @@ setMethod(f = "re_size", |
1120 | 1123 |
} else { |
1121 | 1124 |
if(length(annotation_width) == 1) { |
1122 | 1125 |
if(length(object@anno_list) > 1) { |
1123 |
- warning_wrap("`annotation_width` is set with length of one while with multiplt annotations, `annotation_width` is treated as `width`.") |
|
1126 |
+ warning_wrap("`annotation_width` is set with length of one while with multiple annotations, `annotation_width` is treated as `width`.") |
|
1127 |
+ } |
|
1128 |
+ if(length(object@anno_list) == 1 && !inherits(annotation_width, "unit")) { |
|
1129 |
+ stop_wrap("When there is only one annotation, `annotation_width` should be set as a unit object.") |
|
1124 | 1130 |
} |
1125 | 1131 |
width = annotation_width[1] |
1126 | 1132 |
if(!inherits(width, "unit")) { |
... | ... |
@@ -553,6 +553,8 @@ setMethod(f = "get_legend_param_list", |
553 | 553 |
# -n Total number of slices. |
554 | 554 |
# -... Pass to `grid::viewport` which contains all the annotations. |
555 | 555 |
# -test Is it in test mode? The value can be logical or a text which is plotted as the title of plot. |
556 |
+# -anno_mark_param It contains specific parameters for drawing `anno_mark` and pass to the |
|
557 |
+# `draw,SingleAnnotation-method`. |
|
556 | 558 |
# |
557 | 559 |
# == value |
558 | 560 |
# No value is returned. |
... | ... |
@@ -563,7 +565,7 @@ setMethod(f = "get_legend_param_list", |
563 | 565 |
setMethod(f = "draw", |
564 | 566 |
signature = "HeatmapAnnotation", |
565 | 567 |
definition = function(object, index, k = 1, n = 1, ..., |
566 |
- test = FALSE) { |
|
568 |
+ test = FALSE, anno_mark_param = list()) { |
|
567 | 569 |
|
568 | 570 |
which = object@which |
569 | 571 |
n_anno = length(object@anno_list) |
... | ... |
@@ -609,21 +611,23 @@ setMethod(f = "draw", |
609 | 611 |
for(i in seq_len(n_anno)) { |
610 | 612 |
pushViewport(viewport(y = sum(anno_size[seq(i, n_anno)]) + sum(gap[seq(i, n_anno)]) - gap[n_anno], |
611 | 613 |
height = anno_size[i], just = c("center", "top"))) |
612 |
- oe = try(draw(object@anno_list[[i]], index, k, n)) |
|
613 |
- if(inherits(oe, "try-error")) { |
|
614 |
- cat("Error when drawing annotation '", object@anno_list[[i]]@name, "'\n", sep = "") |
|
615 |
- stop_wrap(oe) |
|
616 |
- } |
|
614 |
+ draw(object@anno_list[[i]], index, k, n, anno_mark_param = anno_mark_param) |
|
615 |
+ # oe = try(draw(object@anno_list[[i]], index, k, n)) |
|
616 |
+ # if(inherits(oe, "try-error")) { |
|
617 |
+ # cat("Error when drawing annotation '", object@anno_list[[i]]@name, "'\n", sep = "") |
|
618 |
+ # stop_wrap(oe) |
|
619 |
+ # } |
|
617 | 620 |
upViewport() |
618 | 621 |
} |
619 | 622 |
} else if(which == "row") { |
620 | 623 |
for(i in seq_len(n_anno)) { |
621 | 624 |
pushViewport(viewport(x = sum(anno_size[seq_len(i)]) + sum(gap[seq_len(i)]) - gap[i], width = anno_size[i], just = c("right", "center"))) |
622 |
- oe = try(draw(object@anno_list[[i]], index, k, n)) |
|
623 |
- if(inherits(oe, "try-error")) { |
|
624 |
- cat("Error when drawing annotation '", object@anno_list[[i]]@name, "'\n", sep = "") |
|
625 |
- stop_wrap(oe) |
|
626 |
- } |
|
625 |
+ draw(object@anno_list[[i]], index, k, n, anno_mark_param = anno_mark_param) |
|
626 |
+ # oe = try(draw(object@anno_list[[i]], index, k, n)) |
|
627 |
+ # if(inherits(oe, "try-error")) { |
|
628 |
+ # cat("Error when drawing annotation '", object@anno_list[[i]]@name, "'\n", sep = "") |
|
629 |
+ # stop_wrap(oe) |
|
630 |
+ # } |
|
627 | 631 |
upViewport() |
628 | 632 |
} |
629 | 633 |
} |
... | ... |
@@ -913,6 +917,10 @@ names.HeatmapAnnotation = function(x) { |
913 | 917 |
return(x) |
914 | 918 |
} |
915 | 919 |
|
920 |
+anno_type = function(ha) { |
|
921 |
+ sapply(ha@anno_list, function(x) x@fun@fun_name) |
|
922 |
+} |
|
923 |
+ |
|
916 | 924 |
|
917 | 925 |
# == title |
918 | 926 |
# Subset the HeatmapAnnotation object |
... | ... |
@@ -1075,8 +1075,23 @@ setMethod(f = "re_size", |
1075 | 1075 |
if(is.null(annotation_height)) { |
1076 | 1076 |
is_annotation_size_set = FALSE |
1077 | 1077 |
} else { |
1078 |
- is_annotation_size_set = TRUE |
|
1079 |
- annotation_size_adjusted = annotation_height |
|
1078 |
+ if(length(annotation_height) == 1) { |
|
1079 |
+ if(length(object@anno_list) > 1) { |
|
1080 |
+ warning_wrap("`annotation_height` is set with length of one while with multiplt annotations, `annotation_height` is treated as `height`.") |
|
1081 |
+ } |
|
1082 |
+ height = annotation_height[1] |
|
1083 |
+ if(!inherits(height, "unit")) { |
|
1084 |
+ stop_wrap("`height` should be a `unit` object") |
|
1085 |
+ } |
|
1086 |
+ if(!is_abs_unit(height)) { |
|
1087 |
+ stop_wrap("`height` should be an absolute unit.") |
|
1088 |
+ } |
|
1089 |
+ is_size_set = TRUE |
|
1090 |
+ is_annotation_size_set = FALSE |
|
1091 |
+ } else { |
|
1092 |
+ is_annotation_size_set = TRUE |
|
1093 |
+ annotation_size_adjusted = annotation_height |
|
1094 |
+ } |
|
1080 | 1095 |
} |
1081 | 1096 |
size_adjusted = height |
1082 | 1097 |
size_name = "height" |
... | ... |
@@ -1095,8 +1110,23 @@ setMethod(f = "re_size", |
1095 | 1110 |
if(is.null(annotation_width)) { |
1096 | 1111 |
is_annotation_size_set = FALSE |
1097 | 1112 |
} else { |
1098 |
- is_annotation_size_set = TRUE |
|
1099 |
- annotation_size_adjusted = annotation_width |
|
1113 |
+ if(length(annotation_width) == 1) { |
|
1114 |
+ if(length(object@anno_list) > 1) { |
|
1115 |
+ warning_wrap("`annotation_width` is set with length of one while with multiplt annotations, `annotation_width` is treated as `width`.") |
|
1116 |
+ } |
|
1117 |
+ width = annotation_width[1] |
|
1118 |
+ if(!inherits(width, "unit")) { |
|
1119 |
+ stop_wrap("`width` should be a `unit` object") |
|
1120 |
+ } |
|
1121 |
+ if(!is_abs_unit(width)) { |
|
1122 |
+ stop_wrap("`width` should be an absolute unit.") |
|
1123 |
+ } |
|
1124 |
+ is_size_set = TRUE |
|
1125 |
+ is_annotation_size_set = FALSE |
|
1126 |
+ } else { |
|
1127 |
+ is_annotation_size_set = TRUE |
|
1128 |
+ annotation_size_adjusted = annotation_width |
|
1129 |
+ } |
|
1100 | 1130 |
} |
1101 | 1131 |
size_adjusted = width |
1102 | 1132 |
size_name = "width" |
... | ... |
@@ -243,7 +243,7 @@ HeatmapAnnotation = function(..., |
243 | 243 |
an = names(anno_value_list) |
244 | 244 |
show_annotation_name = recycle_param(show_annotation_name, an, TRUE) |
245 | 245 |
annotation_name_side = recycle_param(annotation_name_side, an, ifelse(which == "column", "right", "bottom")) |
246 |
- if(inherits(annotation_name_offset, "unit")) annotation_name_offset = unit_to_str(annotation_name_offset) |
|
246 |
+ if(inherits(annotation_name_offset, "unit")) annotation_name_offset = to_unit_str(annotation_name_offset) |
|
247 | 247 |
annotation_name_offset = recycle_param(annotation_name_offset, an, NULL, as.list = TRUE) |
248 | 248 |
annotation_name_rot = recycle_param(annotation_name_rot, an, NULL, as.list = TRUE) |
249 | 249 |
if(missing(border)) { |
... | ... |
@@ -101,9 +101,9 @@ HeatmapAnnotation = function(..., |
101 | 101 |
|
102 | 102 |
show_annotation_name = TRUE, |
103 | 103 |
annotation_name_gp = gpar(), |
104 |
- annotation_name_offset = unit(1, "mm"), |
|
104 |
+ annotation_name_offset = NULL, |
|
105 | 105 |
annotation_name_side = ifelse(which == "column", "right", "bottom"), |
106 |
- annotation_name_rot = ifelse(which == "column", 0, 90), |
|
106 |
+ annotation_name_rot = NULL, |
|
107 | 107 |
|
108 | 108 |
annotation_height = NULL, |
109 | 109 |
annotation_width = NULL, |
... | ... |
@@ -242,9 +242,10 @@ HeatmapAnnotation = function(..., |
242 | 242 |
|
243 | 243 |
an = names(anno_value_list) |
244 | 244 |
show_annotation_name = recycle_param(show_annotation_name, an, TRUE) |
245 |
- annotation_name_offset = recycle_param(annotation_name_offset, an, TRUE) |
|
246 |
- annotation_name_side = recycle_param(annotation_name_side, an, TRUE) |
|
247 |
- annotation_name_rot = recycle_param(annotation_name_rot, an, TRUE) |
|
245 |
+ annotation_name_side = recycle_param(annotation_name_side, an, ifelse(which == "column", "right", "bottom")) |
|
246 |
+ if(inherits(annotation_name_offset, "unit")) annotation_name_offset = unit_to_str(annotation_name_offset) |
|
247 |
+ annotation_name_offset = recycle_param(annotation_name_offset, an, NULL, as.list = TRUE) |
|
248 |
+ annotation_name_rot = recycle_param(annotation_name_rot, an, NULL, as.list = TRUE) |
|
248 | 249 |
if(missing(border)) { |
249 | 250 |
if(!is.null(ht_opt$annotation_border)) border = ht_opt$annotation_border |
250 | 251 |
} |
... | ... |
@@ -296,16 +297,11 @@ HeatmapAnnotation = function(..., |
296 | 297 |
arg_list = list(name = ag, which = which, |
297 | 298 |
show_name = show_annotation_name[i_anno], |
298 | 299 |
name_gp = subset_gp(annotation_name_gp, i_anno), |
299 |
- name_offset = annotation_name_offset[i_anno], |
|
300 |
+ name_offset = annotation_name_offset[[i_anno]], |
|
300 | 301 |
name_side = annotation_name_side[i_anno], |
301 |
- name_rot = annotation_name_rot[i_anno], |
|
302 |
+ name_rot = annotation_name_rot[[i_anno]], |
|
302 | 303 |
border = border[i_anno]) |
303 |
- # if(!is_name_offset_called) { |
|
304 |
- # arg_list$name_rot = NULL |
|
305 |
- # } |
|
306 |
- # if(!is_name_rot_called) { |
|
307 |
- # arg_list$name_offset = NULL |
|
308 |
- # } |
|
304 |
+ |
|
309 | 305 |
if(inherits(anno_value_list[[ag]], c("function", "AnnotationFunction"))) { |
310 | 306 |
arg_list$fun = anno_value_list[[ag]] |
311 | 307 |
if(inherits(anno_value_list[[ag]], "function")) { |
... | ... |
@@ -818,7 +818,17 @@ setMethod(f = "add_heatmap", |
818 | 818 |
# ha |
819 | 819 |
c.HeatmapAnnotation = function(..., gap = unit(0, "mm")) { |
820 | 820 |
anno_list = list(...) |
821 |
+ if(length(anno_list) == 1) { |
|
822 |
+ return(anno_list[[1]]) |
|
823 |
+ } |
|
824 |
+ # remove NULL |
|
825 |
+ anno_list = anno_list[ !sapply(anno_list, is.null) ] |
|
826 |
+ if(length(anno_list) == 1) { |
|
827 |
+ return(anno_list[[1]]) |
|
828 |
+ } |
|
829 |
+ |
|
821 | 830 |
n = length(anno_list) |
831 |
+ |
|
822 | 832 |
if(length(unique(sapply(anno_list, function(x) x@which))) != 1) { |
823 | 833 |
stop_wrap("All annotations should be all row annotation or all column annotation.") |
824 | 834 |
} |
... | ... |
@@ -300,12 +300,12 @@ HeatmapAnnotation = function(..., |
300 | 300 |
name_side = annotation_name_side[i_anno], |
301 | 301 |
name_rot = annotation_name_rot[i_anno], |
302 | 302 |
border = border[i_anno]) |
303 |
- if(!is_name_offset_called) { |
|
304 |
- arg_list$name_rot = NULL |
|
305 |
- } |
|
306 |
- if(!is_name_rot_called) { |
|
307 |
- arg_list$name_offset = NULL |
|
308 |
- } |
|
303 |
+ # if(!is_name_offset_called) { |
|
304 |
+ # arg_list$name_rot = NULL |
|
305 |
+ # } |
|
306 |
+ # if(!is_name_rot_called) { |
|
307 |
+ # arg_list$name_offset = NULL |
|
308 |
+ # } |
|
309 | 309 |
if(inherits(anno_value_list[[ag]], c("function", "AnnotationFunction"))) { |
310 | 310 |
arg_list$fun = anno_value_list[[ag]] |
311 | 311 |
if(inherits(anno_value_list[[ag]], "function")) { |
... | ... |
@@ -348,8 +348,22 @@ HeatmapAnnotation = function(..., |
348 | 348 |
} |
349 | 349 |
} |
350 | 350 |
|
351 |
+ |
|
351 | 352 |
n_total_anno = length(anno_list) |
352 | 353 |
|
354 |
+ ## check whether anno_list contains zoomed anno_empty |
|
355 |
+ if(n_total_anno > 1) { |
|
356 |
+ for(i in seq_len(n_total_anno)) { |
|
357 |
+ anno = anno_list[[i]]@fun |
|
358 |
+ if(identical(anno@fun_name, "anno_empty")) { |
|
359 |
+ if(anno@var_env$zoom) { |
|
360 |
+ stop_wrap("You set `zoom = TRUE` in `anno_empty()` for the empty annotation. The HeatmapAnnotation object only allows to contain one single annotation if it is a zoomed empty annotation.") |
|
361 |
+ } |
|
362 |
+ } |
|
363 |
+ } |
|
364 |
+ } |
|
365 |
+ |
|
366 |
+ |
|
353 | 367 |
if(is.null(gap)) gap = unit(0, "mm") |
354 | 368 |
|
355 | 369 |
# the nth gap does not really matter |
... | ... |
@@ -559,6 +573,7 @@ setMethod(f = "draw", |
559 | 573 |
n_anno = length(object@anno_list) |
560 | 574 |
anno_size = object@anno_size |
561 | 575 |
gap = object@gap |
576 |
+ vp_param = list(...) |
|
562 | 577 |
|
563 | 578 |
if(is.character(test)) { |
564 | 579 |
test2 = TRUE |
... | ... |
@@ -572,7 +587,7 @@ setMethod(f = "draw", |
572 | 587 |
if(which == "column") pushViewport(viewport(width = unit(1, "npc") - unit(3, "cm"), height = object@height)) |
573 | 588 |
if(which == "row") pushViewport(viewport(height = unit(1, "npc") - unit(3, "cm"), width = object@width)) |
574 | 589 |
} else { |
575 |
- pushViewport(viewport(...)) |
|
590 |
+ pushViewport(do.call(viewport, vp_param)) |
|
576 | 591 |
} |
577 | 592 |
|