Browse code

anoying rebase

git-svn-id: https://hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/ComplexHeatmap@111684 bc3139a8-67e5-0310-9ffc-ced21a209358

z.gu authored on 20/12/2015 21:42:51
Showing 41 changed files

... ...
@@ -1,4 +1,8 @@
1
+<<<<<<< HEAD
1 2
 CHANEGS in VERSION 1.7.4
3
+=======
4
+CHANEGS in VERSION 1.8.0
5
+>>>>>>> master
2 6
 
3 7
 * width of the heatmap body are calculated correctly if it is set as a fixed unit
4 8
 * there is no dendrogram is nrows in a row-slice is 1
... ...
@@ -6,6 +10,12 @@ CHANEGS in VERSION 1.7.4
6 10
 * bottom annotations are attached to the bottom edge of the heatmap 
7 11
   if there are additional blank space
8 12
 * colors for NA can be set by "_NA_" in annotations
13
+<<<<<<< HEAD
14
+=======
15
+* `row_dend_reorder` and `column_dend_reorder` are set to `TRUE` by default again -_-!!
16
+* optimize the way to specify na_col in heatmap annotations
17
+* correct wrong viewport names in decorate_* functions
18
+>>>>>>> master
9 19
 
10 20
 ===============================
11 21
 
... ...
@@ -12,7 +12,7 @@ AdditiveUnit = setClass("AdditiveUnit")
12 12
 # Constructor method for AdditiveUnit class
13 13
 #
14 14
 # == param
15
-# -... arguments.
15
+# -... black hole arguments.
16 16
 #
17 17
 # == details
18 18
 # This method is not used in the package.
... ...
@@ -110,7 +110,9 @@ ColorMapping = function(name, colors = NULL, levels = NULL,
110 110
 	}
111 111
 
112 112
 	.Object@name = name
113
-	.Object@na_col = na_col
113
+	na_col = t(col2rgb(na_col, alpha = TRUE))
114
+	na_col = rgb(na_col[, 1:3, drop = FALSE], alpha = na_col[, 4], maxColorValue = 255)
115
+	.Object@na_col = na_col[1]
114 116
 
115 117
 	return(.Object)
116 118
 }
