Browse code

annotations support drawing names

Zuguang Gu authored on 12/06/2016 18:34:55
Showing 10 changed files

... ...
@@ -1,100 +1,96 @@
1
-export(column_anno_histogram)
2
-export(anno_boxplot)
3
-exportMethods(column_order)
1
+export('+.AdditiveUnit')
2
+export(AdditiveUnit)
4 3
 export(ColorMapping)
4
+export(Heatmap)
5 5
 export(HeatmapAnnotation)
6
+export(HeatmapList)
7
+export(Legend)
8
+export(SingleAnnotation)
9
+export(anno_barplot)
10
+export(anno_boxplot)
11
+export(anno_density)
12
+export(anno_histogram)
13
+export(anno_link)
14
+export(anno_points)
15
+export(anno_text)
16
+export(columnAnnotation)
17
+export(column_anno_barplot)
6 18
 export(column_anno_boxplot)
7
-export(selectArea)
8
-export(row_anno_barplot)
9
-export(Heatmap)
10
-export(row_anno_points)
19
+export(column_anno_density)
20
+export(column_anno_histogram)
21
+export(column_anno_link)
22
+export(column_anno_points)
11 23
 export(column_anno_text)
12
-export(decorate_row_dend)
13
-export(decorate_column_dend)
14
-exportMethods(draw)
15
-export(unify_mat_list)
16
-exportMethods(draw_heatmap_body)
17
-exportMethods(color_mapping_legend)
18
-exportMethods(prepare)
19 24
 export(decorate_annotation)
20
-exportMethods(map_to_colors)
25
+export(decorate_column_dend)
26
+export(decorate_column_names)
27
+export(decorate_column_title)
28
+export(decorate_dend)
21 29
 export(decorate_dimnames)
22
-export(column_anno_points)
23
-exportMethods(component_height)
24
-export(row_anno_text)
25
-exportClasses(SingleAnnotation)
26
-export(SingleAnnotation)
27
-export(oncoPrint)
28
-exportClasses(AdditiveUnit)
29
-export(AdditiveUnit)
30
-export(max_text_height)
30
+export(decorate_heatmap_body)
31
+export(decorate_row_dend)
32
+export(decorate_row_names)
33
+export(decorate_row_title)
34
+export(decorate_title)
35
+export(densityHeatmap)
36
+export(dist2)
31 37
 export(enhanced_basicplot)
32
-exportMethods(annotation_legend_size)
33
-exportMethods(row_order)
34
-export(Legend)
35
-export(AdditiveUnit)
36
-exportMethods(draw_heatmap_list)
37
-export(row_anno_density)
38
+export(grid.dendrogram)
39
+export(ht_global_opt)
38 40
 export(is_abs_unit)
39
-export(dist2)
40
-export(decorate_heatmap_body)
41
-exportMethods(draw_heatmap_legend)
42
-exportMethods(add_heatmap)
43
-export(anno_barplot)
44
-exportMethods(row_dend)
45
-export(row_anno_boxplot)
41
+export(max_text_height)
46 42
 export(max_text_width)
47
-export(anno_link)
48
-exportMethods(make_layout)
49
-export(decorate_row_title)
50
-export(anno_histogram)
43
+export(oncoPrint)
51 44
 export(plotDataFrame)
52
-exportMethods(draw_dimnames)
45
+export(rowAnnotation)
46
+export(row_anno_barplot)
47
+export(row_anno_boxplot)
48
+export(row_anno_density)
49
+export(row_anno_histogram)
50
+export(row_anno_link)
51
+export(row_anno_points)
52
+export(row_anno_text)
53
+export(selectArea)
54
+export(unify_mat_list)
55
+exportClasses(AdditiveUnit)
56
+export(AdditiveUnit)
53 57
 exportClasses(ColorMapping)
54 58
 export(ColorMapping)
59
+exportClasses(Heatmap)
60
+export(Heatmap)
55 61
 exportClasses(HeatmapAnnotation)
56 62
 export(HeatmapAnnotation)
