... | ... |
@@ -304,7 +304,7 @@ Heatmap = function(matrix, col, name, |
304 | 304 |
show_heatmap_legend = TRUE, |
305 | 305 |
heatmap_legend_param = list(title = name), |
306 | 306 |
|
307 |
- use_raster = nrow(matrix) > 5000, |
|
307 |
+ use_raster = nrow(matrix) > 2000 || ncol(matrix) > 2000, |
|
308 | 308 |
raster_device = c("png", "jpeg", "tiff", "CairoPNG", "CairoJPEG", "CairoTIFF"), |
309 | 309 |
raster_quality = 2, |
310 | 310 |
raster_device_param = list(), |
... | ... |
@@ -1015,6 +1015,19 @@ make_cluster = function(object, which = c("row", "column")) { |
1015 | 1015 |
lt$fmt = title |
1016 | 1016 |
do.call(sprintf, lt) |
1017 | 1017 |
}) |
1018 |
+ } else if(grepl("@\\{.+\\}", title)) { |
|
1019 |
+ title = apply(unique(split), 1, function(x) { |
|
1020 |
+ x = x |
|
1021 |
+ GetoptLong::qq(title) |
|
1022 |
+ }) |
|
1023 |
+ } else if(grepl("\\{.+\\}", title)) { |
|
1024 |
+ if(!requireNamespace("glue")) { |
|
1025 |
+ stop("You need to install glue package.") |
|
1026 |
+ } |
|
1027 |
+ title = apply(unique(split), 1, function(x) { |
|
1028 |
+ x = x |
|
1029 |
+ glue::glue(title) |
|
1030 |
+ }) |
|
1018 | 1031 |
} |
1019 | 1032 |
} |
1020 | 1033 |
} |
... | ... |
@@ -140,7 +140,10 @@ HeatmapAnnotation = function(..., |
140 | 140 |
warning("`df` should be a data frame while not a matrix. Convert it to data frame.") |
141 | 141 |
df = as.data.frame(df) |
142 | 142 |
} else if(!is.data.frame(df)) { |
143 |
- stop("`df` should be a data frame.") |
|
143 |
+ oe = try(df <- as.data.frame(df), silent = TRUE) |
|
144 |
+ if(inherits(oe, "try-errir")) { |
|
145 |
+ stop("`df` should be a data frame.") |
|
146 |
+ } |
|
144 | 147 |
} |
145 | 148 |
} |
146 | 149 |
|
... | ... |
@@ -555,6 +558,7 @@ setMethod(f = "draw", |
555 | 558 |
test2 = TRUE |
556 | 559 |
} else { |
557 | 560 |
test2 = test |
561 |
+ test = "" |
|
558 | 562 |
} |
559 | 563 |
|
560 | 564 |
if(test2) { |