... | ... |
@@ -57,6 +57,7 @@ HeatmapAnnotation = setClass("HeatmapAnnotation", |
57 | 57 |
# -height Height of the complete column annotations. |
58 | 58 |
# -width Width of the complete heatmap annotations. |
59 | 59 |
# -gp Graphic parameters for simple annotations (with ``fill`` parameter ignored). |
60 |
+# -border border of single annotations. |
|
60 | 61 |
# -gap Gap between each two annotation. It can be a single value or a vector of `grid::unit` objects. |
61 | 62 |
# -show_annotation_name Whether show annotation names? For column annotation, annotation names are drawn either on the left |
62 | 63 |
# or the right, and for row annotations, names are draw either on top to at bottom. The value can be a vector. |
... | ... |
@@ -91,6 +92,7 @@ HeatmapAnnotation = function(..., |
91 | 92 |
height = NULL, # total height |
92 | 93 |
width = NULL, # total width |
93 | 94 |
gp = gpar(col = NA), |
95 |
+ border = FALSE, |
|
94 | 96 |
gap = unit(0, "mm"), |
95 | 97 |
show_annotation_name = TRUE, |
96 | 98 |
annotation_name_gp = gpar(), |
... | ... |
@@ -204,18 +206,13 @@ HeatmapAnnotation = function(..., |
204 | 206 |
is_name_rot_called = !missing(annotation_name_rot) |
205 | 207 |
|
206 | 208 |
n_total_anno = length(anno_value_list) |
207 |
- if(length(show_annotation_name) == 1) { |
|
208 |
- show_annotation_name = rep(show_annotation_name, n_total_anno) |
|
209 |
- } |
|
210 |
- if(length(annotation_name_offset) == 1) { |
|
211 |
- annotation_name_offset = rep(annotation_name_offset, n_total_anno) |
|
212 |
- } |
|
213 |
- if(length(annotation_name_side) == 1) { |
|
214 |
- annotation_name_side = rep(annotation_name_side, n_total_anno) |
|
215 |
- } |
|
216 |
- if(length(annotation_name_rot) == 1) { |
|
217 |
- annotation_name_rot = rep(annotation_name_rot, n_total_anno) |
|
218 |
- } |
|
209 |
+ |
|
210 |
+ an = names(anno_value_list) |
|
211 |
+ show_annotation_name = recycle_param(show_annotation_name, an, TRUE) |
|
212 |
+ annotation_name_offset = recycle_param(annotation_name_offset, an, TRUE) |
|
213 |
+ annotation_name_side = recycle_param(annotation_name_side, an, TRUE) |
|
214 |
+ annotation_name_rot = recycle_param(annotation_name_rot, an, TRUE) |
|
215 |
+ border = recycle_param(border, an, FALSE) |
|
219 | 216 |
annotation_name_gp = recycle_gp(annotation_name_gp, n_total_anno) |
220 | 217 |
|
221 | 218 |
if(!missing(col)) { |
... | ... |
@@ -265,7 +262,8 @@ HeatmapAnnotation = function(..., |
265 | 262 |
name_gp = subset_gp(annotation_name_gp, i_anno), |
266 | 263 |
name_offset = annotation_name_offset[i_anno], |
267 | 264 |
name_side = annotation_name_side[i_anno], |
268 |
- name_rot = annotation_name_rot[i_anno]) |
|
265 |
+ name_rot = annotation_name_rot[i_anno], |
|
266 |
+ border = border[i_anno]) |
|
269 | 267 |
if(!is_name_offset_called) { |
270 | 268 |
arg_list$name_rot = NULL |
271 | 269 |
} |
... | ... |
@@ -301,7 +299,7 @@ HeatmapAnnotation = function(..., |
301 | 299 |
} |
302 | 300 |
i_simple = i_simple + 1 |
303 | 301 |
} else { |
304 |
- stop("Annotations should be vector/data frame/matrix/functions.") |
|
302 |
+ stop(paste0(ag, ": annotations should be vector/data frame (only `df`)/matrix/functions.")) |
|
305 | 303 |
} |
306 | 304 |
|
307 | 305 |
} |
... | ... |
@@ -181,6 +181,7 @@ setMethod(f = "adjust_heatmap_list", |
181 | 181 |
object@layout$max_top_component_height = max_top_component_height |
182 | 182 |
object@layout$row_anno_max_bottom_extended = row_anno_max_bottom_extended |
183 | 183 |
object@layout$max_bottom_component_height = max_bottom_component_height |
184 |
+ object@layout$max_title_component_height = max_title_component_height |
|
184 | 185 |
|
185 | 186 |
## left and right |
186 | 187 |
column_anno_max_left_extended = unit(0, "mm") |
... | ... |
@@ -381,6 +382,7 @@ setMethod(f = "adjust_heatmap_list", |
381 | 382 |
object@layout$max_left_component_width = max_left_component_width |
382 | 383 |
object@layout$column_anno_max_right_extended = column_anno_max_right_extended |
383 | 384 |
object@layout$max_right_component_width = max_right_component_width |
385 |
+ object@layout$max_title_component_width = max_title_component_width |
|
384 | 386 |
|
385 | 387 |
## top and bottom |
386 | 388 |
row_anno_max_top_extended = unit(0, "mm") |
... | ... |
@@ -452,11 +454,24 @@ setMethod(f = "draw_heatmap_list", |
452 | 454 |
n = length(object@ht_list) |
453 | 455 |
ht_gap = object@ht_list_param$ht_gap |
454 | 456 |
|
457 |
+# padding = unit(c(0, 0, 0, 0), "mm") |
|
458 |
+ |
|
459 |
+# if((has_heatmap_list_component(object, "heatmap_legend_right") || |
|
460 |
+# has_heatmap_list_component(object, "annotation_legend_right")) && |
|
461 |
+# !has_heatmap_list_component(object, "row_title_right")) { |
|
462 |
+# if(object@layout$column_anno_max_right_extended[[1]] > object@layout$max_right_component_width[[1]]) { |
|
463 |
+# padding[4] = object@layout$column_anno_max_right_extended - object@layout$max_right_component_width + GLOBAL_PADDING[4] |
|
464 |
+# } |
|
465 |
+# } |
|
466 |
+# browser() |
|
467 |
+# pushViewport(viewport(x = padding[2], y = padding[1], width = unit(1, "npc") - padding[2] - padding[4], |
|
468 |
+# height = unit(1, "npc") - padding[1] - padding[3], just = c("left", "bottom"))) |
|
469 |
+ |
|
455 | 470 |
if(object@direction == "horizontal") { |
456 | 471 |
|
457 | 472 |
heatmap_width = object@layout$heatmap_width |
458 |
- max_bottom_component_height = object@layout$max_bottom_component_height |
|
459 |
- max_top_component_height = object@layout$max_top_component_height |
|
473 |
+ max_bottom_component_height = object@layout$max_bottom_component_height + object@layout$max_title_component_height[2] |
|
474 |
+ max_top_component_height = object@layout$max_top_component_height + object@layout$max_title_component_height[1] |
|
460 | 475 |
|
461 | 476 |
if(all(sapply(object@ht_list, function(ht) { |
462 | 477 |
if(inherits(ht, "Heatmap")) { |
... | ... |
@@ -476,7 +491,7 @@ setMethod(f = "draw_heatmap_list", |
476 | 491 |
} |
477 | 492 |
|
478 | 493 |
pushViewport(viewport(name = "main_heatmap_list")) |
479 |
- |
|
494 |
+ |
|
480 | 495 |
i_main = object@ht_list_param$main_heatmap |
481 | 496 |
ht_main = object@ht_list[[i_main]] |
482 | 497 |
slice_y = ht_main@layout$slice$y |
... | ... |
@@ -510,8 +525,8 @@ setMethod(f = "draw_heatmap_list", |
510 | 525 |
upViewport() |
511 | 526 |
} else { |
512 | 527 |
heatmap_height = object@layout$heatmap_height |
513 |
- max_left_component_width = object@layout$max_left_component_width |
|
514 |
- max_right_component_width = object@layout$max_right_component_width |
|
528 |
+ max_left_component_width = object@layout$max_left_component_width + object@layout$max_title_component_width[1] |
|
529 |
+ max_right_component_width = object@layout$max_right_component_width + object@layout$max_title_component_width[2] |
|
515 | 530 |
|
516 | 531 |
if(all(sapply(object@ht_list, function(ht) { |
517 | 532 |
if(inherits(ht, "Heatmap")) { |
... | ... |
@@ -531,7 +546,7 @@ setMethod(f = "draw_heatmap_list", |
531 | 546 |
} |
532 | 547 |
|
533 | 548 |
pushViewport(viewport(name = "main_heatmap_list")) |
534 |
- |
|
549 |
+ |
|
535 | 550 |
i_main = object@ht_list_param$main_heatmap |
536 | 551 |
ht_main = object@ht_list[[i_main]] |
537 | 552 |
slice_x = ht_main@layout$slice$x |
... | ... |
@@ -564,6 +579,7 @@ setMethod(f = "draw_heatmap_list", |
564 | 579 |
|
565 | 580 |
upViewport() |
566 | 581 |
} |
582 |
+ # upViewport() |
|
567 | 583 |
|
568 | 584 |
}) |
569 | 585 |
|
... | ... |
@@ -401,7 +401,7 @@ draw_legend = function(ColorMappingList, ColorMappingParamList, side = c("right" |
401 | 401 |
} else if(side == "top") { |
402 | 402 |
draw(pk, y = unit(1, "npc"), just = "top") |
403 | 403 |
} else if(side == "bottom") { |
404 |
- draw(pk, y = unit(0, "npc"), just = "bottom") |
|
404 |
+ draw(pk, y = unit(1, "npc"), just = "top") |
|
405 | 405 |
} |
406 | 406 |
} |
407 | 407 |
|
... | ... |
@@ -66,6 +66,7 @@ SingleAnnotation = setClass("SingleAnnotation", |
66 | 66 |
# -show_legend If it is a simple annotation, whether show legend in the final heatmap? |
67 | 67 |
# -gp Since simple annotation is represented as rows of grids. This argument controls graphic parameters for the simple annotation. |
68 | 68 |
# The ``fill`` parameter is ignored here. |
69 |
+# -border border, only work for simple annotation |
|
69 | 70 |
# -legend_param Parameters for the legend. See `color_mapping_legend,ColorMapping-method` for all possible options. |
70 | 71 |
# -show_name Whether show annotation name? |
71 | 72 |
# -name_gp Graphic parameters for annotation name. |
... | ... |
@@ -143,6 +144,7 @@ SingleAnnotation = function(name, value, col, fun, |
143 | 144 |
which = c("column", "row"), |
144 | 145 |
show_legend = TRUE, |
145 | 146 |
gp = gpar(col = NA), |
147 |
+ border = FALSE, |
|
146 | 148 |
legend_param = list(), |
147 | 149 |
show_name = TRUE, |
148 | 150 |
name_gp = gpar(fontsize = 12), |
... | ... |
@@ -453,7 +455,7 @@ SingleAnnotation = function(name, value, col, fun, |
453 | 455 |
value = value |
454 | 456 |
|
455 | 457 |
if(verbose) qqcat("@{name}: generate AnnotationFunction for simple annotation values by anno_simple()\n") |
456 |
- .Object@fun = anno_simple(value, col = color_mapping, which = which, na_col = na_col, gp = gp) |
|
458 |
+ .Object@fun = anno_simple(value, col = color_mapping, which = which, na_col = na_col, gp = gp, border = border) |
|
457 | 459 |
if(missing(width)) { |
458 | 460 |
.Object@width = .Object@fun@width |
459 | 461 |
} else { |
... | ... |
@@ -7,8 +7,6 @@ |
7 | 7 |
# -density_param Parameters send to `stats::density`, ``na.rm`` is enforced to be ``TRUE``. |
8 | 8 |
# -col A vector of colors that density values are mapped to. |
9 | 9 |
# -color_space The color space in which colors are interpolated. Pass to `circlize::colorRamp2`. |
10 |
-# -top_annotation A `HeatmapAnnotation-class` object which is put on top of the heatmap. |
|
11 |
-# -bottom_annotation A `HeatmapAnnotation-class` object which is put at bottom of the heatmap. |
|
12 | 10 |
# -ylab Label on y-axis. |
13 | 11 |
# -column_title Title of the heatmap. |
14 | 12 |
# -title Same as ``column_title``. |
... | ... |
@@ -58,8 +56,6 @@ densityHeatmap = function(data, |
58 | 56 |
|
59 | 57 |
col = rev(brewer.pal(11, "Spectral")), |
60 | 58 |
color_space = "LAB", |
61 |
- top_annotation = NULL, |
|
62 |
- bottom_annotation = NULL, |
|
63 | 59 |
ylab = deparse(substitute(data)), |
64 | 60 |
column_title = paste0("Density heatmap of ", deparse(substitute(data))), |
65 | 61 |
title = column_title, |
... | ... |
@@ -474,3 +474,31 @@ normalize_graphic_param_to_mat = function(x, nc, nr, name) { |
474 | 474 |
} |
475 | 475 |
} |
476 | 476 |
} |
477 |
+ |
|
478 |
+recycle_param = function(x, all_names, default) { |
|
479 |
+ n = length(all_names) |
|
480 |
+ if(length(x) == n) { |
|
481 |
+ return(x) |
|
482 |
+ } else { |
|
483 |
+ nm = names(x) |
|
484 |
+ if(length(intersect(nm, all_names)) == 0) { |
|
485 |
+ nm = NULL |
|
486 |
+ } |
|
487 |
+ if(is.null(nm)) { |
|
488 |
+ if(length(x) == 1) { |
|
489 |
+ x = rep(x, n) |
|
490 |
+ } else { |
|
491 |
+ if(length(x) > n) { |
|
492 |
+ x = x[1:n] |
|
493 |
+ } else { |
|
494 |
+ x = c(x, rep(default, n - length(x))) |
|
495 |
+ } |
|
496 |
+ } |
|
497 |
+ } else { |
|
498 |
+ x2 = structure(rep(default, n), names = all_names) |
|
499 |
+ x2[intersect(nm, all_names)] = x[intersect(nm, all_names)] |
|
500 |
+ x = x2 |
|
501 |
+ } |
|
502 |
+ return(x) |
|
503 |
+ } |
|
504 |
+} |
477 | 505 |
similarity index 91% |
478 | 506 |
rename from vignettes/generate_random_dataset.R |
479 | 507 |
rename to inst/extdata/generate_random_dataset.R |
... | ... |
@@ -11,7 +11,7 @@ anno = data.frame(type = type, gender = gender, age = age, mutation, stringsAsFa |
11 | 11 |
|
12 | 12 |
anno_col = list(type = c("Tumor" = "red", "Control" = "blue"), |
13 | 13 |
gender = c("F" = "pink", "M" = "darkgreen"), |
14 |
- mutation = c("TRUE" = "black", "FALSE" = "white")) |
|
14 |
+ mutation = c("TRUE" = "black", "FALSE" = "#EEEEEE")) |
|
15 | 15 |
|
16 | 16 |
###################################### |
17 | 17 |
# generate methylation matrix |
... | ... |
@@ -50,9 +50,9 @@ dimnames(mat_expr) = dimnames(mat_meth) |
50 | 50 |
|
51 | 51 |
############################################################# |
52 | 52 |
# matrix for correlation between methylation and expression |
53 |
-cor_pvalue = -log10(sapply(seq_len(nrow(mat_meth)), function(i) { |
|
53 |
+cor_pvalue = sapply(seq_len(nrow(mat_meth)), function(i) { |
|
54 | 54 |
cor.test(mat_meth[i, ], mat_expr[i, ])$p.value |
55 |
-})) |
|
55 |
+}) |
|
56 | 56 |
|
57 | 57 |
##################################################### |
58 | 58 |
# matrix for types of genes |
... | ... |
@@ -120,5 +120,7 @@ rand_repressive = function(m) { |
120 | 120 |
anno_states = data.frame( |
121 | 121 |
tss = sapply(mean_meth, rand_tss), |
122 | 122 |
enhancer = sapply(mean_meth, rand_enhancer), |
123 |
- rand_repressive = sapply(mean_meth, rand_repressive)) |
|
123 |
+ repressive = sapply(mean_meth, rand_repressive)) |
|
124 | 124 |
|
125 |
+save(mat_meth, mat_expr, anno, anno_col, anno_states, cor_pvalue, direction, |
|
126 |
+ anno_gene, gene_type, tss_dist, file = "random_meth_expr_data.RData") |
... | ... |
@@ -17,6 +17,7 @@ HeatmapAnnotation(..., |
17 | 17 |
height = NULL, # total height |
18 | 18 |
width = NULL, # total width |
19 | 19 |
gp = gpar(col = NA), |
20 |
+ border = FALSE, |
|
20 | 21 |
gap = unit(0, "mm"), |
21 | 22 |
show_annotation_name = TRUE, |
22 | 23 |
annotation_name_gp = gpar(), |
... | ... |
@@ -39,6 +40,7 @@ HeatmapAnnotation(..., |
39 | 40 |
\item{height}{Height of the complete column annotations.} |
40 | 41 |
\item{width}{Width of the complete heatmap annotations.} |
41 | 42 |
\item{gp}{Graphic parameters for simple annotations (with \code{fill} parameter ignored).} |
43 |
+ \item{border}{border of single annotations.} |
|
42 | 44 |
\item{gap}{Gap between each two annotation. It can be a single value or a vector of \code{\link[grid]{unit}} objects.} |
43 | 45 |
\item{show_annotation_name}{Whether show annotation names? For column annotation, annotation names are drawn either on the left or the right, and for row annotations, names are draw either on top to at bottom. The value can be a vector.} |
44 | 46 |
\item{annotation_name_gp}{Graphic parameters for anntation names. Graphic paramters can be vectors.} |
... | ... |
@@ -12,6 +12,7 @@ SingleAnnotation(name, value, col, fun, |
12 | 12 |
which = c("column", "row"), |
13 | 13 |
show_legend = TRUE, |
14 | 14 |
gp = gpar(col = NA), |
15 |
+ border = FALSE, |
|
15 | 16 |
legend_param = list(), |
16 | 17 |
show_name = TRUE, |
17 | 18 |
name_gp = gpar(fontsize = 12), |
... | ... |
@@ -30,6 +31,7 @@ SingleAnnotation(name, value, col, fun, |
30 | 31 |
\item{which}{Whether the annotation is a row annotation or a column annotation?} |
31 | 32 |
\item{show_legend}{If it is a simple annotation, whether show legend in the final heatmap?} |
32 | 33 |
\item{gp}{Since simple annotation is represented as rows of grids. This argument controls graphic parameters for the simple annotation. The \code{fill} parameter is ignored here.} |
34 |
+ \item{border}{border, only work for simple annotation} |
|
33 | 35 |
\item{legend_param}{Parameters for the legend. See \code{\link{color_mapping_legend,ColorMapping-method}} for all possible options.} |
34 | 36 |
\item{show_name}{Whether show annotation name?} |
35 | 37 |
\item{name_gp}{Graphic parameters for annotation name.} |
... | ... |
@@ -12,8 +12,6 @@ densityHeatmap(data, |
12 | 12 |
|
13 | 13 |
col = rev(brewer.pal(11, "Spectral")), |
14 | 14 |
color_space = "LAB", |
15 |
- top_annotation = NULL, |
|
16 |
- bottom_annotation = NULL, |
|
17 | 15 |
ylab = deparse(substitute(data)), |
18 | 16 |
column_title = paste0("Density heatmap of ", deparse(substitute(data))), |
19 | 17 |
title = column_title, |
... | ... |
@@ -41,8 +39,6 @@ densityHeatmap(data, |
41 | 39 |
\item{density_param}{Parameters send to \code{\link[stats]{density}}, \code{na.rm} is enforced to be \code{TRUE}.} |
42 | 40 |
\item{col}{A vector of colors that density values are mapped to.} |
43 | 41 |
\item{color_space}{The color space in which colors are interpolated. Pass to \code{\link[circlize]{colorRamp2}}.} |
44 |
- \item{top_annotation}{A \code{\link{HeatmapAnnotation-class}} object which is put on top of the heatmap.} |
|
45 |
- \item{bottom_annotation}{A \code{\link{HeatmapAnnotation-class}} object which is put at bottom of the heatmap.} |
|
46 | 42 |
\item{ylab}{Label on y-axis.} |
47 | 43 |
\item{column_title}{Title of the heatmap.} |
48 | 44 |
\item{title}{Same as \code{column_title}.} |
... | ... |
@@ -12,6 +12,10 @@ Common use of ComplexHeatmap package |
12 | 12 |
|
13 | 13 |
------------------------------------------------------------- |
14 | 14 |
|
15 |
+In this vignette we only show the most used cases of the ComplexHeatmap package. |
|
16 |
+ComplexHeatmap package is highly flexible and users can find the complete reference |
|
17 |
+in [](). |
|
18 |
+ |
|
15 | 19 |
```{r global_settings, echo = FALSE, message = FALSE} |
16 | 20 |
library(markdown) |
17 | 21 |
options(markdown.HTML.options = c(options('markdown.HTML.options')[[1]], "toc")) |
... | ... |
@@ -26,16 +30,121 @@ knitr::opts_chunk$set( |
26 | 30 |
options(markdown.HTML.stylesheet = "custom.css") |
27 | 31 |
|
28 | 32 |
options(width = 100) |
33 |
+ |
|
34 |
+library(circlize) |
|
35 |
+library(ComplexHeatmap) |
|
29 | 36 |
``` |
30 | 37 |
|
38 |
+First we load the circlize package and ComplexHeatmap package. The circlize |
|
39 |
+package is used very often with ComplexHeatmap for generating color mapping |
|
40 |
+functions. |
|
41 |
+ |
|
31 | 42 |
```{r} |
32 | 43 |
library(circlize) |
33 | 44 |
library(ComplexHeatmap) |
45 |
+``` |
|
34 | 46 |
|
35 |
-source("generate_random_dataset.R") |
|
47 |
+In the vignette, we demonstrate ComplexHeatmap package with a randomly |
|
48 |
+generated DNA methylation data and gene expression data. |
|
49 |
+ |
|
50 |
+```{r} |
|
51 |
+load(system.file("extdata", "random_meth_expr_data.RData", package = "ComplexHeatmap")) |
|
36 | 52 |
``` |
37 | 53 |
|
38 |
-# A Single Heatmap with annotations |
|
54 |
+The data variables are: |
|
55 |
+ |
|
56 |
+- `mat_meth`: The methylation matrix for 1000 DMRs in 20 samples. The value in |
|
57 |
+ the matrix is the mean methylation of all CpGs in a DMR. |
|
58 |
+- `mat_expr`: The gene expression matrix. The $i^th$ row is the gene having |
|
59 |
+ the closest TSS to the $i^th$ DMR in `mat_meth`. The samples are the same as in `mat_meth`. |
|
60 |
+ |
|
61 |
+The annotation variables for samples are: |
|
62 |
+ |
|
63 |
+- `anno`: The annotation data frame. There are five annotations: |
|
64 |
+ - `type`: Whether the sample is a tumor sample or a control sample. |
|
65 |
+ - `gender`: Whether the patient is a male or female. There are two `NA` |
|
66 |
+ values in it. |
|
67 |
+ - `age`: Age of the patient. It is a numeric annotation. |
|
68 |
+ - `mut1` and `mut2`: Whether the sample has mutation for the two genes. |
|
69 |
+ The value is logical. |
|
70 |
+- `anno_col`: The color of annotations in `anno`. |
|
71 |
+ |
|
72 |
+```{r} |
|
73 |
+anno |
|
74 |
+anno_col |
|
75 |
+``` |
|
76 |
+ |
|
77 |
+The annotation variables for DMRs or the associated genes are: |
|
78 |
+ |
|
79 |
+- `direction`: The direction of methylation, i.e. whether the DMR is |
|
80 |
+ hyper-methylated in tumor? |
|
81 |
+- `cor_pvalue`: The p-value for the correlation test between DMR methylation |
|
82 |
+ and gene expression. |
|
83 |
+- `gene_type`: Gene types, e.g. protein-coding gene, or lincRNA. |
|
84 |
+- `tss_dist`: The distance from DMR to the nearest TSS. |
|
85 |
+- `anno_gene`: Annotation to genes, e.g. TSS, intragenic, intergenic. |
|
86 |
+- `anno_states`: The value is how much percent in a DMR is covered by a |
|
87 |
+ certain chromatin states. There are three different chromatin states in this |
|
88 |
+ data frame: active TSS state, enhancer state and repressive state. |
|
89 |
+ |
|
90 |
+You may find we didn't set the colors for the annotations of DMRs or genes, we |
|
91 |
+will demonstrate how random colors are assigned to them if the colors are not |
|
92 |
+set. |
|
93 |
+ |
|
94 |
+In real case, this set of data types is very common for many epigenomic |
|
95 |
+researches, which always have data of DNA methylation, gene expression and |
|
96 |
+histone modifications, or some of them. We will show here how ComplexHeatmap |
|
97 |
+package easily helps the integrative analysis of multiple datasets to find the |
|
98 |
+associations hiding behind it. |
|
99 |
+ |
|
100 |
+## A Single Heatmap with annotations |
|
101 |
+ |
|
102 |
+A single heatmap is the most used way to visualize matrix-like data. |
|
103 |
+ |
|
104 |
+Drawing a heatmap is straightforward. The only mandatory argument is the |
|
105 |
+matrix. However, a heatmap can have different components: names or labels by |
|
106 |
+the heatmap, the dendrograms, the annotations for rows or columns and the |
|
107 |
+title of the heatmap. All these components can be added by `Heatmap()` |
|
108 |
+function. The `Heatmap()` function has huge number of arguments which give |
|
109 |
+exact control of the heatmap components and users can refer to ... |
|
110 |
+ |
|
111 |
+In following example, we added column and row dendrogram, column annotations |
|
112 |
+and column names. The dendrograms and row/columns names are natural to add. If |
|
113 |
+the matrix has row names or column names, they are added to the heatmap by |
|
114 |
+default, and clustering is turned on, dendrograms are also added to the |
|
115 |
+heatmap. |
|
116 |
+ |
|
117 |
+Annotations are a little bit complex to configure. Because the aim of ComplexHeatmap |
|
118 |
+package is to provide a flexible way to control many types of annotations, the package |
|
119 |
+has a `HeatmapAnnotation()` function to properly construct heatmap annotations. |
|
120 |
+ |
|
121 |
+In following, apart from `col` and `annotation_legend_param`, all other |
|
122 |
+arguments specify single annotations and they are combined as a global heatmap |
|
123 |
+annotation. The simplest annotation is heatmap-like annotation for which you |
|
124 |
+only to specify it as a numeric or character vector (e.g. the `type` and |
|
125 |
+`gender` annotation). The heatmap-like annotation can also be a matrix (e.g. |
|
126 |
+`mutation` annotation) that the annotation will be represented as a multi-row |
|
127 |
+or multi-column annotation and they share one color mapping schema. Moreover, |
|
128 |
+the annotation can be so-called "complex annotations" that it is defined by a |
|
129 |
+annotation function. A annotation function is defined by users and basically |
|
130 |
+users can draw whatever they want. |
|
131 |
+ |
|
132 |
+In ComplexHeatmap package, there are already several pre-defined annotation functions. |
|
133 |
+In following, `anno_points()` generates an annotation function given the data and the |
|
134 |
+settings (check the returned value of `anno_points(1:10)`). |
|
135 |
+ |
|
136 |
+Colors for the legends are controlled by `col`. `col` can only control colors for |
|
137 |
+"simple annotations" which are specified by a vector or a matrix. The value of `col` |
|
138 |
+should be a named list where the name in `col` should correspond to the names of |
|
139 |
+the annotations (e.g. `mutation` in following example) because that is the way to |
|
140 |
+connect `col` to individual annotations. The discrete annotations (e.g. in character) |
|
141 |
+have the color as a named vector and the continous annotations have color as a |
|
142 |
+color mapping function which is generated by `circlize::colorRmap2()`. You can check |
|
143 |
+the value of `anno_col` for example. |
|
144 |
+ |
|
145 |
+In following code, we also customized the legend for the mutation annotation because |
|
146 |
+the labels or the levels in `mutation` is `TRUE` and `FALSE` and we change to `has mutation` |
|
147 |
+and `no mutation`. |
|
39 | 148 |
|
40 | 149 |
```{r} |
41 | 150 |
Heatmap(mat_meth, name = "methylation", |
... | ... |
@@ -44,72 +153,211 @@ Heatmap(mat_meth, name = "methylation", |
44 | 153 |
gender = anno$gender, |
45 | 154 |
age = anno_points(anno$age, ylim = c(0, 80)), |
46 | 155 |
mutation = as.matrix(anno[, c("mut1", "mut2")]), |
47 |
- col = anno_col |
|
156 |
+ col = anno_col, |
|
157 |
+ border = c(mutation = TRUE), |
|
158 |
+ annotation_legend_param = list( |
|
159 |
+ mutation = list( |
|
160 |
+ at = c("TRUE", "FALSE"), |
|
161 |
+ labels = c("has mutation", "no mutation") |
|
162 |
+ )) |
|
48 | 163 |
), column_title = "Differential Methylated Regions") |
49 | 164 |
``` |
50 | 165 |
|
166 |
+As you may notice, the legends are arranged into two columns. The reason for |
|
167 |
+doing this is we always assume the matrix itself gives the major information, |
|
168 |
+especially when you have several heatmaps add horizontally, while the column |
|
169 |
+annotations give the secondary information. However, if you want to merge the |
|
170 |
+heatmap legends and annotaiton legends, you need to explicitly draw the |
|
171 |
+heatmap by `draw()` function and specify `merge_legends = TRUE`. |
|
172 |
+ |
|
173 |
+Also, as mentioned before, the heatmap has components on the four sides. We |
|
174 |
+can set the title to the left of the heatmap by setting `row_title` and we put |
|
175 |
+the annotation to the bottom of the heatmap by switching to |
|
176 |
+`bottom_annotation`. we can also control the side of the annotation name to |
|
177 |
+the left by setting the `annotation_name_side` argument in |
|
178 |
+`HeatmapAnnotation()`. |
|
179 |
+ |
|
51 | 180 |
```{r} |
52 |
-Heatmap(mat_meth, name = "methylation", |
|
53 |
- top_annotation = HeatmapAnnotation( |
|
181 |
+ht = Heatmap(mat_meth, name = "methylation", |
|
182 |
+ bottom_annotation = HeatmapAnnotation( |
|
54 | 183 |
df = anno, |
55 | 184 |
annotation_name_side = "left" |
56 |
- ), column_title = "Differential Methylated Regions") |
|
185 |
+ ), row_title = "Differential Methylated Regions") |
|
186 |
+draw(ht, merge_legends = TRUE) |
|
57 | 187 |
``` |
58 | 188 |
|
189 |
+We can also set the left and right annotation which is similar as top and |
|
190 |
+bottom annotation. The main difference is you need to use `rowAnnotation()` |
|
191 |
+or `HeatmapAnntation(..., which = "row")` to construct the row annotations. |
|
192 |
+the `anno_*()` functions, if you specify them inside `rowAnnotation()`, you |
|
193 |
+don't need to ... |
|
194 |
+ |
|
59 | 195 |
```{r} |
60 | 196 |
Heatmap(mat_meth, name = "methylation", |
61 | 197 |
top_annotation = HeatmapAnnotation( |
62 |
- df = anno, |
|
63 |
- col = anno_col, |
|
64 |
- annotation_name_side = "left" |
|
198 |
+ type = anno$type, |
|
199 |
+ gender = anno$gender, |
|
200 |
+ age = anno_points(anno$age, ylim = c(0, 80)), |
|
201 |
+ col = anno_col |
|
65 | 202 |
), |
66 | 203 |
right_annotation = rowAnnotation( |
67 | 204 |
anno_gene = anno_gene, |
68 |
- tss_dist = anno_points(tss_dist), |
|
69 |
- col = list(anno_gene = anno_gene_col) |
|
205 |
+ tss_dist = anno_points(tss_dist, size = unit(0.5, "mm"), |
|
206 |
+ width = unit(2, "cm")) |
|
70 | 207 |
), |
71 | 208 |
column_title = "Differential Methylated Regions") |
72 | 209 |
``` |
73 | 210 |
|
211 |
+ComplexHeatmap package supports to split heatmaps by rows or/and by columns. |
|
212 |
+The split can be applied by k-means clustering, by cutting the dendrograms, |
|
213 |
+or by a categorical data frame. In following example, we simply split the |
|
214 |
+heatmap into 2 groups horizontally and 4 groups vertically. |
|
74 | 215 |
|
75 |
-```{r} |
|
76 |
-Heatmap(mat_meth, name = "methylation", |
|
77 |
- top_annotation = HeatmapAnnotation( |
|
78 |
- type = anno$type, |
|
79 |
- gender = anno$gender, |
|
80 |
- age = anno_points(anno$age, ylim = c(0, 80)), |
|
81 |
- mutation = as.matrix(anno[, c("mut1", "mut2")]), |
|
82 |
- col = anno_col |
|
83 |
- ), |
|
216 |
+```{r, fig.width = 8} |
|
217 |
+ht = Heatmap(mat_meth, name = "methylation", |
|
84 | 218 |
right_annotation = rowAnnotation( |
219 |
+ direction = direction, |
|
220 |
+ pvalue = -log10(cor_pvalue), |
|
85 | 221 |
anno_gene = anno_gene, |
86 |
- tss_dist = anno_points(tss_dist), |
|
87 |
- col = list(anno_gene = anno_gene_col) |
|
222 |
+ gene_type = gene_type, |
|
223 |
+ tss_dist = anno_points(tss_dist, size = unit(0.5, "mm"), |
|
224 |
+ width = unit(2, "cm")), |
|
225 |
+ states = as.matrix(anno_states), |
|
226 |
+ col = list( |
|
227 |
+ pvalue = colorRamp2(c(0, 2, 4), c("green", "white", "red")), |
|
228 |
+ states = colorRamp2(c(0, 1), c("white", "orange"))), |
|
229 |
+ annotation_legend_param = list( |
|
230 |
+ pvalue = list(at = c(0, 2, 4), labels = c("1", "0.01", "0.0001"))) |
|
88 | 231 |
), |
89 | 232 |
show_column_names = FALSE, |
90 | 233 |
column_title = "Differential Methylated Regions", |
91 | 234 |
column_km = 2, row_km = 4) |
235 |
+draw(ht) |
|
92 | 236 |
``` |
93 | 237 |
|
238 |
+When k-means splitting and data frame splitting are both provided, they are combined. |
|
239 |
+ |
|
240 |
+```{r, fig.width = 8} |
|
241 |
+draw(ht, row_km = 2, row_split = direction) |
|
242 |
+``` |
|
94 | 243 |
|
95 | 244 |
## Heatmap List |
96 | 245 |
|
246 |
+One unique advantage of ComplexHeatmap is it supports adding a list of heatmaps and annotations. |
|
247 |
+"+" operator is for horizontal add. |
|
248 |
+ |
|
249 |
+ |
|
97 | 250 |
```{r} |
98 | 251 |
meth_col_fun = colorRamp2(c(0, 0.5, 1), c("blue", "white", "red")) |
99 | 252 |
expr_col_fun = colorRamp2(c(-2, 0, 2), c("green", "white", "red")) |
100 |
-ht_list = Heatmap(mat_meth, name = "methylation", col = meth_col_fun) + |
|
101 |
- Heatmap(mat_expr, name = "epxression", col = expr_col_fun) |
|
253 |
+ht_list = Heatmap(mat_meth, name = "methylation", col = meth_col_fun, |
|
254 |
+ column_title = "Methylation") + |
|
255 |
+ Heatmap(mat_expr, name = "epxression", col = expr_col_fun, |
|
256 |
+ column_title = "Expression") |
|
257 |
+draw(ht_list, row_km = 4) |
|
258 |
+``` |
|
259 |
+ |
|
260 |
+As memtioned, row anntations can be attached to the heatmap by `left_annotation` or |
|
261 |
+by `right_annotation`. Actually they can also be separated and add to the heatmaps. |
|
262 |
+so `Heatmap(..., left_annotation = rowAnnotation(...))` is similar as `Heatmap(...) + rowAnnotation(...)`. |
|
263 |
+ |
|
264 |
+```{r} |
|
265 |
+ht_list = Heatmap(mat_meth, name = "methylation", col = meth_col_fun, |
|
266 |
+ column_title = "Methylation") + |
|
267 |
+ Heatmap(mat_expr, name = "epxression", col = expr_col_fun, |
|
268 |
+ column_title = "Expression") + |
|
269 |
+ rowAnnotation(anno_gene = anno_gene, |
|
270 |
+ tss_dist = anno_points(tss_dist, size = unit(0.5, "mm"), |
|
271 |
+ width = unit(2, "cm")) |
|
272 |
+ ) |
|
102 | 273 |
draw(ht_list, row_km = 4) |
103 | 274 |
``` |
104 | 275 |
|
276 |
+ComplexHeatmap also supports add heatmap vertically, you just need to change the add operator |
|
277 |
+to `%v%`. |
|
105 | 278 |
|
106 | 279 |
```{r} |
107 |
-ht_list = Heatmap(mat_meth[1:40, ], name = "methylation", col = meth_col_fun) %v% |
|
108 |
- Heatmap(mat_expr[1:40, ], name = "epxression", col = expr_col_fun) |
|
280 |
+ht_list = Heatmap(mat_meth[1:40, ], name = "methylation", col = meth_col_fun, |
|
281 |
+ row_km = 2, row_title = "Methylation", show_column_names = FALSE) %v% |
|
282 |
+ Heatmap(mat_expr[1:40, ], name = "epxression", col = expr_col_fun, |
|
283 |
+ row_km = 2, row_title = "Expression") |
|
109 | 284 |
draw(ht_list, column_km = 2) |
110 | 285 |
``` |
111 | 286 |
|
112 |
-## OncoPrint |
|
287 |
+And similar, column annotations can be separated from teh heatmap and add to the list. |
|
288 |
+ |
|
289 |
+```{r} |
|
290 |
+ht_list = Heatmap(mat_meth[1:40, ], name = "methylation", col = meth_col_fun, |
|
291 |
+ row_km = 2, row_title = "Methylation", show_column_names = FALSE) %v% |
|
292 |
+ columnAnnotation( |
|
293 |
+ type = anno$type, |
|
294 |
+ gender = anno$gender, |
|
295 |
+ age = anno_points(anno$age, ylim = c(0, 80)), |
|
296 |
+ mutation = as.matrix(anno[, c("mut1", "mut2")]), |
|
297 |
+ col = anno_col, |
|
298 |
+ annotation_name_side = "left" |
|
299 |
+ ) %v% |
|
300 |
+ Heatmap(mat_expr[1:40, ], name = "epxression", col = expr_col_fun, |
|
301 |
+ row_km = 2, row_title = "Expression") |
|
302 |
+draw(ht_list, column_km = 2) |
|
303 |
+``` |
|
113 | 304 |
|
114 | 305 |
## Density as a heatmap |
115 | 306 |
|
307 |
+```{r} |
|
308 |
+densityHeatmap(mat_meth[1:40, ], ylab = "methylation values", |
|
309 |
+ title = "Methylation distribution in samples") |
|
310 |
+``` |
|
311 |
+ |
|
312 |
+```{r, fig.height = 10} |
|
313 |
+densityHeatmap(mat_meth[1:40, ], ylab = "methylation values", |
|
314 |
+ show_column_names = FALSE, |
|
315 |
+ title = "Methylation distribution in samples", |
|
316 |
+ top_annotation = HeatmapAnnotation(type = anno$type, col = anno_col)) %v% |
|
317 |
+columnAnnotation( |
|
318 |
+ gender = anno$gender, |
|
319 |
+ age = anno_points(anno$age, ylim = c(0, 80)), |
|
320 |
+ col = anno_col |
|
321 |
+) %v% |
|
322 |
+Heatmap(mat_expr[1:40, ], name = "epxression", col = expr_col_fun, |
|
323 |
+ row_km = 2, row_title = "Expression", heatmap_body_height = unit(6, "cm")) |
|
324 |
+``` |
|
325 |
+ |
|
326 |
+## OncoPrint |
|
327 |
+ |
|
328 |
+```{r, fig.width = 10} |
|
329 |
+mat = readRDS(system.file("extdata", "tcga_lung_adenocarcinoma_provisional_ras_raf_mek_jnk_signalling.rds", |
|
330 |
+ package = "ComplexHeatmap")) |
|
331 |
+alter_fun = list( |
|
332 |
+ background = function(x, y, w, h) { |
|
333 |
+ grid.rect(x, y, w-unit(0.5, "mm"), h-unit(0.5, "mm"), gp = gpar(fill = "#CCCCCC", col = NA)) |
|
334 |
+ }, |
|
335 |
+ HOMDEL = function(x, y, w, h) { |
|
336 |
+ grid.rect(x, y, w-unit(0.5, "mm"), h-unit(0.5, "mm"), gp = gpar(fill = "blue", col = NA)) |
|
337 |
+ }, |
|
338 |
+ AMP = function(x, y, w, h) { |
|
339 |
+ grid.rect(x, y, w-unit(0.5, "mm"), h-unit(0.5, "mm"), gp = gpar(fill = "red", col = NA)) |
|
340 |
+ }, |
|
341 |
+ MUT = function(x, y, w, h) { |
|
342 |
+ grid.rect(x, y, w-unit(0.5, "mm"), h*0.33, gp = gpar(fill = "#008000", col = NA)) |
|
343 |
+ } |
|
344 |
+) |
|
345 |
+col = c("MUT" = "#008000", "AMP" = "red", "HOMDEL" = "blue") |
|
346 |
+oncoPrint(mat, get_type = function(x) strsplit(x, ";")[[1]], |
|
347 |
+ alter_fun = alter_fun, col = col, |
|
348 |
+ remove_empty_columns = TRUE, remove_empty_rows = TRUE, |
|
349 |
+ column_title = "OncoPrint for TCGA Lung Adenocarcinoma, genes in Ras Raf MEK JNK signalling", |
|
350 |
+ heatmap_legend_param = list(title = "Alternations", at = c("AMP", "HOMDEL", "MUT"), |
|
351 |
+ labels = c("Amplification", "Deep deletion", "Mutation"))) |
|
352 |
+``` |
|
353 |
+ |
|
354 |
+ |
|
355 |
+ |
|
356 |
+## Stacked plot |
|
357 |
+ |
|
358 |
+## Session Info |
|
359 |
+ |
|
360 |
+```{r} |
|
361 |
+sessionInfo() |
|
362 |
+``` |
|
363 |
+ |
116 | 364 |
deleted file mode 100755 |
... | ... |
@@ -1,36 +0,0 @@ |
1 |
-<!-- |
|
2 |
-%\VignetteEngine{knitr} |
|
3 |
-%\VignetteIndexEntry{7. Interactive with Heatmaps} |
|
4 |
- |
|
5 |
-Interactive with Heatmaps |
|
6 |
-======================================== |
|
7 |
- |
|
8 |
-**Author**: Zuguang Gu ( z.gu@dkfz.de ) |
|
9 |
- |
|
10 |
-**Date**: `r Sys.Date()` |
|
11 |
- |
|
12 |
- |
|
13 |
-```{r global_settings, echo = FALSE, message = FALSE} |
|
14 |
-library(markdown) |
|
15 |
- |
|
16 |
-library(knitr) |
|
17 |
-knitr::opts_chunk$set( |
|
18 |
- error = FALSE, |
|
19 |
- tidy = FALSE, |
|
20 |
- message = FALSE, |
|
21 |
- fig.align = "center", |
|
22 |
- fig.width = 5, |
|
23 |
- fig.height = 5) |
|
24 |
-options(markdown.HTML.stylesheet = "custom.css") |
|
25 |
- |
|
26 |
-options(width = 100) |
|
27 |
-``` |
|
28 |
- |
|
29 |
-If the heatmap is plotted in the interactive graphic device, users can use mouse |
|
30 |
-to select a sub-area in the heatmap and retrieve index for rows and columns in that selected area. |
|
31 |
-Since heatmaps are always used to visualize patterns that are clustered together, |
|
32 |
-this feature can greatly give convinience to extract the sub-matrix that users are interested in. |
|
33 |
- |
|
34 |
-<p><img src="select_region.gif" width="600" /></p> |