57
-export(anno_points)
58
-exportMethods(draw_title)
59
-export(ht_global_opt)
60
-export('+.AdditiveUnit')
61
-export(decorate_column_names)
62
-export(column_anno_barplot)
63
-export(densityHeatmap)
64
-exportMethods(heatmap_legend_size)
65 63
 exportClasses(HeatmapList)
66 64
 export(HeatmapList)
67
-export(column_anno_density)
68
-exportClasses(Heatmap)
69
-export(Heatmap)
70
-exportMethods(draw_annotation_legend)
71
-exportMethods(column_dend)
72
-exportMethods(set_component_height)
73
-export(row_anno_link)
74
-exportMethods(make_column_cluster)
75
-export(HeatmapList)
76
-exportMethods(draw_annotation)
65
+exportClasses(SingleAnnotation)
77 66
 export(SingleAnnotation)
78
-export(row_anno_histogram)
79
-exportMethods(get_color_mapping_list)
80
-exportMethods(make_row_cluster)
67
+exportMethods(add_heatmap)
68
+exportMethods(annotation_legend_size)
69
+exportMethods(color_mapping_legend)
70
+exportMethods(column_dend)
71
+exportMethods(column_order)
72
+exportMethods(component_height)
81 73
 exportMethods(component_width)
82
-export(decorate_column_title)
74
+exportMethods(draw)
75
+exportMethods(draw_annotation)
76
+exportMethods(draw_annotation_legend)
83 77
 exportMethods(draw_dend)
78
+exportMethods(draw_dimnames)
79
+exportMethods(draw_heatmap_body)
80
+exportMethods(draw_heatmap_legend)
81
+exportMethods(draw_heatmap_list)
82
+exportMethods(draw_title)
83
+exportMethods(get_color_mapping_list)
84 84
 exportMethods(get_color_mapping_param_list)
85
-export(grid.dendrogram)
86
-export(decorate_title)
87
-export(decorate_dend)
88
-export(rowAnnotation)
89
-export(column_anno_link)
90
-export(columnAnnotation)
91
-export(decorate_row_names)
92
-export(anno_text)
93
-export(anno_density)
94
-
95
-
96
-
97
-
85
+exportMethods(heatmap_legend_size)
86
+exportMethods(make_column_cluster)
87
+exportMethods(make_layout)
88
+exportMethods(make_row_cluster)
89
+exportMethods(map_to_colors)
90
+exportMethods(prepare)
91
+exportMethods(row_dend)
92
+exportMethods(row_order)
93
+exportMethods(set_component_height)
98 94
 
99 95
 import(grDevices)
100 96
 import(graphics)
... ...
@@ -113,12 +109,9 @@ importFrom("colorspace", rainbow_hcl)
113 109
 importFrom("dendextend", "labels<-")
114 110
 importFrom("dendextend", get_branches_heights)
115 111
 importFrom("dendextend", nnodes)
112
+importFrom("methods", "new", "show")
116 113
 importFrom("methods", setClass)
117 114
 importFrom("methods", setGeneric)
118 115
 importFrom("methods", setMethod)
119
-importFrom("methods", "new", "show")
120 116
 importFrom("utils", "getFromNamespace")
121 117
 
122
-
123
-
124
-
... ...
@@ -1,6 +1,7 @@
1 1
 CHANGES in VERSION 1.11.5
2 2
 
3 3
 * `gap` in `HeatmapAnnotation` has been adjusted
4
+* annotations support drawing names of either sides
4 5
 
5 6
 =============================
6 7
 
... ...
@@ -25,10 +25,10 @@ setGeneric('prepare', function(object, ...) standardGeneric('prepare'))
25 25
 
26 26
 setGeneric('draw_annotation', function(object, ...) standardGeneric('draw_annotation'))
27 27
 
28
-setGeneric('draw_dimnames', function(object, ...) standardGeneric('draw_dimnames'))
29
-
30 28
 setGeneric('get_color_mapping_param_list', function(object, ...) standardGeneric('get_color_mapping_param_list'))
31 29
 
30
+setGeneric('draw_dimnames', function(object, ...) standardGeneric('draw_dimnames'))
31
+
32 32
 setGeneric('color_mapping_legend', function(object, ...) standardGeneric('color_mapping_legend'))
