Commit id: 5ad458034f4b9d76d4514db6d764125aed0f3dd3
adjust legends
git-svn-id: https://hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/ComplexHeatmap@106971 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -7,6 +7,7 @@ CHANGES in VERSION 1.2.6 |
7 | 7 |
* insert `k = NULL` into anno_function if they are row annotations |
8 | 8 |
* add a new vignette "quick examples" |
9 | 9 |
* change style for continuous legend color bar |
10 |
+* label order of discrete legend has been adjusted (now it is from top to bottom) |
|
10 | 11 |
|
11 | 12 |
========================================= |
12 | 13 |
|
... | ... |
@@ -276,10 +276,17 @@ setMethod(f = "color_mapping_legend", |
276 | 276 |
x = unit(rep(0, nlevel), "npc") |
277 | 277 |
y = (0:(nlevel-1))*(legend_grid_height) |
278 | 278 |
y = unit(1, "npc") - y |
279 |
- gf = packGrob(gf, row = 2, col = 1, grob = rectGrob(x, rev(y), width = legend_grid_width, height = rev(legend_grid_height), just = c("left", "top"), |
|
280 |
- gp = gpar(col = legend_grid_border, fill = object@colors))) |
|
281 |
- gf = packGrob(gf, row = 2, col = 2, grob = textGrob(object@levels, x + grid_padding, rev(y) - legend_grid_height*0.5, |
|
282 |
- just = c("left", "center"), gp = legend_label_gp), width = grid_padding + legend_label_max_width, force.width = TRUE) |
|
279 |
+ if(object@type == "discrete") { |
|
280 |
+ gf = packGrob(gf, row = 2, col = 2, grob = textGrob(object@levels, x + grid_padding, y - legend_grid_height*0.5, |
|
281 |
+ just = c("left", "center"), gp = legend_label_gp), width = grid_padding + legend_label_max_width, force.width = TRUE) |
|
282 |
+ gf = packGrob(gf, row = 2, col = 1, grob = rectGrob(x, y, width = legend_grid_width, height = legend_grid_height, just = c("left", "top"), |
|
283 |
+ gp = gpar(col = legend_grid_border, fill = object@colors))) |
|
284 |
+ } else { |
|
285 |
+ gf = packGrob(gf, row = 2, col = 2, grob = textGrob(object@levels, x + grid_padding, rev(y) - legend_grid_height*0.5, |
|
286 |
+ just = c("left", "center"), gp = legend_label_gp), width = grid_padding + legend_label_max_width, force.width = TRUE) |
|
287 |
+ gf = packGrob(gf, row = 2, col = 1, grob = rectGrob(x, rev(y), width = legend_grid_width, height = rev(legend_grid_height), just = c("left", "top"), |
|
288 |
+ gp = gpar(col = legend_grid_border, fill = object@colors))) |
|
289 |
+ } |
|
283 | 290 |
} else { |
284 | 291 |
label_height = grobHeight(textGrob("foo", gp = legend_label_gp)) |
285 | 292 |
gf = frameGrob(layout = grid.layout(nrow = 2, ncol = 2, widths = unit.c(legend_grid_width, grid_padding + legend_label_max_width), |
... | ... |
@@ -291,6 +298,8 @@ setMethod(f = "color_mapping_legend", |
291 | 298 |
x = unit(rep(0, nlevel), "npc") |
292 | 299 |
y = seq(0, 1, length = nlevel) * (unit(1, "npc") - label_height) + label_height*0.5 |
293 | 300 |
y = unit(1, "npc") - y |
301 |
+ gf = packGrob(gf, row = 2, col = 2, grob = textGrob(object@levels, x + grid_padding, rev(y), |
|
302 |
+ just = c("left", "center"), gp = legend_label_gp), width = grid_padding + legend_label_max_width, force.width = TRUE, height = (2*nlevel-1)*label_height, force.height = TRUE) |
|
294 | 303 |
|
295 | 304 |
colors = unlist(lapply(seq_len(nlevel-1), function(i) object@col_fun(seq(as.numeric(object@levels[i]), as.numeric(object@levels[i+1]), length = 16)))) |
296 | 305 |
x2 = unit(rep(0, length(colors)), "npc") |
... | ... |
@@ -298,8 +307,7 @@ setMethod(f = "color_mapping_legend", |
298 | 307 |
y2 = y2[-length(y2)] * unit(1, "npc") |
299 | 308 |
gf = packGrob(gf, row = 2, col = 1, grob = rectGrob(x2, rev(y2), width = legend_grid_width, height = (unit(1, "npc"))*(1/length(colors)), just = c("left", "top"), |
300 | 309 |
gp = gpar(col = rev(colors), fill = rev(colors))), height = (2*nlevel-1)*label_height, force.height = TRUE) |
301 |
- gf = packGrob(gf, row = 2, col = 2, grob = textGrob(object@levels, x + grid_padding, rev(y) - label_height*0.5, |
|
302 |
- just = c("left", "center"), gp = legend_label_gp), width = grid_padding + legend_label_max_width, force.width = TRUE, height = (2*nlevel-1)*label_height, force.height = TRUE) |
|
310 |
+ |
|
303 | 311 |
} |
304 | 312 |
|
305 | 313 |
|
... | ... |
@@ -225,9 +225,9 @@ Heatmap = function(matrix, col, name, na_col = "grey", rect_gp = gpar(col = NA), |
225 | 225 |
show_column_names = TRUE, column_names_max_height = unit(4, "cm"), |
226 | 226 |
column_names_gp = gpar(fontsize = 12), |
227 | 227 |
top_annotation = new("HeatmapAnnotation"), |
228 |
- top_annotation_height = unit(5*length(top_annotation@anno_list), "mm"), |
|
228 |
+ top_annotation_height = unit(5*length(top_annotation@anno_list), "mm") + sum(top_annotation@gap), |
|
229 | 229 |
bottom_annotation = new("HeatmapAnnotation"), |
230 |
- bottom_annotation_height = unit(5*length(bottom_annotation@anno_list), "mm"), |
|
230 |
+ bottom_annotation_height = unit(5*length(bottom_annotation@anno_list), "mm") + sum(bottom_annotation@gap), |
|
231 | 231 |
km = 1, split = NULL, gap = unit(1, "mm"), |
232 | 232 |
combined_name_fun = function(x) paste(x, collapse = "/"), |
233 | 233 |
width = NULL, show_heatmap_legend = TRUE, |
... | ... |
@@ -28,7 +28,8 @@ HeatmapAnnotation = setClass("HeatmapAnnotation", |
28 | 28 |
prototype = list( |
29 | 29 |
anno_list = list(), |
30 | 30 |
size = unit(0, "null"), |
31 |
- which = "row" |
|
31 |
+ which = "row", |
|
32 |
+ gap = unit(0, "null") |
|
32 | 33 |
), |
33 | 34 |
contains = "AdditiveUnit" |
34 | 35 |
) |
... | ... |
@@ -126,7 +127,7 @@ HeatmapAnnotation = function(df, name, col, color_bar = rep("discrete", ncol(df) |
126 | 127 |
if(is.null(fun_name)) { |
127 | 128 |
stop("functions should be specified as named arguments.") |
128 | 129 |
} |
129 |
- if(any(fun_name %in% c("df", "col", "show_legend", "which", "height", "width", "annotation_height", "annotation_width", "gp"))) { |
|
130 |
+ if(any(fun_name %in% c("df", "col", "show_legend", "which", "height", "width", "annotation_height", "annotation_width", "gp", "color_bar"))) { |
|
130 | 131 |
stop("function names should be same as other argument names.") |
131 | 132 |
} |
132 | 133 |
|
... | ... |
@@ -137,6 +138,18 @@ HeatmapAnnotation = function(df, name, col, color_bar = rep("discrete", ncol(df) |
137 | 138 |
|
138 | 139 |
n_anno = length(anno_list) |
139 | 140 |
|
141 |
+ if(is.null(gap)) gap = unit(0, "null") |
|
142 |
+ |
|
143 |
+ if(length(gap) == 1) { |
|
144 |
+ .Object@gap = rep(gap, n_anno) |
|
145 |
+ } else if(length(gap) == n_anno - 1) { |
|
146 |
+ .Object@gap = unit.c(gap, unit(0, "null")) |
|
147 |
+ } else if(length(gap) < n_anno - 1) { |
|
148 |
+ stop("Length of `gap` is wrong.") |
|
149 |
+ } else { |
|
150 |
+ .Object@gap = gap |
|
151 |
+ } |
|
152 |
+ |
|
140 | 153 |
anno_size = switch(which, |
141 | 154 |
column = annotation_height, |
142 | 155 |
row = annotation_width) |
... | ... |
@@ -148,7 +161,7 @@ HeatmapAnnotation = function(df, name, col, color_bar = rep("discrete", ncol(df) |
148 | 161 |
} |
149 | 162 |
|
150 | 163 |
if(!is.unit(anno_size)) { |
151 |
- anno_size = unit(anno_size/sum(anno_size), "npc") |
|
164 |
+ anno_size = anno_size/sum(anno_size)*(unit(1, "npc") - sum(.Object@gap)) |
|
152 | 165 |
} |
153 | 166 |
|
154 | 167 |
|
... | ... |
@@ -162,17 +175,7 @@ HeatmapAnnotation = function(df, name, col, color_bar = rep("discrete", ncol(df) |
162 | 175 |
|
163 | 176 |
.Object@size = size |
164 | 177 |
|
165 |
- if(is.null(gap)) gap = unit(0, "null") |
|
166 |
- |
|
167 |
- if(length(gap) == 1) { |
|
168 |
- .Object@gap = rep(gap, n_anno) |
|
169 |
- } else if(length(gap) == n_anno - 1) { |
|
170 |
- .Object@gap = unit.c(gap, unit(0, "null")) |
|
171 |
- } else if(length(gap) < n_anno - 1) { |
|
172 |
- stop("Length of `gap` is wrong.") |
|
173 |
- } else { |
|
174 |
- .Object@gap = gap |
|
175 |
- } |
|
178 |
+ |
|
176 | 179 |
|
177 | 180 |
return(.Object) |
178 | 181 |
} |
... | ... |
@@ -30,9 +30,9 @@ Heatmap(matrix, col, name, na_col = "grey", rect_gp = gpar(col = NA), |
30 | 30 |
show_column_names = TRUE, column_names_max_height = unit(4, "cm"), |
31 | 31 |
column_names_gp = gpar(fontsize = 12), |
32 | 32 |
top_annotation = new("HeatmapAnnotation"), |
33 |
- top_annotation_height = unit(5*length(top_annotation@anno_list), "mm"), |
|
33 |
+ top_annotation_height = unit(5*length(top_annotation@anno_list), "mm") + sum(top_annotation@gap), |
|
34 | 34 |
bottom_annotation = new("HeatmapAnnotation"), |
35 |
- bottom_annotation_height = unit(5*length(bottom_annotation@anno_list), "mm"), |
|
35 |
+ bottom_annotation_height = unit(5*length(bottom_annotation@anno_list), "mm") + sum(bottom_annotation@gap), |
|
36 | 36 |
km = 1, split = NULL, gap = unit(1, "mm"), |
37 | 37 |
combined_name_fun = function(x) paste(x, collapse = "/"), |
38 | 38 |
width = NULL, show_heatmap_legend = TRUE, |
... | ... |
@@ -212,7 +212,8 @@ Heatmap(mat, name = "foo", column_hclust_height = unit(2, "cm")) |
212 | 212 |
There are three ways to specify distance metric for clustering: |
213 | 213 |
|
214 | 214 |
- specify distance as a pre-defined option. The valid values are the supported methods |
215 |
- in `dist()` function and within `pearson`, `spearman` and `kendall`. |
|
215 |
+ in `dist()` function and within `pearson`, `spearman` and `kendall`. `NA` values are ignored |
|
216 |
+ for pre-defined clustering but with giving a warning. |
|
216 | 217 |
- a self-defined function which calculates distance from a matrix. The function should |
217 | 218 |
only contain one argument. Please note for clustering on columns, the matrix will be transposed |
218 | 219 |
automatically. |
... | ... |
@@ -517,7 +518,9 @@ draw(ha, 1:10) |
517 | 518 |
You can combine more than one annotations into the object. |
518 | 519 |
|
519 | 520 |
```{r heatmap_annotation_mixed_with_complex, fig.width = 7, fig.height = 2} |
520 |
-ha = HeatmapAnnotation(df = df, points = anno_points(value)) |
|
521 |
+ha = HeatmapAnnotation(df = df, points = anno_points(value), |
|
522 |
+ col = list(type = c("a" = "red", "b" = "blue"), |
|
523 |
+ age = colorRamp2(c(0, 20), c("white", "red")))) |
|
521 | 524 |
ha |
522 | 525 |
draw(ha, 1:10) |
523 | 526 |
``` |
... | ... |
@@ -529,12 +532,16 @@ annotations shown in the heatmap. |
529 | 532 |
|
530 | 533 |
```{r, fig.width = 7, fig.height = 3} |
531 | 534 |
ha = HeatmapAnnotation(df = df, points = anno_points(value), boxplot = anno_boxplot(mat), |
535 |
+ col = list(type = c("a" = "red", "b" = "blue"), |
|
536 |
+ age = colorRamp2(c(0, 20), c("white", "red"))), |
|
532 | 537 |
annotation_height = c(1, 2, 3, 4)) |
533 | 538 |
draw(ha, 1:10) |
534 | 539 |
``` |
535 | 540 |
|
536 | 541 |
```{r, fig.width = 7, fig.height = 3} |
537 | 542 |
ha = HeatmapAnnotation(df = df, points = anno_points(value), boxplot = anno_boxplot(mat), |
543 |
+ col = list(type = c("a" = "red", "b" = "blue"), |
|
544 |
+ age = colorRamp2(c(0, 20), c("white", "red"))), |
|
538 | 545 |
annotation_height = unit.c((unit(1, "npc") - unit(4, "cm"))*0.5, (unit(1, "npc") - unit(4, "cm"))*0.5, |
539 | 546 |
unit(2, "cm"), unit(2, "cm"))) |
540 | 547 |
draw(ha, 1:10) |
... | ... |
@@ -547,16 +554,29 @@ and `anno_boxplot()` support axes. Please note we didn't allocate space for axes |
547 | 554 |
we only assume there are empty spaces for showing axes. |
548 | 555 |
|
549 | 556 |
```{r add_annotation} |
550 |
-ha = HeatmapAnnotation(df = df, points = anno_points(value)) |
|
557 |
+ha = HeatmapAnnotation(df = df, points = anno_points(value), |
|
558 |
+ col = list(type = c("a" = "red", "b" = "blue"), |
|
559 |
+ age = colorRamp2(c(0, 20), c("white", "red")))) |
|
551 | 560 |
ha_boxplot = HeatmapAnnotation(boxplot = anno_boxplot(mat, axis = TRUE)) |
552 | 561 |
Heatmap(mat, name = "foo", top_annotation = ha, bottom_annotation = ha_boxplot, |
553 | 562 |
bottom_annotation_height = unit(3, "cm")) |
554 | 563 |
``` |
555 | 564 |
|
565 |
+Gaps below each annotation can be specified by `gap` in `HeatmapAnnotation()`. |
|
566 |
+ |
|
567 |
+```{r} |
|
568 |
+ha = HeatmapAnnotation(df = df, points = anno_points(value), gap = unit(c(2, 4), "mm"), |
|
569 |
+ col = list(type = c("a" = "red", "b" = "blue"), |
|
570 |
+ age = colorRamp2(c(0, 20), c("white", "red")))) |
|
571 |
+Heatmap(mat, name = "foo", top_annotation = ha) |
|
572 |
+``` |
|
573 |
+ |
|
556 | 574 |
You can suppress some of the annotation legend by specifying `show_legend` to `FALSE` when creating the `HeatmapAnnotation` object. |
557 | 575 |
|
558 | 576 |
```{r annotation_show} |
559 |
-ha = HeatmapAnnotation(df = df, show_legend = FALSE) |
|
577 |
+ha = HeatmapAnnotation(df = df, show_legend = FALSE, |
|
578 |
+ col = list(type = c("a" = "red", "b" = "blue"), |
|
579 |
+ age = colorRamp2(c(0, 20), c("white", "red")))) |
|
560 | 580 |
Heatmap(mat, name = "foo", top_annotation = ha) |
561 | 581 |
``` |
562 | 582 |
|
... | ... |
@@ -712,7 +732,9 @@ If you don't like the default discrete color bar for legends, you can specify `h |
712 | 732 |
For the simple annotation which contains continuous values, `color_bar` can also be set to `continuous`. |
713 | 733 |
|
714 | 734 |
```{r} |
715 |
-ha = HeatmapAnnotation(df = data.frame(value = runif(10)), color_bar = "continuous") |
|
735 |
+ha = HeatmapAnnotation(df = data.frame(value = runif(10)), |
|
736 |
+ col = list(value = colorRamp2(c(0, 1), c("white", "blue"))), |
|
737 |
+ color_bar = "continuous") |
|
716 | 738 |
Heatmap(mat, name = "ht1", top_annotation = ha, heatmap_legend_color_bar = "continuous") |
717 | 739 |
``` |
718 | 740 |
|
... | ... |
@@ -784,14 +806,15 @@ Row annotation is also defined by the `HeatmapAnnotation` class, but with specif |
784 | 806 |
|
785 | 807 |
```{r row_annotation, fig.width = 1, fig.height = 7} |
786 | 808 |
df = data.frame(type = c(rep("a", 6), rep("b", 6))) |
787 |
-ha = HeatmapAnnotation(df = df, which = "row", width = unit(1, "cm")) |
|
809 |
+ha = HeatmapAnnotation(df = df, col = list(type = c("a" = "red", "b" = "blue")), |
|
810 |
+ which = "row", width = unit(1, "cm")) |
|
788 | 811 |
draw(ha, 1:12) |
789 | 812 |
``` |
790 | 813 |
|
791 | 814 |
There is a shortcut function `rowAnnotation()` which is same as `HeatmapAnnotation(..., which = "row")`. |
792 | 815 |
|
793 | 816 |
```{r, eval = FALSE} |
794 |
-ha = rowAnnotation(df = df, width = unit(1, "cm")) |
|
817 |
+ha = rowAnnotation(df = df, col = list(type = c("a" = "red", "b" = "blue")), width = unit(1, "cm")) |
|
795 | 818 |
``` |
796 | 819 |
|
797 | 820 |
Similar, there can be more than one row annotation. Note in `anno_boxplot()`, `which` is set to `row` |
... | ... |
@@ -799,6 +822,7 @@ to tell that boxplot is calcualted by rows. |
799 | 822 |
|
800 | 823 |
```{r, fig.width = 3, fig.height = 7} |
801 | 824 |
ha_combined = rowAnnotation(df = df, boxplot = anno_boxplot(mat, which = "row"), |
825 |
+ col = list(type = c("a" = "red", "b" = "blue")), |
|
802 | 826 |
annotation_width = c(1, 3)) |
803 | 827 |
draw(ha_combined, 1:12) |
804 | 828 |
``` |
... | ... |
@@ -879,7 +903,7 @@ split row annotaitons: |
879 | 903 |
|
880 | 904 |
```{r all_row_annotations, fig.width = 7} |
881 | 905 |
nr = nrow(mat) |
882 |
-ha = rowAnnotation(df = df, width = NULL) |
|
906 |
+ha = rowAnnotation(df = df, col = list(type = c("a" = "red", "b" = "blue")), width = NULL) |
|
883 | 907 |
text = paste0("row", seq_len(nr)) |
884 | 908 |
ha_text = rowAnnotation(text = anno_text(text, which = "row"), width = max(grobWidth(textGrob(text)))) |
885 | 909 |
Heatmap(matrix(nrow = nr, ncol = 0), split = sample(c("A", "B"), nr, replace = TRUE)) + |
... | ... |
@@ -918,7 +942,8 @@ ha_column1 = HeatmapAnnotation(points = anno_points(rnorm(10))) |
918 | 942 |
ht1 = Heatmap(mat, name = "ht1", km = 2, row_title = "Heatmap 1", column_title = "Heatmap 1", |
919 | 943 |
top_annotation = ha_column1) |
920 | 944 |
|
921 |
-ha_column2 = HeatmapAnnotation(df = data.frame(type = c(rep("a", 5), rep("b", 5)))) |
|
945 |
+ha_column2 = HeatmapAnnotation(df = data.frame(type = c(rep("a", 5), rep("b", 5))), |
|
946 |
+ col = list(type = c("a" = "red", "b" = "blue"))) |
|
922 | 947 |
ht2 = Heatmap(mat, name = "ht2", row_title = "Heatmap 2", column_title = "Heatmap 2", |
923 | 948 |
bottom_annotation = ha_column2) |
924 | 949 |
|
... | ... |
@@ -1023,7 +1048,8 @@ it will be exceeding the figure region. |
1023 | 1048 |
```{r} |
1024 | 1049 |
df = data.frame(type1 = c(rep("a", 5), rep("b", 5)), |
1025 | 1050 |
type2 = c(rep("A", 3), rep("B", 7))) |
1026 |
-ha = HeatmapAnnotation(df) |
|
1051 |
+ha = HeatmapAnnotation(df, col = list(type1 = c("a" = "red", "b" = "blue"), |
|
1052 |
+ type2 = c("A" = "green", "B" = "orange"))) |
|
1027 | 1053 |
Heatmap(mat, name = "ht", top_annotation = ha) |
1028 | 1054 |
for(an in colnames(df)) { |
1029 | 1055 |
seekViewport(qq("annotation_@{an}")) |
... | ... |
@@ -1129,6 +1155,7 @@ Here the package has a `densityHeatmap()` function, the usage is quite straightf |
1129 | 1155 |
```{r, density} |
1130 | 1156 |
matrix = matrix(rnorm(100), 10); colnames(matrix) = letters[1:10] |
1131 | 1157 |
ha = HeatmapAnnotation(df = data.frame(anno = rep(c("A", "B"), each = 5)), |
1158 |
+ col = list(anno = c("A" = "green", "B" = "orange")), |
|
1132 | 1159 |
points = anno_points(runif(10))) |
1133 | 1160 |
densityHeatmap(matrix, anno = ha) |
1134 | 1161 |
``` |
... | ... |
@@ -1,5 +1,6 @@ |
1 | 1 |
library(ComplexHeatmap) |
2 | 2 |
library(circlize) |
3 |
+library(RColorBrewer) |
|
3 | 4 |
|
4 | 5 |
rand_meth = function(k, mean) { |
5 | 6 |
(runif(k) - 0.5)*min(c(1-mean), mean) + mean |
... | ... |
@@ -97,8 +98,8 @@ ht_list = Heatmap(mat_meth, name = "methylation", col = colorRamp2(c(0, 0.5, 1), |
97 | 98 |
Heatmap(mat_expr[, column_tree$order], name = "expression", col = colorRamp2(c(-2, 0, 2), c("green", "white", "red")), |
98 | 99 |
cluster_columns = FALSE, top_annotation = ha2, column_names_gp = gpar(fontsize = 8), column_title = "Expression", column_title_gp = gpar(fontsize = 10)) + |
99 | 100 |
Heatmap(cor_pvalue, name = "-log10(cor_p)", col = colorRamp2(c(0, 2, 4), c("white", "white", "red")), column_names_gp = gpar(fontsize = 8)) + |
100 |
- Heatmap(gene_type, name = "gene type", column_names_gp = gpar(fontsize = 8)) + |
|
101 |
- Heatmap(anno_gene, name = "anno_gene", column_names_gp = gpar(fontsize = 8)) + |
|
101 |
+ Heatmap(gene_type, name = "gene type", col = brewer.pal(length(unique(gene_type)), "Set1"), column_names_gp = gpar(fontsize = 8)) + |
|
102 |
+ Heatmap(anno_gene, name = "anno_gene", col = brewer.pal(length(unique(anno_gene)), "Set2"), column_names_gp = gpar(fontsize = 8)) + |
|
102 | 103 |
Heatmap(dist, name = "dist_tss", col = colorRamp2(c(0, 10000), c("black", "white")), column_names_gp = gpar(fontsize = 8)) + |
103 | 104 |
Heatmap(anno_enhancer, name = "anno_enhancer", col = colorRamp2(c(0, 1), c("white", "orange")), cluster_columns = FALSE, column_names_gp = gpar(fontsize = 8), column_title = "Enhancer", column_title_gp = gpar(fontsize = 10)) |
104 | 105 |
|
... | ... |
@@ -52,5 +52,19 @@ Boston_scaled = apply(Boston, 2, scale) |
52 | 52 |
Heatmap(Boston_scaled, cluster_columns = boston.pv$hclust, heatmap_legend_title = "Boston") |
53 | 53 |
``` |
54 | 54 |
|
55 |
+## Change styles of legend |
|
56 |
+ |
|
57 |
+By default, for both discrete and continuous colors, the legend is represented as a discrete color bar. |
|
58 |
+But continuous colors can also be set to continuous color bar. You can change the legend style both |
|
59 |
+for heatmap legend and simple annotation legend. |
|
60 |
+ |
|
61 |
+```{r} |
|
62 |
+mat = matrix(rnorm(100), 10) |
|
63 |
+ha = HeatmapAnnotation(df = data.frame(value = runif(10)), |
|
64 |
+ col = list(value = colorRamp2(c(0, 1), c("white", "red"))), |
|
65 |
+ color_bar = "continuous") |
|
66 |
+Heatmap(mat, heatmap_legend_title = "mat", heatmap_legend_color_bar = "continuous", |
|
67 |
+ top_annotation = ha) |
|
68 |
+``` |
|
55 | 69 |
|
56 | 70 |
|