... | ... |
@@ -11,7 +11,7 @@ Imports: circlize (>= 0.4.5), GetoptLong, colorspace, clue, |
11 | 11 |
Suggests: testthat (>= 1.0.0), knitr, markdown, dendsort, |
12 | 12 |
Cairo, jpeg, tiff, fastcluster, |
13 | 13 |
dendextend (>= 1.0.1), grImport, grImport2, glue, |
14 |
- GenomicRanges |
|
14 |
+ GenomicRanges, gridtext |
|
15 | 15 |
VignetteBuilder: knitr |
16 | 16 |
Description: Complex heatmaps are efficient to visualize associations |
17 | 17 |
between different sources of data sets and reveal potential patterns. |
... | ... |
@@ -226,31 +226,35 @@ anno_simple = function(x, col, na_col = "grey", |
226 | 226 |
y = (n - seq_len(n) + 0.5) / n |
227 | 227 |
if(is.matrix(value)) { |
228 | 228 |
|
229 |
- nc = ncol(value) |
|
230 |
- pch = pch[index, , drop = FALSE] |
|
231 |
- |
|
232 |
- for(i in seq_len(nc)) { |
|
233 |
- fill = map_to_colors(color_mapping, value[index, i]) |
|
234 |
- grid.rect(x = (i-0.5)/nc, y, height = 1/n, width = 1/nc, |
|
235 |
- gp = do.call("gpar", c(list(fill = fill), gp))) |
|
236 |
- if(!is.null(pch)) { |
|
237 |
- l = !is.na(pch[, i]) |
|
238 |
- grid.points(x = rep((i-0.5)/nc, sum(l)), y = y[l], pch = pch[l, i], |
|
239 |
- size = {if(length(pt_size) == 1) pt_size else pt_size[i]}, |
|
240 |
- gp = subset_gp(pt_gp, i)) |
|
241 |
- } |
|
242 |
- } |
|
229 |
+ nc = ncol(value) |
|
230 |
+ pch = pch[index, , drop = FALSE] |
|
231 |
+ |
|
232 |
+ for(i in seq_len(nc)) { |
|
233 |
+ fill = map_to_colors(color_mapping, value[index, i]) |
|
234 |
+ grid.rect(x = (i-0.5)/nc, y, height = 1/n, width = 1/nc, |
|
235 |
+ gp = do.call("gpar", c(list(fill = fill), gp))) |
|
236 |
+ if(!is.null(pch)) { |
|
237 |
+ l = !is.na(pch[, i]) |
|
238 |
+ if(any(l)) { |
|
239 |
+ grid.points(x = rep((i-0.5)/nc, sum(l)), y = y[l], pch = pch[l, i], |
|
240 |
+ size = {if(length(pt_size) == 1) pt_size else pt_size[i]}, |
|
241 |
+ gp = subset_gp(pt_gp, i)) |
|
242 |
+ } |
|
243 |
+ } |
|
244 |
+ } |
|
243 | 245 |
} else { |
244 |
- fill = map_to_colors(color_mapping, value[index]) |
|
245 |
- grid.rect(x = 0.5, y, height = 1/n, width = 1, gp = do.call("gpar", c(list(fill = fill), gp))) |
|
246 |
- if(!is.null(pch)) { |
|
247 |
- pch = pch[index] |
|
248 |
- pt_size = pt_size[index] |
|
249 |
- pt_gp = subset_gp(pt_gp, index) |
|
250 |
- l = !is.na(pch) |
|
251 |
- grid.points(x = rep(0.5, sum(l)), y = y[l], pch = pch[l], size = pt_size[l], |
|
252 |
- gp = subset_gp(pt_gp, which(l))) |
|
253 |
- } |
|
246 |
+ fill = map_to_colors(color_mapping, value[index]) |
|
247 |
+ grid.rect(x = 0.5, y, height = 1/n, width = 1, gp = do.call("gpar", c(list(fill = fill), gp))) |
|
248 |
+ if(!is.null(pch)) { |
|
249 |
+ pch = pch[index] |
|
250 |
+ pt_size = pt_size[index] |
|
251 |
+ pt_gp = subset_gp(pt_gp, index) |
|
252 |
+ l = !is.na(pch) |
|
253 |
+ if(any(l)) { |
|
254 |
+ grid.points(x = rep(0.5, sum(l)), y = y[l], pch = pch[l], size = pt_size[l], |
|
255 |
+ gp = subset_gp(pt_gp, which(l))) |
|
256 |
+ } |
|
257 |
+ } |
|
254 | 258 |
} |
255 | 259 |
if(border) grid.rect(gp = gpar(fill = "transparent")) |
256 | 260 |
} |
... | ... |
@@ -262,29 +266,33 @@ anno_simple = function(x, col, na_col = "grey", |
262 | 266 |
if(is.matrix(value)) { |
263 | 267 |
|
264 | 268 |
nc = ncol(value) |
265 |
- pch = pch[index, , drop = FALSE] |
|
266 |
- |
|
267 |
- for(i in seq_len(nc)) { |
|
269 |
+ pch = pch[index, , drop = FALSE] |
|
270 |
+ |
|
271 |
+ for(i in seq_len(nc)) { |
|
268 | 272 |
fill = map_to_colors(color_mapping, value[index, i]) |
269 | 273 |
grid.rect(x, y = (nc-i +0.5)/nc, width = 1/n, height = 1/nc, gp = do.call("gpar", c(list(fill = fill), gp))) |
270 |
- if(!is.null(pch)){ |
|
271 |
- l = !is.na(pch[, i]) |
|
272 |
- grid.points(x[l], y = rep((nc-i +0.5)/nc, sum(l)), pch = pch[l, i], |
|
273 |
- size = {if(length(pt_size) == 1) pt_size else pt_size[i]}, |
|
274 |
- gp = subset_gp(pt_gp, i)) |
|
275 |
- } |
|
276 |
- } |
|
274 |
+ if(!is.null(pch)){ |
|
275 |
+ l = !is.na(pch[, i]) |
|
276 |
+ if(any(l)) { |
|
277 |
+ grid.points(x[l], y = rep((nc-i +0.5)/nc, sum(l)), pch = pch[l, i], |
|
278 |
+ size = {if(length(pt_size) == 1) pt_size else pt_size[i]}, |
|
279 |
+ gp = subset_gp(pt_gp, i)) |
|
280 |
+ } |
|
281 |
+ } |
|
282 |
+ } |
|
277 | 283 |
} else { |
278 |
- fill = map_to_colors(color_mapping, value[index]) |
|
279 |
- grid.rect(x, y = 0.5, width = 1/n, height = 1, gp = do.call("gpar", c(list(fill = fill), gp))) |
|
280 |
- if(!is.null(pch)) { |
|
281 |
- pch = pch[index] |
|
282 |
- pt_size = pt_size[index] |
|
283 |
- pt_gp = subset_gp(pt_gp, index) |
|
284 |
- l = !is.na(pch) |
|
285 |
- grid.points(x[l], y = rep(0.5, sum(l)), pch = pch[l], size = pt_size[l], |
|
286 |
- gp = subset_gp(pt_gp, which(l))) |
|
287 |
- } |
|
284 |
+ fill = map_to_colors(color_mapping, value[index]) |
|
285 |
+ grid.rect(x, y = 0.5, width = 1/n, height = 1, gp = do.call("gpar", c(list(fill = fill), gp))) |
|
286 |
+ if(!is.null(pch)) { |
|
287 |
+ pch = pch[index] |
|
288 |
+ pt_size = pt_size[index] |
|
289 |
+ pt_gp = subset_gp(pt_gp, index) |
|
290 |
+ l = !is.na(pch) |
|
291 |
+ if(any(l)) { |
|
292 |
+ grid.points(x[l], y = rep(0.5, sum(l)), pch = pch[l], size = pt_size[l], |
|
293 |
+ gp = subset_gp(pt_gp, which(l))) |
|
294 |
+ } |
|
295 |
+ } |
|
288 | 296 |
} |
289 | 297 |
if(border) grid.rect(gp = gpar(fill = "transparent")) |
290 | 298 |
} |
... | ... |
@@ -1,106 +1,106 @@ |
1 |
-`[.grob` = function(x, i) { |
|
2 |
- x2 = x |
|
3 |
- for(nm in SUBSETABLE_FIELDS[[ intersect(names(SUBSETABLE_FIELDS), class(x)) ]]) { |
|
4 |
- if(inherits(x2[[nm]], "gpar")) { |
|
5 |
- # change to the class defined here |
|
6 |
- class(x2[[nm]]) = "gpar" |
|
7 |
- } |
|
1 |
+# `[.grob` = function(x, i) { |
|
2 |
+# x2 = x |
|
3 |
+# for(nm in SUBSETABLE_FIELDS[[ intersect(names(SUBSETABLE_FIELDS), class(x)) ]]) { |
|
4 |
+# if(inherits(x2[[nm]], "gpar")) { |
|
5 |
+# # change to the class defined here |
|
6 |
+# class(x2[[nm]]) = "gpar" |
|
7 |
+# } |
|
8 | 8 |
|
9 |
- if(length(x2[[nm]]) > 1) { |
|
10 |
- x2[[nm]] = x2[[nm]][i] |
|
11 |
- } |
|
12 |
- } |
|
13 |
- x2 |
|
14 |
-} |
|
9 |
+# if(length(x2[[nm]]) > 1) { |
|
10 |
+# x2[[nm]] = x2[[nm]][i] |
|
11 |
+# } |
|
12 |
+# } |
|
13 |
+# x2 |
|
14 |
+# } |
|
15 | 15 |
|
16 |
-`[.gpar` = function(x, i) { |
|
17 |
- lapply(x, function(y) { |
|
18 |
- if(length(y) > 1) { |
|
19 |
- y[i] |
|
20 |
- } else { |
|
21 |
- y |
|
22 |
- } |
|
23 |
- }) |
|
24 |
-} |
|
16 |
+# `[.gpar` = function(x, i) { |
|
17 |
+# lapply(x, function(y) { |
|
18 |
+# if(length(y) > 1) { |
|
19 |
+# y[i] |
|
20 |
+# } else { |
|
21 |
+# y |
|
22 |
+# } |
|
23 |
+# }) |
|
24 |
+# } |
|
25 | 25 |
|
26 |
-SUBSETABLE_FIELDS = list( |
|
27 |
- "text" = c("label", "x", "y", "gp"), |
|
28 |
- "richtext_grob" = c("gp", "children", "childrenOrder") |
|
29 |
-) |
|
26 |
+# SUBSETABLE_FIELDS = list( |
|
27 |
+# "text" = c("label", "x", "y", "gp"), |
|
28 |
+# "richtext_grob" = c("gp", "children", "childrenOrder") |
|
29 |
+# ) |
|
30 | 30 |
|
31 |
-length.text = function(x) { |
|
32 |
- length(x$label) |
|
33 |
-} |
|
31 |
+# length.text = function(x) { |
|
32 |
+# length(x$label) |
|
33 |
+# } |
|
34 | 34 |
|
35 |
-length.richtext_grob = function(x) { |
|
36 |
- length(x$children) |
|
37 |
-} |
|
35 |
+# length.richtext_grob = function(x) { |
|
36 |
+# length(x$children) |
|
37 |
+# } |
|
38 | 38 |
|
39 |
-update_xy = function (gb, x, y, ...) { |
|
40 |
- UseMethod("update_xy") |
|
41 |
-} |
|
39 |
+# update_xy = function (gb, x, y, ...) { |
|
40 |
+# UseMethod("update_xy") |
|
41 |
+# } |
|
42 | 42 |
|
43 |
-update_xy.text = function(gb, x, y, ...) { |
|
44 |
- n = length(gb$label) |
|
45 |
- if(!missing(x)) { |
|
46 |
- if(n > 1 & length(x) > 1 && n != length(x)) { |
|
47 |
- stop_wrap("Length of `x` should be the same as the length of labels.") |
|
48 |
- } |
|
49 |
- gb$x = x |
|
50 |
- } |
|
51 |
- if(!missing(y)) { |
|
52 |
- if(n > 1 & length(y) > 1 && n != length(y)) { |
|
53 |
- stop_wrap("Length of `y` should be the same as the length of labels.") |
|
54 |
- } |
|
55 |
- gb$y = y |
|
56 |
- } |
|
57 |
- gb |
|
58 |
-} |
|
43 |
+# update_xy.text = function(gb, x, y, ...) { |
|
44 |
+# n = length(gb$label) |
|
45 |
+# if(!missing(x)) { |
|
46 |
+# if(n > 1 & length(x) > 1 && n != length(x)) { |
|
47 |
+# stop_wrap("Length of `x` should be the same as the length of labels.") |
|
48 |
+# } |
|
49 |
+# gb$x = x |
|
50 |
+# } |
|
51 |
+# if(!missing(y)) { |
|
52 |
+# if(n > 1 & length(y) > 1 && n != length(y)) { |
|
53 |
+# stop_wrap("Length of `y` should be the same as the length of labels.") |
|
54 |
+# } |
|
55 |
+# gb$y = y |
|
56 |
+# } |
|
57 |
+# gb |
|
58 |
+# } |
|
59 | 59 |
|
60 |
-update_xy.richtext_grob = function(gb, x, y, ...) { |
|
61 |
- n = length(gb$children) |
|
60 |
+# update_xy.richtext_grob = function(gb, x, y, ...) { |
|
61 |
+# n = length(gb$children) |
|
62 | 62 |
|
63 |
- if(!missing(x)) { |
|
64 |
- if(n > 1 & length(x) > 1 && n != length(x)) { |
|
65 |
- stop_wrap("Length of `x` should be the same as the length of labels.") |
|
66 |
- } |
|
67 |
- for(i in 1:n) { |
|
68 |
- if(length(x) == 1) { |
|
69 |
- gb$children[[i]]$vp$x = x |
|
70 |
- } else { |
|
71 |
- gb$children[[i]]$vp$x = x[i] |
|
72 |
- } |
|
73 |
- } |
|
74 |
- } |
|
75 |
- if(!missing(y)) { |
|
76 |
- if(n > 1 & length(y) > 1 && n != length(y)) { |
|
77 |
- stop_wrap("Length of `y` should be the same as the length of labels.") |
|
78 |
- } |
|
79 |
- for(i in 1:n) { |
|
80 |
- if(length(y) == 1) { |
|
81 |
- gb$children[[i]]$vp$y = y |
|
82 |
- } else { |
|
83 |
- gb$children[[i]]$vp$y = y[i] |
|
84 |
- } |
|
85 |
- } |
|
86 |
- } |
|
87 |
- gb |
|
88 |
-} |
|
63 |
+# if(!missing(x)) { |
|
64 |
+# if(n > 1 & length(x) > 1 && n != length(x)) { |
|
65 |
+# stop_wrap("Length of `x` should be the same as the length of labels.") |
|
66 |
+# } |
|
67 |
+# for(i in 1:n) { |
|
68 |
+# if(length(x) == 1) { |
|
69 |
+# gb$children[[i]]$vp$x = x |
|
70 |
+# } else { |
|
71 |
+# gb$children[[i]]$vp$x = x[i] |
|
72 |
+# } |
|
73 |
+# } |
|
74 |
+# } |
|
75 |
+# if(!missing(y)) { |
|
76 |
+# if(n > 1 & length(y) > 1 && n != length(y)) { |
|
77 |
+# stop_wrap("Length of `y` should be the same as the length of labels.") |
|
78 |
+# } |
|
79 |
+# for(i in 1:n) { |
|
80 |
+# if(length(y) == 1) { |
|
81 |
+# gb$children[[i]]$vp$y = y |
|
82 |
+# } else { |
|
83 |
+# gb$children[[i]]$vp$y = y[i] |
|
84 |
+# } |
|
85 |
+# } |
|
86 |
+# } |
|
87 |
+# gb |
|
88 |
+# } |
|
89 | 89 |
|
90 |
-textGrob = function(label, ...) { |
|
91 |
- if(inherits(label, "grob")) { |
|
92 |
- return(label) |
|
93 |
- } else { |
|
94 |
- grid::textGrob(label, ...) |
|
95 |
- } |
|
96 |
-} |
|
90 |
+# textGrob = function(label, ...) { |
|
91 |
+# if(inherits(label, "grob")) { |
|
92 |
+# return(label) |
|
93 |
+# } else { |
|
94 |
+# grid::textGrob(label, ...) |
|
95 |
+# } |
|
96 |
+# } |
|
97 | 97 |
|
98 |
-grid.text = function(label, x = unit(0.5, "npc"), y = unit(0.5, "npc"), ...) { |
|
99 |
- if(inherits(label, "grob")) { |
|
100 |
- gb = label |
|
101 |
- gb = update_xy(gb, x, y) |
|
102 |
- grid.draw(gb) |
|
103 |
- } else { |
|
104 |
- grid::grid.text(label, x, y, ...) |
|
105 |
- } |
|
106 |
-} |
|
98 |
+# grid.text = function(label, x = unit(0.5, "npc"), y = unit(0.5, "npc"), ...) { |
|
99 |
+# if(inherits(label, "grob")) { |
|
100 |
+# gb = label |
|
101 |
+# gb = update_xy(gb, x, y) |
|
102 |
+# grid.draw(gb) |
|
103 |
+# } else { |
|
104 |
+# grid::grid.text(label, x, y, ...) |
|
105 |
+# } |
|
106 |
+# } |
... | ... |
@@ -184,13 +184,6 @@ for(rot in seq(0, 360, by = 45)) { |
184 | 184 |
draw(anno, test = paste0("rot =", rot)) |
185 | 185 |
} |
186 | 186 |
|
187 |
-##### test anno_richtext #### |
|
188 |
-anno = anno_richtext(richtext_grob(month.name, box_gp = gpar(col = "red"), rot = 90, hjust = 1, y = unit(1, "npc"))) |
|
189 |
-draw(anno, test = "month names") |
|
190 |
-anno = anno_richtext(richtext_grob(month.name, box_gp = gpar(col = "red"), hjust = 0, x = unit(0, "npc")), which = "row") |
|
191 |
-draw(anno, test = "month names") |
|
192 |
- |
|
193 |
- |
|
194 | 187 |
|
195 | 188 |
##### test anno_barplot ##### |
196 | 189 |
anno = anno_barplot(1:10) |
197 | 190 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,34 @@ |
1 |
+ |
|
2 |
+ |
|
3 |
+##### test anno_richtext #### |
|
4 |
+anno = anno_text(month.name) |
|
5 |
+ |
|
6 |
+anno = anno_richtext(richtext_grob(month.name, box_gp = gpar(col = "red"), rot = 90, hjust = 1, y = unit(1, "npc"))) |
|
7 |
+draw(anno, test = "month names") |
|
8 |
+anno = anno_richtext(richtext_grob(month.name, box_gp = gpar(col = "red"), hjust = 0, x = unit(0, "npc")), which = "row") |
|
9 |
+draw(anno, test = "month names") |
|
10 |
+ |
|
11 |
+ |
|
12 |
+reprex({ |
|
13 |
+library(gridtext) |
|
14 |
+library(grid) |
|
15 |
+gb = richtext_grob(month.name, rot = 90, align_widths = FALSE) |
|
16 |
+convertHeight(grobHeight(gb), "mm") |
|
17 |
+gb = richtext_grob(month.name, rot = 90, align_widths = TRUE) |
|
18 |
+convertHeight(grobHeight(gb), "mm") |
|
19 |
+ |
|
20 |
+# only September |
|
21 |
+gb = richtext_grob(month.name[9], rot = 90, align_widths = FALSE) |
|
22 |
+convertHeight(grobHeight(gb), "mm") |
|
23 |
+}) |
|
24 |
+ |
|
25 |
+m = matrix(rnorm(144), 12) |
|
26 |
+rownames(m) = month.name |
|
27 |
+colnames(m) = month.name |
|
28 |
+ |
|
29 |
+Heatmap(m, row_labels = richtext_grob(rownames(m), align_widths = TRUE, box_gp = gpar(col = "red"), x = 0, hjust = 0), |
|
30 |
+ column_labels = richtext_grob(colnames(m), box_gp = gpar(col = "blue"), y = 1, hjust = 1, rot = 90)) |
|
31 |
+ |
|
32 |
+ |
|
33 |
+ |
|
34 |
+Heatmap(m) |
|
0 | 35 |
\ No newline at end of file |