Browse code

add show_quantiles argument

Zuguang Gu authored on 08/05/2019 11:24:33
Showing 3 changed files

... ...
@@ -2,7 +2,7 @@ Package: ComplexHeatmap
2 2
 Type: Package
3 3
 Title: Make Complex Heatmaps
4 4
 Version: 1.99.8
5
-Date: 2019-04-28
5
+Date: 2019-05-03
6 6
 Author: Zuguang Gu
7 7
 Maintainer: Zuguang Gu <z.gu@dkfz.de>
8 8
 Depends: R (>= 3.1.2), methods, grid, graphics, stats, grDevices
... ...
@@ -16,6 +16,7 @@
16 16
 # -ylab_gp Graphic parameters for y-labels.
17 17
 # -tick_label_gp Graphic parameters for y-ticks.
18 18
 # -quantile_gp Graphic parameters for the quantiles.
19
+# -show_quantiles Whether show quantile lines.
19 20
 # -column_order Order of columns.
20 21
 # -column_names_side Pass to `Heatmap`.
21 22
 # -show_column_names Pass to `Heatmap`.
... ...
@@ -73,6 +74,7 @@ densityHeatmap = function(data,
73 74
 	ylab_gp = gpar(fontsize = 12),
74 75
 	tick_label_gp = gpar(fontsize = 10),
75 76
 	quantile_gp = gpar(fontsize = 10),
77
+	show_quantiles = TRUE,
76 78
 
77 79
 	column_order = NULL,
78 80
 	column_names_side = "bottom",
... ...
@@ -167,16 +169,18 @@ densityHeatmap = function(data,
167 169
 		left_annotation = rowAnnotation(axis = anno_empty(border = FALSE, 
168 170
 				width = grobHeight(textGrob(ylab, gp = ylab_gp))*2 + max_text_width(bb, gp = tick_label_gp) + unit(4, "mm")),
169 171
 			show_annotation_name = FALSE), 
170
-		right_annotation = rowAnnotation(quantile = anno_empty(border = FALSE, 
172
+		right_annotation = {if(show_quantiles) {rowAnnotation(quantile = anno_empty(border = FALSE, 
171 173
 				width = grobWidth(textGrob("100%", gp = quantile_gp)) + unit(6, "mm")),
172
-			show_annotation_name = FALSE),
174
+			show_annotation_name = FALSE)} else NULL},
173 175
 		...
174 176
 	)
175 177
 
176 178
 	random_str = paste(sample(c(letters, LETTERS, 0:9), 8), collapse = "")
177 179
 	ht@name = paste0(ht@name, "_", random_str)
178 180
 	names(ht@left_annotation) = paste0(names(ht@left_annotation), "_", random_str)
179
-	names(ht@right_annotation) = paste0(names(ht@right_annotation), "_", random_str)
181
+	if(show_quantiles) {
182
+		names(ht@right_annotation) = paste0(names(ht@right_annotation), "_", random_str)
183
+	}
180 184
 
181 185
 	post_fun = function(ht) {
182 186
 		column_order = column_order(ht)
... ...
@@ -189,16 +193,18 @@ densityHeatmap = function(data,
189 193
 			grid.text(ylab, x = grobHeight(textGrob(ylab, gp = ylab_gp)), rot = 90)
190 194
 		}, slice = 1)
191 195
 
192
-		for(i_slice in 1:n_slice) {
193
-			decorate_heatmap_body(paste0("density_", random_str), {
194
-				n = length(column_order[[i_slice]])
195
-				pushViewport(viewport(xscale = c(0.5, n + 0.5), yscale = c(min_x, max_x), clip = TRUE))
196
-				for(i in seq_len(5)) {
197
-					grid.lines(1:n, quantile_list[i, column_order[[i_slice]] ], default.units = "native", gp = gpar(lty = 2))
198
-				}
199
-				grid.lines(1:n, mean_value[ column_order[[i_slice]] ], default.units = "native", gp = gpar(lty = 2, col = "darkred"))
200
-				upViewport()
201
-			}, column_slice = i_slice)
196
+		if(!is.null(ht@right_annotation)) {
197
+			for(i_slice in 1:n_slice) {
198
+				decorate_heatmap_body(paste0("density_", random_str), {
199
+					n = length(column_order[[i_slice]])
200
+					pushViewport(viewport(xscale = c(0.5, n + 0.5), yscale = c(min_x, max_x), clip = TRUE))
201
+					for(i in seq_len(5)) {
202
+						grid.lines(1:n, quantile_list[i, column_order[[i_slice]] ], default.units = "native", gp = gpar(lty = 2))
203
+					}
204
+					grid.lines(1:n, mean_value[ column_order[[i_slice]] ], default.units = "native", gp = gpar(lty = 2, col = "darkred"))
205
+					upViewport()
206
+				}, column_slice = i_slice)
207
+			}
202 208
 		}
203 209
 
204 210
 		decorate_heatmap_body(paste0("density_", random_str), {
... ...
@@ -208,41 +214,43 @@ densityHeatmap = function(data,
208 214
 			upViewport()
209 215
 		}, column_slice = 1)
210 216
 
211
-		decorate_heatmap_body(paste0("density_", random_str), {
212
-			n = length(column_order[[n_slice]])
213
-			
214
-			lq = !apply(quantile_list, 1, function(x) all(x > max_x) || all(x < min_x))
215
-			lq = c(lq, !(all(mean_value > max_x) || all(mean_value < min_x)))
216
-			if(sum(lq) == 0) {
217
-				return(NULL)
218
-			}
217
+		if(!is.null(ht@right_annotation)) {
218
+			decorate_heatmap_body(paste0("density_", random_str), {
219
+				n = length(column_order[[n_slice]])
220
+				
221
+				lq = !apply(quantile_list, 1, function(x) all(x > max_x) || all(x < min_x))
222
+				lq = c(lq, !(all(mean_value > max_x) || all(mean_value < min_x)))
223
+				if(sum(lq) == 0) {
224
+					return(NULL)
225
+				}
219 226
 
220
-			labels = c(rownames(quantile_list), "mean")
221
-			y = c(quantile_list[, column_order[[n_slice]][n] ], mean_value[ column_order[[n_slice]][n] ])
222
-			labels = labels[lq]
223
-			y = y[lq]
224
-			od = order(y)
225
-			y = y[od]
226
-			labels = labels[od]
227
-			
228
-			pushViewport(viewport(xscale = c(0.5, n + 0.5), yscale = c(min_x, max_x), clip = FALSE))
229
-			text_height = convertHeight(grobHeight(textGrob(labels[1])) * (1 + 0.2), "native", valueOnly = TRUE)
230
-	        h1 = y - text_height*0.5
231
-	        h2 = y + text_height*0.5
232
-	        pos = rev(smartAlign(h1, h2, c(min_x, max_x)))
233
-	        h = (pos[, 1] + pos[, 2])/2
234
-	        link_width = unit(6, "mm")
235
-	        n2 = length(labels)
236
-	        grid.text(labels, unit(1, "npc") + rep(link_width, n2), h, default.units = "native", just = "left", gp = quantile_gp)
237
-	        link_width = link_width - unit(1, "mm")
238
-	        ly = y <= max_x & y >= min_x
239
-	        if(sum(ly)) {
240
-		        grid.segments(unit(rep(1, n2), "npc")[ly], y[ly], unit(1, "npc") + rep(link_width * (1/3), n2)[ly], y[ly], default.units = "native")
241
-		        grid.segments(unit(1, "npc") + rep(link_width * (1/3), n2)[ly], y[ly], unit(1, "npc") + rep(link_width * (2/3), n2)[ly], h[ly], default.units = "native")
242
-		        grid.segments(unit(1, "npc") + rep(link_width * (2/3), n2)[ly], h[ly], unit(1, "npc") + rep(link_width, n2)[ly], h[ly], default.units = "native")
243
-		    }
244
-			upViewport()
245
-		}, column_slice = n_slice)
227
+				labels = c(rownames(quantile_list), "mean")
228
+				y = c(quantile_list[, column_order[[n_slice]][n] ], mean_value[ column_order[[n_slice]][n] ])
229
+				labels = labels[lq]
230
+				y = y[lq]
231
+				od = order(y)
232
+				y = y[od]
233
+				labels = labels[od]
234
+				
235
+				pushViewport(viewport(xscale = c(0.5, n + 0.5), yscale = c(min_x, max_x), clip = FALSE))
236
+				text_height = convertHeight(grobHeight(textGrob(labels[1])) * (1 + 0.2), "native", valueOnly = TRUE)
237
+		        h1 = y - text_height*0.5
238
+		        h2 = y + text_height*0.5
239
+		        pos = rev(smartAlign(h1, h2, c(min_x, max_x)))
240
+		        h = (pos[, 1] + pos[, 2])/2
241
+		        link_width = unit(6, "mm")
242
+		        n2 = length(labels)
243
+		        grid.text(labels, unit(1, "npc") + rep(link_width, n2), h, default.units = "native", just = "left", gp = quantile_gp)
244
+		        link_width = link_width - unit(1, "mm")
245
+		        ly = y <= max_x & y >= min_x
246
+		        if(sum(ly)) {
247
+			        grid.segments(unit(rep(1, n2), "npc")[ly], y[ly], unit(1, "npc") + rep(link_width * (1/3), n2)[ly], y[ly], default.units = "native")
248
+			        grid.segments(unit(1, "npc") + rep(link_width * (1/3), n2)[ly], y[ly], unit(1, "npc") + rep(link_width * (2/3), n2)[ly], h[ly], default.units = "native")
249
+			        grid.segments(unit(1, "npc") + rep(link_width * (2/3), n2)[ly], h[ly], unit(1, "npc") + rep(link_width, n2)[ly], h[ly], default.units = "native")
250
+			    }
251
+				upViewport()
252
+			}, column_slice = n_slice)
253
+		}
246 254
 	}
247 255
 
248 256
 	ht@heatmap_param$post_fun = post_fun
... ...
@@ -22,6 +22,7 @@ densityHeatmap(data,
22 22
     ylab_gp = gpar(fontsize = 12),
23 23
     tick_label_gp = gpar(fontsize = 10),
24 24
     quantile_gp = gpar(fontsize = 10),
25
+    show_quantiles = TRUE,
25 26
     
26 27
     column_order = NULL,
27 28
     column_names_side = "bottom",
... ...
@@ -52,6 +53,7 @@ densityHeatmap(data,
52 53
   \item{ylab_gp}{Graphic parameters for y-labels.}
53 54
   \item{tick_label_gp}{Graphic parameters for y-ticks.}
54 55
   \item{quantile_gp}{Graphic parameters for the quantiles.}
56
+  \item{show_quantiles}{Whether show quantile lines.}
55 57
   \item{column_order}{Order of columns.}
56 58
   \item{column_names_side}{Pass to \code{\link{Heatmap}}.}
57 59
   \item{show_column_names}{Pass to \code{\link{Heatmap}}.}