... ...
@@ -235,7 +235,7 @@ Heatmap = function(matrix, col, name,
235 235
     row_dend_side = c("left", "right"),
236 236
     row_dend_width = unit(10, "mm"), 
237 237
     show_row_dend = TRUE, 
238
-    row_dend_reorder = FALSE,
238
+    row_dend_reorder = TRUE,
239 239
     row_dend_gp = gpar(), 
240 240
     row_hclust_side = row_dend_side,
241 241
     row_hclust_width = row_dend_width, 
... ...
@@ -249,7 +249,7 @@ Heatmap = function(matrix, col, name,
249 249
     column_dend_height = unit(10, "mm"), 
250 250
     show_column_dend = TRUE, 
251 251
     column_dend_gp = gpar(), 
252
-    column_dend_reorder = FALSE,
252
+    column_dend_reorder = TRUE,
253 253
     column_hclust_side = column_dend_side, 
254 254
     column_hclust_height = column_dend_height, 
255 255
     show_column_hclust = show_column_dend, 
... ...
@@ -41,6 +41,7 @@ HeatmapAnnotation = setClass("HeatmapAnnotation",
41 41
 # -df a data frame. Each column will be treated as a simple annotation. The data frame must have column names.
42 42
 # -name name of the heatmap annotation, optional.
43 43
 # -col a list of colors which contains color mapping to columns in ``df``. See `SingleAnnotation` for how to set colors.
44
+# -na_col color for ``NA`` values in simple annotations.
44 45
 # -annotation_legend_param a list which contains parameters for annotation legends
45 46
 # -show_legend whether show legend for each column in ``df``.
46 47
 # -... functions which define complex annotations. Values should be named arguments.
... ...
@@ -65,7 +66,7 @@ HeatmapAnnotation = setClass("HeatmapAnnotation",
65 66
 # == author
66 67
 # Zuguang Gu <z.gu@dkfz.de>
67 68
 #
68
-HeatmapAnnotation = function(df, name, col, 
69
+HeatmapAnnotation = function(df, name, col, na_col = "grey",
69 70
 	annotation_legend_param = list(), 
70 71
 	show_legend = TRUE, 
71 72
 	..., 
... ...
@@ -92,7 +93,7 @@ HeatmapAnnotation = function(df, name, col,
92 93
 
93 94
     arg_list = as.list(match.call())[-1]
94 95
     called_args = names(arg_list)
95
-    anno_args = setdiff(called_args, c("name", "col", "annotation_legend_param", "show_legend", "which", 
96
+    anno_args = setdiff(called_args, c("name", "col", "na_col", "annotation_legend_param", "show_legend", "which", 
96 97
     	                             "annotation_height", "annotation_width", "height", "width", "gp", "gap"))
97 98
     if(any(anno_args == "")) stop("annotations should have names.")
98 99
     if(any(duplicated(anno_args))) stop("names of annotations should be unique.")
... ...
@@ -160,14 +161,14 @@ HeatmapAnnotation = function(df, name, col,
160 161
 
161 162
 		    if(missing(col)) {
162 163
 		        for(i in seq_len(n_anno)) {
163
-		        	anno_list = c(anno_list, list(SingleAnnotation(name = anno_name[i], value = df[, i], which = which, show_legend = show_legend[i_simple + i], gp = gp, legend_param = annotation_legend_param[[i_simple + i]])))
164
+		        	anno_list = c(anno_list, list(SingleAnnotation(name = anno_name[i], value = df[, i], na_col = na_col, which = which, show_legend = show_legend[i_simple + i], gp = gp, legend_param = annotation_legend_param[[i_simple + i]])))
164 165
 		        }
165 166
 		    } else {
166 167
 		        for(i in seq_len(n_anno)) {
167 168
 		        	if(is.null(col[[ anno_name[i] ]])) { # if the color is not provided
168
-		        		anno_list = c(anno_list, list(SingleAnnotation(name = anno_name[i], value = df[, i], which = which, show_legend = show_legend[i_simple + i], gp = gp, legend_param = annotation_legend_param[[i_simple + i]])))
169
+		        		anno_list = c(anno_list, list(SingleAnnotation(name = anno_name[i], value = df[, i], na_col = na_col, which = which, show_legend = show_legend[i_simple + i], gp = gp, legend_param = annotation_legend_param[[i_simple + i]])))
169 170
 		        	} else {
170
-		        		anno_list = c(anno_list, list(SingleAnnotation(name = anno_name[i], value = df[, i], col = col[[ anno_name[i] ]], which = which, show_legend = show_legend[i_simple + i], gp = gp, legend_param = annotation_legend_param[[i_simple + i]])))
171
+		        		anno_list = c(anno_list, list(SingleAnnotation(name = anno_name[i], value = df[, i], na_col = na_col, col = col[[ anno_name[i] ]], which = which, show_legend = show_legend[i_simple + i], gp = gp, legend_param = annotation_legend_param[[i_simple + i]])))
171 172
 		        	}
172 173
 		        }
173 174
 		    }
... ...
@@ -183,12 +184,12 @@ HeatmapAnnotation = function(df, name, col,
183 184
 			    	stop("length of simple annotations differ.")
184 185
 			    }
185 186
 				if(missing(col)) {
186
-			        anno_list = c(anno_list, list(SingleAnnotation(name = ag, value = anno_arg_list[[ag]], which = which, show_legend = show_legend[i_simple + 1], gp = gp, legend_param = annotation_legend_param[[i_simple + 1]])))
187
+			        anno_list = c(anno_list, list(SingleAnnotation(name = ag, value = anno_arg_list[[ag]], na_col = na_col, which = which, show_legend = show_legend[i_simple + 1], gp = gp, legend_param = annotation_legend_param[[i_simple + 1]])))
187 188
 			    } else {
188 189
 			        if(is.null(col[[ ag ]])) { # if the color is not provided
189
-			        	anno_list = c(anno_list, list(SingleAnnotation(name = ag, value = anno_arg_list[[ag]], which = which, show_legend = show_legend[i_simple + 1], gp = gp, legend_param = annotation_legend_param[[i_simple + 1]])))
190
+			        	anno_list = c(anno_list, list(SingleAnnotation(name = ag, value = anno_arg_list[[ag]], na_col = na_col, which = which, show_legend = show_legend[i_simple + 1], gp = gp, legend_param = annotation_legend_param[[i_simple + 1]])))
190 191
 			        } else {
191
-			        	anno_list = c(anno_list, list(SingleAnnotation(name = ag, value = anno_arg_list[[ag]], col = col[[ ag ]], which = which, show_legend = show_legend[i_simple + 1], gp = gp, legend_param = annotation_legend_param[[i_simple + 1]])))
192
+			        	anno_list = c(anno_list, list(SingleAnnotation(name = ag, value = anno_arg_list[[ag]], na_col = na_col, col = col[[ ag ]], which = which, show_legend = show_legend[i_simple + 1], gp = gp, legend_param = annotation_legend_param[[i_simple + 1]])))
192 193
 			        }
193 194
 			    }
194 195
 			    i_simple = i_simple + 1
... ...
@@ -8,6 +8,16 @@
8 8
 # == value
9 9
 # A list contains row orders which correspond to the original matrix
10 10
 #
11
+# == author
12
+# Zuguang Gu <z.gu@dkfz.de>
13
+#
14
+# == example
15
+# mat = matrix(rnorm(100), 10)
16
+# ht_list = Heatmap(mat) + Heatmap(mat)
17
+# row_order(ht_list)
18
+# ht = Heatmap(mat, km = 2) + Heatmap(mat)
19
+# row_order(ht_list)
20
+#
11 21
 setMethod(f = "row_order",
12 22
 	signature = "HeatmapList",
13 23
 	definition = function(object) {
... ...
@@ -18,9 +28,6 @@ setMethod(f = "row_order",
18 28
 	for(i in seq_len(n)) {
19 29
         if(inherits(object@ht_list[[i]], "Heatmap")) {
20 30
         	lt = object@ht_list[[i]]@row_order_list
21
-        	if(length(object@ht_list[[i]]@row_title) > 0) {
22
-        		names(lt) = object@ht_list[[i]]@row_title
23
-        	}
24 31
         	return(lt)
25 32
         }
26 33
     }
... ...
@@ -38,6 +45,16 @@ setMethod(f = "row_order",
38 45
 # == value
39 46
 # A list contains row orders which correspond to the original matrix
40 47
 #
48
+# == author
49
+# Zuguang Gu <z.gu@dkfz.de>
50
+#
51
+# == example
52
+# mat = matrix(rnorm(100), 10)
53
+# ht = Heatmap(mat)
54
+# row_order(ht)
55
+# ht = Heatmap(mat, km = 2)
56
+# row_order(ht)
57
+#
41 58
 setMethod(f = "row_order",
42 59
 	signature = "Heatmap",
43 60
 	definition = function(object) {
... ...
@@ -45,9 +62,6 @@ setMethod(f = "row_order",
45 62
 	object = prepare(object)
46 63
 
47 64
 	lt = object@row_order_list
48
-	if(length(object@row_title) > 0) {
49
-		names(lt) = object@row_title
50
-	}
51 65
 	return(lt)
52 66
 	
53 67
 })
... ...
@@ -61,6 +75,16 @@ setMethod(f = "row_order",
61 75
 # == value
62 76
 # A list contains column orders which correspond every matrix
63 77
 #
78
+# == author
79
+# Zuguang Gu <z.gu@dkfz.de>
80
+#
81
+# == example
82
+# mat = matrix(rnorm(100), 10)
83
+# ht_list = Heatmap(mat) + Heatmap(mat)
84
+# column_order(ht_list)
85
+# ht = Heatmap(mat, km = 2) + Heatmap(mat)
86
+# column_order(ht_list)
87
+#
64 88
 setMethod(f = "column_order",
65 89
 	signature = "HeatmapList",
66 90
 	definition = function(object) {
... ...
@@ -91,6 +115,16 @@ setMethod(f = "column_order",
91 115
 # == value
92 116
 # A vector containing column orders
93 117
 #
118
+# == author
119
+# Zuguang Gu <z.gu@dkfz.de>
120
+#
121
+# == example
122
+# mat = matrix(rnorm(100), 10)
123
+# ht = Heatmap(mat)
124
+# column_order(ht)
125
+# ht = Heatmap(mat, km = 2)
126
+# column_order(ht)
127
+#
94 128
 setMethod(f = "column_order",
95 129
 	signature = "Heatmap",
96 130
 	definition = function(object) {
... ...
@@ -110,6 +144,16 @@ setMethod(f = "column_order",
110 144
 # == value
111 145
 # A list of dendrograms for which each dendrogram corresponds to a row slice
112 146
 #
147
+# == author
148
+# Zuguang Gu <z.gu@dkfz.de>
149
+#
150
+# == example
151
+# mat = matrix(rnorm(100), 10)
152
+# ht_list = Heatmap(mat) + Heatmap(mat)
153
+# row_dend(ht_list)
154
+# ht_list = Heatmap(mat, km = 2) + Heatmap(mat)
155
+# row_dend(ht_list)
156
+#
113 157
 setMethod(f = "row_dend",
114 158
 	signature = "HeatmapList",
115 159
 	definition = function(object) {
... ...
@@ -120,9 +164,6 @@ setMethod(f = "row_dend",
120 164
     for(i in seq_len(n)) {
121 165
         if(inherits(object@ht_list[[i]], "Heatmap")) {
122 166
         	lt = object@ht_list[[i]]@row_dend_list
123
-        	if(length(object@ht_list[[i]]@row_title) > 0) {
124
-        		names(lt) = object@ht_list[[i]]@row_title
125
-        	}
126 167
         	return(lt)
127 168
         }
128 169
     }
... ...
@@ -139,6 +180,16 @@ setMethod(f = "row_dend",
139 180
 # == value
140 181
 # A list of dendrograms for which each dendrogram corresponds to a row slice
141 182
 #
183
+# == author
184
+# Zuguang Gu <z.gu@dkfz.de>
185
+#
186
+# == example
187
+# mat = matrix(rnorm(100), 10)
188
+# ht = Heatmap(mat)
189
+# row_dend(ht)
190
+# ht = Heatmap(mat, km = 2)
191
+# row_dend(ht)
192
+#
142 193
 setMethod(f = "row_dend",
143 194
 	signature = "Heatmap",
144 195
 	definition = function(object) {
... ...
@@ -146,9 +197,6 @@ setMethod(f = "row_dend",
146 197
 	object = prepare(object)
147 198
 
148 199
 	lt = object@row_dend_list
149
-	if(length(object@row_title) > 0) {
150
-		names(lt) = object@row_title
151
-	}
152 200
 	return(lt)
153 201
 })
154 202
 
... ...
@@ -161,6 +209,16 @@ setMethod(f = "row_dend",
161 209
 # == value
162 210
 # A list of dendrograms for which dendrogram corresponds to each matrix
163 211
 #
212
+# == author
213
+# Zuguang Gu <z.gu@dkfz.de>
214
+#
215
+# == example
216
+# mat = matrix(rnorm(100), 10)
217
+# ht_list = Heatmap(mat) + Heatmap(mat)
218
+# column_dend(ht_list)
219
+# ht_list = Heatmap(mat, km = 2) + Heatmap(mat)
220
+# column_dend(ht_list)
221
+#
164 222
 setMethod(f = "column_dend",
165 223
 	signature = "HeatmapList",
166 224
 	definition = function(object) {
... ...
@@ -191,6 +249,16 @@ setMethod(f = "column_dend",
191 249
 # == value
192 250
 # A dendrogram object
193 251
 #
252
+# == author
253
+# Zuguang Gu <z.gu@dkfz.de>
254
+#
255
+# == example
256
+# mat = matrix(rnorm(100), 10)
257
+# ht = Heatmap(mat)
258
+# column_dend(ht)
259
+# ht = Heatmap(mat, km = 2)
260
+# column_dend(ht)
261
+#
194 262
 setMethod(f = "column_dend",
195 263
 	signature = "Heatmap",
196 264
 	definition = function(object) {
... ...
@@ -48,13 +48,14 @@ SingleAnnotation = setClass("SingleAnnotation",
48 48
 # Constructor method for SingleAnnotation class
49 49
 #
50 50
 # == param
51
-# -name name for this annotation. If it is not specified, an internal name is assigned to it.
51
+# -name name for this annotation. If it is not specified, an internal name is assigned.
52 52
 # -value A vector of discrete or continuous annotation.
53 53
 # -col colors corresponding to ``value``. If the mapping is discrete mapping, the value of ``col``
54 54
 #      should be a vector; If the mapping is continuous mapping, the value of ``col`` should be 
55 55
 #      a color mapping function. 
56 56
 # -fun a self-defined function to add annotation graphics. The argument of this function should only 
57 57
 #      be a vector of index that corresponds to rows or columns.
58
+# -na_col color for ``NA`` values in simple annotations.
58 59
 # -which is the annotation a row annotation or a column annotation?
59 60
 # -show_legend if it is a simple annotation, whether show legend when making the complete heatmap.
60 61
 # -gp Since simple annotation is represented as a row of grids. This argument controls graphic parameters for the simple annotation.
... ...
@@ -77,6 +78,10 @@ SingleAnnotation = setClass("SingleAnnotation",
77 78
 # One thing that users should be careful is the difference of coordinates when the annotation is a row
78 79
 # annotation or a column annotation. 
79 80
 #
81
+# == seealso
82
+# There are following built-in annotation functions that can be used to generate complex annotations: 
83
+# `anno_points`, `anno_barplot`, `anno_histogram`, `anno_boxplot`, `anno_density`, `anno_text` and `anno_link`.
84
+# 
80 85
 # == value
81 86
 # A `SingleAnnotation-class` object.
82 87
 #
... ...
@@ -84,6 +89,7 @@ SingleAnnotation = setClass("SingleAnnotation",
84 89
 # Zuguang Gu <z.gu@dkfz.de>
85 90
 #
86 91
 SingleAnnotation = function(name, value, col, fun, 
92
+	na_col = "grey",
87 93
 	which = c("column", "row"), 
88 94
 	show_legend = TRUE, 
89 95
 	gp = gpar(col = NA), 
... ...
@@ -138,12 +144,15 @@ SingleAnnotation = function(name, value, col, fun,
138 144
     		if("_NA_" %in% names(col)) {
139 145
     			na_col = col["_NA_"]
140 146
     			col = col[names(col) != "_NA_"]
147
+<<<<<<< HEAD
141 148
     		} else {
142 149
     			na_col = "#FFFFFF"
150
+=======
151
+>>>>>>> master
143 152
     		}
144 153
             color_mapping = ColorMapping(name = name, colors = col, na_col = na_col)
145 154
         } else if(is.function(col)) {
146
-            color_mapping = ColorMapping(name = name, col_fun = col)
155
+            color_mapping = ColorMapping(name = name, col_fun = col, na_col = na_col)
147 156
         }
148 157
 
149 158
         .Object@color_mapping = color_mapping
... ...
@@ -2,9 +2,9 @@
2 2
 # Decorate the heatmap body
3 3
 #
4 4
 # == param
5
-# -heatmap name of the heatmap
5
+# -heatmap name of the heatmap which is set as ``name`` option in `Heatmap` function
6 6
 # -code code that adds graphics in the selected heatmap body
7
-# -slice index of row slices in the heatmap
7
+# -slice index of row slices in the heatmap if it is split by rows
8 8
 #
9 9
 # == details
10 10
 # There is a viewport for each row slice in each heatmap.
... ...
@@ -43,9 +43,15 @@
43 43
 #
44 44
 decorate_heatmap_body = function(heatmap, code, slice = 1) {
45 45
 
46
-	vp_name = paste0(heatmap, "_heatmap_body_", slice)
46
+	if(is.null(slice)) {
47
+		vp_name = paste0(heatmap, "_heatmap_body_", 1)
48
+		seekViewport(vp_name)
49
+		upViewport()
50
+	} else {
51
+		vp_name = paste0(heatmap, "_heatmap_body_", slice)
52
+		seekViewport(vp_name)
53
+	}
47 54
 
48
-	seekViewport(vp_name)
49 55
 	e = new.env(parent = parent.frame())
50 56
 	eval(substitute(code), envir = e)
51 57
 
... ...
@@ -94,7 +100,14 @@ decorate_dend = function(heatmap, code, slice = 1, which = c("column", "row")) {
94 100
 	if(which == "column") {
95 101
 		vp_name = paste0(heatmap, "_dend_", which)
96 102
 	} else if(which == "row") {
97
-		vp_name = paste0(heatmap, "_dend_", which, "_", slice)
103
+		if(is.null(slice)) {
104
+			vp_name = paste0(heatmap, "_dend_", which, "_", 1)
105
+			seekViewport(vp_name)
106
+			upViewport()
107
+		} else {
108
+			vp_name = paste0(heatmap, "_dend_", which, "_", slice)
109
+			seekViewport(vp_name)
110
+		}
98 111
 	}
99 112
 
100 113
 	seekViewport(vp_name)
... ...
@@ -197,7 +210,14 @@ decorate_dimnames = function(heatmap, code, slice = 1, which = c("column", "row"
197 210
 	if(which == "column") {
198 211
 		vp_name = paste0(heatmap, "_", which, "_names")
199 212
 	} else if(which == "row") {
200
-		vp_name = paste0(heatmap, "_", which, "_names_", slice)
213
+		if(is.null(slice)) {
214
+			vp_name = paste0(heatmap, "_", which, "_names_", 1)
215
+			seekViewport(vp_name)
216
+			upViewport()
217
+		} else {
218
+			vp_name = paste0(heatmap, "_", which, "_names_", slice)
219
+			seekViewport(vp_name)
220
+		}
201 221
 	}
202 222
 
203 223
 	seekViewport(vp_name)
... ...
@@ -287,7 +307,14 @@ decorate_title = function(heatmap, code, slice = 1, which = c("column", "row"))
287 307
 	if(which == "column") {
288 308
 		vp_name = paste0(heatmap, "_", which, "_title")
289 309
 	} else if(which == "row") {
290
-		vp_name = paste0(heatmap, "_", which, "_title_", slice)
310
+		if(is.null(slice)) {
311
+			vp_name = paste0(heatmap, "_", which, "_title_", 1)
312
+			seekViewport(vp_name)
313
+			upViewport()
314
+		} else {
315
+			vp_name = paste0(heatmap, "_", which, "_title_", slice)
316
+			seekViewport(vp_name)
317
+		}
291 318
 	}
292 319
 
293 320
 	seekViewport(vp_name)
... ...
@@ -376,9 +403,9 @@ decorate_column_title = function(...) {
376 403
 #     grid.rect(gp = gpar(fill = "#FF000080"))
377 404
 # }, slice = 2)
378 405
 #
379
-decorate_annotation = function(annotation, code, slice = NULL) {
406
+decorate_annotation = function(annotation, code, slice) {
380 407
 
381
-	if(is.null(slice)) {
408
+	if(missing(slice)) {
382 409
 		vp_name = paste0("annotation_", annotation)
383 410
 		o = try(seekViewport(vp_name), silent = TRUE)
384 411
 		if(inherits(o, "try-error")) {
... ...
@@ -391,8 +418,14 @@ decorate_annotation = function(annotation, code, slice = NULL) {
391 418
 		}
392 419
 		seekViewport(vp_name)
393 420
 	} else {
394
-		vp_name = paste0("annotation_", annotation, "_", slice)
395
-		seekViewport(vp_name)
421
+		if(is.null(slice)) {
422
+			vp_name = paste0("annotation_", annotation, "_", 1)
423
+			seekViewport(vp_name)
424
+			upViewport()
425
+		} else {
426
+			vp_name = paste0("annotation_", annotation, "_", slice)
427
+			seekViewport(vp_name)
428
+		}
396 429
 	}
397 430
 
398 431
 	e = new.env(parent = parent.frame())
... ...
@@ -104,5 +104,5 @@ densityHeatmap = function(data,
104 104
 		upViewport()
105 105
 	})
106 106
 
107
-	return(invisible(ht_list))
107
+	return(invisible(NULL))
108 108
 }
... ...
@@ -17,6 +17,7 @@
17 17
 # -pch shape of outlier points in the boxplot
18 18
 # -size size of hte outlier points in the boxplot
19 19
 # -axis_gp graphic parameters for the axis
20
+# -padding padding of the plot
20 21
 # -heatmap_legend_list a list of `grid::grob` which contains legend. It can be generated by `color_mapping_legend,ColorMapping-method`.
21 22
 #
22 23
 # == details
... ...
@@ -42,6 +43,7 @@ enhanced_basicplot = function(data, ..., ylim = NULL,
42 43
     ylab = deparse(substitute(data)), title = NULL, title_gp = gpar(fontsize = 14),
43 44
     type = c("boxplot", "barplot"), width = 0.8, gp = gpar(), 
44 45
     pch = 1, size = unit(2, "mm"), axis_gp = gpar(fontsize = 8),
46
+    padding = unit(c(2, 18, 2, 2), "mm"),
45 47
     heatmap_legend_list = list()) {
46 48
 
47 49
     if(!(inherits(data, c("matrix")) || inherits(data, "list") || is.atomic(data))) {
... ...
@@ -76,7 +78,7 @@ enhanced_basicplot = function(data, ..., ylim = NULL,
76 78
     ht = Heatmap(mat_foo, name = "main", cluster_rows = FALSE, cluster_columns = FALSE,
77 79
                 rect_gp = gpar(type = "none"), show_heatmap_legend = FALSE, ...)
78 80
 
79
-    draw(ht, padding = unit(c(2, 18, 2, 2), "mm"), column_title = title, column_title_gp = title_gp,
81
+    draw(ht, padding = padding, column_title = title, column_title_gp = title_gp,
80 82
         heatmap_legend_list = heatmap_legend_list)
81 83
 
82 84
     if(is.matrix(data)) {
... ...
@@ -1,7 +1,7 @@
1 1
 
2 2
 
3 3
 # == title
4
-# Global options for heatmaps
4
+# Global graphic options for heatmaps
5 5
 #
6 6
 # == param
7 7
 # -... options, see 'details' section
... ...
@@ -11,8 +11,8 @@
11 11
 #
12 12
 # == details
13 13
 # You can set some parameters for all heatmaps/annotations simultaneously by this global function.
14
-# Pleast note you should better to put it in the first beginning of your heatmap code and reset
15
-# all option values to get avoid of affecting next heatmap plotting.
14
+# Pleast note you should put it before your heatmap code and reset
15
+# all option values after drawing the heatmaps to get rid of affecting next heatmap plotting.
16 16
 #
17 17
 # There are following parameters:
18 18
 #
... ...
@@ -42,6 +42,9 @@
42 42
 # Besides the normal absolute units (e.g. "mm", "inches"), this function
43 43
 # simply treat `grid::grob` objects as absolute units.
44 44
 #
45
+# For a complex unit which is combination of different units, it is absolute
46
+# only if all units included are absolute units.
47
+#
45 48
 # == value
46 49
 # A logical value.
47 50
 #
... ...
@@ -52,6 +55,7 @@
52 55
 # is_abs_unit(unit(1, "mm"))
53 56
 # is_abs_unit(unit(1, "npc"))
54 57
 # is_abs_unit(textGrob("foo"))
58
+# is_abs_unit(unit(1, "mm") + unit(1, "npc"))
55 59
 #
56 60
 is_abs_unit = function(u) {
57 61
 	if(inherits(u, "unit.arithmetic")) .is_abs_unit.unit.arithmetic(u)
... ...
@@ -23,7 +23,10 @@
23 23
 # -remove_empty_columns if there is no alteration in that sample, whether remove it on the heatmap
24 24
 # -heatmap_legend_param pass to `Heatmap`
25 25
 # -top_annotation by default the top annotation contains barplots representing frequency of mutations in every sample.
26
+<<<<<<< HEAD
26 27
 # -top_annotation_height height of the top annotation, should be a `grid::unit` object.
28
+=======
29
+>>>>>>> master
27 30
 # -barplot_ignore alterations that you don't want to put on the barplots.
28 31
 # -... pass to `Heatmap`, so can set ``bottom_annotation`` here.
29 32
 #
... ...
@@ -55,8 +58,13 @@ oncoPrint = function(mat, get_type = function(x) x,
55 58
 	row_barplot_width = unit(2, "cm"),
56 59
 	remove_empty_columns = FALSE,
57 60
 	heatmap_legend_param = list(title = "Alterations"),
61
+<<<<<<< HEAD
58 62
 	top_annotation = HeatmapAnnotation(column_bar = anno_column_bar),
59 63
 	top_annotation_height = unit(2, "cm"),
64
+=======
65
+	top_annotation = HeatmapAnnotation(column_bar = anno_column_bar, 
66
+		annotation_height = unit(2, "cm")),
67
+>>>>>>> master
60 68
 	barplot_ignore = NULL,
61 69
 	...) {
62 70
 
... ...
@@ -81,8 +89,12 @@ oncoPrint = function(mat, get_type = function(x) x,
81 89
 		})
82 90
 	} else if(inherits(mat, "list")) {
83 91
 		mat_list = mat
92
+
84 93
 		all_type = names(mat_list)
85 94
 		mat_list = lapply(mat_list, function(x) {
95
+				if(!is.matrix(x)) {
96
+					stop("Expect a list of matrix (not data frames).")
97
+				}
86 98
 				oattr = attributes(x)
87 99
 				x = as.logical(x)
88 100
 				attributes(x) = oattr
... ...
@@ -250,7 +262,11 @@ oncoPrint = function(mat, get_type = function(x) x,
250 262
 				add_oncoprint(type, x, y, width, height)
251 263
 			}
252 264
 		}, show_column_names = show_column_names,
265
+<<<<<<< HEAD
253 266
 		top_annotation = top_annotation, top_annotation_height = top_annotation_height,
267
+=======
268
+		top_annotation = top_annotation,
269
+>>>>>>> master
254 270
 		heatmap_legend_param = heatmap_legend_param, ...)
255 271
 
256 272
 	if(show_row_barplot) {
... ...
@@ -273,6 +289,9 @@ oncoPrint = function(mat, get_type = function(x) x,
273 289
 # == details
274 290
 # All matrix will be unified to have same row names and column names
275 291
 #
292
+# == value
293
+# A list of matrix
294
+#
276 295
 # == author
277 296
 # Zuguang Gu <z.gu@dkfz.de>
278 297
 #
... ...
@@ -102,6 +102,8 @@ plotDataFrame = function(df, overlap = 0.25, nlevel = 30, show_row_names = TRUE,
102 102
 
103 103
 		if(is.null(main_heatmap)) {
104 104
 			main_heatmap = which.max(sapply(group, length))
105
+		} else if(!is.numeric(main_heatmap) && !is.null(group_names)) {
106
+			main_heatmap = which(group_names == main_heatmap)[1]
105 107
 		}
106 108
 
107 109
 		i_max = max(unlist(group))
... ...
@@ -82,8 +82,10 @@ default_col = function(x, main_matrix = FALSE) {
82 82
 # -dend a `stats::dendrogram` object.
83 83
 # -facing facing of the dendrogram.
84 84
 # -max_height maximum height of the dendrogram. It is useful to make dendrograms comparable
85
-#             if you want to plot more than one dendrograms.
85
+#             if you want to plot more than one dendrograms. Height for each dendrogram can be obtained by
86
+#             ``attr(dend, "height")``.
86 87
 # -order should leaves of dendrogram be put in the normal order (1, ..., n) or reverse order (n, ..., 1)?
88
+#        It may matters for the dendrograms putting on left and right.
87 89
 # -... pass to `grid::viewport` which contains the dendrogram.
88 90
 #
89 91
 # == details
... ...
@@ -466,14 +468,21 @@ list_component = function() {
466 468
 # -text a vector of text
467 469
 # -... pass to `grid::textGrob`
468 470
 #
471
+# == details
472
+# Simply calculate maximum width of a list of `grid::textGrob` objects.
473
+#
469 474
 # == value
470 475
 # A `grid::unit` object.
471 476
 #
472 477
 # == author
473 478
 # Zuguang Gu <z.gu@dkfz.de>
474 479
 #
480
+# == seealso
481
+# `max_text_width` is always used to calculate the size of viewport when there is text annotation (`anno_text`)
482
+#
475 483
 # == example
476
-# max_text_width(letters, gp = gpar(fontsize = 10))
484
+# x = c("a", "bb", "ccc")
485
+# max_text_width(x, gp = gpar(fontsize = 10))
477 486
 #
478 487
 max_text_width = function(text, ...) {
479 488
     max(do.call("unit.c", lapply(text, function(x) grobWidth(textGrob(x, ...)))))
... ...
@@ -486,14 +495,21 @@ max_text_width = function(text, ...) {
486 495
 # -text a vector of text
487 496
 # -... pass to `grid::textGrob`
488 497
 #
498
+# == details
499
+# Simply calculate maximum height of a list of `grid::textGrob` objects.
500
+#
489 501
 # == value
490 502
 # A `grid::unit` object.
491 503
 #
504
+# == seealso
505
+# `max_text_height` is always used to calculate the size of viewport when there is text annotation (`anno_text`)
506
+#
492 507
 # == author
493 508
 # Zuguang Gu <z.gu@dkfz.de>
494 509
 #
495 510
 # == example
496
-# max_text_height(letters, gp = gpar(fontsize = 10))
511
+# x = c("a", "b\nb", "c\nc\nc")
512
+# max_text_height(x, gp = gpar(fontsize = 10))
497 513
 #
498 514
 max_text_height = function(text, ...) {
499 515
     max(do.call("unit.c", lapply(text, function(x) grobHeight(textGrob(x, ...)))))
... ...
@@ -11,7 +11,7 @@ AdditiveUnit(...)
11 11
 }
12 12
 \arguments{
13 13
 
14
-  \item{...}{arguments.}
14
+  \item{...}{black hole arguments.}
15 15
 
16 16
 }
17 17
 \details{
... ...
@@ -26,7 +26,7 @@ Heatmap(matrix, col, name,
26 26
     row_dend_side = c("left", "right"),
27 27
     row_dend_width = unit(10, "mm"),
28 28
     show_row_dend = TRUE,
29
-    row_dend_reorder = FALSE,
29
+    row_dend_reorder = TRUE,
30 30
     row_dend_gp = gpar(),
31 31
     row_hclust_side = row_dend_side,
32 32
     row_hclust_width = row_dend_width,
... ...
@@ -40,7 +40,7 @@ Heatmap(matrix, col, name,
40 40
     column_dend_height = unit(10, "mm"),
41 41
     show_column_dend = TRUE,
42 42
     column_dend_gp = gpar(),
43
-    column_dend_reorder = FALSE,
43
+    column_dend_reorder = TRUE,
44 44
     column_hclust_side = column_dend_side,
45 45
     column_hclust_height = column_dend_height,
46 46
     show_column_hclust = show_column_dend,
... ...
@@ -7,7 +7,7 @@ Constructor method for HeatmapAnnotation class
7 7
 Constructor method for HeatmapAnnotation class
8 8
 }
9 9
 \usage{
10
-HeatmapAnnotation(df, name, col,
10
+HeatmapAnnotation(df, name, col, na_col = "grey",
11 11
     annotation_legend_param = list(),
12 12
     show_legend = TRUE,
13 13
     ...,
... ...
@@ -24,6 +24,7 @@ HeatmapAnnotation(df, name, col,
24 24
   \item{df}{a data frame. Each column will be treated as a simple annotation. The data frame must have column names.}
25 25
   \item{name}{name of the heatmap annotation, optional.}
26 26
   \item{col}{a list of colors which contains color mapping to columns in \code{df}. See \code{\link{SingleAnnotation}} for how to set colors.}
27
+  \item{na_col}{color for \code{NA} values in simple annotations.}
27 28
   \item{annotation_legend_param}{a list which contains parameters for annotation legends}
28 29
   \item{show_legend}{whether show legend for each column in \code{df}.}
29 30
   \item{...}{functions which define complex annotations. Values should be named arguments.}
... ...
@@ -8,6 +8,7 @@ Constructor method for SingleAnnotation class
8 8
 }
9 9
 \usage{
10 10
 SingleAnnotation(name, value, col, fun,
11
+    na_col = "grey",
11 12
     which = c("column", "row"),
12 13
     show_legend = TRUE,
13 14
     gp = gpar(col = NA),
... ...
@@ -15,10 +16,11 @@ SingleAnnotation(name, value, col, fun,
15 16
 }
16 17
 \arguments{
17 18
 
18
-  \item{name}{name for this annotation. If it is not specified, an internal name is assigned to it.}
19
+  \item{name}{name for this annotation. If it is not specified, an internal name is assigned.}
19 20
   \item{value}{A vector of discrete or continuous annotation.}
20 21
   \item{col}{colors corresponding to \code{value}. If the mapping is discrete mapping, the value of \code{col} should be a vector; If the mapping is continuous mapping, the value of \code{col} should be  a color mapping function. }
21 22
   \item{fun}{a self-defined function to add annotation graphics. The argument of this function should only  be a vector of index that corresponds to rows or columns.}
23
+  \item{na_col}{color for \code{NA} values in simple annotations.}
22 24
   \item{which}{is the annotation a row annotation or a column annotation?}
23 25
   \item{show_legend}{if it is a simple annotation, whether show legend when making the complete heatmap.}
24 26
   \item{gp}{Since simple annotation is represented as a row of grids. This argument controls graphic parameters for the simple annotation.}
... ...
@@ -42,6 +44,10 @@ and \code{fun} will be applied on each of the row slices.
42 44
 One thing that users should be careful is the difference of coordinates when the annotation is a row
43 45
 annotation or a column annotation.
44 46
 }
47
+\seealso{
48
+There are following built-in annotation functions that can be used to generate complex annotations: 
49
+\code{\link{anno_points}}, \code{\link{anno_barplot}}, \code{\link{anno_histogram}}, \code{\link{anno_boxplot}}, \code{\link{anno_density}}, \code{\link{anno_text}} and \code{\link{anno_link}}.
50
+}
45 51
 \value{
46 52
 A \code{\link{SingleAnnotation-class}} object.
47 53
 }
... ...
@@ -27,6 +27,9 @@ Sometimes there are many rows or columns in the heatmap and we want to mark some
27 27
 This annotation function is used to mark these rows and connect labels and corresponding rows
28 28
 with links.
29 29
 }
30
+\value{
31
+A graphic function which can be set in \code{\link{HeatmapAnnotation}} constructor method.
32
+}
30 33
 \author{
31 34
 Zuguang Gu <z.gu@dkfz.de>
32 35
 }
... ...
@@ -17,8 +17,13 @@ Get column dendrograms from a heatmap
17 17
 \value{
18 18
 A dendrogram object
19 19
 }
20
+\author{
21
+Zuguang Gu <z.gu@dkfz.de>
22
+}
20 23
 \examples{
21
-# There is no example
22
-NULL
23
-
24
+mat = matrix(rnorm(100), 10)
25
+ht = Heatmap(mat)
26
+column_dend(ht)
27
+ht = Heatmap(mat, km = 2)
28
+column_dend(ht)
24 29
 }
... ...
@@ -17,8 +17,13 @@ Get column dendrograms from a heatmap list
17 17
 \value{
18 18
 A list of dendrograms for which dendrogram corresponds to each matrix
19 19
 }
20
+\author{
21
+Zuguang Gu <z.gu@dkfz.de>
22
+}
20 23
 \examples{
21
-# There is no example
22
-NULL
23
-
24
+mat = matrix(rnorm(100), 10)
25
+ht_list = Heatmap(mat) + Heatmap(mat)
26
+column_dend(ht_list)
27
+ht_list = Heatmap(mat, km = 2) + Heatmap(mat)
28
+column_dend(ht_list)
24 29
 }
... ...
@@ -17,8 +17,13 @@ Get column order from a heatmap list
17 17
 \value{
18 18
 A vector containing column orders
19 19
 }
20
+\author{
21
+Zuguang Gu <z.gu@dkfz.de>
22
+}
20 23
 \examples{
21
-# There is no example
22
-NULL
23
-
24
+mat = matrix(rnorm(100), 10)
25
+ht = Heatmap(mat)
26
+column_order(ht)
27
+ht = Heatmap(mat, km = 2)
28
+column_order(ht)
24 29
 }
... ...
@@ -17,8 +17,13 @@ Get column order from a heatmap list
17 17
 \value{
18 18
 A list contains column orders which correspond every matrix
19 19
 }
20
+\author{
21
+Zuguang Gu <z.gu@dkfz.de>
22
+}
20 23
 \examples{
21
-# There is no example
22
-NULL
23
-
24
+mat = matrix(rnorm(100), 10)
25
+ht_list = Heatmap(mat) + Heatmap(mat)
26
+column_order(ht_list)
27
+ht = Heatmap(mat, km = 2) + Heatmap(mat)
28
+column_order(ht_list)
24 29
 }
... ...
@@ -7,7 +7,7 @@ Decorate the heatmap annotation
7 7
 Decorate the heatmap annotation
8 8
 }
9 9
 \usage{
10
-decorate_annotation(annotation, code, slice = NULL)
10
+decorate_annotation(annotation, code, slice)
11 11
 }
12 12
 \arguments{
13 13
 
... ...
@@ -11,9 +11,9 @@ decorate_heatmap_body(heatmap, code, slice = 1)
11 11
 }
12 12
 \arguments{
13 13
 
14
-  \item{heatmap}{name of the heatmap}
14
+  \item{heatmap}{name of the heatmap which is set as \code{name} option in \code{\link{Heatmap}} function}
15 15
   \item{code}{code that adds graphics in the selected heatmap body}
16
-  \item{slice}{index of row slices in the heatmap}
16
+  \item{slice}{index of row slices in the heatmap if it is split by rows}
17 17
 
18 18
 }
19 19
 \details{
... ...
@@ -33,8 +33,11 @@ colnames(mat) = letters[1:10]
33 33
 
34 34
 d2 = dist2(mat)
35 35
 d2 = dist2(mat, pairwise_fun = function(x, y) 1 - cor(x, y))
36
+# distance only calculated within 10 and 90 quantile of each vector
36 37
 d2 = dist2(mat, pairwise_fun = function(x, y) {
37
-    l = is.na(x) & is.na(y)
38
+	q1 = quantile(x, c(0.1, 0.9))
39
+	q2 = quantile(y, c(0.1, 0.9))
40
+    l = x > q1[1] & x < q1[2] & y > q2[1] & y < q2[2]
38 41
     sqrt(sum((x[l] - y[l])^2))
39 42
 })
40 43
 
... ...
@@ -11,6 +11,7 @@ enhanced_basicplot(data, ..., ylim = NULL,
11 11
     ylab = deparse(substitute(data)), title = NULL, title_gp = gpar(fontsize = 14),
12 12
     type = c("boxplot", "barplot"), width = 0.8, gp = gpar(),
13 13
     pch = 1, size = unit(2, "mm"), axis_gp = gpar(fontsize = 8),
14
+    padding = unit(c(2, 18, 2, 2), "mm"),
14 15
     heatmap_legend_list = list())
15 16
 }
16 17
 \arguments{
... ...
@@ -27,6 +28,7 @@ enhanced_basicplot(data, ..., ylim = NULL,
27 28
   \item{pch}{shape of outlier points in the boxplot}
28 29
   \item{size}{size of hte outlier points in the boxplot}
29 30
   \item{axis_gp}{graphic parameters for the axis}
31
+  \item{padding}{padding of the plot}
30 32
   \item{heatmap_legend_list}{a list of \code{\link[grid]{grob}} which contains legend. It can be generated by \code{\link{color_mapping_legend,ColorMapping-method}}.}
31 33
 
32 34
 }
... ...
@@ -14,8 +14,8 @@ grid.dendrogram(dend, facing = c("bottom", "top", "left", "right"),
14 14
 
15 15
   \item{dend}{a \code{\link[stats]{dendrogram}} object.}
16 16
   \item{facing}{facing of the dendrogram.}
17
-  \item{max_height}{maximum height of the dendrogram. It is useful to make dendrograms comparable if you want to plot more than one dendrograms.}
18
-  \item{order}{should leaves of dendrogram be put in the normal order (1, ..., n) or reverse order (n, ..., 1)?}
17
+  \item{max_height}{maximum height of the dendrogram. It is useful to make dendrograms comparable if you want to plot more than one dendrograms. Height for each dendrogram can be obtained by \code{attr(dend, "height")}.}
18
+  \item{order}{should leaves of dendrogram be put in the normal order (1, ..., n) or reverse order (n, ..., 1)? It may matters for the dendrograms putting on left and right.}
19 19
   \item{...}{pass to \code{\link[grid]{viewport}} which contains the dendrogram.}
20 20
 
21 21
 }
... ...
@@ -1,10 +1,10 @@
1 1
 \name{ht_global_opt}
2 2
 \alias{ht_global_opt}
3 3
 \title{
4
-Global options for heatmaps
4
+Global graphic options for heatmaps
5 5
 }
6 6
 \description{
7
-Global options for heatmaps
7
+Global graphic options for heatmaps
8 8
 }
9 9
 \usage{
10 10
 ht_global_opt(..., RESET = FALSE, READ.ONLY = NULL)
... ...
@@ -18,8 +18,8 @@ ht_global_opt(..., RESET = FALSE, READ.ONLY = NULL)
18 18
 }
19 19
 \details{
20 20
 You can set some parameters for all heatmaps/annotations simultaneously by this global function.
21
-Pleast note you should better to put it in the first beginning of your heatmap code and reset
22
-all option values to get avoid of affecting next heatmap plotting.
21
+Pleast note you should put it before your heatmap code and reset
22
+all option values after drawing the heatmaps to get rid of affecting next heatmap plotting.
23 23
 
24 24
 There are following parameters:
25 25
 
... ...
@@ -17,6 +17,9 @@ is_abs_unit(u)
17 17
 \details{
18 18
 Besides the normal absolute units (e.g. "mm", "inches"), this function
19 19
 simply treat \code{\link[grid]{grob}} objects as absolute units.
20
+
21
+For a complex unit which is combination of different units, it is absolute
22
+only if all units included are absolute units.
20 23
 }
21 24
 \value{
22 25
 A logical value.
... ...
@@ -28,4 +31,5 @@ Zuguang Gu <z.gu@dkfz.de>
28 31
 is_abs_unit(unit(1, "mm"))
29 32
 is_abs_unit(unit(1, "npc"))
30 33
 is_abs_unit(textGrob("foo"))
34
+is_abs_unit(unit(1, "mm") + unit(1, "npc"))
31 35
 }
... ...
@@ -14,13 +14,20 @@ max_text_height(text, ...)
14 14
   \item{text}{a vector of text}
15 15
   \item{...}{pass to \code{\link[grid]{textGrob}}}
16 16
 
17
+}
18
+\details{
19
+Simply calculate maximum height of a list of \code{\link[grid]{textGrob}} objects.
17 20
 }
18 21
 \value{
19 22
 A \code{\link[grid]{unit}} object.
20 23
 }
24
+\seealso{
25
+\code{\link{max_text_height}} is always used to calculate the size of viewport when there is text annotation (\code{\link{anno_text}})
26
+}
21 27
 \author{
22 28
 Zuguang Gu <z.gu@dkfz.de>
23 29
 }
24 30
 \examples{
25
-max_text_height(letters, gp = gpar(fontsize = 10))
31
+x = c("a", "b\nb", "c\nc\nc")
32
+max_text_height(x, gp = gpar(fontsize = 10))
26 33
 }
... ...
@@ -14,6 +14,9 @@ max_text_width(text, ...)
14 14
   \item{text}{a vector of text}
15 15
   \item{...}{pass to \code{\link[grid]{textGrob}}}
16 16
 
17
+}
18
+\details{
19
+Simply calculate maximum width of a list of \code{\link[grid]{textGrob}} objects.
17 20
 }
18 21
 \value{
19 22
 A \code{\link[grid]{unit}} object.
... ...
@@ -21,6 +24,10 @@ A \code{\link[grid]{unit}} object.
21 24
 \author{
22 25
 Zuguang Gu <z.gu@dkfz.de>
23 26
 }
27
+\seealso{
28
+\code{\link{max_text_width}} is always used to calculate the size of viewport when there is text annotation (\code{\link{anno_text}})
29
+}
24 30
 \examples{
25
-max_text_width(letters, gp = gpar(fontsize = 10))
31
+x = c("a", "bb", "ccc")
32
+max_text_width(x, gp = gpar(fontsize = 10))
26 33
 }
... ...
@@ -18,8 +18,8 @@ oncoPrint(mat, get_type = function(x) x,
18 18
     row_barplot_width = unit(2, "cm"),
19 19
     remove_empty_columns = FALSE,
20 20
     heatmap_legend_param = list(title = "Alterations"),
21
-    top_annotation = HeatmapAnnotation(column_bar = anno_column_bar),
22
-    top_annotation_height = unit(2, "cm"),
21
+    top_annotation = HeatmapAnnotation(column_bar = anno_column_bar,
22
+    annotation_height = unit(2, "cm")),
23 23
     barplot_ignore = NULL,
24 24
     ...)
25 25
 }
... ...
@@ -39,7 +39,6 @@ oncoPrint(mat, get_type = function(x) x,
39 39
   \item{remove_empty_columns}{if there is no alteration in that sample, whether remove it on the heatmap}
40 40
   \item{heatmap_legend_param}{pass to \code{\link{Heatmap}}}
41 41
   \item{top_annotation}{by default the top annotation contains barplots representing frequency of mutations in every sample.}
42
-  \item{top_annotation_height}{height of the top annotation, should be a \code{\link[grid]{unit}} object.}
43 42
   \item{barplot_ignore}{alterations that you don't want to put on the barplots.}
44 43
   \item{...}{pass to \code{\link{Heatmap}}, so can set \code{bottom_annotation} here.}
45 44
 
... ...
@@ -17,8 +17,13 @@ Get row dendrograms from a heatmap
17 17
 \value{
18 18
 A list of dendrograms for which each dendrogram corresponds to a row slice
19 19
 }
20
+\author{
21
+Zuguang Gu <z.gu@dkfz.de>
22
+}
20 23
 \examples{
21
-# There is no example
22
-NULL
23
-
24
+mat = matrix(rnorm(100), 10)
25
+ht = Heatmap(mat)
26
+row_dend(ht)
27
+ht = Heatmap(mat, km = 2)
28
+row_dend(ht)
24 29
 }
... ...
@@ -17,8 +17,13 @@ Get row dendrograms from a heatmap list
17 17
 \value{
18 18
 A list of dendrograms for which each dendrogram corresponds to a row slice
19 19
 }
20
+\author{
21
+Zuguang Gu <z.gu@dkfz.de>
22
+}
20 23
 \examples{
21
-# There is no example
22
-NULL
23
-
24
+mat = matrix(rnorm(100), 10)
25
+ht_list = Heatmap(mat) + Heatmap(mat)
26
+row_dend(ht_list)
27
+ht_list = Heatmap(mat, km = 2) + Heatmap(mat)
28
+row_dend(ht_list)
24 29
 }
... ...
@@ -17,8 +17,13 @@ Get row order from a heatmap
17 17
 \value{
18 18
 A list contains row orders which correspond to the original matrix
19 19
 }
20
+\author{
21
+Zuguang Gu <z.gu@dkfz.de>
22
+}
20 23
 \examples{
21
-# There is no example
22
-NULL
23
-
24
+mat = matrix(rnorm(100), 10)
25
+ht = Heatmap(mat)
26
+row_order(ht)
27
+ht = Heatmap(mat, km = 2)
28
+row_order(ht)
24 29
 }
... ...
@@ -17,8 +17,13 @@ Get row order from a heatmap list
17 17
 \value{
18 18
 A list contains row orders which correspond to the original matrix
19 19
 }
20
+\author{
21
+Zuguang Gu <z.gu@dkfz.de>
22
+}
20 23
 \examples{
21
-# There is no example
22
-NULL
23
-
24
+mat = matrix(rnorm(100), 10)
25
+ht_list = Heatmap(mat) + Heatmap(mat)
26
+row_order(ht_list)
27
+ht = Heatmap(mat, km = 2) + Heatmap(mat)
28
+row_order(ht_list)
24 29
 }
... ...
@@ -18,6 +18,9 @@ unify_mat_list(mat_list, default = 0)
18 18
 \details{
19 19
 All matrix will be unified to have same row names and column names
20 20
 }
21
+\value{
22
+A list of matrix
23
+}
21 24
 \author{
22 25
 Zuguang Gu <z.gu@dkfz.de>
23 26
 }
... ...
@@ -76,6 +76,20 @@ ha
76 76
 draw(ha, 1:10)
77 77
 ```
78 78
 
79
+Color for `NA` can be set by `na_col`:
80
+
81
+```{r, fig.width = 7, fig.height = 1}
82
+df2 = data.frame(type = c(rep("a", 5), rep("b", 5)),
83
+                age = sample(1:20, 10))
84
+df2$type[5] = NA
85
+df2$age[5] = NA
86
+ha = HeatmapAnnotation(df = df2, 
87
+  col = list(type = c("a" =  "red", "b" = "blue"),
88
+             age = colorRamp2(c(0, 20), c("white", "red"))),
89
+  na_col = "grey")
90
+draw(ha, 1:10)
91
+```
92
+
79 93
 Put more than one annotations by a data frame.
80 94
 
81 95
 ```{r heatmap_annotation_mixed, fig.width = 7, fig.height = 1}
... ...
@@ -531,7 +545,7 @@ upViewport(2)
531 545
 
532 546
 ## Mark some of the rows/columns
533 547
 
534
-From version 1.7.4, a new annotation function `anno_link()` was added which connects labels and subset of the rows
548
+From version 1.8.0, a new annotation function `anno_link()` was added which connects labels and subset of the rows
535 549
 by links. It is helpful when there are many rows/columns and we want to mark some of the rows (e.g. in a gene expression
536 550
 matrix, we want to mark some important genes of interest.)
537 551
 
... ...
@@ -133,8 +133,7 @@ decorate_heatmap_body("ht1", {
133 133
     grid.lines(c(0.5, 0.5), c(0, 1), gp = gpar(lty = 2, lwd = 2))
134 134
 }, slice = 2)
135 135
 
136
-suppressPackageStartupMessages(library(dendextend))
137
-decorate_dend("ht1", {
136
+decorate_column_dend("ht1", {
138 137
     tree = column_dend(ht_list)$ht1
139 138
     ind = cutree(as.hclust(tree), k = 2)[order.dendrogram(tree)]
140 139
 
... ...
@@ -144,13 +143,13 @@ decorate_dend("ht1", {
144 143
     x2 = c(last_index(ind == 1), last_index(ind == 2))
145 144
     grid.rect(x = x1/length(ind), width = (x2 - x1)/length(ind), just = "left",
146 145
         default.units = "npc", gp = gpar(fill = c("#FF000040", "#00FF0040"), col = NA))
147
-}, which = "column")
146
+})
148 147
 
149
-decorate_dimnames("ht2", {
148
+decorate_row_names("ht2", {
150 149
     grid.rect(gp = gpar(fill = "#FF000040"))
151
-}, which = "row", slice = 2)
150
+}, slice = 2)
152 151
 
153
-decorate_title("ht1", {
152
+decorate_row_title("ht1", {
154 153
     grid.rect(gp = gpar(fill = "#00FF0040"))
155 154
 }, which = "row", slice = 1)
156 155