33 33
 
34 34
 setGeneric('draw', function(object, ...) standardGeneric('draw'))
... ...
@@ -52,6 +52,11 @@ HeatmapAnnotation = setClass("HeatmapAnnotation",
52 52
 # -width width of the whole heatmap annotations, only used for row annotation when appending to the list of heatmaps.
53 53
 # -gp graphic parameters for simple annotations.
54 54
 # -gap gap between each annotation
55
+# -show_annotation_name whether show annotation names. For column annotation, annotation names are drawn either on the left
56
+#   or the right, and for row annotations, names are draw either on top to at bottom. The value can be a vector.
57
+# -annotation_name_gp graphic parameters for anntation names. Graphic paramters can be vectors.
58
+# -annotation_name_offset offset to the annotations, `grid::unit` object. The value can be a vector.
59
+# -annotation_name_side side of the annotation names.
55 60
 #
56 61
 # == details
57 62
 # The simple annotations are defined by ``df`` and ``col`` arguments. Complex annotations are
... ...
@@ -76,7 +81,11 @@ HeatmapAnnotation = function(df, name, col, na_col = "grey",
76 81
 	height = calc_anno_size(), 
77 82
 	width = calc_anno_size(), 
78 83
 	gp = gpar(col = NA),
79
-	gap = unit(0, "mm")) {
84
+	gap = unit(0, "mm"),
85
+	show_annotation_name = FALSE,
86
+	annotation_name_gp = gpar(),
87
+	annotation_name_offset = unit(2, "mm"),
88
+	annotation_name_side = ifelse(which == "column", "right", "bottom")) {
80 89
 
81 90
 	.Object = new("HeatmapAnnotation")
82 91
 
... ...
@@ -94,7 +103,8 @@ HeatmapAnnotation = function(df, name, col, na_col = "grey",
94 103
     arg_list = as.list(match.call())[-1]
95 104
     called_args = names(arg_list)
96 105
     anno_args = setdiff(called_args, c("name", "col", "na_col", "annotation_legend_param", "show_legend", "which", 
97
-    	                             "annotation_height", "annotation_width", "height", "width", "gp", "gap"))
106
+    	                             "annotation_height", "annotation_width", "height", "width", "gp", "gap",
107
+    	                             "show_annotation_name", "annotation_name_gp", "annotation_name_offset", "annotation_name_side"))
98 108
     if(any(anno_args == "")) stop("annotations should have names.")
99 109
     if(any(duplicated(anno_args))) stop("names of annotations should be unique.")
100 110
     anno_arg_list = list(...)
... ...
@@ -143,7 +153,27 @@ HeatmapAnnotation = function(df, name, col, na_col = "grey",
143 153
 		}
144 154
 	}
145 155
 
156
+	n_total_anno = 0
157
+	for(ag in anno_args) {
158
+		if(ag == "df") {
159
+			n_total_anno = n_total_anno + ncol(df)
160
+		} else {
161
+			n_total_anno = n_total_anno + 1
162
+		}
163
+	}
164
+	if(length(show_annotation_name) == 1) {
165
+    	show_annotation_name = rep(show_annotation_name, n_total_anno)
166
+    }
167
+    if(length(annotation_name_offset) == 1) {
168
+    	annotation_name_offset = rep(annotation_name_offset, n_total_anno)
169
+    }
170
+    if(length(annotation_name_side) == 1) {
171
+    	annotation_name_side = rep(annotation_name_side, n_total_anno)
172
+    }
173
+    annotation_name_gp = recycle_gp(annotation_name_gp, n_total_anno)
174
+
146 175
 	i_simple = 0
176
+	i_anno = 0
147 177
 	simple_length = NULL
