... | ... |
@@ -420,20 +420,6 @@ text_width = function(text, gp = gpar()) { |
420 | 420 |
convertWidth(u, "mm") |
421 | 421 |
} |
422 | 422 |
|
423 |
-grid.text = function(label, x = unit(0.5, "npc"), y = unit(0.5, "npc"), |
|
424 |
- just = "centre", hjust = NULL, vjust = NULL, rot = 0, check.overlap = FALSE, |
|
425 |
- default.units = "npc", name = NULL, gp = gpar(), draw = TRUE, |
|
426 |
- vp = NULL) { |
|
427 |
- tg <- textGrob(label = label, x = x, y = y, just = just, |
|
428 |
- hjust = hjust, vjust = vjust, rot = rot, check.overlap = check.overlap, |
|
429 |
- default.units = default.units, name = name, gp = gp, |
|
430 |
- vp = vp) |
|
431 |
- tw = text_width(label) |
|
432 |
- th = text_height(label) |
|
433 |
- grid.draw(tg) |
|
434 |
- if(identical(just, "")) |
|
435 |
-} |
|
436 |
- |
|
437 | 423 |
text_height = function(text, gp = gpar()) { |
438 | 424 |
if(is.null(text)) { |
439 | 425 |
return(unit(0, "mm")) |
... | ... |
@@ -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() |