Commit id: 2ce5060f81b028cc27862c97f7a2bae0607abb65
add gaps between heatmap components
git-svn-id: https://hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/ComplexHeatmap@103994 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -992,13 +992,13 @@ setMethod(f = "draw_hclust", |
992 | 992 |
pushViewport(viewport(name = paste(object@name, which, "cluster", sep = "_"), ...)) |
993 | 993 |
|
994 | 994 |
if(side == "left") { |
995 |
- grid.dendrogram(dend, name = paste(object@name, "hclust_row", k, sep = "_"), max_height = max_height, facing = "right", order = "reverse", x = unit(1, "mm"), width = unit(1, "npc") - unit(1, "mm"), just = "left") |
|
995 |
+ grid.dendrogram(dend, name = paste(object@name, "hclust_row", k, sep = "_"), max_height = max_height, facing = "right", order = "reverse", x = unit(1, "mm"), width = unit(1, "npc") - unit(3, "mm"), just = "left") |
|
996 | 996 |
} else if(side == "right") { |
997 |
- grid.dendrogram(dend, name = paste(object@name, "hclust_row", k, sep = "_"), max_height = max_height, facing = "left", order = "reverse", x = unit(0, "null"), width = unit(1, "npc") - unit(1, "mm"), just = "left") |
|
997 |
+ grid.dendrogram(dend, name = paste(object@name, "hclust_row", k, sep = "_"), max_height = max_height, facing = "left", order = "reverse", x = unit(0, "null"), width = unit(1, "npc") - unit(3, "mm"), just = "left") |
|
998 | 998 |
} else if(side == "top") { |
999 |
- grid.dendrogram(dend, name = paste(object@name, "hclust_column", sep = "_"), max_height = max_height, facing = "bottom", y = unit(0, "null"), height = unit(1, "npc") - unit(1, "mm"), just = "bottom") |
|
999 |
+ grid.dendrogram(dend, name = paste(object@name, "hclust_column", sep = "_"), max_height = max_height, facing = "bottom", y = unit(2, "mm"), height = unit(1, "npc") - unit(3, "mm"), just = "bottom") |
|
1000 | 1000 |
} else if(side == "bottom") { |
1001 |
- grid.dendrogram(dend, name = paste(object@name, "hclust_column", sep = "_"), max_height = max_height, facing = "top", y = unit(1, "mm"), height = unit(1, "npc") - unit(1, "mm"), just = "bottom") |
|
1001 |
+ grid.dendrogram(dend, name = paste(object@name, "hclust_column", sep = "_"), max_height = max_height, facing = "top", y = unit(1, "mm"), height = unit(1, "npc") - unit(3, "mm"), just = "bottom") |
|
1002 | 1002 |
} |
1003 | 1003 |
|
1004 | 1004 |
upViewport() |
... | ... |
@@ -1171,7 +1171,11 @@ setMethod(f = "draw_annotation", |
1171 | 1171 |
return(invisible(NULL)) |
1172 | 1172 |
} |
1173 | 1173 |
|
1174 |
- draw(annotation, index = object@column_order) |
|
1174 |
+ if(which == "top") { |
|
1175 |
+ draw(annotation, index = object@column_order, y = unit(2, "mm"), height = unit(1, "npc") - unit(2, "mm"), just = "bottom") |
|
1176 |
+ } else { |
|
1177 |
+ draw(annotation, index = object@column_order, y = unit(0, "null"), height = unit(1, "npc") - unit(2, "mm"), just = "bottom") |
|
1178 |
+ } |
|
1175 | 1179 |
}) |
1176 | 1180 |
|
1177 | 1181 |
# == title |
... | ... |
@@ -40,7 +40,7 @@ HeatmapAnnotation = setClass("HeatmapAnnotation", |
40 | 40 |
# |
41 | 41 |
# == param |
42 | 42 |
# -df a data frame. Each column will be treated as a simple annotation. The data frame must have column names. |
43 |
-# -name name of the heatmap annotation |
|
43 |
+# -name name of the heatmap annotation, optional. |
|
44 | 44 |
# -col a list of colors which contains color mapping to columns in ``df``. See `SingleAnnotation` for how to set colors. |
45 | 45 |
# -show_legend whether show legend for each column in ``df``. |
46 | 46 |
# -... functions which define complex annotations. Values should be named arguments. |
... | ... |
@@ -54,7 +54,7 @@ HeatmapAnnotation = setClass("HeatmapAnnotation", |
54 | 54 |
# |
55 | 55 |
# == details |
56 | 56 |
# The simple annotations are defined by ``df`` and ``col`` arguments. Complex annotations are |
57 |
-# defined by the function list. |
|
57 |
+# defined by the function list. So you need to at least to define ``df` or a annotation function. |
|
58 | 58 |
# |
59 | 59 |
# == value |
60 | 60 |
# A `HeatmapAnnotation-class` object. |
... | ... |
@@ -65,7 +65,7 @@ HeatmapAnnotation = setClass("HeatmapAnnotation", |
65 | 65 |
# == author |
66 | 66 |
# Zuguang Gu <z.gu@dkfz.de> |
67 | 67 |
# |
68 |
-HeatmapAnnotation = function(df, name, col, show_legend, ..., |
|
68 |
+HeatmapAnnotation = function(df, name, col, show_legend = rep(TRUE, n_anno), ..., |
|
69 | 69 |
which = c("column", "row"), annotation_height = 1, annotation_width = 1, |
70 | 70 |
height = unit(1, "cm"), width = unit(1, "cm"), gp = gpar(col = NA), |
71 | 71 |
gap = unit(0, "null")) { |
... | ... |
@@ -90,9 +90,6 @@ HeatmapAnnotation = function(df, name, col, show_legend, ..., |
90 | 90 |
anno_name = colnames(df) |
91 | 91 |
n_anno = ncol(df) |
92 | 92 |
|
93 |
- if(missing(show_legend)) { |
|
94 |
- show_legend = rep(TRUE, n_anno) |
|
95 |
- } |
|
96 | 93 |
if(length(show_legend) == 1) { |
97 | 94 |
show_legend = rep(show_legend, n_anno) |
98 | 95 |
} |
... | ... |
@@ -111,6 +108,9 @@ HeatmapAnnotation = function(df, name, col, show_legend, ..., |
111 | 108 |
} |
112 | 109 |
} |
113 | 110 |
} |
111 |
+ if(which == "column") { |
|
112 |
+ anno_list = rev(anno_list) |
|
113 |
+ } |
|
114 | 114 |
|
115 | 115 |
# self-defined anntatoin graph are passed by a list of named functions |
116 | 116 |
fun_list = list(...) |
... | ... |
@@ -518,6 +518,7 @@ setMethod(f = "make_layout", |
518 | 518 |
# |
519 | 519 |
# == param |
520 | 520 |
# -object a `HeatmapList-class` object |
521 |
+# -padding padding of the plot. Elements correspond to bottom, left, top, right paddings. |
|
521 | 522 |
# -... pass to `make_layout,HeatmapList-method` |
522 | 523 |
# -newpage whether to create a new page |
523 | 524 |
# |
... | ... |
@@ -535,7 +536,7 @@ setMethod(f = "make_layout", |
535 | 536 |
# |
536 | 537 |
setMethod(f = "draw", |
537 | 538 |
signature = "HeatmapList", |
538 |
- definition = function(object, ..., newpage= TRUE) { |
|
539 |
+ definition = function(object, padding = unit(c(2, 2, 2, 2), "mm"), ..., newpage= TRUE) { |
|
539 | 540 |
|
540 | 541 |
if(! any(sapply(object@ht_list, inherits, "Heatmap"))) { |
541 | 542 |
stop("There should be at least one Heatmap in the heatmap list.") |
... | ... |
@@ -547,8 +548,17 @@ setMethod(f = "draw", |
547 | 548 |
|
548 | 549 |
object = make_layout(object, ...) |
549 | 550 |
|
551 |
+ if(length(padding) == 1) { |
|
552 |
+ padding = rep(padding, 4) |
|
553 |
+ } else if(length(padding) == 2) { |
|
554 |
+ padding = rep(padding, 2) |
|
555 |
+ } else if(length(padding) != 4) { |
|
556 |
+ stop("`padding` can only have length of 1, 2, 4") |
|
557 |
+ } |
|
558 |
+ |
|
550 | 559 |
layout = grid.layout(nrow = 7, ncol = 7, widths = component_width(object, 1:7), heights = component_height(object, 1:7)) |
551 |
- pushViewport(viewport(layout = layout, name = "global")) |
|
560 |
+ pushViewport(viewport(layout = layout, name = "global", width = unit(1, "npc") - padding[2] - padding[4], |
|
561 |
+ height = unit(1, "npc") - padding[1] - padding[3])) |
|
552 | 562 |
ht_layout_index = object@layout$layout_index |
553 | 563 |
ht_graphic_fun_list = object@layout$graphic_fun_list |
554 | 564 |
|
... | ... |
@@ -1097,6 +1107,8 @@ draw_legend = function(ColorMappingList, side = c("right", "left", "top", "botto |
1097 | 1107 |
|
1098 | 1108 |
if(side %in% c("left", "right")) { |
1099 | 1109 |
|
1110 |
+ ColorMappingList = rev(ColorMappingList) |
|
1111 |
+ |
|
1100 | 1112 |
width = max(cm_width) |
1101 | 1113 |
height = sum(cm_height) + gap*(n + length(annotation_legend_list) -1) |
1102 | 1114 |
|
... | ... |
@@ -49,7 +49,7 @@ default_col = function(x, main_matrix = FALSE) { |
49 | 49 |
|
50 | 50 |
if(is.character(x)) { # discrete |
51 | 51 |
levels = unique(x) |
52 |
- colors = rainbow_hcl(length(levels), c = 60, l = 75) |
|
52 |
+ colors = hsv(runif(length(levels)), runif(length(levels)), 1) |
|
53 | 53 |
names(colors) = levels |
54 | 54 |
return(colors) |
55 | 55 |
} else if(is.numeric(x)) { |
... | ... |
@@ -60,7 +60,7 @@ default_col = function(x, main_matrix = FALSE) { |
60 | 60 |
col_fun = colorRamp2(seq(min(x), max(x), length.out = 100), diverge_hcl(100, c = 100, l = c(50, 90), power = 1)) |
61 | 61 |
} |
62 | 62 |
} else { |
63 |
- col_fun = colorRamp2(range(min(x), max(x)), c("white", rainbow_hcl(1, c = 60, l = 75))) |
|
63 |
+ col_fun = colorRamp2(range(min(x), max(x)), c("white", hsv(runif(1), runif(1), 1))) |
|
64 | 64 |
} |
65 | 65 |
return(col_fun) |
66 | 66 |
} |