148 178
     for(ag in anno_args) {
149 179
 		if(ag == "df") {
... ...
@@ -161,21 +191,35 @@ HeatmapAnnotation = function(df, name, col, na_col = "grey",
161 191
 
162 192
 		    if(missing(col)) {
163 193
 		        for(i in seq_len(n_anno)) {
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]])))
194
+		        	i_anno = i_anno + 1
195
+		        	anno_list = c(anno_list, list(SingleAnnotation(name = anno_name[i], value = df[, i], na_col = na_col, which = which, 
196
+		        		show_legend = show_legend[i_simple + i], gp = gp, legend_param = annotation_legend_param[[i_simple + i]],
197
+		        		show_name = show_annotation_name[i_anno], name_gp = subset_gp(annotation_name_gp, i_anno), 
198
+		        		name_offset = annotation_name_offset[i_anno], name_side = annotation_name_side[i_anno])))
165 199
 		        }
166 200
 		    } else {
167 201
 		        for(i in seq_len(n_anno)) {
202
+		        	i_anno = i_anno + 1
168 203
 		        	if(is.null(col[[ anno_name[i] ]])) { # if the color is not provided
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]])))
204
+		        		anno_list = c(anno_list, list(SingleAnnotation(name = anno_name[i], value = df[, i], na_col = na_col, which = which, 
205
+		        			show_legend = show_legend[i_simple + i], gp = gp, legend_param = annotation_legend_param[[i_simple + i]],
206
+		        			show_name = show_annotation_name[i_anno], name_gp = subset_gp(annotation_name_gp, i_anno), 
207
+		        			name_offset = annotation_name_offset[i_anno], name_side = annotation_name_side[i_anno])))
170 208
 		        	} else {
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]])))
209
+		        		anno_list = c(anno_list, list(SingleAnnotation(name = anno_name[i], value = df[, i], na_col = na_col, col = col[[ anno_name[i] ]], 
210
+		        			which = which, show_legend = show_legend[i_simple + i], gp = gp, legend_param = annotation_legend_param[[i_simple + i]],
211
+		        			show_name = show_annotation_name[i_anno], name_gp = subset_gp(annotation_name_gp, i_anno), 
212
+		        			name_offset = annotation_name_offset[i_anno], name_side = annotation_name_side[i_anno])))
172 213
 		        	}
173 214
 		        }
174 215
 		    }
175 216
 		    i_simple = i_simple + n_anno
176 217
 		} else {
218
+			i_anno = i_anno + 1
177 219
 			if(inherits(anno_arg_list[[ag]], "function")) {
178
-				anno_list = c(anno_list, list(SingleAnnotation(name = ag, fun = anno_arg_list[[ag]], which = which)))
220
+				anno_list = c(anno_list, list(SingleAnnotation(name = ag, fun = anno_arg_list[[ag]], which = which,
221
+					show_name = show_annotation_name[i_anno], name_gp = subset_gp(annotation_name_gp, i_anno), 
222
+		        	name_offset = annotation_name_offset[i_anno], name_side = annotation_name_side[i_anno])))
179 223
 			} else if(is.atomic(anno_arg_list[[ag]])) {
180 224
 
181 225
 			    if(is.null(simple_length)) {
... ...
@@ -184,12 +228,21 @@ HeatmapAnnotation = function(df, name, col, na_col = "grey",
184 228
 			    	stop("length of simple annotations differ.")
185 229
 			    }
186 230
 				if(missing(col)) {
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]])))
231
+			        anno_list = c(anno_list, list(SingleAnnotation(name = ag, value = anno_arg_list[[ag]], na_col = na_col, which = which, 
232
+			        	show_legend = show_legend[i_simple + 1], gp = gp, legend_param = annotation_legend_param[[i_simple + 1]],
233
+			        	show_name = show_annotation_name[i_anno], name_gp = subset_gp(annotation_name_gp, i_anno), 
234
+		        		name_offset = annotation_name_offset[i_anno], name_side = annotation_name_side[i_anno])))
188 235
 			    } else {
189 236
 			        if(is.null(col[[ ag ]])) { # if the color is not provided
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]])))
237
+			        	anno_list = c(anno_list, list(SingleAnnotation(name = ag, value = anno_arg_list[[ag]], na_col = na_col, which = which, 
238
+			        		show_legend = show_legend[i_simple + 1], gp = gp, legend_param = annotation_legend_param[[i_simple + 1]],
239
+			        		show_name = show_annotation_name[i_anno], name_gp = subset_gp(annotation_name_gp, i_anno), 
240
+		        		name_offset = annotation_name_offset[i_anno], name_side = annotation_name_side[i_anno])))
191 241
 			        } else {
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]])))
242
+			        	anno_list = c(anno_list, list(SingleAnnotation(name = ag, value = anno_arg_list[[ag]], na_col = na_col, col = col[[ ag ]], 
243
+			        		which = which, show_legend = show_legend[i_simple + 1], gp = gp, legend_param = annotation_legend_param[[i_simple + 1]],
244
+			        		show_name = show_annotation_name[i_anno], name_gp = subset_gp(annotation_name_gp, i_anno), 
245
+		        			name_offset = annotation_name_offset[i_anno], name_side = annotation_name_side[i_anno])))
193 246
 			        }
