... | ... |
@@ -3,6 +3,9 @@ CHANGES in VERSION 1.99.5 |
3 | 3 |
* add `UpSet()` and some related functions to make Upset plots |
4 | 4 |
* fixed bugs of drawing legends |
5 | 5 |
* add `test_alter_fun()` |
6 |
+* `HeatmapAnnotation()`: fixed a bug for setting `height` when all annotations are simple annotations. |
|
7 |
+* `default_col()`: if the fraction of positive values in the matrix is in (0.3, 0.7), the color mapping |
|
8 |
+ is symmetric to zero. |
|
6 | 9 |
|
7 | 10 |
======================== |
8 | 11 |
|
... | ... |
@@ -1041,7 +1041,7 @@ setMethod(f = "re_size", |
1041 | 1041 |
height = NULL, |
1042 | 1042 |
width = NULL, |
1043 | 1043 |
anno_simple_size = ht_opt$anno_simple_size, |
1044 |
- simple_anno_size_adjust = FALSE) { |
|
1044 |
+ simple_anno_size_adjust = NULL) { |
|
1045 | 1045 |
|
1046 | 1046 |
if(object@which == "column") { |
1047 | 1047 |
if(!missing(width) || !missing(annotation_width)) { |
... | ... |
@@ -1054,9 +1054,17 @@ setMethod(f = "re_size", |
1054 | 1054 |
} |
1055 | 1055 |
} |
1056 | 1056 |
|
1057 |
+ all_simple_annotation = all(sapply(object@anno_list, function(x) is_simple_annotation(x) || is_matrix_annotation(x))) |
|
1058 |
+ if(is.null(simple_anno_size_adjust)) { |
|
1059 |
+ if(all_simple_annotation) { |
|
1060 |
+ simple_anno_size_adjust = TRUE |
|
1061 |
+ } else { |
|
1062 |
+ simple_anno_size_adjust = FALSE |
|
1063 |
+ } |
|
1064 |
+ } |
|
1057 | 1065 |
which = object@which |
1058 | 1066 |
if(!simple_anno_size_adjust) { |
1059 |
- if(all(sapply(object@anno_list, function(x) is_simple_annotation(x) || is_matrix_annotation(x)))) { |
|
1067 |
+ if(all_simple_annotation) { |
|
1060 | 1068 |
if(which == "column") { |
1061 | 1069 |
height = sum(object@anno_size) + sum(object@gap) - object@gap[length(object@gap)] |
1062 | 1070 |
object@height = convertHeight(height, "mm") |
... | ... |
@@ -1064,6 +1072,9 @@ setMethod(f = "re_size", |
1064 | 1072 |
width = sum(object@anno_size) + sum(object@gap) - object@gap[length(object@gap)] |
1065 | 1073 |
object@width = convertWidth(width, "mm") |
1066 | 1074 |
} |
1075 |
+ if(ht_opt$verbose) { |
|
1076 |
+ message_wrap("`simple_anno_size_adjust` is set to FALSE and all annotations are simple annotations or matrix annotations, the heights of all annotations are not adjusted.") |
|
1077 |
+ } |
|
1067 | 1078 |
return(object) |
1068 | 1079 |
} |
1069 | 1080 |
} |
... | ... |
@@ -1083,6 +1094,11 @@ setMethod(f = "re_size", |
1083 | 1094 |
if(is.null(annotation_height)) { |
1084 | 1095 |
is_annotation_size_set = FALSE |
1085 | 1096 |
} else { |
1097 |
+ if(length(annotation_height) == 1) { |
|
1098 |
+ if(!inherits(annotation_height, "unit")) { |
|
1099 |
+ annotation_height = rep(annotation_height, length(object@anno_list)) |
|
1100 |
+ } |
|
1101 |
+ } |
|
1086 | 1102 |
if(length(annotation_height) == 1) { |
1087 | 1103 |
if(length(object@anno_list) > 1) { |
1088 | 1104 |
warning_wrap("`annotation_height` is set with length of one while with multiple annotations, `annotation_height` is treated as `height`.") |
... | ... |
@@ -1090,7 +1106,9 @@ setMethod(f = "re_size", |
1090 | 1106 |
if(length(object@anno_list) == 1 && !inherits(annotation_height, "unit")) { |
1091 | 1107 |
stop_wrap("When there is only one annotation, `annotation_height` should be set as a unit object.") |
1092 | 1108 |
} |
1093 |
- height = annotation_height[1] |
|
1109 |
+ if(!inherits(height, "unit")) { |
|
1110 |
+ height = annotation_height[1] |
|
1111 |
+ } |
|
1094 | 1112 |
if(!inherits(height, "unit")) { |
1095 | 1113 |
stop_wrap("`height` should be a `unit` object") |
1096 | 1114 |
} |
... | ... |
@@ -1121,6 +1139,11 @@ setMethod(f = "re_size", |
1121 | 1139 |
if(is.null(annotation_width)) { |
1122 | 1140 |
is_annotation_size_set = FALSE |
1123 | 1141 |
} else { |
1142 |
+ if(length(annotation_width) == 1) { |
|
1143 |
+ if(!inherits(annotation_width, "unit")) { |
|
1144 |
+ annotation_width = rep(annotation_width, length(object@anno_list)) |
|
1145 |
+ } |
|
1146 |
+ } |
|
1124 | 1147 |
if(length(annotation_width) == 1) { |
1125 | 1148 |
if(length(object@anno_list) > 1) { |
1126 | 1149 |
warning_wrap("`annotation_width` is set with length of one while with multiple annotations, `annotation_width` is treated as `width`.") |
... | ... |
@@ -1128,7 +1151,9 @@ setMethod(f = "re_size", |
1128 | 1151 |
if(length(object@anno_list) == 1 && !inherits(annotation_width, "unit")) { |
1129 | 1152 |
stop_wrap("When there is only one annotation, `annotation_width` should be set as a unit object.") |
1130 | 1153 |
} |
1131 |
- width = annotation_width[1] |
|
1154 |
+ if(!inherits(width, "unit")) { |
|
1155 |
+ width = annotation_width[1] |
|
1156 |
+ } |
|
1132 | 1157 |
if(!inherits(width, "unit")) { |
1133 | 1158 |
stop_wrap("`width` should be a `unit` object") |
1134 | 1159 |
} |
... | ... |
@@ -72,16 +72,30 @@ default_col = function(x, main_matrix = FALSE) { |
72 | 72 |
return(colors) |
73 | 73 |
} else if(is.numeric(x)) { |
74 | 74 |
if(main_matrix) { |
75 |
- if(length(unique(x)) > 100) { |
|
76 |
- q1 = quantile(x, 0.01) |
|
77 |
- q2 = quantile(x, 0.99) |
|
78 |
- if(length(unique(x[x > q1 & x < q2])) == 1) { |
|
79 |
- col_fun = colorRamp2(seq(min(x), max(x), length = 3), c("blue", "#EEEEEE", "red")) |
|
75 |
+ p = sum(x > 0)/length(x) |
|
76 |
+ if(p > 0.3 & p < 0.7) { |
|
77 |
+ if(ht_opt$verbose) { |
|
78 |
+ cat("This matrix has both negative and positive values, use a color mapping symmetric to zero\n") |
|
79 |
+ } |
|
80 |
+ if(length(unique(x)) >= 100) { |
|
81 |
+ q1 = quantile(abs(x), 0.99) |
|
82 |
+ col_fun = colorRamp2(c(-q1, 0, q1), c("blue", "#EEEEEE", "red")) |
|
80 | 83 |
} else { |
81 |
- col_fun = colorRamp2(seq(q1, q2, length = 3), c("blue", "#EEEEEE", "red")) |
|
84 |
+ q1 = max(abs(x)) |
|
85 |
+ col_fun = colorRamp2(c(-q1, 0, q1), c("blue", "#EEEEEE", "red")) |
|
82 | 86 |
} |
83 | 87 |
} else { |
84 |
- col_fun = colorRamp2(seq(min(x), max(x), length = 3), c("blue", "#EEEEEE", "red")) |
|
88 |
+ if(length(unique(x)) >= 100) { |
|
89 |
+ q1 = quantile(x, 0.01) |
|
90 |
+ q2 = quantile(x, 0.99) |
|
91 |
+ if(length(unique(x[x > q1 & x < q2])) == 1) { |
|
92 |
+ col_fun = colorRamp2(seq(min(x), max(x), length = 3), c("blue", "#EEEEEE", "red")) |
|
93 |
+ } else { |
|
94 |
+ col_fun = colorRamp2(seq(q1, q2, length = 3), c("blue", "#EEEEEE", "red")) |
|
95 |
+ } |
|
96 |
+ } else { |
|
97 |
+ col_fun = colorRamp2(seq(min(x), max(x), length = 3), c("blue", "#EEEEEE", "red")) |
|
98 |
+ } |
|
85 | 99 |
} |
86 | 100 |
} else { |
87 | 101 |
#col_fun = colorRamp2(range(min(x), max(x)), c("white", hsv(runif(1), 1, 1))) |
... | ... |
@@ -35,7 +35,7 @@ Legend(at, labels = at, col_fun, nrow = NULL, ncol = 1, by_row = FALSE, |
35 | 35 |
\item{background}{Background colors for the grids. It is used when points and lines are the legend graphics.} |
36 | 36 |
\item{type}{Type of legends. The value can be one of \code{grid}, \code{points} and \code{lines}.} |
37 | 37 |
\item{legend_gp}{Graphic parameters for the legend grids. You should control the filled color of the legend grids by \code{gpar(fill = ...)}.} |
38 |
- \item{pch}{Type of points if points are used as legend. Note you can use single-letter as pch, e.g. \code{pch = 'A'}.} |
|
38 |
+ \item{pch}{Type of points if points are used as legend. Note you can use single-letter as pch, e.g. \code{pch = 'A'}. There are three additional integers that are valid for \code{pch}: 26 and 27 for single diagonal lines and 28 for double diagonal lines.} |
|
39 | 39 |
\item{size}{Size of points.} |
40 | 40 |
\item{legend_height}{Height of the whole legend body. It is only used for vertical continous legend.} |
41 | 41 |
\item{legend_width}{Width of the whole legend body. It is only used for horizontal continous legend.} |
... | ... |
@@ -11,7 +11,7 @@ oncoPrint(mat, |
11 | 11 |
get_type = default_get_type, |
12 | 12 |
alter_fun, |
13 | 13 |
alter_fun_is_vectorized = NULL, |
14 |
- col, |
|
14 |
+ col = NULL, |
|
15 | 15 |
|
16 | 16 |
top_annotation = HeatmapAnnotation(cbar = anno_oncoprint_barplot()), |
17 | 17 |
right_annotation = rowAnnotation(rbar = anno_oncoprint_barplot()), |