Browse code

Added the ability to return a list of heatmaps to 'moduleHeatmap'. This made the generation of module heatmaps in the report much quicker as the data does not have to be renormalized each time

Joshua D. Campbell authored on 26/09/2021 18:26:49
Showing 1 changed files
... ...
@@ -16,9 +16,11 @@
16 16
 #'  \linkS4class{SingleCellExperiment} object. Default "counts".
17 17
 #' @param altExpName The name for the \link{altExp} slot
18 18
 #'  to use. Default "featureSubset".
19
-#' @param featureModule Integer Vector. The featureModule(s) to display.
19
+#' @param modules Integer Vector. The featureModule(s) to display.
20 20
 #'  Multiple modules can be included in a vector. Default \code{NULL} which
21 21
 #'  plots all module heatmaps.
22
+#' @param featureModule Same as \code{modules}. Either can be used to specify
23
+#' the modules to display. 
22 24
 #' @param col Passed to \link[ComplexHeatmap]{Heatmap}. Set color boundaries
23 25
 #'  and colors.
24 26
 #' @param topCells Integer. Number of cells with the highest and lowest
... ...
@@ -100,6 +102,9 @@
100 102
 #' and reduced the memory of the plot and the size of a file. If \code{NULL},
101 103
 #' then rasterization will be automatically determined by the underlying
102 104
 #' \link[ComplexHeatmap]{Heatmap} function. Default \code{TRUE}.
105
+#' @param returnAsList Boolean. If \code{TRUE}, then a list of plots will be
106
+#' returned instead of a single multi-panel figure. These plots can be 
107
+#' displayed using the \link[grid]{grid.draw} function. Default \code{FALSE}.
103 108
 #' @param ... Additional parameters passed to \link[ComplexHeatmap]{Heatmap}.
104 109
 #' @return A \link[multipanelfigure]{multi_panel_figure} object if plotting
105 110
 #'  more than one module heatmaps. Otherwise a
