Browse code

version bump

Zuguang Gu authored on 26/03/2019 14:25:36
Showing 19 changed files

... ...
@@ -1,7 +1,7 @@
1 1
 Package: ComplexHeatmap
2 2
 Type: Package
3 3
 Title: Make Complex Heatmaps
4
-Version: 1.99.6
4
+Version: 1.99.7
5 5
 Date: 2019-03-15
6 6
 Author: Zuguang Gu
7 7
 Maintainer: Zuguang Gu <z.gu@dkfz.de>
... ...
@@ -1,11 +1,13 @@
1 1
 CHANGES in VERSION 1.99.6
2 2
 
3
-* adjust the size of heatmap annotations and add testing scripts
4
-* run multiple times k-means to get a consensus partition
5
-* `show_heatmap_legend` is set to FALSE if `rect_gp = gpar(type = "none")`
6
-* add `restore_matrix()`
7
-* add `row_names_centered`/`column_names_centered` arguments to `Heatmap()`
8
-* `gp` in `anno_text()` supports `fill` and `border`
3
+* adjust the size of heatmap annotations and add testing scripts.
4
+* run multiple times k-means to get a consensus partition.
5
+* `show_heatmap_legend` is set to FALSE if `rect_gp = gpar(type = "none")`.
6
+* add `restore_matrix()`.
7
+* add `row_names_centered`/`column_names_centered` arguments to `Heatmap()`.
8
+* `gp` in `anno_text()` supports `fill` and `border`.
9
+* `Legend` adds boxplot-style legend.
10
+* adjustment according to annotation extension is improved.
9 11
 
10 12
 ========================
11 13
 
... ...
@@ -391,7 +391,7 @@ setMethod(f = "show",
391 391
 			cat("  subsetable variable:", paste(var_subsetable, collapse = ", "), "\n")
392 392
 		}
393 393
 	}
394
-	cat("  this object is ", ifelse(object@subsetable, "\b", "not "), "subsetable\n", sep = "")
394
+	cat("  this object is ", ifelse(object@subsetable, "", "not "), "subsetable\n", sep = "")
395 395
 	dirt = c("bottom", "left", "top", "right")
