... | ... |
@@ -567,9 +567,11 @@ oncoPrint = function(mat, name, |
567 | 567 |
|
568 | 568 |
# adjust order of alter_fun3 with at |
569 | 569 |
if(!is.null(heatmap_legend_param$at)) { |
570 |
- if(length(setdiff(heatmap_legend_param$at, names(alter_fun3))) == 0) { |
|
571 |
- alter_fun3 = alter_fun3[heatmap_legend_param$at] |
|
572 |
- } |
|
570 |
+ ind = which(heatmap_legend_param$at %in% names(alter_fun3)) |
|
571 |
+ heatmap_legend_param$at = heatmap_legend_param$at[ind] |
|
572 |
+ heatmap_legend_param$labels = heatmap_legend_param$labels[ind] |
|
573 |
+ |
|
574 |
+ alter_fun3 = alter_fun3[heatmap_legend_param$at] |
|
573 | 575 |
} |
574 | 576 |
|
575 | 577 |
heatmap_legend_param$graphics = alter_fun3 |
... | ... |
@@ -23,6 +23,7 @@ |
23 | 23 |
# -pct_gp Graphic paramters for percent values |
24 | 24 |
# -pct_digits Digits for the percent values. |
25 | 25 |
# -pct_side Side of the percent values to the oncoPrint. This argument is currently disabled. |
26 |
+# -pct_include Alteration types that are included for the calculation of percent values. |
|
26 | 27 |
# -row_labels Labels as the row names of the oncoPrint. |
27 | 28 |
# -show_row_names Whether show row names? |
28 | 29 |
# -row_names_side Side of the row names to the oncoPrint. This argument is currently disabled. |
... | ... |
@@ -69,6 +70,7 @@ oncoPrint = function(mat, name, |
69 | 70 |
pct_gp = gpar(fontsize = 10), |
70 | 71 |
pct_digits = 0, |
71 | 72 |
pct_side = "left", |
73 |
+ pct_include = NULL, |
|
72 | 74 |
|
73 | 75 |
row_labels = NULL, |
74 | 76 |
show_row_names = TRUE, |
... | ... |
@@ -368,7 +370,10 @@ oncoPrint = function(mat, name, |
368 | 370 |
} |
369 | 371 |
|
370 | 372 |
# for each gene, percent of samples that have alterations |
371 |
- pct_num = rowSums(apply(arr, 1:2, any)) / ncol(mat_list[[1]]) |
|
373 |
+ if(is.null(pct_include)) { |
|
374 |
+ pct_include = dimnames(arr)[[3]] |
|
375 |
+ } |
|
376 |
+ pct_num = rowSums(apply(arr[, , dimnames(arr)[[3]] %in% pct_include, drop = FALSE], 1:2, any)) / ncol(mat_list[[1]]) |
|
372 | 377 |
pct = paste0(round(pct_num * 100, digits = pct_digits), "%") |
373 | 378 |
|
374 | 379 |
### now the annotations |
... | ... |
@@ -809,7 +809,7 @@ anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
809 | 809 |
var_import = list(border, type, bar_width, beside, axis, axis_param, anno_size, ylim, show_fraction) |
810 | 810 |
) |
811 | 811 |
|
812 |
- anno@subsetable = TRUE |
|
812 |
+ anno@subsettable = TRUE |
|
813 | 813 |
anno@show_name = FALSE |
814 | 814 |
|
815 | 815 |
if(exists("arr", envir = parent.frame(1))) { |
... | ... |
@@ -135,7 +135,7 @@ oncoPrint = function(mat, name, |
135 | 135 |
|
136 | 136 |
## check whether there are NA values in the matrix |
137 | 137 |
if(any(is.na(mat))) { |
138 |
- message_wrap("Found NA values in the matrix and treat as no alteration. If `NA` means no alteration, you can explicitly set it to empty strings like ''. If `NA` is an alteration type, you should format it to a string like `'NA'` and define a graphic for it.") |
|
138 |
+ message_wrap("Found NA values in the matrix and treat as no alteration. If `NA` means no alteration, you can explicitly set it to empty strings like ''. If `NA` is an alteration type, you should format it to a string like `'NA'` and define graphics for it.") |
|
139 | 139 |
} |
140 | 140 |
|
141 | 141 |
mat_list = lapply(all_type, function(type) { |
... | ... |
@@ -711,6 +711,7 @@ unify_mat_list = function(mat_list, default = 0) { |
711 | 711 |
# -type A vector of the alteration types in the data. It can be a subset of all alteration types if you don't want to show them all. |
712 | 712 |
# -which Is it a row annotation or a column annotation? |
713 | 713 |
# -bar_width Width of the bars. |
714 |
+# -beside Will bars be stacked or be positioned beside each other? |
|
714 | 715 |
# -ylim Data range. |
715 | 716 |
# -show_fraction Whether to show the numbers or the fractions? |
716 | 717 |
# -axis Whether draw axis? |
... | ... |
@@ -726,7 +727,7 @@ unify_mat_list = function(mat_list, default = 0) { |
726 | 727 |
# Zuguang Gu <z.gu@dkfz.de> |
727 | 728 |
# |
728 | 729 |
anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
729 |
- bar_width = 0.6, ylim = NULL, show_fraction = FALSE, axis = TRUE, |
|
730 |
+ bar_width = 0.6, beside = FALSE, ylim = NULL, show_fraction = FALSE, axis = TRUE, |
|
730 | 731 |
axis_param = if(which == "column") default_axis_param("column") else list(side = "top", labels_rot = 0), |
731 | 732 |
width = NULL, height = NULL, border = FALSE) { |
732 | 733 |
|
... | ... |
@@ -761,7 +762,7 @@ anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
761 | 762 |
v = v[, !is.na(col), drop = FALSE] |
762 | 763 |
col = col[!is.na(col)] |
763 | 764 |
fun = anno_barplot(v, gp = gpar(fill = col, col = NA), which = "column", ylim = ylim, |
764 |
- baseline = 0, height = anno_size$height, border = border, bar_width = bar_width, |
|
765 |
+ baseline = 0, height = anno_size$height, border = border, bar_width = bar_width, beside = beside, |
|
765 | 766 |
axis = axis, axis_param = axis_param)@fun |
766 | 767 |
fun(index, k, n) |
767 | 768 |
} |
... | ... |
@@ -788,7 +789,7 @@ anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
788 | 789 |
v = v[, !is.na(col), drop = FALSE] |
789 | 790 |
col = col[!is.na(col)] |
790 | 791 |
fun = anno_barplot(v, gp = gpar(fill = col, col = NA), which = "row", ylim = ylim, |
791 |
- baseline = 0, width = anno_size$width, border = border, bar_width = bar_width, |
|
792 |
+ baseline = 0, width = anno_size$width, border = border, bar_width = bar_width, beside = beside, |
|
792 | 793 |
axis = axis, axis_param = axis_param)@fun |
793 | 794 |
fun(index, k, n) |
794 | 795 |
} |
... | ... |
@@ -805,7 +806,7 @@ anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
805 | 806 |
which = which, |
806 | 807 |
width = anno_size$width, |
807 | 808 |
height = anno_size$height, |
808 |
- var_import = list(border, type, bar_width, axis, axis_param, anno_size, ylim, show_fraction) |
|
809 |
+ var_import = list(border, type, bar_width, beside, axis, axis_param, anno_size, ylim, show_fraction) |
|
809 | 810 |
) |
810 | 811 |
|
811 | 812 |
anno@subsetable = TRUE |
... | ... |
@@ -299,6 +299,8 @@ oncoPrint = function(mat, name, |
299 | 299 |
if(alter_fun_is_vectorized) { |
300 | 300 |
layer_fun = function(j, i, x, y, w, h, fill) { |
301 | 301 |
v = pindex(arr, i, j) |
302 |
+ v = as.vector(v) |
|
303 |
+ names(v) = dimnames[[3]] |
|
302 | 304 |
af(x, y, w, h, v, j, i) |
303 | 305 |
} |
304 | 306 |
cell_fun = NULL |
... | ... |
@@ -306,6 +308,7 @@ oncoPrint = function(mat, name, |
306 | 308 |
layer_fun = NULL |
307 | 309 |
cell_fun = function(j, i, x, y, w, h, fill) { |
308 | 310 |
v = arr[i, j, ] |
311 |
+ names(v) = dimnames[[3]] |
|
309 | 312 |
af(x, y, w, h, v, j, i) |
310 | 313 |
} |
311 | 314 |
} |
... | ... |
@@ -184,10 +184,10 @@ oncoPrint = function(mat, name, |
184 | 184 |
} |
185 | 185 |
|
186 | 186 |
if(missing(name)) { |
187 |
- name = paste0("matrix_", get_oncoprint_index() + 1) |
|
187 |
+ name = paste0("oncoPrint_", get_oncoprint_index() + 1) |
|
188 | 188 |
increase_oncoprint_index() |
189 | 189 |
} else if(is.null(name)) { |
190 |
- name = paste0("matrix_", get_oncoprint_index() + 1) |
|
190 |
+ name = paste0("oncnPrint_", get_oncoprint_index() + 1) |
|
191 | 191 |
increase_oncoprint_index() |
192 | 192 |
} |
193 | 193 |
|
... | ... |
@@ -8,6 +8,7 @@ |
8 | 8 |
# value representing whether the alteration is present or absent. |
9 | 9 |
# When the value is a list, the names of the list represent alteration types. |
10 | 10 |
# You can use `unify_mat_list` to make all matrix having same row names and column names. |
11 |
+# -name Name of the oncoPrint. Not necessary to specify. |
|
11 | 12 |
# -get_type If different alterations are encoded in the matrix as complex strings, this self-defined function |
12 | 13 |
# determines how to extract them. It only works when ``mat`` is a matrix. The default value is `default_get_type`. |
13 | 14 |
# -alter_fun A single function or a list of functions which defines how to add graphics for different alterations. |
... | ... |
@@ -53,7 +54,7 @@ |
53 | 54 |
# == author |
54 | 55 |
# Zuguang Gu <z.gu@dkfz.de> |
55 | 56 |
# |
56 |
-oncoPrint = function(mat, |
|
57 |
+oncoPrint = function(mat, name, |
|
57 | 58 |
get_type = default_get_type, |
58 | 59 |
alter_fun, |
59 | 60 |
alter_fun_is_vectorized = NULL, |
... | ... |
@@ -182,6 +183,14 @@ oncoPrint = function(mat, |
182 | 183 |
arr[, , i] = mat_list[[i]] |
183 | 184 |
} |
184 | 185 |
|
186 |
+ if(missing(name)) { |
|
187 |
+ name = paste0("matrix_", get_oncoprint_index() + 1) |
|
188 |
+ increase_oncoprint_index() |
|
189 |
+ } else if(is.null(name)) { |
|
190 |
+ name = paste0("matrix_", get_oncoprint_index() + 1) |
|
191 |
+ increase_oncoprint_index() |
|
192 |
+ } |
|
193 |
+ |
|
185 | 194 |
oncoprint_row_order = function() { |
186 | 195 |
order(rowSums(count_matrix), n_mut, decreasing = TRUE) |
187 | 196 |
} |
... | ... |
@@ -468,13 +477,17 @@ oncoPrint = function(mat, |
468 | 477 |
|
469 | 478 |
##################################################################### |
470 | 479 |
# the main matrix |
471 |
- if(length(col)) { |
|
472 |
- pheudo = c(names(col), rep(NA, nrow(arr)*ncol(arr) - length(col))) |
|
473 |
- } else { |
|
474 |
- pheudo = c("mutation", rep(NA, nrow(arr)*ncol(arr) - 1)) |
|
480 |
+ if(length(col) == 0) { |
|
475 | 481 |
col = c("mutation" = "black") |
476 | 482 |
} |
477 | 483 |
|
484 |
+ pheudo = apply(arr, 1:2, function(x) { |
|
485 |
+ if(all(!x)) { |
|
486 |
+ return("") |
|
487 |
+ } else { |
|
488 |
+ paste(all_type[x], collapse = ";") |
|
489 |
+ } |
|
490 |
+ }) |
|
478 | 491 |
dim(pheudo) = dim(arr)[1:2] |
479 | 492 |
dimnames(pheudo) = dimnames(arr)[1:2] |
480 | 493 |
|
... | ... |
@@ -558,7 +571,7 @@ oncoPrint = function(mat, |
558 | 571 |
} |
559 | 572 |
} |
560 | 573 |
|
561 |
- ht = Heatmap(pheudo, col = col, |
|
574 |
+ ht = Heatmap(pheudo, name = name, col = col, |
|
562 | 575 |
rect_gp = gpar(type = "none"), |
563 | 576 |
cluster_rows = cluster_rows, cluster_columns = cluster_columns, |
564 | 577 |
row_order = row_order, column_order = column_order, |
... | ... |
@@ -172,7 +172,12 @@ oncoPrint = function(mat, |
172 | 172 |
message_wrap(paste0("All mutation types: ", paste(all_type, collapse = ", "), ".")) |
173 | 173 |
|
174 | 174 |
# type as the third dimension |
175 |
- arr = array(FALSE, dim = c(dim(mat_list[[1]]), length(all_type)), dimnames = c(dimnames(mat_list[[1]]), list(all_type))) |
|
175 |
+ if(is.null(dimnames(mat_list[[1]]))) { |
|
176 |
+ dimnames = c(list(NULL), list(NULL), list(all_type)) |
|
177 |
+ } else { |
|
178 |
+ dimnames = c(dimnames(mat_list[[1]]), list(all_type)) |
|
179 |
+ } |
|
180 |
+ arr = array(FALSE, dim = c(dim(mat_list[[1]]), length(all_type)), dimnames = dimnames) |
|
176 | 181 |
for(i in seq_along(all_type)) { |
177 | 182 |
arr[, , i] = mat_list[[i]] |
178 | 183 |
} |
... | ... |
@@ -392,6 +392,28 @@ oncoPrint = function(mat, |
392 | 392 |
} else { |
393 | 393 |
rn_ha = NULL |
394 | 394 |
} |
395 |
+ |
|
396 |
+ |
|
397 |
+ if(!is.null(top_annotation)) { |
|
398 |
+ if(inherits(top_annotation, "AnnotationFunction")) { |
|
399 |
+ stop_wrap("The annotation function `anno_*()` should be put inside `HeatmapAnnotation()`.") |
|
400 |
+ } |
|
401 |
+ } |
|
402 |
+ if(!is.null(bottom_annotation)) { |
|
403 |
+ if(inherits(bottom_annotation, "AnnotationFunction")) { |
|
404 |
+ stop_wrap("The annotation function `anno_*()` should be put inside `HeatmapAnnotation()`.") |
|
405 |
+ } |
|
406 |
+ } |
|
407 |
+ if(!is.null(left_annotation)) { |
|
408 |
+ if(inherits(left_annotation, "AnnotationFunction")) { |
|
409 |
+ stop_wrap("The annotation function `anno_*()` should be put inside `rowAnnotation()`.") |
|
410 |
+ } |
|
411 |
+ } |
|
412 |
+ if(!is.null(right_annotation)) { |
|
413 |
+ if(inherits(right_annotation, "AnnotationFunction")) { |
|
414 |
+ stop_wrap("The annotation function `anno_*()` should be put inside `rowAnnotation()`.") |
|
415 |
+ } |
|
416 |
+ } |
|
395 | 417 |
|
396 | 418 |
if(is.null(left_annotation)) { |
397 | 419 |
if(pct_side == "left") { |
... | ... |
@@ -715,6 +715,8 @@ anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
715 | 715 |
} else { |
716 | 716 |
v = apply(arr, c(2, 3), sum) |
717 | 717 |
} |
718 |
+ v = v[, !is.na(col), drop = FALSE] |
|
719 |
+ col = col[!is.na(col)] |
|
718 | 720 |
fun = anno_barplot(v, gp = gpar(fill = col, col = NA), which = "column", ylim = ylim, |
719 | 721 |
baseline = 0, height = anno_size$height, border = border, bar_width = bar_width, |
720 | 722 |
axis = axis, axis_param = axis_param)@fun |
... | ... |
@@ -740,6 +742,8 @@ anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
740 | 742 |
} else { |
741 | 743 |
v = apply(arr, c(1, 3), sum) |
742 | 744 |
} |
745 |
+ v = v[, !is.na(col), drop = FALSE] |
|
746 |
+ col = col[!is.na(col)] |
|
743 | 747 |
fun = anno_barplot(v, gp = gpar(fill = col, col = NA), which = "row", ylim = ylim, |
744 | 748 |
baseline = 0, width = anno_size$width, border = border, bar_width = bar_width, |
745 | 749 |
axis = axis, axis_param = axis_param)@fun |
... | ... |
@@ -87,7 +87,7 @@ oncoPrint = function(mat, |
87 | 87 |
remove_empty_columns = FALSE, |
88 | 88 |
remove_empty_rows = FALSE, |
89 | 89 |
show_column_names = FALSE, |
90 |
- heatmap_legend_param = list(title = "Alterations"), |
|
90 |
+ heatmap_legend_param = NULL, |
|
91 | 91 |
...) { |
92 | 92 |
|
93 | 93 |
dev.null() |
... | ... |
@@ -169,7 +169,7 @@ oncoPrint = function(mat, |
169 | 169 |
stop_wrap("Incorrect type of 'mat'") |
170 | 170 |
} |
171 | 171 |
|
172 |
- message_wrap(paste0("All mutation types: ", paste(all_type, collapse = ", "))) |
|
172 |
+ message_wrap(paste0("All mutation types: ", paste(all_type, collapse = ", "), ".")) |
|
173 | 173 |
|
174 | 174 |
# type as the third dimension |
175 | 175 |
arr = array(FALSE, dim = c(dim(mat_list[[1]]), length(all_type)), dimnames = c(dimnames(mat_list[[1]]), list(all_type))) |
... | ... |
@@ -347,7 +347,7 @@ oncoPrint = function(mat, |
347 | 347 |
# validate col |
348 | 348 |
sdf = setdiff(all_type, names(col)) |
349 | 349 |
if(length(sdf) > 0) { |
350 |
- message_wrap(paste0("Colors are not defined for: ", paste(sdf, collapse = ", "))) |
|
350 |
+ message_wrap(paste0("Colors are not defined for: ", paste(sdf, collapse = ", "), ". They won't be shown in the barplots.")) |
|
351 | 351 |
} |
352 | 352 |
|
353 | 353 |
# for each gene, percent of samples that have alterations |
... | ... |
@@ -468,6 +468,69 @@ oncoPrint = function(mat, |
468 | 468 |
} |
469 | 469 |
} |
470 | 470 |
|
471 |
+ if(is.list(alter_fun)) { |
|
472 |
+ if(is.null(alter_fun$background)) { |
|
473 |
+ background_fun = function(x, y, w, h) NULL |
|
474 |
+ } else { |
|
475 |
+ background_fun = alter_fun$background |
|
476 |
+ } |
|
477 |
+ |
|
478 |
+ alter_fun2 = alter_fun[names(alter_fun) != "background"] |
|
479 |
+ alter_fun3 = alter_fun2 |
|
480 |
+ for(i in seq_along(alter_fun2)) { |
|
481 |
+ alter_fun3[[i]] = local({ |
|
482 |
+ i = i |
|
483 |
+ function(x, y, w, h) { |
|
484 |
+ background_fun(x, y, w, h) |
|
485 |
+ alter_fun2[[i]](x, y, w, h) |
|
486 |
+ } |
|
487 |
+ }) |
|
488 |
+ } |
|
489 |
+ } else { |
|
490 |
+ all_type_binary = structure(rep(FALSE, length(all_type)), names = all_type) |
|
491 |
+ background_fun = function(x, y, w, h) { |
|
492 |
+ alter_fun(x, y, w, h, all_type_binary) |
|
493 |
+ } |
|
494 |
+ alter_fun3 = list() |
|
495 |
+ for(nm in all_type) { |
|
496 |
+ alter_fun3[[nm]] = local({ |
|
497 |
+ all_type_binary2 = all_type_binary |
|
498 |
+ all_type_binary2[nm] = TRUE |
|
499 |
+ function(x, y, w, h) { |
|
500 |
+ alter_fun(x, y, w, h, all_type_binary2) |
|
501 |
+ } |
|
502 |
+ }) |
|
503 |
+ } |
|
504 |
+ } |
|
505 |
+ |
|
506 |
+ if(is.null(heatmap_legend_param)) { |
|
507 |
+ heatmap_legend_param = list( |
|
508 |
+ title = "Alterations", |
|
509 |
+ at = names(alter_fun3), |
|
510 |
+ graphics = alter_fun3 |
|
511 |
+ ) |
|
512 |
+ col2 = structure(rep(NA, length(alter_fun3)), names = names(alter_fun3)) |
|
513 |
+ col2[names(col)] = col |
|
514 |
+ col = col2 |
|
515 |
+ } else { |
|
516 |
+ if(! "graphics" %in% names(heatmap_legend_param)) { |
|
517 |
+ if(is.null(heatmap_legend_param$at)) heatmap_legend_param$at = names(alter_fun3) |
|
518 |
+ if(is.null(heatmap_legend_param$labels)) heatmap_legend_param$labels = heatmap_legend_param$at |
|
519 |
+ |
|
520 |
+ # adjust order of alter_fun3 with at |
|
521 |
+ if(!is.null(heatmap_legend_param$at)) { |
|
522 |
+ if(length(setdiff(heatmap_legend_param$at, names(alter_fun3))) == 0) { |
|
523 |
+ alter_fun3 = alter_fun3[heatmap_legend_param$at] |
|
524 |
+ } |
|
525 |
+ } |
|
526 |
+ |
|
527 |
+ heatmap_legend_param$graphics = alter_fun3 |
|
528 |
+ col2 = structure(rep(NA, length(alter_fun3)), names = names(alter_fun3)) |
|
529 |
+ col2[names(col)] = col |
|
530 |
+ col = col2 |
|
531 |
+ } |
|
532 |
+ } |
|
533 |
+ |
|
471 | 534 |
ht = Heatmap(pheudo, col = col, |
472 | 535 |
rect_gp = gpar(type = "none"), |
473 | 536 |
cluster_rows = cluster_rows, cluster_columns = cluster_columns, |
... | ... |
@@ -722,6 +785,12 @@ anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
722 | 785 |
guess_alter_fun_is_vectorized = function(alter_fun) { |
723 | 786 |
n = 50 |
724 | 787 |
if(is.list(alter_fun)) { |
788 |
+ |
|
789 |
+ # check whether grid.polygon is called |
|
790 |
+ if(any(sapply(alter_fun, function(f) any(grepl("grid\\.polygon\\(", as.character(body(f))))))) { |
|
791 |
+ return(FALSE) |
|
792 |
+ } |
|
793 |
+ |
|
725 | 794 |
x = unit(1:n/n, "npc") |
726 | 795 |
y = unit(1:n/n, "npc") |
727 | 796 |
w = unit(1:n, "mm") |
... | ... |
@@ -736,6 +805,7 @@ guess_alter_fun_is_vectorized = function(alter_fun) { |
736 | 805 |
if(inherits(oe, "try-error")) { |
737 | 806 |
return(FALSE) |
738 | 807 |
} else { |
808 |
+ message_wrap("`alter_fun` is assumed vectorizable. If it does not generate correct plot, please set `alter_fun_is_vectorized = FALSE` in `oncoPrint()`.") |
|
739 | 809 |
return(TRUE) |
740 | 810 |
} |
741 | 811 |
} else { |
... | ... |
@@ -722,8 +722,8 @@ anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
722 | 722 |
guess_alter_fun_is_vectorized = function(alter_fun) { |
723 | 723 |
n = 50 |
724 | 724 |
if(is.list(alter_fun)) { |
725 |
- x = 1:n |
|
726 |
- y = 1:n |
|
725 |
+ x = unit(1:n/n, "npc") |
|
726 |
+ y = unit(1:n/n, "npc") |
|
727 | 727 |
w = unit(1:n, "mm") |
728 | 728 |
h = unit(1:n, "mm") |
729 | 729 |
dev.null() |
... | ... |
@@ -754,7 +754,8 @@ guess_alter_fun_is_vectorized = function(alter_fun) { |
754 | 754 |
# |
755 | 755 |
default_get_type = function(x) { |
756 | 756 |
x = strsplit(x, "\\s*[;:,|]\\s*")[[1]] |
757 |
- x[!x %in% c("na", "NA")] |
|
757 |
+ # x[!x %in% c("na", "NA")] |
|
758 |
+ x |
|
758 | 759 |
} |
759 | 760 |
|
760 | 761 |
# == title |
... | ... |
@@ -606,6 +606,7 @@ unify_mat_list = function(mat_list, default = 0) { |
606 | 606 |
# -which Is it a row annotation or a column annotation? |
607 | 607 |
# -bar_width Width of the bars. |
608 | 608 |
# -ylim Data range. |
609 |
+# -show_fraction Whether to show the numbers or the fractions? |
|
609 | 610 |
# -axis Whether draw axis? |
610 | 611 |
# -axis_param Parameters for controlling axis. |
611 | 612 |
# -width Width of the annotation. |
... | ... |
@@ -619,7 +620,7 @@ unify_mat_list = function(mat_list, default = 0) { |
619 | 620 |
# Zuguang Gu <z.gu@dkfz.de> |
620 | 621 |
# |
621 | 622 |
anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
622 |
- bar_width = 0.6, ylim = NULL, axis = TRUE, |
|
623 |
+ bar_width = 0.6, ylim = NULL, show_fraction = FALSE, axis = TRUE, |
|
623 | 624 |
axis_param = if(which == "column") default_axis_param("column") else list(side = "top", labels_rot = 0), |
624 | 625 |
width = NULL, height = NULL, border = FALSE) { |
625 | 626 |
|
... | ... |
@@ -646,8 +647,12 @@ anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
646 | 647 |
arr = arr[, , all_type, drop = FALSE] |
647 | 648 |
col = col[all_type] |
648 | 649 |
|
649 |
- count = apply(arr, c(2, 3), sum) |
|
650 |
- fun = anno_barplot(count, gp = gpar(fill = col, col = NA), which = "column", ylim = ylim, |
|
650 |
+ if(show_fraction) { |
|
651 |
+ v = apply(arr, c(2, 3), sum)/dim(arr)[1] |
|
652 |
+ } else { |
|
653 |
+ v = apply(arr, c(2, 3), sum) |
|
654 |
+ } |
|
655 |
+ fun = anno_barplot(v, gp = gpar(fill = col, col = NA), which = "column", ylim = ylim, |
|
651 | 656 |
baseline = 0, height = anno_size$height, border = border, bar_width = bar_width, |
652 | 657 |
axis = axis, axis_param = axis_param)@fun |
653 | 658 |
fun(index, k, n) |
... | ... |
@@ -667,8 +672,12 @@ anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
667 | 672 |
arr = arr[, , all_type, drop = FALSE] |
668 | 673 |
col = col[all_type] |
669 | 674 |
|
670 |
- count = apply(arr, c(1, 3), sum) |
|
671 |
- fun = anno_barplot(count, gp = gpar(fill = col, col = NA), which = "row", ylim = ylim, |
|
675 |
+ if(show_fraction) { |
|
676 |
+ v = apply(arr, c(1, 3), sum)/dim(arr)[2] |
|
677 |
+ } else { |
|
678 |
+ v = apply(arr, c(1, 3), sum) |
|
679 |
+ } |
|
680 |
+ fun = anno_barplot(v, gp = gpar(fill = col, col = NA), which = "row", ylim = ylim, |
|
672 | 681 |
baseline = 0, width = anno_size$width, border = border, bar_width = bar_width, |
673 | 682 |
axis = axis, axis_param = axis_param)@fun |
674 | 683 |
fun(index, k, n) |
... | ... |
@@ -686,7 +695,7 @@ anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
686 | 695 |
which = which, |
687 | 696 |
width = anno_size$width, |
688 | 697 |
height = anno_size$height, |
689 |
- var_import = list(border, type, bar_width, axis, axis_param, anno_size, ylim) |
|
698 |
+ var_import = list(border, type, bar_width, axis, axis_param, anno_size, ylim, show_fraction) |
|
690 | 699 |
) |
691 | 700 |
|
692 | 701 |
anno@subsetable = TRUE |
... | ... |
@@ -499,7 +499,7 @@ oncoPrint = function(mat, |
499 | 499 |
# -width Relative width of the rectangle. |
500 | 500 |
# -height Relative height of the rectangle. |
501 | 501 |
# -horiz_margin Horizontal margin. E.g. if you want 1mm margin on top and 1mm margin |
502 |
-# at bottom of the rectangle, set this value to ``unit(1, 'mm')`. |
|
502 |
+# at bottom of the rectangle, set this value to ``unit(1, 'mm')``. |
|
503 | 503 |
# -vertical_margin Vertical margin. |
504 | 504 |
# -fill Filled color. |
505 | 505 |
# -col Border color. |
... | ... |
@@ -527,7 +527,7 @@ oncoPrint = function(mat, |
527 | 527 |
# |
528 | 528 |
alter_graphic = function(graphic = c("rect", "point"), |
529 | 529 |
width = 1, height = 1, |
530 |
- vertical_margin = unit(0, "mm"), horiz_margin = unit(0, "mm"), |
|
530 |
+ horiz_margin = unit(1, "pt"), vertical_margin = unit(1, "pt"), |
|
531 | 531 |
fill = "red", col = NA, pch = 16, ...) { |
532 | 532 |
|
533 | 533 |
graphic = match.arg(graphic)[1] |
... | ... |
@@ -539,13 +539,23 @@ alter_graphic = function(graphic = c("rect", "point"), |
539 | 539 |
if(!is.numeric(height)) { |
540 | 540 |
stop_wrap("`height` should be nummeric.") |
541 | 541 |
} |
542 |
+ if(width != 1) { |
|
543 |
+ if(missing(horiz_margin)) { |
|
544 |
+ horiz_margin = unit(0, "pt") |
|
545 |
+ } |
|
546 |
+ } |
|
547 |
+ if(height != 1) { |
|
548 |
+ if(missing(vertical_margin)) { |
|
549 |
+ vertical_margin = unit(0, "pt") |
|
550 |
+ } |
|
551 |
+ } |
|
542 | 552 |
fun = function(x, y, w, h) { |
543 | 553 |
w = w*width |
544 | 554 |
h = h*height |
545 |
- grid.rect(x, y, w*width - horiz_margin*2, h*height - vertical_margin*2, |
|
555 |
+ grid.rect(x, y, w - horiz_margin*2, h - vertical_margin*2, |
|
546 | 556 |
gp = gpar(fill = fill, col = col, ...)) |
547 | 557 |
} |
548 |
- } else if(graphc == "point") { |
|
558 |
+ } else if(graphic == "point") { |
|
549 | 559 |
fun = function(x, y, w, h) { |
550 | 560 |
grid.points(x, y, pch = pch, gp = gpar(fill = fill, col = col, ...)) |
551 | 561 |
} |
... | ... |
@@ -11,6 +11,7 @@ |
11 | 11 |
# -get_type If different alterations are encoded in the matrix as complex strings, this self-defined function |
12 | 12 |
# determines how to extract them. It only works when ``mat`` is a matrix. The default value is `default_get_type`. |
13 | 13 |
# -alter_fun A single function or a list of functions which defines how to add graphics for different alterations. |
14 |
+# You can use `alter_graphic` to automatically generate for rectangles and points. |
|
14 | 15 |
# -alter_fun_is_vectorized Whether ``alter_fun`` is implemented vectorized. Internally the function will guess. |
15 | 16 |
# -col A vector of color for which names correspond to alteration types. |
16 | 17 |
# -top_annotation Annotation put on top of the oncoPrint. By default it is barplot which shows the number of genes with a certain alteration in each sample. |
... | ... |
@@ -490,6 +491,68 @@ oncoPrint = function(mat, |
490 | 491 |
return(ht) |
491 | 492 |
} |
492 | 493 |
|
494 |
+# == title |
|
495 |
+# Automatically generate alter_fun |
|
496 |
+# |
|
497 |
+# == param |
|
498 |
+# -graphic Graphic to draw. |
|
499 |
+# -width Relative width of the rectangle. |
|
500 |
+# -height Relative height of the rectangle. |
|
501 |
+# -horiz_margin Horizontal margin. E.g. if you want 1mm margin on top and 1mm margin |
|
502 |
+# at bottom of the rectangle, set this value to ``unit(1, 'mm')`. |
|
503 |
+# -vertical_margin Vertical margin. |
|
504 |
+# -fill Filled color. |
|
505 |
+# -col Border color. |
|
506 |
+# -pch Pch for points |
|
507 |
+# -... Pass to `grid::gpar` |
|
508 |
+# |
|
509 |
+# == details |
|
510 |
+# This function aims to simplify the definition of functions in ``alter_fun``. Now it only |
|
511 |
+# supports rectangles and points. |
|
512 |
+# |
|
513 |
+# == example |
|
514 |
+# mat = read.table(textConnection( |
|
515 |
+# "s1,s2,s3 |
|
516 |
+# g1,snv;indel,snv,indel |
|
517 |
+# g2,,snv;indel,snv |
|
518 |
+# g3,snv,,indel;snv"), row.names = 1, header = TRUE, sep = ",", stringsAsFactors = FALSE) |
|
519 |
+# mat = as.matrix(mat) |
|
520 |
+# col = c(snv = "red", indel = "blue") |
|
521 |
+# |
|
522 |
+# oncoPrint(mat, |
|
523 |
+# alter_fun = list( |
|
524 |
+# snv = alter_graphic("rect", width = 0.9, height = 0.9, fill = col["snv"]), |
|
525 |
+# indel = alter_graphic("rect", width = 0.9, height = 0.9, fill = col["indel"]) |
|
526 |
+# ), col = col) |
|
527 |
+# |
|
528 |
+alter_graphic = function(graphic = c("rect", "point"), |
|
529 |
+ width = 1, height = 1, |
|
530 |
+ vertical_margin = unit(0, "mm"), horiz_margin = unit(0, "mm"), |
|
531 |
+ fill = "red", col = NA, pch = 16, ...) { |
|
532 |
+ |
|
533 |
+ graphic = match.arg(graphic)[1] |
|
534 |
+ |
|
535 |
+ if(graphic == "rect") { |
|
536 |
+ if(!is.numeric(width)) { |
|
537 |
+ stop_wrap("`width` should be nummeric.") |
|
538 |
+ } |
|
539 |
+ if(!is.numeric(height)) { |
|
540 |
+ stop_wrap("`height` should be nummeric.") |
|
541 |
+ } |
|
542 |
+ fun = function(x, y, w, h) { |
|
543 |
+ w = w*width |
|
544 |
+ h = h*height |
|
545 |
+ grid.rect(x, y, w*width - horiz_margin*2, h*height - vertical_margin*2, |
|
546 |
+ gp = gpar(fill = fill, col = col, ...)) |
|
547 |
+ } |
|
548 |
+ } else if(graphc == "point") { |
|
549 |
+ fun = function(x, y, w, h) { |
|
550 |
+ grid.points(x, y, pch = pch, gp = gpar(fill = fill, col = col, ...)) |
|
551 |
+ } |
|
552 |
+ } |
|
553 |
+ return(fun) |
|
554 |
+} |
|
555 |
+ |
|
493 | 556 |
ONCOPRINT_ENV = new.env() |
494 | 557 |
ONCOPRINT_ENV$fun_env = NULL |
495 | 558 |
|
... | ... |
@@ -128,6 +128,11 @@ oncoPrint = function(mat, |
128 | 128 |
all_type = all_type[!is.na(all_type)] |
129 | 129 |
all_type = all_type[grepl("\\S", all_type)] |
130 | 130 |
|
131 |
+ ## check whether there are NA values in the matrix |
|
132 |
+ if(any(is.na(mat))) { |
|
133 |
+ message_wrap("Found NA values in the matrix and treat as no alteration. If `NA` means no alteration, you can explicitly set it to empty strings like ''. If `NA` is an alteration type, you should format it to a string like `'NA'` and define a graphic for it.") |
|
134 |
+ } |
|
135 |
+ |
|
131 | 136 |
mat_list = lapply(all_type, function(type) { |
132 | 137 |
m = sapply(mat, function(x) type %in% get_type2(x)) |
133 | 138 |
dim(m) = dim(mat) |
... | ... |
@@ -30,6 +30,8 @@ |
30 | 30 |
# -column_names_gp Pass to `Heatmap`. |
31 | 31 |
# -column_split Pass to `Heatmap`. |
32 | 32 |
# -row_order Order of rows. By default rows are sorted by the number of occurence of the alterations. |
33 |
+# -cluster_rows If it is set, it must be a dendrogram/hclust object. |
|
34 |
+# -cluster_columns If it is set, it must be a dendrogram/hclust object. |
|
33 | 35 |
# -column_order Order of columns. By default the columns are sorted to show the mutual exclusivity of alterations. |
34 | 36 |
# -remove_empty_columns If there is no alteration in some samples, whether remove them on the oncoPrint? |
35 | 37 |
# -remove_empty_rows If there is no alteration in some samples, whether remove them on the oncoPrint? |
... | ... |
@@ -78,6 +80,8 @@ oncoPrint = function(mat, |
78 | 80 |
|
79 | 81 |
row_order = NULL, |
80 | 82 |
column_order = NULL, |
83 |
+ cluster_rows = FALSE, |
|
84 |
+ cluster_columns = FALSE, |
|
81 | 85 |
|
82 | 86 |
remove_empty_columns = FALSE, |
83 | 87 |
remove_empty_rows = FALSE, |
... | ... |
@@ -439,14 +443,25 @@ oncoPrint = function(mat, |
439 | 443 |
dimnames(pheudo) = dimnames(arr)[1:2] |
440 | 444 |
|
441 | 445 |
if(length(arg_list)) { |
442 |
- if(any(arg_names %in% c("rect_gp", "cluster_rows", "cluster_columns", "cell_fun"))) { |
|
443 |
- stop_wrap("'rect_gp', 'cluster_rows', 'cluster_columns', 'cell_fun' are not allowed to use in `oncoPrint()`.") |
|
446 |
+ if(any(arg_names %in% c("rect_gp", "cell_fun"))) { |
|
447 |
+ stop_wrap("'rect_gp', 'cell_fun' are not allowed to use in `oncoPrint()`.") |
|
448 |
+ } |
|
449 |
+ |
|
450 |
+ if("cluster_rows" %in% arg_names) { |
|
451 |
+ if(!inherits(cluster_rows, c("dendrogram", "hclust"))) { |
|
452 |
+ stop_wrap("`cluster_rows` can only be a dendrogram/hclust object if it is set.") |
|
453 |
+ } |
|
454 |
+ } |
|
455 |
+ if("cluster_columns" %in% arg_names) { |
|
456 |
+ if(!inherits(cluster_columns, c("dendrogram", "hclust"))) { |
|
457 |
+ stop_wrap("`cluster_columns` can only be a dendrogram/hclust object if it is set.") |
|
458 |
+ } |
|
444 | 459 |
} |
445 | 460 |
} |
446 | 461 |
|
447 | 462 |
ht = Heatmap(pheudo, col = col, |
448 | 463 |
rect_gp = gpar(type = "none"), |
449 |
- cluster_rows = FALSE, cluster_columns = FALSE, |
|
464 |
+ cluster_rows = cluster_rows, cluster_columns = cluster_columns, |
|
450 | 465 |
row_order = row_order, column_order = column_order, |
451 | 466 |
row_split = row_split, |
452 | 467 |
column_labels = column_labels, |
... | ... |
@@ -509,9 +509,10 @@ unify_mat_list = function(mat_list, default = 0) { |
509 | 509 |
# -type A vector of the alteration types in the data. It can be a subset of all alteration types if you don't want to show them all. |
510 | 510 |
# -which Is it a row annotation or a column annotation? |
511 | 511 |
# -bar_width Width of the bars. |
512 |
+# -ylim Data range. |
|
512 | 513 |
# -axis Whether draw axis? |
513 | 514 |
# -axis_param Parameters for controlling axis. |
514 |
-# -width Wisth of the annotation. |
|
515 |
+# -width Width of the annotation. |
|
515 | 516 |
# -height Height of the annotation. |
516 | 517 |
# -border Whether draw the border? |
517 | 518 |
# |
... | ... |
@@ -522,7 +523,7 @@ unify_mat_list = function(mat_list, default = 0) { |
522 | 523 |
# Zuguang Gu <z.gu@dkfz.de> |
523 | 524 |
# |
524 | 525 |
anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
525 |
- bar_width = 0.6, axis = TRUE, |
|
526 |
+ bar_width = 0.6, ylim = NULL, axis = TRUE, |
|
526 | 527 |
axis_param = if(which == "column") default_axis_param("column") else list(side = "top", labels_rot = 0), |
527 | 528 |
width = NULL, height = NULL, border = FALSE) { |
528 | 529 |
|
... | ... |
@@ -550,7 +551,7 @@ anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
550 | 551 |
col = col[all_type] |
551 | 552 |
|
552 | 553 |
count = apply(arr, c(2, 3), sum) |
553 |
- fun = anno_barplot(count, gp = gpar(fill = col, col = NA), which = "column", |
|
554 |
+ fun = anno_barplot(count, gp = gpar(fill = col, col = NA), which = "column", ylim = ylim, |
|
554 | 555 |
baseline = 0, height = anno_size$height, border = border, bar_width = bar_width, |
555 | 556 |
axis = axis, axis_param = axis_param)@fun |
556 | 557 |
fun(index, k, n) |
... | ... |
@@ -571,7 +572,7 @@ anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
571 | 572 |
col = col[all_type] |
572 | 573 |
|
573 | 574 |
count = apply(arr, c(1, 3), sum) |
574 |
- fun = anno_barplot(count, gp = gpar(fill = col, col = NA), which = "row", |
|
575 |
+ fun = anno_barplot(count, gp = gpar(fill = col, col = NA), which = "row", ylim = ylim, |
|
575 | 576 |
baseline = 0, width = anno_size$width, border = border, bar_width = bar_width, |
576 | 577 |
axis = axis, axis_param = axis_param)@fun |
577 | 578 |
fun(index, k, n) |
... | ... |
@@ -589,7 +590,7 @@ anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
589 | 590 |
which = which, |
590 | 591 |
width = anno_size$width, |
591 | 592 |
height = anno_size$height, |
592 |
- var_import = list(border, type, bar_width, axis, axis_param, anno_size) |
|
593 |
+ var_import = list(border, type, bar_width, axis, axis_param, anno_size, ylim) |
|
593 | 594 |
) |
594 | 595 |
|
595 | 596 |
anno@subsetable = TRUE |
... | ... |
@@ -94,8 +94,8 @@ oncoPrint = function(mat, |
94 | 94 |
if("axis_gp" %in% arg_names) { |
95 | 95 |
stop_wrap("`axis_gp` is removed from the arguments. Please set `axis_param(gp = ...)` in `anno_oncoprint_barplot()` when you define the `top_annotation` or `right_annotation`.") |
96 | 96 |
} |
97 |
- if("show_row_names" %in% arg_names) { |
|
98 |
- stop_wrap("`show_row_names` is removed from the arguments. Please directly remove `anno_oncoprint_barplot()` in `right_annotation` to remove barplots on the left of the oncoPrint.") |
|
97 |
+ if("show_row_barplot" %in% arg_names) { |
|
98 |
+ stop_wrap("`show_row_barplot` is removed from the arguments. Please directly remove `anno_oncoprint_barplot()` in `right_annotation` to remove barplots on the right of the oncoPrint.") |
|
99 | 99 |
} |
100 | 100 |
if("row_barplot_width" %in% arg_names) { |
101 | 101 |
stop_wrap("`row_barplot_width` is removed from the arguments. Please directly set `width` in `anno_oncoprint_barplot()` in `right_annotation`.") |
... | ... |
@@ -110,6 +110,10 @@ oncoPrint = function(mat, |
110 | 110 |
stop_wrap("`barplot_ignore` is removed from the arguments. The subset of alterations now can be controlled in `anno_oncoprint_barplot()`.") |
111 | 111 |
} |
112 | 112 |
|
113 |
+ if(inherits(col, "function")) { |
|
114 |
+ stop_wrap("`col` should be specified as a vector.") |
|
115 |
+ } |
|
116 |
+ |
|
113 | 117 |
# convert mat to mat_list |
114 | 118 |
if(inherits(mat, "data.frame")) { |
115 | 119 |
mat = as.matrix(mat) |
... | ... |
@@ -152,8 +156,7 @@ oncoPrint = function(mat, |
152 | 156 |
stop_wrap("Incorrect type of 'mat'") |
153 | 157 |
} |
154 | 158 |
|
155 |
- cat("All mutation types:", paste(all_type, collapse = ", "), "\n") |
|
156 |
- |
|
159 |
+ message_wrap(paste0("All mutation types: ", paste(all_type, collapse = ", "))) |
|
157 | 160 |
|
158 | 161 |
# type as the third dimension |
159 | 162 |
arr = array(FALSE, dim = c(dim(mat_list[[1]]), length(all_type)), dimnames = c(dimnames(mat_list[[1]]), list(all_type))) |
... | ... |
@@ -573,7 +576,7 @@ anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
573 | 576 |
axis = axis, axis_param = axis_param)@fun |
574 | 577 |
fun(index, k, n) |
575 | 578 |
} |
576 |
- |
|
579 |
+ |
|
577 | 580 |
if(which == "row") { |
578 | 581 |
fun = row_fun |
579 | 582 |
} else if(which == "column") { |
... | ... |
@@ -592,8 +595,19 @@ anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
592 | 595 |
anno@subsetable = TRUE |
593 | 596 |
anno@show_name = FALSE |
594 | 597 |
|
598 |
+ if(exists("arr", envir = parent.frame(1))) { |
|
599 |
+ arr = get("arr", envir = parent.frame(1)) |
|
600 |
+ if(which == "row") { |
|
601 |
+ data_scale = c(0, max(apply(arr, 1, sum))) |
|
602 |
+ } else { |
|
603 |
+ data_scale = c(0, max(apply(arr, 2, sum))) |
|
604 |
+ } |
|
605 |
+ } else { |
|
606 |
+ data_scale = c(0, 100) |
|
607 |
+ } |
|
608 |
+ |
|
595 | 609 |
axis_param = validate_axis_param(axis_param, which) |
596 |
- axis_grob = if(axis) construct_axis_grob(axis_param, which, c(0, 100)) else NULL |
|
610 |
+ axis_grob = if(axis) construct_axis_grob(axis_param, which, data_scale) else NULL |
|
597 | 611 |
anno@extended = update_anno_extend(anno, axis_grob, axis_param) |
598 | 612 |
|
599 | 613 |
return(anno) |
... | ... |
@@ -445,9 +445,13 @@ oncoPrint = function(mat, |
445 | 445 |
rect_gp = gpar(type = "none"), |
446 | 446 |
cluster_rows = FALSE, cluster_columns = FALSE, |
447 | 447 |
row_order = row_order, column_order = column_order, |
448 |
- row_split = row_split, column_split = column_split, |
|
448 |
+ row_split = row_split, |
|
449 |
+ column_labels = column_labels, |
|
450 |
+ column_names_gp = column_names_gp, |
|
451 |
+ column_split = column_split, |
|
449 | 452 |
cell_fun = cell_fun, layer_fun = layer_fun, |
450 | 453 |
top_annotation = top_annotation, |
454 |
+ bottom_annotation = bottom_annotation, |
|
451 | 455 |
left_annotation = left_annotation, |
452 | 456 |
right_annotation = right_annotation, |
453 | 457 |
show_row_names = FALSE, |
... | ... |
@@ -54,7 +54,7 @@ oncoPrint = function(mat, |
54 | 54 |
get_type = default_get_type, |
55 | 55 |
alter_fun, |
56 | 56 |
alter_fun_is_vectorized = NULL, |
57 |
- col, |
|
57 |
+ col = NULL, |
|
58 | 58 |
|
59 | 59 |
top_annotation = HeatmapAnnotation(cbar = anno_oncoprint_barplot()), |
60 | 60 |
right_annotation = rowAnnotation(rbar = anno_oncoprint_barplot()), |
... | ... |
@@ -331,7 +331,7 @@ oncoPrint = function(mat, |
331 | 331 |
# validate col |
332 | 332 |
sdf = setdiff(all_type, names(col)) |
333 | 333 |
if(length(sdf) > 0) { |
334 |
- stop_wrap(paste0("You should define colors for:", paste(sdf, collapse = ", "))) |
|
334 |
+ message_wrap(paste0("Colors are not defined for: ", paste(sdf, collapse = ", "))) |
|
335 | 335 |
} |
336 | 336 |
|
337 | 337 |
# for each gene, percent of samples that have alterations |
... | ... |
@@ -339,6 +339,10 @@ oncoPrint = function(mat, |
339 | 339 |
pct = paste0(round(pct_num * 100, digits = pct_digits), "%") |
340 | 340 |
|
341 | 341 |
### now the annotations |
342 |
+ if(length(col) == 0) { |
|
343 |
+ if(missing(top_annotation)) top_annotation = NULL |
|
344 |
+ if(missing(right_annotation)) right_annotation = NULL |
|
345 |
+ } |
|
342 | 346 |
top_annotation = top_annotation |
343 | 347 |
right_annotation = right_annotation |
344 | 348 |
|
... | ... |
@@ -421,7 +425,13 @@ oncoPrint = function(mat, |
421 | 425 |
|
422 | 426 |
##################################################################### |
423 | 427 |
# the main matrix |
424 |
- pheudo = c(all_type, rep(NA, nrow(arr)*ncol(arr) - length(all_type))) |
|
428 |
+ if(length(col)) { |
|
429 |
+ pheudo = c(names(col), rep(NA, nrow(arr)*ncol(arr) - length(col))) |
|
430 |
+ } else { |
|
431 |
+ pheudo = c("mutation", rep(NA, nrow(arr)*ncol(arr) - 1)) |
|
432 |
+ col = c("mutation" = "black") |
|
433 |
+ } |
|
434 |
+ |
|
425 | 435 |
dim(pheudo) = dim(arr)[1:2] |
426 | 436 |
dimnames(pheudo) = dimnames(arr)[1:2] |
427 | 437 |
|
... | ... |
@@ -523,7 +533,7 @@ anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
523 | 533 |
all_type = pf$all_type |
524 | 534 |
col = pf$col |
525 | 535 |
|
526 |
- if(is.null(type)) type = all_type |
|
536 |
+ if(is.null(type)) type = names(col) |
|
527 | 537 |
|
528 | 538 |
all_type = intersect(all_type, type) |
529 | 539 |
if(length(all_type) == 0) { |
... | ... |
@@ -544,7 +554,7 @@ anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
544 | 554 |
all_type = pf$all_type |
545 | 555 |
col = pf$col |
546 | 556 |
|
547 |
- if(is.null(type)) type = all_type |
|
557 |
+ if(is.null(type)) type = names(col) |
|
548 | 558 |
|
549 | 559 |
all_type = intersect(all_type, type) |
550 | 560 |
if(length(all_type) == 0) { |
... | ... |
@@ -615,7 +615,133 @@ guess_alter_fun_is_vectorized = function(alter_fun) { |
615 | 615 |
# == param |
616 | 616 |
# -x A strings which encode multiple altertations. |
617 | 617 |
# |
618 |
+# == details |
|
619 |
+# It recognizes following separators: ``;:,|``. |
|
620 |
+# |
|
618 | 621 |
default_get_type = function(x) { |
619 | 622 |
x = strsplit(x, "\\s*[;:,|]\\s*")[[1]] |
620 | 623 |
x[!x %in% c("na", "NA")] |
621 | 624 |
} |
625 |
+ |
|
626 |
+# == title |
|
627 |
+# Test alter_fun for oncoPrint() |
|
628 |
+# |
|
629 |
+# == param |
|
630 |
+# -fun The ``alter_fun`` for `oncoPrint`. The value can be a list of functions or a single function. See https://jokergoo.github.io/ComplexHeatmap-reference/book/oncoprint.html#define-the-alter-fun |
|
631 |
+# -type A vector of alteration types. It is only used when ``fun`` is a single function. |
|
632 |
+# -asp_ratio The aspect ratio (width/height) for the small rectangles. |
|
633 |
+# |
|
634 |
+# == details |
|
635 |
+# This function helps you to have a quick view of how the graphics for each alteration type |
|
636 |
+# and combinations look like. |
|
637 |
+# |
|
638 |
+# == example |
|
639 |
+# alter_fun = list( |
|
640 |
+# mut1 = function(x, y, w, h) grid.rect(x, y, w, h, gp = gpar(fill = "red", col = NA)), |
|
641 |
+# mut2 = function(x, y, w, h) grid.rect(x, y, w, h, gp = gpar(fill = "blue", col = NA)), |
|
642 |
+# mut3 = function(x, y, w, h) grid.rect(x, y, w, h, gp = gpar(fill = "yellow", col = NA)), |
|
643 |
+# mut4 = function(x, y, w, h) grid.rect(x, y, w, h, gp = gpar(fill = "purple", col = NA)), |
|
644 |
+# mut5 = function(x, y, w, h) grid.rect(x, y, w, h, gp = gpar(lwd = 2)), |
|
645 |
+# mut6 = function(x, y, w, h) grid.points(x, y, pch = 16), |
|
646 |
+# mut7 = function(x, y, w, h) grid.segments(x - w*0.5, y - h*0.5, x + w*0.5, y + h*0.5, gp = gpar(lwd = 2)) |
|
647 |
+# ) |
|
648 |
+# test_alter_fun(alter_fun) |
|
649 |
+test_alter_fun = function(fun, type, asp_ratio = 1) { |
|
650 |
+ background_fun = NULL |
|
651 |
+ if(inherits(fun, "list")) { |
|
652 |
+ fun_type = "list" |
|
653 |
+ type = names(fun) |
|
654 |
+ |
|
655 |
+ if("background" %in% type) { |
|
656 |
+ background_fun = fun$background |
|
657 |
+ } |
|
658 |
+ type = setdiff(type, "background") |
|
659 |
+ |
|
660 |
+ if(length(type) == 0) { |
|
661 |
+ stop_wrap("'type' should be of the names of the function list defined in `fun`.") |
|
662 |
+ } |
|
663 |
+ |
|
664 |
+ cat("`alter_fun` is defined as a list of functions.\n") |
|
665 |
+ cat("Functions are defined for following alteration types:\n") |
|
666 |
+ cat(paste(strwrap(paste(names(fun), collapse = ", "), initial = " "), collapse = "\n"), "\n") |
|
667 |
+ if(!is.null(background_fun)) { |
|
668 |
+ cat("Background is also defined.\n") |
|
669 |
+ } |
|
670 |
+ } else{ |
|
671 |
+ fun_type = "function" |
|
672 |
+ if(length(as.list(formals(fun))) != 5) { |
|
673 |
+ stop_wrap("If `alter_fun` is defined as a single function, it needs to have five arguments. Check example at https://jokergoo.github.io/ComplexHeatmap-reference/book/oncoprint.html#define-the-alter-fun.") |
|
674 |
+ } |
|
675 |
+ |
|
676 |
+ if(missing(type)) { |
|
677 |
+ stop_wrap("You need to provide a vector of alteration types for `type` argument to test.") |
|
678 |
+ } |
|
679 |
+ |
|
680 |
+ type = setdiff(type, "background") |
|
681 |
+ } |
|
682 |
+ |
|
683 |
+ tl = lapply(type, function(x) x) |
|
684 |
+ names(tl) = type |
|
685 |
+ if(length(type) >= 2) { |
|
686 |
+ tl2 = as.list(as.data.frame(combn(type, 2), stringsAsFactors = FALSE)) |
|
687 |
+ } else { |
|
688 |
+ tl2 = NULL |
|
689 |
+ } |
|
690 |
+ if(length(type) >= 3) { |
|
691 |
+ tl2 = c(tl2, as.list(as.data.frame(combn(type, 3), stringsAsFactors = FALSE))) |
|
692 |
+ } |
|
693 |
+ |
|
694 |
+ if(!is.null(tl2)) { |
|
695 |
+ tl2 = tl2[sample(length(tl2), min(length(tl), length(tl2)), prob = sapply(tl2, length))] |
|
696 |
+ tl2 = tl2[order(sapply(tl2, length))] |
|
697 |
+ names(tl2) = sapply(tl2, paste, collapse = "+") |
|
698 |
+ } |
|
699 |
+ |
|
700 |
+ # draw the examples |
|
701 |
+ grid_width = asp_ratio*max_text_height("A")*2 |
|
702 |
+ grid_height = max_text_height("A")*2 + unit(2, "mm") |
|
703 |
+ text_width_1 = max_text_width(names(tl)) |
|
704 |
+ w = text_width_1 + unit(1, "mm") + grid_width |
|
705 |
+ if(!is.null(tl2)) { |
|
706 |
+ text_width_2 = max_text_width(names(tl2)) |
|
707 |
+ w = w + unit(5, "mm") + text_width_2 + unit(1, "mm") + grid_width |
|
708 |
+ } |
|
709 |
+ n = length(tl) |
|
710 |
+ h = grid_height*n |
|
711 |
+ |
|
712 |
+ grid.newpage() |
|
713 |
+ pushViewport(viewport(width = w, height = h)) |
|
714 |
+ for(i in 1:n) { |
|
715 |
+ grid.text(names(tl)[i], text_width_1, (n - i + 0.5)/n, just = "right") |
|
716 |
+ if(is.null(background_fun)) { |
|
717 |
+ grid.rect(text_width_1 + unit(1, "mm") + grid_width*0.5, unit((n - i + 0.5)/n, "npc"), grid_width, grid_height - unit(2, "mm"), gp = gpar(fill = "#CCCCCC", col = NA)) |
|
718 |
+ } else { |
|
719 |
+ background_fun(text_width_1 + unit(1, "mm") + grid_width*0.5, unit((n - i + 0.5)/n, "npc"), grid_width, grid_height - unit(2, "mm")) |
|
720 |
+ } |
|
721 |
+ if(fun_type == "list") { |
|
722 |
+ fun[[ tl[[i]] ]](text_width_1 + unit(1, "mm") + grid_width*0.5, unit((n - i + 0.5)/n, "npc"), grid_width, grid_height - unit(2, "mm")) |
|
723 |
+ } else { |
|
724 |
+ fun(text_width_1 + unit(1, "mm") + grid_width*0.5, unit((n - i + 0.5)/n, "npc"), grid_width, grid_height - unit(2, "mm"), tl[[i]]) |
|
725 |
+ } |
|
726 |
+ } |
|
727 |
+ if(!is.null(tl2)) { |
|
728 |
+ n2 = length(tl2) |
|
729 |
+ for(i in 1:n2) { |
|
730 |
+ grid.text(names(tl2)[i], text_width_1 + unit(1, "mm") + grid_width + unit(5, "mm") + text_width_2, (n - i + 0.5)/n, just = "right") |
|
731 |
+ if(is.null(background_fun)) { |
|
732 |
+ grid.rect(text_width_1 + unit(2, "mm") + unit(5, "mm") + grid_width + text_width_2 + grid_width*0.5, unit((n - i + 0.5)/n, "npc"), grid_width, grid_height - unit(2, "mm"), gp = gpar(fill = "#CCCCCC", col = NA)) |
|
733 |
+ } else { |
|
734 |
+ background_fun(text_width_1 + unit(2, "mm") + unit(5, "mm") + grid_width + text_width_2 + grid_width*0.5, unit((n - i + 0.5)/n, "npc"), grid_width, grid_height - unit(2, "mm")) |
|
735 |
+ } |
|
736 |
+ if(fun_type == "list") { |
|
737 |
+ for(j in tl2[[i]]) { |
|
738 |
+ fun[[ j ]](text_width_1 + unit(2, "mm") + unit(5, "mm") + grid_width + text_width_2 + grid_width*0.5, unit((n - i + 0.5)/n, "npc"), grid_width, grid_height - unit(2, "mm")) |
|
739 |
+ } |
|
740 |
+ } else { |
|
741 |
+ fun(text_width_1 + unit(2, "mm") + grid_width + unit(5, "mm") + text_width_2 + grid_width*0.5, unit((n - i + 0.5)/n, "npc"), grid_width, grid_height - unit(2, "mm"), tl2[[i]]) |
|
742 |
+ } |
|
743 |
+ } |
|
744 |
+ } |
|
745 |
+ popViewport() |
|
746 |
+ |
|
747 |
+} |
... | ... |
@@ -435,6 +435,7 @@ oncoPrint = function(mat, |
435 | 435 |
rect_gp = gpar(type = "none"), |
436 | 436 |
cluster_rows = FALSE, cluster_columns = FALSE, |
437 | 437 |
row_order = row_order, column_order = column_order, |
438 |
+ row_split = row_split, column_split = column_split, |
|
438 | 439 |
cell_fun = cell_fun, layer_fun = layer_fun, |
439 | 440 |
top_annotation = top_annotation, |
440 | 441 |
left_annotation = left_annotation, |
... | ... |
@@ -9,7 +9,7 @@ |
9 | 9 |
# When the value is a list, the names of the list represent alteration types. |
10 | 10 |
# You can use `unify_mat_list` to make all matrix having same row names and column names. |
11 | 11 |
# -get_type If different alterations are encoded in the matrix as complex strings, this self-defined function |
12 |
-# determines how to extract them. It only works when ``mat`` is a matrix. |
|
12 |
+# determines how to extract them. It only works when ``mat`` is a matrix. The default value is `default_get_type`. |
|
13 | 13 |
# -alter_fun A single function or a list of functions which defines how to add graphics for different alterations. |
14 | 14 |
# -alter_fun_is_vectorized Whether ``alter_fun`` is implemented vectorized. Internally the function will guess. |
15 | 15 |
# -col A vector of color for which names correspond to alteration types. |
... | ... |
@@ -51,10 +51,7 @@ |
51 | 51 |
# Zuguang Gu <z.gu@dkfz.de> |
52 | 52 |
# |
53 | 53 |
oncoPrint = function(mat, |
54 |
- get_type = function(x) { |
|
55 |
- x = strsplit(x, "\\s*[;:,|]\\s*")[[1]] |
|
56 |
- x[!x %in% c("na", "NA")] |
|
57 |
- }, |
|
54 |
+ get_type = default_get_type, |
|
58 | 55 |
alter_fun, |
59 | 56 |
alter_fun_is_vectorized = NULL, |
60 | 57 |
col, |
... | ... |
@@ -611,3 +608,13 @@ guess_alter_fun_is_vectorized = function(alter_fun) { |
611 | 608 |
} |
612 | 609 |
} |
613 | 610 |
|
611 |
+# == title |
|
612 |
+# Default get_type for oncoPrint() |
|
613 |
+# |
|
614 |
+# == param |
|
615 |
+# -x A strings which encode multiple altertations. |
|
616 |
+# |
|
617 |
+default_get_type = function(x) { |
|
618 |
+ x = strsplit(x, "\\s*[;:,|]\\s*")[[1]] |
|
619 |
+ x[!x %in% c("na", "NA")] |
|
620 |
+} |
... | ... |
@@ -51,7 +51,10 @@ |
51 | 51 |
# Zuguang Gu <z.gu@dkfz.de> |
52 | 52 |
# |
53 | 53 |
oncoPrint = function(mat, |
54 |
- get_type = function(x) strsplit(x, "\\s*[;:,|]\\s*")[[1]], |
|
54 |
+ get_type = function(x) { |
|
55 |
+ x = strsplit(x, "\\s*[;:,|]\\s*")[[1]] |
|
56 |
+ x[!x %in% c("na", "NA")] |
|
57 |
+ }, |
|
55 | 58 |
alter_fun, |
56 | 59 |
alter_fun_is_vectorized = NULL, |
57 | 60 |
col, |
... | ... |
@@ -115,12 +118,13 @@ oncoPrint = function(mat, |
115 | 118 |
mat = as.matrix(mat) |
116 | 119 |
} |
117 | 120 |
if(inherits(mat, "matrix")) { |
118 |
- all_type = unique(unlist(lapply(mat, get_type))) |
|
121 |
+ get_type2 = function(x) gsub("^\\s+|\\s+$", "", get_type(x)) |
|
122 |
+ all_type = unique(unlist(lapply(mat, get_type2))) |
|
119 | 123 |
all_type = all_type[!is.na(all_type)] |
120 | 124 |
all_type = all_type[grepl("\\S", all_type)] |
121 | 125 |
|
122 | 126 |
mat_list = lapply(all_type, function(type) { |
123 |
- m = sapply(mat, function(x) type %in% get_type(x)) |
|
127 |
+ m = sapply(mat, function(x) type %in% get_type2(x)) |
|
124 | 128 |
dim(m) = dim(mat) |
125 | 129 |
dimnames(m) = dimnames(mat) |
126 | 130 |
m |
... | ... |
@@ -180,7 +180,7 @@ oncoPrint = function(mat, |
180 | 180 |
|
181 | 181 |
if(missing(alter_fun)) { |
182 | 182 |
if(length(mat_list) == 1) { |
183 |
- af = list( |
|
183 |
+ alter_fun = list( |
|
184 | 184 |
background = function(x, y, w, h, j, i) { |
185 | 185 |
grid.rect(x, y, w, h, gp = gpar(fill = "#CCCCCC", col = NA)) |
186 | 186 |
}, |
... | ... |
@@ -189,10 +189,10 @@ oncoPrint = function(mat, |
189 | 189 |
} |
190 | 190 |
) |
191 | 191 |
alter_fun_is_vectorized = TRUE |
192 |
- names(af) = c("background", names(mat_list)) |
|
192 |
+ names(alter_fun) = c("background", names(mat_list)) |
|
193 | 193 |
col = "red" |
194 | 194 |
} else if(length(mat_list) == 2) { |
195 |
- af = list( |
|
195 |
+ alter_fun = list( |
|
196 | 196 |
background = function(x, y, w, h, j, i) { |
197 | 197 |
grid.rect(x, y, w, h, gp = gpar(fill = "#CCCCCC", col = NA)) |
198 | 198 |
}, |
... | ... |
@@ -204,7 +204,7 @@ oncoPrint = function(mat, |
204 | 204 |
} |
205 | 205 |
) |
206 | 206 |
alter_fun_is_vectorized = TRUE |
207 |
- names(af) = c("background", names(mat_list)) |
|
207 |
+ names(alter_fun) = c("background", names(mat_list)) |
|
208 | 208 |
col = c("red", "blue") |
209 | 209 |
} else { |
210 | 210 |
stop_wrap("`alter_fun` should be specified.") |
... | ... |
@@ -234,7 +234,7 @@ oncoPrint = function(mat, |
234 | 234 |
layer_fun = function(j, i, x, y, w, h, fill) { |
235 | 235 |
alter_fun$background(x, y, w, h) |
236 | 236 |
for(nm in all_type) { |
237 |
- m = arr[, , nm] |
|
237 |
+ m = arr[, , nm, drop = FALSE] |
|
238 | 238 |
l = pindex(m, i, j) |
239 | 239 |
if(sum(l)) { |
240 | 240 |
alter_fun[[nm]](x[l], y[l], w[l], h[l]) |
... | ... |
@@ -361,10 +361,10 @@ oncoPrint = function(mat, |
361 | 361 |
} |
362 | 362 |
if(show_row_names) { |
363 | 363 |
if(row_names_side == "right") { |
364 |
- rn_ha = rowAnnotation(rownames = anno_text(row_labels, gp = row_names_gp, just = "left", location = unit(0, "npc"), width = max_text_width(pct, gp = row_names_gp) + unit(1, "mm")), |
|
364 |
+ rn_ha = rowAnnotation(rownames = anno_text(row_labels, gp = row_names_gp, just = "left", location = unit(0, "npc"), width = max_text_width(row_labels, gp = row_names_gp) + unit(1, "mm")), |
|
365 | 365 |
show_annotation_name = FALSE) |
366 | 366 |
} else { |
367 |
- rn_ha = rowAnnotation(rownames = anno_text(row_labels, gp = row_names_gp, just = "right", location = unit(1, "npc"), width = max_text_width(pct, gp = row_names_gp) + unit(1, "mm")), |
|
367 |
+ rn_ha = rowAnnotation(rownames = anno_text(row_labels, gp = row_names_gp, just = "right", location = unit(1, "npc"), width = max_text_width(row_labels, gp = row_names_gp) + unit(1, "mm")), |
|
368 | 368 |
show_annotation_name = FALSE) |
369 | 369 |
} |
370 | 370 |
names(rn_ha) = paste0("rownames_", random_str()) |
... | ... |
@@ -88,6 +88,28 @@ oncoPrint = function(mat, |
88 | 88 |
arg_list = as.list(match.call())[-1] |
89 | 89 |
arg_names = names(arg_list) |
90 | 90 |
|
91 |
+ if("alter_fun_list" %in% arg_names) { |
|
92 |
+ stop_wrap("`alter_fun_list` is removed from the arguments.") |
|
93 |
+ } |
|
94 |
+ if("axis_gp" %in% arg_names) { |
|
95 |
+ stop_wrap("`axis_gp` is removed from the arguments. Please set `axis_param(gp = ...)` in `anno_oncoprint_barplot()` when you define the `top_annotation` or `right_annotation`.") |
|
96 |
+ } |
|
97 |
+ if("show_row_names" %in% arg_names) { |
|
98 |
+ stop_wrap("`show_row_names` is removed from the arguments. Please directly remove `anno_oncoprint_barplot()` in `right_annotation` to remove barplots on the left of the oncoPrint.") |
|
99 |
+ } |
|
100 |
+ if("row_barplot_width" %in% arg_names) { |
|
101 |
+ stop_wrap("`row_barplot_width` is removed from the arguments. Please directly set `width` in `anno_oncoprint_barplot()` in `right_annotation`.") |
|
102 |
+ } |
|
103 |
+ if("top_annotation_height" %in% arg_names) { |
|
104 |
+ stop_wrap("`top_annotation_height` is removed from the arguments. Please directly set `height` in `anno_oncoprint_barplot()` in `top_annotation`.") |
|
105 |
+ } |
|
106 |
+ if("bottom_annotation_height" %in% arg_names) { |
|
107 |
+ stop_wrap("`bottom_annotation_height` is removed from the arguments. Please directly set `height` in `bottom_annotation`.") |
|
108 |
+ } |
|
109 |
+ if("barplot_ignore" %in% arg_names) { |
|
110 |
+ stop_wrap("`barplot_ignore` is removed from the arguments. The subset of alterations now can be controlled in `anno_oncoprint_barplot()`.") |
|
111 |
+ } |
|
112 |
+ |
|
91 | 113 |
# convert mat to mat_list |
92 | 114 |
if(inherits(mat, "data.frame")) { |
93 | 115 |
mat = as.matrix(mat) |
... | ... |
@@ -362,10 +362,10 @@ oncoPrint = function(mat, |
362 | 362 |
left_annotation = left_annotation[l_non_empty_row, ] |
363 | 363 |
} |
364 | 364 |
if(pct_side == "left") { |
365 |
- left_annotation = c(left_annotation, pct_ha) |
|
365 |
+ left_annotation = c(left_annotation, pct_ha, gap = unit(1, "mm")) |
|
366 | 366 |
} |
367 | 367 |
if(row_names_side == "left") { |
368 |
- left_annotation = c(left_annotation, rn_ha) |
|
368 |
+ left_annotation = c(left_annotation, rn_ha, gap = unit(1, "mm")) |
|
369 | 369 |
} |
370 | 370 |
} |
371 | 371 |
|
... | ... |
@@ -381,10 +381,10 @@ oncoPrint = function(mat, |
381 | 381 |
right_annotation = right_annotation[l_non_empty_row, ] |
382 | 382 |
} |
383 | 383 |
if(pct_side == "right") { |
384 |
- if(!is.null(pct_ha)) right_annotation = c(pct_ha, right_annotation) |
|
384 |
+ if(!is.null(pct_ha)) right_annotation = c(pct_ha, right_annotation, gap = unit(1, "mm")) |
|
385 | 385 |
} |
386 | 386 |
if(row_names_side == "right") { |
387 |
- if(!is.null(rn_ha)) right_annotation = c(rn_ha, right_annotation) |
|
387 |
+ if(!is.null(rn_ha)) right_annotation = c(rn_ha, right_annotation, gap = unit(1, "mm")) |
|
388 | 388 |
} |
389 | 389 |
} |
390 | 390 |
if(remove_empty_columns) { |
... | ... |
@@ -326,15 +326,25 @@ oncoPrint = function(mat, |
326 | 326 |
} |
327 | 327 |
|
328 | 328 |
if(show_pct) { |
329 |
- pct_ha = rowAnnotation(pct = anno_text(pct, just = "right", location = unit(1, "npc"), gp = pct_gp), |
|
330 |
- show_annotation_name = FALSE) |
|
329 |
+ if(pct_side == "left") { |
|
330 |
+ pct_ha = rowAnnotation(pct = anno_text(pct, just = "right", location = unit(1, "npc"), gp = pct_gp, width = max_text_width(pct, gp = pct_gp) + unit(1, "mm")), |
|
331 |
+ show_annotation_name = FALSE) |
|
332 |
+ } else { |
|
333 |
+ pct_ha = rowAnnotation(pct = anno_text(pct, just = "left", location = unit(0, "npc"), gp = pct_gp, width = max_text_width(pct, gp = pct_gp) + unit(1, "mm")), |
|
334 |
+ show_annotation_name = FALSE) |
|
335 |
+ } |
|
331 | 336 |
names(pct_ha) = paste0("pct_", random_str()) |
332 | 337 |
} else { |
333 | 338 |
pct_ha = NULL |
334 | 339 |
} |
335 | 340 |
if(show_row_names) { |
336 |
- rn_ha = rowAnnotation(rownames = anno_text(row_labels, gp = pct_gp, just = "left", location = unit(0, "npc")), |
|
337 |
- show_annotation_name = FALSE) |
|
341 |
+ if(row_names_side == "right") { |
|
342 |
+ rn_ha = rowAnnotation(rownames = anno_text(row_labels, gp = row_names_gp, just = "left", location = unit(0, "npc"), width = max_text_width(pct, gp = row_names_gp) + unit(1, "mm")), |
|
343 |
+ show_annotation_name = FALSE) |
|
344 |
+ } else { |
|
345 |
+ rn_ha = rowAnnotation(rownames = anno_text(row_labels, gp = row_names_gp, just = "right", location = unit(1, "npc"), width = max_text_width(pct, gp = row_names_gp) + unit(1, "mm")), |
|
346 |
+ show_annotation_name = FALSE) |
|
347 |
+ } |
|
338 | 348 |
names(rn_ha) = paste0("rownames_", random_str()) |
339 | 349 |
} else { |
340 | 350 |
rn_ha = NULL |
... | ... |
@@ -15,7 +15,7 @@ |
15 | 15 |
# -col A vector of color for which names correspond to alteration types. |
16 | 16 |
# -top_annotation Annotation put on top of the oncoPrint. By default it is barplot which shows the number of genes with a certain alteration in each sample. |
17 | 17 |
# -right_annotation Annotation put on the right of the oncoPrint. By default it is barplot which shows the number of samples with a certain alteration in each gene. |
18 |
-# -left_annotation Annotation put on the left of teh oncoPrint. |
|
18 |
+# -left_annotation Annotation put on the left of the oncoPrint. |
|
19 | 19 |
# -bottom_annotation Annotation put at the bottom of the oncoPrint. |
20 | 20 |
# -show_pct whether show percent values on the left of the oncoprint? |
21 | 21 |
# -pct_gp Graphic paramters for percent values |
... | ... |
@@ -377,6 +377,14 @@ oncoPrint = function(mat, |
377 | 377 |
if(!is.null(rn_ha)) right_annotation = c(rn_ha, right_annotation) |
378 | 378 |
} |
379 | 379 |
} |
380 |
+ if(remove_empty_columns) { |
|
381 |
+ if(!is.null(top_annotation)) { |
|
382 |
+ top_annotation = top_annotation[l_non_empty_column, ] |
|
383 |
+ } |
|
384 |
+ if(!is.null(bottom_annotation)) { |
|
385 |
+ bottom_annotation = bottom_annotation[l_non_empty_column, ] |
|
386 |
+ } |
|
387 |
+ } |
|
380 | 388 |
|
381 | 389 |
##################################################################### |
382 | 390 |
# the main matrix |
... | ... |
@@ -449,10 +457,12 @@ unify_mat_list = function(mat_list, default = 0) { |
449 | 457 |
# == param |
450 | 458 |
# -type A vector of the alteration types in the data. It can be a subset of all alteration types if you don't want to show them all. |
451 | 459 |
# -which Is it a row annotation or a column annotation? |
460 |
+# -bar_width Width of the bars. |
|
461 |
+# -axis Whether draw axis? |
|
462 |
+# -axis_param Parameters for controlling axis. |
|
452 | 463 |
# -width Wisth of the annotation. |
453 | 464 |
# -height Height of the annotation. |
454 | 465 |
# -border Whether draw the border? |
455 |
-# -... Other parameters passed to `anno_barplot`. |
|
456 | 466 |
# |
457 | 467 |
# == detail |
458 | 468 |
# This annotation function should always be used with `oncoPrint`. |
... | ... |
@@ -463,7 +473,7 @@ unify_mat_list = function(mat_list, default = 0) { |
463 | 473 |
anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"), |
464 | 474 |
bar_width = 0.6, axis = TRUE, |
465 | 475 |
axis_param = if(which == "column") default_axis_param("column") else list(side = "top", labels_rot = 0), |
466 |
- width = NULL, height = NULL, border = FALSE, ...) { |
|
476 |
+ width = NULL, height = NULL, border = FALSE) { |
|
467 | 477 |
|
468 | 478 |
if(is.null(.ENV$current_annotation_which)) { |
469 | 479 |
which = match.arg(which)[1] |
... | ... |
@@ -15,20 +15,20 @@ |
15 | 15 |
# -col A vector of color for which names correspond to alteration types. |
16 | 16 |
# -top_annotation Annotation put on top of the oncoPrint. By default it is barplot which shows the number of genes with a certain alteration in each sample. |
17 | 17 |
# -right_annotation Annotation put on the right of the oncoPrint. By default it is barplot which shows the number of samples with a certain alteration in each gene. |
18 |
-# -left_annotation |
|
18 |
+# -left_annotation Annotation put on the left of teh oncoPrint. |
|
19 | 19 |
# -bottom_annotation Annotation put at the bottom of the oncoPrint. |
20 | 20 |
# -show_pct whether show percent values on the left of the oncoprint? |
21 | 21 |
# -pct_gp Graphic paramters for percent values |
22 | 22 |
# -pct_digits Digits for the percent values. |
23 | 23 |
# -pct_side Side of the percent values to the oncoPrint. This argument is currently disabled. |
24 |
-# -row_labels |
|
24 |
+# -row_labels Labels as the row names of the oncoPrint. |
|
25 | 25 |
# -show_row_names Whether show row names? |
26 | 26 |
# -row_names_side Side of the row names to the oncoPrint. This argument is currently disabled. |
27 | 27 |
# -row_names_gp Graphic parameters for the row names. |
28 |
-# -row_split |
|
29 |
-# -column_labels |
|
30 |
-# -column_names_gp |
|
31 |
-# -column_split |
|
28 |
+# -row_split Pass to `Heatmap`. |
|
29 |
+# -column_labels Pass to `Heatmap`. |
|
30 |
+# -column_names_gp Pass to `Heatmap`. |
|
31 |
+# -column_split Pass to `Heatmap`. |
|
32 | 32 |
# -row_order Order of rows. By default rows are sorted by the number of occurence of the alterations. |
33 | 33 |
# -column_order Order of columns. By default the columns are sorted to show the mutual exclusivity of alterations. |
34 | 34 |
# -remove_empty_columns If there is no alteration in some samples, whether remove them on the oncoPrint? |
... | ... |
@@ -371,10 +371,10 @@ oncoPrint = function(mat, |
371 | 371 |
right_annotation = right_annotation[l_non_empty_row, ] |
372 | 372 |
} |
373 | 373 |
if(pct_side == "right") { |
374 |
- right_annotation = c(pct_ha, right_annotation) |
|
374 |
+ if(!is.null(pct_ha)) right_annotation = c(pct_ha, right_annotation) |
|
375 | 375 |
} |
376 | 376 |
if(row_names_side == "right") { |
377 |
- right_annotation = c(rn_ha, right_annotation) |
|
377 |
+ if(!is.null(rn_ha)) right_annotation = c(rn_ha, right_annotation) |
|
378 | 378 |
} |
379 | 379 |
} |
380 | 380 |
|
... | ... |
@@ -15,14 +15,20 @@ |
15 | 15 |
# -col A vector of color for which names correspond to alteration types. |
16 | 16 |
# -top_annotation Annotation put on top of the oncoPrint. By default it is barplot which shows the number of genes with a certain alteration in each sample. |
17 | 17 |
# -right_annotation Annotation put on the right of the oncoPrint. By default it is barplot which shows the number of samples with a certain alteration in each gene. |
18 |
+# -left_annotation |
|
18 | 19 |
# -bottom_annotation Annotation put at the bottom of the oncoPrint. |
19 | 20 |
# -show_pct whether show percent values on the left of the oncoprint? |
20 | 21 |
# -pct_gp Graphic paramters for percent values |
21 | 22 |
# -pct_digits Digits for the percent values. |
22 | 23 |
# -pct_side Side of the percent values to the oncoPrint. This argument is currently disabled. |
24 |
+# -row_labels |
|
23 | 25 |
# -show_row_names Whether show row names? |
24 | 26 |
# -row_names_side Side of the row names to the oncoPrint. This argument is currently disabled. |
25 | 27 |
# -row_names_gp Graphic parameters for the row names. |
28 |
+# -row_split |
|
29 |
+# -column_labels |
|
30 |
+# -column_names_gp |
|
31 |
+# -column_split |
|
26 | 32 |
# -row_order Order of rows. By default rows are sorted by the number of occurence of the alterations. |
27 | 33 |
# -column_order Order of columns. By default the columns are sorted to show the mutual exclusivity of alterations. |
28 | 34 |
# -remove_empty_columns If there is no alteration in some samples, whether remove them on the oncoPrint? |
... | ... |
@@ -50,18 +56,25 @@ oncoPrint = function(mat, |
50 | 56 |
alter_fun_is_vectorized = NULL, |
51 | 57 |
col, |
52 | 58 |
|
53 |
- top_annotation = HeatmapAnnotation(column_barplot = anno_oncoprint_barplot()), |
|
54 |
- right_annotation = rowAnnotation(row_barplot = anno_oncoprint_barplot( |
|
55 |
- axis_param = list(side = "top", labels_rot = 0))), |
|
59 |
+ top_annotation = HeatmapAnnotation(cbar = anno_oncoprint_barplot()), |
|
60 |
+ right_annotation = rowAnnotation(rbar = anno_oncoprint_barplot()), |
|
61 |
+ left_annotation = NULL, |
|
56 | 62 |
bottom_annotation = NULL, |
57 | 63 |
|
58 | 64 |
show_pct = TRUE, |
59 | 65 |
pct_gp = gpar(fontsize = 10), |
60 | 66 |
pct_digits = 0, |
61 | 67 |
pct_side = "left", |
68 |
+ |
|
69 |
+ row_labels = NULL, |
|
62 | 70 |
show_row_names = TRUE, |
63 | 71 |
row_names_side = "right", |
64 | 72 |
row_names_gp = pct_gp, |
73 |
+ row_split = NULL, |
|
74 |
+ |
|
75 |
+ column_labels = NULL, |
|
76 |
+ column_names_gp = gpar(fontsize = 10), |
|
77 |
+ column_split = NULL, |
|
65 | 78 |
|
66 | 79 |
row_order = NULL, |
67 | 80 |
column_order = NULL, |
... | ... |
@@ -72,13 +85,9 @@ oncoPrint = function(mat, |
72 | 85 |
heatmap_legend_param = list(title = "Alterations"), |
73 | 86 |
...) { |
74 | 87 |
|
75 |
- arg_list = list(...) |
|
88 |
+ arg_list = as.list(match.call())[-1] |
|
76 | 89 |
arg_names = names(arg_list) |
77 | 90 |
|
78 |
- oe = environment(anno_oncoprint_barplot) |
|
79 |
- environment(anno_oncoprint_barplot) = environment() |
|
80 |
- on.exit(environment(anno_oncoprint_barplot) <- oe) |
|
81 |
- |
|
82 | 91 |
# convert mat to mat_list |
83 | 92 |
if(inherits(mat, "data.frame")) { |
84 | 93 |
mat = as.matrix(mat) |
... | ... |
@@ -269,15 +278,31 @@ oncoPrint = function(mat, |
269 | 278 |
column_order = structure(seq_len(dim(arr)[2]), names = dimnames(arr)[[2]])[column_order] |
270 | 279 |
} |
271 | 280 |
names(column_order) = as.character(column_order) |
281 |
+ |
|
282 |
+ l_non_empty_column = rowSums(apply(arr, c(2, 3), sum)) > 0 |
|
283 |
+ l_non_empty_row = rowSums(apply(arr, c(1, 3), sum)) > 0 |
|
284 |
+ |
|
285 |
+ if(is.null(row_labels)) row_labels = dimnames(arr)[[1]] |
|
272 | 286 |
if(remove_empty_columns) { |
273 |
- l = rowSums(apply(arr, c(2, 3), sum)) > 0 |
|
274 |
- arr = arr[, l, , drop = FALSE] |
|
275 |
- column_order = structure(seq_len(sum(l)), names = which(l))[as.character(intersect(column_order, which(l)))] |
|
287 |
+ arr = arr[, l_non_empty_column, , drop = FALSE] |
|
288 |
+ column_order = structure(seq_len(sum(l_non_empty_column)), names = which(l_non_empty_column))[as.character(intersect(column_order, which(l_non_empty_column)))] |
|
289 |