... ...
@@ -111,6 +116,7 @@ setGeneric("moduleHeatmap",
111 116
     function(x,
112 117
         useAssay = "counts",
113 118
         altExpName = "featureSubset",
119
+        modules = NULL,        
114 120
         featureModule = NULL,
115 121
         col = circlize::colorRamp2(c(-2, 0, 2),
116 122
             c("#1E90FF", "#FFFFFF", "#CD2626")),
... ...
@@ -136,6 +142,7 @@ setGeneric("moduleHeatmap",
136 142
         unit = "mm",
137 143
         ncol = NULL,
138 144
         useRaster = TRUE,
145
+        returnAsList = FALSE,
139 146
         ...) {
140 147
     standardGeneric("moduleHeatmap")})
141 148
 
... ...
@@ -151,6 +158,7 @@ setMethod("moduleHeatmap",
151 158
     function(x,
152 159
         useAssay = "counts",
153 160
         altExpName = "featureSubset",
161
+        modules = NULL,
154 162
         featureModule = NULL,
155 163
         col = circlize::colorRamp2(c(-2, 0, 2),
156 164
             c("#1E90FF", "#FFFFFF", "#CD2626")),
... ...
@@ -176,8 +184,15 @@ setMethod("moduleHeatmap",
176 184
         unit = "mm",
177 185
         ncol = NULL,
178 186
         useRaster = TRUE,
187
+        returnAsList = FALSE,
179 188
         ...) {
180 189
 
190
+        # 'modules' is an easier parameter name to remember so we include 
191
+        # support for both. 
192
+        if(!is.null(modules)) {
193
+            featureModule <- modules
194
+        }
195
+        
181 196
         altExp <- SingleCellExperiment::altExp(x, altExpName)
182 197
 
183 198
         counts <- SummarizedExperiment::assay(altExp, i = useAssay)
... ...
@@ -212,6 +227,8 @@ setMethod("moduleHeatmap",
212 227
 
213 228
         if (moduleLabel == "auto") {
214 229
             moduleLabel <- paste0("Module ", as.character(featureModule))
230
+        } else if (length(moduleLabel) == 1 & length(featureModule) > 1) {
231
+            moduleLabel <- rep(moduleLabel, length(featureModule))
215 232
         } else if (length(moduleLabel) != length(featureModule)) {
216 233
             stop("Invalid 'moduleLabel' length")
217 234
         }
... ...
@@ -264,12 +281,20 @@ setMethod("moduleHeatmap",
264 281
 
265 282
         # Get max rowFontSize if multiple modules are selected
266 283
         if (is.null(rowFontSize)) {
267
-          if (length(featureIndices) > 1) {
284
+          if (length(featureIndices) > 1 & !isTRUE(returnAsList)) {
285
+            # If there is more than 1 module selected, then the miniumum size
286
+            # size will be caculated for each module. This will ensure that
287
+            # all modules will have the same rowFontSize and the module
288
+            # heatmaps will have the same width. 
268 289
             maxlen <- max(unlist(lapply(featureIndices, length)))
269 290
             maxlen <- maxlen * sqrt(length(featureIndices))
270
-            rowFontSize <- min(200 / maxlen, 20)
291
+            rowFontSize <- rep(min(200 / maxlen, 20), length(featureIndices))
271 292
           } else {
272
-            rowFontSize <- min(200 / length(featureIndices[[1]]), 20)
293
+            # If there is only one plot or each plot will be generated 
294
+            # separately and returned in a list, then the size of the labels,
295
+            # will be caculated for each module separately.
296
+            len <- unlist(lapply(featureIndices, length))
297
+            rowFontSize <- pmin(200 / len, 20)
273 298
           }
274 299
         }
275 300
 
... ...
@@ -288,7 +313,7 @@ setMethod("moduleHeatmap",
288 313
                 showFeatureNames = showFeatureNames,
289 314
                 displayNames = displayNames[featureIndices[[i]]],
290 315
                 trim = trim,
291
-                rowFontSize = rowFontSize,
316
+                rowFontSize = rowFontSize[i],
292 317
                 showHeatmapLegend = showHeatmapLegend,
293 318
                 showTopAnnotationLegend = showTopAnnotationLegend,
294 319
                 showTopAnnotationName = showTopAnnotationName,
... ...
@@ -315,17 +340,22 @@ setMethod("moduleHeatmap",
315 340
                     wrap.grobs = TRUE)
316 341
             }
317 342
 
318
-            figure <- multipanelfigure::multi_panel_figure(
319
-                columns = ncol,
320
-                rows = nrow,
321
-                width = width,
322
-                height = height,
323
-                unit = unit)
324
-
325
-            for (i in seq(length(plts))) {
326
-                figure <- suppressMessages(multipanelfigure::fill_panel(figure,
327
-                    plts[[i]], label = ""))
343
+            if(isTRUE(returnAsList)) {
344
+                figure <- plts    
345
+            } else {
346
+                figure <- multipanelfigure::multi_panel_figure(
347
+                    columns = ncol,
348
+                    rows = nrow,
349
+                    width = width,
350
+                    height = height,
351
+                    unit = unit)
352
+                
353
+                for (i in seq(length(plts))) {
354
+                    figure <- suppressMessages(multipanelfigure::fill_panel(figure,
355
+                                                                            plts[[i]], label = ""))
356
+                }
328 357
             }
358
+            
329 359
             suppressWarnings(return(figure))
330 360
         }
331 361
     }
... ...
@@ -410,6 +440,10 @@ setMethod("moduleHeatmap",
410 440
         } else {
411 441
             stop("'scaleRow' needs to be of class 'function'")
412 442
         }
443
+        # If the standard deviation was 0 then the values will be NA
444
+        # Replacing the NAs with zero will keep the row the middle color
445
+        # rather than grey (default with ComplexHeatmap)
446
+        filteredNormCounts[is.na(filteredNormCounts)] <- 0
413 447
     }
414 448
 
415 449
     if (!is.null(trim)) {
Browse code

Fixed lints

Joshua D. Campbell authored on 19/07/2021 13:17:02
Showing 1 changed files
... ...
@@ -264,7 +264,7 @@ setMethod("moduleHeatmap",
264 264
 
265 265
         # Get max rowFontSize if multiple modules are selected
266 266
         if (is.null(rowFontSize)) {
267
-          if(length(featureIndices) > 1) {
267
+          if (length(featureIndices) > 1) {
268 268
             maxlen <- max(unlist(lapply(featureIndices, length)))
269 269
             maxlen <- maxlen * sqrt(length(featureIndices))
270 270
             rowFontSize <- min(200 / maxlen, 20)
... ...
@@ -272,7 +272,7 @@ setMethod("moduleHeatmap",
272 272
             rowFontSize <- min(200 / length(featureIndices[[1]]), 20)
273 273
           }
274 274
         }
275
-        
275
+
276 276
         plts <- vector("list", length = length(featureModule))
277 277
         for (i in seq(length(featureModule))) {
278 278
             plts[[i]] <- .plotModuleHeatmap(normCounts = normCounts,
Browse code

Adjustments to automatic rowFonSize in moduleHeatmap when many modules are selected

Joshua D. Campbell authored on 16/07/2021 21:07:14
Showing 1 changed files
... ...
@@ -251,6 +251,7 @@ setMethod("moduleHeatmap",
251 251
             }
252 252
         )
253 253
 
254
+        # Set up displayName variable if specified
254 255
         if (is.null(displayName)) {
255 256
             displayNames <- rownames(altExp)
256 257
         } else {
... ...
@@ -261,8 +262,18 @@ setMethod("moduleHeatmap",
261 262
         z <- celdaClusters(x, altExpName = altExpName)
262 263
         y <- celdaModules(x, altExpName = altExpName)
263 264
 
265
+        # Get max rowFontSize if multiple modules are selected
266
+        if (is.null(rowFontSize)) {
267
+          if(length(featureIndices) > 1) {
268
+            maxlen <- max(unlist(lapply(featureIndices, length)))
269
+            maxlen <- maxlen * sqrt(length(featureIndices))
270
+            rowFontSize <- min(200 / maxlen, 20)
271
+          } else {
272
+            rowFontSize <- min(200 / length(featureIndices[[1]]), 20)
273
+          }
274
+        }
275
+        
264 276
         plts <- vector("list", length = length(featureModule))
265
-
266 277
         for (i in seq(length(featureModule))) {
267 278
             plts[[i]] <- .plotModuleHeatmap(normCounts = normCounts,
268 279
                 col = col,
... ...
@@ -413,10 +424,6 @@ setMethod("moduleHeatmap",
413 424
         filteredNormCounts[filteredNormCounts > trim[2]] <- trim[2]
414 425
     }
415 426
 
416
-    if (is.null(rowFontSize)) {
417
-        rowFontSize <- min(200 / nrow(filteredNormCounts), 20)
418
-    }
419
-
420 427
     if (isTRUE(showModuleLabel)) {
421 428
         plt <- ComplexHeatmap::Heatmap(matrix = filteredNormCounts,
422 429
             col = col,
Browse code

show empty gene in moduleHeatmap

zhewa authored on 17/05/2021 20:24:10
Showing 1 changed files
... ...
@@ -369,9 +369,10 @@ setMethod("moduleHeatmap",
369 369
     filteredNormCounts <-
370 370
         normCounts[featureIndices, cellIndices, drop = FALSE]
371 371
 
372
-    filteredNormCounts <-
373
-        filteredNormCounts[rowSums(filteredNormCounts > 0) > 0, ,
374
-            drop = FALSE]
372
+    # Show/hide features with 0 counts in these cells in the module
373
+    # filteredNormCounts <-
374
+    #     filteredNormCounts[rowSums(filteredNormCounts > 0) > 0, ,
375
+    #         drop = FALSE]
375 376
 
376 377
     geneIx <- match(rownames(filteredNormCounts), rownames(normCounts))
377 378
     cellIx <- match(colnames(filteredNormCounts), colnames(normCounts))
... ...
@@ -420,7 +421,7 @@ setMethod("moduleHeatmap",
420 421
         plt <- ComplexHeatmap::Heatmap(matrix = filteredNormCounts,
421 422
             col = col,
422 423
             row_title = moduleLabel,
423
-            row_title_gp = gpar(fontsize = moduleLabelSize),
424
+            row_title_gp = grid::gpar(fontsize = moduleLabelSize),
424 425
             show_column_names = FALSE,
425 426
             show_row_names = showFeatureNames,
426 427
             row_labels = displayNames,
Browse code

add arguments to generic functions

zhewa authored on 01/05/2021 20:59:26
Showing 1 changed files
... ...
@@ -107,7 +107,36 @@
107 107
 #' @importFrom methods .hasSlot
108 108
 #' @importFrom multipanelfigure multi_panel_figure
109 109
 #' @export
110
-setGeneric("moduleHeatmap", function(x, ...) {
110
+setGeneric("moduleHeatmap",
111
+    function(x,
112
+        useAssay = "counts",
113
+        altExpName = "featureSubset",
114
+        featureModule = NULL,
115
+        col = circlize::colorRamp2(c(-2, 0, 2),
116
+            c("#1E90FF", "#FFFFFF", "#CD2626")),
117
+        topCells = 100,
118
+        topFeatures = NULL,
119
+        normalizedCounts = NA,
120
+        normalize = "proportion",
121
+        transformationFun = sqrt,
122
+        scaleRow = scale,
123
+        showFeatureNames = TRUE,
124
+        displayName = NULL,
125
+        trim = c(-2, 2),
126
+        rowFontSize = NULL,
127
+        showHeatmapLegend = FALSE,
128
+        showTopAnnotationLegend = FALSE,
129
+        showTopAnnotationName = FALSE,
130
+        topAnnotationHeight = 5,
131
+        showModuleLabel = TRUE,
132
+        moduleLabel = "auto",
133
+        moduleLabelSize = NULL,
134
+        width = "auto",
135
+        height = "auto",
136
+        unit = "mm",
137
+        ncol = NULL,
138
+        useRaster = TRUE,
139
+        ...) {
111 140
     standardGeneric("moduleHeatmap")})
112 141
 
113 142
 
Browse code

Merge branch 'devel' of github.com:campbio/celda into devel

zhewa authored on 27/04/2021 14:07:40
Showing 0 changed files
Browse code

add displayName to moduleHeatmap and plotDimReduceFeature

zhewa authored on 21/04/2021 19:45:24
Showing 1 changed files
... ...
@@ -9,7 +9,8 @@
9 9
 #' @param x A numeric \link{matrix} of counts or a
10 10
 #'  \linkS4class{SingleCellExperiment}
11 11
 #'  with the matrix located in the assay slot under \code{useAssay}.
12
-#'  Rows represent features and columns represent cells.
12
+#'  Rows represent features and columns represent cells. Celda
13
+#'  results must be present under \code{metadata(altExp(x, altExpName))}.
13 14
 #' @param useAssay A string specifying which \link{assay}
14 15
 #'  slot to use if \code{x} is a
15 16
 #'  \linkS4class{SingleCellExperiment} object. Default "counts".
... ...
@@ -52,16 +53,21 @@
52 53
 #'  divides the library size of each cell by the mean library size across all
53 54
 #'  cells. Default "proportion".
54 55
 #' @param transformationFun Function. Passed to \link{normalizeCounts} if
55
-#'  \code{normalizedCounts} is \code{NA}. Applys a transformation such as
56
+#'  \code{normalizedCounts} is \code{NA}. Applies a transformation such as
56 57
 #'  \link{sqrt}, \link{log}, \link{log2}, \link{log10}, or \link{log1p}.
57
-#'  If NULL, no transformation will be applied. Occurs after normalization.
58
-#'  Default \link{sqrt}.
58
+#'  If \code{NULL}, no transformation will be applied. Occurs after
59
+#'  normalization. Default \link{sqrt}.
59 60
 #' @param scaleRow Function. Which function to use to scale each individual
60 61
 #'  row. Set to NULL to disable. Occurs after normalization and log
61 62
 #'  transformation. For example, \link{scale} will Z-score transform each row.
62 63
 #'  Default \link{scale}.
63
-#' @param showFeaturenames Logical. Wheter feature names should be displayed.
64
+#' @param showFeaturenames Logical. Whether feature names should be displayed.
64 65
 #'  Default TRUE.
66
+#' @param displayName Character. The column name of
67
+#'  \code{rowData(altExp(x, altExpName))} that specifies the display names for
68
+#'  the features. Default \code{NULL}, which displays the row names. Only works
69
+#'  if \code{showFeaturenames} is \code{TRUE} and \code{x} is a
70
+#'  \linkS4class{SingleCellExperiment} object.
65 71
 #' @param trim Numeric vector. Vector of length two that specifies the lower
66 72
 #'  and upper bounds for plotting the data. This threshold is applied
67 73
 #'  after row scaling. Set to NULL to disable. Default \code{c(-2,2)}.
... ...
@@ -108,7 +114,8 @@ setGeneric("moduleHeatmap", function(x, ...) {
108 114
 #' @rdname moduleHeatmap
109 115
 #' @examples
110 116
 #' data(sceCeldaCG)
111
-#' moduleHeatmap(sceCeldaCG, width = 250, height = 250)
117
+#' moduleHeatmap(sceCeldaCG, width = 250, height = 250,
118
+#'  displayName = "rownames")
112 119
 #' @export
113 120
 setMethod("moduleHeatmap",
114 121
     signature(x = "SingleCellExperiment"),
... ...
@@ -125,6 +132,7 @@ setMethod("moduleHeatmap",
125 132
         transformationFun = sqrt,
126 133
         scaleRow = scale,
127 134
         showFeaturenames = TRUE,
135
+        displayName = NULL,
128 136
         trim = c(-2, 2),
129 137
         rowFontSize = NULL,
130 138
         showHeatmapLegend = FALSE,
... ...
@@ -214,6 +222,13 @@ setMethod("moduleHeatmap",
214 222
             }
215 223
         )
216 224
 
225
+        if (is.null(displayName)) {
226
+            displayNames <- rownames(altExp)
227
+        } else {
228
+            displayNames <- SummarizedExperiment::rowData(altExp)[[
229
+                displayName]]
230
+        }
231
+
217 232
         z <- celdaClusters(x, altExpName = altExpName)
218 233
         y <- celdaModules(x, altExpName = altExpName)
219 234
 
... ...
@@ -231,6 +246,7 @@ setMethod("moduleHeatmap",
231 246
                 altExpName = altExpName,
232 247
                 scaleRow = scaleRow,
233 248
                 showFeaturenames = showFeaturenames,
249
+                displayNames = displayNames[featureIndices[[i]]],
234 250
                 trim = trim,
235 251
                 rowFontSize = rowFontSize,
236 252
                 showHeatmapLegend = showHeatmapLegend,
... ...
@@ -287,6 +303,7 @@ setMethod("moduleHeatmap",
287 303
     altExpName,
288 304
     scaleRow,
289 305
     showFeaturenames,
306
+    displayNames,
290 307
     trim,
291 308
     rowFontSize,
292 309
     showHeatmapLegend,
... ...
@@ -373,6 +390,7 @@ setMethod("moduleHeatmap",
373 390
             row_title_gp = gpar(fontsize = moduleLabelSize),
374 391
             show_column_names = FALSE,
375 392
             show_row_names = showFeaturenames,
393
+            row_labels = displayNames,
376 394
             row_names_gp = grid::gpar(fontsize = rowFontSize),
377 395
             cluster_rows = FALSE,
378 396
             cluster_columns = FALSE,
... ...
@@ -394,6 +412,7 @@ setMethod("moduleHeatmap",
394 412
             col = col,
395 413
             show_column_names = FALSE,
396 414
             show_row_names = showFeaturenames,
415
+            row_labels = displayNames,
397 416
             row_names_gp = grid::gpar(fontsize = rowFontSize),
398 417
             cluster_rows = FALSE,
399 418
             cluster_columns = FALSE,
Browse code

Fix lints

Joshua D. Campbell authored on 07/04/2021 21:37:51
Showing 1 changed files
... ...
@@ -366,10 +366,10 @@ setMethod("moduleHeatmap",
366 366
         filteredNormCounts[filteredNormCounts > trim[2]] <- trim[2]
367 367
     }
368 368
 
369
-    if(is.null(rowFontSize)) {
369
+    if (is.null(rowFontSize)) {
370 370
         rowFontSize <- min(200 / nrow(filteredNormCounts), 20)
371 371
     }
372
-    
372
+
373 373
     if (isTRUE(showModuleLabel)) {
374 374
         plt <- ComplexHeatmap::Heatmap(matrix = filteredNormCounts,
375 375
             col = col,
Browse code

Tweaked auto sizing of fonts in moduleHeatmap. Fixed typo in parameter name

Joshua D. Campbell authored on 07/04/2021 01:56:50
Showing 1 changed files
... ...
@@ -60,12 +60,12 @@
60 60
 #'  row. Set to NULL to disable. Occurs after normalization and log
61 61
 #'  transformation. For example, \link{scale} will Z-score transform each row.
62 62
 #'  Default \link{scale}.
63
-#' @param showFeaturenames Logical. Wheter feature names should be displayed.
63
+#' @param showFeatureNames Logical. Whether feature names should be displayed.
64 64
 #'  Default TRUE.
65 65
 #' @param trim Numeric vector. Vector of length two that specifies the lower
66 66
 #'  and upper bounds for plotting the data. This threshold is applied
67 67
 #'  after row scaling. Set to NULL to disable. Default \code{c(-2,2)}.
68
-#' @param rowFontSize Integer. Font size for feature names. If \code{NULL},
68
+#' @param rowFontSize Numeric. Font size for feature names. If \code{NULL},
69 69
 #' then the size will automatically be determined. Default \code{NULL}.
70 70
 #' @param showHeatmapLegend Passed to \link[ComplexHeatmap]{Heatmap}. Show
71 71
 #'  legend for expression levels.
... ...
@@ -124,7 +124,7 @@ setMethod("moduleHeatmap",
124 124
         normalize = "proportion",
125 125
         transformationFun = sqrt,
126 126
         scaleRow = scale,
127
-        showFeaturenames = TRUE,
127
+        showFeatureNames = TRUE,
128 128
         trim = c(-2, 2),
129 129
         rowFontSize = NULL,
130 130
         showHeatmapLegend = FALSE,
... ...
@@ -230,7 +230,7 @@ setMethod("moduleHeatmap",
230 230
                 topCells = topCells,
231 231
                 altExpName = altExpName,
232 232
                 scaleRow = scaleRow,
233
-                showFeaturenames = showFeaturenames,
233
+                showFeatureNames = showFeatureNames,
234 234
                 trim = trim,
235 235
                 rowFontSize = rowFontSize,
236 236
                 showHeatmapLegend = showHeatmapLegend,
... ...
@@ -286,7 +286,7 @@ setMethod("moduleHeatmap",
286 286
     topCells,
287 287
     altExpName,
288 288
     scaleRow,
289
-    showFeaturenames,
289
+    showFeatureNames,
290 290
     trim,
291 291
     rowFontSize,
292 292
     showHeatmapLegend,
... ...
@@ -366,13 +366,17 @@ setMethod("moduleHeatmap",
366 366
         filteredNormCounts[filteredNormCounts > trim[2]] <- trim[2]
367 367
     }
368 368
 
369
+    if(is.null(rowFontSize)) {
370
+        rowFontSize <- min(200 / nrow(filteredNormCounts), 20)
371
+    }
372
+    
369 373
     if (isTRUE(showModuleLabel)) {
370 374
         plt <- ComplexHeatmap::Heatmap(matrix = filteredNormCounts,
371 375
             col = col,
372 376
             row_title = moduleLabel,
373 377
             row_title_gp = gpar(fontsize = moduleLabelSize),
374 378
             show_column_names = FALSE,
375
-            show_row_names = showFeaturenames,
379
+            show_row_names = showFeatureNames,
376 380
             row_names_gp = grid::gpar(fontsize = rowFontSize),
377 381
             cluster_rows = FALSE,
378 382
             cluster_columns = FALSE,
... ...
@@ -393,7 +397,7 @@ setMethod("moduleHeatmap",
393 397
         plt <- ComplexHeatmap::Heatmap(matrix = filteredNormCounts,
394 398
             col = col,
395 399
             show_column_names = FALSE,
396
-            show_row_names = showFeaturenames,
400
+            show_row_names = showFeatureNames,
397 401
             row_names_gp = grid::gpar(fontsize = rowFontSize),
398 402
             cluster_rows = FALSE,
399 403
             cluster_columns = FALSE,
Browse code

Added ncol parameter to moduleHeatmap

Joshua D. Campbell authored on 01/04/2021 14:43:46
Showing 1 changed files
... ...
@@ -87,6 +87,9 @@
87 87
 #'  height of the output figure.
88 88
 #' @param unit Passed to \link[multipanelfigure]{multi_panel_figure}. Single
89 89
 #'  character object defining the unit of all dimensions defined.
90
+#' @param ncol Integer. Number of columns of module heatmaps. If \code{NULL},
91
+#' then this will be automatically calculated so that the number of columns
92
+#' and rows will be approximately the same. Default \code{NULL}.
90 93
 #' @param useRaster Boolean. Rasterizing will make the heatmap a single object
91 94
 #' and reduced the memory of the plot and the size of a file. If \code{NULL},
92 95
 #' then rasterization will be automatically determined by the underlying
... ...
@@ -134,6 +137,7 @@ setMethod("moduleHeatmap",
134 137
         width = "auto",
135 138
         height = "auto",
136 139
         unit = "mm",
140
+        ncol = NULL,
137 141
         useRaster = TRUE,
138 142
         ...) {
139 143
 
... ...
@@ -244,7 +248,9 @@ setMethod("moduleHeatmap",
244 248
         if (isTRUE(returnHeatmap)) {
245 249
             return(plts[[1]])
246 250
         } else {
247
-            ncol <- floor(sqrt(length(plts)))
251
+            if (is.null(ncol)) {
252
+              ncol <- floor(sqrt(length(plts)))
253
+            }
248 254
             nrow <- ceiling(length(plts) / ncol)
249 255
 
250 256
             for (i in seq(length(plts))) {
... ...
@@ -253,7 +259,8 @@ setMethod("moduleHeatmap",
253 259
                     wrap.grobs = TRUE)
254 260
             }
255 261
 
256
-            figure <- multipanelfigure::multi_panel_figure(columns = ncol,
262
+            figure <- multipanelfigure::multi_panel_figure(
263
+                columns = ncol,
257 264
                 rows = nrow,
258 265
                 width = width,
259 266
                 height = height,
Browse code

fix lints

Joshua D. Campbell authored on 01/04/2021 03:29:31
Showing 1 changed files
... ...
@@ -90,7 +90,7 @@
90 90
 #' @param useRaster Boolean. Rasterizing will make the heatmap a single object
91 91
 #' and reduced the memory of the plot and the size of a file. If \code{NULL},
92 92
 #' then rasterization will be automatically determined by the underlying
93
-#' \link[ComplexHeatmap]{Heatmap} function. Default \code{TRUE}. 
93
+#' \link[ComplexHeatmap]{Heatmap} function. Default \code{TRUE}.
94 94
 #' @param ... Additional parameters passed to \link[ComplexHeatmap]{Heatmap}.
95 95
 #' @return A \link[multipanelfigure]{multi_panel_figure} object if plotting
96 96
 #'  more than one module heatmaps. Otherwise a
Browse code

changed some moduleHeatmap defaults

Joshua D. Campbell authored on 01/04/2021 02:51:11
Showing 1 changed files
... ...
@@ -64,8 +64,9 @@
64 64
 #'  Default TRUE.
65 65
 #' @param trim Numeric vector. Vector of length two that specifies the lower
66 66
 #'  and upper bounds for plotting the data. This threshold is applied
67
-#'  after row scaling. Set to NULL to disable. Default c(-2,2).
68
-#' @param rowFontSize Integer. Font size for genes.
67
+#'  after row scaling. Set to NULL to disable. Default \code{c(-2,2)}.
68
+#' @param rowFontSize Integer. Font size for feature names. If \code{NULL},
69
+#' then the size will automatically be determined. Default \code{NULL}.
69 70
 #' @param showHeatmapLegend Passed to \link[ComplexHeatmap]{Heatmap}. Show
70 71
 #'  legend for expression levels.
71 72
 #' @param showTopAnnotationLegend Passed to
... ...
@@ -122,14 +123,14 @@ setMethod("moduleHeatmap",
122 123
         scaleRow = scale,
123 124
         showFeaturenames = TRUE,
124 125
         trim = c(-2, 2),
125
-        rowFontSize = 6,
126
+        rowFontSize = NULL,
126 127
         showHeatmapLegend = FALSE,
127 128
         showTopAnnotationLegend = FALSE,
128 129
         showTopAnnotationName = FALSE,
129
-        topAnnotationHeight = 1.5,
130
+        topAnnotationHeight = 5,
130 131
         showModuleLabel = TRUE,
131 132
         moduleLabel = "auto",
132
-        moduleLabelSize = 13,
133
+        moduleLabelSize = NULL,
133 134
         width = "auto",
134 135
         height = "auto",
135 136
         unit = "mm",
... ...
@@ -170,9 +171,8 @@ setMethod("moduleHeatmap",
170 171
 
171 172
         if (moduleLabel == "auto") {
172 173
             moduleLabel <- paste0("Module ", as.character(featureModule))
173
-        } else if (length(moduleLabel) != length(unique(celdaModules(x,
174
-            altExpName = altExpName)))) {
175
-            stop("Invalid 'moduleLabel' length!")
174
+        } else if (length(moduleLabel) != length(featureModule)) {
175
+            stop("Invalid 'moduleLabel' length")
176 176
         }
177 177
 
178 178
         # factorize counts matrix
... ...
@@ -379,7 +379,8 @@ setMethod("moduleHeatmap",
379 379
                 show_legend = showTopAnnotationLegend,
380 380
                 show_annotation_name = showTopAnnotationName,
381 381
                 col = list(cell = ccols),
382
-                simple_anno_size = grid::unit(topAnnotationHeight, unit)),
382
+                simple_anno_size = grid::unit(topAnnotationHeight, unit),
383
+                simple_anno_size_adjust = TRUE),
383 384
             ...)
384 385
     } else {
385 386
         plt <- ComplexHeatmap::Heatmap(matrix = filteredNormCounts,
... ...
@@ -399,7 +400,8 @@ setMethod("moduleHeatmap",
399 400
                 show_legend = showTopAnnotationLegend,
400 401
                 show_annotation_name = showTopAnnotationName,
401 402
                 col = list(cell = ccols),
402
-                simple_anno_size = grid::unit(topAnnotationHeight, unit)),
403
+                simple_anno_size = grid::unit(topAnnotationHeight, unit),
404
+                simple_anno_size_adjust = TRUE),
403 405
             ...)
404 406
     }
405 407
     return(plt)
Browse code

Added parameter to set raster in moduleHeatmap. default is TRUE

Joshua D. Campbell authored on 31/03/2021 13:27:14
Showing 1 changed files
... ...
@@ -86,6 +86,10 @@
86 86
 #'  height of the output figure.
87 87
 #' @param unit Passed to \link[multipanelfigure]{multi_panel_figure}. Single
88 88
 #'  character object defining the unit of all dimensions defined.
89
+#' @param useRaster Boolean. Rasterizing will make the heatmap a single object
90
+#' and reduced the memory of the plot and the size of a file. If \code{NULL},
91
+#' then rasterization will be automatically determined by the underlying
92
+#' \link[ComplexHeatmap]{Heatmap} function. Default \code{TRUE}. 
89 93
 #' @param ... Additional parameters passed to \link[ComplexHeatmap]{Heatmap}.
90 94
 #' @return A \link[multipanelfigure]{multi_panel_figure} object if plotting
91 95
 #'  more than one module heatmaps. Otherwise a
... ...
@@ -129,6 +133,7 @@ setMethod("moduleHeatmap",
129 133
         width = "auto",
130 134
         height = "auto",
131 135
         unit = "mm",
136
+        useRaster = TRUE,
132 137
         ...) {
133 138
 
134 139
         altExp <- SingleCellExperiment::altExp(x, altExpName)
... ...
@@ -231,6 +236,7 @@ setMethod("moduleHeatmap",
231 236
                 showModuleLabel = showModuleLabel,
232 237
                 moduleLabel = moduleLabel[i],
233 238
                 moduleLabelSize = moduleLabelSize,
239
+                useRaster = useRaster,
234 240
                 unit = unit,
235 241
                 ... = ...)
236 242
         }
... ...
@@ -283,6 +289,7 @@ setMethod("moduleHeatmap",
283 289
     showModuleLabel,
284 290
     moduleLabel,
285 291
     moduleLabelSize,
292
+    useRaster,
286 293
     unit,
287 294
     ...) {
288 295
 
... ...
@@ -364,6 +371,7 @@ setMethod("moduleHeatmap",
364 371
             cluster_columns = FALSE,
365 372
             heatmap_legend_param = list(title = "Expression"),
366 373
             show_heatmap_legend = showHeatmapLegend,
374
+            use_raster = useRaster,
367 375
             top_annotation = ComplexHeatmap::HeatmapAnnotation(
368 376
                 cell = factor(zToPlot,
369 377
                     levels = stringr::str_sort(unique(zToPlot),
... ...
@@ -383,6 +391,7 @@ setMethod("moduleHeatmap",
383 391
             cluster_columns = FALSE,
384 392
             heatmap_legend_param = list(title = "Expression"),
385 393
             show_heatmap_legend = showHeatmapLegend,
394
+            use_raster = useRaster,
386 395
             top_annotation = ComplexHeatmap::HeatmapAnnotation(
387 396
                 cell = factor(zToPlot,
388 397
                     levels = stringr::str_sort(unique(zToPlot),
Browse code

fix lint

zhewa authored on 08/11/2020 23:33:51
Showing 1 changed files
... ...
@@ -242,7 +242,8 @@ setMethod("moduleHeatmap",
242 242
             nrow <- ceiling(length(plts) / ncol)
243 243
 
244 244
             for (i in seq(length(plts))) {
245
-                plts[[i]] <- grid::grid.grabExpr(ComplexHeatmap::draw(plts[[i]]),
245
+                plts[[i]] <- grid::grid.grabExpr(
246
+                    ComplexHeatmap::draw(plts[[i]]),
246 247
                     wrap.grobs = TRUE)
247 248
             }
248 249
 
Browse code

moduleHeatmap

zhewa authored on 08/11/2020 23:11:22
Showing 1 changed files
... ...
@@ -87,7 +87,9 @@
87 87
 #' @param unit Passed to \link[multipanelfigure]{multi_panel_figure}. Single
88 88
 #'  character object defining the unit of all dimensions defined.
89 89
 #' @param ... Additional parameters passed to \link[ComplexHeatmap]{Heatmap}.
90
-#' @return A \link[multipanelfigure]{multi_panel_figure} object.
90
+#' @return A \link[multipanelfigure]{multi_panel_figure} object if plotting
91
+#'  more than one module heatmaps. Otherwise a
92
+#'  \link[ComplexHeatmap]{HeatmapList} object is returned.
91 93
 #' @importFrom methods .hasSlot
92 94
 #' @importFrom multipanelfigure multi_panel_figure
93 95
 #' @export
... ...
@@ -155,6 +157,12 @@ setMethod("moduleHeatmap",
155 157
             featureModule <- sort(unique(celdaModules(x)))
156 158
         }
157 159
 
160
+        if (length(featureModule) == 1) {
161
+            returnHeatmap <- TRUE
162
+        } else {
163
+            returnHeatmap <- FALSE
164
+        }
165
+
158 166
         if (moduleLabel == "auto") {
159 167
             moduleLabel <- paste0("Module ", as.character(featureModule))
160 168
         } else if (length(moduleLabel) != length(unique(celdaModules(x,
... ...
@@ -227,25 +235,29 @@ setMethod("moduleHeatmap",
227 235
                 ... = ...)
228 236
         }
229 237
 
230
-        ncol <- floor(sqrt(length(plts)))
231
-        nrow <- ceiling(length(plts) / ncol)
238
+        if (isTRUE(returnHeatmap)) {
239
+            return(plts[[1]])
240
+        } else {
241
+            ncol <- floor(sqrt(length(plts)))
242
+            nrow <- ceiling(length(plts) / ncol)
232 243
 
233
-        for (i in seq(length(plts))) {
234
-            plts[[i]] <- grid::grid.grabExpr(ComplexHeatmap::draw(plts[[i]]),
235
-                wrap.grobs = TRUE)
236
-        }
244
+            for (i in seq(length(plts))) {
245
+                plts[[i]] <- grid::grid.grabExpr(ComplexHeatmap::draw(plts[[i]]),
246
+                    wrap.grobs = TRUE)
247
+            }
237 248
 
238
-        figure <- multipanelfigure::multi_panel_figure(columns = ncol,
239
-            rows = nrow,
240
-            width = width,
241
-            height = height,
242
-            unit = unit)
249
+            figure <- multipanelfigure::multi_panel_figure(columns = ncol,
250
+                rows = nrow,
251
+                width = width,
252
+                height = height,
253
+                unit = unit)
243 254
 
244
-        for (i in seq(length(plts))) {
245
-            figure <- suppressMessages(multipanelfigure::fill_panel(figure,
246
-                plts[[i]], label = ""))
255
+            for (i in seq(length(plts))) {
256
+                figure <- suppressMessages(multipanelfigure::fill_panel(figure,
257
+                    plts[[i]], label = ""))
258
+            }
259
+            suppressWarnings(return(figure))
247 260
         }
248
-        suppressWarnings(return(figure))
249 261
     }
250 262
 )
251 263
 
Browse code

remove leftAnnotation options in moduleHeatmap, add row title

zhewa authored on 07/11/2020 22:45:47
Showing 1 changed files
... ...
@@ -72,29 +72,20 @@
72 72
 #'  \link[ComplexHeatmap]{HeatmapAnnotation}. Show legend for cell annotation.
73 73
 #' @param showTopAnnotationName Passed to
74 74
 #'  \link[ComplexHeatmap]{HeatmapAnnotation}. Show heatmap top annotation name.
75
-#' @param showLeftAnnotationLegend Passed to
76
-#'  \link[ComplexHeatmap]{HeatmapAnnotation}. Show legend for feature module
77
-#'  annotation.
78 75
 #' @param topAnnotationHeight Passed to
79 76
 #'  \link[ComplexHeatmap]{HeatmapAnnotation}. Column annotation height.
80 77
 #'  \link[ComplexHeatmap]{rowAnnotation}. Show legend for module annotation.
81
-#' @param showLeftAnnotation Show left annotation. Default \code{FALSE}.
82
-#' @param showLeftAnnotationName Passed to
83
-#'  \link[ComplexHeatmap]{rowAnnotation}. Show heatmap left annotation name.
84
-#' @param leftAnnotationWidth Passed to
85
-#'  \link[ComplexHeatmap]{rowAnnotation}. Row annotation width.
78
+#' @param showModuleLabel Show left side module labels.
79
+#' @param moduleLabel The left side row titles for module heatmap. Must be
80
+#'  vector of the same length as \code{featureModule}. Default "auto", which
81
+#'  automatically pulls module labels from \code{x}.
82
+#' @param moduleLabelSize Passed to \link{gpar}. The size of text (in points).
86 83
 #' @param width Passed to \link[multipanelfigure]{multi_panel_figure}. The
87 84
 #'  width of the output figure.
88 85
 #' @param height Passed to \link[multipanelfigure]{multi_panel_figure}. The
89 86
 #'  height of the output figure.
90 87
 #' @param unit Passed to \link[multipanelfigure]{multi_panel_figure}. Single
91 88
 #'  character object defining the unit of all dimensions defined.
92
-#' @param ModuleLabel Must be
93
-#'  vector of the same length as \code{length(unique(celdaModules(x)))} or
94
-#'  \code{length(unique(celdaClusters(x)$y))}. Set to \code{""} to disable.
95
-#' @param labelJust Passed to \link[multipanelfigure]{fill_panel}.
96
-#'  Justification for the label within the interpanel spacing grob to the
97
-#'  top-left of the panel content grob.
98 89
 #' @param ... Additional parameters passed to \link[ComplexHeatmap]{Heatmap}.
99 90
 #' @return A \link[multipanelfigure]{multi_panel_figure} object.
100 91
 #' @importFrom methods .hasSlot
... ...
@@ -130,15 +121,12 @@ setMethod("moduleHeatmap",
130 121
         showTopAnnotationLegend = FALSE,
131 122
         showTopAnnotationName = FALSE,
132 123
         topAnnotationHeight = 1.5,
133
-        showLeftAnnotation = FALSE,
134
-        showLeftAnnotationLegend = FALSE,
135
-        showLeftAnnotationName = FALSE,
136
-        leftAnnotationWidth = 1.5,
124
+        showModuleLabel = TRUE,
125
+        moduleLabel = "auto",
126
+        moduleLabelSize = 13,
137 127
         width = "auto",
138 128
         height = "auto",
139 129
         unit = "mm",
140
-        ModuleLabel = "auto",
141
-        labelJust = c("right", "bottom"),
142 130
         ...) {
143 131
 
144 132
         altExp <- SingleCellExperiment::altExp(x, altExpName)
... ...
@@ -167,16 +155,11 @@ setMethod("moduleHeatmap",
167 155
             featureModule <- sort(unique(celdaModules(x)))
168 156
         }
169 157
 
170
-        if (is.null(ModuleLabel)) {
171
-            ModuleLabel <- NULL
172
-        } else if (ModuleLabel == "auto") {
173
-            ModuleLabel <- as.character(featureModule)
174
-        } else if (ModuleLabel == "") {
175
-            ModuleLabel <- rep("", length = length(unique(celdaModules(x,
176
-                altExpName = altExpName))))
177
-        } else if (length(ModuleLabel) != length(unique(celdaModules(x,
158
+        if (moduleLabel == "auto") {
159
+            moduleLabel <- paste0("Module ", as.character(featureModule))
160
+        } else if (length(moduleLabel) != length(unique(celdaModules(x,
178 161
             altExpName = altExpName)))) {
179
-            stop("Invalid 'ModuleLabel' length!")
162
+            stop("Invalid 'moduleLabel' length!")
180 163
         }
181 164
 
182 165
         # factorize counts matrix
... ...
@@ -237,15 +220,13 @@ setMethod("moduleHeatmap",
237 220
                 showTopAnnotationLegend = showTopAnnotationLegend,
238 221
                 showTopAnnotationName = showTopAnnotationName,
239 222
                 topAnnotationHeight = topAnnotationHeight,
240
-                showLeftAnnotation = showLeftAnnotation,
241
-                showLeftAnnotationLegend = showLeftAnnotationLegend,
242
-                showLeftAnnotationName = showLeftAnnotationName,
243
-                leftAnnotationWidth = leftAnnotationWidth,
223
+                showModuleLabel = showModuleLabel,
224
+                moduleLabel = moduleLabel[i],
225
+                moduleLabelSize = moduleLabelSize,
244 226
                 unit = unit,
245 227
                 ... = ...)
246 228
         }
247 229
 
248
-
249 230
         ncol <- floor(sqrt(length(plts)))
250 231
         nrow <- ceiling(length(plts) / ncol)
251 232
 
... ...
@@ -261,13 +242,8 @@ setMethod("moduleHeatmap",
261 242
             unit = unit)
262 243
 
263 244
         for (i in seq(length(plts))) {
264
-            if (!is.null(ModuleLabel)) {
265
-                figure <- suppressMessages(multipanelfigure::fill_panel(figure,
266
-                    plts[[i]], label = ModuleLabel[i], label_just = labelJust))
267
-            } else {
268
-                figure <- suppressMessages(multipanelfigure::fill_panel(figure,
269
-                    plts[[i]], label_just = labelJust))
270
-            }
245
+            figure <- suppressMessages(multipanelfigure::fill_panel(figure,
246
+                plts[[i]], label = ""))
271 247
         }
272 248
         suppressWarnings(return(figure))
273 249
     }
... ...
@@ -291,10 +267,9 @@ setMethod("moduleHeatmap",
291 267
     showTopAnnotationLegend,
292 268
     showTopAnnotationName,
293 269
     topAnnotationHeight,
294
-    showLeftAnnotation,
295
-    showLeftAnnotationLegend,
296
-    showLeftAnnotationName,
297
-    leftAnnotationWidth,
270
+    showModuleLabel,
271
+    moduleLabel,
272
+    moduleLabelSize,
298 273
     unit,
299 274
     ...) {
300 275
 
... ...
@@ -364,9 +339,11 @@ setMethod("moduleHeatmap",
364 339
         filteredNormCounts[filteredNormCounts > trim[2]] <- trim[2]
365 340
     }
366 341
 
367
-    if (isTRUE(showLeftAnnotation)) {
342
+    if (isTRUE(showModuleLabel)) {
368 343
         plt <- ComplexHeatmap::Heatmap(matrix = filteredNormCounts,
369 344
             col = col,
345
+            row_title = moduleLabel,
346
+            row_title_gp = gpar(fontsize = moduleLabelSize),
370 347
             show_column_names = FALSE,
371 348
             show_row_names = showFeaturenames,
372 349
             row_names_gp = grid::gpar(fontsize = rowFontSize),
... ...
@@ -382,14 +359,6 @@ setMethod("moduleHeatmap",
382 359
                 show_annotation_name = showTopAnnotationName,
383 360
                 col = list(cell = ccols),
384 361
                 simple_anno_size = grid::unit(topAnnotationHeight, unit)),
385
-            left_annotation = ComplexHeatmap::rowAnnotation(
386
-                module = factor(yToPlot,
387
-                    levels = stringr::str_sort(unique(yToPlot),
388
-                        numeric = TRUE)),
389
-                show_legend = showLeftAnnotationLegend,
390
-                show_annotation_name = showLeftAnnotationName,
391
-                col = list(module = rcols),
392
-                simple_anno_size = grid::unit(leftAnnotationWidth, unit)),
393 362
             ...)
394 363
     } else {
395 364
         plt <- ComplexHeatmap::Heatmap(matrix = filteredNormCounts,
Browse code

fix doc warning file link in package does not exist and so has been treated as a topic

zhewa authored on 16/10/2020 21:36:32
Showing 1 changed files
... ...
@@ -10,10 +10,10 @@
10 10
 #'  \linkS4class{SingleCellExperiment}
11 11
 #'  with the matrix located in the assay slot under \code{useAssay}.
12 12
 #'  Rows represent features and columns represent cells.
13
-#' @param useAssay A string specifying which \link[SummarizedExperiment]{assay}
13
+#' @param useAssay A string specifying which \link{assay}
14 14
 #'  slot to use if \code{x} is a
15 15
 #'  \linkS4class{SingleCellExperiment} object. Default "counts".
16
-#' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot
16
+#' @param altExpName The name for the \link{altExp} slot
17 17
 #'  to use. Default "featureSubset".
18 18
 #' @param featureModule Integer Vector. The featureModule(s) to display.
19 19
 #'  Multiple modules can be included in a vector. Default \code{NULL} which
Browse code

fix bioc check doc warning. Fix vignette

zhewa authored on 13/10/2020 18:47:29
Showing 1 changed files
... ...
@@ -15,8 +15,6 @@
15 15
 #'  \linkS4class{SingleCellExperiment} object. Default "counts".
16 16
 #' @param altExpName The name for the \link[SingleCellExperiment]{altExp} slot
17 17
 #'  to use. Default "featureSubset".
18
-#' @param celdaMod Celda object of class \link{celda_G} or \link{celda_CG}. Used
19
-#'  only if \code{x} is a matrix object.
20 18
 #' @param featureModule Integer Vector. The featureModule(s) to display.
21 19
 #'  Multiple modules can be included in a vector. Default \code{NULL} which
22 20
 #'  plots all module heatmaps.
Browse code

upgrade probabilityMap

zhewa authored on 13/10/2020 00:14:45
Showing 1 changed files
... ...
@@ -100,6 +100,7 @@
100 100
 #' @param ... Additional parameters passed to \link[ComplexHeatmap]{Heatmap}.
101 101
 #' @return A \link[multipanelfigure]{multi_panel_figure} object.
102 102
 #' @importFrom methods .hasSlot
103
+#' @importFrom multipanelfigure multi_panel_figure
103 104
 #' @export
104 105
 setGeneric("moduleHeatmap", function(x, ...) {
105 106
     standardGeneric("moduleHeatmap")})
Browse code

minor fix

zhewa authored on 05/10/2020 18:34:31
Showing 1 changed files
... ...
@@ -1,9 +1,11 @@
1 1
 #' @title Heatmap for featureModules
2
-#' @description Renders a heatmap for selected featureModules. Cells are
2
+#' @description Renders a heatmap for selected \code{featureModule}. Cells are
3 3
 #'  ordered from those with the lowest probability of the module on the left to
4 4
 #'  the highest probability on the right. Features are ordered from those
5 5
 #'  with the highest probability in the module
6
-#'  on the top to the lowest probability on the bottom.
6
+#'  on the top to the lowest probability on the bottom. Use of
7
+#'  \link[multipanelfigure]{save_multi_panel_figure} is recommended for
8
+#'  outputting figures in various formats.
7 9
 #' @param x A numeric \link{matrix} of counts or a
8 10
 #'  \linkS4class{SingleCellExperiment}
9 11
 #'  with the matrix located in the assay slot under \code{useAssay}.
... ...
@@ -73,12 +75,15 @@
73 75
 #' @param showTopAnnotationName Passed to
74 76
 #'  \link[ComplexHeatmap]{HeatmapAnnotation}. Show heatmap top annotation name.
75 77
 #' @param showLeftAnnotationLegend Passed to
76
-#' @param annotationHeight Passed to
78
+#'  \link[ComplexHeatmap]{HeatmapAnnotation}. Show legend for feature module
79
+#'  annotation.
80
+#' @param topAnnotationHeight Passed to
77 81
 #'  \link[ComplexHeatmap]{HeatmapAnnotation}. Column ann