1 | 1 |
deleted file mode 100644 |
... | ... |
@@ -1,577 +0,0 @@ |
1 |
- |
|
2 |
-normalize_graphic_param_to_mat(1, nc = 2, nr = 4, "foo") |
|
3 |
-normalize_graphic_param_to_mat(1:2, nc = 2, nr = 4, "foo") |
|
4 |
-normalize_graphic_param_to_mat(1:4, nc = 2, nr = 4, "foo") |
|
5 |
- |
|
6 |
-### AnnotationFunction constructor ##### |
|
7 |
-fun = function(index) { |
|
8 |
- x = runif(10) |
|
9 |
- pushViewport(viewport(xscale = c(0.5, 10.5), yscale = c(0, 1))) |
|
10 |
- grid.points(index, x[index]) |
|
11 |
- popViewport() |
|
12 |
-} |
|
13 |
-anno = AnnotationFunction(fun = fun) |
|
14 |
- |
|
15 |
-x = runif(10) |
|
16 |
-fun = function(index) { |
|
17 |
- pushViewport(viewport(xscale = c(0.5, 10.5), yscale = c(0, 1))) |
|
18 |
- grid.points(index, x[index]) |
|
19 |
- popViewport() |
|
20 |
-} |
|
21 |
-anno = AnnotationFunction(fun = fun, var_imported = "x") |
|
22 |
-anno = AnnotationFunction(fun = fun, var_imported = list(x)) |
|
23 |
- |
|
24 |
- |
|
25 |
-devAskNewPage(ask = TRUE) |
|
26 |
- |
|
27 |
-########### testing anno_simple ############ |
|
28 |
-anno = anno_simple(1:10) |
|
29 |
-draw(anno, test = "as a simple vector") |
|
30 |
-draw(anno[1:5], test = "subset of column annotation") |
|
31 |
-anno = anno_simple(1:10, which = "row") |
|
32 |
-draw(anno, test = "as row annotation") |
|
33 |
-draw(anno[1:5], test = "subste of row annotation") |
|
34 |
- |
|
35 |
-anno = anno_simple(1:10, col = structure(rand_color(10), names = 1:10)) |
|
36 |
-draw(anno, test = "self-define colors") |
|
37 |
- |
|
38 |
-anno = anno_simple(1:10, border = TRUE) |
|
39 |
-draw(anno, test = "border") |
|
40 |
-anno = anno_simple(1:10, gp = gpar(col = "red")) |
|
41 |
-draw(anno, test = "gp for the grids") |
|
42 |
- |
|
43 |
-anno = anno_simple(c(1:9, NA)) |
|
44 |
-draw(anno, test = "vector has NA values") |
|
45 |
- |
|
46 |
-anno = anno_simple(cbind(1:10, 10:1)) |
|
47 |
-draw(anno, test = "a matrix") |
|
48 |
-draw(anno[1:5], test = "subste of a matrix") |
|
49 |
- |
|
50 |
-anno = anno_simple(1:10, pch = 1, pt_gp = gpar(col = "red"), pt_size = unit(seq(1, 10), "mm")) |
|
51 |
-draw(anno, test = "with symbols + pt_gp + pt_size") |
|
52 |
-anno = anno_simple(1:10, pch = 1:10) |
|
53 |
-draw(anno, test = "pch is a vector") |
|
54 |
-anno = anno_simple(1:10, pch = c(1:4, NA, 6:8, NA, 10, 11)) |
|
55 |
-draw(anno, test = "pch has NA values") |
|
56 |
- |
|
57 |
-anno = anno_simple(cbind(1:10, 10:1), pch = 1, pt_gp = gpar(col = "blue")) |
|
58 |
-draw(anno, test = "matrix with symbols") |
|
59 |
-anno = anno_simple(cbind(1:10, 10:1), pch = 1:2) |
|
60 |
-draw(anno, test = "matrix, length of pch is number of annotations") |
|
61 |
-anno = anno_simple(cbind(1:10, 10:1), pch = 1:10) |
|
62 |
-draw(anno, test = "matrix, length of pch is length of samples") |
|
63 |
-anno = anno_simple(cbind(1:10, 10:1), pch = matrix(1:20, nc = 2)) |
|
64 |
-draw(anno, test = "matrix, pch is a matrix") |
|
65 |
-pch = matrix(1:20, nc = 2) |
|
66 |
-pch[sample(length(pch), 10)] = NA |
|
67 |
-anno = anno_simple(cbind(1:10, 10:1), pch = pch) |
|
68 |
-draw(anno, test = "matrix, pch is a matrix with NA values") |
|
69 |
- |
|
70 |
- |
|
71 |
-####### test anno_empty ###### |
|
72 |
-anno = anno_empty() |
|
73 |
-draw(anno, test = "anno_empty") |
|
74 |
-anno = anno_empty(border = FALSE) |
|
75 |
-draw(anno, test = "anno_empty without border") |
|
76 |
- |
|
77 |
-###### test anno_image ##### |
|
78 |
-image1 = sample(dir("~/Downloads/IcoMoon-Free-master/PNG/64px", full.names = TRUE), 10) |
|
79 |
-anno = anno_image(image1) |
|
80 |
-draw(anno, test = "png") |
|
81 |
-draw(anno[1:5], test = "subset of png") |
|
82 |
-anno = anno_image(image1, which = "row") |
|
83 |
-draw(anno, test = "png on rows") |
|
84 |
-image2 = sample(dir("~/Downloads/IcoMoon-Free-master/SVG/", full.names = TRUE), 10) |
|
85 |
-anno = anno_image(image2) |
|
86 |
-draw(anno, test = "svg") |
|
87 |
-image3 = sample(dir("~/Downloads/IcoMoon-Free-master/EPS/", full.names = TRUE), 10) |
|
88 |
-anno = anno_image(image3) |
|
89 |
-draw(anno, test = "eps") |
|
90 |
-image4 = sample(dir("~/Downloads/IcoMoon-Free-master/PDF/", full.names = TRUE), 10) |
|
91 |
-anno = anno_image(image4) |
|
92 |
-draw(anno, test = "pdf") |
|
93 |
- |
|
94 |
-anno = anno_image(c(image1[1:3], image2[1:3], image3[1:3], image4[1:3])) |
|
95 |
-draw(anno, test = "png+svg+eps+pdf") |
|
96 |
- |
|
97 |
-anno = anno_image(image1, gp = gpar(fill = 1:10, col = "black")) |
|
98 |
-draw(anno, test = "png + gp") |
|
99 |
-draw(anno[1:5], test = "png + gp") |
|
100 |
- |
|
101 |
-anno = anno_image(image1, space = unit(3, "mm")) |
|
102 |
-draw(anno, test = "space") |
|
103 |
- |
|
104 |
-image1[1] = "" |
|
105 |
-anno = anno_image(image1) |
|
106 |
-draw(anno, test = "png") |
|
107 |
- |
|
108 |
-######## test anno_points ##### |
|
109 |
-anno = anno_points(runif(10)) |
|
110 |
-draw(anno, test = "anno_points") |
|
111 |
-anno = anno_points(matrix(runif(20), nc = 2), pch = 1:2) |
|
112 |
-draw(anno, test = "matrix") |
|
113 |
-anno = anno_points(c(1:5, 1:5)) |
|
114 |
-draw(anno, test = "anno_points") |
|
115 |
-anno = anno_points(cbind(c(1:5, 1:5), c(5:1, 5:1)), gp = gpar(col = 2:3)) |
|
116 |
-draw(anno, test = "matrix") |
|
117 |
- |
|
118 |
-anno = anno_points(1:10, gp = gpar(col = rep(2:3, each = 5)), pch = rep(2:3, each = 5)) |
|
119 |
-draw(anno, test = "anno_points") |
|
120 |
-draw(anno, index = c(1, 3, 5, 7, 9, 2, 4, 6, 8, 10), test = "anno_points") |
|
121 |
- |
|
122 |
-anno = anno_points(c(1:5, NA, 7:10)) |
|
123 |
-draw(anno, test = "anno_points") |
|
124 |
- |
|
125 |
- |
|
126 |
-anno = anno_points(runif(10), axis_param = list(direction = "reverse"), ylim = c(0, 1)) |
|
127 |
-draw(anno, test = "anno_points") |
|
128 |
- |
|
129 |
-anno = anno_points(runif(10), axis_param = list(direction = "reverse"), ylim = c(0, 1), which = "row") |
|
130 |
-draw(anno, test = "anno_points") |
|
131 |
- |
|
132 |
-# pch as image |
|
133 |
-image1 = sample(dir("/desktop-home/guz/Downloads/IcoMoon-Free-master/PNG/64px", full.names = TRUE), 10) |
|
134 |
-x = runif(10) |
|
135 |
-anno1 = anno_points(x, pch = image1, pch_as_image = TRUE, size = unit(5, "mm"), height = unit(4, "cm")) |
|
136 |
-anno2 = anno_points(x, height = unit(4, "cm")) |
|
137 |
-draw(anno1, test = "anno_points") |
|
138 |
-draw(anno2, test = "anno_points") |
|
139 |
- |
|
140 |
-##### test anno_lines ### |
|
141 |
-anno = anno_lines(runif(10)) |
|
142 |
-draw(anno, test = "anno_lines") |
|
143 |
-anno = anno_lines(cbind(c(1:5, 1:5), c(5:1, 5:1)), gp = gpar(col = 2:3)) |
|
144 |
-draw(anno, test = "matrix") |
|
145 |
-anno = anno_lines(cbind(c(1:5, 1:5), c(5:1, 5:1)), gp = gpar(col = 2:3), |
|
146 |
- add_points = TRUE, pt_gp = gpar(col = 5:6), pch = c(1, 16)) |
|
147 |
-draw(anno, test = "matrix") |
|
148 |
-anno = anno_lines(sort(rnorm(10)), height = unit(2, "cm"), smooth = TRUE, add_points = TRUE) |
|
149 |
-draw(anno, test = "anno_lines, smooth") |
|
150 |
-anno = anno_lines(cbind(sort(rnorm(10)), sort(rnorm(10), decreasing = TRUE)), |
|
151 |
- height = unit(2, "cm"), smooth = TRUE, add_points = TRUE, gp = gpar(col = 2:3)) |
|
152 |
-draw(anno, test = "anno_lines, smooth, matrix") |
|
153 |
- |
|
154 |
-anno = anno_lines(sort(rnorm(10)), width = unit(2, "cm"), smooth = TRUE, add_points = TRUE, which = "row") |
|
155 |
-draw(anno, test = "anno_lines, smooth, by row") |
|
156 |
-anno = anno_lines(cbind(sort(rnorm(10)), sort(rnorm(10), decreasing = TRUE)), |
|
157 |
- width = unit(2, "cm"), smooth = TRUE, add_points = TRUE, gp = gpar(col = 2:3), which = "row") |
|
158 |
-draw(anno, test = "anno_lines, smooth, matrix, by row") |
|
159 |
- |
|
160 |
-anno = anno_lines(c(1:5, NA, 7:10)) |
|
161 |
-draw(anno, test = "anno_lines") |
|
162 |
- |
|
163 |
-anno = anno_lines(runif(10), axis_param = list(direction = "reverse")) |
|
164 |
-draw(anno, test = "anno_lines") |
|
165 |
- |
|
166 |
-###### test anno_text ####### |
|
167 |
-anno = anno_text(month.name) |
|
168 |
-draw(anno, test = "month names") |
|
169 |
-anno = anno_text(month.name, gp = gpar(fontsize = 16)) |
|
170 |
-draw(anno, test = "month names with fontsize") |
|
171 |
-anno = anno_text(month.name, gp = gpar(fontsize = 1:12+4)) |
|
172 |
-draw(anno, test = "month names with changing fontsize") |
|
173 |
-anno = anno_text(month.name, which = "row") |
|
174 |
-draw(anno, test = "month names on rows") |
|
175 |
-anno = anno_text(month.name, location = 0, rot = 45, just = "left", gp = gpar(col = 1:12)) |
|
176 |
-draw(anno, test = "with rotations") |
|
177 |
-anno = anno_text(month.name, location = 1, rot = 45, just = "right", gp = gpar(fontsize = 1:12+4)) |
|
178 |
-draw(anno, test = "with rotations") |
|
179 |
- |
|
180 |
-devAskNewPage(ask = TRUE) |
|
181 |
-for(rot in seq(0, 360, by = 45)) { |
|
182 |
- anno = anno_text(month.name, which = "row", location = 0, rot = rot, |
|
183 |
- just = "left") |
|
184 |
- draw(anno, test = paste0("rot =", rot)) |
|
185 |
-} |
|
186 |
- |
|
187 |
- |
|
188 |
-##### test anno_barplot ##### |
|
189 |
-anno = anno_barplot(1:10) |
|
190 |
-draw(anno, test = "a vector") |
|
191 |
-draw(anno[1:5], test = "a vector, subset") |
|
192 |
-anno = anno_barplot(1:10, which = "row") |
|
193 |
-draw(anno, test = "a vector") |
|
194 |
-anno = anno_barplot(1:10, bar_width = 1) |
|
195 |
-draw(anno, test = "bar_width") |
|
196 |
-anno = anno_barplot(1:10, gp = gpar(fill = 1:10)) |
|
197 |
-draw(anno, test = "fill colors") |
|
198 |
- |
|
199 |
-anno = anno_barplot(matrix(nc = 2, c(1:10, 10:1))) |
|
200 |
-draw(anno, test = "a matrix") |
|
201 |
-draw(anno[1:5], test = "a matrix, subset") |
|
202 |
-anno = anno_barplot(matrix(nc = 2, c(1:10, 10:1)), which = "row") |
|
203 |
-draw(anno, test = "a matrix, on rows") |
|
204 |
-anno = anno_barplot(matrix(nc = 2, c(1:10, 10:1)), gp = gpar(fill = 2:3, col = 2:3)) |
|
205 |
-draw(anno, test = "a matrix with fill") |
|
206 |
- |
|
207 |
-m = matrix(runif(4*10), nc = 4) |
|
208 |
-m = t(apply(m, 1, function(x) x/sum(x))) |
|
209 |
-anno = anno_barplot(m) |
|
210 |
-draw(anno, test = "proportion matrix") |
|
211 |
-anno = anno_barplot(m, gp = gpar(fill = 2:5), bar_width = 1, height = unit(6, "cm")) |
|
212 |
-draw(anno, test = "proportion matrix") |
|
213 |
- |
|
214 |
-anno = anno_barplot(c(1:5, NA, 7:10)) |
|
215 |
-draw(anno, test = "a vector") |
|
216 |
- |
|
217 |
-anno = anno_barplot(1:10, which = "row", axis_param = list(direction = "reverse")) |
|
218 |
-draw(anno, test = "a vector") |
|
219 |
- |
|
220 |
-anno = anno_barplot(1:10, baseline = 5, which = "row", axis_param = list(direction = "reverse")) |
|
221 |
-draw(anno, test = "a vector") |
|
222 |
- |
|
223 |
-anno = anno_barplot(matrix(nc = 2, c(1:10, 10:1)), which = "row", axis_param = list(direction = "reverse")) |
|
224 |
-draw(anno, test = "a vector") |
|
225 |
- |
|
226 |
- |
|
227 |
-##### test anno_boxplot ##### |
|
228 |
-set.seed(123) |
|
229 |
-m = matrix(rnorm(100), 10) |
|
230 |
-anno = anno_boxplot(m, height = unit(4, "cm")) |
|
231 |
-draw(anno, test = "anno_boxplot") |
|
232 |
-draw(anno[1:5], test = "subset") |
|
233 |
-anno = anno_boxplot(m, height = unit(4, "cm"), gp = gpar(fill = 1:10)) |
|
234 |
-draw(anno, test = "anno_boxplot with gp") |
|
235 |
-anno = anno_boxplot(m, height = unit(4, "cm"), box_width = 0.9) |
|
236 |
-draw(anno, test = "anno_boxplot with box_width") |
|
237 |
- |
|
238 |
-m = matrix(rnorm(100), 10) |
|
239 |
-m[1, ] = NA |
|
240 |
-anno = anno_boxplot(m, height = unit(4, "cm")) |
|
241 |
-draw(anno, test = "anno_boxplot") |
|
242 |
- |
|
243 |
- |
|
244 |
-####### test anno_joyplot #### |
|
245 |
-m = matrix(rnorm(1000), nc = 10) |
|
246 |
-lt = apply(m, 2, function(x) data.frame(density(x)[c("x", "y")])) |
|
247 |
-anno = anno_joyplot(lt, width = unit(4, "cm"), which = "row") |
|
248 |
-draw(anno, test = "joyplot") |
|
249 |
-anno = anno_joyplot(lt, width = unit(4, "cm"), which = "row", gp = gpar(fill = 1:10)) |
|
250 |
-draw(anno, test = "joyplot + col") |
|
251 |
-anno = anno_joyplot(lt, width = unit(4, "cm"), which = "row", scale = 1) |
|
252 |
-draw(anno, test = "joyplot + scale") |
|
253 |
- |
|
254 |
-m = matrix(rnorm(5000), nc = 50) |
|
255 |
-lt = apply(m, 2, function(x) data.frame(density(x)[c("x", "y")])) |
|
256 |
-anno = anno_joyplot(lt, width = unit(4, "cm"), which = "row", gp = gpar(fill = NA), scale = 4) |
|
257 |
-draw(anno, test = "joyplot") |
|
258 |
- |
|
259 |
-######## test anno_horizon ###### |
|
260 |
-lt = lapply(1:20, function(x) cumprod(1 + runif(1000, -x/100, x/100)) - 1) |
|
261 |
-anno = anno_horizon(lt, which = "row") |
|
262 |
-draw(anno, test = "horizon chart") |
|
263 |
-anno = anno_horizon(lt, which = "row", gp = gpar(pos_fill = "orange", neg_fill = "darkgreen")) |
|
264 |
-draw(anno, test = "horizon chart, col") |
|
265 |
-anno = anno_horizon(lt, which = "row", negative_from_top = TRUE) |
|
266 |
-draw(anno, test = "horizon chart + negative_from_top") |
|
267 |
-anno = anno_horizon(lt, which = "row", gap = unit(1, "mm")) |
|
268 |
-draw(anno, test = "horizon chart + gap") |
|
269 |
-anno = anno_horizon(lt, which = "row", gp = gpar(pos_fill = rep(c("orange", "red"), each = 10), |
|
270 |
- neg_fill = rep(c("darkgreen", "blue"), each = 10))) |
|
271 |
-draw(anno, test = "horizon chart, col") |
|
272 |
- |
|
273 |
-####### test anno_histogram #### |
|
274 |
-m = matrix(rnorm(1000), nc = 10) |
|
275 |
-anno = anno_histogram(t(m), which = "row") |
|
276 |
-draw(anno, test = "row histogram") |
|
277 |
-draw(anno[1:5], test = "subset row histogram") |
|
278 |
-anno = anno_histogram(t(m), which = "row", gp = gpar(fill = 1:10)) |
|
279 |
-draw(anno, test = "row histogram with color") |
|
280 |
-anno = anno_histogram(t(m), which = "row", n_breaks = 20) |
|
281 |
-draw(anno, test = "row histogram with color") |
|
282 |
-m[1, ] = NA |
|
283 |
-anno = anno_histogram(t(m), which = "row") |
|
284 |
-draw(anno, test = "row histogram") |
|
285 |
- |
|
286 |
- |
|
287 |
-####### test anno_density ###### |
|
288 |
-anno = anno_density(t(m), which = "row") |
|
289 |
-draw(anno, test = "normal density") |
|
290 |
-draw(anno[1:5], test = "normal density, subset") |
|
291 |
-anno = anno_density(t(m), which = "row", type = "violin") |
|
292 |
-draw(anno, test = "violin") |
|
293 |
-anno = anno_density(t(m), which = "row", type = "heatmap") |
|
294 |
-draw(anno, test = "heatmap") |
|
295 |
-anno = anno_density(t(m), which = "row", type = "heatmap", heatmap_colors = c("white", "orange")) |
|
296 |
-draw(anno, test = "heatmap, colors") |
|
297 |
- |
|
298 |
- |
|
299 |
-###### anno_mark ### |
|
300 |
-library(gridtext) |
|
301 |
-grid.text = function(text, x = 0.5, y = 0.5, gp = gpar(), rot = 0, default.units = "npc", just = "center") { |
|
302 |
- if(length(just) == 1) { |
|
303 |
- if(just == "center") { |
|
304 |
- just = c("center", "center") |
|
305 |
- } else if(just == "bottom") { |
|
306 |
- just = c("center", "bottom") |
|
307 |
- } else if (just == "top") { |
|
308 |
- just = c("center", "top") |
|
309 |
- } else if(just == "left") { |
|
310 |
- just = c("left", "center") |
|
311 |
- } else if(just == "right") { |
|
312 |
- just = c("right", "center") |
|
313 |
- } |
|
314 |
- } |
|
315 |
- just2 = c(0.5, 0.5) |
|
316 |
- if(is.character(just)) { |
|
317 |
- just2[1] = switch(just[1], "center" = 0.5, "left" = 0, "right" = 1) |
|
318 |
- just2[2] = switch(just[2], "center" = 0.5, "bottom" = 0, "top" = 1) |
|
319 |
- } |
|
320 |
- gb = richtext_grob(text, x = x, y = y, gp = gpar(fontsize = 10), box_gp = gpar(col = "black"), |
|
321 |
- default.units = default.units, hjust = just2[1], vjust = just2[2], rot = rot) |
|
322 |
- grid.draw(gb) |
|
323 |
-} |
|
324 |
- |
|
325 |
-anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = month.name[1:10], which = "row") |
|
326 |
-draw(anno, index = 1:100, test = "anno_mark") |
|
327 |
- |
|
328 |
-anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = month.name[1:10], labels_rot = 30, which = "column") |
|
329 |
-draw(anno, index = 1:100, test = "anno_mark") |
|
330 |
- |
|
331 |
-m = matrix(1:1000, byrow = TRUE, nr = 100) |
|
332 |
-anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = month.name[1:10], which = "row", labels_rot = 30) |
|
333 |
-Heatmap(m, cluster_rows = F, cluster_columns = F) + rowAnnotation(mark = anno) |
|
334 |
-Heatmap(m) + rowAnnotation(mark = anno) |
|
335 |
- |
|
336 |
-ht_list = Heatmap(m, cluster_rows = F, cluster_columns = F) + rowAnnotation(mark = anno) |
|
337 |
-draw(ht_list, row_split = c(rep("a", 95), rep("b", 5))) |
|
338 |
- |
|
339 |
- |
|
340 |
-grid.newpage() |
|
341 |
-pushViewport(viewport(x = 0.45, w = 0.7, h = 0.95)) |
|
342 |
-h = unit(0, "mm") |
|
343 |
-for(rot in seq(0, 360, by = 30)[-13]) { |
|
344 |
- anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = strrep(letters[1:10], 4), labels_rot = rot, which = "column", side = "bottom") |
|
345 |
- h = h + height(anno) |
|
346 |
- pushViewport(viewport(y = h, height = height(anno), just = "top")) |
|
347 |
- grid.rect() |
|
348 |
- draw(anno, index = 1:100) |
|
349 |
- grid::grid.text(qq("labels_rot = @{rot}"), unit(1, "npc") + unit(2, "mm"), just = "left") |
|
350 |
- popViewport() |
|
351 |
-} |
|
352 |
- |
|
353 |
- |
|
354 |
-grid.newpage() |
|
355 |
-pushViewport(viewport(w = 0.9, h = 0.9)) |
|
356 |
-w = unit(0, "mm") |
|
357 |
-for(rot in seq(0, 360, by = 30)) { |
|
358 |
- anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = strrep(letters[1:10], 4), labels_rot = rot, which = "row", side = "left") |
|
359 |
- w = w + width(anno) |
|
360 |
- pushViewport(viewport(x = w, width = width(anno), just = "right")) |
|
361 |
- grid.rect() |
|
362 |
- draw(anno, index = 1:100) |
|
363 |
- popViewport() |
|
364 |
-} |
|
365 |
- |
|
366 |
- |
|
367 |
- |
|
368 |
-### graphic parameters after reordering |
|
369 |
-index = c(1, 3, 5, 7, 9, 2, 4, 6, 8, 10) |
|
370 |
-anno = anno_simple(1:10, pch = 1:10, pt_gp = gpar(col = rep(c(1, 2), each = 5)), |
|
371 |
- pt_size = unit(1:10, "mm")) |
|
372 |
-draw(anno, index, test = "a numeric vector") |
|
373 |
-anno = anno_simple(1:10, pch = 1:10, pt_gp = gpar(col = rep(c(1, 2), each = 5)), |
|
374 |
- pt_size = unit(1:10, "mm"), which = "row") |
|
375 |
-draw(anno, index, test = "a numeric vector") |
|
376 |
- |
|
377 |
- |
|
378 |
-anno = anno_points(1:10, pch = 1:10, gp = gpar(col = rep(c(1, 2), each = 5)), |
|
379 |
- size = unit(1:10, "mm")) |
|
380 |
-draw(anno, index, test = "a numeric vector") |
|
381 |
-anno = anno_points(1:10, pch = 1:10, gp = gpar(col = rep(c(1, 2), each = 5)), |
|
382 |
- size = unit(1:10, "mm"), which = "row") |
|
383 |
-draw(anno, index, test = "a numeric vector") |
|
384 |
- |
|
385 |
- |
|
386 |
-anno = anno_lines(sort(runif(10)), pch = 1:10, pt_gp = gpar(col = rep(c(1, 2), each = 5)), |
|
387 |
- size = unit(1:10, "mm"), add_points = TRUE) |
|
388 |
-draw(anno, index, test = "a numeric vector") |
|
389 |
-anno = anno_lines(sort(runif(10)), pch = 1:10, pt_gp = gpar(col = rep(c(1, 2), each = 5)), |
|
390 |
- size = unit(1:10, "mm"), add_points = TRUE, which = "row") |
|
391 |
-draw(anno, index, test = "a numeric vector") |
|
392 |
- |
|
393 |
- |
|
394 |
-anno = anno_barplot(1:10, gp = gpar(fill = rep(c(1, 2), each = 5))) |
|
395 |
-draw(anno, index, test = "a numeric vector") |
|
396 |
-anno = anno_barplot(1:10, gp = gpar(fill = rep(c(1, 2), each = 5)), which = "row") |
|
397 |
-draw(anno, index, test = "a numeric vector") |
|
398 |
- |
|
399 |
-anno = anno_barplot(cbind(1:10, 10:1), gp = gpar(fill = 1:2)) |
|
400 |
-draw(anno, index, test = "a numeric vector") |
|
401 |
-anno = anno_barplot(cbind(1:10, 10:1), gp = gpar(fill = 1:2), which = "row") |
|
402 |
-draw(anno, index, test = "a numeric vector") |
|
403 |
- |
|
404 |
- |
|
405 |
-m = matrix(rnorm(100), 10) |
|
406 |
-m = m[, order(apply(m, 2, median))] |
|
407 |
-anno = anno_boxplot(m, pch = 1:10, gp = gpar(fill = rep(c(1, 2), each = 5)), |
|
408 |
- size = unit(1:10, "mm"), height = unit(4, "cm")) |
|
409 |
-draw(anno, index, test = "a numeric vector") |
|
410 |
-anno = anno_boxplot(t(m), pch = 1:10, gp = gpar(fill = rep(c(1, 2), each = 5)), |
|
411 |
- size = unit(1:10, "mm"), which = "row", width = unit(4, "cm")) |
|
412 |
-draw(anno, index, test = "a numeric vector") |
|
413 |
- |
|
414 |
-anno = anno_histogram(m, gp = gpar(fill = rep(c(1, 2), each = 5))) |
|
415 |
-draw(anno, index, test = "a numeric vector") |
|
416 |
-anno = anno_histogram(t(m), gp = gpar(fill = rep(c(1, 2), each = 5)), which = "row") |
|
417 |
-draw(anno, index, test = "a numeric vector") |
|
418 |
- |
|
419 |
-anno = anno_density(m, gp = gpar(fill = rep(c(1, 2), each = 5))) |
|
420 |
-draw(anno, index, test = "a numeric vector") |
|
421 |
-anno = anno_density(t(m), gp = gpar(fill = rep(c(1, 2), each = 5)), which = "row") |
|
422 |
-draw(anno, index, test = "a numeric vector") |
|
423 |
- |
|
424 |
- |
|
425 |
-anno = anno_density(m, type = "violin", gp = gpar(fill = rep(c(1, 2), each = 5))) |
|
426 |
-draw(anno, index, test = "a numeric vector") |
|
427 |
-anno = anno_density(t(m), type = "violin", gp = gpar(fill = rep(c(1, 2), each = 5)), which = "row") |
|
428 |
-draw(anno, index, test = "a numeric vector") |
|
429 |
- |
|
430 |
- |
|
431 |
-anno = anno_text(month.name, gp = gpar(col = rep(c(1, 2), each = 5))) |
|
432 |
-draw(anno, index, test = "a numeric vector") |
|
433 |
-anno = anno_text(month.name, gp = gpar(col = rep(c(1, 2), each = 5)), which= "row") |
|
434 |
-draw(anno, index, test = "a numeric vector") |
|
435 |
- |
|
436 |
-lt = lapply(1:10, function(x) cumprod(1 + runif(1000, -x/100, x/100)) - 1) |
|
437 |
-anno = anno_horizon(lt, gp = gpar(pos_fill = rep(c(1, 2), each = 5), neg_fill = rep(c(3, 4), each = 5)), which = "row") |
|
438 |
-draw(anno, index, test = "a numeric vector") |
|
439 |
- |
|
440 |
-m = matrix(rnorm(1000), nc = 10) |
|
441 |
-lt = apply(m, 2, function(x) data.frame(density(x)[c("x", "y")])) |
|
442 |
-anno = anno_joyplot(lt, gp = gpar(fill = rep(c(1, 2), each = 5)), |
|
443 |
- width = unit(4, "cm"), which = "row") |
|
444 |
-draw(anno, index, test = "joyplot") |
|
445 |
- |
|
446 |
- |
|
447 |
-anno = anno_block(gp = gpar(fill = 1:4)) |
|
448 |
-draw(anno, index = 1:10, k = 1, n = 4, test = "anno_block") |
|
449 |
-draw(anno, index = 1:10, k = 2, n = 4, test = "anno_block") |
|
450 |
- |
|
451 |
-anno = anno_block(gp = gpar(fill = 1:4), labels = letters[1:4], labels_gp = gpar(col = "white")) |
|
452 |
-draw(anno, index = 1:10, k = 2, n = 4, test = "anno_block") |
|
453 |
-draw(anno, index = 1:10, k = 4, n = 4, test = "anno_block") |
|
454 |
-draw(anno, index = 1:10, k = 2, n = 2, test = "anno_block") |
|
455 |
- |
|
456 |
-anno = anno_block(gp = gpar(fill = 1:4), labels = letters[1:4], labels_gp = gpar(col = "white"), which = "row") |
|
457 |
-draw(anno, index = 1:10, k = 2, n = 4, test = "anno_block") |
|
458 |
- |
|
459 |
- |
|
460 |
-### anno_zoom |
|
461 |
-fa = sort(sample(letters[1:3], 100, replace = TRUE, prob = c(1, 2, 3))) |
|
462 |
-panel_fun = function(index, nm) { |
|
463 |
- grid.rect() |
|
464 |
- grid.text(nm) |
|
465 |
-} |
|
466 |
-anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun) |
|
467 |
-draw(anno, index = 1:100, test = "anno_zoom") |
|
468 |
- |
|
469 |
-anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun, |
|
470 |
- gap = unit(1, "cm")) |
|
471 |
-draw(anno, index = 1:100, test = "anno_zoom, set gap") |
|
472 |
- |
|
473 |
-anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun, |
|
474 |
- size = 1:3) |
|
475 |
-draw(anno, index = 1:100, test = "anno_zoom, size set as relative values") |
|
476 |
- |
|
477 |
-anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun, |
|
478 |
- size = 1:3, extend = unit(1, "cm")) |
|
479 |
-draw(anno, index = 1:100, test = "anno_zoom, extend") |
|
480 |
- |
|
481 |
-anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun, |
|
482 |
- size = unit(1:3, "cm")) |
|
483 |
-draw(anno, index = 1:100, test = "anno_zoom, size set as absolute values") |
|
484 |
- |
|
485 |
-anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun, |
|
486 |
- size = unit(c(2, 20, 40), "cm")) |
|
487 |
-draw(anno, index = 1:100, test = "anno_zoom, big size") |
|
488 |
- |
|
489 |
-anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun, |
|
490 |
- size = 1:3, gap = unit(1, "cm")) |
|
491 |
-draw(anno, index = 1:100, test = "anno_zoom, size set as relative values, gap") |
|
492 |
- |
|
493 |
-anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun, |
|
494 |
- size = unit(1:3, "cm"), gap = unit(1, "cm")) |
|
495 |
-draw(anno, index = 1:100, test = "anno_zoom, size set as absolute values, gap") |
|
496 |
- |
|
497 |
- |
|
498 |
-anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun, |
|
499 |
- size = unit(1:3, "cm"), side = "left") |
|
500 |
-draw(anno, index = 1:100, test = "anno_zoom, side") |
|
501 |
- |
|
502 |
- |
|
503 |
-anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun, |
|
504 |
- size = unit(1:3, "cm"), link_gp = gpar(fill = 1:3)) |
|
505 |
-draw(anno, index = 1:100, test = "anno_zoom, link_gp") |
|
506 |
- |
|
507 |
-anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun, |
|
508 |
- size = unit(1:3, "cm"), link_gp = gpar(fill = 1:3), |
|
509 |
- link_width = unit(2, "cm"), width = unit(4, "cm")) |
|
510 |
-draw(anno, index = 1:100, test = "anno_zoom, width") |
|
511 |
- |
|
512 |
-anno = anno_zoom(align_to = list(a = 1:10, b = 30:45, c = 70:90), |
|
513 |
- which = "row", panel_fun = panel_fun, size = unit(1:3, "cm")) |
|
514 |
-draw(anno, index = 1:100, test = "anno_zoom, a list of indices") |
|
515 |
- |
|
516 |
-anno = anno_zoom(align_to = fa, which = "column", panel_fun = panel_fun, |
|
517 |
- size = unit(1:3, "cm")) |
|
518 |
-draw(anno, index = 1:100, test = "anno_zoom, column annotation") |
|
519 |
- |
|
520 |
- |
|
521 |
-m = matrix(rnorm(100*10), nrow = 100) |
|
522 |
-hc = hclust(dist(m)) |
|
523 |
-fa2 = cutree(hc, k = 4) |
|
524 |
-anno = anno_zoom(align_to = fa2, which = "row", panel_fun = panel_fun) |
|
525 |
-draw(anno, index = hc$order, test = "anno_zoom, column annotation") |
|
526 |
- |
|
527 |
-anno = anno_zoom(align_to = fa2, which = "column", panel_fun = panel_fun) |
|
528 |
-draw(anno, index = hc$order, test = "anno_zoom, column annotation") |
|
529 |
- |
|
530 |
- |
|
531 |
-anno = anno_zoom(align_to = fa2, which = "row", panel_fun = panel_fun) |
|
532 |
-Heatmap(m, cluster_rows = hc, right_annotation = rowAnnotation(foo = anno)) |
|
533 |
-Heatmap(m, cluster_rows = hc, right_annotation = rowAnnotation(foo = anno), row_split = 2) |
|
534 |
- |
|
535 |
- |
|
536 |
-anno = anno_zoom(align_to = fa2, which = "row", panel_fun = panel_fun, size = unit(1:4, "cm")) |
|
537 |
-Heatmap(m, cluster_rows = hc, right_annotation = rowAnnotation(foo = anno)) |
|
538 |
- |
|
539 |
-set.seed(123) |
|
540 |
-m = matrix(rnorm(100*10), nrow = 100) |
|
541 |
-subgroup = sample(letters[1:3], 100, replace = TRUE, prob = c(1, 5, 10)) |
|
542 |
-rg = range(m) |
|
543 |
-panel_fun = function(index, nm) { |
|
544 |
- pushViewport(viewport(xscale = rg, yscale = c(0, 2))) |
|
545 |
- grid.rect() |
|
546 |
- grid.xaxis(gp = gpar(fontsize = 8)) |
|
547 |
- grid.boxplot(m[index, ], pos = 1, direction = "horizontal") |
|
548 |
- grid.text(paste("distribution of group", nm), mean(rg), y = 1.9, |
|
549 |
- just = "top", default.units = "native", gp = gpar(fontsize = 10)) |
|
550 |
- popViewport() |
|
551 |
-} |
|
552 |
-anno = anno_zoom(align_to = subgroup, which = "row", panel_fun = panel_fun, |
|
553 |
- size = unit(2, "cm"), gap = unit(1, "cm"), width = unit(4, "cm")) |
|
554 |
-Heatmap(m, right_annotation = rowAnnotation(foo = anno), row_split = subgroup) |
|
555 |
- |
|
556 |
-panel_fun2 = function(index, nm) { |
|
557 |
- pushViewport(viewport()) |
|
558 |
- grid.rect() |
|
559 |
- n = floor(length(index)/4) |
|
560 |
- txt = paste("gene function", 1:n, collapse = "\n") |
|
561 |
- grid.text(txt, 0.95, 0.5, default.units = "npc", just = "right", gp = gpar(fontsize = 8)) |
|
562 |
- popViewport() |
|
563 |
-} |
|
564 |
-anno2 = anno_zoom(align_to = subgroup, which = "row", panel_fun = panel_fun2, |
|
565 |
- gap = unit(1, "cm"), width = unit(3, "cm"), side = "left") |
|
566 |
- |
|
567 |
-# in infinite loop |
|
568 |
-Heatmap(m, right_annotation = rowAnnotation(subgroup = subgroup, foo = anno, |
|
569 |
- show_annotation_name = FALSE), |
|
570 |
- left_annotation = rowAnnotation(bar = anno2, subgroup = subgroup, show_annotation_name = FALSE), |
|
571 |
- show_row_dend = FALSE, |
|
572 |
- row_split = subgroup) |
|
573 |
- |
|
574 |
-Heatmap(m, right_annotation = rowAnnotation(foo = anno), |
|
575 |
- left_annotation = rowAnnotation(bar = anno2), |
|
576 |
- show_row_dend = FALSE, |
|
577 |
- row_split = subgroup) |
... | ... |
@@ -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) |
... | ... |
@@ -184,6 +184,12 @@ 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 |
+ |
|
187 | 193 |
|
188 | 194 |
|
189 | 195 |
##### test anno_barplot ##### |
... | ... |
@@ -129,6 +129,14 @@ draw(anno, test = "anno_points") |
129 | 129 |
anno = anno_points(runif(10), axis_param = list(direction = "reverse"), ylim = c(0, 1), which = "row") |
130 | 130 |
draw(anno, test = "anno_points") |
131 | 131 |
|
132 |
+# pch as image |
|
133 |
+image1 = sample(dir("/desktop-home/guz/Downloads/IcoMoon-Free-master/PNG/64px", full.names = TRUE), 10) |
|
134 |
+x = runif(10) |
|
135 |
+anno1 = anno_points(x, pch = image1, pch_as_image = TRUE, size = unit(5, "mm"), height = unit(4, "cm")) |
|
136 |
+anno2 = anno_points(x, height = unit(4, "cm")) |
|
137 |
+draw(anno1, test = "anno_points") |
|
138 |
+draw(anno2, test = "anno_points") |
|
139 |
+ |
|
132 | 140 |
##### test anno_lines ### |
133 | 141 |
anno = anno_lines(runif(10)) |
134 | 142 |
draw(anno, test = "anno_lines") |
... | ... |
@@ -331,14 +331,15 @@ draw(ht_list, row_split = c(rep("a", 95), rep("b", 5))) |
331 | 331 |
|
332 | 332 |
|
333 | 333 |
grid.newpage() |
334 |
-pushViewport(viewport(w = 0.9, h = 0.9)) |
|
334 |
+pushViewport(viewport(x = 0.45, w = 0.7, h = 0.95)) |
|
335 | 335 |
h = unit(0, "mm") |
336 |
-for(rot in seq(0, 360, by = 30)) { |
|
336 |
+for(rot in seq(0, 360, by = 30)[-13]) { |
|
337 | 337 |
anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = strrep(letters[1:10], 4), labels_rot = rot, which = "column", side = "bottom") |
338 | 338 |
h = h + height(anno) |
339 | 339 |
pushViewport(viewport(y = h, height = height(anno), just = "top")) |
340 | 340 |
grid.rect() |
341 | 341 |
draw(anno, index = 1:100) |
342 |
+ grid::grid.text(qq("labels_rot = @{rot}"), unit(1, "npc") + unit(2, "mm"), just = "left") |
|
342 | 343 |
popViewport() |
343 | 344 |
} |
344 | 345 |
|
... | ... |
@@ -290,6 +290,31 @@ draw(anno, test = "heatmap, colors") |
290 | 290 |
|
291 | 291 |
|
292 | 292 |
###### anno_mark ### |
293 |
+library(gridtext) |
|
294 |
+grid.text = function(text, x = 0.5, y = 0.5, gp = gpar(), rot = 0, default.units = "npc", just = "center") { |
|
295 |
+ if(length(just) == 1) { |
|
296 |
+ if(just == "center") { |
|
297 |
+ just = c("center", "center") |
|
298 |
+ } else if(just == "bottom") { |
|
299 |
+ just = c("center", "bottom") |
|
300 |
+ } else if (just == "top") { |
|
301 |
+ just = c("center", "top") |
|
302 |
+ } else if(just == "left") { |
|
303 |
+ just = c("left", "center") |
|
304 |
+ } else if(just == "right") { |
|
305 |
+ just = c("right", "center") |
|
306 |
+ } |
|
307 |
+ } |
|
308 |
+ just2 = c(0.5, 0.5) |
|
309 |
+ if(is.character(just)) { |
|
310 |
+ just2[1] = switch(just[1], "center" = 0.5, "left" = 0, "right" = 1) |
|
311 |
+ just2[2] = switch(just[2], "center" = 0.5, "bottom" = 0, "top" = 1) |
|
312 |
+ } |
|
313 |
+ gb = richtext_grob(text, x = x, y = y, gp = gpar(fontsize = 10), box_gp = gpar(col = "black"), |
|
314 |
+ default.units = default.units, hjust = just2[1], vjust = just2[2], rot = rot) |
|
315 |
+ grid.draw(gb) |
|
316 |
+} |
|
317 |
+ |
|
293 | 318 |
anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = month.name[1:10], which = "row") |
294 | 319 |
draw(anno, index = 1:100, test = "anno_mark") |
295 | 320 |
|
... | ... |
@@ -306,10 +331,12 @@ draw(ht_list, row_split = c(rep("a", 95), rep("b", 5))) |
306 | 331 |
|
307 | 332 |
|
308 | 333 |
grid.newpage() |
309 |
-pushViewport(viewport(layout = grid.layout(nrow = 12, ncol = 1))) |
|
310 |
-for(rot in seq(0, 360, by = 30)[-13]) { |
|
334 |
+pushViewport(viewport(w = 0.9, h = 0.9)) |
|
335 |
+h = unit(0, "mm") |
|
336 |
+for(rot in seq(0, 360, by = 30)) { |
|
311 | 337 |
anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = strrep(letters[1:10], 4), labels_rot = rot, which = "column", side = "bottom") |
312 |
- pushViewport(viewport(layout.pos.col = 1, layout.pos.row = rot/30 + 1)) |
|
338 |
+ h = h + height(anno) |
|
339 |
+ pushViewport(viewport(y = h, height = height(anno), just = "top")) |
|
313 | 340 |
grid.rect() |
314 | 341 |
draw(anno, index = 1:100) |
315 | 342 |
popViewport() |
... | ... |
@@ -317,10 +344,12 @@ for(rot in seq(0, 360, by = 30)[-13]) { |
317 | 344 |
|
318 | 345 |
|
319 | 346 |
grid.newpage() |
320 |
-pushViewport(viewport(layout = grid.layout(nrow = 1, ncol = 12))) |
|
321 |
-for(rot in seq(0, 360, by = 30)[-13]) { |
|
322 |
- anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = strrep(letters[1:10], 4), labels_rot = rot, which = "row", side = "right") |
|
323 |
- pushViewport(viewport(layout.pos.row = 1, layout.pos.col = rot/30 + 1)) |
|
347 |
+pushViewport(viewport(w = 0.9, h = 0.9)) |
|
348 |
+w = unit(0, "mm") |
|
349 |
+for(rot in seq(0, 360, by = 30)) { |
|
350 |
+ anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = strrep(letters[1:10], 4), labels_rot = rot, which = "row", side = "left") |
|
351 |
+ w = w + width(anno) |
|
352 |
+ pushViewport(viewport(x = w, width = width(anno), just = "right")) |
|
324 | 353 |
grid.rect() |
325 | 354 |
draw(anno, index = 1:100) |
326 | 355 |
popViewport() |
... | ... |
@@ -304,18 +304,28 @@ Heatmap(m) + rowAnnotation(mark = anno) |
304 | 304 |
ht_list = Heatmap(m, cluster_rows = F, cluster_columns = F) + rowAnnotation(mark = anno) |
305 | 305 |
draw(ht_list, row_split = c(rep("a", 95), rep("b", 5))) |
306 | 306 |
|
307 |
-pl = list() |
|
307 |
+ |
|
308 |
+grid.newpage() |
|
309 |
+pushViewport(viewport(layout = grid.layout(nrow = 12, ncol = 1))) |
|
308 | 310 |
for(rot in seq(0, 360, by = 30)[-13]) { |
309 |
- anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = letters[1:10], labels_rot = rot, which = "column") |
|
310 |
- pl[[as.character(rot)]] = grid.grabExpr(draw(anno, index = 1:100, test = qq("labels_rot = @{rot}"))) |
|
311 |
+ anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = strrep(letters[1:10], 4), labels_rot = rot, which = "column", side = "bottom") |
|
312 |
+ pushViewport(viewport(layout.pos.col = 1, layout.pos.row = rot/30 + 1)) |
|
313 |
+ grid.rect() |
|
314 |
+ draw(anno, index = 1:100) |
|
315 |
+ popViewport() |
|
311 | 316 |
} |
312 |
-pushViewport(viewport(layout = grid.layout(nrow = 12, ncol = 1))) |
|
313 |
-for(i in seq_along(pl)) { |
|
314 |
- pushViewport(viewport(layout.pos.row = i, layout.pos.col = 1)) |
|
315 |
- grid.draw(pl[[i]]) |
|
317 |
+ |
|
318 |
+ |
|
319 |
+grid.newpage() |
|
320 |
+pushViewport(viewport(layout = grid.layout(nrow = 1, ncol = 12))) |
|
321 |
+for(rot in seq(0, 360, by = 30)[-13]) { |
|
322 |
+ anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = strrep(letters[1:10], 4), labels_rot = rot, which = "row", side = "right") |
|
323 |
+ pushViewport(viewport(layout.pos.row = 1, layout.pos.col = rot/30 + 1)) |
|
324 |
+ grid.rect() |
|
325 |
+ draw(anno, index = 1:100) |
|
316 | 326 |
popViewport() |
317 | 327 |
} |
318 |
-popViewport() |
|
328 |
+ |
|
319 | 329 |
|
320 | 330 |
|
321 | 331 |
### graphic parameters after reordering |
... | ... |
@@ -304,6 +304,19 @@ Heatmap(m) + rowAnnotation(mark = anno) |
304 | 304 |
ht_list = Heatmap(m, cluster_rows = F, cluster_columns = F) + rowAnnotation(mark = anno) |
305 | 305 |
draw(ht_list, row_split = c(rep("a", 95), rep("b", 5))) |
306 | 306 |
|
307 |
+pl = list() |
|
308 |
+for(rot in seq(0, 360, by = 30)[-13]) { |
|
309 |
+ anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = letters[1:10], labels_rot = rot, which = "column") |
|
310 |
+ pl[[as.character(rot)]] = grid.grabExpr(draw(anno, index = 1:100, test = qq("labels_rot = @{rot}"))) |
|
311 |
+} |
|
312 |
+pushViewport(viewport(layout = grid.layout(nrow = 12, ncol = 1))) |
|
313 |
+for(i in seq_along(pl)) { |
|
314 |
+ pushViewport(viewport(layout.pos.row = i, layout.pos.col = 1)) |
|
315 |
+ grid.draw(pl[[i]]) |
|
316 |
+ popViewport() |
|
317 |
+} |
|
318 |
+popViewport() |
|
319 |
+ |
|
307 | 320 |
|
308 | 321 |
### graphic parameters after reordering |
309 | 322 |
index = c(1, 3, 5, 7, 9, 2, 4, 6, 8, 10) |
... | ... |
@@ -293,7 +293,7 @@ draw(anno, test = "heatmap, colors") |
293 | 293 |
anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = month.name[1:10], which = "row") |
294 | 294 |
draw(anno, index = 1:100, test = "anno_mark") |
295 | 295 |
|
296 |
-anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = month.name[1:10], labels_rot = 30, which = "row") |
|
296 |
+anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = month.name[1:10], labels_rot = 30, which = "column") |
|
297 | 297 |
draw(anno, index = 1:100, test = "anno_mark") |
298 | 298 |
|
299 | 299 |
m = matrix(1:1000, byrow = TRUE, nr = 100) |
... | ... |
@@ -293,8 +293,11 @@ draw(anno, test = "heatmap, colors") |
293 | 293 |
anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = month.name[1:10], which = "row") |
294 | 294 |
draw(anno, index = 1:100, test = "anno_mark") |
295 | 295 |
|
296 |
+anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = month.name[1:10], labels_rot = 30, which = "row") |
|
297 |
+draw(anno, index = 1:100, test = "anno_mark") |
|
298 |
+ |
|
296 | 299 |
m = matrix(1:1000, byrow = TRUE, nr = 100) |
297 |
-anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = month.name[1:10], which = "row") |
|
300 |
+anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = month.name[1:10], which = "row", labels_rot = 30) |
|
298 | 301 |
Heatmap(m, cluster_rows = F, cluster_columns = F) + rowAnnotation(mark = anno) |
299 | 302 |
Heatmap(m) + rowAnnotation(mark = anno) |
300 | 303 |
|
... | ... |
@@ -123,6 +123,12 @@ anno = anno_points(c(1:5, NA, 7:10)) |
123 | 123 |
draw(anno, test = "anno_points") |
124 | 124 |
|
125 | 125 |
|
126 |
+anno = anno_points(runif(10), axis_param = list(direction = "reverse"), ylim = c(0, 1)) |
|
127 |
+draw(anno, test = "anno_points") |
|
128 |
+ |
|
129 |
+anno = anno_points(runif(10), axis_param = list(direction = "reverse"), ylim = c(0, 1), which = "row") |
|
130 |
+draw(anno, test = "anno_points") |
|
131 |
+ |
|
126 | 132 |
##### test anno_lines ### |
127 | 133 |
anno = anno_lines(runif(10)) |
128 | 134 |
draw(anno, test = "anno_lines") |
... | ... |
@@ -146,6 +152,8 @@ draw(anno, test = "anno_lines, smooth, matrix, by row") |
146 | 152 |
anno = anno_lines(c(1:5, NA, 7:10)) |
147 | 153 |
draw(anno, test = "anno_lines") |
148 | 154 |
|
155 |
+anno = anno_lines(runif(10), axis_param = list(direction = "reverse")) |
|
156 |
+draw(anno, test = "anno_lines") |
|
149 | 157 |
|
150 | 158 |
###### test anno_text ####### |
151 | 159 |
anno = anno_text(month.name) |
... | ... |
@@ -199,6 +207,16 @@ draw(anno, test = "proportion matrix") |
199 | 207 |
anno = anno_barplot(c(1:5, NA, 7:10)) |
200 | 208 |
draw(anno, test = "a vector") |
201 | 209 |
|
210 |
+anno = anno_barplot(1:10, which = "row", axis_param = list(direction = "reverse")) |
|
211 |
+draw(anno, test = "a vector") |
|
212 |
+ |
|
213 |
+anno = anno_barplot(1:10, baseline = 5, which = "row", axis_param = list(direction = "reverse")) |
|
214 |
+draw(anno, test = "a vector") |
|
215 |
+ |
|
216 |
+anno = anno_barplot(matrix(nc = 2, c(1:10, 10:1)), which = "row", axis_param = list(direction = "reverse")) |
|
217 |
+draw(anno, test = "a vector") |
|
218 |
+ |
|
219 |
+ |
|
202 | 220 |
##### test anno_boxplot ##### |
203 | 221 |
set.seed(123) |
204 | 222 |
m = matrix(rnorm(100), 10) |
1 | 1 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,496 @@ |
1 |
+ |
|
2 |
+normalize_graphic_param_to_mat(1, nc = 2, nr = 4, "foo") |
|
3 |
+normalize_graphic_param_to_mat(1:2, nc = 2, nr = 4, "foo") |
|
4 |
+normalize_graphic_param_to_mat(1:4, nc = 2, nr = 4, "foo") |
|
5 |
+ |
|
6 |
+### AnnotationFunction constructor ##### |
|
7 |
+fun = function(index) { |
|
8 |
+ x = runif(10) |
|
9 |
+ pushViewport(viewport(xscale = c(0.5, 10.5), yscale = c(0, 1))) |
|
10 |
+ grid.points(index, x[index]) |
|
11 |
+ popViewport() |
|
12 |
+} |
|
13 |
+anno = AnnotationFunction(fun = fun) |
|
14 |
+ |
|
15 |
+x = runif(10) |
|
16 |
+fun = function(index) { |
|
17 |
+ pushViewport(viewport(xscale = c(0.5, 10.5), yscale = c(0, 1))) |
|
18 |
+ grid.points(index, x[index]) |
|
19 |
+ popViewport() |
|
20 |
+} |
|
21 |
+anno = AnnotationFunction(fun = fun, var_imported = "x") |
|
22 |
+anno = AnnotationFunction(fun = fun, var_imported = list(x)) |
|
23 |
+ |
|
24 |
+ |
|
25 |
+devAskNewPage(ask = TRUE) |
|
26 |
+ |
|
27 |
+########### testing anno_simple ############ |
|
28 |
+anno = anno_simple(1:10) |
|
29 |
+draw(anno, test = "as a simple vector") |
|
30 |
+draw(anno[1:5], test = "subset of column annotation") |
|
31 |
+anno = anno_simple(1:10, which = "row") |
|
32 |
+draw(anno, test = "as row annotation") |
|
33 |
+draw(anno[1:5], test = "subste of row annotation") |
|
34 |
+ |
|
35 |
+anno = anno_simple(1:10, col = structure(rand_color(10), names = 1:10)) |
|
36 |
+draw(anno, test = "self-define colors") |
|
37 |
+ |
|
38 |
+anno = anno_simple(1:10, border = TRUE) |
|
39 |
+draw(anno, test = "border") |
|
40 |
+anno = anno_simple(1:10, gp = gpar(col = "red")) |
|
41 |
+draw(anno, test = "gp for the grids") |
|
42 |
+ |
|
43 |
+anno = anno_simple(c(1:9, NA)) |
|
44 |
+draw(anno, test = "vector has NA values") |
|
45 |
+ |
|
46 |
+anno = anno_simple(cbind(1:10, 10:1)) |
|
47 |
+draw(anno, test = "a matrix") |
|
48 |
+draw(anno[1:5], test = "subste of a matrix") |
|
49 |
+ |
|
50 |
+anno = anno_simple(1:10, pch = 1, pt_gp = gpar(col = "red"), pt_size = unit(seq(1, 10), "mm")) |
|
51 |
+draw(anno, test = "with symbols + pt_gp + pt_size") |
|
52 |
+anno = anno_simple(1:10, pch = 1:10) |
|
53 |
+draw(anno, test = "pch is a vector") |
|
54 |
+anno = anno_simple(1:10, pch = c(1:4, NA, 6:8, NA, 10, 11)) |
|
55 |
+draw(anno, test = "pch has NA values") |
|
56 |
+ |
|
57 |
+anno = anno_simple(cbind(1:10, 10:1), pch = 1, pt_gp = gpar(col = "blue")) |
|
58 |
+draw(anno, test = "matrix with symbols") |
|
59 |
+anno = anno_simple(cbind(1:10, 10:1), pch = 1:2) |
|
60 |
+draw(anno, test = "matrix, length of pch is number of annotations") |
|
61 |
+anno = anno_simple(cbind(1:10, 10:1), pch = 1:10) |
|
62 |
+draw(anno, test = "matrix, length of pch is length of samples") |
|
63 |
+anno = anno_simple(cbind(1:10, 10:1), pch = matrix(1:20, nc = 2)) |
|
64 |
+draw(anno, test = "matrix, pch is a matrix") |
|
65 |
+pch = matrix(1:20, nc = 2) |
|
66 |
+pch[sample(length(pch), 10)] = NA |
|
67 |
+anno = anno_simple(cbind(1:10, 10:1), pch = pch) |
|
68 |
+draw(anno, test = "matrix, pch is a matrix with NA values") |
|
69 |
+ |
|
70 |
+ |
|
71 |
+####### test anno_empty ###### |
|
72 |
+anno = anno_empty() |
|
73 |
+draw(anno, test = "anno_empty") |
|
74 |
+anno = anno_empty(border = FALSE) |
|
75 |
+draw(anno, test = "anno_empty without border") |
|
76 |
+ |
|
77 |
+###### test anno_image ##### |
|
78 |
+image1 = sample(dir("~/Downloads/IcoMoon-Free-master/PNG/64px", full.names = TRUE), 10) |
|
79 |
+anno = anno_image(image1) |
|
80 |
+draw(anno, test = "png") |
|
81 |
+draw(anno[1:5], test = "subset of png") |
|
82 |
+anno = anno_image(image1, which = "row") |
|
83 |
+draw(anno, test = "png on rows") |
|
84 |
+image2 = sample(dir("~/Downloads/IcoMoon-Free-master/SVG/", full.names = TRUE), 10) |
|
85 |
+anno = anno_image(image2) |
|
86 |
+draw(anno, test = "svg") |
|
87 |
+image3 = sample(dir("~/Downloads/IcoMoon-Free-master/EPS/", full.names = TRUE), 10) |
|
88 |
+anno = anno_image(image3) |
|
89 |
+draw(anno, test = "eps") |
|
90 |
+image4 = sample(dir("~/Downloads/IcoMoon-Free-master/PDF/", full.names = TRUE), 10) |
|
91 |
+anno = anno_image(image4) |
|
92 |
+draw(anno, test = "pdf") |
|
93 |
+ |
|
94 |
+anno = anno_image(c(image1[1:3], image2[1:3], image3[1:3], image4[1:3])) |
|
95 |
+draw(anno, test = "png+svg+eps+pdf") |
|
96 |
+ |
|
97 |
+anno = anno_image(image1, gp = gpar(fill = 1:10, col = "black")) |
|
98 |
+draw(anno, test = "png + gp") |
|
99 |
+draw(anno[1:5], test = "png + gp") |
|
100 |
+ |
|
101 |
+anno = anno_image(image1, space = unit(3, "mm")) |
|
102 |
+draw(anno, test = "space") |
|
103 |
+ |
|
104 |
+image1[1] = "" |
|
105 |
+anno = anno_image(image1) |
|
106 |
+draw(anno, test = "png") |
|
107 |
+ |
|
108 |
+######## test anno_points ##### |
|
109 |
+anno = anno_points(runif(10)) |
|
110 |
+draw(anno, test = "anno_points") |
|
111 |
+anno = anno_points(matrix(runif(20), nc = 2), pch = 1:2) |
|
112 |
+draw(anno, test = "matrix") |
|
113 |
+anno = anno_points(c(1:5, 1:5)) |
|
114 |
+draw(anno, test = "anno_points") |
|
115 |
+anno = anno_points(cbind(c(1:5, 1:5), c(5:1, 5:1)), gp = gpar(col = 2:3)) |
|
116 |
+draw(anno, test = "matrix") |
|
117 |
+ |
|
118 |
+anno = anno_points(1:10, gp = gpar(col = rep(2:3, each = 5)), pch = rep(2:3, each = 5)) |
|
119 |
+draw(anno, test = "anno_points") |
|
120 |
+draw(anno, index = c(1, 3, 5, 7, 9, 2, 4, 6, 8, 10), test = "anno_points") |
|
121 |
+ |
|
122 |
+anno = anno_points(c(1:5, NA, 7:10)) |
|
123 |
+draw(anno, test = "anno_points") |
|
124 |
+ |
|
125 |
+ |
|
126 |
+##### test anno_lines ### |
|
127 |
+anno = anno_lines(runif(10)) |
|
128 |
+draw(anno, test = "anno_lines") |
|
129 |
+anno = anno_lines(cbind(c(1:5, 1:5), c(5:1, 5:1)), gp = gpar(col = 2:3)) |
|
130 |
+draw(anno, test = "matrix") |
|
131 |
+anno = anno_lines(cbind(c(1:5, 1:5), c(5:1, 5:1)), gp = gpar(col = 2:3), |
|
132 |
+ add_points = TRUE, pt_gp = gpar(col = 5:6), pch = c(1, 16)) |
|
133 |
+draw(anno, test = "matrix") |
|
134 |
+anno = anno_lines(sort(rnorm(10)), height = unit(2, "cm"), smooth = TRUE, add_points = TRUE) |
|
135 |
+draw(anno, test = "anno_lines, smooth") |
|
136 |
+anno = anno_lines(cbind(sort(rnorm(10)), sort(rnorm(10), decreasing = TRUE)), |
|
137 |
+ height = unit(2, "cm"), smooth = TRUE, add_points = TRUE, gp = gpar(col = 2:3)) |
|
138 |
+draw(anno, test = "anno_lines, smooth, matrix") |
|
139 |
+ |
|
140 |
+anno = anno_lines(sort(rnorm(10)), width = unit(2, "cm"), smooth = TRUE, add_points = TRUE, which = "row") |
|
141 |
+draw(anno, test = "anno_lines, smooth, by row") |
|
142 |
+anno = anno_lines(cbind(sort(rnorm(10)), sort(rnorm(10), decreasing = TRUE)), |
|
143 |
+ width = unit(2, "cm"), smooth = TRUE, add_points = TRUE, gp = gpar(col = 2:3), which = "row") |
|
144 |
+draw(anno, test = "anno_lines, smooth, matrix, by row") |
|
145 |
+ |
|
146 |
+anno = anno_lines(c(1:5, NA, 7:10)) |
|
147 |
+draw(anno, test = "anno_lines") |
|
148 |
+ |
|
149 |
+ |
|
150 |
+###### test anno_text ####### |
|
151 |
+anno = anno_text(month.name) |
|
152 |
+draw(anno, test = "month names") |
|
153 |
+anno = anno_text(month.name, gp = gpar(fontsize = 16)) |
|
154 |
+draw(anno, test = "month names with fontsize") |
|
155 |
+anno = anno_text(month.name, gp = gpar(fontsize = 1:12+4)) |
|
156 |
+draw(anno, test = "month names with changing fontsize") |
|
157 |
+anno = anno_text(month.name, which = "row") |
|
158 |
+draw(anno, test = "month names on rows") |
|
159 |
+anno = anno_text(month.name, location = 0, rot = 45, just = "left", gp = gpar(col = 1:12)) |
|
160 |
+draw(anno, test = "with rotations") |
|
161 |
+anno = anno_text(month.name, location = 1, rot = 45, just = "right", gp = gpar(fontsize = 1:12+4)) |
|
162 |
+draw(anno, test = "with rotations") |
|
163 |
+ |
|
164 |
+devAskNewPage(ask = TRUE) |
|
165 |
+for(rot in seq(0, 360, by = 45)) { |
|
166 |
+ anno = anno_text(month.name, which = "row", location = 0, rot = rot, |
|
167 |
+ just = "left") |
|
168 |
+ draw(anno, test = paste0("rot =", rot)) |
|
169 |
+} |
|
170 |
+ |
|
171 |
+ |
|
172 |
+ |
|
173 |
+##### test anno_barplot ##### |
|
174 |
+anno = anno_barplot(1:10) |
|
175 |
+draw(anno, test = "a vector") |
|
176 |
+draw(anno[1:5], test = "a vector, subset") |
|
177 |
+anno = anno_barplot(1:10, which = "row") |
|
178 |
+draw(anno, test = "a vector") |
|
179 |
+anno = anno_barplot(1:10, bar_width = 1) |
|
180 |
+draw(anno, test = "bar_width") |
|
181 |
+anno = anno_barplot(1:10, gp = gpar(fill = 1:10)) |
|
182 |
+draw(anno, test = "fill colors") |
|
183 |
+ |
|
184 |
+anno = anno_barplot(matrix(nc = 2, c(1:10, 10:1))) |
|
185 |
+draw(anno, test = "a matrix") |
|
186 |
+draw(anno[1:5], test = "a matrix, subset") |
|
187 |
+anno = anno_barplot(matrix(nc = 2, c(1:10, 10:1)), which = "row") |
|
188 |
+draw(anno, test = "a matrix, on rows") |
|
189 |
+anno = anno_barplot(matrix(nc = 2, c(1:10, 10:1)), gp = gpar(fill = 2:3, col = 2:3)) |
|
190 |
+draw(anno, test = "a matrix with fill") |
|
191 |
+ |
|
192 |
+m = matrix(runif(4*10), nc = 4) |
|
193 |
+m = t(apply(m, 1, function(x) x/sum(x))) |
|
194 |
+anno = anno_barplot(m) |
|
195 |
+draw(anno, test = "proportion matrix") |
|
196 |
+anno = anno_barplot(m, gp = gpar(fill = 2:5), bar_width = 1, height = unit(6, "cm")) |
|
197 |
+draw(anno, test = "proportion matrix") |
|
198 |
+ |
|
199 |
+anno = anno_barplot(c(1:5, NA, 7:10)) |
|
200 |
+draw(anno, test = "a vector") |
|
201 |
+ |
|
202 |
+##### test anno_boxplot ##### |
|
203 |
+set.seed(123) |
|
204 |
+m = matrix(rnorm(100), 10) |
|
205 |
+anno = anno_boxplot(m, height = unit(4, "cm")) |
|
206 |
+draw(anno, test = "anno_boxplot") |
|
207 |
+draw(anno[1:5], test = "subset") |
|
208 |
+anno = anno_boxplot(m, height = unit(4, "cm"), gp = gpar(fill = 1:10)) |
|
209 |
+draw(anno, test = "anno_boxplot with gp") |
|
210 |
+anno = anno_boxplot(m, height = unit(4, "cm"), box_width = 0.9) |
|
211 |
+draw(anno, test = "anno_boxplot with box_width") |
|
212 |
+ |
|
213 |
+m = matrix(rnorm(100), 10) |
|
214 |
+m[1, ] = NA |
|
215 |
+anno = anno_boxplot(m, height = unit(4, "cm")) |
|
216 |
+draw(anno, test = "anno_boxplot") |
|
217 |
+ |
|
218 |
+ |
|
219 |
+####### test anno_joyplot #### |
|
220 |
+m = matrix(rnorm(1000), nc = 10) |
|
221 |
+lt = apply(m, 2, function(x) data.frame(density(x)[c("x", "y")])) |
|
222 |
+anno = anno_joyplot(lt, width = unit(4, "cm"), which = "row") |
|
223 |
+draw(anno, test = "joyplot") |
|
224 |
+anno = anno_joyplot(lt, width = unit(4, "cm"), which = "row", gp = gpar(fill = 1:10)) |
|
225 |
+draw(anno, test = "joyplot + col") |
|
226 |
+anno = anno_joyplot(lt, width = unit(4, "cm"), which = "row", scale = 1) |
|
227 |
+draw(anno, test = "joyplot + scale") |
|
228 |
+ |
|
229 |
+m = matrix(rnorm(5000), nc = 50) |
|
230 |
+lt = apply(m, 2, function(x) data.frame(density(x)[c("x", "y")])) |
|
231 |
+anno = anno_joyplot(lt, width = unit(4, "cm"), which = "row", gp = gpar(fill = NA), scale = 4) |
|
232 |
+draw(anno, test = "joyplot") |
|
233 |
+ |
|
234 |
+######## test anno_horizon ###### |
|
235 |
+lt = lapply(1:20, function(x) cumprod(1 + runif(1000, -x/100, x/100)) - 1) |
|
236 |
+anno = anno_horizon(lt, which = "row") |
|
237 |
+draw(anno, test = "horizon chart") |
|
238 |
+anno = anno_horizon(lt, which = "row", gp = gpar(pos_fill = "orange", neg_fill = "darkgreen")) |
|
239 |
+draw(anno, test = "horizon chart, col") |
|
240 |
+anno = anno_horizon(lt, which = "row", negative_from_top = TRUE) |
|
241 |
+draw(anno, test = "horizon chart + negative_from_top") |
|
242 |
+anno = anno_horizon(lt, which = "row", gap = unit(1, "mm")) |
|
243 |
+draw(anno, test = "horizon chart + gap") |
|
244 |
+anno = anno_horizon(lt, which = "row", gp = gpar(pos_fill = rep(c("orange", "red"), each = 10), |
|
245 |
+ neg_fill = rep(c("darkgreen", "blue"), each = 10))) |
|
246 |
+draw(anno, test = "horizon chart, col") |
|
247 |
+ |
|
248 |
+####### test anno_histogram #### |
|
249 |
+m = matrix(rnorm(1000), nc = 10) |
|
250 |
+anno = anno_histogram(t(m), which = "row") |
|
251 |
+draw(anno, test = "row histogram") |
|
252 |
+draw(anno[1:5], test = "subset row histogram") |
|
253 |
+anno = anno_histogram(t(m), which = "row", gp = gpar(fill = 1:10)) |
|
254 |
+draw(anno, test = "row histogram with color") |
|
255 |
+anno = anno_histogram(t(m), which = "row", n_breaks = 20) |
|
256 |
+draw(anno, test = "row histogram with color") |
|
257 |
+m[1, ] = NA |
|
258 |
+anno = anno_histogram(t(m), which = "row") |
|
259 |
+draw(anno, test = "row histogram") |
|
260 |
+ |
|
261 |
+ |
|
262 |
+####### test anno_density ###### |
|
263 |
+anno = anno_density(t(m), which = "row") |
|
264 |
+draw(anno, test = "normal density") |
|
265 |
+draw(anno[1:5], test = "normal density, subset") |
|
266 |
+anno = anno_density(t(m), which = "row", type = "violin") |
|
267 |
+draw(anno, test = "violin") |
|
268 |
+anno = anno_density(t(m), which = "row", type = "heatmap") |
|
269 |
+draw(anno, test = "heatmap") |
|
270 |
+anno = anno_density(t(m), which = "row", type = "heatmap", heatmap_colors = c("white", "orange")) |
|
271 |
+draw(anno, test = "heatmap, colors") |
|
272 |
+ |
|
273 |
+ |
|
274 |
+###### anno_mark ### |
|
275 |
+anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = month.name[1:10], which = "row") |
|
276 |
+draw(anno, index = 1:100, test = "anno_mark") |
|
277 |
+ |
|
278 |
+m = matrix(1:1000, byrow = TRUE, nr = 100) |
|
279 |
+anno = anno_mark(at = c(1:4, 20, 60, 97:100), labels = month.name[1:10], which = "row") |
|
280 |
+Heatmap(m, cluster_rows = F, cluster_columns = F) + rowAnnotation(mark = anno) |
|
281 |
+Heatmap(m) + rowAnnotation(mark = anno) |
|
282 |
+ |
|
283 |
+ht_list = Heatmap(m, cluster_rows = F, cluster_columns = F) + rowAnnotation(mark = anno) |
|
284 |
+draw(ht_list, row_split = c(rep("a", 95), rep("b", 5))) |
|
285 |
+ |
|
286 |
+ |
|
287 |
+### graphic parameters after reordering |
|
288 |
+index = c(1, 3, 5, 7, 9, 2, 4, 6, 8, 10) |
|
289 |
+anno = anno_simple(1:10, pch = 1:10, pt_gp = gpar(col = rep(c(1, 2), each = 5)), |
|
290 |
+ pt_size = unit(1:10, "mm")) |
|
291 |
+draw(anno, index, test = "a numeric vector") |
|
292 |
+anno = anno_simple(1:10, pch = 1:10, pt_gp = gpar(col = rep(c(1, 2), each = 5)), |
|
293 |
+ pt_size = unit(1:10, "mm"), which = "row") |
|
294 |
+draw(anno, index, test = "a numeric vector") |
|
295 |
+ |
|
296 |
+ |
|
297 |
+anno = anno_points(1:10, pch = 1:10, gp = gpar(col = rep(c(1, 2), each = 5)), |
|
298 |
+ size = unit(1:10, "mm")) |
|
299 |
+draw(anno, index, test = "a numeric vector") |
|
300 |
+anno = anno_points(1:10, pch = 1:10, gp = gpar(col = rep(c(1, 2), each = 5)), |
|
301 |
+ size = unit(1:10, "mm"), which = "row") |
|
302 |
+draw(anno, index, test = "a numeric vector") |
|
303 |
+ |
|
304 |
+ |
|
305 |
+anno = anno_lines(sort(runif(10)), pch = 1:10, pt_gp = gpar(col = rep(c(1, 2), each = 5)), |
|
306 |
+ size = unit(1:10, "mm"), add_points = TRUE) |
|
307 |
+draw(anno, index, test = "a numeric vector") |
|
308 |
+anno = anno_lines(sort(runif(10)), pch = 1:10, pt_gp = gpar(col = rep(c(1, 2), each = 5)), |
|
309 |
+ size = unit(1:10, "mm"), add_points = TRUE, which = "row") |
|
310 |
+draw(anno, index, test = "a numeric vector") |
|
311 |
+ |
|
312 |
+ |
|
313 |
+anno = anno_barplot(1:10, gp = gpar(fill = rep(c(1, 2), each = 5))) |
|
314 |
+draw(anno, index, test = "a numeric vector") |
|
315 |
+anno = anno_barplot(1:10, gp = gpar(fill = rep(c(1, 2), each = 5)), which = "row") |
|
316 |
+draw(anno, index, test = "a numeric vector") |
|
317 |
+ |
|
318 |
+anno = anno_barplot(cbind(1:10, 10:1), gp = gpar(fill = 1:2)) |
|
319 |
+draw(anno, index, test = "a numeric vector") |
|
320 |
+anno = anno_barplot(cbind(1:10, 10:1), gp = gpar(fill = 1:2), which = "row") |
|
321 |
+draw(anno, index, test = "a numeric vector") |
|
322 |
+ |
|
323 |
+ |
|
324 |
+m = matrix(rnorm(100), 10) |
|
325 |
+m = m[, order(apply(m, 2, median))] |
|
326 |
+anno = anno_boxplot(m, pch = 1:10, gp = gpar(fill = rep(c(1, 2), each = 5)), |
|
327 |
+ size = unit(1:10, "mm"), height = unit(4, "cm")) |
|
328 |
+draw(anno, index, test = "a numeric vector") |
|
329 |
+anno = anno_boxplot(t(m), pch = 1:10, gp = gpar(fill = rep(c(1, 2), each = 5)), |
|
330 |
+ size = unit(1:10, "mm"), which = "row", width = unit(4, "cm")) |
|
331 |
+draw(anno, index, test = "a numeric vector") |
|
332 |
+ |
|
333 |
+anno = anno_histogram(m, gp = gpar(fill = rep(c(1, 2), each = 5))) |
|
334 |
+draw(anno, index, test = "a numeric vector") |
|
335 |
+anno = anno_histogram(t(m), gp = gpar(fill = rep(c(1, 2), each = 5)), which = "row") |
|
336 |
+draw(anno, index, test = "a numeric vector") |
|
337 |
+ |
|
338 |
+anno = anno_density(m, gp = gpar(fill = rep(c(1, 2), each = 5))) |
|
339 |
+draw(anno, index, test = "a numeric vector") |
|
340 |
+anno = anno_density(t(m), gp = gpar(fill = rep(c(1, 2), each = 5)), which = "row") |
|
341 |
+draw(anno, index, test = "a numeric vector") |
|
342 |
+ |
|
343 |
+ |
|
344 |
+anno = anno_density(m, type = "violin", gp = gpar(fill = rep(c(1, 2), each = 5))) |
|
345 |
+draw(anno, index, test = "a numeric vector") |
|
346 |
+anno = anno_density(t(m), type = "violin", gp = gpar(fill = rep(c(1, 2), each = 5)), which = "row") |
|
347 |
+draw(anno, index, test = "a numeric vector") |
|
348 |
+ |
|
349 |
+ |
|
350 |
+anno = anno_text(month.name, gp = gpar(col = rep(c(1, 2), each = 5))) |
|
351 |
+draw(anno, index, test = "a numeric vector") |
|
352 |
+anno = anno_text(month.name, gp = gpar(col = rep(c(1, 2), each = 5)), which= "row") |
|
353 |
+draw(anno, index, test = "a numeric vector") |
|
354 |
+ |
|
355 |
+lt = lapply(1:10, function(x) cumprod(1 + runif(1000, -x/100, x/100)) - 1) |
|
356 |
+anno = anno_horizon(lt, gp = gpar(pos_fill = rep(c(1, 2), each = 5), neg_fill = rep(c(3, 4), each = 5)), which = "row") |
|
357 |
+draw(anno, index, test = "a numeric vector") |
|
358 |
+ |
|
359 |
+m = matrix(rnorm(1000), nc = 10) |
|
360 |
+lt = apply(m, 2, function(x) data.frame(density(x)[c("x", "y")])) |
|
361 |
+anno = anno_joyplot(lt, gp = gpar(fill = rep(c(1, 2), each = 5)), |
|
362 |
+ width = unit(4, "cm"), which = "row") |
|
363 |
+draw(anno, index, test = "joyplot") |
|
364 |
+ |
|
365 |
+ |
|
366 |
+anno = anno_block(gp = gpar(fill = 1:4)) |
|
367 |
+draw(anno, index = 1:10, k = 1, n = 4, test = "anno_block") |
|
368 |
+draw(anno, index = 1:10, k = 2, n = 4, test = "anno_block") |
|
369 |
+ |
|
370 |
+anno = anno_block(gp = gpar(fill = 1:4), labels = letters[1:4], labels_gp = gpar(col = "white")) |
|
371 |
+draw(anno, index = 1:10, k = 2, n = 4, test = "anno_block") |
|
372 |
+draw(anno, index = 1:10, k = 4, n = 4, test = "anno_block") |
|
373 |
+draw(anno, index = 1:10, k = 2, n = 2, test = "anno_block") |
|
374 |
+ |
|
375 |
+anno = anno_block(gp = gpar(fill = 1:4), labels = letters[1:4], labels_gp = gpar(col = "white"), which = "row") |
|
376 |
+draw(anno, index = 1:10, k = 2, n = 4, test = "anno_block") |
|
377 |
+ |
|
378 |
+ |
|
379 |
+### anno_zoom |
|
380 |
+fa = sort(sample(letters[1:3], 100, replace = TRUE, prob = c(1, 2, 3))) |
|
381 |
+panel_fun = function(index, nm) { |
|
382 |
+ grid.rect() |
|
383 |
+ grid.text(nm) |
|
384 |
+} |
|
385 |
+anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun) |
|
386 |
+draw(anno, index = 1:100, test = "anno_zoom") |
|
387 |
+ |
|
388 |
+anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun, |
|
389 |
+ gap = unit(1, "cm")) |
|
390 |
+draw(anno, index = 1:100, test = "anno_zoom, set gap") |
|
391 |
+ |
|
392 |
+anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun, |
|
393 |
+ size = 1:3) |
|
394 |
+draw(anno, index = 1:100, test = "anno_zoom, size set as relative values") |
|
395 |
+ |
|
396 |
+anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun, |
|
397 |
+ size = 1:3, extend = unit(1, "cm")) |
|
398 |
+draw(anno, index = 1:100, test = "anno_zoom, extend") |
|
399 |
+ |
|
400 |
+anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun, |
|
401 |
+ size = unit(1:3, "cm")) |
|
402 |
+draw(anno, index = 1:100, test = "anno_zoom, size set as absolute values") |
|
403 |
+ |
|
404 |
+anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun, |
|
405 |
+ size = unit(c(2, 20, 40), "cm")) |
|
406 |
+draw(anno, index = 1:100, test = "anno_zoom, big size") |
|
407 |
+ |
|
408 |
+anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun, |
|
409 |
+ size = 1:3, gap = unit(1, "cm")) |
|
410 |
+draw(anno, index = 1:100, test = "anno_zoom, size set as relative values, gap") |
|
411 |
+ |
|
412 |
+anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun, |
|
413 |
+ size = unit(1:3, "cm"), gap = unit(1, "cm")) |
|
414 |
+draw(anno, index = 1:100, test = "anno_zoom, size set as absolute values, gap") |
|
415 |
+ |
|
416 |
+ |
|
417 |
+anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun, |
|
418 |
+ size = unit(1:3, "cm"), side = "left") |
|
419 |
+draw(anno, index = 1:100, test = "anno_zoom, side") |
|
420 |
+ |
|
421 |
+ |
|
422 |
+anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun, |
|
423 |
+ size = unit(1:3, "cm"), link_gp = gpar(fill = 1:3)) |
|
424 |
+draw(anno, index = 1:100, test = "anno_zoom, link_gp") |
|
425 |
+ |
|
426 |
+anno = anno_zoom(align_to = fa, which = "row", panel_fun = panel_fun, |
|
427 |
+ size = unit(1:3, "cm"), link_gp = gpar(fill = 1:3), |
|
428 |
+ link_width = unit(2, "cm"), width = unit(4, "cm")) |
|
429 |
+draw(anno, index = 1:100, test = "anno_zoom, width") |
|
430 |
+ |
|
431 |
+anno = anno_zoom(align_to = list(a = 1:10, b = 30:45, c = 70:90), |
|
432 |
+ which = "row", panel_fun = panel_fun, size = unit(1:3, "cm")) |
|
433 |
+draw(anno, index = 1:100, test = "anno_zoom, a list of indices") |
|
434 |
+ |
|
435 |
+anno = anno_zoom(align_to = fa, which = "column", panel_fun = panel_fun, |
|
436 |
+ size = unit(1:3, "cm")) |
|
437 |
+draw(anno, index = 1:100, test = "anno_zoom, column annotation") |
|
438 |
+ |
|
439 |
+ |
|
440 |
+m = matrix(rnorm(100*10), nrow = 100) |
|
441 |
+hc = hclust(dist(m)) |
|
442 |
+fa2 = cutree(hc, k = 4) |
|
443 |
+anno = anno_zoom(align_to = fa2, which = "row", panel_fun = panel_fun) |
|
444 |
+draw(anno, index = hc$order, test = "anno_zoom, column annotation") |
|
445 |
+ |
|
446 |
+anno = anno_zoom(align_to = fa2, which = "column", panel_fun = panel_fun) |
|
447 |
+draw(anno, index = hc$order, test = "anno_zoom, column annotation") |
|
448 |
+ |
|
449 |
+ |
|
450 |
+anno = anno_zoom(align_to = fa2, which = "row", panel_fun = panel_fun) |
|
451 |
+Heatmap(m, cluster_rows = hc, right_annotation = rowAnnotation(foo = anno)) |
|
452 |
+Heatmap(m, cluster_rows = hc, right_annotation = rowAnnotation(foo = anno), row_split = 2) |
|
453 |
+ |
|
454 |
+ |
|
455 |
+anno = anno_zoom(align_to = fa2, which = "row", panel_fun = panel_fun, size = unit(1:4, "cm")) |
|
456 |
+Heatmap(m, cluster_rows = hc, right_annotation = rowAnnotation(foo = anno)) |
|
457 |
+ |
|
458 |
+set.seed(123) |
|
459 |
+m = matrix(rnorm(100*10), nrow = 100) |
|
460 |
+subgroup = sample(letters[1:3], 100, replace = TRUE, prob = c(1, 5, 10)) |
|
461 |
+rg = range(m) |
|
462 |
+panel_fun = function(index, nm) { |
|
463 |
+ pushViewport(viewport(xscale = rg, yscale = c(0, 2))) |
|
464 |
+ grid.rect() |
|
465 |
+ grid.xaxis(gp = gpar(fontsize = 8)) |
|
466 |
+ grid.boxplot(m[index, ], pos = 1, direction = "horizontal") |
|
467 |
+ grid.text(paste("distribution of group", nm), mean(rg), y = 1.9, |
|
468 |
+ just = "top", default.units = "native", gp = gpar(fontsize = 10)) |
|
469 |
+ popViewport() |
|
470 |
+} |
|
471 |
+anno = anno_zoom(align_to = subgroup, which = "row", panel_fun = panel_fun, |
|
472 |
+ size = unit(2, "cm"), gap = unit(1, "cm"), width = unit(4, "cm")) |
|
473 |
+Heatmap(m, right_annotation = rowAnnotation(foo = anno), row_split = subgroup) |
|
474 |
+ |
|
475 |
+panel_fun2 = function(index, nm) { |
|
476 |
+ pushViewport(viewport()) |
|
477 |
+ grid.rect() |
|
478 |
+ n = floor(length(index)/4) |
|
479 |
+ txt = paste("gene function", 1:n, collapse = "\n") |
|
480 |
+ grid.text(txt, 0.95, 0.5, default.units = "npc", just = "right", gp = gpar(fontsize = 8)) |
|
481 |
+ popViewport() |
|
482 |
+} |
|
483 |
+anno2 = anno_zoom(align_to = subgroup, which = "row", panel_fun = panel_fun2, |
|
484 |
+ gap = unit(1, "cm"), width = unit(3, "cm"), side = "left") |
|
485 |
+ |
|
486 |
+# in infinite loop |
|
487 |
+Heatmap(m, right_annotation = rowAnnotation(subgroup = subgroup, foo = anno, |
|
488 |
+ show_annotation_name = FALSE), |
|
489 |
+ left_annotation = rowAnnotation(bar = anno2, subgroup = subgroup, show_annotation_name = FALSE), |
|
490 |
+ show_row_dend = FALSE, |
|
491 |
+ row_split = subgroup) |
|
492 |
+ |
|
493 |
+Heatmap(m, right_annotation = rowAnnotation(foo = anno), |
|
494 |
+ left_annotation = rowAnnotation(bar = anno2), |
|
495 |
+ show_row_dend = FALSE, |
|
496 |
+ row_split = subgroup) |