396 396
 	for(i in 1:4) {
397 397
 		if(!identical(unit(0, "mm"), object@extended[i])) {
... ...
@@ -354,9 +354,17 @@ Heatmap = function(matrix, col, name,
354 354
         }
355 355
     }
356 356
 
357
-    if(ncol(matrix) == 0) {
358
-        show_heatmap_legend = FALSE
359
-        .Object@heatmap_param$show_heatmap_legend = FALSE
357
+    # if(ncol(matrix) == 0 || nrow(matrix) == 0) {
358
+    #     show_heatmap_legend = FALSE
359
+    #     .Object@heatmap_param$show_heatmap_legend = FALSE
360
+    # }
361
+    if(ncol(matrix) == 0 && (!is.null(left_annotation) || !is.null(right_annotation))) {
362
+        message_wrap("If you have row annotations for a zeor-column matrix, please directly use in form of `rowAnnotation(...) + NULL`")
363
+        return(invisible(NULL))
364
+    }
365
+    if(nrow(matrix) == 0 && (!is.null(top_annotation) || !is.null(bottom_annotation))) {
366
+        message_wrap("If you have column annotations for a zero-row matrix, please directly use in form of `HeatmapAnnotation(...) %v% NULL`")
367
+        return(invisible(NULL))
360 368
     }
361 369
     if(identical(rect_gp$type, "none")) {
362 370
         show_heatmap_legend = FALSE
... ...
@@ -1430,6 +1438,10 @@ make_cluster = function(object, which = c("row", "column")) {
1430 1438
         }
1431 1439
     }
1432 1440
     slot(object, paste0(which, "_title")) = title
1441
+    # check whether height of the dendrogram is zero
1442
+    if(all(sapply(dend_list, dend_heights) == 0)) {
1443
+        slot(object, paste0(which, "_dend_param"))$show = FALSE
1444
+    }
1433 1445
     return(object)
1434 1446
 
1435 1447
 }
... ...
@@ -52,7 +52,7 @@ HeatmapAnnotation = setClass("HeatmapAnnotation",
52 52
 #      See `SingleAnnotation` for how to set colors.
53 53
 # -na_col Color for ``NA`` values in simple annotations.
54 54
 # -annotation_legend_param A list which contains parameters for annotation legends. See `color_mapping_legend,ColorMapping-method` for all possible options.
55
-# -show_legend Whether show annotation legends. The value can be one single value or a vector which corresponds to simple annotations.
55
+# -show_legend Whether show annotation legends. The value can be one single value or a vector.
56 56
 # -which Are these row annotations or column annotations?
57 57
 # -gp Graphic parameters for simple annotations (with ``fill`` parameter ignored).
58 58
 # -border border of single annotations.
... ...
@@ -215,6 +215,10 @@ HeatmapAnnotation = function(...,
215 215
     if(length(show_legend) == 1) {
216 216
 		show_legend = recycle_param(show_legend, simple_anno_name, TRUE)
217 217
 	}
218
+	# check length of show_legend
219
+	if(length(show_legend) == length(anno_value_list) && !all(l_simple_anno)) {
220
+		show_legend = show_legend[l_simple_anno]
221
+	}
218 222
 
219 223
 	###### normalize `heatmap_legend_param` #######
220 224
 	if(length(annotation_legend_param) == 0) {
... ...
@@ -206,6 +206,7 @@ setMethod(f = "add_heatmap",
206 206
 # -km = this modifies ``km`` of the main heatmap
207 207
 # -split this modifies ``split`` of the main heatmap
208 208
 # -row_km this modifies ``row_km`` of the main heatmap
209
+# -row_km_repeats this modifies ``row_km_repeats`` of the main heatmap
209 210
 # -row_split this modifies ``row_split`` of the main heatmap
210 211
 # -height this modifies ``height`` of the main heatmap
211 212
 # -heatmap_height this modifies ``heatmap_height`` of the main heatmap
... ...
@@ -219,6 +220,7 @@ setMethod(f = "add_heatmap",
219 220
 # -column_dend_gp this modifies ``column_dend_gp`` of the main heatmap
220 221
 # -column_order this modifies ``column_order`` of the main heatmap
221 222
 # -column_km this modifies ``column_km`` of the main heatmap
223
+# -column_km_repeats this modifies ``column_km_repeats`` of the main heatmap
222 224
 # -column_split this modifies ``column_split`` of the main heatmap
223 225
 # -width this modifies ``width`` of the main heatmap
224 226
 # -heatmap_width this modifies ``heatmap_width`` of the main heatmap
... ...
@@ -298,6 +300,7 @@ setMethod(f = "draw",
298 300
     km = NULL,
299 301
     split = NULL,
300 302
     row_km = km,
303
+    row_km_repeats = NULL,
301 304
     row_split = split,
302 305
     height = NULL,
303 306
     heatmap_height = NULL,
... ...
@@ -312,6 +315,7 @@ setMethod(f = "draw",
312 315
     column_dend_gp = NULL,
313 316
     column_order = NULL,
314 317
     column_km = NULL,
318
+    column_km_repeats = NULL,
315 319
     column_split = NULL,
316 320
     width = NULL,
317 321
     heatmap_width = NULL,
... ...
@@ -465,6 +469,7 @@ setMethod(f = "draw",
465 469
         row_dend_gp = row_dend_gp,
466 470
         row_order = row_order,
467 471
         row_km = row_km,
472
+        row_km_repeats = row_km_repeats,
468 473
         row_split = row_split,
469 474
         height = height,
470 475
         heatmap_height = heatmap_height,
... ...
@@ -479,6 +484,7 @@ setMethod(f = "draw",
479 484
         column_dend_gp = column_dend_gp,
480 485
         column_order = column_order,
481 486
         column_km = column_km,
487
+        column_km_repeats = column_km_repeats,
482 488
         column_split = column_split,
483 489
         width = width,
484 490
         heatmap_width = heatmap_width
... ...
@@ -514,7 +520,7 @@ setMethod(f = "draw",
514 520
     ht_graphic_fun_list = object@layout$graphic_fun_list
515 521
 
516 522
     for(j in seq_len(nrow(ht_layout_index))) {
517
-        pushViewport(viewport(layout.pos.row = ht_layout_index[j, 1], layout.pos.col = ht_layout_index[j, 2]))
523
+        pushViewport(viewport(name = paste0("global-", rownames(ht_layout_index)[j]), layout.pos.row = ht_layout_index[j, 1], layout.pos.col = ht_layout_index[j, 2]))
518 524
         ht_graphic_fun_list[[j]](object)
519 525
         upViewport()
520 526
     }
... ...
@@ -50,6 +50,7 @@ setMethod(f = "adjust_heatmap_list",
50 50
         }
51 51
 
52 52
         # since each heatmap actually has nine rows, calculate the maximum height of corresponding rows in all heatmap 
53
+        max_title_component_width = unit(c(0, 0), "mm")
53 54
         max_title_component_height = unit.c(
54 55
             max(do.call("unit.c", lapply(object@ht_list[ht_index], function(ht) component_height(ht, "column_title_top")))),
55 56
             max(do.call("unit.c", lapply(object@ht_list[ht_index], function(ht) component_height(ht, "column_title_bottom"))))
... ...
@@ -191,6 +192,7 @@ setMethod(f = "adjust_heatmap_list",
191 192
             object@layout$row_anno_max_bottom_extended = row_anno_max_bottom_extended
192 193
             object@layout$max_bottom_component_height = max_bottom_component_height
193 194
             object@layout$max_title_component_height = max_title_component_height
195
+            object@layout$max_title_component_width = max_title_component_width
194 196
 
195 197
             ## left and right
196 198
             column_anno_max_left_extended = unit(0, "mm")
... ...
@@ -251,6 +253,7 @@ setMethod(f = "adjust_heatmap_list",
251 253
             }
252 254
         }
253 255
 
256
+        max_title_component_height = unit(c(0, 0), "mm")
254 257
         max_title_component_width = unit.c(
255 258
             max(do.call("unit.c", lapply(object@ht_list[ht_index], function(ht) component_width(ht, "row_title_left")))),
256 259
             max(do.call("unit.c", lapply(object@ht_list[ht_index], function(ht) component_width(ht, "row_title_right"))))
... ...
@@ -392,6 +395,7 @@ setMethod(f = "adjust_heatmap_list",
392 395
             object@layout$column_anno_max_right_extended = column_anno_max_right_extended
393 396
             object@layout$max_right_component_width = max_right_component_width
394 397
             object@layout$max_title_component_width = max_title_component_width
398
+            object@layout$max_title_component_height = max_title_component_height
395 399
 
396 400
             ## top and bottom
397 401
             row_anno_max_top_extended = unit(0, "mm")
... ...
@@ -399,6 +403,7 @@ setMethod(f = "adjust_heatmap_list",
399 403
             if(inherits(object@ht_list[[1]], "Heatmap")) {
400 404
                 ht_first = object@ht_list[[1]]
401 405
                 max_top_component_height = sum(component_height(ht_first, c("column_names_top", "column_dend_top", "column_anno_top", "column_title_top")))
406
+
402 407
                 u = unit(0, "mm")
403 408
                 if(!is.null(ht_first@left_annotation)) {
404 409
                     u = unit.c(u, ht_first@left_annotation@extended[3])
... ...
@@ -499,20 +504,22 @@ setMethod(f = "adjust_heatmap_list",
499 504
             }
500 505
         }
501 506
     }
507
+
502 508
     if(is.null(adjust_annotation_extension)) adjust_annotation_extension = TRUE
503 509
     if(adjust_annotation_extension) {
504
-        if(object@layout$row_anno_max_bottom_extended[[1]] > object@layout$max_bottom_component_height[[1]]) {
505
-            padding[1] = object@layout$row_anno_max_bottom_extended - object@layout$max_bottom_component_height
510
+        # note e.g. max_*_component_height does not include the height of titles
511
+        if(object@layout$row_anno_max_bottom_extended[[1]] > object@layout$max_bottom_component_height[[1]]+ object@layout$max_title_component_height[[2]]) {
512
+            padding[1] = object@layout$row_anno_max_bottom_extended - object@layout$max_bottom_component_height - object@layout$max_title_component_height[2]
506 513
         }
507
-        if(object@layout$column_anno_max_left_extended[[1]] > object@layout$max_left_component_width[[1]]) {
508
-            padding[2] = object@layout$column_anno_max_left_extended - object@layout$max_left_component_width + GLOBAL_PADDING[2]
514
+        if(object@layout$column_anno_max_left_extended[[1]] > object@layout$max_left_component_width[[1]] + object@layout$max_title_component_width[[1]]) {
515
+            padding[2] = object@layout$column_anno_max_left_extended - object@layout$max_left_component_width - object@layout$max_title_component_width[1]
509 516
         }
510 517
             
511
-        if(object@layout$row_anno_max_top_extended[[1]] > object@layout$max_top_component_height[[1]]) {
512
-            padding[3] = object@layout$row_anno_max_top_extended - object@layout$max_top_component_height + GLOBAL_PADDING[3]
518
+        if(object@layout$row_anno_max_top_extended[[1]] > object@layout$max_top_component_height[[1]] + object@layout$max_title_component_height[[1]]) {
519
+            padding[3] = object@layout$row_anno_max_top_extended - object@layout$max_top_component_height - object@layout$max_title_component_height[1]
513 520
         }
514
-        if(object@layout$column_anno_max_right_extended[[1]] > object@layout$max_right_component_width[[1]]) {
515
-            padding[4] = object@layout$column_anno_max_right_extended - object@layout$max_right_component_width + GLOBAL_PADDING[4]
521
+        if(object@layout$column_anno_max_right_extended[[1]] > object@layout$max_right_component_width[[1]] + object@layout$max_title_component_width[[2]]) {
522
+            padding[4] = object@layout$column_anno_max_right_extended - object@layout$max_right_component_width - object@layout$max_title_component_width[2]
516 523
         }
517 524
     }
518 525
     object@layout$heatmap_list_padding = padding
... ...
@@ -35,6 +35,7 @@
35 35
 # -row_dend_gp Overwrite the corresponding setting in the main heatmap.
36 36
 # -row_order Overwrite the corresponding setting in the main heatmap.
37 37
 # -row_km Overwrite the corresponding setting in the main heatmap.
38
+# -row_km_repeats Overwrite the corresponding setting in the main heatmap.
38 39
 # -row_split Overwrite the corresponding setting in the main heatmap.
39 40
 # -height Overwrite the corresponding setting in the main heatmap.
40 41
 # -heatmap_height Overwrite the corresponding setting in the main heatmap.
... ...
@@ -48,6 +49,7 @@
48 49
 # -column_dend_gp Overwrite the corresponding setting in the main heatmap.
49 50
 # -column_order Overwrite the corresponding setting in the main heatmap.
50 51
 # -column_km Overwrite the corresponding setting in the main heatmap.
52
+# -column_km_repeats Overwrite the corresponding setting in the main heatmap.
51 53
 # -column_split Overwrite the corresponding setting in the main heatmap.
52 54
 # -width Overwrite the corresponding setting in the main heatmap.
53 55
 # -heatmap_width Overwrite the corresponding setting in the main heatmap.
... ...
@@ -104,6 +106,7 @@ setMethod(f = "make_layout",
104 106
     row_dend_gp = NULL,
105 107
     row_order = NULL,
106 108
     row_km = NULL,
109
+    row_km_repeats = NULL,
107 110
     row_split = NULL,
108 111
     height = NULL,
109 112
     heatmap_height = NULL,
... ...
@@ -118,6 +121,7 @@ setMethod(f = "make_layout",
118 121
     column_dend_gp = NULL,
119 122
     column_order = NULL,
120 123
     column_km = NULL,
124
+    column_km_repeats = NULL,
121 125
     column_split = NULL,
122 126
     width = NULL,
123 127
     heatmap_width = NULL) {
... ...
@@ -235,6 +239,10 @@ setMethod(f = "make_layout",
235 239
             object@ht_list[[i_main]]@matrix_param$row_km = row_km
236 240
             if(verbose) qqcat("set row_km to main heatmap\n")
237 241
         }
242
+        if(!is.null(row_km_repeats)) {
243
+            object@ht_list[[i_main]]@matrix_param$row_km_repeats = row_km_repeats
244
+            if(verbose) qqcat("set row_km_repeats to main heatmap\n")
245
+        }
238 246
 
239 247
         if(!is.null(row_gap)) {
240 248
             object@ht_list[[i_main]]@matrix_param$row_gap = row_gap
... ...
@@ -372,6 +380,10 @@ setMethod(f = "make_layout",
372 380
             object@ht_list[[i_main]]@matrix_param$column_km = column_km
373 381
             if(verbose) qqcat("set column_km to main heatmap\n")
374 382
         }
383
+        if(!is.null(column_km_repeats)) {
384
+            object@ht_list[[i_main]]@matrix_param$column_km_repeats = column_km_repeats
385
+            if(verbose) qqcat("set column_km_repeats to main heatmap\n")
386
+        }
375 387
 
376 388
         if(!is.null(column_gap)) {
377 389
             object@ht_list[[i_main]]@matrix_param$column_gap = column_gap
... ...
@@ -848,6 +860,16 @@ setMethod(f = "make_layout",
848 860
             }
849 861
         }
850 862
     }
863
+    if(length(heatmap_legend_list) != 0) {
864
+        if(inherits(heatmap_legend_list, c("Legends", "grob"))) {
865
+            heatmap_legend_list = list(heatmap_legend_list)
866
+        }
867
+    }
868
+    if(length(annotation_legend_list) != 0) {
869
+        if(inherits(annotation_legend_list, c("Legends", "grob"))) {
870
+            annotation_legend_list = list(annotation_legend_list)
871
+        }
872
+    }
851 873
     if(merge_legends) {
852 874
         heatmap_legend_list = c(heatmap_legend_list, annotation_legend_list)
853 875
     }
... ...
@@ -60,7 +60,7 @@ Legends = function(...) {
60 60
 # -labels_rot Text rotation for labels. It should only be used for horizontal continuous legend.
61 61
 # -border Color of legend grid borders. It also works for the ticks in the continuous legend.
62 62
 # -background Background colors for the grids. It is used when points and lines are the legend graphics.
63
-# -type Type of legends. The value can be one of ``grid``, ``points`` and ``lines``.
63
+# -type Type of legends. The value can be one of ``grid``, ``points``, ``lines`` and ``boxplot``.
64 64
 # -legend_gp Graphic parameters for the legend grids. You should control the filled color of the legend grids by ``gpar(fill = ...)``.
65 65
 # -pch Type of points if points are used as legend. Note you can use single-letter as pch, e.g. ``pch = 'A'``.
66 66
 #      There are three additional integers that are valid for ``pch``: 26 and 27 for single diagonal lines and 28 for double diagonal lines.
... ...
@@ -425,6 +425,18 @@ discrete_legend_body = function(at, labels = at, nrow = NULL, ncol = 1, by_row =
425 425
 					         gp = subset_gp(legend_gp, index))
426 426
 			))
427 427
 		}
428
+		if(any(c("boxplot", "box") %in% type)) {
429
+			gl = c(gl, list(
430
+				segmentsGrob(x0 = grid_x, y0 = grid_y - grid_height*0.45, 
431
+					         x1 = grid_x, y1 = grid_y + grid_height*0.45,
432
+					         gp = subset_gp(legend_gp, index)),
433
+				rectGrob(x = grid_x, y = grid_y, width = grid_width*0.9, height = grid_height*0.5,
434
+					     gp = subset_gp(legend_gp, index)),
435
+				segmentsGrob(x0 = grid_x - grid_width*0.45, y0 = grid_y, 
436
+					         x1 = grid_x + grid_width*0.45, y1 = grid_y,
437
+					         gp = subset_gp(legend_gp, index))
438
+			))
439
+		}
428 440
 	}
429 441
 
430 442
 	class(gl) = "gList"
... ...
@@ -742,6 +754,8 @@ horizontal_continuous_legend_body = function(at, labels = at, col_fun,
742 754
 # == param
743 755
 # -... A list of objects returned by `Legend`.
744 756
 # -gap Gap between two neighbouring legends. The value is a `grid::unit` object with length of one.
757
+#      It is the same as ``row_gap`` if the direction if vertial and the same as ``column_gap`` if
758
+#      the direction is horizontal.
745 759
 # -row_gap Horizontal gaps between legends.
746 760
 # -column_gap Vertical gaps between legends.
747 761
 # -direction The direction to arrange legends.
... ...
@@ -765,7 +779,7 @@ horizontal_continuous_legend_body = function(at, labels = at, col_fun,
765 779
 # draw(pd, test = "two legends")
766 780
 # pd = packLegend(lgd1, lgd2, direction = "horizontal")
767 781
 # draw(pd, test = "two legends packed horizontally")
768
-packLegend = function(...,gap = unit(2, "mm"), row_gap = unit(2, "mm"), column_gap = unit(2, "mm"),
782
+packLegend = function(..., gap = unit(2, "mm"), row_gap = unit(2, "mm"), column_gap = unit(2, "mm"),
769 783
 	direction = c("vertical", "horizontal"),
770 784
 	max_width = NULL, max_height = NULL, list = NULL) {
771 785
 
... ...
@@ -94,8 +94,8 @@ oncoPrint = function(mat,
94 94
 	if("axis_gp" %in% arg_names) {
95 95
 		stop_wrap("`axis_gp` is removed from the arguments. Please set `axis_param(gp = ...)` in `anno_oncoprint_barplot()` when you define the `top_annotation` or `right_annotation`.")
96 96
 	}
97
-	if("show_row_names" %in% arg_names) {
98
-		stop_wrap("`show_row_names` is removed from the arguments. Please directly remove `anno_oncoprint_barplot()` in `right_annotation` to remove barplots on the left of the oncoPrint.")
97
+	if("show_row_barplot" %in% arg_names) {
98
+		stop_wrap("`show_row_barplot` is removed from the arguments. Please directly remove `anno_oncoprint_barplot()` in `right_annotation` to remove barplots on the right of the oncoPrint.")
99 99
 	}
100 100
 	if("row_barplot_width" %in% arg_names) {
101 101
 		stop_wrap("`row_barplot_width` is removed from the arguments. Please directly set `width` in `anno_oncoprint_barplot()` in `right_annotation`.")
... ...
@@ -110,6 +110,10 @@ oncoPrint = function(mat,
110 110
 		stop_wrap("`barplot_ignore` is removed from the arguments. The subset of alterations now can be controlled in `anno_oncoprint_barplot()`.")
111 111
 	}
112 112
 
113
+	if(inherits(col, "function")) {
114
+		stop_wrap("`col` should be specified as a vector.")
115
+	}
116
+
113 117
 	# convert mat to mat_list
114 118
 	if(inherits(mat, "data.frame")) {
115 119
 		mat = as.matrix(mat)
... ...
@@ -152,8 +156,7 @@ oncoPrint = function(mat,
152 156
 		stop_wrap("Incorrect type of 'mat'")
153 157
 	}
154 158
 
155
-	cat("All mutation types:", paste(all_type, collapse = ", "), "\n")
156
-
159
+	message_wrap(paste0("All mutation types: ", paste(all_type, collapse = ", ")))
157 160
 
158 161
 	# type as the third dimension
159 162
 	arr = array(FALSE, dim = c(dim(mat_list[[1]]), length(all_type)), dimnames = c(dimnames(mat_list[[1]]), list(all_type)))
... ...
@@ -573,7 +576,7 @@ anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"),
573 576
 			axis = axis, axis_param = axis_param)@fun
574 577
 		fun(index, k, n)
575 578
 	}
576
-	
579
+
577 580
 	if(which == "row") {
578 581
 		fun = row_fun
579 582
 	} else if(which == "column") {
... ...
@@ -592,8 +595,19 @@ anno_oncoprint_barplot = function(type = NULL, which = c("column", "row"),
592 595
 	anno@subsetable = TRUE
593 596
 	anno@show_name = FALSE
594 597
 
598
+	if(exists("arr", envir = parent.frame(1))) {
599
+		arr = get("arr", envir = parent.frame(1))
600
+		if(which == "row") {
601
+			data_scale = c(0, max(apply(arr, 1, sum)))
602
+		} else {
603
+			data_scale = c(0, max(apply(arr, 2, sum)))
604
+		}
605
+	} else {
606
+		data_scale = c(0, 100)
607
+	}
608
+
595 609
 	axis_param = validate_axis_param(axis_param, which)
596
-	axis_grob = if(axis) construct_axis_grob(axis_param, which, c(0, 100)) else NULL
610
+	axis_grob = if(axis) construct_axis_grob(axis_param, which, data_scale) else NULL
597 611
 	anno@extended = update_anno_extend(anno, axis_grob, axis_param)
598 612
 
599 613
 	return(anno) 
... ...
@@ -56,7 +56,7 @@ default_col = function(x, main_matrix = FALSE) {
56 56
         x = as.vector(x)
57 57
     }
58 58
 
59
-    if(length(unique(x)) == 1) {
59
+    if(length(unique(as.vector(x))) == 1) {
60 60
         x = as.character(x)
61 61
     }
62 62
 
... ...
@@ -11,18 +11,6 @@ If you use it in published research, please cite:
11 11
 Gu, Z. Complex heatmaps reveal patterns and correlations in multidimensional 
12 12
   genomic data. Bioinformatics 2016.
13 13
 ========================================
14
-
15
-This version is a major update of the package. The major new features are:
16
-
17
-1. Support splitting heatmaps by columns.
18
-2. Support concatenating heatmaps/annotations vertically.
19
-3. Provide more types of heatmap annotations.
20
-4. Support UpSet plot.
21
-
22
-Note this version is not 100% compatible with the older versions (< 1.99.0).
23
-Please check by `vignette('difference_to_old_versions', package = 'ComplexHeatmap')`.
24
-
25
-Above messages will be removed in the future.
26 14
 ")	
27 15
 
28 16
     packageStartupMessage(msg)
... ...
@@ -37,7 +37,7 @@ HeatmapAnnotation(...,
37 37
   \item{col}{A list of colors which contain color mapping to \code{df} or simple annotations defined in \code{...}.  See \code{\link{SingleAnnotation}} for how to set colors.}
38 38
   \item{na_col}{Color for \code{NA} values in simple annotations.}
39 39
   \item{annotation_legend_param}{A list which contains parameters for annotation legends. See \code{\link{color_mapping_legend,ColorMapping-method}} for all possible options.}
40
-  \item{show_legend}{Whether show annotation legends. The value can be one single value or a vector which corresponds to simple annotations.}
40
+  \item{show_legend}{Whether show annotation legends. The value can be one single value or a vector.}
41 41
   \item{which}{Are these row annotations or column annotations?}
42 42
   \item{gp}{Graphic parameters for simple annotations (with \code{fill} parameter ignored).}
43 43
   \item{border}{border of single annotations.}
... ...
@@ -33,7 +33,7 @@ Legend(at, labels = at, col_fun, nrow = NULL, ncol = 1, by_row = FALSE,
33 33
   \item{labels_rot}{Text rotation for labels. It should only be used for horizontal continuous legend.}
34 34
   \item{border}{Color of legend grid borders. It also works for the ticks in the continuous legend.}
35 35
   \item{background}{Background colors for the grids. It is used when points and lines are the legend graphics.}
36
-  \item{type}{Type of legends. The value can be one of \code{grid}, \code{points} and \code{lines}.}
36
+  \item{type}{Type of legends. The value can be one of \code{grid}, \code{points}, \code{lines} and \code{boxplot}.}
37 37
   \item{legend_gp}{Graphic parameters for the legend grids. You should control the filled color of the legend grids by \code{gpar(fill = ...)}.}
38 38
   \item{pch}{Type of points if points are used as legend. Note you can use single-letter as pch, e.g. \code{pch = 'A'}. There are three additional integers that are valid for \code{pch}: 26 and 27 for single diagonal lines and 28 for double diagonal lines.}
39 39
   \item{size}{Size of points.}
... ...
@@ -50,6 +50,7 @@ Draw a list of heatmaps
50 50
     km = NULL,
51 51
     split = NULL,
52 52
     row_km = km,
53
+    row_km_repeats = NULL,
53 54
     row_split = split,
54 55
     height = NULL,
55 56
     heatmap_height = NULL,
... ...
@@ -64,6 +65,7 @@ Draw a list of heatmaps
64 65
     column_dend_gp = NULL,
65 66
     column_order = NULL,
66 67
     column_km = NULL,
68
+    column_km_repeats = NULL,
67 69
     column_split = NULL,
68 70
     width = NULL,
69 71
     heatmap_width = NULL,
... ...
@@ -124,6 +126,7 @@ Draw a list of heatmaps
124 126
   \item{km}{= this modifies \code{km} of the main heatmap}
125 127
   \item{split}{this modifies \code{split} of the main heatmap}
126 128
   \item{row_km}{this modifies \code{row_km} of the main heatmap}
129
+  \item{row_km_repeats}{this modifies \code{row_km_repeats} of the main heatmap}
127 130
   \item{row_split}{this modifies \code{row_split} of the main heatmap}
128 131
   \item{height}{this modifies \code{height} of the main heatmap}
129 132
   \item{heatmap_height}{this modifies \code{heatmap_height} of the main heatmap}
... ...
@@ -137,6 +140,7 @@ Draw a list of heatmaps
137 140
   \item{column_dend_gp}{this modifies \code{column_dend_gp} of the main heatmap}
138 141
   \item{column_order}{this modifies \code{column_order} of the main heatmap}
139 142
   \item{column_km}{this modifies \code{column_km} of the main heatmap}
143
+  \item{column_km_repeats}{this modifies \code{column_km_repeats} of the main heatmap}
140 144
   \item{column_split}{this modifies \code{column_split} of the main heatmap}
141 145
   \item{width}{this modifies \code{width} of the main heatmap}
142 146
   \item{heatmap_width}{this modifies \code{heatmap_width} of the main heatmap}
... ...
@@ -45,6 +45,7 @@ Make Layout for the Heatmap List
45 45
     row_dend_gp = NULL,
46 46
     row_order = NULL,
47 47
     row_km = NULL,
48
+    row_km_repeats = NULL,
48 49
     row_split = NULL,
49 50
     height = NULL,
50 51
     heatmap_height = NULL,
... ...
@@ -59,6 +60,7 @@ Make Layout for the Heatmap List
59 60
     column_dend_gp = NULL,
60 61
     column_order = NULL,
61 62
     column_km = NULL,
63
+    column_km_repeats = NULL,
62 64
     column_split = NULL,
63 65
     width = NULL,
64 66
     heatmap_width = NULL)
... ...
@@ -97,6 +99,7 @@ Make Layout for the Heatmap List
97 99
   \item{row_dend_gp}{Overwrite the corresponding setting in the main heatmap.}
98 100
   \item{row_order}{Overwrite the corresponding setting in the main heatmap.}
99 101
   \item{row_km}{Overwrite the corresponding setting in the main heatmap.}
102
+  \item{row_km_repeats}{Overwrite the corresponding setting in the main heatmap.}
100 103
   \item{row_split}{Overwrite the corresponding setting in the main heatmap.}
101 104
   \item{height}{Overwrite the corresponding setting in the main heatmap.}
102 105
   \item{heatmap_height}{Overwrite the corresponding setting in the main heatmap.}
... ...
@@ -110,6 +113,7 @@ Make Layout for the Heatmap List
110 113
   \item{column_dend_gp}{Overwrite the corresponding setting in the main heatmap.}
111 114
   \item{column_order}{Overwrite the corresponding setting in the main heatmap.}
112 115
   \item{column_km}{Overwrite the corresponding setting in the main heatmap.}
116
+  \item{column_km_repeats}{Overwrite the corresponding setting in the main heatmap.}
113 117
   \item{column_split}{Overwrite the corresponding setting in the main heatmap.}
114 118
   \item{width}{Overwrite the corresponding setting in the main heatmap.}
115 119
   \item{heatmap_width}{Overwrite the corresponding setting in the main heatmap.}
... ...
@@ -7,14 +7,14 @@ Pack Legends
7 7
 Pack Legends
8 8
 }
9 9
 \usage{
10
-packLegend(...,gap = unit(2, "mm"), row_gap = unit(2, "mm"), column_gap = unit(2, "mm"),
10
+packLegend(..., gap = unit(2, "mm"), row_gap = unit(2, "mm"), column_gap = unit(2, "mm"),
11 11
     direction = c("vertical", "horizontal"),
12 12
     max_width = NULL, max_height = NULL, list = NULL)
13 13
 }
14 14
 \arguments{
15 15
 
16 16
   \item{...}{A list of objects returned by \code{\link{Legend}}.}
17
-  \item{gap}{Gap between two neighbouring legends. The value is a \code{\link[grid]{unit}} object with length of one.}
17
+  \item{gap}{Gap between two neighbouring legends. The value is a \code{\link[grid]{unit}} object with length of one. It is the same as \code{row_gap} if the direction if vertial and the same as \code{column_gap} if the direction is horizontal.}
18 18
   \item{row_gap}{Horizontal gaps between legends.}
19 19
   \item{column_gap}{Vertical gaps between legends.}
20 20
   \item{direction}{The direction to arrange legends.}
21 21
deleted file mode 100644
... ...
@@ -1,124 +0,0 @@
1
-<!--
2
-%\VignetteEngine{knitr}
3
-%\VignetteIndexEntry{Difference to older versions}
4
-
5
-
6
-Difference to Older Versions of ComplexHeatmap Package
7
-=================================================
8
-
9
-**Author**: Zuguang Gu ( z.gu@dkfz.de )
10
-
11
-**Date**: `r Sys.Date()`
12
-
13
-**Package version**: `r installed.packages()["ComplexHeatmap", "Version"]`
14
-
15
-
16
-<style type="text/css">
17
-h1, h2, h3, h4, h5 {
18
-    line-height: 120%;
19
-}
20
-</style>
21
-
22
-From version 1.99.0 of **ComplexHeatmap**, there are big changes to the older versions. The major
23
-functionalities are still the same, but it is not 100% compatible. This vignette lists the
24
-changes between the new and old versions.
25
-
26
-## Heatmap() function
27
-
28
-- New arguments `column_km` and `column_split` to split heatmap by columns. The old `km` and `split`
29
-  are renamed to `row_km` and `row_split`, although `km` and `split` are still usable.
30
-- A new argument `border` controls the border of the heatmap body. If heatmap is split into slices,
31
-  all the slices will have borders.
32
-- Row title and column title allow background color by e.g. `column_title_gp = gpar(fill = ...)`.
33
-- `cluster_rows` and `cluster_columns` also allow objects which can be converted to `dendrogram`.
34
-- If `cluster_rows` and `cluster_columns` are provided as clustering object, dendrogram reordering
35
-  is turned off by default.
36
-- Add examples of how to integrate seriation.
37
-  (https://jokergoo.github.io/ComplexHeatmap-reference/book/a-single-heatmap.html#heatmap-seriation)
38
-- Row names and column names allow rotation by `row_names_rot` and `column_names_rot`.
39
-- New arguments `row_labels` and `column_labels` which can be set to replace row names and column
40
-  names on the heatmap.
41
-- When heatmap is split and clustering is performed, there is a parent dendrogram which is
42
-  calculated from mean values in slices and put on top of the children dendrograms. There is a dashed
43
-  line showing the part of the parent dendrogram and emphasizing the dendrogram is combined from
44
-  several dendrograms.
45
-- Remove `combined_name_fun` argument and control the titles for the heatmap slices directly by
46
-  `row_title` and `column_title`. The two arguments support a string template which is convinient to
47
-  control the title for each slice.
48
-  (https://jokergoo.github.io/ComplexHeatmap-reference/book/a-single-heatmap.html#titles-for-splitting)
49
-- New argument `layer_fun` is a vectorized version of `cell_fun`. This functionality is too
50
-  low-level and normally users will not use it.
51
-  (https://jokergoo.github.io/ComplexHeatmap-reference/book/a-single-heatmap.html#customize-the-heatmap-body)
52
-- New arguments `width`, `heatmap_width`, `height`, `heatmap_height` to control the size of the
53
-  heatmap.
54
-  (https://jokergoo.github.io/ComplexHeatmap-reference/book/a-single-heatmap.html#size-of-the-heatmap)
55
-- New arguments `left_annotation` and `right_annotation`, which means row annotations can be components
56
-  of the heatmap, just like column annotations.
57
-- Remove `top_annotation_height` and `bottom_annotation_height`. The height of annotations should be
58
-  set in `HeatmapAnnotation()` function now.
59
-
60
-## HeatmapAnnotation() function
61
-
62
-- All annotations have default width/height now. E.g. the column simple annotation has height of 5mm
63
-  and the column barplot annotation has height of 1cm.
64
-- Provide more annotation functions: `anno_empty()`, `anno_simple`, `anno_image()`, `anno_block()`,
65
-  `anno_lines()`, `anno_joyplot()`, `anno_horizon()`, `anno_summary()`, `anno_zoom()`.
66
-  (https://jokergoo.github.io/ComplexHeatmap-reference/book/heatmap-annotations.html)
67
-- The size of the annotations are better to be set in the annotation functions, e.g.
68
-  `anno_points(..., height = )`, but you can still set `annotation_height`.
69
-- The axis for the annotations (e.g. `anno_points()`, ...) can be controlled by the `axis_param`
70
-  argument in the annotation function.
71
-- `anno_link()` is now renamed to `anno_mark()`. This annotation has default width and no need to
72
-  manually calcualte.
73
-- `anno_text()`: the size of the annotation is automatically calculated.
74
-- By default, the annotation names and axes are drawn and the space for them are also taken into
75
-  account for the layout of the final heatmap.
76
-- Two `HeatmapAnnotation` objects can be added as a single `HeatmapAnnotation` object by `c()`.
77
-  (https://jokergoo.github.io/ComplexHeatmap-reference/book/heatmap-annotations.html#heatmap-annotation-utility-function)
78
-- No need to use `row_anno_*()` functions, now `anno_*()` functions can automatically check whether
79
-  they are in column annotations or row annotations.
80
-
81
-## A list of heatmaps
82
-
83
-- Heatmaps and annotations can be concatenated vertically by `%v%`.
84
-  (https://jokergoo.github.io/ComplexHeatmap-reference/book/a-list-of-heatmaps.html#vertical-concatenation)
85
-- More arguments for the main heatmap can be controlled directly in `draw()`.
86
-  (https://jokergoo.github.io/ComplexHeatmap-reference/book/a-list-of-heatmaps.html#control-main-heatmap-in-draw-function)
87
-- Global options can be temporarily set in `draw()`. (https://jokergoo.github.io/ComplexHeatmap-reference/book/a-list-of-heatmaps.html#change-parameters-globally, the last paragraph.)
88
-- Annotations and column names are nicely adjusted.
89
-  (https://jokergoo.github.io/ComplexHeatmap-reference/book/a-list-of-heatmaps.html#annotations-as-components-are-adjusted)
90
-
91
-## Legends
92
-
93
-- Legends are re-implemented as a `gTree` object internally. `Legend()` and `packLegend()` all
94
-  returns a `Legends` object. This object can be treated as a single graphic element and can be drawn by
95
-  specifying the positions on the viewport. (https://jokergoo.github.io/ComplexHeatmap-reference/book/legends.html)
96
-- Positions of legend labels are automatically adjusted if they overlap.
97
-- A list of legends are automatically wrapped into multiple columns or rows if they are too long and
98
-  exceed the plotting region.
99
-
100
-## oncoPrint() function
101
-
102
-- It automatially tests whether functions in `alter_fun` are vectorized.
103
-- The oncoPrint barplot annotations are now controlled by `anno_oncoprint_barplot()` and they are
104
-  basically normal heatmap annotations. Also axis is controlled in `anno_oncoprint_barplot()`.
105
-- `barplot_ignore` is removed and the subset of alterations in directly controlled in
106
-  `anno_oncoprint_barplot()`.
107
-- Similar as `Heatmap()`, all the argument related to the size of annotations are removed and they
108
-  should be set directly in `HeatmapAnnotation()` or `anno_oncoprint_barplot()`.
109
-- New arguments `remove_empty_rows` and `remove_empty_columns`. If the number of rows and columns
110
-  gets smaller, all the oncoPrint components (e.g. row names, annotations) will be adjusted as well.
111
-- `oncoPrint()` now returns a `Heatmap` object which can be concatenated to other
112
-  heatmaps/annotations horizontally or vertically.
113
-
114
-## densityHeatmap() function
115
-
116
-- Columns can be clustered by the Kolmogorov-Smirnov distance between distributions.
117
-- `densityHeatmap()` returns a vertical heatmap that more heatmaps and annotations can concatenate
118
-  to it vertically.
119
-
120
-## UpSet() function
121
-- Add a new `UpSet()` function to make UpSet plots and can be concatenated to other heatmaps/annotations. (https://jokergoo.github.io/ComplexHeatmap-reference/book/upset-plot.html)
122
-
... ...
@@ -26,26 +26,33 @@ library(ComplexHeatmap)
26 26
 
27 27
 ### There is no plot comming out after running Heatmap() function.
28 28
 
29
-In this case, you need to use `draw()` function explicitly. See https://jokergoo.github.io/ComplexHeatmap-reference/book/a-single-heatmap.html#plot-the-heatmap and https://jokergoo.github.io/ComplexHeatmap-reference/book/a-list-of-heatmaps.html#plot-the-heamtap-list.
29
+In this case, you need to use `draw()` function explicitly. See
30
+https://jokergoo.github.io/ComplexHeatmap-reference/book/a-single-heatmap.html#plot-the-heatmap
31
+and
32
+https://jokergoo.github.io/ComplexHeatmap-reference/book/a-list-of-heatmaps.html#plot-the-heamtap-list.
30 33
 
31 34
 ### Retrieve orders and dendrograms.
32 35
 
33
-For retrieving orders and dendrograms from a single heatmap. See https://jokergoo.github.io/ComplexHeatmap-reference/book/a-single-heatmap.html#get-orders-and-dendrograms-from-heatmap.
36
+For retrieving orders and dendrograms from a single heatmap. See
37
+https://jokergoo.github.io/ComplexHeatmap-reference/book/a-single-heatmap.html#get-orders-and-dendrograms-from-heatmap.
34 38
 
35
-For retrieving orders and dendrograms from a list of heatmaps. See https://jokergoo.github.io/ComplexHeatmap-reference/book/a-list-of-heatmaps.html#get-orders-and-dendrograms-from-a-list-of-heatmaps.
39
+For retrieving orders and dendrograms from a list of heatmaps. See
40
+https://jokergoo.github.io/ComplexHeatmap-reference/book/a-list-of-heatmaps.html#get-orders-and-dendrograms-from-a-list-of-heatmaps.
36 41
 
37 42
 ### How should I control the height or width of the heatmap annotations?
38 43
 
39
-For complex annotations generated by `anno_*()` functions, width or height should be set inside 
40
-the `anno_*()` function, such as `anno_points(..., height = ...)`. The size of simple annotations
41
-is controlled by `anno_simple_size`. The `width`/`height` and `annotation_width`/`annotation_height`
42
-are used to adjust the size for multiple annotations which are put in one `HeatmapAnnotation` object.
43
-See https://jokergoo.github.io/ComplexHeatmap-reference/book/heatmap-annotations.html#multiple-annotations
44
+For complex annotations generated by `anno_*()` functions, width or height
45
+should be set inside the `anno_*()` function, such as `anno_points(..., height = ...)`. The size of simple annotations is controlled by `anno_simple_size`.
46
+The `width`/`height` and `annotation_width`/`annotation_height` are used to
47
+adjust the size for multiple annotations which are put in one
48
+`HeatmapAnnotation` object. See
49
+https://jokergoo.github.io/ComplexHeatmap-reference/book/heatmap-annotations.html#multiple-annotations
44 50
 
45 51
 ### How should I control the axes of the annotations?
46 52
 
47
-In the annotation functions `anno_*()`, the argument `axis_param` can be used to set the axes. The value
48
-should be a list and the default settings for axis can be get by:
53
+In the annotation functions `anno_*()`, the argument `axis_param` can be used
54
+to set the axes. The value should be a list and the default settings for axis
55
+can be get by:
49 56
 
50 57
 ```{r, eval = FALSE}
51 58
 default_axis_param("column")
... ...
@@ -54,16 +61,19 @@ default_axis_param("row")
54 61
 
55 62
 ### How to control the style of legends?
56 63
 
57
-The style of legends can be controlled by `heatmap_legend_param` in `Heatmap()`, or
58
-`annotation_legend_param` in `HeatmapAnnotation()`. The parameters for controlling legends are those
59
-arguments in `Legend()` function. See
64
+The style of legends can be controlled by `heatmap_legend_param` in
65
+`Heatmap()`, or `annotation_legend_param` in `HeatmapAnnotation()`. The
66
+parameters for controlling legends are those arguments in `Legend()` function.
67
+See
60 68
 https://jokergoo.github.io/ComplexHeatmap-reference/book/legends.html#heatmap-and-annotation-legends.
61 69
 
62 70
 ### Some text are cut by the plotting region.
63 71
 
64
-The layout of the **ComplexHeatmap** is not perfect that it is still possible some of the text are
65
-drawn out of the plotting region. In this case, you can set the `padding` argument in `draw()` function
66
-to increase the blank areas around the final plot. See https://jokergoo.github.io/ComplexHeatmap-reference/book/a-list-of-heatmaps.html#manually-increase-space-around-the-plot.
72
+The layout of the **ComplexHeatmap** is not perfect that it is still possible
73
+some of the text are drawn out of the plotting region. In this case, you can
74
+set the `padding` argument in `draw()` function to increase the blank areas
75
+around the final plot. See
76
+https://jokergoo.github.io/ComplexHeatmap-reference/book/a-list-of-heatmaps.html#manually-increase-space-around-the-plot.
67 77
 
68 78
 ### Can the heatmaps be added vertically?
69 79
 
... ...
@@ -76,8 +86,8 @@ methematical expression.
76 86
 
77 87
 ### I have many heatmaps and I want to put them into different panels for a big figure for my paper.
78 88
 
79
-You can set `newpage = FALSE` in `draw()` function and use `grid.layout()` to manage the layout of
80
-your panels. 
89
+You can set `newpage = FALSE` in `draw()` function and use `grid.layout()` to
90
+manage the layout of your panels.
81 91
 
82 92
 ```{r, eval = FALSE}
83 93
 pushViewport(viewport(layout = grid.layout(...)))
... ...
@@ -87,8 +97,9 @@ popViewport()
87 97
 ...
88 98
 ```
89 99
 
90
-But I more suggest to use `grid.grabExpr()` to directly capture the output of the
91
-heatmap and later draw the whole plot as a single graphic element by `grid.draw()`.
100
+But I more suggest to use `grid.grabExpr()` to directly capture the output of
101
+the heatmap and later draw the whole plot as a single graphic element by
102
+`grid.draw()`.
92 103
 
93 104
 ```{r, eval = FALSE}
94 105
 ht_grob = grid.grabExpr(draw(ht, ...))
... ...
@@ -102,7 +113,8 @@ popViewport()
102 113
 
103 114
 ### I have a matrix with too many rows and I want to simplify the row dendrogram.
104 115
 
105
-You can first group your rows into several groups and make a group-level dendrogram on it. See following example:
116
+You can first group your rows into several groups and make a group-level
117
+dendrogram on it. See following example:
106 118
 
107 119
 ```{r}
108 120
 m = matrix(rnorm(1000*10), nr = 1000)
... ...
@@ -115,13 +127,14 @@ Heatmap(m, cluster_rows = cluster_within_group(t(m), group),
115 127
 ### I have a matrix with huge nunmber of rows or columns, what is the efficient way to visualize it?
116 128
 
117 129
 Heatmap is used to visualize the global patterns of your matrix while not
118
-every single row or column. I suggest to random sample rows or columns
119
-into a reasonable small number, and the final heatmap should be the same as if
120
-you still insist to use the full matrix.
130
+every single row or column. I suggest to random sample rows or columns into a
131
+reasonable small number, and the final heatmap should be the same as if you
132
+still insist to use the full matrix.
121 133
 
122 134
 ### How to add axes for dendrograms?
123 135
 
124
-You need to use `decorate_row_dend()` or `decorate_column_dend()` to manually add the axes. See following examples:
136
+You need to use `decorate_row_dend()` or `decorate_column_dend()` to manually
137
+add the axes. See following examples:
125 138
 
126 139
 ```{r}
127 140
 m = matrix(rnorm(100), 10)
... ...
@@ -145,3 +158,14 @@ Note for the left row dendrogram, the x-axis is from right to left, you need to
145 158
 and `label` in `grid.xaxis()` function.
146 159
 
147 160
 You can also check `annotation_axis_grob()` function (later use `grid.draw()` to draw the axes) to draw a nicer axis.
161
+
162
+### I still have a problem with the package and I am lost in the see of the huge vignette.
163
+
164
+The vignette (https://jokergoo.github.io/ComplexHeatmap-reference/book/)
165
+contains huge number of examples and plots showing different usage of the
166
+package. It is sometimes not easy to find the solution you are looking for. In
167
+this case, don't hesitate to write me an email. I am glad to answer all of your
168
+questions!
169
+
170
+
171
+