Browse code

oncoprint: columns are sorted to show mmutual exclusivity

jokergoo authored on 06/10/2015 12:05:23
Showing 5 changed files

... ...
@@ -2,6 +2,8 @@ CHANGES in VERSION 1.4.4
2 2
 
3 3
 * NULL can be added to the heatmap list
4 4
 * give message if users mess up with row and column annotations
5
+* `oncoPrint`: columns are sorted by `memo sort` method to enhance
6
+  the mutual exclusivity.
5 7
 
6 8
 ==================================
7 9
 
... ...
@@ -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('get_color_mapping_param_list', function(object, ...) standardGeneric('get_color_mapping_param_list'))
29
-
30 28
 setGeneric('draw_dimnames', function(object, ...) standardGeneric('draw_dimnames'))
31 29
 
30
+setGeneric('get_color_mapping_param_list', function(object, ...) standardGeneric('get_color_mapping_param_list'))
31
+
32 32
 setGeneric('color_mapping_legend', function(object, ...) standardGeneric('color_mapping_legend'))
33 33
 
34 34
 setGeneric('draw', function(object, ...) standardGeneric('draw'))
... ...
@@ -10,6 +10,10 @@
10 10
 # -alter_fun_list a list of functions which define how to add graphics for different alterations.
11 11
 #                 The names of the list should cover all alteration types.
12 12
 # -col a vector of color for which names correspond to alteration types.
13
+# -row_order order of genes. By default it is sorted by frequency of alterations decreasingly.
14
+#                            Set it to ``NULL`` if you don't want to set the order
15
+# -column_order order of samples. By default the order is calculated by the 'memo sort' method which can visualize
16
+#                                 the mutual exclusivity across genes.
13 17
 # -show_column_names whether show column names
14 18
 # -pct_gp graphic paramters for percent row annotation
15 19
 # -axis_gp graphic paramters for axes
... ...
@@ -23,6 +27,9 @@
23 27
 # == details
24 28
 # The function returns a normal heatmap list and you can add more heatmaps/row annotations to it.
25 29
 #
30
+# The 'memo sort' method is from https://gist.github.com/armish/564a65ab874a770e2c26 . Thanks to
31
+# B. Arman Aksoy for contributing the code.
32
+#
26 33
 # For more explanation, please go to the vignette.
27 34
 #
28 35
 # == value
... ...
@@ -33,6 +40,8 @@
33 40
 #