194 247
 			    }
195 248
 			    i_simple = i_simple + 1
... ...
@@ -199,19 +252,19 @@ HeatmapAnnotation = function(df, name, col, na_col = "grey",
199 252
 		}
200 253
 	}
201 254
 
202
-	n_anno = length(anno_list)
255
+	n_total_anno = length(anno_list)
203 256
 
204 257
 	if(is.null(gap)) gap = unit(0, "mm")
205 258
 
206 259
 	# the nth gap does not really matter
207 260
     if(length(gap) == 1) {
208
-    	.Object@gap = rep(gap, n_anno)
209
-    } else if(length(gap) == n_anno - 1) {
261
+    	.Object@gap = rep(gap, n_total_anno)
262
+    } else if(length(gap) == n_total_anno - 1) {
210 263
     	.Object@gap = unit.c(gap, unit(0, "mm"))
211
-    } else if(length(gap) < n_anno - 1) {
264
+    } else if(length(gap) < n_total_anno - 1) {
212 265
     	stop("Length of `gap` is wrong.")
213 266
     } else {
214
-    	gap[n_anno] = unit(0, "mm")
267
+    	gap[n_total_anno] = unit(0, "mm")
215 268
     	.Object@gap = gap
216 269
     }
217 270
 
... ...
@@ -221,7 +274,7 @@ HeatmapAnnotation = function(df, name, col, na_col = "grey",
221 274
 
222 275
 	if(length(anno_size) == 1) {
223 276
 		if(!is.unit(anno_size)) {
224
-			anno_size = rep(anno_size, n_anno)
277
+			anno_size = rep(anno_size, n_total_anno)
225 278
 		}
226 279
 	}
227 280
 
... ...
@@ -61,6 +61,10 @@ SingleAnnotation = setClass("SingleAnnotation",
61 61
 # -show_legend if it is a simple annotation, whether show legend when making the complete heatmap.
62 62
 # -gp Since simple annotation is represented as a row of grids. This argument controls graphic parameters for the simple annotation.
63 63
 # -legend_param parameters for the legend. See `color_mapping_legend,ColorMapping-method` for options.
64
+# -show_name whether show annotation name
65
+# -name_gp graphic parameters for annotation name
66
+# -name_offset offset to the annotation, a `grid::unit` object
67
+# -name_side 'right' and 'left' for column annotations and 'top' and 'bottom' for row annotations
64 68
 #
65 69
 # == details
66 70
 # The most simple annotation is one row or one column grids in which different colors
... ...
@@ -109,11 +109,18 @@ ht_global_opt = setGlobalOptions(
109 109
 		.value = FALSE,
110 110
 		.filter = function(x) {
111 111
 				if(x) {
112
-					ComplexHeatmap:::hclust = fastcluster::hclust 
112
+					if(require(fastcluster)) {
113
+						assign("hclust", envir = topenv()) = getFromNamespace("hclust", "fastcluster")
114
+					} else {
115
+						stop("Cannot find fastcluster package.")
116
+					}
113 117
 				} else {
114
-					ComplexHeatmap:::hclust = stats::hclust
118
+					assign("hclust", envir = topenv()) = getFromNamespace("hclust", "stats")
115 119
 				}
116 120
 				x
117 121
 			}
118 122
 		)
119 123
 )
124
+
125
+hclust = getFromNamespace("hclust", "stats")
126
+
... ...
@@ -39,8 +39,6 @@ increase_color_mapping_index = function() {
39 39
     INDEX_ENV$I_COLOR_MAPPING = INDEX_ENV$I_COLOR_MAPPING + 1
40 40
 }
41 41
 
42
-hclust = stats::hclust
43
-
44 42
 # default colors for matrix or annotations
45 43
 # this function should be improved later
46 44
 default_col = function(x, main_matrix = FALSE) {
... ...
@@ -17,7 +17,11 @@ HeatmapAnnotation(df, name, col, na_col = "grey",
17 17
     height = calc_anno_size(),
18 18
     width = calc_anno_size(),
19 19
     gp = gpar(col = NA),
20
-    gap = unit(0, "mm"))
20
+    gap = unit(0, "mm"),
21
+    show_annotation_name = FALSE,
22
+    annotation_name_gp = gpar(),
23
+    annotation_name_offset = unit(2, "mm"),
24
+    annotation_name_side = ifelse(which == "column", "right", "bottom"))
21 25
 }
