Browse code

translate stats::heatmap() and gplots::heatmap.2()

Zuguang Gu authored on 13/12/2020 20:54:51
Showing 143 changed files

... ...
@@ -1,8 +1,8 @@
1 1
 Package: ComplexHeatmap
2 2
 Type: Package
3 3
 Title: Make Complex Heatmaps
4
-Version: 2.7.1.1010
5
-Date: 2020-12-8
4
+Version: 2.7.1.1011
5
+Date: 2020-12-13
6 6
 Author: Zuguang Gu
7 7
 Maintainer: Zuguang Gu <z.gu@dkfz.de>
8 8
 Depends: R (>= 3.1.2), methods, grid, graphics, stats, grDevices
... ...
@@ -13,7 +13,7 @@ Suggests: testthat (>= 1.0.0), knitr, markdown, dendsort,
13 13
     jpeg, tiff, fastcluster, EnrichedHeatmap,
14 14
     dendextend (>= 1.0.1), grImport, grImport2, glue,
15 15
     GenomicRanges, gridtext, pheatmap (>= 1.0.12),
16
-    shiny, S4Vectors (>= 0.26.1)
16
+    shiny, S4Vectors (>= 0.26.1), gridGraphics, gplots
17 17
 VignetteBuilder: knitr
18 18
 Description: Complex heatmaps are efficient to visualize associations 
19 19
     between different sources of data sets and reveal potential patterns. 
... ...
@@ -21,4 +21,4 @@ Description: Complex heatmaps are efficient to visualize associations
21 21
     multiple heatmaps and supports various annotation graphics.
22 22
 biocViews: Software, Visualization, Sequencing
23 23
 URL: https://github.com/jokergoo/ComplexHeatmap, https://jokergoo.github.io/ComplexHeatmap-reference/book/
24
-License: MIT + file LICENSE
25 24
\ No newline at end of file
25
+License: MIT + file LICENSE
... ...
@@ -154,6 +154,8 @@ export("columnAnnotation")
154 154
 export("comb_degree")
155 155
 export("comb_name")
156 156
 export("comb_size")
157
+export("compare_heatmap")
158
+export("compare_heatmap.2")
157 159
 export("compare_pheatmap")
158 160
 export("complement_size")
159 161
 export("decorate_annotation")
... ...
@@ -181,6 +183,8 @@ export("grid.annotation_axis")
181 183
 export("grid.boxplot")
182 184
 export("grid.dendrogram")
183 185
 export("gt_render")
186
+export("heatmap")
187
+export("heatmap.2")
184 188
 export("ht_global_opt")
185 189
 export("ht_opt")
186 190
 export("ht_pos_on_device")
... ...
@@ -12,6 +12,7 @@ CHANGES in VERSION 2.7.1
12 12
 * add `bin_genome()` and `normalize_genomic_signals_to_bins()`
13 13
 * print messages if directly sending `anno_*()` functions to `top_annotation` or similar arguments.
14 14
 * `pheatmap()`: set heatmap name to " " so that there is no legend title by default.
15
+* also translate `stats::heatmap()` and `gplots::heatmap.2()`.
15 16
 
16 17
 ========================
17 18
 
... ...
@@ -243,12 +243,17 @@ AnnotationFunction = function(fun, fun_name = "", which = c("column", "row"),
243 243
 			stop_wrap("This object is not subsetable.")
244 244
 		}
245 245
 		x = copy_all(x)
246
+		if(x@fun_name == "anno_mark") {
247
+			ind_at = which(x@var_env[["at"]] %in% i)
248
+		}
246 249
 		for(var in names(x@subset_rule)) {
250
+			
247 251
 			oe = try(x@var_env[[var]] <- x@subset_rule[[var]](x@var_env[[var]], i), silent = TRUE)
248 252
 			if(inherits(oe, "try-error")) {
249 253
 				message(paste0("An error when subsetting ", var))
250 254
 				stop_wrap(oe)
251 255
 			}
256
+			
252 257
 		}
253 258
 		if(is.logical(i)) {
254 259
 			x@n = sum(i)
255 260
new file mode 100644
... ...
@@ -0,0 +1,855 @@
1
+# == title
2
+# Translate stats::heatmap to ComplexHeatmap::Heatmap
3
+#
4
+# == alias
5
+# stats_heatmap
6
+#
7
+# == param
8
+# -x The input matrix.
9
+# -col A vector of colors.
10
+# -Rowv The same as in `stats::heatmap`.
11
+# -Colv The same as in `stats::heatmap`.
12
+# -distfun The same as in `stats::heatmap`.
13
+# -hclustfun The same as in `stats::heatmap`.
14
+# -reorderfun The same as in `stats::heatmap`.
15
+# -add.expr Ignored.
16
+# -symm Ignored.
17
+# -revC Ignored.
18
+# -scale The same as in `stats::heatmap`.
19
+# -na.rm Ignored.
20
+# -margins Ignored.
21
+# -ColSideColors The same as in `stats::heatmap`.
22
+# -RowSideColors The same as in `stats::heatmap`.
23
+# -cexRow The same as in `stats::heatmap`.
24
+# -cexCol The same as in `stats::heatmap`.
25
+# -labRow The same as in `stats::heatmap`.
26
+# -labCol The same as in `stats::heatmap`.
27
+# -main The same as in `stats::heatmap`.
28
+# -xlab The same as in `stats::heatmap`.
29
+# -ylab The same as in `stats::heatmap`.
30
+# -keep.dendro Ignored.
31
+# -verbose Ignored.
32
+# -... Other arguments passed to `Heatmap`.
33
+#
34
+# == value
35
+# A `Heatmap-class` object.
36
+#
37
+# == seealso
38
+# `compare_heatmap` that compares heatmaps between ``stats::heatmap()`` and ``ComplexHeatmap::heatmap()``.
39
+heatmap = function(x, 
40
+	col = hcl.colors(12, "YlOrRd", rev = TRUE),
41
+	Rowv = NULL, 
42
+	Colv = NULL,
43
+    distfun = dist, 
44
+    hclustfun = hclust,
45
+    reorderfun = function(d, w) reorder(d, w),
46
+    add.expr, 
47
+    symm = FALSE, 
48
+    revC = identical(Colv, "Rowv"),
49
+    scale = c("row", "column", "none"), 
50
+    na.rm = TRUE,
51
+    margins = c(5, 5), 
52
+    ColSideColors, 
53
+    RowSideColors,
54
+    cexRow = 0.2 + 1/log10(nr), 
55
+    cexCol = 0.2 + 1/log10(nc),
56
+    labRow = NULL, 
57
+    labCol = NULL, 
58
+    main = NULL,
59
+    xlab = NULL, 
60
+    ylab = NULL,
61
+    keep.dendro = FALSE, 
62
+    verbose = getOption("verbose"), 
63
+    ...) {
64
+
65
+	if(is.data.frame(x)) {
66
+        warning_wrap("The input is a data frame, convert it to the matrix.")
67
+        mat = as.matrix(x)
68
+    } else {
69
+    	mat = x
70
+    }
71
+
72
+    nr = nrow(mat)
73
+    nc = ncol(mat)
74
+
75
+    ht_param = list()
76
+
77
+    # Rowv can be 1. NA, 2. a dendrogram object, 3. a vector, 4. a logical value, 5. NULL
78
+    if(identical(Rowv, NA)) {
79
+    	ht_param$cluster_rows = FALSE
80
+
81
+    	mat = mat[nr:1, , drop = FALSE]
82
+    	if(!missing(RowSideColors)) {
83
+    		RowSideColors = rev(RowSideColors)
84
+    	}
85
+        if(is.null(rownames(mat))) labRow = seq_len(nr)
86
+        if(!is.null(labRow)) {
87
+            labRow = rev(labRow)
88
+        }
89
+    } else {
90
+    	if(is.null(Rowv)) {
91
+    		row_dend = as.dendrogram(hclustfun(distfun(mat)))
92
+    		row_dend = reorderfun(row_dend, -rowMeans(mat))
93
+    	} else if(inherits(Rowv, c("dendrogram", "hclust"))) {
94
+    		row_dend = as.dendrogram(Rowv)
95
+    	} else if(is.vector(Rowv)) {
96
+    		if(length(Rowv) == nr) {
97
+    			row_dend = as.dendrogram(hclustfun(distfun(mat)))
98
+    			row_dend = reorderfun(row_dend, Rowv)
99
+    		} else if(length(Rowv) == 1 && is.logical(Rowv)) {
100
+    			if(Rowv) {
101
+    				row_dend = as.dendrogram(hclustfun(distfun(mat)))
102
+    				row_dend = reorderfun(row_dend, -rowMeans(mat))
103
+    			} else {
104
+    				row_dend = as.dendrogram(hclustfun(distfun(mat)))
105
+    				row_dend = rev(row_dend)
106
+    			}
107
+    		} else {
108
+    			stop_wrap("Wrong value for 'Rowv'.")
109
+    		}
110
+    	}
111
+
112
+    	ht_param$cluster_rows = row_dend
113
+    }
114
+
115
+    if(identical(Colv, NA)) {
116
+    	ht_param$cluster_columns = FALSE
117
+    } else {
118
+    	if(is.null(Colv)) {
119
+    		column_dend = as.dendrogram(hclustfun(distfun(t(mat))))
120
+    		column_dend = reorderfun(column_dend, colMeans(mat))
121
+    	} else if(inherits(Colv, c("dendrogram", "hclust"))) {
122
+    		column_dend = as.dendrogram(Colv)
123
+    	} else if(is.vector(Colv)) {
124
+    		if(length(Colv) == nc) {
125
+    			column_dend = as.dendrogram(hclustfun(distfun(t(mat))))
126
+    			column_dend = reorderfun(column_dend, Colv)
127
+    		} else if(length(Colv) == 1 && is.logical(Colv)) {
128
+    			if(Colv) {
129
+    				column_dend = as.dendrogram(hclustfun(distfun(t(mat))))
130
+    				column_dend = reorderfun(column_dend, -colMeans(mat))
131
+    			} else {
132
+    				column_dend = as.dendrogram(hclustfun(distfun(t(mat))))
133
+    			}
134
+    		} else {
135
+    			stop_wrap("Wrong value for 'Colv'.")
136
+    		}
137
+    	}
138
+
139
+    	ht_param$cluster_columns = column_dend
140
+    }
141
+
142
+    ht_param$row_dend_width = unit(2, "cm")
143
+    ht_param$column_dend_height = unit(2, "cm")
144
+
145
+    scale = match.arg(scale)[1]
146
+    if("row" %in% scale) {
147
+
148
+        if(any(is.na(mat))) {
149
+            mat = (mat - rowMeans(mat, na.rm = TRUE))/rowSds(mat, na.rm = TRUE)
150
+        } else {
151
+            mat = t(scale(t(mat)))
152
+        }
153
+        message_wrap("Note, in 'heatmap()', when rows are scaled, the row dendrogram is still calculated from the original matrix (not from the scaled matrix).")
154
+    } else if("column" %in% scale) {
155
+        if(any(is.na(mat))) {
156
+            mat = t((t(mat) - colMeans(mat, na.rm = TRUE))/colSds(mat, na.rm = TRUE))
157
+        } else {
158
+            mat = scale(mat)
159
+        }
160
+        message_wrap("Note, in 'heatmap()', when columns are scaled, the column dendrogram is still calculated from the original matrix (not from the scaled matrix).")
161
+    }
162
+
163
+    ht_param$matrix = mat
164
+
165
+    # if color is a color mapping function
166
+    if(is.function(col)) {
167
+        ht_param$col = col
168
+    } else {
169
+        n_col = length(col)
170
+        if(identical(scale, "row") || identical(scale, "column")) {
171
+            lim = max(abs(mat), na.rm = TRUE)
172
+            ht_param$col = colorRamp2(seq(-lim, lim, length = n_col), col)
173
+        } else {
174
+            ht_param$col = colorRamp2(seq(min(mat, na.rm = TRUE), max(mat, na.rm = TRUE), length = n_col), col)
175
+        } 
176
+    }
177
+    
178
+    if(!missing(ColSideColors)) {
179
+    	ht_param$top_annotation = HeatmapAnnotation(column = ColSideColors,
180
+    		col = list(column = structure(unique(ColSideColors), names = unique(ColSideColors))),
181
+    		show_legend = FALSE, show_annotation_name = FALSE)
182
+    }
183
+    if(!missing(RowSideColors)) {
184
+    	ht_param$left_annotation = rowAnnotation(row = RowSideColors,
185
+    		col = list(row = structure(unique(RowSideColors), names = unique(RowSideColors))),
186
+    		show_legend = FALSE, show_annotation_name = FALSE)
187
+    }
188
+
189
+    if(!is.null(labRow)) {
190
+    	ht_param$row_labels = labRow
191
+    } else if(is.null(rownames(mat))) {
192
+    	ht_param$row_labels = seq_len(nr)
193
+    } else {
194
+    	ht_param$row_labels = rownames(mat)
195
+    }
196
+
197
+    if(!is.null(labCol)) {
198
+    	ht_param$column_labels = labCol
199
+    } else if(is.null(colnames(mat))) {
200
+    	ht_param$column_labels = seq_len(nc)
201
+    } else {
202
+    	ht_param$column_labels = colnames(mat)
203
+    }
204
+
205
+    ht_param$row_names_gp = gpar(cex = cexRow)
206
+    ht_param$column_names_gp = gpar(cex = cexCol)
207
+
208
+    if(!is.null(main)) {
209
+    	ht_param$column_title = main
210
+    }
211
+    if(!is.null(xlab)) {
212
+    	if(is.null(ht_param$column_labels)) {
213
+    		ht_param$bottom_annotation = HeatmapAnnotation(xlab = anno_block(labels = xlab, gp = gpar(col = NA)))
214
+    	} else {
215
+    		ht_param$bottom_annotation = HeatmapAnnotation(
216
+    			colnames = anno_text(ht_param$column_labels, gp = ht_param$column_names_gp),
217
+    			xlab = anno_block(labels = xlab, gp = gpar(col = NA))
218
+    		)
219
+    		ht_param$show_column_names = FALSE
220
+    	}
221
+    }
222
+    if(!is.null(ylab)) {
223
+    	if(is.null(ht_param$row_labels)) {
224
+    		ht_param$right_annotation = rowAnnotation(ylab = anno_block(labels = ylab, gp = gpar(col = NA)))
225
+    	} else {
226
+    		ht_param$right_annotation = rowAnnotation(
227
+    			rownames = anno_text(ht_param$row_labels, gp = ht_param$row_names_gp),
228
+    			ylab = anno_block(labels = ylab, gp = gpar(col = NA))
229
+    		)
230
+    		ht_param$show_row_names = FALSE
231
+    	}
232
+    }
233
+
234
+    heatmap_legend_param = list(title = "")
235
+    ht_param$heatmap_legend_param = heatmap_legend_param
236
+
237
+    if(!missing(add.expr)) {
238
+    	warning_wrap("argument `add.expr` is not supported in heatmap -> Heatmap translation, skip it.")
239
+    }
240
+
241
+    ht_param = c(ht_param, list(...))
242
+    ht = do.call(Heatmap, ht_param)
243
+    attr(ht, "translate_from") = "heatmap"
244
+    ht
245
+}
246
+
247
+# == title
248
+# Compare heatmaps between stats::heatmap() and ComplexHeatmap::heatmap()
249
+#
250
+# == param
251
+# -... The same set of arguments passed to ``stats::heatmap`` and ``ComplexHeatmap::heatmap``.
252
+#
253
+# == details
254
+# The function plots two heatmaps, one by ``stats::heatmap`` and one by ``ComplexHeatmap::heatmap``.
255
+# Users can see the difference between the two implementations.
256
+#
257
+# == example
258
+# mat = matrix(rnorm(100), 10)
259
+# compare_heatmap(mat)
260
+compare_heatmap = function(...) {
261
+    p1 = gridGraphics::echoGrob(function() stats::heatmap(...))
262
+    p2 = grid.grabExpr(draw(heatmap(...)))
263
+    grid.newpage()
264
+    pushViewport(viewport(x = 0, width = 0.5, y = 0, height = unit(1, "npc") - unit(1, "cm"), just = c("left", "bottom")))
265
+    grid.draw(p1)
266
+    popViewport()
267
+    pushViewport(viewport(x = 0, width = 0.5, y = 1, height = unit(1, "cm"), just = c("left", "top")))
268
+    grid.text("stats::heatmap()")
269
+    popViewport()
270
+    pushViewport(viewport(x = 0.5, width = 0.5, y = 0, height = unit(1, "npc") - unit(1, "cm"), just = c("left", "bottom")))
271
+    grid.draw(p2)
272
+    popViewport()
273
+    pushViewport(viewport(x = 0.5, width = 0.5, y = 1, height = unit(1, "cm"), just = c("left", "top")))
274
+    grid.text("ComplexHeatmap::heatmap()")
275
+    popViewport()
276
+}
277
+
278
+
279
+# == title
280
+# Translate gplots::heatmap.2 to ComplexHeatmap::Heatmap
281
+#
282
+# == param
283
+# -x The input matrix.
284
+# -Rowv The same as in `gplots::heatmap.2`.
285
+# -Colv The same as in `gplots::heatmap.2`.
286
+# -distfun The same as in `gplots::heatmap.2`.
287
+# -hclustfun The same as in `gplots::heatmap.2`.
288
+# -dendrogram The same as in `gplots::heatmap.2`.
289
+# -reorderfun The same as in `gplots::heatmap.2`.
290
+# -symm Ignored.
291
+# -scale The same as in `gplots::heatmap.2`.
292
+# -na.rm Ignored.
293
+# -revC Ignored.
294
+# -add.expr Ignored.
295
+# -breaks The same as in `gplots::heatmap.2`.
296
+# -symbreaks Ignored.
297
+# -col The same as in `gplots::heatmap.2`.
298
+# -colsep Ignored.
299
+# -rowsep Ignored.
300
+# -sepcolor Ignored.
301
+# -sepwidth Ignored.
302
+# -cellnote The same as in `gplots::heatmap.2`.
303
+# -notecex The same as in `gplots::heatmap.2`.
304
+# -notecol The same as in `gplots::heatmap.2`.
305
+# -na.color The same as in `gplots::heatmap.2`.
306
+# -trace 'both' is reset to 'column', others are the same as in `gplots::heatmap.2`.
307
+# -tracecol The same as in `gplots::heatmap.2`.
308
+# -hline The same as in `gplots::heatmap.2`.
309
+# -vline The same as in `gplots::heatmap.2`.
310
+# -linecol The same as in `gplots::heatmap.2`.
311
+# -margins Ignored.
312
+# -ColSideColors The same as in `gplots::heatmap.2`.
313
+# -RowSideColors The same as in `gplots::heatmap.2`.
314
+# -cexRow The same as in `gplots::heatmap.2`.
315
+# -cexCol The same as in `gplots::heatmap.2`.
316
+# -labRow The same as in `gplots::heatmap.2`.
317
+# -labCol The same as in `gplots::heatmap.2`.
318
+# -srtRow Ignored.
319
+# -srtCol Ignored.
320
+# -adjRow Ignored.
321
+# -adjCol Ignored.
322
+# -offsetRow Ignored.
323
+# -offsetCol Ignored.
324
+# -colRow The same as in `gplots::heatmap.2`.
325
+# -colCol The same as in `gplots::heatmap.2`.
326
+# -key Always TRUE.
327
+# -keysize Ignored.
328
+# -density.info The same as in `gplots::heatmap.2`.
329
+# -denscol The same as in `gplots::heatmap.2`.
330
+# -symkey Ignored.
331
+# -densadj The same as in `gplots::heatmap.2`.
332
+# -key.title Always "Color Key".
333
+# -key.xlab Always "Value".
334
+# -key.ylab "Count" or "Density", depends on the value of ``density.info``.
335
+# -key.xtickfun Ignored.
336
+# -key.ytickfun Ignored.
337
+# -key.par Ignored.
338
+# -main The same as in `gplots::heatmap.2`.
339
+# -xlab The same as in `gplots::heatmap.2`.
340
+# -ylab The same as in `gplots::heatmap.2`.
341
+# -lmat Ignored.
342
+# -lhei Ignored.
343
+# -lwid Ignored.
344
+# -extrafun Ignored.
345
+# -... Other arguments passed to `Heatmap`.
346
+#
347
+# == value
348
+# A `Heatmap-class` object.
349
+#
350
+# == seealso
351
+# `compare_heatmap.2` that compares heatmaps between ``gplots::heatmap.2()`` and ``ComplexHeatmap::heatmap.2()``.
352
+heatmap.2 = function(x,
353
+
354
+    # dendrogram control
355
+    Rowv = TRUE,
356
+    Colv = TRUE,
357
+    distfun = dist,
358
+    hclustfun = hclust,
359
+    dendrogram = c("both","row","column","none"),
360
+    reorderfun = function(d, w) reorder(d, w),
361
+    symm = FALSE,
362
+
363
+    # data scaling
364
+    scale = c("none","row", "column"),
365
+    na.rm=TRUE,
366
+
367
+    # image plot
368
+    revC = identical(Colv, "Rowv"),
369
+    add.expr,
370
+
371
+    # mapping data to colors
372
+    breaks,
373
+    symbreaks=any(x < 0, na.rm=TRUE) || scale!="none",
374
+
375
+    # colors
376
+    col="heat.colors",
377
+
378
+    # block sepration
379
+    colsep,
380
+    rowsep,
381
+    sepcolor="white",
382
+    sepwidth=c(0.05,0.05),
383
+
384
+    # cell labeling
385
+    cellnote,
386
+    notecex=1.0,
387
+    notecol="cyan",
388
+    na.color=par("bg"),
389
+
390
+    # level trace
391
+    trace=c("column","row","both","none"),
392
+    tracecol="cyan",
393
+    hline=median(breaks),
394
+    vline=median(breaks),
395
+    linecol=tracecol,
396
+
397
+    # Row/Column Labeling
398
+    margins = c(5, 5),
399
+    ColSideColors,
400
+    RowSideColors,
401
+    cexRow = 0.2 + 1/log10(nr),
402
+    cexCol = 0.2 + 1/log10(nc),
403
+    labRow = NULL,
404
+    labCol = NULL,
405
+    srtRow = NULL,
406
+    srtCol = NULL,
407
+    adjRow = c(0,NA),
408
+    adjCol = c(NA,0),
409
+    offsetRow = 0.5,
410
+    offsetCol = 0.5,
411
+    colRow = NULL,
412
+    colCol = NULL,
413
+
414
+    # color key + density info
415
+    key = TRUE,
416
+    keysize = 1.5,
417
+    density.info=c("histogram","density","none"),
418
+    denscol=tracecol,
419
+    symkey = any(x < 0, na.rm=TRUE) || symbreaks,
420
+    densadj = 0.25,
421
+    key.title = NULL,
422
+    key.xlab = NULL,
423
+    key.ylab = NULL,
424
+    key.xtickfun = NULL,
425
+    key.ytickfun = NULL,
426
+    key.par=list(),
427
+
428
+    # plot labels
429
+    main = NULL,
430
+    xlab = NULL,
431
+    ylab = NULL,
432
+
433
+    # plot layout
434
+    lmat = NULL,
435
+    lhei = NULL,
436
+    lwid = NULL,
437
+
438
+    # extras
439
+    extrafun=NULL,
440
+    ...
441
+    ) {
442
+
443
+    if(is.data.frame(x)) {
444
+        warning_wrap("The input is a data frame, convert it to the matrix.")
445
+        mat = as.matrix(x)
446
+    } else {
447
+        mat = x
448
+    }
449
+
450
+    nr = nrow(mat)
451
+    nc = ncol(mat)
452
+
453
+    ht_param = list()
454
+
455
+    # Rowv can be 1. NA, 2. a dendrogram object, 3. a vector, 4. a logical value, 5. NULL
456
+    if(identical(Rowv, NA) || identical(Rowv, NULL) || identical(Rowv, FALSE)) {
457
+        ht_param$cluster_rows = FALSE
458
+    } else {
459
+        if(inherits(Rowv, c("dendrogram", "hclust"))) {
460
+            row_dend = as.dendrogram(Rowv)
461
+        } else if(is.vector(Rowv)) {
462
+            if(length(Rowv) == nr) {
463
+                row_dend = as.dendrogram(hclustfun(distfun(mat)))
464
+                row_dend = reorderfun(row_dend, Rowv)
465
+            } else if(length(Rowv) == 1 && is.logical(Rowv)) {
466
+                if(Rowv) {
467
+                    row_dend = as.dendrogram(hclustfun(distfun(mat)))
468
+                    row_dend = reorderfun(row_dend, -rowMeans(mat))
469
+                }
470
+            } else {
471
+                stop_wrap("Wrong value for 'Rowv'.")
472
+            }
473
+        }
474
+
475
+        ht_param$cluster_rows = row_dend
476
+    }
477
+
478
+    if(identical(Colv, NA) || identical(Colv, NULL) || identical(Colv, FALSE)) {
479
+        ht_param$cluster_columns = FALSE
480
+    } else {
481
+        if(inherits(Colv, c("dendrogram", "hclust"))) {
482
+            column_dend = as.dendrogram(Colv)
483
+        } else if(is.vector(Colv)) {
484
+            if(length(Colv) == nc) {
485
+                column_dend = as.dendrogram(hclustfun(distfun(t(mat))))
486
+                column_dend = reorderfun(column_dend, Colv)
487
+            } else if(length(Colv) == 1 && is.logical(Colv)) {
488
+                if(Colv) {
489
+                    column_dend = as.dendrogram(hclustfun(distfun(t(mat))))
490
+                    column_dend = reorderfun(column_dend, colMeans(mat))
491
+                }
492
+            } else {
493
+                stop_wrap("Wrong value for 'Colv'.")
494
+            }
495
+        }
496
+
497
+        ht_param$cluster_columns = column_dend
498
+    }
499
+
500
+    dendrogram = match.arg(dendrogram)[1]
501
+    if("both" %in% dendrogram) {
502
+        ht_param$show_row_dend = TRUE
503
+        ht_param$show_column_dend = TRUE
504
+    } else if("row" %in% dendrogram) {
505
+        ht_param$show_row_dend = TRUE
506
+        ht_param$show_column_dend = FALSE
507
+    } else if("column" %in% dendrogram) {
508
+        ht_param$show_row_dend = FALSE
509
+        ht_param$show_column_dend = TRUE
510
+    } else if("none" %in% dendrogram) {
511
+        ht_param$show_row_dend = FALSE
512
+        ht_param$show_column_dend = FALSE
513
+    }
514
+
515
+    ht_param$row_dend_width = unit(4, "cm")
516
+    ht_param$column_dend_height = unit(3, "cm")
517
+
518
+    
519
+    scale = match.arg(scale)[1]
520
+    if("row" %in% scale) {
521
+        if(any(is.na(mat))) {
522
+            mat = (mat - rowMeans(mat, na.rm = TRUE))/rowSds(mat, na.rm = TRUE)
523
+        } else {
524
+            mat = t(scale(t(mat)))
525
+        }
526
+        message_wrap("Note, in 'heatmap.2()', when rows are scaled, the row dendrogram is still calculated from the original matrix (not from the scaled matrix).")
527
+    } else if("column" %in% scale) {
528
+        if(any(is.na(mat))) {
529
+            mat = t((t(mat) - colMeans(mat, na.rm = TRUE))/colSds(mat, na.rm = TRUE))
530
+        } else {
531
+            mat = scale(mat)
532
+        }
533
+        message_wrap("Note, in 'heatmap.2()', when columns are scaled, the column dendrogram is still calculated from the original matrix (not from the scaled matrix).")
534
+    }
535
+
536
+    ht_param$matrix = mat
537
+
538
+    ##### how to process `col` is directly from gplots::heatmap.2 ####
539
+    if(is.character(col) && length(col) == 1) {
540
+        col <- get(col, mode="function")
541
+    }
542
+    if(missing(breaks) || is.null(breaks) || length(breaks)<1 ) {
543
+      if( missing(col) ||  is.function(col) )
544
+        breaks <- 16
545
+      else
546
+        breaks <- length(col)+1
547
+    }
548
+
549
+    if(length(breaks)==1)
550
+    {
551
+      if(!symbreaks)
552
+        breaks <- seq( min(mat, na.rm=na.rm), max(mat,na.rm=na.rm), length=breaks)
553
+      else
554
+        {
555
+          extreme <- max(abs(mat), na.rm=TRUE)
556
+          breaks <- seq( -extreme, extreme, length=breaks )
557
+        }
558
+    }
559
+
560
+    nbr <- length(breaks)
561
+    ncol <- length(breaks)-1
562
+
563
+    if(class(col)=="function") col <- col(ncol)
564
+    #### until here ###
565
+    
566
+    n_col = ncol
567
+
568
+    if(identical(scale, "row") || identical(scale, "column")) {
569
+        lim = max(abs(mat), na.rm = TRUE)
570
+        ht_param$col = colorRamp2(seq(-lim, lim, length = n_col), col)
571
+    } else {
572
+        ht_param$col = colorRamp2(seq(min(mat, na.rm = TRUE), max(mat, na.rm = TRUE), length = n_col), col)
573
+    } 
574
+    
575
+
576
+    if(!missing(colsep)) {
577
+        warning_wrap("argument `colsep` is not supported in heatmap.2 -> Heatmap translation, skip it. Suggest to use `column_split` argument in Heatmap() which can be directly used here.")
578
+    }
579
+    if(!missing(rowsep)) {
580
+        warning_wrap("argument `rowsep` is not supported in heatmap.2 -> Heatmap translation, skip it. Suggest to use `row_split` argument in Heatmap() which can be directly used here.")
581
+    }
582
+
583
+    if(!missing(cellnote)) {
584
+        ht_param$layer_fun = function(j, i, x, y, w, h, fill) {
585
+            grid.text(pindex(cellnote, i, j), x, y, gp = gpar(cex = notecex, col = notecol))
586
+        }
587
+    }
588
+    ht_param$na_col = na.color
589
+    
590
+    if(!missing(ColSideColors)) {
591
+        ht_param$top_annotation = HeatmapAnnotation(column = ColSideColors,
592
+            col = list(column = structure(unique(ColSideColors), names = unique(ColSideColors))),
593
+            show_legend = FALSE, show_annotation_name = FALSE)
594
+    }
595
+    if(!missing(RowSideColors)) {
596
+        ht_param$left_annotation = rowAnnotation(row = RowSideColors,
597
+            col = list(row = structure(unique(RowSideColors), names = unique(RowSideColors))),
598
+            show_legend = FALSE, show_annotation_name = FALSE)
599
+    }
600
+
601
+    if(identical(ht_param$cluster_rows, FALSE)) {
602
+        if(is.null(ht_param$left_annotation)) {
603
+            ht_param$left_annotation = rowAnnotation(foo1 = anno_empty(width = unit(4, "cm"), border = FALSE))
604
+        } else {
605
+            ht_param$left_annotation = c(ht_param$left_annotation, rowAnnotation(foo1 = anno_empty(width = unit(3.5, "cm"))))
606
+        }
607
+    }
608
+
609
+    if(identical(ht_param$cluster_columns, FALSE)) {
610
+        if(is.null(ht_param$top_annotation)) {
611
+            ht_param$top_annotation = HeatmapAnnotation(foo2 = anno_empty(height = unit(3, "cm"), border = FALSE))
612
+        } else {
613
+            ht_param$top_annotation = c(ht_param$top_annotation, HeatmapAnnotation(foo2 = anno_empty(height = unit(3.5, "cm"))))
614
+        }
615
+    }
616
+
617
+    if(!is.null(labRow)) {
618
+        ht_param$row_labels = labRow
619
+    } else if(is.null(rownames(mat))) {
620
+        ht_param$row_labels = seq_len(nr)
621
+    } else {
622
+        ht_param$row_labels = rownames(mat)
623
+    }
624
+
625
+    if(!is.null(labCol)) {
626
+        ht_param$column_labels = labCol
627
+    } else if(is.null(colnames(mat))) {
628
+        ht_param$column_labels = seq_len(nc)
629
+    } else {
630
+        ht_param$column_labels = colnames(mat)
631
+    }
632
+
633
+    if(is.null(colRow)) colRow = "black"
634
+    ht_param$row_names_gp = gpar(cex = cexRow, col = colRow)
635
+    if(is.null(colCol)) colCol = "black"
636
+    ht_param$column_names_gp = gpar(cex = cexCol, col = colCol)
637
+
638
+    if(!is.null(srtRow)) {
639
+        ht_param$row_names_rot = srtRow
640
+    }
641
+    if(!is.null(srtCol)) {
642
+        ht_param$column_names_rot = srtCol
643
+    }
644
+
645
+    if(!is.null(main)) {
646
+        ht_param$column_title = main
647
+    }
648
+    if(!is.null(xlab)) {
649
+        if(is.null(ht_param$column_labels)) {
650
+            ht_param$bottom_annotation = HeatmapAnnotation(xlab = anno_block(labels = xlab, gp = gpar(col = NA)))
651
+        } else {
652
+            ht_param$bottom_annotation = HeatmapAnnotation(
653
+                colnames = anno_text(ht_param$column_labels, gp = ht_param$column_names_gp),
654
+                xlab = anno_block(labels = xlab, gp = gpar(col = NA))
655
+            )
656
+            ht_param$show_column_names = FALSE
657
+        }
658
+    }
659
+    if(!is.null(ylab)) {
660
+        if(is.null(ht_param$row_labels)) {
661
+            ht_param$right_annotation = rowAnnotation(ylab = anno_block(labels = ylab, gp = gpar(col = NA)))
662
+        } else {
663
+            ht_param$right_annotation = rowAnnotation(
664
+                rownames = anno_text(ht_param$row_labels, gp = ht_param$row_names_gp),
665
+                ylab = anno_block(labels = ylab, gp = gpar(col = NA))
666
+            )
667
+            ht_param$show_row_names = FALSE
668
+        }
669
+    }
670
+
671
+    ht_param$show_heatmap_legend = FALSE
672
+
673
+    trace = match.arg(trace)[1]
674
+    min = breaks[1]
675
+    max = breaks[length(breaks)]
676
+    rg = max - min
677
+
678
+    layer_fun = NULL
679
+    if(trace == "both") {
680
+        warning_wrap("trace = 'both' is not supported, change to trace = 'column'.")
681
+        trace = "column"
682
+    }
683
+    if(trace == "column") {
684
+        layer_fun = function(j, i, x, y, w, h, fill) {
685
+            ind_mat = restore_matrix(j, i, x, y)
686
+
687
+            ind = ind_mat[1, ]
688
+            grid.segments(x[ind], unit(0, "npc"), x[ind], unit(1, "npc"), gp = gpar(col = linecol, lty = 2))
689
+            for(ki in seq_len(ncol(ind_mat))) {
690
+                ind = ind_mat[, ki]
691
+                offset = (mat[i[ind], j[ind[1]]] - min)/(max - min)*w[ind]
692
+                pos_x = rep(x[ind] - w[ind]*0.5 + offset, each = 2)
693
+                pos_y = rep(y[ind] + h[ind]*0.5, each = 2)
694
+                pos_y[seq_along(ind) %% 2 == 0] = y[ind] - h[ind]*0.5
695
+                grid.lines(pos_x, pos_y, gp = gpar(col = tracecol))
696
+            }
697
+        }
698
+    } else if(trace == "row") {
699
+        layer_fun = function(j, i, x, y, w, h, fill) {
700
+            ind_mat = restore_matrix(j, i, x, y)
701
+
702
+            ind = ind_mat[, 1]
703
+            grid.segments(unit(0, "npc"), y[ind], unit(1, "npc"), y[ind], gp = gpar(col = linecol, lty = 2))
704
+            for(ki in seq_len(nrow(ind_mat))) {
705
+                ind = ind_mat[ki, ]
706
+                offset = (mat[i[ind[1]], j[ind]] - min)/(max - min)*h[ind]
707
+                pos_x = rep(x[ind] - w[ind]*0.5, each = 2)
708
+                pos_x[seq_along(ind) %% 2 == 0] = x[ind] + w[ind]*0.5
709
+                pos_y = rep(y[ind] - h[ind]*0.5 + offset, each = 2)
710
+                grid.lines(pos_x, pos_y, gp = gpar(col = tracecol))
711
+            }
712
+        }
713
+    }
714
+    if(!is.null(ht_param$layer_fun)) {
715
+        fun1 = ht_param$layer_fun
716
+        fun2 = layer_fun
717
+        fun3 = function(j, i, x, y, w, h, fill) {
718
+            fun1(j, i, x, y, w, h, fill)
719
+            fun2(j, i, x, y, w, h, fill)
720
+        }
721
+        layer_fun = fun3
722
+    }
723
+    ht_param$layer_fun = layer_fun
724
+
725
+
726
+    random_str = paste(sample(c(letters, LETTERS, 0:9), 8), collapse = "")
727
+    ht_param$name = paste0("heatmap.2_", random_str)
728
+
729
+    density.info = match.arg(density.info)[1]
730
+    if(is.null(key.xlab)) key.xlab = "Value"
731
+    if(is.null(key.ylab)) {
732
+        if(density.info == "histogram") key.ylab = "Count"
733
+        if(density.info == "density") key.ylab = "Density"
734
+    }
735
+
736
+    if(density.info == "none") {
737
+        post_fun = NULL
738
+    } else {
739
+        post_fun = function(ht) {
740
+            decorate_heatmap_body(paste0("heatmap.2_", random_str), {
741
+                pushViewport(viewport(unit(0, "npc"), unit(1, "npc"), width = unit(4, "cm"), height = unit(3, "cm"), just = c("right", "bottom")))
742
+
743
+                left_width = unit(1, "cm")
744
+                bottom_height = unit(1, "cm")
745
+                top_height = unit(0.5, "cm")
746
+
747
+                if(density.info == "histogram") {
748
+                    tb = hist(mat, breaks = breaks, plot = FALSE)
749
+                    x_at = pretty(range(tb$breaks), n = 3)
750
+                    y_at = pretty(range(tb$counts), n = 3)
751
+                    x_range = range(tb$breaks)
752
+                    y_range = range(tb$counts); y_range[2] = y_range[2] + (y_range[2] - y_range[1])*0.05
753
+                } else if(density.info == "density") {
754
+                    den = density(mat, na.rm = TRUE, from = min(breaks), to = max(breaks), adjust = densadj)
755
+                    den_x = den$x
756
+                    den_y = den$y
757
+                    x_range = range(breaks)
758
+                    l = den_x >= x_range[1] & den_x <= x_range[2]
759
+                    den_x = den_x[l]
760
+                    den_y = den_y[l]
761
+                    x_at = pretty(range(den_x), n = 3)
762
+                    y_at = pretty(range(den_y), n = 3)
763
+                    y_range = range(den_y); y_range[2] = y_range[2] + (y_range[2] - y_range[1])*0.05
764
+                }
765
+
766
+                x_at = x_at[x_at >= x_range[1] & x_at <= x_range[2]]
767
+                y_at = y_at[y_at >= y_range[1] & y_at <= y_range[2]]
768
+                pushViewport(viewport(x = left_width, y = bottom_height, 
769
+                    width = unit(1, "npc") - left_width - unit(2, "mm"), height = unit(1, "npc") - bottom_height- top_height,
770
+                    just = c("left", "bottom"), xscale = x_range, yscale = y_range))
771
+
772
+                x = seq(min(breaks), max(breaks), length = 101)
773
+                grid.rect(x = x[1:100], width = (x_range[2] - x_range[1])/100, default.units = "native", just = "left",
774
+                    gp = gpar(fill = ht_param$col(x + (x_range[2] - x_range[1])/100*0.5), col = NA))
775
+
776
+                if(density.info == "histogram") {
777
+                    x = rep(tb$breaks, each = 2); x = x[-c(1, length(x))]
778
+                    y = rep(tb$counts, each = 2)
779
+                } else if(density.info == "density") {
780
+                    x = den_x
781
+                    y = den_y
782
+                }
783
+                grid.lines(x, y, default.units = "native", gp = gpar(col = denscol))
784
+                if(trace == "column") {
785
+                    grid.lines(c(vline, vline), unit(c(0, 1), "npc"), default.units = "native", gp = gpar(col = linecol, lty = 2))
786
+                } else if(trace == "row") {
787
+                    grid.lines(unit(c(0, 1), "npc"), c(hline, hline), default.units = "native", gp = gpar(col = linecol, lty = 2))
788
+                }
789
+                grid.rect(gp = gpar(fill = "transparent"))
790
+                grid.xaxis(at = x_at, gp = gpar(fontsize = 8))
791
+                grid.text(key.xlab, y = unit(0, "npc") - unit(8, "mm"), gp = gpar(fontsize = 8))
792
+                grid.yaxis(at = y_at, gp = gpar(fontsize = 8))
793
+                grid.text(key.ylab, x = unit(0, "npc") - unit(8, "mm"), gp = gpar(fontsize = 8), rot = 90)
794
+                grid.text("Color Key", y = unit(1, "npc") + top_height*0.5, gp = gpar(fontface = "bold", fontsize = 10))
795
+                popViewport()
796
+
797
+                popViewport()
798
+            })
799
+        }
800
+    }
801
+    ht_param$post_fun = post_fun
802
+    
803
+    if(!missing(add.expr)) {
804
+        warning_wrap("argument `add.expr` is not supported in heatmap.2 -> Heatmap translation, skip it.")
805
+    }
806
+
807
+    if(!is.null(lmat)) {
808
+        warning_wrap("argument `lmat` is not supported in heatmap.2 -> Heatmap translation, skip it.")
809
+    }
810
+    if(!is.null(lhei)) {
811
+        warning_wrap("argument `lhei` is not supported in heatmap.2 -> Heatmap translation, skip it.")
812
+    }
813
+    if(!is.null(lwid)) {
814
+        warning_wrap("argument `lwid` is not supported in heatmap.2 -> Heatmap translation, skip it.")
815
+    }
816
+    if(!is.null(extrafun)) {
817
+        warning_wrap("argument `extrafun` is not supported in heatmap.2 -> Heatmap translation, skip it.")
818
+    }
819
+
820
+    ht_param = c(ht_param, list(...))
821
+    ht = do.call(Heatmap, ht_param)
822
+    attr(ht, "translate_from") = "heatmap"
823
+    ht
824
+}
825
+
826
+# == title
827
+# Compare heatmaps between gplots::heatmap.2() and ComplexHeatmap::heatmap()
828
+#
829
+# == param
830
+# -... The same set of arguments passed to ``gplots::heatmap.2`` and ``ComplexHeatmap::heatmap.2``.
831
+#
832
+# == details
833
+# The function plots two heatmaps, one by ``gplots::heatmap.2`` and one by ``ComplexHeatmap::heatmap.2``.
834
+# Users can see the difference between the two implementations.
835
+#
836
+# == example
837
+# mat = matrix(rnorm(100), 10)
838
+# compare_heatmap.2(mat)
839
+compare_heatmap.2 = function(...) {
840
+    p1 = gridGraphics::echoGrob(function() gplots::heatmap.2(...))
841
+    p2 = grid.grabExpr(draw(heatmap.2(...)))
842
+    grid.newpage()
843
+    pushViewport(viewport(x = 0, width = 0.5, y = 0, height = unit(1, "npc") - unit(1, "cm"), just = c("left", "bottom")))
844
+    grid.draw(p1)
845
+    popViewport()
846
+    pushViewport(viewport(x = 0, width = 0.5, y = 1, height = unit(1, "cm"), just = c("left", "top")))
847
+    grid.text("gplots::heatmap.2()")
848
+    popViewport()
849
+    pushViewport(viewport(x = 0.5, width = 0.5, y = 0, height = unit(1, "npc") - unit(1, "cm"), just = c("left", "bottom")))
850
+    grid.draw(p2)
851
+    popViewport()
852
+    pushViewport(viewport(x = 0.5, width = 0.5, y = 1, height = unit(1, "cm"), just = c("left", "top")))
853
+    grid.text("ComplexHeatmap::heatmap.2()")
854
+    popViewport()
855
+}
... ...
@@ -65,7 +65,7 @@
65 65
 # A `Heatmap-class` object.
66 66
 #
67 67
 # == seealso
68
-# `compare_pheatmap` that ompares heatmaps between ``pheatmap::pheatmap()`` and ``ComplexHeatmap::pheatmap()``.
68
+# `compare_pheatmap` that compares heatmaps between ``pheatmap::pheatmap()`` and ``ComplexHeatmap::pheatmap()``.
69 69
 pheatmap = function(mat, 
70 70
     color = colorRampPalette(rev(brewer.pal(n = 7, name = "RdYlBu")))(100), 
71 71
     kmeans_k = NA, 
... ...
@@ -452,7 +452,7 @@ pheatmap = function(mat,
452 452
     }
453 453
     ht_param = c(ht_param, list(...))
454 454
     ht = do.call(Heatmap, ht_param)
455
-    attr(ht, "pheatmap") = TRUE
455
+    attr(ht, "translate_from") = "pheatmap"
456 456
     ht
457 457
 }
458 458
 
... ...
@@ -460,10 +460,10 @@ pheatmap = function(mat,
460 460
 # Compare heatmaps between pheatmap::pheatmap() and ComplexHeatmap::pheatmap()
461 461
 #
462 462
 # == param
463
-# -... The same set of rguments passed to `pheatmap::pheatmap` and `pheatmap`.
463
+# -... The same set of arguments passed to ``pheatmap::pheatmap`` and ``ComplexHeatmap::pheatmap``.
464 464
 #
465 465
 # == details
466
-# The function plots two heatmaps, one by `pheatmap::pheatmap` and one by `pheatmap`.
466
+# The function plots two heatmaps, one by ``pheatmap::pheatmap`` and one by ``ComplexHeatmap::pheatmap``.
467 467
 # Users can see the difference between the two implementations.
468 468
 #
469 469
 # == example
... ...
@@ -15,5 +15,4 @@ method and the \code{\%v\%v} method so that above three classes can be appended
15 15
 \examples{
16 16
 # There is no example
17 17
 NULL
18
-
19 18
 }
... ...
@@ -26,5 +26,4 @@ Zuguang Gu <z.gu@dkfz.de>
26 26
 \examples{
27 27
 # There is no example
28 28
 NULL
29
-
30 29
 }
... ...
@@ -22,5 +22,4 @@ See \code{\link{AnnotationFunction}} constructor for details.
22 22
 \examples{
23 23
 # There is no example
24 24
 NULL
25
-
26 25
 }
... ...
@@ -26,5 +26,4 @@ Zuguang Gu <z.gu@dkfz.de>
26 26
 \examples{
27 27
 # There is no example
28 28
 NULL
29
-
30 29
 }
... ...
@@ -40,5 +40,4 @@ The complete reference of ComplexHeatmap package is available at \url{http://jok
40 40
 \examples{
41 41
 # There is no example
42 42
 NULL
43
-
44 43
 }
... ...
@@ -22,5 +22,4 @@ Internally used.
22 22
 \examples{
23 23
 # There is no example
24 24
 NULL
25
-
26 25
 }
... ...
@@ -30,5 +30,4 @@ Zuguang Gu <z.gu@dkfz.de>
30 30
 \examples{
31 31
 # There is no example
32 32
 NULL
33
-
34 33
 }
... ...
@@ -212,5 +212,4 @@ Zuguang Gu <z.gu@dkfz.de>
212 212
 \examples{
213 213
 # There is no example
214 214
 NULL
215
-
216 215
 }
... ...
@@ -25,5 +25,4 @@ Zuguang Gu <z.gu@dkfz.de>
25 25
 \examples{
26 26
 # There is no example
27 27
 NULL
28
-
29 28
 }
... ...
@@ -84,5 +84,4 @@ Zuguang Gu <z.gu@dkfz.de>
84 84
 \examples{
85 85
 # There is no example
86 86
 NULL
87
-
88 87
 }
... ...
@@ -27,5 +27,4 @@ Zuguang Gu <z.gu@dkfz.de>
27 27
 \examples{
28 28
 # There is no example
29 29
 NULL
30
-
31 30
 }
... ...
@@ -26,5 +26,4 @@ Zuguang Gu <z.gu@dkfz.de>
26 26
 \examples{
27 27
 # There is no example
28 28
 NULL
29
-
30 29
 }
... ...
@@ -26,5 +26,4 @@ Zuguang Gu <z.gu@dkfz.de>
26 26
 \examples{
27 27
 # There is no example
28 28
 NULL
29
-
30 29
 }
... ...
@@ -28,5 +28,4 @@ Zuguang Gu <z.gu@dkfz.de>
28 28
 \examples{
29 29
 # There is no example
30 30
 NULL
31
-
32 31
 }
... ...
@@ -40,5 +40,4 @@ Zuguang Gu <z.gu@dkfz.de>
40 40
 \examples{
41 41
 # There is no example
42 42
 NULL
43
-
44 43
 }
... ...
@@ -28,5 +28,4 @@ Zuguang Gu <z.gu@dkfz.de>
28 28
 \examples{
29 29
 # There is no example
30 30
 NULL
31
-
32 31
 }
... ...
@@ -28,5 +28,4 @@ Zuguang Gu <z.gu@dkfz.de>
28 28
 \examples{
29 29
 # There is no example
30 30
 NULL
31
-
32 31
 }
... ...
@@ -28,5 +28,4 @@ Zuguang Gu <z.gu@dkfz.de>
28 28
 \examples{
29 29
 # There is no example
30 30
 NULL
31
-
32 31
 }
... ...
@@ -1,6 +1,5 @@
1 1
 \name{adjust_heatmap_list-HeatmapList-method}
2 2
 \alias{adjust_heatmap_list,HeatmapList-method}
3
-\alias{adjust_heatmap_list}
4 3
 \title{
5 4
 Adjust Heatmap List
6 5
 }
... ...
@@ -24,8 +23,8 @@ This function is only for internal use.
24 23
 \author{
25 24
 Zuguang Gu <z.gu@dkfz.de>
26 25
 }
26
+\alias{adjust_heatmap_list}
27 27
 \examples{
28 28
 # There is no example
29 29
 NULL
30
-
31 30
 }
... ...
@@ -20,5 +20,4 @@ This function is the same as \code{\link{anno_zoom}}. It links subsets of rows o
20 20
 \examples{
21 21
 # There is no example
22 22
 NULL
23
-
24 23
 }
... ...
@@ -35,5 +35,4 @@ Zuguang Gu <z.gu@dkfz.de>
35 35
 \examples{
36 36
 # There is no example
37 37
 NULL
38
-
39 38
 }
... ...
@@ -1,6 +1,5 @@
1 1
 \name{annotation_legend_size-HeatmapList-method}
2 2
 \alias{annotation_legend_size,HeatmapList-method}
3
-\alias{annotation_legend_size}
4 3
 \title{
5 4
 Size of the Annotation Legends
6 5
 }
... ...
@@ -28,8 +27,8 @@ A \code{\link[grid]{unit}} object.
28 27
 \author{
29 28
 Zuguang Gu <z.gu@dkfz.de>
30 29
 }
30
+\alias{annotation_legend_size}
31 31
 \examples{
32 32
 # There is no example
33 33
 NULL
34
-
35 34
 }
... ...
@@ -1,6 +1,5 @@
1 1
 \name{attach_annotation-Heatmap-method}
2 2
 \alias{attach_annotation,Heatmap-method}
3
-\alias{attach_annotation}
4 3
 \title{
5 4
 Attach heatmap annotations to the heatmap
6 5
 }
... ...
@@ -29,3 +28,4 @@ ha2 = HeatmapAnnotation(bar = letters[1:10])
29 28
 ht = attach_annotation(ht, ha2)
30 29
 ht
31 30
 }
31
+\alias{attach_annotation}
... ...
@@ -23,5 +23,4 @@ A \code{\link[GenomicRanges:GRanges-class]{GRanges}} object of the genomic bins.
23 23
 \examples{
24 24
 # There is no example
25 25
 NULL
26
-
27 26
 }
... ...
@@ -1,6 +1,5 @@
1 1
 \name{color_mapping_legend-ColorMapping-method}
2 2
 \alias{color_mapping_legend,ColorMapping-method}
3
-\alias{color_mapping_legend}
4 3
 \title{
5 4
 Draw Legend Based on Color Mapping
6 5
 }
... ...
@@ -70,8 +69,8 @@ A \code{\link{Legends-class}} object.
70 69
 \author{
71 70
 Zuguang Gu <z.gu@dkfz.de>
72 71
 }
72
+\alias{color_mapping_legend}
73 73
 \examples{
74 74
 # There is no example
75 75
 NULL
76
-
77 76
 }
... ...
@@ -29,5 +29,4 @@ Zuguang Gu <z.gu@dkfz.de>
29 29
 \examples{
30 30
 # There is no example
31 31
 NULL
32
-
33 32
 }
34 33
new file mode 100644
... ...
@@ -0,0 +1,24 @@
1
+\name{compare_heatmap.2}
2
+\alias{compare_heatmap.2}
3
+\title{
4
+Compare heatmaps between gplots::heatmap.2() and ComplexHeatmap::heatmap()
5
+}
6
+\description{
7
+Compare heatmaps between gplots::heatmap.2() and ComplexHeatmap::heatmap()
8
+}
9
+\usage{
10
+compare_heatmap.2(...)
11
+}
12
+\arguments{
13
+
14
+  \item{...}{The same set of arguments passed to \code{gplots::heatmap.2} and \code{ComplexHeatmap::heatmap.2}.}
15
+
16
+}
17
+\details{
18
+The function plots two heatmaps, one by \code{gplots::heatmap.2} and one by \code{ComplexHeatmap::heatmap.2}.
19
+Users can see the difference between the two implementations.
20
+}
21
+\examples{
22
+mat = matrix(rnorm(100), 10)
23
+compare_heatmap.2(mat)
24
+}
0 25
new file mode 100644
... ...
@@ -0,0 +1,24 @@
1
+\name{compare_heatmap}
2
+\alias{compare_heatmap}
3
+\title{
4
+Compare heatmaps between stats::heatmap() and ComplexHeatmap::heatmap()
5
+}
6
+\description{
7
+Compare heatmaps between stats::heatmap() and ComplexHeatmap::heatmap()
8
+}
9
+\usage{
10
+compare_heatmap(...)
11
+}
12
+\arguments{
13
+
14
+  \item{...}{The same set of arguments passed to \code{stats::heatmap} and \code{ComplexHeatmap::heatmap}.}
15
+
16
+}
17
+\details{
18
+The function plots two heatmaps, one by \code{stats::heatmap} and one by \code{ComplexHeatmap::heatmap}.
19
+Users can see the difference between the two implementations.
20
+}
21
+\examples{
22
+mat = matrix(rnorm(100), 10)
23
+compare_heatmap(mat)
24
+}
... ...
@@ -11,11 +11,11 @@ compare_pheatmap(...)
11 11
 }
12 12
 \arguments{
13 13
 
14
-  \item{...}{The same set of rguments passed to \code{\link[pheatmap]{pheatmap}} and \code{\link{pheatmap}}.}
14
+  \item{...}{The same set of arguments passed to \code{pheatmap::pheatmap} and \code{ComplexHeatmap::pheatmap}.}
15 15
 
16 16
 }
17 17
 \details{
18
-The function plots two heatmaps, one by \code{\link[pheatmap]{pheatmap}} and one by \code{\link{pheatmap}}.
18
+The function plots two heatmaps, one by \code{pheatmap::pheatmap} and one by \code{ComplexHeatmap::pheatmap}.
19 19
 Users can see the difference between the two implementations.
20 20
 }
21 21
 \examples{
... ...
@@ -20,5 +20,4 @@ If there is no complement set, it returns zero.
20 20
 \examples{
21 21
 # There is no example
22 22
 NULL
23
-
24 23
 }
... ...
@@ -31,5 +31,4 @@ Zuguang Gu <z.gu@dkfz.de>
31 31
 \examples{
32 32
 # There is no example
33 33
 NULL
34
-
35 34
 }
... ...
@@ -24,5 +24,4 @@ Zuguang Gu <z.gu@dkfz.de>
24 24
 \examples{
25 25
 # There is no example
26 26
 NULL
27
-
28 27
 }
... ...
@@ -30,5 +30,4 @@ Zuguang Gu <z.gu@dkfz.de>
30 30
 \examples{
31 31
 # There is no example
32 32
 NULL
33
-
34 33
 }
... ...
@@ -27,5 +27,4 @@ Zuguang Gu <z.gu@dkfz.de>
27 27
 \examples{
28 28
 # There is no example
29 29
 NULL
30
-
31 30
 }
... ...
@@ -26,5 +26,4 @@ The environment is at \code{object@var_env}.
26 26
 \examples{
27 27
 # There is no example
28 28
 NULL
29
-
30 29
 }
... ...
@@ -21,5 +21,4 @@ it calls \code{\link{copy_all,AnnotationFunction-method}} to hard copy the varia
21 21
 \examples{
22 22
 # There is no example
23 23
 NULL
24
-
25 24
 }
... ...
@@ -27,5 +27,4 @@ Zuguang Gu <z.gu@dkfz.de>
27 27
 \examples{
28 28
 # There is no example
29 29
 NULL
30
-
31 30
 }
... ...
@@ -27,5 +27,4 @@ Zuguang Gu <z.gu@dkfz.de>
27 27
 \examples{
28 28
 # There is no example
29 29
 NULL
30
-
31 30
 }
... ...
@@ -27,5 +27,4 @@ Zuguang Gu <z.gu@dkfz.de>
27 27
 \examples{
28 28
 # There is no example
29 29
 NULL
30
-
31 30
 }
... ...
@@ -27,5 +27,4 @@ Zuguang Gu <z.gu@dkfz.de>
27 27
 \examples{
28 28
 # There is no example
29 29
 NULL
30
-
31 30
 }
... ...
@@ -27,5 +27,4 @@ Zuguang Gu <z.gu@dkfz.de>
27 27
 \examples{
28 28
 # There is no example
29 29
 NULL
30
-
31 30
 }
... ...
@@ -27,5 +27,4 @@ Zuguang Gu <z.gu@dkfz.de>
27 27
 \examples{
28 28
 # There is no example
29 29
 NULL
30
-
31 30
 }
... ...
@@ -20,5 +20,4 @@ It recognizes following separators: \code{;:,|}.
20 20
 \examples{
21 21
 # There is no example
22 22
 NULL
23
-
24 23
 }
... ...
@@ -17,5 +17,4 @@ dend_heights(x)
17 17
 \examples{
18 18
 # There is no example
19 19
 NULL
20
-
21 20
 }
... ...
@@ -28,5 +28,4 @@ A \code{\link{grob}} object which is contructed by \code{\link[grid:grid.segment
28 28
 \examples{
29 29
 # There is no example
30 30
 NULL
31
-
32 31
 }
... ...
@@ -17,5 +17,4 @@ Dimension of the Heatmap
17 17
 \examples{
18 18
 # There is no example
19 19
 NULL
20
-
21 20
 }
... ...
@@ -28,5 +28,4 @@ which is generally for testing purpose.
28 28
 \examples{
29 29
 # There is no example
30 30
 NULL
31
-
32 31
 }
... ...
@@ -33,5 +33,4 @@ Zuguang Gu <z.gu@dkfz.de>
33 33
 \examples{
34 34
 # There is no example
35 35
 NULL
36
-
37 36
 }
... ...
@@ -30,5 +30,4 @@ Zuguang Gu <z.gu@dkfz.de>
30 30
 \examples{
31 31
 # There is no example
32 32
 NULL
33
-
34 33
 }
... ...
@@ -202,5 +202,4 @@ Zuguang Gu <z.gu@dkfz.de>
202 202
 \examples{
203 203
 # There is no example
204 204
 NULL
205
-
206 205
 }
... ...