34 41
 oncoPrint = function(mat, get_type = function(x) x,
35 42
 	alter_fun_list, col, 
43
+	row_order = oncoprint_row_order(),
44
+	column_order = oncoprint_column_order(),
36 45
 	show_column_names = FALSE, 
37 46
 	pct_gp = gpar(), 
38 47
 	axis_gp = gpar(fontsize = 8), 
... ...
@@ -83,9 +92,39 @@ oncoPrint = function(mat, get_type = function(x) x,
83 92
 		arr[, , i] = mat_list[[i]]
84 93
 	}
85 94
 
95
+	oncoprint_row_order = function() {
96
+		order(rowSums(count_matrix), decreasing = TRUE)
97
+	}
98
+
99
+	oncoprint_column_order = function() {
100
+		scoreCol = function(x) {
101
+			score = 0
102
+			for(i in 1:length(x)) {
103
+				if(x[i]) {
104
+					score = score + 2^(length(x)-i)
105
+				}
106
+			}
107
+			return(score)
108
+		}
109
+		scores = apply(count_matrix[row_order, ], 2, scoreCol)
110
+		order(scores, decreasing=TRUE)
111
+	}
112
+
113
+	count_matrix = apply(arr, c(1, 2), sum)
114
+	if(is.null(row_order)) row_order = seq_len(nrow(count_matrix))
115
+	row_order = row_order
116
+	if(is.character(column_order)) {
117
+		column_order = structure(seq_len(dim(arr)[2]), names = dimnames(arr)[[2]])[column_order]
118
+	}
119
+
86 120
 	if(remove_empty_columns) {
87 121
 		l = rowSums(apply(arr, c(2, 3), sum)) > 0
88 122
 		arr = arr[, l, , drop = FALSE]
123
+		count_matrix = count_matrix[, l, drop = FALSE]
124
+		column_order = column_order
125
+		if(length(column_order) > ncol(count_matrix)) {
126
+			column_order = order(column_order[l])
127
+		}
89 128
 	}
90 129
 
91 130
 	# validate alter_fun_list
... ...
@@ -170,9 +209,10 @@ oncoPrint = function(mat, get_type = function(x) x,
170 209
 	pheudo = c(all_type, rep(NA, nrow(arr)*ncol(arr) - length(all_type)))
171 210
 	dim(pheudo) = dim(arr[, , 1])
172 211
 	dimnames(pheudo) = dimnames(arr[, , 1])
212
+	
173 213
 	if(show_column_barplot) {
174 214
 		ht = Heatmap(pheudo, col = col, rect_gp = gpar(type = "none"), 
175
-			cluster_rows = FALSE, cluster_columns = FALSE,
215
+			cluster_rows = FALSE, cluster_columns = FALSE, row_order = row_order, column_order = column_order,
176 216
 			cell_fun = function(j, i, x, y, width, height, fill) {
177 217
 				z = arr[i, j, ]
178 218
 				add_oncoprint("background", x, y, width, height)
... ...
@@ -183,7 +223,7 @@ oncoPrint = function(mat, get_type = function(x) x,
183 223
 			top_annotation = ha_column_bar, ...)
184 224
 	} else {
185 225
 		ht = Heatmap(pheudo, rect_gp = gpar(type = "none"), 
186
-			cluster_rows = FALSE, cluster_columns = FALSE,
226
+			cluster_rows = FALSE, cluster_columns = FALSE, row_order = row_order, column_order = column_order,
187 227
 			cell_fun = function(j, i, x, y, width, height, fill) {
188 228
 				z = arr[i, j, ]
189 229
 				add_oncoprint("background", x, y, width, height)
... ...
@@ -9,6 +9,8 @@ Make oncoPrint
9 9
 \usage{
10 10
 oncoPrint(mat, get_type = function(x) x,
11 11
     alter_fun_list, col,
12
+    row_order = oncoprint_row_order(),
13
+    column_order = oncoprint_column_order(),
12 14
     show_column_names = FALSE,
13 15
     pct_gp = gpar(),
14 16
     axis_gp = gpar(fontsize = 8),
... ...
@@ -25,6 +27,8 @@ oncoPrint(mat, get_type = function(x) x,
25 27
   \item{get_type}{If different alterations are encoded in the matrix, this self-defined functiondetermines how to extract them. Only work when \code{mat} is a matrix.}
26 28
   \item{alter_fun_list}{a list of functions which define how to add graphics for different alterations.The names of the list should cover all alteration types.}
27 29
   \item{col}{a vector of color for which names correspond to alteration types.}
30
+  \item{row_order}{order of genes. By default it is sorted by frequency of alterations decreasingly.Set it to \code{NULL} if you don't want to set the order}
31
+  \item{column_order}{order of samples. By default the order is calculated by the 'memo sort' method which can visualizethe mutual exclusivity across genes.}
28 32
   \item{show_column_names}{whether show column names}
29 33
   \item{pct_gp}{graphic paramters for percent row annotation}
30 34
   \item{axis_gp}{graphic paramters for axes}
... ...
@@ -39,6 +43,9 @@ oncoPrint(mat, get_type = function(x) x,
39 43
 \details{
40 44
 The function returns a normal heatmap list and you can add more heatmaps/row annotations to it.
41 45
 
46
+The 'memo sort' method is from \url{https://gist.github.com/armish/564a65ab874a770e2c26} . Thanks to
47
+B. Arman Aksoy for contributing the code.
48
+
42 49
 For more explanation, please go to the vignette.
43 50
 }
44 51
 \value{
... ...
@@ -128,15 +128,7 @@ rownames(mat) = mat[, 1]
128 128
 mat = mat[, -1]
129 129
 mat=  mat[, -ncol(mat)]
130 130
 mat = t(as.matrix(mat))
131
-```
132
-
133
-We can adjust the order of the matrix. Here cbioPortal also provides sample orders:
134
-
135
-```{r}
136
-sample_order = scan(paste0(system.file("extdata", package = "ComplexHeatmap"), 
137
-    "/sample_order.txt"), what = "character")
138
-mat = mat[, sample_order]
139
-mat[1:4, 1:4]
131
+head(mat)
140 132
 ```
141 133
 
142 134
 There are three different alterations in `mat`: `HOMDEL`, `AMP` and `MUT`. We first 
... ...
@@ -175,6 +167,27 @@ oncoPrint(mat, get_type = function(x) strsplit(x, ";")[[1]],
175 167
 		labels = c("Amplification", "Deep deletion", "Mutation")))
176 168
 ```
177 169
 
170
+As you see, the genes and samples are sorted automatically. Rows are sorted based on the frequency
171
+of the alterations in all samples and columns are sorted to visualize the mutual exclusivity across genes
172
+based on the "memo sort" method which is
173
+kindly provided by [B. Arman Aksoy](https://gist.github.com/armish/564a65ab874a770e2c26). If you want
174
+to turn off the default sorting, set `row_order` or `column_order` to `NULL`.
175
+
176
+As the normal `Heatmap()` function, `row_order` or `column_order` can be assigned with a vector of 
177
+orders (either numeric or character). Following the order of samples are gathered from cBio as well.
178
+You can see the difference for the sample order between 'memo sort' and the method used by cBio.
179
+
180
+```{r, fig.width = 12, fig.height = 8}
181
+sample_order = scan(paste0(system.file("extdata", package = "ComplexHeatmap"), 
182
+    "/sample_order.txt"), what = "character")
183
+oncoPrint(mat, get_type = function(x) strsplit(x, ";")[[1]],
184
+	alter_fun_list = alter_fun_list, col = col, 
185
+	row_order = NULL, column_order = sample_order,
186
+	column_title = "OncoPrint for TCGA Lung Adenocarcinoma, genes in Ras Raf MEK JNK signalling",
187
+	heatmap_legend_param = list(title = "Alternations", at = c("AMP", "HOMDEL", "MUT"), 
188
+		labels = c("Amplification", "Deep deletion", "Mutation")))
189
+```
190
+
178 191
 By default, if one sample has no alteration, it will be removed from the heatmap, but you can set
179 192
 `remove_empty_columns` to `FALSE` to keep it:
180 193