22 26
 \arguments{
23 27
 
... ...
@@ -35,6 +39,10 @@ HeatmapAnnotation(df, name, col, na_col = "grey",
35 39
   \item{width}{width of the whole heatmap annotations, only used for row annotation when appending to the list of heatmaps.}
36 40
   \item{gp}{graphic parameters for simple annotations.}
37 41
   \item{gap}{gap between each annotation}
42
+  \item{show_annotation_name}{whether show annotation names. For column annotation, annotation names are drawn either on the left or the right, and for row annotations, names are draw either on top to at bottom. The value can be a vector.}
43
+  \item{annotation_name_gp}{graphic parameters for anntation names. Graphic paramters can be vectors.}
44
+  \item{annotation_name_offset}{offset to the annotations, \code{\link[grid]{unit}} object. The value can be a vector.}
45
+  \item{annotation_name_side}{side of the annotation names.}
38 46
 
39 47
 }
40 48
 \details{
... ...
@@ -12,7 +12,11 @@ SingleAnnotation(name, value, col, fun,
12 12
     which = c("column", "row"),
13 13
     show_legend = TRUE,
14 14
     gp = gpar(col = NA),
15
-    legend_param = list())
15
+    legend_param = list(),
16
+    show_name = TRUE,
17
+    name_gp = gpar(fontsize = 12),
18
+    name_offset = unit(2, "mm"),
19
+    name_side = ifelse(which == "column", "right", "bottom"))
16 20
 }
17 21
 \arguments{
18 22
 
... ...
@@ -25,6 +29,10 @@ SingleAnnotation(name, value, col, fun,
25 29
   \item{show_legend}{if it is a simple annotation, whether show legend when making the complete heatmap.}
26 30
   \item{gp}{Since simple annotation is represented as a row of grids. This argument controls graphic parameters for the simple annotation.}
27 31
   \item{legend_param}{parameters for the legend. See \code{\link{color_mapping_legend,ColorMapping-method}} for options.}
32
+  \item{show_name}{whether show annotation name}
33
+  \item{name_gp}{graphic parameters for annotation name}
34
+  \item{name_offset}{offset to the annotation, a \code{\link[grid]{unit}} object}
35
+  \item{name_side}{'right' and 'left' for column annotations and 'top' and 'bottom' for row annotations}
28 36
 
29 37
 }
30 38
 \details{
... ...
@@ -41,6 +41,7 @@ There are following parameters:
41 41
   \item{heatmap_legend_grid_width}{set \code{grid_width} element in \code{legend_param} in \code{\link{SingleAnnotation}}.}
42 42
   \item{heatmap_legend_grid_height}{set \code{grid_height} element in \code{legend_param} in \code{\link{SingleAnnotation}}.}
43 43
   \item{heatmap_legend_grid_border}{set \code{grid_border} element in \code{legend_param} in \code{\link{SingleAnnotation}}.}
44
+  \item{fast_hclust}{whether use \code{\link[fastcluster]{hclust}} to speed up clustering?}
44 45
 }
45 46
 
46 47
 You can get or set option values by the traditional way (like \code{\link[base]{options}}) or by \code{$} operator: