Commit id: 6cf15a1b2514d9c86295206a55c9d5efadc00f70
check row orders
git-svn-id: https://hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/ComplexHeatmap@105276 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -76,6 +76,7 @@ Heatmap = setClass("Heatmap", |
76 | 76 |
row_hclust_list = "list", # one or more row clusters |
77 | 77 |
row_hclust_param = "list", # parameters for row cluster |
78 | 78 |
row_order_list = "list", |
79 |
+ row_order = "numeric", |
|
79 | 80 |
|
80 | 81 |
column_hclust = "ANY", |
81 | 82 |
column_hclust_param = "list", # parameters for column cluster |
... | ... |
@@ -235,6 +236,10 @@ Heatmap = function(matrix, col, name, na_col = "grey", rect_gp = gpar(col = NA), |
235 | 236 |
} |
236 | 237 |
} |
237 | 238 |
|
239 |
+ if(is.null(width)) { |
|
240 |
+ .Object@heatmap_param$width = ncol(matrix) |
|
241 |
+ } |
|
242 |
+ |
|
238 | 243 |
if(ncol(matrix) == 0) { |
239 | 244 |
.Object@heatmap_param$show_heatmap_legend = FALSE |
240 | 245 |
.Object@heatmap_param$width = unit(0, "null") |
... | ... |
@@ -362,10 +367,11 @@ Heatmap = function(matrix, col, name, na_col = "grey", rect_gp = gpar(col = NA), |
362 | 367 |
.Object@row_hclust_param$width = row_hclust_width + unit(1, "mm") # append the gap |
363 | 368 |
.Object@row_hclust_param$show = show_row_hclust |
364 | 369 |
.Object@row_hclust_param$gp = check_gp(row_hclust_gp) |
370 |
+ .Object@row_order_list = list() # default order |
|
365 | 371 |
if(is.null(row_order)) { |
366 |
- .Object@row_order_list = list(seq_len(nrow(matrix))) # default order |
|
367 |
- } else { |
|
368 |
- .Object@row_order_list = list(row_order) |
|
372 |
+ .Object@row_order = seq_len(nrow(matrix)) |
|
373 |
+ } else { |
|
374 |
+ .Object@row_order = row_order |
|
369 | 375 |
} |
370 | 376 |
|
371 | 377 |
if(inherits(cluster_columns, "dendrogram") || inherits(cluster_columns, "hclust")) { |
... | ... |
@@ -457,7 +463,6 @@ Heatmap = function(matrix, col, name, na_col = "grey", rect_gp = gpar(col = NA), |
457 | 463 |
# |
458 | 464 |
# == param |
459 | 465 |
# -object a `Heatmap-class` object. |
460 |
-# -order a pre-defined order. |
|
461 | 466 |
# |
462 | 467 |
# == details |
463 | 468 |
# The function will fill or adjust ``column_hclust`` and ``column_order`` slots. |
... | ... |
@@ -472,17 +477,14 @@ Heatmap = function(matrix, col, name, na_col = "grey", rect_gp = gpar(col = NA), |
472 | 477 |
# |
473 | 478 |
setMethod(f = "make_column_cluster", |
474 | 479 |
signature = "Heatmap", |
475 |
- definition = function(object, order = NULL) { |
|
480 |
+ definition = function(object) { |
|
476 | 481 |
|
477 | 482 |
mat = object@matrix |
478 | 483 |
distance = object@column_hclust_param$distance |
479 | 484 |
method = object@column_hclust_param$method |
485 |
+ order = object@column_order |
|
480 | 486 |
|
481 |
- if(!object@column_hclust_param$cluster && is.null(order)) { |
|
482 |
- order = seq_len(ncol(mat)) |
|
483 |
- } |
|
484 |
- |
|
485 |
- if(is.null(order) || object@column_hclust_param$cluster) { |
|
487 |
+ if(object@column_hclust_param$cluster) { |
|
486 | 488 |
if(!is.null(object@column_hclust_param$obj)) { |
487 | 489 |
object@column_hclust = object@column_hclust_param$obj |
488 | 490 |
} else if(!is.null(object@column_hclust_param$fun)) { |
... | ... |
@@ -490,7 +492,7 @@ setMethod(f = "make_column_cluster", |
490 | 492 |
} else { |
491 | 493 |
object@column_hclust = hclust(get_dist(t(mat), distance), method = method) |
492 | 494 |
} |
493 |
- column_order = get_hclust_order(object@column_hclust) |
|
495 |
+ column_order = get_hclust_order(object@column_hclust) # we don't need the pre-defined orders |
|
494 | 496 |
} else { |
495 | 497 |
column_order = order |
496 | 498 |
} |
... | ... |
@@ -511,9 +513,6 @@ setMethod(f = "make_column_cluster", |
511 | 513 |
# |
512 | 514 |
# == param |
513 | 515 |
# -object a `Heatmap-class` object. |
514 |
-# -order a pre-defined order. |
|
515 |
-# -km if apply k-means clustering on rows, number of clusters. |
|
516 |
-# -split a vector or a data frame by which the rows are be split. |
|
517 | 516 |
# |
518 | 517 |
# == details |
519 | 518 |
# The function will fill or adjust ``row_hclust_list``, ``row_order_list``, ``row_title`` and ``matrix_param`` slots. |
... | ... |
@@ -530,18 +529,16 @@ setMethod(f = "make_column_cluster", |
530 | 529 |
# |
531 | 530 |
setMethod(f = "make_row_cluster", |
532 | 531 |
signature = "Heatmap", |
533 |
- definition = function(object, order = unlist(object@row_order_list), km = object@matrix_param$km, |
|
534 |
- split = object@matrix_param$split) { |
|
532 |
+ definition = function(object) { |
|
535 | 533 |
|
536 | 534 |
mat = object@matrix |
537 | 535 |
distance = object@row_hclust_param$distance |
538 | 536 |
method = object@row_hclust_param$method |
537 |
+ order = object@row_order # pre-defined row order |
|
538 |
+ km = object@matrix_param$km |
|
539 |
+ split = object@matrix_param$split |
|
539 | 540 |
|
540 |
- if(!object@row_hclust_param$cluster && is.null(order)) { |
|
541 |
- order = seq_len(nrow(mat)) |
|
542 |
- } |
|
543 |
- |
|
544 |
- if(is.null(order) || object@row_hclust_param$cluster) { |
|
541 |
+ if(object@row_hclust_param$cluster) { |
|
545 | 542 |
|
546 | 543 |
if(!is.null(object@row_hclust_param$obj)) { |
547 | 544 |
if(km > 1) { |
... | ... |
@@ -555,7 +552,7 @@ setMethod(f = "make_row_cluster", |
555 | 552 |
return(object) |
556 | 553 |
} |
557 | 554 |
|
558 |
- row_order = seq_len(nrow(mat)) # default row order |
|
555 |
+ row_order = seq_len(nrow(mat)) |
|
559 | 556 |
} else { |
560 | 557 |
row_order = order |
561 | 558 |
} |
... | ... |
@@ -570,7 +567,7 @@ setMethod(f = "make_row_cluster", |
570 | 567 |
meanmat = as.matrix(as.data.frame(meanmat)) |
571 | 568 |
hc = hclust(dist(t(meanmat))) |
572 | 569 |
cluster2 = numeric(length(cluster)) |
573 |
- for(i in seq_along(hc$order)) { |
|
570 |
+ for(i in hc$order) { |
|
574 | 571 |
cluster2[cluster == hc$order[i]] = i |
575 | 572 |
} |
576 | 573 |
cluster2 = paste0("cluster", cluster2) |
... | ... |
@@ -600,7 +597,7 @@ setMethod(f = "make_row_cluster", |
600 | 597 |
row_levels = unique(split) |
601 | 598 |
for(i in seq_along(row_levels)) { |
602 | 599 |
l = split == row_levels[i] |
603 |
- row_order_list[[i]] = nature_order[l][ order(row_order[l]) ] |
|
600 |
+ row_order_list[[i]] = intersect(row_order, which(l)) |
|
604 | 601 |
} |
605 | 602 |
|
606 | 603 |
if(!is.null(object@row_title_param$combined_name_fun)) { |
... | ... |
@@ -609,7 +606,7 @@ setMethod(f = "make_row_cluster", |
609 | 606 |
} |
610 | 607 |
|
611 | 608 |
# make hclust in each slice |
612 |
- if(is.null(order) || object@row_hclust_param$cluster) { |
|
609 |
+ if(object@row_hclust_param$cluster) { |
|
613 | 610 |
row_hclust_list = rep(list(NULL), length(row_order_list)) |
614 | 611 |
for(i in seq_along(row_order_list)) { |
615 | 612 |
submat = mat[ row_order_list[[i]], , drop = FALSE] |
... | ... |
@@ -1413,10 +1410,7 @@ setMethod(f = "draw", |
1413 | 1410 |
# |
1414 | 1411 |
# == param |
1415 | 1412 |
# -object a `Heatmap-class` object. |
1416 |
-# -row_order orders of rows, pass to `make_row_cluster,Heatmap-method`. Because if more than one heatmaps |
|
1417 |
-# are drawn by columns, the order of some heatmap will be adjusted by one certain heatmap, this |
|
1418 |
-# argument is used to pass a pre-defined row order. |
|
1419 |
-# -split how to split rows in the matrix, passing to `make_row_cluster,Heatmap-method`. |
|
1413 |
+# -process_rows whether process rows of the heatmap |
|
1420 | 1414 |
# |
1421 | 1415 |
# == detail |
1422 | 1416 |
# The preparation of the heatmap includes following steps: |
... | ... |
@@ -1435,10 +1429,10 @@ setMethod(f = "draw", |
1435 | 1429 |
# |
1436 | 1430 |
setMethod(f = "prepare", |
1437 | 1431 |
signature = "Heatmap", |
1438 |
- definition = function(object, row_order = NULL, split = object@matrix_param$split) { |
|
1432 |
+ definition = function(object, process_rows = TRUE) { |
|
1439 | 1433 |
|
1440 |
- if(object@row_hclust_param$cluster || !is.null(split)) { |
|
1441 |
- object = make_row_cluster(object, order = row_order, split = split) |
|
1434 |
+ if(process_rows) { |
|
1435 |
+ object = make_row_cluster(object) |
|
1442 | 1436 |
} |
1443 | 1437 |
if(object@column_hclust_param$cluster) object = make_column_cluster(object) |
1444 | 1438 |
|
... | ... |
@@ -177,7 +177,6 @@ setMethod(f = "add_heatmap", |
177 | 177 |
# -show_annotation_legend whether show annotation legend. |
178 | 178 |
# -annotation_legend_list a list of self-defined legend, should be wrapped into `grid::grob` objects. |
179 | 179 |
# -gap gap between heatmaps, should be a `grid::unit` object. |
180 |
-# -auto_adjust auto adjust if the number of heatmap is larger than one. |
|
181 | 180 |
# -main_heatmap name or index for the main heatmap |
182 | 181 |
# -row_hclust_side if auto adjust, where to put the row dendrograms for the main heatmap |
183 | 182 |
# -row_sub_title_side if auto adjust, where to put sub row titles for the main heatmap |
... | ... |
@@ -206,7 +205,7 @@ setMethod(f = "make_layout", |
206 | 205 |
show_heatmap_legend = TRUE, |
207 | 206 |
annotation_legend_side = c("right", "left", "bottom", "top"), |
208 | 207 |
show_annotation_legend = TRUE, annotation_legend_list = list(), |
209 |
- gap = unit(3, "mm"), auto_adjust = TRUE, |
|
208 |
+ gap = unit(3, "mm"), |
|
210 | 209 |
main_heatmap = which(sapply(object@ht_list, inherits, "Heatmap"))[1], |
211 | 210 |
row_hclust_side = c("original", "left", "right"), |
212 | 211 |
row_sub_title_side = c("original", "left", "right"), ...) { |
... | ... |
@@ -233,8 +232,8 @@ setMethod(f = "make_layout", |
233 | 232 |
} |
234 | 233 |
} else if(length(gap) == n - 1) { |
235 | 234 |
gap = unit.c(gap, unit(1, "null")) |
236 |
- } else if(length(gap) != n) { |
|
237 |
- stop(paste0("length of `gap` can only be 1 or ", n-1, " or ", n, ".")) |
|
235 |
+ } else if(length(gap) > n) { |
|
236 |
+ stop(paste0("length of `gap` can only be 1 or ", n-1, ".")) |
|
238 | 237 |
} |
239 | 238 |
} else { |
240 | 239 |
if(!is.unit(gap)) { |
... | ... |
@@ -256,133 +255,67 @@ setMethod(f = "make_layout", |
256 | 255 |
} |
257 | 256 |
} |
258 | 257 |
|
259 |
- # else if the zero-column matrix is in the middle, set the front gap to 0 |
|
260 |
- |
|
261 |
- if(auto_adjust) { |
|
262 |
- ht_main = object@ht_list[[i_main]] |
|
263 |
- ht_main = make_row_cluster(ht_main, order = ht_main@row_order_list[[1]]) |
|
264 |
- |
|
265 |
- row_order = unlist(ht_main@row_order_list) |
|
266 |
- split = ht_main@matrix_param$split |
|
267 |
- |
|
268 |
- row_hclust_side = match.arg(row_hclust_side)[1] |
|
269 |
- row_sub_title_side = match.arg(row_sub_title_side)[1] |
|
270 |
- |
|
271 |
- if(row_hclust_side == "left" || row_sub_title_side == "left") { |
|
272 |
- # if the first one is a HeatmapAnnotation object |
|
273 |
- if(inherits(object@ht_list[[1]], "HeatmapAnnotation")) { |
|
274 |
- object = Heatmap(matrix(nrow = nr, ncol = 0)) + object |
|
275 |
- gap = unit.c(unit(0, "null"), gap) |
|
276 |
- i_main = i_main + 1 |
|
277 |
- } |
|
278 |
- |
|
258 |
+ ######## auto adjust ########## |
|
259 |
+ ht_main = object@ht_list[[i_main]] |
|
260 |
+ ht_main = make_row_cluster(ht_main) # with pre-defined order |
|
261 |
+ object@ht_list[[i_main]] = ht_main |
|
262 |
+ |
|
263 |
+ row_hclust_side = match.arg(row_hclust_side)[1] |
|
264 |
+ row_sub_title_side = match.arg(row_sub_title_side)[1] |
|
265 |
+ |
|
266 |
+ if(row_hclust_side == "left" || row_sub_title_side == "left") { |
|
267 |
+ # if the first one is a HeatmapAnnotation object |
|
268 |
+ # add a heatmap with zero column so that we can put titles and hclust on the most left |
|
269 |
+ if(inherits(object@ht_list[[1]], "HeatmapAnnotation")) { |
|
270 |
+ object = Heatmap(matrix(nrow = nr, ncol = 0)) + object |
|
271 |
+ gap = unit.c(unit(0, "null"), gap) |
|
272 |
+ i_main = i_main + 1 |
|
279 | 273 |
} |
274 |
+ |
|
275 |
+ } |
|
280 | 276 |
|
281 |
- if(row_hclust_side == "right" || row_sub_title_side == "right") { |
|
282 |
- # if the last one is a HeatmapAnnotation object |
|
283 |
- if(inherits(object@ht_list[[ length(object@ht_list) ]], "HeatmapAnnotation")) { |
|
284 |
- object = object + Heatmap(matrix(nrow = nr, ncol = 0)) |
|
285 |
- gap = unit.c(gap, unit(0, "null")) |
|
286 |
- } |
|
277 |
+ if(row_hclust_side == "right" || row_sub_title_side == "right") { |
|
278 |
+ # if the last one is a HeatmapAnnotation object |
|
279 |
+ if(inherits(object@ht_list[[ length(object@ht_list) ]], "HeatmapAnnotation")) { |
|
280 |
+ object = object + Heatmap(matrix(nrow = nr, ncol = 0)) |
|
281 |
+ gap = unit.c(gap, unit(0, "null")) |
|
287 | 282 |
} |
288 |
- object@ht_list_param$gap = gap |
|
283 |
+ } |
|
284 |
+ object@ht_list_param$gap = gap |
|
289 | 285 |
|
290 |
- n = length(object@ht_list) |
|
286 |
+ n = length(object@ht_list) |
|
291 | 287 |
|
292 |
- if(row_sub_title_side == "left") { |
|
293 |
- for(i in seq_len(n)) { |
|
294 |
- if(i == 1) { |
|
295 |
- object@ht_list[[i]]@row_title = ht_main@row_title |
|
296 |
- object@ht_list[[i]]@row_title_param = ht_main@row_title_param |
|
297 |
- object@ht_list[[i]]@row_title_param$side = "left" |
|
298 |
- } else { |
|
299 |
- if(inherits(object@ht_list[[i]], "Heatmap")) { |
|
300 |
- object@ht_list[[i]]@row_title = character(0) |
|
301 |
- } |
|
302 |
- } |
|
303 |
- } |
|
304 |
- } else if(row_sub_title_side == "right") { |
|
305 |
- for(i in seq_len(n)) { |
|
306 |
- if(i == n) { |
|
307 |
- object@ht_list[[n]]@row_title = ht_main@row_title |
|
308 |
- object@ht_list[[n]]@row_title_param = ht_main@row_title_param |
|
309 |
- object@ht_list[[n]]@row_title_param$side = "right" |
|
310 |
- } else { |
|
311 |
- if(inherits(object@ht_list[[i]], "Heatmap")) { |
|
312 |
- object@ht_list[[i]]@row_title = character(0) |
|
313 |
- } |
|
314 |
- } |
|
315 |
- } |
|
316 |
- } else { |
|
317 |
- for(i in seq_len(n)) { |
|
318 |
- if(i == i_main) { |
|
319 |
- object@ht_list[[i]]@row_title = ht_main@row_title |
|
320 |
- object@ht_list[[i]]@row_title_param = ht_main@row_title_param |
|
321 |
- } else { |
|
322 |
- if(inherits(object@ht_list[[i]], "Heatmap")) { |
|
323 |
- object@ht_list[[i]]@row_title = character(0) |
|
324 |
- } |
|
325 |
- } |
|
326 |
- } |
|
288 |
+ ## orders of other heatmaps should be changed |
|
289 |
+ for(i in seq_len(n)) { |
|
290 |
+ if(inherits(object@ht_list[[i]], "Heatmap")) { |
|
291 |
+ object@ht_list[[i]]@row_order_list = ht_main@row_order_list |
|
292 |
+ object@ht_list[[i]]@row_order = ht_main@row_order |
|
293 |
+ object@ht_list[[i]]@row_hclust_param$cluster = FALSE # don't do clustering because cluster was already done |
|
327 | 294 |
} |
295 |
+ } |
|
328 | 296 |
|
329 |
- |
|
330 |
- if(row_hclust_side == "left") { |
|
331 |
- for(i in seq_len(n)) { |
|
332 |
- if(i == 1) { |
|
333 |
- object@ht_list[[1]]@row_hclust_list = ht_main@row_hclust_list |
|
334 |
- object@ht_list[[1]]@row_hclust_param = ht_main@row_hclust_param |
|
335 |
- object@ht_list[[1]]@row_hclust_param$side = "left" |
|
336 |
- } else { |
|
337 |
- if(inherits(object@ht_list[[i]], "Heatmap")) { |
|
338 |
- object@ht_list[[i]]@row_hclust_param$show = FALSE |
|
339 |
- } |
|
340 |
- } |
|
341 |
- if(inherits(object@ht_list[[i]], "Heatmap")) { |
|
342 |
- object@ht_list[[i]]@row_order_list = ht_main@row_order_list |
|
343 |
- object@ht_list[[i]]@row_hclust_param$cluster = FALSE |
|
344 |
- } |
|
345 |
- } |
|
346 |
- } else if(row_hclust_side == "right") { |
|
347 |
- for(i in seq_len(n)) { |
|
348 |
- if(i == n) { |
|
349 |
- object@ht_list[[n]]@row_hclust_list = ht_main@row_hclust_list |
|
350 |
- object@ht_list[[n]]@row_hclust_param = ht_main@row_hclust_param |
|
351 |
- object@ht_list[[n]]@row_hclust_param$side = "right" |
|
352 |
- } else { |
|
353 |
- if(inherits(object@ht_list[[i]], "Heatmap")) { |
|
354 |
- object@ht_list[[i]]@row_hclust_param$show = FALSE |
|
355 |
- } |
|
356 |
- } |
|
357 |
- if(inherits(object@ht_list[[i]], "Heatmap")) { |
|
358 |
- object@ht_list[[i]]@row_order_list = ht_main@row_order_list |
|
359 |
- object@ht_list[[i]]@row_hclust_param$cluster = FALSE |
|
360 |
- } |
|
361 |
- } |
|
362 |
- } else { |
|
363 |
- for(i in seq_len(n)) { |
|
364 |
- if(i == i_main) { |
|
365 |
- object@ht_list[[i]]@row_hclust_list = ht_main@row_hclust_list |
|
366 |
- object@ht_list[[i]]@row_hclust_param = ht_main@row_hclust_param |
|
367 |
- } else { |
|
368 |
- if(inherits(object@ht_list[[i]], "Heatmap")) { |
|
369 |
- object@ht_list[[i]]@row_hclust_param$show = FALSE |
|
370 |
- } |
|
371 |
- } |
|
297 |
+ if(row_hclust_side == "left" && i == 1) { |
|
298 |
+ object@ht_list[[1]]@row_hclust_list = ht_main@row_hclust_list |
|
299 |
+ object@ht_list[[1]]@row_hclust_param = ht_main@row_hclust_param |
|
300 |
+ object@ht_list[[1]]@row_hclust_param$side = "left" |
|
301 |
+ } else if(row_hclust_side == "right" && i == n) { |
|
302 |
+ object@ht_list[[n]]@row_hclust_list = ht_main@row_hclust_list |
|
303 |
+ object@ht_list[[n]]@row_hclust_param = ht_main@row_hclust_param |
|
304 |
+ object@ht_list[[n]]@row_hclust_param$side = "right" |
|
305 |
+ } else { |
|
306 |
+ for(i in seq_len(n)) { |
|
307 |
+ if(i != i_main) { |
|
372 | 308 |
if(inherits(object@ht_list[[i]], "Heatmap")) { |
373 |
- object@ht_list[[i]]@row_order_list = ht_main@row_order_list |
|
374 |
- object@ht_list[[i]]@row_hclust_param$cluster = FALSE |
|
309 |
+ object@ht_list[[i]]@row_hclust_param$show = FALSE |
|
375 | 310 |
} |
376 | 311 |
} |
377 | 312 |
} |
313 |
+ } |
|
378 | 314 |
|
379 |
- for(i in seq_len(n)) { |
|
380 |
- # supress row clustering because all rows in all heatmaps are adjusted |
|
381 |
- if(inherits(object@ht_list[[i]], "Heatmap")) { |
|
382 |
- object@ht_list[[i]]@matrix_param$km = 1 |
|
383 |
- object@ht_list[[i]]@row_title_param$combined_name_fun = NULL |
|
384 |
- object@ht_list[[i]] = prepare(object@ht_list[[i]], row_order = NULL, split = NULL) |
|
385 |
- } |
|
315 |
+ for(i in seq_len(n)) { |
|
316 |
+ # supress row clustering because all rows in all heatmaps are adjusted |
|
317 |
+ if(inherits(object@ht_list[[i]], "Heatmap")) { |
|
318 |
+ object@ht_list[[i]] = prepare(object@ht_list[[i]], process_rows = FALSE) |
|
386 | 319 |
} |
387 | 320 |
} |
388 | 321 |
|
... | ... |
@@ -805,8 +738,8 @@ setMethod(f = "draw_heatmap_list", |
805 | 738 |
# number of columns in heatmap whic are not fixed width |
806 | 739 |
heatmap_ncol = sapply(object@ht_list, function(ht) { |
807 | 740 |
if(inherits(ht, "Heatmap")) { |
808 |
- if(is.null(ht@heatmap_param$width)) { |
|
809 |
- return(ncol(ht@matrix)) |
|
741 |
+ if(!is.unit(ht@heatmap_param$width)) { |
|
742 |
+ return(ht@heatmap_param$width) |
|
810 | 743 |
} |
811 | 744 |
} |
812 | 745 |
return(0) |
... | ... |
@@ -814,7 +747,7 @@ setMethod(f = "draw_heatmap_list", |
814 | 747 |
|
815 | 748 |
heatmap_fixed_width = lapply(object@ht_list, function(ht) { |
816 | 749 |
if(inherits(ht, "Heatmap")) { |
817 |
- if(!is.null(ht@heatmap_param$width)) { |
|
750 |
+ if(is.unit(ht@heatmap_param$width)) { |
|
818 | 751 |
return(ht@heatmap_param$width) |
819 | 752 |
} else { |
820 | 753 |
return(unit(0, "null")) |
... | ... |
@@ -2,21 +2,18 @@ |
2 | 2 |
\docType{class} |
3 | 3 |
\alias{AdditiveUnit-class} |
4 | 4 |
\title{ |
5 |
-An internal class |
|
6 |
- |
|
5 |
+An internal class |
|
7 | 6 |
|
8 | 7 |
} |
9 | 8 |
\description{ |
10 |
-An internal class |
|
11 |
- |
|
9 |
+An internal class |
|
12 | 10 |
|
13 | 11 |
} |
14 | 12 |
\details{ |
15 |
-This class is a super class for \code{\link{Heatmap-class}}, \code{\link{HeatmapList-class}} and \code{\link{HeatmapAnnotation-class}} classes. It is only designed for \code{+} generic method so that above three classes can be appended to each other. |
|
16 |
- |
|
13 |
+This class is a super class for \code{\link{Heatmap-class}}, \code{\link{HeatmapList-class}} and \code{\link{HeatmapAnnotation-class}} classes. |
|
14 |
+It is only designed for \code{+} generic method so that above three classes can be appended to each other. |
|
17 | 15 |
|
18 | 16 |
} |
19 | 17 |
\examples{ |
20 | 18 |
# no example |
21 |
-NULL |
|
22 |
-} |
|
19 |
+NULL} |
... | ... |
@@ -1,39 +1,31 @@ |
1 | 1 |
\name{AdditiveUnit} |
2 | 2 |
\alias{AdditiveUnit} |
3 | 3 |
\title{ |
4 |
-Constructor method for AdditiveUnit class |
|
5 |
- |
|
4 |
+Constructor method for AdditiveUnit class |
|
6 | 5 |
|
7 | 6 |
} |
8 | 7 |
\description{ |
9 |
-Constructor method for AdditiveUnit class |
|
10 |
- |
|
8 |
+Constructor method for AdditiveUnit class |
|
11 | 9 |
|
12 | 10 |
} |
13 | 11 |
\usage{ |
14 |
-AdditiveUnit(...) |
|
15 |
-} |
|
12 |
+AdditiveUnit(...)} |
|
16 | 13 |
\arguments{ |
17 | 14 |
|
18 | 15 |
\item{...}{arguments.} |
19 |
- |
|
20 | 16 |
} |
21 | 17 |
\details{ |
22 |
-This method is not used in the package. |
|
23 |
- |
|
18 |
+This method is not used in the package. |
|
24 | 19 |
|
25 | 20 |
} |
26 | 21 |
\value{ |
27 |
-No value is returned. |
|
28 |
- |
|
22 |
+No value is returned. |
|
29 | 23 |
|
30 | 24 |
} |
31 | 25 |
\author{ |
32 |
-Zuguang Gu <z.gu@dkfz.de> |
|
33 |
- |
|
26 |
+Zuguang Gu <z.gu@dkfz.de> |
|
34 | 27 |
|
35 | 28 |
} |
36 | 29 |
\examples{ |
37 | 30 |
# no example |
38 |
-NULL |
|
39 |
-} |
|
31 |
+NULL} |
... | ... |
@@ -2,22 +2,21 @@ |
2 | 2 |
\docType{class} |
3 | 3 |
\alias{ColorMapping-class} |
4 | 4 |
\title{ |
5 |
-Class to map values to colors |
|
6 |
- |
|
5 |
+Class to map values to colors |
|
7 | 6 |
|
8 | 7 |
} |
9 | 8 |
\description{ |
10 |
-Class to map values to colors |
|
11 |
- |
|
9 |
+Class to map values to colors |
|
12 | 10 |
|
13 | 11 |
} |
14 | 12 |
\details{ |
15 |
-The \code{\link{ColorMapping-class}} handles color mapping with both discrete values and continuous values. Discrete values are mapped by setting a vector of colors and continuous values are mapped by setting a color mapping function. |
|
16 |
- |
|
13 |
+The \code{\link{ColorMapping-class}} handles color mapping with both discrete values and continuous values. |
|
14 |
+Discrete values are mapped by setting a vector of colors and continuous values are mapped by setting |
|
15 |
+a color mapping function. |
|
17 | 16 |
|
18 | 17 |
} |
19 | 18 |
\section{Methods}{ |
20 |
-The \code{\link{ColorMapping-class}} provides following methods: |
|
19 |
+The \code{\link{ColorMapping-class}} provides following methods: |
|
21 | 20 |
|
22 | 21 |
\itemize{ |
23 | 22 |
\item \code{\link{ColorMapping}}: contructor methods. |
... | ... |
@@ -25,14 +24,11 @@ The \code{\link{ColorMapping-class}} provides following methods: |
25 | 24 |
\item \code{\link{color_mapping_legend,ColorMapping-method}}: draw legend or get the size of the legend. |
26 | 25 |
} |
27 | 26 |
|
28 |
- |
|
29 | 27 |
} |
30 | 28 |
\author{ |
31 |
-Zuguang Gu <z.gu@dkfz.de> |
|
32 |
- |
|
29 |
+Zuguang Gu <z.gu@dkfz.de> |
|
33 | 30 |
|
34 | 31 |
} |
35 | 32 |
\examples{ |
36 | 33 |
# for examples, please go to `ColorMapping` method page |
37 |
-NULL |
|
38 |
-} |
|
34 |
+NULL} |
... | ... |
@@ -1,42 +1,36 @@ |
1 | 1 |
\name{ColorMapping} |
2 | 2 |
\alias{ColorMapping} |
3 | 3 |
\title{ |
4 |
-Constructor methods for ColorMapping class |
|
5 |
- |
|
4 |
+Constructor methods for ColorMapping class |
|
6 | 5 |
|
7 | 6 |
} |
8 | 7 |
\description{ |
9 |
-Constructor methods for ColorMapping class |
|
10 |
- |
|
8 |
+Constructor methods for ColorMapping class |
|
11 | 9 |
|
12 | 10 |
} |
13 | 11 |
\usage{ |
14 | 12 |
ColorMapping(name, colors = NULL, levels = NULL, |
15 |
- col_fun = NULL, breaks = NULL, na_col = "#FFFFFF") |
|
16 |
-} |
|
13 |
+ col_fun = NULL, breaks = NULL, na_col = "#FFFFFF")} |
|
17 | 14 |
\arguments{ |
18 | 15 |
|
19 | 16 |
\item{name}{name for this color mapping. It is used for drawing the title of the legend.} |
20 | 17 |
\item{colors}{discrete colors.} |
21 |
- \item{levels}{levels that correspond to \code{colors}. If \code{colors} is name indexed, \code{levels} can be ignored.} |
|
18 |
+ \item{levels}{levels that correspond to \code{colors}. If \code{colors} is name indexed, \code{levels} can be ignored.} |
|
22 | 19 |
\item{col_fun}{color mapping function that maps continuous values to colors.} |
23 |
- \item{breaks}{breaks for the continuous color mapping. If \code{col_fun} is generated by \code{\link[circlize]{colorRamp2}}, \code{breaks} can be ignored.} |
|
20 |
+ \item{breaks}{breaks for the continuous color mapping. If \code{col_fun} isgenerated by \code{\link[circlize]{colorRamp2}}, \code{breaks} can be ignored.} |
|
24 | 21 |
\item{na_col}{colors for \code{NA} values.} |
25 |
- |
|
26 | 22 |
} |
27 | 23 |
\details{ |
28 |
-\code{colors} and \code{levels} are used for discrete color mapping, \code{col_fun} and \code{breaks} are used for continuous color mapping. |
|
29 |
- |
|
24 |
+\code{colors} and \code{levels} are used for discrete color mapping, \code{col_fun} and |
|
25 |
+\code{breaks} are used for continuous color mapping. |
|
30 | 26 |
|
31 | 27 |
} |
32 | 28 |
\value{ |
33 |
-A \code{\link{ColorMapping-class}} object. |
|
34 |
- |
|
29 |
+A \code{\link{ColorMapping-class}} object. |
|
35 | 30 |
|
36 | 31 |
} |
37 | 32 |
\author{ |
38 |
-Zuguang Gu <z.gu@dkfz.de> |
|
39 |
- |
|
33 |
+Zuguang Gu <z.gu@dkfz.de> |
|
40 | 34 |
|
41 | 35 |
} |
42 | 36 |
\examples{ |
... | ... |
@@ -56,5 +50,4 @@ cm |
56 | 50 |
require(circlize) |
57 | 51 |
cm = ColorMapping(name = "test", |
58 | 52 |
col_fun = colorRamp2(c(0, 0.5, 1), c("blue", "white", "red"))) |
59 |
-cm |
|
60 |
-} |
|
53 |
+cm} |
... | ... |
@@ -2,19 +2,19 @@ |
2 | 2 |
\docType{package} |
3 | 3 |
\alias{ComplexHeatmap-package} |
4 | 4 |
\title{ |
5 |
-Making complex heatmap |
|
6 |
- |
|
5 |
+Making complex heatmap |
|
7 | 6 |
|
8 | 7 |
} |
9 | 8 |
\description{ |
10 |
-Making complex heatmap |
|
11 |
- |
|
9 |
+Making complex heatmap |
|
12 | 10 |
|
13 | 11 |
} |
14 | 12 |
\details{ |
15 |
-This package aims to provide a simple and flexible way to arrange multiple heatmaps as well as self-defining annotation graphics. |
|
13 |
+This package aims to provide a simple and flexible way to arrange |
|
14 |
+multiple heatmaps as well as self-defining annotation graphics. |
|
16 | 15 |
|
17 |
-The package is implemented in an object oriented way. Components of heatmap lists are abstracted into several classes. |
|
16 |
+The package is implemented in an object oriented way. |
|
17 |
+Components of heatmap lists are abstracted into several classes. |
|
18 | 18 |
|
19 | 19 |
\itemize{ |
20 | 20 |
\item \code{\link{Heatmap-class}}: a single heatmap containing heatmap body, row/column names, titles, dendrograms and column annotations. |
... | ... |
@@ -22,16 +22,16 @@ The package is implemented in an object oriented way. Components of heatmap lis |
22 | 22 |
\item \code{\link{HeatmapAnnotation-class}}: a list of row annotations or column annotations. |
23 | 23 |
} |
24 | 24 |
|
25 |
-There are also several internal classes: |
|
25 |
+There are also several internal classes: |
|
26 | 26 |
|
27 | 27 |
\itemize{ |
28 | 28 |
\item \code{\link{SingleAnnotation-class}}: a single row annotation or column annotation. |
29 | 29 |
\item \code{\link{ColorMapping-class}}: mapping from values to colors. |
30 | 30 |
} |
31 | 31 |
|
32 |
-For plotting one single heatmap, please go to the documentation page of \code{\link{Heatmap}}. For plotting multiple heatmaps, please go to \code{\link{HeatmapList-class}} and \code{+.AdditiveUnit}. |
|
33 |
- |
|
34 |
-The vignette provides detailed explanation of how to use this package. |
|
32 |
+For plotting one single heatmap, please go to the documentation page of \code{\link{Heatmap}}. |
|
33 |
+For plotting multiple heatmaps, please go to \code{\link{HeatmapList-class}} and \code{+.AdditiveUnit}. |
|
35 | 34 |
|
35 |
+The vignette provides detailed explanation of how to use this package. |
|
36 | 36 |
|
37 | 37 |
} |
... | ... |
@@ -2,17 +2,15 @@ |
2 | 2 |
\docType{class} |
3 | 3 |
\alias{Heatmap-class} |
4 | 4 |
\title{ |
5 |
-Class for a single heatmap |
|
6 |
- |
|
5 |
+Class for a single heatmap |
|
7 | 6 |
|
8 | 7 |
} |
9 | 8 |
\description{ |
10 |
-Class for a single heatmap |
|
11 |
- |
|
9 |
+Class for a single heatmap |
|
12 | 10 |
|
13 | 11 |
} |
14 | 12 |
\details{ |
15 |
-The components for a single heamtap are placed into a 9 x 7 layout: |
|
13 |
+The components for a single heamtap are placed into a 9 x 7 layout: |
|
16 | 14 |
|
17 | 15 |
\preformatted{ |
18 | 16 |
+------+ (1) |
... | ... |
@@ -28,7 +26,7 @@ The components for a single heamtap are placed into a 9 x 7 layout: |
28 | 26 |
+------+ (9) |
29 | 27 |
} |
30 | 28 |
|
31 |
-From top to bottom in column 4, the regions are: |
|
29 |
+From top to bottom in column 4, the regions are: |
|
32 | 30 |
|
33 | 31 |
\itemize{ |
34 | 32 |
\item title which is put on the top of the heatmap, graphics are drawn by \code{\link{draw_title,Heatmap-method}}. |
... | ... |
@@ -42,7 +40,7 @@ From top to bottom in column 4, the regions are: |
42 | 40 |
\item title on the bottom, graphics are drawn by \code{\link{draw_title,Heatmap-method}}. |
43 | 41 |
} |
44 | 42 |
|
45 |
-From left to right in row 5, the regions are: |
|
43 |
+From left to right in row 5, the regions are: |
|
46 | 44 |
|
47 | 45 |
\itemize{ |
48 | 46 |
\item title which is put in the left of the heatmap, graphics are drawn by \code{\link{draw_title,Heatmap-method}}. |
... | ... |
@@ -54,12 +52,13 @@ From left to right in row 5, the regions are: |
54 | 52 |
\item title on the right, graphics are drawn by \code{\link{draw_title,Heatmap-method}}. |
55 | 53 |
} |
56 | 54 |
|
57 |
-The \code{\link{Heatmap-class}} is not responsible for heatmap legend and annotation legends. The \code{\link{draw,Heatmap-method}} method will construct a \code{\link{HeatmapList-class}} object which only contains one single heatmap and call \code{\link{draw,HeatmapList-method}} to make a complete heatmap. |
|
58 |
- |
|
55 |
+The \code{\link{Heatmap-class}} is not responsible for heatmap legend and annotation legends. The \code{\link{draw,Heatmap-method}} method |
|
56 |
+will construct a \code{\link{HeatmapList-class}} object which only contains one single heatmap |
|
57 |
+and call \code{\link{draw,HeatmapList-method}} to make a complete heatmap. |
|
59 | 58 |
|
60 | 59 |
} |
61 | 60 |
\section{Methods}{ |
62 |
-The \code{\link{Heatmap-class}} provides following methods: |
|
61 |
+The \code{\link{Heatmap-class}} provides following methods: |
|
63 | 62 |
|
64 | 63 |
\itemize{ |
65 | 64 |
\item \code{\link{Heatmap}}: constructor method. |
... | ... |
@@ -67,14 +66,11 @@ The \code{\link{Heatmap-class}} provides following methods: |
67 | 66 |
\item \code{\link{add_heatmap,Heatmap-method}} append heatmaps and row annotations to a list of heatmaps. |
68 | 67 |
} |
69 | 68 |
|
70 |
- |
|
71 | 69 |
} |
72 | 70 |
\author{ |
73 |
-Zuguang Gu <z.gu@dkfz.de> |
|
74 |
- |
|
71 |
+Zuguang Gu <z.gu@dkfz.de> |
|
75 | 72 |
|
76 | 73 |
} |
77 | 74 |
\examples{ |
78 | 75 |
# for examples, please go to `Heatmap` method page |
79 |
-NULL |
|
80 |
-} |
|
76 |
+NULL} |
... | ... |
@@ -1,13 +1,11 @@ |
1 | 1 |
\name{Heatmap} |
2 | 2 |
\alias{Heatmap} |
3 | 3 |
\title{ |
4 |
-Constructor method for Heatmap class |
|
5 |
- |
|
4 |
+Constructor method for Heatmap class |
|
6 | 5 |
|
7 | 6 |
} |
8 | 7 |
\description{ |
9 |
-Constructor method for Heatmap class |
|
10 |
- |
|
8 |
+Constructor method for Heatmap class |
|
11 | 9 |
|
12 | 10 |
} |
13 | 11 |
\usage{ |
... | ... |
@@ -35,29 +33,28 @@ Heatmap(matrix, col, name, na_col = "grey", rect_gp = gpar(col = NA), |
35 | 33 |
bottom_annotation_height = unit(5*length(bottom_annotation@anno_list), "mm"), |
36 | 34 |
km = 1, split = NULL, gap = unit(1, "mm"), |
37 | 35 |
combined_name_fun = function(x) paste(x, collapse = "/"), |
38 |
- width = NULL, show_heatmap_legend = TRUE) |
|
39 |
-} |
|
36 |
+ width = NULL, show_heatmap_legend = TRUE)} |
|
40 | 37 |
\arguments{ |
41 | 38 |
|
42 |
- \item{matrix}{a matrix. Either numeric or character. If it is a simple vector, it will be converted to a one-column matrix.} |
|
43 |
- \item{col}{a vector of colors if the color mapping is discrete or a color mapping function if the matrix is continuous numbers. If the matrix is continuous, the value can also be a vector of colors so that colors will be interpolated. Pass to \code{\link{ColorMapping}}.} |
|
39 |
+ \item{matrix}{a matrix. Either numeric or character. If it is a simple vector, it will beconverted to a one-column matrix.} |
|
40 |
+ \item{col}{a vector of colors if the color mapping is discrete or a color mapping function if the matrix is continuous numbers. If the matrix is continuous,the value can also be a vector of colors so that colors will be interpolated. Pass to \code{\link{ColorMapping}}.} |
|
44 | 41 |
\item{name}{name of the heatmap. The name is used as the title of the heatmap legend.} |
45 | 42 |
\item{na_col}{color for \code{NA} values.} |
46 | 43 |
\item{rect_gp}{graphic parameters for drawing rectangles (for heatmap body).} |
47 |
- \item{cell_fun}{self-defined function to add graphics on each cell. Seven parameters will be passed into this function: \code{i}, \code{j}, \code{x}, \code{y}, \code{width}, \code{height}, \code{fill} which are row index, column index in \code{matrix}, coordinate of the middle points in the heatmap body viewport, the width and height of the cell and the filled color. } |
|
44 |
+ \item{cell_fun}{self-defined function to add graphics on each cell. Seven parameters will be passed into this function: \code{i}, \code{j}, \code{x}, \code{y}, \code{width}, \code{height}, \code{fill} which are row index,column index in \code{matrix}, coordinate of the middle points in the heatmap body viewport,the width and height of the cell and the filled color. } |
|
48 | 45 |
\item{row_title}{title on row.} |
49 | 46 |
\item{row_title_side}{will the title be put on the left or right of the heatmap?} |
50 | 47 |
\item{row_title_gp}{graphic parameters for drawing text.} |
51 | 48 |
\item{column_title}{title on column.} |
52 | 49 |
\item{column_title_side}{will the title be put on the top or bottom of the heatmap?} |
53 | 50 |
\item{column_title_gp}{graphic parameters for drawing text.} |
54 |
- \item{cluster_rows}{If the value is a logical, it means whether make cluster on rows. The value can also be a \code{\link[stats]{hclust}} or a \code{\link[stats]{dendrogram}} that already contains clustering information. This means you can use any type of clustering methods and render the \code{\link[stats]{dendrogram}} object with self-defined graphic settings.} |
|
55 |
- \item{clustering_distance_rows}{it can be a pre-defined character which is in ("euclidean", "maximum", "manhattan", "canberra", "binary", "minkowski", "pearson", "spearman", "kendall"). It can also be a function. If the function has one argument, the input argument should be a matrix and the returned value should be a \code{\link[stats]{dist}} object. If the function has two arguments, the input arguments are two vectors and the function calculates distance between these two vectors.} |
|
51 |
+ \item{cluster_rows}{If the value is a logical, it means whether make cluster on rows. The value can alsobe a \code{\link[stats]{hclust}} or a \code{\link[stats]{dendrogram}} that already contains clustering information.This means you can use any type of clustering methods and render the \code{\link[stats]{dendrogram}}object with self-defined graphic settings.} |
|
52 |
+ \item{clustering_distance_rows}{it can be a pre-defined character which is in ("euclidean", "maximum", "manhattan", "canberra", "binary", "minkowski", "pearson", "spearman", "kendall"). It can also be a function.If the function has one argument, the input argument should be a matrix and the returned value should be a \code{\link[stats]{dist}} object. If the function has two arguments,the input arguments are two vectors and the function calculates distance between thesetwo vectors.} |
|
56 | 53 |
\item{clustering_method_rows}{method to make cluster, pass to \code{\link[stats]{hclust}}.} |
57 | 54 |
\item{row_hclust_side}{should the row cluster be put on the left or right of the heatmap?} |
58 | 55 |
\item{row_hclust_width}{width of the row cluster, should be a \code{\link[grid]{unit}} object.} |
59 | 56 |
\item{show_row_hclust}{whether show row clusters. } |
60 |
- \item{row_hclust_gp}{graphics parameters for drawing lines. If users already provide a \code{\link[stats]{dendrogram}} object with edges rendered, this argument will be ignored.} |
|
57 |
+ \item{row_hclust_gp}{graphics parameters for drawing lines. If users already provide a \code{\link[stats]{dendrogram}}object with edges rendered, this argument will be ignored.} |
|
61 | 58 |
\item{cluster_columns}{whether make cluster on columns. Same settings as \code{cluster_rows}.} |
62 | 59 |
\item{clustering_distance_columns}{same setting as \code{clustering_distance_rows}.} |
63 | 60 |
\item{clustering_method_columns}{method to make cluster, pass to \code{\link[stats]{hclust}}.} |
... | ... |
@@ -65,11 +62,11 @@ Heatmap(matrix, col, name, na_col = "grey", rect_gp = gpar(col = NA), |
65 | 62 |
\item{column_hclust_height}{height of the column cluster, should be a \code{\link[grid]{unit}} object.} |
66 | 63 |
\item{show_column_hclust}{whether show column clusters.} |
67 | 64 |
\item{column_hclust_gp}{graphic parameters for drawling lines. Same settings as \code{row_hclust_gp}.} |
68 |
- \item{row_order}{order of rows. It makes it easy to adjust row order for a list of heatmaps if this heatmap is selected as the main heatmap. Manually setting row order should turn off clustering} |
|
65 |
+ \item{row_order}{order of rows. It makes it easy to adjust row order for a list of heatmaps if this heatmap is selected as the main heatmap. Manually setting row order should turn off clustering} |
|
69 | 66 |
\item{column_order}{order of column. It makes it easy to adjust column order for both matrix and column annotations.} |
70 | 67 |
\item{row_names_side}{should the row names be put on the left or right of the heatmap?} |
71 | 68 |
\item{show_row_names}{whether show row names.} |
72 |
- \item{row_names_max_width}{maximum width of row names viewport. Because some times row names can be very long, it is not reasonable to show them all.} |
|
69 |
+ \item{row_names_max_width}{maximum width of row names viewport. Because some times row names can be very long, it is not reasonableto show them all.} |
|
73 | 70 |
\item{row_names_gp}{graphic parameters for drawing text.} |
74 | 71 |
\item{column_names_side}{should the column names be put on the top or bottom of the heatmap?} |
75 | 72 |
\item{column_names_max_height}{maximum height of column names viewport.} |
... | ... |
@@ -79,18 +76,18 @@ Heatmap(matrix, col, name, na_col = "grey", rect_gp = gpar(col = NA), |
79 | 76 |
\item{top_annotation_height}{total height of the column annotations on the top.} |
80 | 77 |
\item{bottom_annotation}{a \code{\link{HeatmapAnnotation}} object.} |
81 | 78 |
\item{bottom_annotation_height}{total height of the column annotations on the bottom.} |
82 |
- \item{km}{do k-means clustering on rows. If the value is larger than 1, the heatmap will be split by rows according to the k-means clustering. For each row-clusters, hierarchical clustering is still applied with parameters above.} |
|
79 |
+ \item{km}{do k-means clustering on rows. If the value is larger than 1, the heatmap will be split by rows according to the k-means clustering.For each row-clusters, hierarchical clustering is still applied with parameters above.} |
|
83 | 80 |
\item{split}{a vector or a data frame by which the rows are split.} |
84 | 81 |
\item{gap}{gap between row-slices if the heatmap is split by rows, should be \code{\link[grid]{unit}} object.} |
85 |
- \item{combined_name_fun}{if the heatmap is split by rows, how to make a combined row title for each slice? The input parameter for this function is a vector which contains level names under each column in \code{split}.} |
|
86 |
- \item{width}{the width of the single heatmap, should be a fixed \code{\link[grid]{unit}} object. It is used for the layout when the heatmap is appended to a list of heatmaps.} |
|
82 |
+ \item{combined_name_fun}{if the heatmap is split by rows, how to make a combined row title for each slice?The input parameter for this function is a vector which contains level names under each column in \code{split}.} |
|
83 |
+ \item{width}{the width of the single heatmap, should be a fixed \code{\link[grid]{unit}} object. It is used for the layout when the heatmapis appended to a list of heatmaps.} |
|
87 | 84 |
\item{show_heatmap_legend}{whether show heatmap legend?} |
88 |
- |
|
89 | 85 |
} |
90 | 86 |
\details{ |
91 |
-The initialization function only applies parameter checking and fill values to each slot with proper ones. Then it will be ready for clustering and layout. |
|
87 |
+The initialization function only applies parameter checking and fill values to each slot with proper ones. |
|
88 |
+Then it will be ready for clustering and layout. |
|
92 | 89 |
|
93 |
-Following methods can be applied on the \code{\link{Heatmap-class}} object: |
|
90 |
+Following methods can be applied on the \code{\link{Heatmap-class}} object: |
|
94 | 91 |
|
95 | 92 |
\itemize{ |
96 | 93 |
\item \code{\link{show,Heatmap-method}}: draw a single heatmap with default parameters |
... | ... |
@@ -98,18 +95,16 @@ Following methods can be applied on the \code{\link{Heatmap-class}} object: |
98 | 95 |
\item \code{\link{add_heatmap,Heatmap-method}} append heatmaps and row annotations to a list of heatmaps. |
99 | 96 |
} |
100 | 97 |
|
101 |
-The constructor function pretends to be a high-level graphic function because the \code{show} method of the \code{\link{Heatmap-class}} object actually plots the graphics. |
|
102 |
- |
|
98 |
+The constructor function pretends to be a high-level graphic function because the \code{show} method |
|
99 |
+of the \code{\link{Heatmap-class}} object actually plots the graphics. |
|
103 | 100 |
|
104 | 101 |
} |
105 | 102 |
\value{ |
106 |
-A \code{\link{Heatmap-class}} object. |
|
107 |
- |
|
103 |
+A \code{\link{Heatmap-class}} object. |
|
108 | 104 |
|
109 | 105 |
} |
110 | 106 |
\author{ |
111 |
-Zuguang Gu <z.gu@dkfz.de> |
|
112 |
- |
|
107 |
+Zuguang Gu <z.gu@dkfz.de> |
|
113 | 108 |
|
114 | 109 |
} |
115 | 110 |
\examples{ |
... | ... |
@@ -183,5 +178,4 @@ Heatmap(mat, rect_gp = gpar(col = "white"), |
183 | 178 |
grid.text(mat[i, j], x = x, y = y) |
184 | 179 |
}, |
185 | 180 |
cluster_rows = FALSE, cluster_columns = FALSE, row_names_side = "left", |
186 |
- column_names_side = "top") |
|
187 |
-} |
|
181 |
+ column_names_side = "top")} |
... | ... |
@@ -2,36 +2,32 @@ |
2 | 2 |
\docType{class} |
3 | 3 |
\alias{HeatmapAnnotation-class} |
4 | 4 |
\title{ |
5 |
-Class for heatmap annotations |
|
6 |
- |
|
5 |
+Class for heatmap annotations |
|
7 | 6 |
|
8 | 7 |
} |
9 | 8 |
\description{ |
10 |
-Class for heatmap annotations |
|
11 |
- |
|
9 |
+Class for heatmap annotations |
|
12 | 10 |
|
13 | 11 |
} |
14 | 12 |
\details{ |
15 |
-A complex heatmap contains a list of annotations which represent as different graphics placed on rows and columns. The \code{\link{HeatmapAnnotation-class}} is a category of single annotations which are by a list of \code{\link{SingleAnnotation-class}} objects with same number of rows or columns. |
|
16 |
- |
|
13 |
+A complex heatmap contains a list of annotations which represent as different graphics |
|
14 |
+placed on rows and columns. The \code{\link{HeatmapAnnotation-class}} is a category of single annotations which are |
|
15 |
+by a list of \code{\link{SingleAnnotation-class}} objects with same number of rows or columns. |
|
17 | 16 |
|
18 | 17 |
} |
19 | 18 |
\section{Methods}{ |
20 |
-The \code{\link{HeatmapAnnotation-class}} provides following methods: |
|
19 |
+The \code{\link{HeatmapAnnotation-class}} provides following methods: |
|
21 | 20 |
|
22 | 21 |
\itemize{ |
23 | 22 |
\item \code{\link{HeatmapAnnotation}}: constructor method |
24 | 23 |
\item \code{\link{draw,HeatmapAnnotation-method}}: draw the annotations |
25 | 24 |
} |
26 | 25 |
|
27 |
- |
|
28 | 26 |
} |
29 | 27 |
\author{ |
30 |
-Zuguang Gu <z.gu@dkfz.de> |
|
31 |
- |
|
28 |
+Zuguang Gu <z.gu@dkfz.de> |
|
32 | 29 |
|
33 | 30 |
} |
34 | 31 |
\examples{ |
35 | 32 |
# for examples, please go to `HeatmapAnnotation` method page |
36 |
-NULL |
|
37 |
-} |
|
33 |
+NULL} |
... | ... |
@@ -1,21 +1,18 @@ |
1 | 1 |
\name{HeatmapAnnotation} |
2 | 2 |
\alias{HeatmapAnnotation} |
3 | 3 |
\title{ |
4 |
-Constructor method for HeatmapAnnotation class |
|
5 |
- |
|
4 |
+Constructor method for HeatmapAnnotation class |
|
6 | 5 |
|
7 | 6 |
} |
8 | 7 |
\description{ |
9 |
-Constructor method for HeatmapAnnotation class |
|
10 |
- |
|
8 |
+Constructor method for HeatmapAnnotation class |
|
11 | 9 |
|
12 | 10 |
} |
13 | 11 |
\usage{ |
14 | 12 |
HeatmapAnnotation(df, name, col, show_legend = rep(TRUE, n_anno), ..., |
15 | 13 |
which = c("column", "row"), annotation_height = 1, annotation_width = 1, |
16 | 14 |
height = unit(1, "cm"), width = unit(1, "cm"), gp = gpar(col = NA), |
17 |
- gap = unit(0, "null")) |
|
18 |
-} |
|
15 |
+ gap = unit(0, "null"))} |
|
19 | 16 |
\arguments{ |
20 | 17 |
|
21 | 18 |
\item{df}{a data frame. Each column will be treated as a simple annotation. The data frame must have column names.} |
... | ... |
@@ -30,26 +27,22 @@ HeatmapAnnotation(df, name, col, show_legend = rep(TRUE, n_anno), ..., |
30 | 27 |
\item{width}{width of the whole heatmap annotations, only used for row annotation when appending to the list of heatmaps.} |
31 | 28 |
\item{gp}{graphic parameters for simple annotations.} |
32 | 29 |
\item{gap}{gap between each annotation} |
33 |
- |
|
34 | 30 |
} |
35 | 31 |
\details{ |
36 |
-The simple annotations are defined by \code{df} and \code{col} arguments. Complex annotations are defined by the function list. So you need to at least to define \code{df} or a annotation function. |
|
37 |
- |
|
32 |
+The simple annotations are defined by \code{df} and \code{col} arguments. Complex annotations are |
|
33 |
+defined by the function list. So you need to at least to define \code{df} or a annotation function. |
|
38 | 34 |
|
39 | 35 |
} |
40 | 36 |
\value{ |
41 |
-A \code{\link{HeatmapAnnotation-class}} object. |
|
42 |
- |
|
37 |
+A \code{\link{HeatmapAnnotation-class}} object. |
|
43 | 38 |
|
44 | 39 |
} |
45 | 40 |
\seealso{ |
46 |
-There are two shortcut functions: \code{\link{rowAnnotation}} and \code{\link{columnAnnotation}}. |
|
47 |
- |
|
41 |
+There are two shortcut functions: \code{\link{rowAnnotation}} and \code{\link{columnAnnotation}}. |
|
48 | 42 |
|
49 | 43 |
} |
50 | 44 |
\author{ |
51 |
-Zuguang Gu <z.gu@dkfz.de> |
|
52 |
- |
|
45 |
+Zuguang Gu <z.gu@dkfz.de> |
|
53 | 46 |
|
54 | 47 |
} |
55 | 48 |
\examples{ |
... | ... |
@@ -66,5 +59,4 @@ ha = HeatmapAnnotation(points = anno_points(1:6)) |
66 | 59 |
ha = HeatmapAnnotation(histogram = anno_points(1:6)) |
67 | 60 |
|
68 | 61 |
mat = matrix(rnorm(36), 6) |
69 |
-ha = HeatmapAnnotation(boxplot = anno_boxplot(mat)) |
|
70 |
-} |
|
62 |
+ha = HeatmapAnnotation(boxplot = anno_boxplot(mat))} |
... | ... |
@@ -2,19 +2,17 @@ |
2 | 2 |
\docType{class} |
3 | 3 |
\alias{HeatmapList-class} |
4 | 4 |
\title{ |
5 |
-Class for a list of heatmaps |
|
6 |
- |
|
5 |
+Class for a list of heatmaps |
|
7 | 6 |
|
8 | 7 |
} |
9 | 8 |
\description{ |
10 |
-Class for a list of heatmaps |
|
11 |
- |
|
9 |
+Class for a list of heatmaps |
|
12 | 10 |
|
13 | 11 |
} |
14 | 12 |
\details{ |
15 |
-A heatmap list is defined as a list of heatmaps and row annotations. |
|
13 |
+A heatmap list is defined as a list of heatmaps and row annotations. |
|
16 | 14 |
|
17 |
-The components for the heamtap list are placed into a 7 x 7 layout: |
|
15 |
+The components for the heamtap list are placed into a 7 x 7 layout: |
|
18 | 16 |
|
19 | 17 |
\preformatted{ |
20 | 18 |
+------+(1) |
... | ... |
@@ -28,7 +26,7 @@ The components for the heamtap list are placed into a 7 x 7 layout: |
28 | 26 |
+------+(7) |
29 | 27 |
} |
30 | 28 |
|
31 |
-From top to bottom in column 4, the regions are: |
|
29 |
+From top to bottom in column 4, the regions are: |
|
32 | 30 |
|
33 | 31 |
\itemize{ |
34 | 32 |
\item annotation legend on the top, graphics are drawn by \code{\link{draw_annotation_legend,HeatmapList-method}}. |
... | ... |
@@ -40,7 +38,7 @@ From top to bottom in column 4, the regions are: |
40 | 38 |
\item annotation legend on the bottom, graphics are drawn by \code{\link{draw_annotation_legend,HeatmapList-method}}. |
41 | 39 |
} |
42 | 40 |
|
43 |
-From left to right in row 4, the regions are: |
|
41 |
+From left to right in row 4, the regions are: |
|
44 | 42 |
|
45 | 43 |
\itemize{ |
46 | 44 |
\item annotation legend on the left, graphics are drawn by \code{\link{draw_annotation_legend,HeatmapList-method}}. |
... | ... |
@@ -52,23 +50,21 @@ From left to right in row 4, the regions are: |
52 | 50 |
\item annotation legend on the right, graphics are drawn by \code{\link{draw_annotation_legend,HeatmapList-method}}. |
53 | 51 |
} |
54 | 52 |
|
55 |
-For the list of heatmaps which are placed at (5, 5) in the layout, the heatmaps and row annotations are placed one after the other. |
|
56 |
- |
|
53 |
+For the list of heatmaps which are placed at (5, 5) in the layout, the heatmaps and row annotations |
|
54 |
+are placed one after the other. |
|
57 | 55 |
|
58 | 56 |
} |
59 | 57 |
\section{Methods}{ |
60 |
-The \code{\link{HeatmapList-class}} provides following methods: |
|
58 |
+The \code{\link{HeatmapList-class}} provides following methods: |
|
61 | 59 |
|
62 | 60 |
\itemize{ |
63 | 61 |
\item \code{\link{draw,HeatmapList-method}}: draw the list of heatmaps and row annotations. |
64 | 62 |
\item \code{\link{add_heatmap,HeatmapList-method}} add heatmaps to the list of heatmaps. |
65 | 63 |
} |
66 | 64 |
|
67 |
- |
|
68 | 65 |
} |
69 | 66 |
\author{ |
70 |
-Zuguang Gu <z.gu@dkfz.de> |
|
71 |
- |
|
67 |
+Zuguang Gu <z.gu@dkfz.de> |
|
72 | 68 |
|
73 | 69 |
} |
74 | 70 |
\examples{ |
... | ... |
@@ -87,5 +83,4 @@ ht + ht_list |
87 | 83 |
ha = HeatmapAnnotation(points = anno_points(1:12, which = "row"), |
88 | 84 |
which = "row") |
89 | 85 |
ht + ha |
90 |
-ht_list + ha |
|
91 |
-} |
|
86 |
+ht_list + ha} |
... | ... |
@@ -1,42 +1,33 @@ |
1 | 1 |
\name{HeatmapList} |
2 | 2 |
\alias{HeatmapList} |
3 | 3 |
\title{ |
4 |
-Constructor method for HeatmapList class |
|
5 |
- |
|
4 |
+Constructor method for HeatmapList class |
|
6 | 5 |
|
7 | 6 |
} |
8 | 7 |
\description{ |
9 |
-Constructor method for HeatmapList class |
|
10 |
- |
|
8 |
+Constructor method for HeatmapList class |
|
11 | 9 |
|
12 | 10 |
} |
13 | 11 |
\usage{ |
14 |
-HeatmapList(...) |
|
15 |
-} |
|
12 |
+HeatmapList(...)} |
|
16 | 13 |
\arguments{ |
17 | 14 |
|
18 | 15 |
\item{...}{arguments} |
19 |
- |
|
20 | 16 |
} |
21 | 17 |
\details{ |
22 |
-There is no public constructor method for the \code{\link{HeatmapList-class}}. |
|
23 |
- |
|
18 |
+There is no public constructor method for the \code{\link{HeatmapList-class}}. |
|
24 | 19 |
|
25 | 20 |
} |
26 | 21 |
\value{ |
27 |
-No value is returned. |
|
28 |
- |
|
22 |
+No value is returned. |
|
29 | 23 |
|
30 | 24 |
} |
31 | 25 |
\author{ |
32 |
-Zuguang Gu <z.gu@dkfz.de> |
|
33 |
- |
|
26 |
+Zuguang Gu <z.gu@dkfz.de> |
|
34 | 27 |
|
35 | 28 |
} |
36 | 29 |
\section{Detailes}{ |
37 |
-There is no public constructor method for the \code{\link{HeatmapList-class}}. |
|
38 |
-} |
|
30 |
+There is no public constructor method for the \code{\link{HeatmapList-class}}.} |
|
39 | 31 |
\examples{ |
40 | 32 |
# no example |
41 |
-NULL |
|
42 |
-} |
|
33 |
+NULL} |
... | ... |
@@ -2,43 +2,42 @@ |
2 | 2 |
\docType{class} |
3 | 3 |
\alias{SingleAnnotation-class} |
4 | 4 |
\title{ |
5 |
-Class for a single annotation |
|
6 |
- |
|
5 |
+Class for a single annotation |
|
7 | 6 |
|
8 | 7 |
} |
9 | 8 |
\description{ |
10 |
-Class for a single annotation |
|
11 |
- |
|
9 |
+Class for a single annotation |
|
12 | 10 |
|
13 | 11 |
} |
14 | 12 |
\details{ |
15 |
-A complex heatmap always has more than one annotations on rows and columns. Here the \code{\link{SingleAnnotation-class}} defines the basic unit of annotations. The most simple annotation is one row or one column grids in which different colors represent different classes of the data. The annotation can also be more complex graphics, such as a boxplot that shows data distribution in corresponding row or column. |
|
16 |
- |
|
17 |
-The \code{\link{SingleAnnotation-class}} is used for storing data for a single annotation and provides methods for drawing annotation graphics. |
|
13 |
+A complex heatmap always has more than one annotations on rows and columns. Here |
|
14 |
+the \code{\link{SingleAnnotation-class}} defines the basic unit of annotations. |
|
15 |
+The most simple annotation is one row or one column grids in which different colors |
|
16 |
+represent different classes of the data. The annotation can also be more complex |
|
17 |
+graphics, such as a boxplot that shows data distribution in corresponding row or column. |
|
18 | 18 |
|
19 |
+The \code{\link{SingleAnnotation-class}} is used for storing data for a single annotation and provides |
|
20 |
+methods for drawing annotation graphics. |
|
19 | 21 |
|
20 | 22 |
} |
21 | 23 |
\section{Methods}{ |
22 |
-The \code{\link{SingleAnnotation-class}} provides following methods: |
|
24 |
+The \code{\link{SingleAnnotation-class}} provides following methods: |
|
23 | 25 |
|
24 | 26 |
\itemize{ |
25 | 27 |
\item \code{\link{SingleAnnotation}}: constructor method |
26 | 28 |
\item \code{\link{draw,SingleAnnotation-method}}: draw the single annotation. |
27 | 29 |
} |
28 | 30 |
|
29 |
- |
|
30 | 31 |
} |
31 | 32 |
\seealso{ |
32 |
-The \code{\link{SingleAnnotation-class}} is always used internally. The public \code{\link{HeatmapAnnotation-class}} contains a list of \code{\link{SingleAnnotation-class}} objects and is used to add annotation graphics on heatmaps. |
|
33 |
- |
|
33 |
+The \code{\link{SingleAnnotation-class}} is always used internally. The public \code{\link{HeatmapAnnotation-class}} |
|
34 |
+contains a list of \code{\link{SingleAnnotation-class}} objects and is used to add annotation graphics on heatmaps. |
|
34 | 35 |
|
35 | 36 |
} |
36 | 37 |
\author{ |
37 |
-Zuguang Gu <z.gu@dkfz.de> |
|
38 |
- |
|
38 |
+Zuguang Gu <z.gu@dkfz.de> |
|
39 | 39 |
|
40 | 40 |
} |
41 | 41 |
\examples{ |
42 | 42 |
# for examples, please go to `SingleAnnotation` method page |
43 |
-NULL |
|
44 |
-} |
|
43 |
+NULL} |
... | ... |
@@ -1,49 +1,50 @@ |
1 | 1 |
\name{SingleAnnotation} |
2 | 2 |
\alias{SingleAnnotation} |
3 | 3 |
\title{ |
4 |
-Constructor method for SingleAnnotation class |
|
5 |
- |
|
4 |
+Constructor method for SingleAnnotation class |
|
6 | 5 |
|
7 | 6 |
} |
8 | 7 |
\description{ |
9 |
-Constructor method for SingleAnnotation class |
|
10 |
- |
|
8 |
+Constructor method for SingleAnnotation class |
|
11 | 9 |
|
12 | 10 |
} |
13 | 11 |
\usage{ |
14 | 12 |
SingleAnnotation(name, value, col, fun, which = c("column", "row"), |
15 |
- show_legend = TRUE, gp = gpar(col = NA)) |
|
16 |
-} |
|
13 |
+ show_legend = TRUE, gp = gpar(col = NA))} |
|
17 | 14 |
\arguments{ |
18 | 15 |
|
19 | 16 |
\item{name}{name for this annotation.} |
20 | 17 |
\item{value}{A vector of annotation.} |
21 |
- \item{col}{colors corresponding to \code{value}. If the mapping is discrete mapping, the value of \code{col} should be a vector; If the mapping is continuous mapping, the value of \code{col} should be a color mapping function. } |
|
22 |
- \item{fun}{a self-defined function to add annotation graphics. The argument of this function should only be a vector of index that corresponds to rows or columns.} |
|
18 |
+ \item{col}{colors corresponding to \code{value}. If the mapping is discrete mapping, the value of \code{col}should be a vector; If the mapping is continuous mapping, the value of \code{col} should be a color mapping function. } |
|
19 |
+ \item{fun}{a self-defined function to add annotation graphics. The argument of this function should only be a vector of index that corresponds to rows or columns.} |
|
23 | 20 |
\item{which}{is the annotation a row annotation or a column annotation?} |
24 | 21 |
\item{show_legend}{if it is a simple annotation, whether show legend when making the complete heatmap.} |
25 | 22 |
\item{gp}{graphic parameters for simple annotations.} |
26 |
- |
|
27 | 23 |
} |
28 | 24 |
\details{ |
29 |
-The most simple annotation is one row or one column grids in which different colors represent different classes of the data. Here the function use \code{\link{ColorMapping-class}} to process such simple annotation. \code{value} and \code{col} arguments controls values and colors of the simple annotation and a \code{\link{ColorMapping-class}} object will be constructed based on \code{value} and \code{col}. |
|
25 |
+The most simple annotation is one row or one column grids in which different colors |
|
26 |
+represent different classes of the data. Here the function use \code{\link{ColorMapping-class}} |
|
27 |
+to process such simple annotation. \code{value} and \code{col} arguments controls values and colors |
|
28 |
+of the simple annotation and a \code{\link{ColorMapping-class}} object will be constructed based on \code{value} and \code{col}. |
|
30 | 29 |
|
31 |
-\code{fun} is used to construct a more complex annotation. Users can add any type of annotation graphics by implementing a function. The only input argument of \code{fun} is a index of rows or columns which is already adjusted by the clustering. In the package, there are already several annotation graphic function generators: \code{\link{anno_points}}, \code{\link{anno_histogram}} and \code{\link{anno_boxplot}}. |
|
30 |
+\code{fun} is used to construct a more complex annotation. Users can add any type of annotation graphics |
|
31 |
+by implementing a function. The only input argument of \code{fun} is a index |
|
32 |
+of rows or columns which is already adjusted by the clustering. In the package, there are already |
|
33 |
+several annotation graphic function generators: \code{\link{anno_points}}, \code{\link{anno_histogram}} and \code{\link{anno_boxplot}}. |
|
32 | 34 |
|
33 |
-In the case that row annotations are splitted by rows, \code{index} corresponding to row orders in each row-slice and \code{fun} will be applied on each of the row slices. |
|
34 |
- |
|
35 |
-One thing that users should be careful is the difference of coordinates when the annotation is a row annotation or a column annotation. |
|
35 |
+In the case that row annotations are splitted by rows, \code{index} corresponding to row orders in each row-slice |
|
36 |
+and \code{fun} will be applied on each of the row slices. |
|
36 | 37 |
|
38 |
+One thing that users should be careful is the difference of coordinates when the annotation is a row |
|
39 |
+annotation or a column annotation. |
|
37 | 40 |
|
38 | 41 |
} |
39 | 42 |
\value{ |
40 |
-A \code{\link{SingleAnnotation-class}} object. |
|
41 |
- |
|
43 |
+A \code{\link{SingleAnnotation-class}} object. |
|
42 | 44 |
|
43 | 45 |
} |
44 | 46 |
\author{ |
45 |
-Zuguang Gu <z.gu@dkfz.de> |
|
46 |
- |
|
47 |
+Zuguang Gu <z.gu@dkfz.de> |
|
47 | 48 |
|
48 | 49 |
} |
49 | 50 |
\examples{ |
... | ... |
@@ -62,5 +63,4 @@ SingleAnnotation(value = 1:10) |
62 | 63 |
SingleAnnotation(value = 1:10, col = colorRamp2(c(1, 10), c("blue", "red"))) |
63 | 64 |
|
64 | 65 |
# self-defined graphic function |
65 |
-SingleAnnotation(fun = anno_points(1:10)) |
|
66 |
-} |
|
66 |
+SingleAnnotation(fun = anno_points(1:10))} |
... | ... |
@@ -1,39 +1,33 @@ |
1 | 1 |
\name{+.AdditiveUnit} |
2 | 2 |
\alias{+.AdditiveUnit} |
3 | 3 |
\title{ |
4 |
-Add heatmaps or row annotations to a heatmap list |
|
5 |
- |
|
4 |
+Add heatmaps or row annotations to a heatmap list |
|
6 | 5 |
|
7 | 6 |
} |
8 | 7 |
\description{ |
9 |
-Add heatmaps or row annotations to a heatmap list |
|
10 |
- |
|
8 |
+Add heatmaps or row annotations to a heatmap list |
|
11 | 9 |
|
12 | 10 |
} |
13 | 11 |
\usage{ |
14 |
-\method{+}{AdditiveUnit}(x, y) |
|
15 |
-} |
|
12 |
+\method{+}{AdditiveUnit}(x, y)} |
|
16 | 13 |
\arguments{ |
17 | 14 |
|
18 | 15 |
\item{x}{a \code{\link{Heatmap-class}} object, a \code{\link{HeatmapAnnotation-class}} object or a \code{\link{HeatmapList-class}} object.} |
19 | 16 |
\item{y}{a \code{\link{Heatmap-class}} object, a \code{\link{HeatmapAnnotation-class}} object or a \code{\link{HeatmapList-class}} object.} |
20 |
- |
|
21 | 17 |
} |
22 | 18 |
\details{ |
23 |
-It is only a shortcut function. It actually calls \code{\link{add_heatmap,Heatmap-method}}, \code{\link{add_heatmap,HeatmapList-method}} or \code{\link{add_heatmap,HeatmapAnnotation-method}} depending on the class of the input objects. |
|
24 |
- |
|
25 |
-The \code{\link{HeatmapAnnotation-class}} object to be added should only be row annotations. |
|
19 |
+It is only a shortcut function. It actually calls \code{\link{add_heatmap,Heatmap-method}}, \code{\link{add_heatmap,HeatmapList-method}} |
|
20 |
+or \code{\link{add_heatmap,HeatmapAnnotation-method}} depending on the class of the input objects. |
|
26 | 21 |
|
22 |
+The \code{\link{HeatmapAnnotation-class}} object to be added should only be row annotations. |
|
27 | 23 |
|
28 | 24 |
} |
29 | 25 |
\value{ |
30 |
-A \code{\link{HeatmapList-class}} object. |
|
31 |
- |
|
26 |
+A \code{\link{HeatmapList-class}} object. |
|
32 | 27 |
|
33 | 28 |
} |
34 | 29 |
\author{ |
35 |
-Zuguang Gu <z.gu@dkfz.de> |
|
36 |
- |
|
30 |
+Zuguang Gu <z.gu@dkfz.de> |
|
37 | 31 |
|
38 | 32 |
} |
39 | 33 |
\examples{ |
... | ... |
@@ -54,5 +48,4 @@ ha = HeatmapAnnotation(points = anno_points(1:12, which = "row"), |
54 | 48 |
ht + ha |
55 | 49 |
ht_list + ha |
56 | 50 |
|
57 |
-ha + ha + ht |
|
58 |
-} |
|
51 |
+ha + ha + ht} |
... | ... |
@@ -1,37 +1,30 @@ |
1 | 1 |
\name{add_heatmap-Heatmap-method} |
2 | 2 |
\alias{add_heatmap,Heatmap-method} |
3 | 3 |
\title{ |
4 |
-Add heatmaps or row annotations as a heatmap list |
|
5 |
- |
|
4 |
+Add heatmaps or row annotations as a heatmap list |
|
6 | 5 |
|
7 | 6 |
} |
8 | 7 |
\description{ |
9 |
-Add heatmaps or row annotations as a heatmap list |
|
10 |
- |
|
8 |
+Add heatmaps or row annotations as a heatmap list |
|
11 | 9 |
|
12 | 10 |
} |
13 | 11 |
\usage{ |
14 |
-\S4method{add_heatmap}{Heatmap}(object, x) |
|
15 |
-} |
|
12 |
+\S4method{add_heatmap}{Heatmap}(object, x)} |
|
16 | 13 |
\arguments{ |
17 | 14 |
|
18 | 15 |
\item{object}{a \code{\link{Heatmap-class}} object.} |
19 | 16 |
\item{x}{a \code{\link{Heatmap-class}} object, a \code{\link{HeatmapAnnotation-class}} object or a \code{\link{HeatmapList-class}} object.} |
20 |
- |
|
21 | 17 |
} |
22 | 18 |
\details{ |
23 |
-There is a shortcut function \code{+.AdditiveUnit}. |
|
24 |
- |
|
19 |
+There is a shortcut function \code{+.AdditiveUnit}. |
|
25 | 20 |
|
26 | 21 |
} |
27 | 22 |
\value{ |
28 |
-A \code{\link{HeatmapList-class}} object. |
|
29 |
- |
|
23 |
+A \code{\link{HeatmapList-class}} object. |
|
30 | 24 |
|
31 | 25 |
} |
32 | 26 |
\author{ |
33 |
-Zuguang Gu <z.gu@dkfz.de> |
|
34 |
- |
|
27 |
+Zuguang Gu <z.gu@dkfz.de> |
|
35 | 28 |
|
36 | 29 |
} |
37 | 30 |
\examples{ |
... | ... |
@@ -45,5 +38,4 @@ add_heatmap(ht, ht) |
45 | 38 |
|
46 | 39 |
ha = HeatmapAnnotation(points = anno_points(1:12, which = "row"), |
47 | 40 |
which = "row") |
48 |
-add_heatmap(ht, ha) |
|
49 |
-} |
|
41 |
+add_heatmap(ht, ha)} |
... | ... |
@@ -1,37 +1,30 @@ |
1 | 1 |
\name{add_heatmap-HeatmapAnnotation-method} |
2 | 2 |
\alias{add_heatmap,HeatmapAnnotation-method} |
3 | 3 |
\title{ |
4 |
-Add row annotations or heatmaps as a heatmap list |
|
5 |
- |
|
4 |
+Add row annotations or heatmaps as a heatmap list |
|
6 | 5 |
|
7 | 6 |
} |
8 | 7 |
\description{ |
9 |
-Add row annotations or heatmaps as a heatmap list |
|
10 |
- |
|
8 |
+Add row annotations or heatmaps as a heatmap list |
|
11 | 9 |
|
12 | 10 |
} |
13 | 11 |
\usage{ |
14 |
-\S4method{add_heatmap}{HeatmapAnnotation}(object, x) |
|
15 |
-} |
|
12 |
+\S4method{add_heatmap}{HeatmapAnnotation}(object, x)} |
|
16 | 13 |
\arguments{ |
17 | 14 |
|
18 | 15 |
\item{object}{a \code{\link{HeatmapAnnotation-class}} object.} |
19 | 16 |
\item{x}{a \code{\link{Heatmap-class}} object, a \code{\link{HeatmapAnnotation-class}} object or a \code{\link{HeatmapList-class}} object.} |
20 |
- |
|
21 | 17 |
} |
22 | 18 |
\details{ |
23 |
-There is a shortcut function \code{+.AdditiveUnit}. |
|
24 |
- |
|
19 |
+There is a shortcut function \code{+.AdditiveUnit}. |
|
25 | 20 |
|
26 | 21 |
} |
27 | 22 |
\value{ |
28 |
-A \code{\link{HeatmapList-class}} object. |
|
29 |
- |
|
23 |
+A \code{\link{HeatmapList-class}} object. |
|
30 | 24 |
|
31 | 25 |
} |
32 | 26 |
\author{ |
33 |
-Zuguang Gu <z.gu@dkfz.de> |
|
34 |
- |
|
27 |
+Zuguang Gu <z.gu@dkfz.de> |
|
35 | 28 |
|
36 | 29 |
} |
37 | 30 |
\examples{ |
... | ... |
@@ -44,5 +37,4 @@ ht = Heatmap(mat) |
44 | 37 |
|
45 | 38 |
ha = HeatmapAnnotation(points = anno_points(1:12, which = "row"), |
46 | 39 |
which = "row") |
47 |
-add_heatmap(ha, ht) |
|
48 |
-} |
|
40 |
+add_heatmap(ha, ht)} |
... | ... |
@@ -1,37 +1,30 @@ |
1 | 1 |
\name{add_heatmap-HeatmapList-method} |
2 | 2 |
\alias{add_heatmap,HeatmapList-method} |
3 | 3 |
\title{ |
4 |
-Add heatmaps and row annotations to the heatmap list |
|
5 |
- |
|
4 |
+Add heatmaps and row annotations to the heatmap list |
|
6 | 5 |
|
7 | 6 |
} |
8 | 7 |
\description{ |
9 |
-Add heatmaps and row annotations to the heatmap list |
|
10 |
- |
|
8 |
+Add heatmaps and row annotations to the heatmap list |
|
11 | 9 |
|
12 | 10 |
} |
13 | 11 |
\usage{ |
14 |
-\S4method{add_heatmap}{HeatmapList}(object, x) |
|
15 |
-} |
|
12 |
+\S4method{add_heatmap}{HeatmapList}(object, x)} |
|
16 | 13 |
\arguments{ |
17 | 14 |
|
18 | 15 |
\item{object}{a \code{\link{HeatmapList-class}} object.} |
19 | 16 |
\item{x}{a \code{\link{Heatmap-class}} object or a \code{\link{HeatmapAnnotation-class}} object or a \code{\link{HeatmapList-class}} object.} |
20 |
- |
|
21 | 17 |
} |
22 | 18 |
\details{ |
23 |
-There is a shortcut function \code{+.AdditiveUnit}. |
|
24 |
- |
|
19 |
+There is a shortcut function \code{+.AdditiveUnit}. |
|
25 | 20 |
|
26 | 21 |
} |
27 | 22 |
\value{ |
28 |
-A \code{\link{HeatmapList-class}} object. |
|
29 |
- |
|
23 |
+A \code{\link{HeatmapList-class}} object. |
|
30 | 24 |
|
31 | 25 |
} |
32 | 26 |
\author{ |
33 |
-Zuguang Gu <z.gu@dkfz.de> |
|
34 |
- |
|
27 |
+Zuguang Gu <z.gu@dkfz.de> |
|
35 | 28 |
|
36 | 29 |
} |
37 | 30 |
\examples{ |
... | ... |
@@ -46,5 +39,4 @@ add_heatmap(ht_list, ht) |
46 | 39 |