Commit id: 25191b4dc0bd4242c260ef5abd112d4bdd0ea887
add oncoPrint() function
git-svn-id: https://hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/ComplexHeatmap@107561 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -2,13 +2,14 @@ Package: ComplexHeatmap |
2 | 2 |
Type: Package |
3 | 3 |
Title: Making Complex Heatmaps |
4 | 4 |
Version: 1.3.0 |
5 |
-Date: 2015-8-6 |
|
5 |
+Date: 2015-8-18 |
|
6 | 6 |
Author: Zuguang Gu |
7 | 7 |
Maintainer: Zuguang Gu <z.gu@dkfz.de> |
8 | 8 |
Depends: R (>= 3.1.2), grid, graphics, stats, grDevices |
9 | 9 |
Imports: methods, circlize (>= 0.3.1), GetoptLong, colorspace, |
10 | 10 |
RColorBrewer, dendextend (>= 1.0.1), GlobalOptions (>= 0.0.6) |
11 |
-Suggests: testthat (>= 0.3), knitr, markdown, cluster, MASS, pvclust, dendsort |
|
11 |
+Suggests: testthat (>= 0.3), knitr, markdown, cluster, MASS, pvclust, |
|
12 |
+ dendsort, HilbertCurve (>= 0.99.2) |
|
12 | 13 |
VignetteBuilder: knitr |
13 | 14 |
Description: Complex heatmaps are efficient to visualize associations |
14 | 15 |
between different sources of data sets and reveal potential structures. |
... | ... |
@@ -17,6 +18,6 @@ Description: Complex heatmaps are efficient to visualize associations |
17 | 18 |
biocViews: Software, Visualization, Sequencing |
18 | 19 |
URL: https://github.com/jokergoo/ComplexHeatmap |
19 | 20 |
License: GPL (>= 2) |
20 |
-Packaged: 2015-8-6 00:00:00 UTC; Administrator |
|
21 |
+Packaged: 2015-8-18 00:00:00 UTC; Administrator |
|
21 | 22 |
Repository: Bioconductor |
22 |
-Date/Publication: 2015-8-6 00:00:00 |
|
23 |
+Date/Publication: 2015-8-18 00:00:00 |
... | ... |
@@ -117,6 +117,8 @@ Heatmap = setClass("Heatmap", |
117 | 117 |
# -name name of the heatmap. The name is used as the title of the heatmap legend. |
118 | 118 |
# -na_col color for ``NA`` values. |
119 | 119 |
# -rect_gp graphic parameters for drawing rectangles (for heatmap body). |
120 |
+# -color_space the color space in which colors are interpolated. Only used if ``matrix`` is numeric and |
|
121 |
+# ``col`` is a vector of colors. Pass to `circlize::colorRamp2`. |
|
120 | 122 |
# -cell_fun self-defined function to add graphics on each cell. Seven parameters will be passed into |
121 | 123 |
# this function: ``i``, ``j``, ``x``, ``y``, ``width``, ``height``, ``fill`` which are row index, |
122 | 124 |
# column index in ``matrix``, coordinate of the middle points in the heatmap body viewport, |
... | ... |
@@ -204,8 +206,8 @@ Heatmap = setClass("Heatmap", |
204 | 206 |
# == author |
205 | 207 |
# Zuguang Gu <z.gu@dkfz.de> |
206 | 208 |
# |
207 |
-Heatmap = function(matrix, col, name, na_col = "grey", rect_gp = gpar(col = NA), |
|
208 |
- cell_fun = function(j, i, x, y, width, height, fill) NULL, |
|
209 |
+Heatmap = function(matrix, col, name, na_col = "grey", color_space = "LAB", |
|
210 |
+ rect_gp = gpar(col = NA), cell_fun = function(j, i, x, y, width, height, fill) NULL, |
|
209 | 211 |
row_title = character(0), row_title_side = c("left", "right"), |
210 | 212 |
row_title_gp = gpar(fontsize = 14), |
211 | 213 |
row_title_rot = switch(row_title_side[1], "left" = 90, "right" = 270), |
... | ... |
@@ -377,7 +379,7 @@ Heatmap = function(matrix, col, name, na_col = "grey", rect_gp = gpar(col = NA), |
377 | 379 |
.Object@matrix_color_mapping = ColorMapping(colors = col, name = name, na_col = na_col) |
378 | 380 |
} else if(is.numeric(matrix)) { |
379 | 381 |
col = colorRamp2(seq(min(matrix, na.rm = TRUE), max(matrix, na.rm = TRUE), length = length(col)), |
380 |
- col) |
|
382 |
+ col, space = color_space) |
|
381 | 383 |
.Object@matrix_color_mapping = ColorMapping(col_fun = col, name = name, na_col = na_col) |
382 | 384 |
} else { |
383 | 385 |
stop("`col` should have names to map to values in `mat`.") |
... | ... |
@@ -5,6 +5,7 @@ |
5 | 5 |
# == param |
6 | 6 |
# -data a matrix or a list. If it is a matrix, density will be calculated by columns. |
7 | 7 |
# -col a list of colors that density values are scaled to. |
8 |
+# -color_space the color space in which colors are interpolated. Pass to `circlize::colorRamp2`. |
|
8 | 9 |
# -anno annotation for matrix columns or list. The value should be a vector or a data frame. |
9 | 10 |
# It can also be a `HeatmapAnnotation-class` object. |
10 | 11 |
# -ylab label on y-axis in the plot |
... | ... |
@@ -31,7 +32,7 @@ |
31 | 32 |
# densityHeatmap(lt) |
32 | 33 |
# |
33 | 34 |
densityHeatmap = function(data, col = rev(brewer.pal(11, "Spectral")), |
34 |
- anno = NULL, ylab = deparse(substitute(data)), |
|
35 |
+ color_space = "RGB", anno = NULL, ylab = deparse(substitute(data)), |
|
35 | 36 |
title = paste0("Density heatmap of ", deparse(substitute(data)))) { |
36 | 37 |
|
37 | 38 |
if(is.matrix(data)) { |
... | ... |
@@ -62,13 +63,13 @@ densityHeatmap = function(data, col = rev(brewer.pal(11, "Spectral")), |
62 | 63 |
colnames(mat) = nm |
63 | 64 |
|
64 | 65 |
if(is.null(anno)) { |
65 |
- ht = Heatmap(mat, col = col, name = "density", cluster_rows = FALSE, cluster_columns = FALSE) |
|
66 |
+ ht = Heatmap(mat, col = col, color_space = color_space, name = "density", cluster_rows = FALSE, cluster_columns = FALSE) |
|
66 | 67 |
} else if(inherits(anno, "HeatmapAnnotation")) { |
67 |
- ht = Heatmap(mat, col = col, top_annotation = anno, name = "density", cluster_rows = FALSE, cluster_columns = FALSE) |
|
68 |
+ ht = Heatmap(mat, col = col, color_space = color_space, top_annotation = anno, name = "density", cluster_rows = FALSE, cluster_columns = FALSE) |
|
68 | 69 |
} else { |
69 | 70 |
if(!is.data.frame(anno)) anno = data.frame(anno = anno) |
70 | 71 |
ha = HeatmapAnnotation(df = anno) |
71 |
- ht = Heatmap(mat, col = col, top_annotation = ha, name = "density", cluster_rows = FALSE, cluster_columns = FALSE) |
|
72 |
+ ht = Heatmap(mat, col = col, color_space = color_space, top_annotation = ha, name = "density", cluster_rows = FALSE, cluster_columns = FALSE) |
|
72 | 73 |
} |
73 | 74 |
|
74 | 75 |
bb = grid.pretty(c(min_x, max_x)) |
75 | 76 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,196 @@ |
1 |
+ |
|
2 |
+# == title |
|
3 |
+# Make oncoPrint |
|
4 |
+# |
|
5 |
+# == param |
|
6 |
+# -mat a character matrix which encodes mulitple alterations or a list of matrix for which every matrix contains binary |
|
7 |
+# value representing the alteration is present or absent. When it is a list, the names represent alteration types. |
|
8 |
+# -get_type If different alterations are encoded in the matrix, this self-defined function |
|
9 |
+# determines how to extract them. Only work when ``mat`` is a matrix. |
|
10 |
+# -alter_fun_list a list of functions which define how to add graphics for different alterations. |
|
11 |
+# The names of the list should cover all alteration types. |
|
12 |
+# -col a vector of color for which names correspond to alteration types. |
|
13 |
+# -show_column_names whether show column names |
|
14 |
+# -pct_gp graphic paramters for percent row annotation |
|
15 |
+# -axis_gp graphic paramters for axes |
|
16 |
+# -show_row_barplot whether show barplot annotation on rows |
|
17 |
+# -row_barplot_width width of barplot annotation on rows. It should be a `grid::unit` object |
|
18 |
+# -show_column_barplot whether show barplot annotation on columns |
|
19 |
+# -column_barplot_height height of barplot annotatioin on columns. it should be a `grid::unit` object. |
|
20 |
+# -... pass to `Heatmap` |
|
21 |
+# |
|
22 |
+# == details |
|
23 |
+# The function returns a normal heatmap list and you can add more heatmaps/row annotations to it. |
|
24 |
+# |
|
25 |
+# For more explanation, please go to the vignette. |
|
26 |
+# |
|
27 |
+# == value |
|
28 |
+# a `HeatmapList-class` object. |
|
29 |
+# |
|
30 |
+# == author |
|
31 |
+# Zuguang Gu <z.gu@dkfz.de> |
|
32 |
+# |
|
33 |
+oncoPrint = function(mat, get_type = function(x) x, |
|
34 |
+ alter_fun_list, col, show_column_names = FALSE, |
|
35 |
+ pct_gp = gpar(), axis_gp = gpar(fontsize = 8), |
|
36 |
+ show_row_barplot = TRUE, row_barplot_width = unit(2, "cm"), |
|
37 |
+ show_column_barplot = TRUE, column_barplot_height = unit(2, "cm"), |
|
38 |
+ ...) { |
|
39 |
+ |
|
40 |
+ # convert mat to mat_list |
|
41 |
+ if(inherits(mat, "matrix")) { |
|
42 |
+ |
|
43 |
+ all_type = unique(unlist(lapply(mat, get_type))) |
|
44 |
+ all_type = all_type[!is.na(all_type)] |
|
45 |
+ all_type = all_type[grepl("\\S", all_type)] |
|
46 |
+ |
|
47 |
+ mat_list = lapply(all_type, function(type) { |
|
48 |
+ m = sapply(mat, function(x) type %in% get_type(x)) |
|
49 |
+ dim(m) = dim(mat) |
|
50 |
+ dimnames(m) = dimnames(mat) |
|
51 |
+ m |
|
52 |
+ }) |
|
53 |
+ } else if(inherits(mat, "list")) { |
|
54 |
+ mat_list = mat |
|
55 |
+ all_type = names(mat_list) |
|
56 |
+ mat_list = lapply(mat_list, function(x) { |
|
57 |
+ oattr = attributes(x) |
|
58 |
+ x = as.logical(x) |
|
59 |
+ attributes(x) = oattr |
|
60 |
+ x |
|
61 |
+ }) |
|
62 |
+ |
|
63 |
+ if(length(unique(sapply(mat_list, nrow))) > 1) { |
|
64 |
+ stop("All matrix in 'mat_list' should have same number of rows.") |
|
65 |
+ } |
|
66 |
+ |
|
67 |
+ if(length(unique(sapply(mat_list, ncol))) > 1) { |
|
68 |
+ stop("All matrix in 'mat_list' should have same number of columns.") |
|
69 |
+ } |
|
70 |
+ } else { |
|
71 |
+ stop("Incorrect type of 'mat'") |
|
72 |
+ } |
|
73 |
+ |
|
74 |
+ # type as the third dimension |
|
75 |
+ arr = array(FALSE, dim = c(dim(mat_list[[1]]), length(all_type)), dimnames = c(dimnames(mat_list[[1]]), list(all_type))) |
|
76 |
+ for(i in seq_along(all_type)) { |
|
77 |
+ arr[, , i] = mat_list[[i]] |
|
78 |
+ } |
|
79 |
+ |
|
80 |
+ l = rowSums(apply(arr, c(2, 3), sum)) > 0 |
|
81 |
+ arr = arr[, l, , drop = FALSE] |
|
82 |
+ |
|
83 |
+ # validate alter_fun_list |
|
84 |
+ if(is.null(alter_fun_list$background)) alter_fun_list$background = function(x, y, w, h) grid.rect(x, y, w, h, gp = gpar(fill = "#CCCCCC", col = NA)) |
|
85 |
+ sdf = setdiff(all_type, names(alter_fun_list)) |
|
86 |
+ if(length(sdf) > 0) { |
|
87 |
+ stop(paste0("You should define shape function for:", paste(sdf, collapse = ", "))) |
|
88 |
+ } |
|
89 |
+ |
|
90 |
+ all_type = names(alter_fun_list) |
|
91 |
+ all_type = setdiff(all_type, "background") |
|
92 |
+ |
|
93 |
+ arr = arr[, , all_type, drop = FALSE] |
|
94 |
+ |
|
95 |
+ # validate col |
|
96 |
+ sdf = setdiff(all_type, names(col)) |
|
97 |
+ if(length(sdf) > 0) { |
|
98 |
+ stop(paste0("You should define colors for:", paste(sdf, collapse = ", "))) |
|
99 |
+ } |
|
100 |
+ |
|
101 |
+ add_oncoprint = function(type, x, y, width, height) { |
|
102 |
+ alter_fun_list[[type]](x, y, width, height) |
|
103 |
+ } |
|
104 |
+ |
|
105 |
+ # for each gene, percent of samples that have alterations |
|
106 |
+ pct = rowSums(apply(arr, 1:2, any)) / ncol(mat_list[[1]]) |
|
107 |
+ pct = paste0(round(pct * 100), "%") |
|
108 |
+ ha_pct = rowAnnotation(pct = row_anno_text(pct, just = "right", offset = unit(1, "npc"), gp = pct_gp), width = grobWidth(textGrob("100%", gp = pct_gp))) |
|
109 |
+ |
|
110 |
+ ##################################################################### |
|
111 |
+ # row annotation which is a barplot |
|
112 |
+ anno_row_bar = function(index, k = NULL, N = NULL) { |
|
113 |
+ n = length(index) |
|
114 |
+ count = apply(arr, c(1, 3), sum)[index, , drop = FALSE] |
|
115 |
+ max_count = max(rowSums(count)) |
|
116 |
+ pushViewport(viewport(xscale = c(0, max_count*1.1), yscale = c(0.5, n + 0.5))) |
|
117 |
+ for(i in seq_len(nrow(count))) { |
|
118 |
+ if(any(count[i, ] > 0)) { |
|
119 |
+ x = count[i, ] |
|
120 |
+ x = x[x > 0] |
|
121 |
+ x2 = cumsum(x) |
|
122 |
+ type = all_type[count[i, ] > 0] |
|
123 |
+ # row order is from top to end while coordinate of y is from bottom to top |
|
124 |
+ # so here we need to use n-i+1 |
|
125 |
+ grid.rect(x2, n-i+1, width = x, height = 0.8, default.units = "native", just = "right", gp = gpar(col = NA, fill = col[type])) |
|
126 |
+ } |
|
127 |
+ } |
|
128 |
+ breaks = grid.pretty(c(0, max_count)) |
|
129 |
+ if(k == 1) { |
|
130 |
+ grid.xaxis(at = breaks, label = breaks, main = FALSE, gp = axis_gp) |
|
131 |
+ } |
|
132 |
+ upViewport() |
|
133 |
+ } |
|
134 |
+ |
|
135 |
+ ha_row_bar = rowAnnotation(row_bar = anno_row_bar, width = row_barplot_width) |
|
136 |
+ |
|
137 |
+ ################################################################### |
|
138 |
+ # column annotation which is also a barplot |
|
139 |
+ anno_column_bar = function(index) { |
|
140 |
+ n = length(index) |
|
141 |
+ count = apply(arr, c(2, 3), sum)[index, , drop = FALSE] |
|
142 |
+ max_count = max(rowSums(count)) |
|
143 |
+ pushViewport(viewport(yscale = c(0, max_count*1.1), xscale = c(0.5, n + 0.5))) |
|
144 |
+ for(i in seq_len(nrow(count))) { |
|
145 |
+ if(any(count[i, ] > 0)) { |
|
146 |
+ y = count[i, ] |
|
147 |
+ y = y[y > 0] |
|
148 |
+ y2 = cumsum(y) |
|
149 |
+ type = all_type[count[i, ] > 0] |
|
150 |
+ grid.rect(i, y2, height = y, width = 0.8, default.units = "native", just = "top", gp = gpar(col = NA, fill = col[type])) |
|
151 |
+ } |
|
152 |
+ } |
|
153 |
+ breaks = grid.pretty(c(0, max_count)) |
|
154 |
+ grid.yaxis(at = breaks, label = breaks, gp = axis_gp) |
|
155 |
+ upViewport() |
|
156 |
+ } |
|
157 |
+ |
|
158 |
+ ha_column_bar = HeatmapAnnotation(column_bar = anno_column_bar, which = "column", height = column_barplot_height) |
|
159 |
+ |
|
160 |
+ ##################################################################### |
|
161 |
+ # the main matrix |
|
162 |
+ pheudo = c(all_type, rep(NA, nrow(arr)*ncol(arr) - length(all_type))) |
|
163 |
+ dim(pheudo) = dim(arr[, , 1]) |
|
164 |
+ dimnames(pheudo) = dimnames(arr[, , 1]) |
|
165 |
+ if(show_column_barplot) { |
|
166 |
+ ht = Heatmap(pheudo, col = col, rect_gp = gpar(type = "none"), |
|
167 |
+ cluster_rows = FALSE, cluster_columns = FALSE, |
|
168 |
+ cell_fun = function(j, i, x, y, width, height, fill) { |
|
169 |
+ z = arr[i, j, ] |
|
170 |
+ add_oncoprint("background", x, y, width, height) |
|
171 |
+ for(type in all_type[z]) { |
|
172 |
+ add_oncoprint(type, x, y, width, height) |
|
173 |
+ } |
|
174 |
+ }, show_column_names = show_column_names, |
|
175 |
+ top_annotation = ha_column_bar, ...) |
|
176 |
+ } else { |
|
177 |
+ ht = Heatmap(pheudo, rect_gp = gpar(type = "none"), |
|
178 |
+ cluster_rows = FALSE, cluster_columns = FALSE, |
|
179 |
+ cell_fun = function(j, i, x, y, width, height, fill) { |
|
180 |
+ z = arr[i, j, ] |
|
181 |
+ add_oncoprint("background", x, y, width, height) |
|
182 |
+ for(type in all_type[z]) { |
|
183 |
+ add_oncoprint(type, x, y, width, height) |
|
184 |
+ } |
|
185 |
+ }, show_column_names = show_column_names, ...) |
|
186 |
+ } |
|
187 |
+ |
|
188 |
+ if(show_row_barplot) { |
|
189 |
+ ht_list = ha_pct + ht + ha_row_bar |
|
190 |
+ } else { |
|
191 |
+ ht_list = ha_pct + ht |
|
192 |
+ } |
|
193 |
+ |
|
194 |
+ return(ht_list) |
|
195 |
+ |
|
196 |
+} |
|
0 | 197 |
\ No newline at end of file |
... | ... |
@@ -7,8 +7,8 @@ Constructor method for Heatmap class |
7 | 7 |
Constructor method for Heatmap class |
8 | 8 |
} |
9 | 9 |
\usage{ |
10 |
-Heatmap(matrix, col, name, na_col = "grey", rect_gp = gpar(col = NA), |
|
11 |
- cell_fun = function(j, i, x, y, width, height, fill) NULL, |
|
10 |
+Heatmap(matrix, col, name, na_col = "grey", color_space = "LAB", |
|
11 |
+ rect_gp = gpar(col = NA), cell_fun = function(j, i, x, y, width, height, fill) NULL, |
|
12 | 12 |
row_title = character(0), row_title_side = c("left", "right"), |
13 | 13 |
row_title_gp = gpar(fontsize = 14), |
14 | 14 |
row_title_rot = switch(row_title_side[1], "left" = 90, "right" = 270), |
... | ... |
@@ -45,6 +45,7 @@ Heatmap(matrix, col, name, na_col = "grey", rect_gp = gpar(col = NA), |
45 | 45 |
\item{name}{name of the heatmap. The name is used as the title of the heatmap legend.} |
46 | 46 |
\item{na_col}{color for \code{NA} values.} |
47 | 47 |
\item{rect_gp}{graphic parameters for drawing rectangles (for heatmap body).} |
48 |
+ \item{color_space}{the color space in which colors are interpolated. Only used if \code{matrix} is numeric and \code{col} is a vector of colors. Pass to \code{\link[circlize]{colorRamp2}}.} |
|
48 | 49 |
\item{cell_fun}{self-defined function to add graphics on each cell. Seven parameters will be passed into this function: \code{i}, \code{j}, \code{x}, \code{y}, \code{width}, \code{height}, \code{fill} which are row index,column index in \code{matrix}, coordinate of the middle points in the heatmap body viewport,the width and height of the cell and the filled color. } |
49 | 50 |
\item{row_title}{title on row.} |
50 | 51 |
\item{row_title_side}{will the title be put on the left or right of the heatmap?} |
... | ... |
@@ -8,13 +8,14 @@ Use colors to represent density distribution |
8 | 8 |
} |
9 | 9 |
\usage{ |
10 | 10 |
densityHeatmap(data, col = rev(brewer.pal(11, "Spectral")), |
11 |
- anno = NULL, ylab = deparse(substitute(data)), |
|
11 |
+ color_space = "RGB", anno = NULL, ylab = deparse(substitute(data)), |
|
12 | 12 |
title = paste0("Density heatmap of ", deparse(substitute(data)))) |
13 | 13 |
} |
14 | 14 |
\arguments{ |
15 | 15 |
|
16 | 16 |
\item{data}{a matrix or a list. If it is a matrix, density will be calculated by columns.} |
17 | 17 |
\item{col}{a list of colors that density values are scaled to.} |
18 |
+ \item{color_space}{the color space in which colors are interpolated. Pass to \code{\link[circlize]{colorRamp2}}.} |
|
18 | 19 |
\item{anno}{annotation for matrix columns or list. The value should be a vector or a data frame. It can also be a \code{\link{HeatmapAnnotation-class}} object.} |
19 | 20 |
\item{ylab}{label on y-axis in the plot} |
20 | 21 |
\item{title}{title of the plot} |
21 | 22 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,43 @@ |
1 |
+\name{oncoPrint} |
|
2 |
+\alias{oncoPrint} |
|
3 |
+\title{ |
|
4 |
+Make oncoPrint |
|
5 |
+} |
|
6 |
+\description{ |
|
7 |
+Make oncoPrint |
|
8 |
+} |
|
9 |
+\usage{ |
|
10 |
+oncoPrint(mat, get_type = function(x) x, |
|
11 |
+ alter_fun_list, col, show_column_names = FALSE, |
|
12 |
+ pct_gp = gpar(), axis_gp = gpar(fontsize = 8), |
|
13 |
+ show_row_barplot = TRUE, row_barplot_width = unit(2, "cm"), |
|
14 |
+ show_column_barplot = TRUE, column_barplot_height = unit(2, "cm"), |
|
15 |
+ ...) |
|
16 |
+} |
|
17 |
+\arguments{ |
|
18 |
+ |
|
19 |
+ \item{mat}{a character matrix which encodes mulitple alterations or a list of matrix for which every matrix contains binaryvalue representing the alteration is present or absent. When it is a list, the names represent alteration types.} |
|
20 |
+ \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.} |
|
21 |
+ \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.} |
|
22 |
+ \item{col}{a vector of color for which names correspond to alteration types.} |
|
23 |
+ \item{show_column_names}{whether show column names} |
|
24 |
+ \item{pct_gp}{graphic paramters for percent row annotation} |
|
25 |
+ \item{axis_gp}{graphic paramters for axes} |
|
26 |
+ \item{show_row_barplot}{whether show barplot annotation on rows} |
|
27 |
+ \item{row_barplot_width}{width of barplot annotation on rows. It should be a \code{\link[grid]{unit}} object} |
|
28 |
+ \item{show_column_barplot}{whether show barplot annotation on columns} |
|
29 |
+ \item{column_barplot_height}{height of barplot annotatioin on columns. it should be a \code{\link[grid]{unit}} object.} |
|
30 |
+ \item{...}{pass to \code{\link{Heatmap}}} |
|
31 |
+ |
|
32 |
+} |
|
33 |
+\details{ |
|
34 |
+The function returns a normal heatmap list and you can add more heatmaps/row annotations to it. |
|
35 |
+ |
|
36 |
+For more explanation, please go to the vignette. |
|
37 |
+} |
|
38 |
+\value{ |
|
39 |
+a \code{\link{HeatmapList-class}} object. |
|
40 |
+} |
|
41 |
+\author{ |
|
42 |
+Zuguang Gu <z.gu@dkfz.de> |
|
43 |
+} |
0 | 44 |
deleted file mode 100644 |
... | ... |
@@ -1,173 +0,0 @@ |
1 |
-Case ID KEAP1 TMTC1 OR4C16 ZNF676 STK11 TP53 KRAS EGFR CDKN2A MAGEC1 NAV3 CDH10 MROH2B OR5W2 OR5D14 RIT1 LRRTM4 NRG3 U2AF1 TBX22 BAGE2 OR4C15 ZNF492 FERD3L OR2T34 CCDC178 SERPINB4 ZNF804A PABPC3 EPHA6 ELTD1 OR2L3 REG1B CD5L CNBD1 REG3A GABRB3 OR2T4 TRIM58 OR4A5 NRAS BRAF OR2L8 HGF OR8H2 ADAMTS2 ZNF268 OR5I1 KCNT2 THEMIS GBA3 ASTN2 |
|
2 |
-TCGA-05-4384-01 MUT; MUT; MUT; MUT; MUT; |
|
3 |
-TCGA-05-4390-01 MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; |
|
4 |
-TCGA-05-4425-01 MUT; MUT; MUT; |
|
5 |
-TCGA-38-4631-01 MUT; MUT; HOMDEL; MUT; MUT; AMP; MUT; MUT; MUT; MUT; MUT; MUT; |
|
6 |
-TCGA-38-4632-01 MUT; MUT; MUT; MUT; MUT; MUT; MUT; |
|
7 |
-TCGA-38-6178-01 MUT; MUT;AMP; MUT;HOMDEL; |
|
8 |
-TCGA-44-6144-01 MUT; MUT; MUT; MUT; MUT; AMP; MUT; |
|
9 |
-TCGA-44-6145-01 MUT; MUT; MUT; MUT; MUT; AMP; AMP; MUT; MUT; |
|
10 |
-TCGA-44-6146-01 MUT; |
|
11 |
-TCGA-44-6147-01 MUT; MUT; |
|
12 |
-TCGA-44-6148-01 |
|
13 |
-TCGA-49-4488-01 MUT; MUT; MUT; MUT; MUT; |
|
14 |
-TCGA-50-5930-01 HOMDEL; MUT; |
|
15 |
-TCGA-50-5931-01 MUT; MUT; AMP; AMP; MUT; MUT; AMP; MUT; MUT; |
|
16 |
-TCGA-50-5932-01 MUT; MUT; HOMDEL; MUT; AMP; AMP; AMP; AMP; AMP; AMP; |
|
17 |
-TCGA-50-5933-01 MUT; MUT; AMP; MUT; MUT;AMP; MUT; MUT; MUT; |
|
18 |
-TCGA-50-5935-01 MUT; MUT; |
|
19 |
-TCGA-50-5941-01 MUT; MUT; MUT; MUT;AMP; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; |
|
20 |
-TCGA-50-5942-01 MUT; MUT; MUT; MUT; MUT; |
|
21 |
-TCGA-50-5944-01 MUT; MUT; HOMDEL; HOMDEL; AMP; |
|
22 |
-TCGA-50-5946-01 MUT; HOMDEL; |
|
23 |
-TCGA-50-6591-01 MUT; MUT;AMP; MUT; |
|
24 |
-TCGA-50-6592-01 MUT; HOMDEL; MUT; MUT; MUT; MUT; MUT; MUT; |
|
25 |
-TCGA-50-6593-01 MUT; MUT; MUT; MUT; MUT; MUT; MUT; |
|
26 |
-TCGA-50-6594-01 MUT;HOMDEL; MUT; AMP; MUT; AMP; AMP; HOMDEL; HOMDEL; HOMDEL; MUT; MUT; MUT; MUT; MUT; MUT;HOMDEL; MUT; HOMDEL; AMP; HOMDEL; |
|
27 |
-TCGA-55-6543-01 |
|
28 |
-TCGA-67-4679-01 MUT; MUT; MUT; |
|
29 |
-TCGA-67-6215-01 AMP; AMP; MUT; AMP; MUT;AMP; AMP; AMP; MUT; AMP; AMP; |
|
30 |
-TCGA-67-6216-01 |
|
31 |
-TCGA-67-6217-01 MUT; MUT; MUT; AMP; |
|
32 |
-TCGA-73-4658-01 MUT; MUT; MUT; |
|
33 |
-TCGA-73-4676-01 MUT; MUT; AMP; MUT; AMP; |
|
34 |
-TCGA-75-5122-01 AMP; MUT; |
|
35 |
-TCGA-75-5125-01 MUT; MUT; HOMDEL; AMP; MUT; MUT; |
|
36 |
-TCGA-75-5126-01 MUT; MUT; MUT; MUT; MUT; MUT; |
|
37 |
-TCGA-75-6203-01 HOMDEL; MUT; |
|
38 |
-TCGA-75-6205-01 |
|
39 |
-TCGA-75-6206-01 MUT; MUT; |
|
40 |
-TCGA-75-6207-01 MUT; MUT; MUT; MUT; AMP; |
|
41 |
-TCGA-75-6211-01 MUT; MUT; HOMDEL; AMP; HOMDEL; MUT; HOMDEL; MUT; MUT; MUT; MUT; HOMDEL; MUT; |
|
42 |
-TCGA-75-6212-01 MUT; |
|
43 |
-TCGA-86-6562-01 HOMDEL; AMP; AMP; AMP; AMP; AMP; AMP; AMP; AMP; AMP; |
|
44 |
-TCGA-05-4396-01 MUT; MUT; MUT; MUT; MUT; MUT; MUT;AMP; MUT;AMP; MUT;AMP; MUT; MUT; MUT; AMP; MUT; MUT; MUT; MUT; MUT;AMP; MUT;AMP; MUT; MUT; MUT;AMP; AMP; AMP; MUT;AMP; MUT; MUT; MUT; MUT;AMP; MUT; MUT;AMP; |
|
45 |
-TCGA-05-4405-01 MUT; MUT; MUT; |
|
46 |
-TCGA-05-4410-01 MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; |
|
47 |
-TCGA-05-4415-01 HOMDEL; MUT; MUT; MUT; AMP; MUT; MUT; MUT; |
|
48 |
-TCGA-05-4417-01 MUT; MUT; MUT; MUT; MUT; MUT; |
|
49 |
-TCGA-05-4424-01 MUT; MUT; MUT;AMP; MUT;AMP; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; |
|
50 |
-TCGA-05-4427-01 MUT; MUT; MUT; MUT; MUT; MUT; AMP; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT;AMP; |
|
51 |
-TCGA-05-4433-01 AMP; MUT; MUT;AMP; MUT; AMP; |
|
52 |
-TCGA-44-6774-01 MUT; MUT; MUT; AMP; MUT; |
|
53 |
-TCGA-44-6775-01 MUT;HOMDEL; MUT; |
|
54 |
-TCGA-44-6776-01 MUT; MUT; MUT; MUT; MUT; MUT; |
|
55 |
-TCGA-44-6777-01 MUT; MUT; MUT; AMP; MUT; MUT; MUT; MUT; |
|
56 |
-TCGA-44-6778-01 MUT; MUT; MUT; MUT; MUT; MUT; MUT; |
|
57 |
-TCGA-44-6779-01 MUT; MUT; MUT; HOMDEL; MUT; |
|
58 |
-TCGA-49-4487-01 MUT; MUT; MUT; AMP; MUT;AMP; AMP; MUT; MUT; |
|
59 |
-TCGA-49-4490-01 MUT; MUT; HOMDEL; HOMDEL; |
|
60 |
-TCGA-49-4512-01 MUT; |
|
61 |
-TCGA-49-4514-01 MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; |
|
62 |
-TCGA-49-6742-01 MUT; HOMDEL; AMP; MUT; MUT; MUT; |
|
63 |
-TCGA-49-6743-01 MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; |
|
64 |
-TCGA-49-6744-01 MUT; MUT; MUT; MUT; |
|
65 |
-TCGA-49-6745-01 AMP; AMP; HOMDEL; HOMDEL; |
|
66 |
-TCGA-49-6767-01 MUT; HOMDEL; MUT; HOMDEL; MUT; MUT; MUT; MUT; |
|
67 |
-TCGA-50-5044-01 MUT; HOMDEL; HOMDEL; MUT; |
|
68 |
-TCGA-50-5051-01 MUT; MUT; MUT; |
|
69 |
-TCGA-50-5072-01 MUT; HOMDEL; MUT; MUT; MUT; |
|
70 |
-TCGA-50-6590-01 MUT; MUT;AMP; MUT; MUT; MUT; MUT;AMP; MUT; AMP; MUT; AMP; MUT;AMP; AMP; |
|
71 |
-TCGA-50-6595-01 MUT; MUT; MUT; |
|
72 |
-TCGA-50-6597-01 AMP; AMP; AMP; AMP; AMP; |
|
73 |
-TCGA-55-6642-01 MUT; HOMDEL; MUT; |
|
74 |
-TCGA-55-6712-01 MUT; AMP; MUT; MUT; |
|
75 |
-TCGA-71-6725-01 MUT; |
|
76 |
-TCGA-91-6828-01 MUT; MUT; MUT; HOMDEL; |
|
77 |
-TCGA-91-6829-01 MUT; MUT; AMP; AMP; AMP; MUT; AMP; AMP; AMP; MUT; MUT;AMP; AMP; MUT; AMP; AMP; AMP; MUT; MUT; MUT; |
|
78 |
-TCGA-91-6831-01 MUT; MUT; HOMDEL; HOMDEL; MUT; MUT;AMP; MUT; MUT; MUT; |
|
79 |
-TCGA-91-6835-01 AMP; AMP; MUT; MUT; AMP; AMP; |
|
80 |
-TCGA-91-6836-01 AMP; MUT; MUT;AMP; MUT; MUT; MUT;AMP; MUT; MUT; AMP; MUT; MUT; |
|
81 |
-TCGA-35-3615-01 MUT; MUT; MUT; MUT; AMP; MUT; MUT; HOMDEL; HOMDEL; |
|
82 |
-TCGA-44-2655-01 MUT; AMP; AMP; AMP; AMP; AMP; MUT;AMP; AMP; AMP; |
|
83 |
-TCGA-44-2656-01 MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; |
|
84 |
-TCGA-44-2659-01 MUT; MUT; MUT; MUT; MUT; |
|
85 |
-TCGA-44-2662-01 MUT; MUT; MUT; MUT; MUT; |
|
86 |
-TCGA-44-2665-01 HOMDEL; MUT; |
|
87 |
-TCGA-44-2666-01 MUT; MUT; |
|
88 |
-TCGA-44-2668-01 MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; |
|
89 |
-TCGA-55-1592-01 MUT; AMP; HOMDEL; AMP; AMP; AMP; MUT; MUT; AMP; MUT; AMP; MUT; MUT; |
|
90 |
-TCGA-55-1594-01 MUT; AMP; MUT; |
|
91 |
-TCGA-55-1595-01 MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; |
|
92 |
-TCGA-55-1596-01 MUT; MUT; AMP; MUT; MUT; MUT; MUT; |
|
93 |
-TCGA-64-1676-01 MUT; MUT; AMP; MUT;AMP; MUT; MUT; AMP; MUT; MUT; MUT; MUT; AMP; |
|
94 |
-TCGA-64-1677-01 MUT; MUT; MUT; MUT; MUT; HOMDEL; MUT; MUT; |
|
95 |
-TCGA-64-1678-01 MUT; MUT; |
|
96 |
-TCGA-64-1680-01 HOMDEL; MUT; |
|
97 |
-TCGA-67-3770-01 MUT; MUT; HOMDEL; MUT; |
|
98 |
-TCGA-67-3771-01 MUT; MUT; MUT; MUT; MUT; MUT; MUT; AMP; AMP; MUT; MUT;AMP; MUT; MUT;AMP; AMP; |
|
99 |
-TCGA-67-3772-01 MUT; HOMDEL; MUT; |
|
100 |
-TCGA-67-3773-01 MUT; AMP; MUT; MUT; |
|
101 |
-TCGA-67-3774-01 MUT; MUT; MUT;AMP; MUT; |
|
102 |
-TCGA-05-4244-01 MUT; AMP; MUT; HOMDEL; MUT; HOMDEL; HOMDEL; HOMDEL; HOMDEL; MUT; MUT; |
|
103 |
-TCGA-05-4249-01 MUT; AMP; MUT; AMP; AMP; AMP; AMP; AMP; MUT; AMP; AMP; MUT; |
|
104 |
-TCGA-05-4250-01 MUT;AMP; MUT;AMP; MUT; MUT; MUT; |
|
105 |
-TCGA-35-4122-01 MUT; HOMDEL; MUT; MUT; AMP; MUT; |
|
106 |
-TCGA-35-4123-01 MUT; MUT; MUT; MUT; MUT; MUT; |
|
107 |
-TCGA-44-2657-01 AMP; AMP; MUT;AMP; MUT; MUT; MUT; |
|
108 |
-TCGA-44-2661-01 |
|
109 |
-TCGA-44-3398-01 MUT; MUT; MUT; |
|
110 |
-TCGA-44-3918-01 MUT;AMP; MUT; MUT; MUT; MUT; AMP; MUT; MUT; MUT; MUT; MUT; MUT; MUT; |
|
111 |
-TCGA-44-3919-01 |
|
112 |
-TCGA-44-4112-01 MUT; AMP; MUT; MUT; AMP; MUT; |
|
113 |
-TCGA-05-4382-01 HOMDEL; MUT; MUT; HOMDEL; MUT; MUT; HOMDEL; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; AMP; MUT; MUT; MUT; MUT;AMP; MUT; MUT; MUT;AMP; AMP; MUT; MUT;AMP; MUT; MUT; MUT; |
|
114 |
-TCGA-05-4389-01 MUT; HOMDEL; MUT; MUT; MUT; AMP; MUT; MUT; |
|
115 |
-TCGA-05-4395-01 MUT; MUT; MUT; MUT; MUT; MUT; |
|
116 |
-TCGA-05-4397-01 MUT; AMP; MUT; AMP; MUT; AMP; MUT;AMP; MUT; MUT; AMP; AMP; AMP; MUT; MUT; AMP; MUT; |
|
117 |
-TCGA-05-4398-01 MUT; MUT;HOMDEL; MUT; MUT; MUT; MUT; MUT; |
|
118 |
-TCGA-05-4402-01 MUT; MUT;AMP; HOMDEL; |
|
119 |
-TCGA-05-4403-01 MUT; HOMDEL; MUT; |
|
120 |
-TCGA-05-4418-01 MUT; MUT; MUT; HOMDEL; AMP; MUT; MUT; MUT; |
|
121 |
-TCGA-05-4420-01 MUT; MUT; MUT; MUT; MUT; MUT; |
|
122 |
-TCGA-05-4422-01 MUT; AMP; AMP; MUT; |
|
123 |
-TCGA-05-4426-01 MUT; MUT; AMP; MUT; AMP; |
|
124 |
-TCGA-05-4430-01 MUT; MUT; MUT; MUT; MUT; MUT; |
|
125 |
-TCGA-05-4432-01 MUT; MUT; HOMDEL; MUT; MUT; MUT; MUT; MUT; HOMDEL; MUT; MUT; AMP; MUT; HOMDEL; MUT; |
|
126 |
-TCGA-05-4434-01 MUT; HOMDEL; AMP; HOMDEL; AMP; |
|
127 |
-TCGA-38-4625-01 MUT; MUT; MUT;HOMDEL; MUT; MUT; MUT; |
|
128 |
-TCGA-38-4626-01 MUT; MUT; MUT; MUT; MUT; MUT; |
|
129 |
-TCGA-38-4627-01 MUT; MUT; |
|
130 |
-TCGA-38-4628-01 MUT;AMP; HOMDEL; AMP; AMP; MUT; MUT; MUT; AMP; AMP; |
|
131 |
-TCGA-38-4629-01 MUT; MUT; HOMDEL; MUT;AMP; MUT; MUT; |
|
132 |
-TCGA-38-4630-01 MUT; AMP; |
|
133 |
-TCGA-44-3396-01 MUT;HOMDEL; HOMDEL; MUT; MUT; |
|
134 |
-TCGA-49-4486-01 MUT; MUT; MUT; MUT; |
|
135 |
-TCGA-49-4494-01 MUT; HOMDEL; MUT; MUT; MUT; HOMDEL; |
|
136 |
-TCGA-49-4501-01 MUT;AMP; AMP; MUT; |
|
137 |
-TCGA-49-4505-01 MUT; MUT; MUT; MUT; AMP; MUT; MUT; |
|
138 |
-TCGA-49-4506-01 MUT; MUT; AMP; AMP; MUT; AMP; AMP; AMP; AMP; AMP; MUT; AMP; |
|
139 |
-TCGA-49-4507-01 MUT; AMP; MUT; AMP; HOMDEL; MUT; AMP; MUT; |
|
140 |
-TCGA-49-4510-01 AMP; MUT;AMP; AMP; MUT; AMP; |
|
141 |
-TCGA-73-4659-01 MUT; MUT; MUT; AMP; MUT; AMP; AMP; AMP; AMP; MUT; |
|
142 |
-TCGA-73-4662-01 MUT; AMP; AMP; AMP; MUT; MUT; MUT; AMP; AMP; AMP; AMP; AMP; AMP; AMP; |
|
143 |
-TCGA-73-4666-01 MUT; MUT; MUT; MUT; MUT; MUT; MUT; AMP; |
|
144 |
-TCGA-73-4668-01 MUT; MUT; AMP; HOMDEL; MUT; AMP; AMP; MUT; MUT; MUT; MUT; MUT; MUT; MUT; |
|
145 |
-TCGA-73-4670-01 MUT; MUT; MUT; MUT; MUT; HOMDEL; MUT; MUT; MUT; MUT; |
|
146 |
-TCGA-73-4675-01 MUT; |
|
147 |
-TCGA-73-4677-01 MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; |
|
148 |
-TCGA-05-5420-01 |
|
149 |
-TCGA-05-5423-01 MUT; MUT; AMP; AMP; MUT;AMP; AMP; AMP; |
|
150 |
-TCGA-05-5425-01 AMP; |
|
151 |
-TCGA-05-5428-01 MUT; AMP; AMP; MUT; MUT; MUT; MUT; MUT;AMP; MUT; MUT; MUT; |
|
152 |
-TCGA-05-5429-01 HOMDEL; MUT; |
|
153 |
-TCGA-05-5715-01 HOMDEL; AMP; AMP; |
|
154 |
-TCGA-35-5375-01 MUT; MUT; AMP; MUT; MUT; MUT; MUT; MUT; MUT; |
|
155 |
-TCGA-44-5643-01 MUT; MUT; |
|
156 |
-TCGA-44-5645-01 MUT; MUT; MUT;AMP; |
|
157 |
-TCGA-50-5045-01 MUT; MUT; MUT; MUT;AMP; AMP; MUT; MUT; MUT; |
|
158 |
-TCGA-50-5049-01 MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; |
|
159 |
-TCGA-50-5055-01 |
|
160 |
-TCGA-50-5066-01 MUT; MUT; MUT; MUT; MUT; MUT; |
|
161 |
-TCGA-50-5068-01 MUT; MUT; HOMDEL; MUT; MUT; |
|
162 |
-TCGA-50-5936-01 MUT; MUT; HOMDEL; |
|
163 |
-TCGA-50-5939-01 MUT; MUT; MUT; AMP; MUT; |
|
164 |
-TCGA-55-5899-01 MUT; MUT;HOMDEL; MUT; HOMDEL; MUT; HOMDEL; MUT; HOMDEL; HOMDEL; |
|
165 |
-TCGA-64-5774-01 HOMDEL; MUT; MUT; HOMDEL; HOMDEL; MUT; HOMDEL; HOMDEL; HOMDEL; HOMDEL; |
|
166 |
-TCGA-64-5775-01 MUT; MUT; HOMDEL; MUT; MUT; AMP; |
|
167 |
-TCGA-64-5778-01 MUT; MUT; MUT; MUT;AMP; AMP; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; |
|
168 |
-TCGA-64-5779-01 MUT; MUT; MUT; MUT; MUT; HOMDEL; MUT; |
|
169 |
-TCGA-64-5781-01 MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; MUT; |
|
170 |
-TCGA-64-5815-01 MUT; HOMDEL; MUT;AMP; AMP; |
|
171 |
-TCGA-75-5146-01 MUT; MUT; MUT; MUT; MUT; MUT; |
|
172 |
-TCGA-75-5147-01 MUT; AMP; AMP; |
|
173 |
-TCGA-80-5611-01 MUT; AMP; MUT; MUT; AMP; |
174 | 0 |
deleted file mode 100644 |
... | ... |
@@ -1,123 +0,0 @@ |
1 |
-library(ComplexHeatmap) |
|
2 |
-library(GetoptLong) |
|
3 |
- |
|
4 |
-mat = read.table("tcga_lung_adenocarcinoma_provisional_ras_raf_mek_jnk_signalling.txt", header = TRUE,stringsAsFactors=FALSE, sep = "\t") |
|
5 |
-mat[is.na(mat)] = "" |
|
6 |
-rownames(mat) = mat[, 1] |
|
7 |
-mat = mat[, -1] |
|
8 |
-mat= mat[, -ncol(mat)] |
|
9 |
-mat = t(as.matrix(mat)) |
|
10 |
- |
|
11 |
-sample_order = scan("sample_order.txt", what = "character") |
|
12 |
-mat = mat[, sample_order] |
|
13 |
- |
|
14 |
-mat_origin = mat |
|
15 |
-mat = mat[, !apply(mat, 2, function(x) all(grepl("^\\s*$", x)))] |
|
16 |
- |
|
17 |
-altered = ncol(mat)/ncol(mat_origin) |
|
18 |
- |
|
19 |
-type_col = c("AMP" = "red", "HOMDEL"= "blue", "MUT" = "#008000") |
|
20 |
-type_name = c("AMP" = "Amplification", "HOMDEL" = "Deep deletion", "MUT" = "Mutation") |
|
21 |
- |
|
22 |
- |
|
23 |
-add_oncoprint = function(type, x, y, width, height) { |
|
24 |
- if(any(type %in% "")) { |
|
25 |
- grid.rect(x, y, width - unit(0.5, "mm"), height - unit(1, "mm"), gp = gpar(col = NA, fill = "#CCCCCC")) |
|
26 |
- } |
|
27 |
- if(any(type %in% "AMP")) { |
|
28 |
- grid.rect(x, y, width - unit(0.5, "mm"), height - unit(1, "mm"), gp = gpar(col = NA, fill = type_col["AMP"])) |
|
29 |
- } |
|
30 |
- if(any(type %in% "HOMDEL")) { |
|
31 |
- grid.rect(x, y, width - unit(0.5, "mm"), height - unit(1, "mm"), gp = gpar(col = NA, fill = type_col["HOMDEL"])) |
|
32 |
- } |
|
33 |
- if(any(type %in% "MUT")) { |
|
34 |
- grid.rect(x, y, width - unit(0.5, "mm"), height*(1/3), gp = gpar(col = NA, fill = type_col["MUT"])) |
|
35 |
- } |
|
36 |
-} |
|
37 |
- |
|
38 |
-##################################################################### |
|
39 |
-# row annotation which shows percent of mutations in all samples |
|
40 |
-pct = apply(mat_origin, 1, function(x) sum(!grepl("^\\s*$", x))/length(x))*100 |
|
41 |
-pct = paste0(round(pct),"%") |
|
42 |
-ha_pct = rowAnnotation(pct = anno_text(pct, which = "row"), width = grobWidth(textGrob("100%", gp = gpar(fontsize = 10)))) |
|
43 |
- |
|
44 |
- |
|
45 |
-##################################################################### |
|
46 |
-# row annotation which is a barplot |
|
47 |
-anno_row_bar = function(index) { |
|
48 |
- n = length(index) |
|
49 |
- tb = apply(mat[index, ], 1, function(x) { |
|
50 |
- x = unlist(strsplit(x, ";")) |
|
51 |
- x = x[!grepl("^\\s*$", x)] |
|
52 |
- x = sort(x) |
|
53 |
- table(x) |
|
54 |
- }) |
|
55 |
- max_count = max(sapply(tb, sum)) |
|
56 |
- pushViewport(viewport(xscale = c(0, max_count*1.1), yscale = c(0.5, n + 0.5))) |
|
57 |
- for(i in seq_along(tb)) { |
|
58 |
- if(length(tb[[i]])) { |
|
59 |
- x = cumsum(tb[[i]]) |
|
60 |
- # row order is from top to end while coordinate of y is from bottom to top |
|
61 |
- # so here we need to use n-i+1 |
|
62 |
- grid.rect(x, n-i+1, width = tb[[i]], height = 0.8, default.units = "native", just = "right", gp = gpar(col = NA, fill = type_col[names(tb[[i]])])) |
|
63 |
- } |
|
64 |
- } |
|
65 |
- breaks = grid.pretty(c(0, max_count)) |
|
66 |
- grid.xaxis(at = breaks, label = breaks, main = FALSE, gp = gpar(fontsize = 10)) |
|
67 |
- upViewport() |
|
68 |
-} |
|
69 |
- |
|
70 |
-ha_row_bar = rowAnnotation(row_bar = anno_row_bar, width = unit(4, "cm")) |
|
71 |
- |
|
72 |
-################################################################### |
|
73 |
-# column annotation which is also a barplot |
|
74 |
-anno_column_bar = function(index) { |
|
75 |
- n = length(index) |
|
76 |
- tb = apply(mat[, index], 2, function(x) { |
|
77 |
- x = unlist(strsplit(x, ";")) |
|
78 |
- x = x[!grepl("^\\s*$", x)] |
|
79 |
- x = sort(x) |
|
80 |
- table(x) |
|
81 |
- }) |
|
82 |
- max_count = max(sapply(tb, sum)) |
|
83 |
- pushViewport(viewport(yscale = c(0, max_count*1.1), xscale = c(0.5, n + 0.5))) |
|
84 |
- for(i in seq_along(tb)) { |
|
85 |
- if(length(tb[[i]])) { |
|
86 |
- y = cumsum(tb[[i]]) |
|
87 |
- grid.rect(i, y, height = tb[[i]], width = 0.8, default.units = "native", just = "top", gp = gpar(col = NA, fill = type_col[names(tb[[i]])])) |
|
88 |
- } |
|
89 |
- } |
|
90 |
- breaks = grid.pretty(c(0, max_count)) |
|
91 |
- grid.yaxis(at = breaks, label = breaks, gp = gpar(fontsize = 10)) |
|
92 |
- upViewport() |
|
93 |
-} |
|
94 |
- |
|
95 |
-ha_column_bar = HeatmapAnnotation(column_bar = anno_column_bar, which = "column") |
|
96 |
- |
|
97 |
- |
|
98 |
- |
|
99 |
-##################################################################### |
|
100 |
-# the main matrix |
|
101 |
-ht = Heatmap(mat, rect_gp = gpar(type = "none"), cell_fun = function(j, i, x, y, width, height, fill) { |
|
102 |
- if(grepl("^\\s*$", mat[i, j])) { |
|
103 |
- type = "" |
|
104 |
- } else { |
|
105 |
- type = unique(strsplit(mat[i, j], ";")[[1]]) |
|
106 |
- } |
|
107 |
- if(setequal(type, "MUT")) { |
|
108 |
- type = c("MUT", "") |
|
109 |
- } |
|
110 |
- add_oncoprint(type, x, y, width, height) |
|
111 |
-}, row_names_gp = gpar(fontsize = 10), show_column_names = FALSE, show_heatmap_legend = FALSE, |
|
112 |
-top_annotation = ha_column_bar, top_annotation_height = unit(2, "cm")) |
|
113 |
- |
|
114 |
-ht_list = ha_pct + ht + ha_row_bar |
|
115 |
- |
|
116 |
-######################################################### |
|
117 |
-# legend |
|
118 |
-legend = legendGrob(labels = type_name[names(type_col)], pch = 15, gp = gpar(col = type_col), nrow = 1) |
|
119 |
- |
|
120 |
-#pdf("oncoprint.pdf", width = 10, height = 10) |
|
121 |
-draw(ht_list, newpage = FALSE, annotation_legend_side = "bottom", annotation_legend_list = list(legend), column_title = qq("OncoPrint for TCGA Lung Adenocarcinoma, genes in Ras Raf MEK JNK signalling.\nAltered in @{ncol(mat)}/@{ncol(mat_origin)} (@{round(altered*100)}% of cases)"), column_title_gp = gpar(fontsize = 12, fontface = "bold")) |
|
122 |
-#dev.off() |
|
123 |
- |
... | ... |
@@ -68,7 +68,7 @@ to get full use of the package. |
68 | 68 |
There are several vignettes in the package. Each vignette focuses on a specific topic. Following |
69 | 69 |
lists the general topics discussed in these vignettes: |
70 | 70 |
|
71 |
- 1. [**Making a single Heatmap**](1.single_heatmap.html) |
|
71 |
+ 1. [**Making a single Heatmap**](s2.single_heatmap.html) |
|
72 | 72 |
|
73 | 73 |
This vignette introduces the basic configuration for making a single heatmap. Similar as other |
74 | 74 |
R functions/packages, the basic usage is quite similar, but there are several unique features |
... | ... |
@@ -90,28 +90,32 @@ lists the general topics discussed in these vignettes: |
90 | 90 |
different levels that split the heatmap. |
91 | 91 |
- The heatmap body itself can be completely self-defined. |
92 | 92 |
|
93 |
- 2. [**Making a list of heatmaps**](2.a_list_of_heatmaps.html) |
|
93 |
+ 2. [**Making a list of heatmaps**](s3.a_list_of_heatmaps.html) |
|
94 | 94 |
|
95 | 95 |
This vignette introduces how to concatenate a list of heatmaps and how adjustment is applied to keep |
96 | 96 |
the correspondence of the heatmaps. |
97 | 97 |
|
98 |
- 3. [**Heatmap annotations**](3.heatmap_annotation.html) |
|
98 |
+ 3. [**Heatmap annotations**](s4.heatmap_annotation.html) |
|
99 | 99 |
|
100 | 100 |
This vignette introduces the concept of the heatmap annotation and demonstrate how to make simple annotations |
101 | 101 |
as well as complex annotations. Also, the vignette explains the difference between column annotations |
102 | 102 |
and row annotations. |
103 | 103 |
|
104 |
- 4. [**Heatmap and Annotation Legends**](4.legend.html) |
|
104 |
+ 4. [**Heatmap and Annotation Legends**](s5.legend.html) |
|
105 | 105 |
|
106 | 106 |
This vignette introduces how to configurate the heatmap legend and annotation legend, also |
107 | 107 |
how to add self-defined legends. |
108 | 108 |
|
109 |
- 5. [**Heatmap decoration**](5.heatmap_decoration.html) |
|
109 |
+ 5. [**Heatmap decoration**](s6.heatmap_decoration.html) |
|
110 | 110 |
|
111 | 111 |
This vignette introduces methods to add more self-defined graphics to the heatmaps after the heatmaps |
112 | 112 |
are generated. |
113 | 113 |
|
114 |
- 6. [**Examples**](6.examples.html) |
|
114 |
+ 6. [**Examples**](s7.examples.html) |
|
115 | 115 |
|
116 | 116 |
More simulated and real-world examples are shown in this vignette. |
117 |
+ |
|
118 |
+ 7. [**OncoPrint**](s8.oncoprint.html) |
|
117 | 119 |
|
120 |
+ How to make an oncoPrint. |
|
121 |
+ |
... | ... |
@@ -117,8 +117,8 @@ mat_with_na[sample(c(TRUE, FALSE), nrow(mat)*ncol(mat), replace = TRUE, prob = c |
117 | 117 |
Heatmap(mat_with_na, na_col = "orange") |
118 | 118 |
``` |
119 | 119 |
|
120 |
-Color space is important for interpolating colors. By default, colors are linearly interpolated in [LAB](https://en.wikipedia.org/wiki/Lab_color_space), but you can select the color space in `colorRamp2()` function. Compare following two plots |
|
121 |
-(`+` operation on two heatmaps will be introduced in [**Making a list of heatmaps**](a3.a_list_of_heatmap.html) vignette): |
|
120 |
+Color space is important for interpolating colors. By default, colors are linearly interpolated in [LAB color space](https://en.wikipedia.org/wiki/Lab_color_space), but you can select the color space in `colorRamp2()` function. Compare following two plots |
|
121 |
+(`+` operation on two heatmaps will be introduced in [**Making a list of heatmaps**](s3.a_list_of_heatmaps.html) vignette): |
|
122 | 122 |
|
123 | 123 |
```{r, fig.width = 10} |
124 | 124 |
f1 = colorRamp2(seq(min(mat), max(mat), length = 3), c("blue", "#EEEEEE", "red")) |
... | ... |
@@ -127,22 +127,39 @@ Heatmap(mat, col = f1, column_title = "LAB color space") + |
127 | 127 |
Heatmap(mat, col = f2, column_title = "RGB color space") |
128 | 128 |
``` |
129 | 129 |
|
130 |
-On following figure, corresponding values change evenly on x-axis, you can see how colors change under different |
|
131 |
-color spaces. Choosing a proper color space is a little bit subjective and it depends on specific data and color theme. |
|
130 |
+On following figure, corresponding values change evenly on the folded axis, you can see how colors change under different |
|
131 |
+color spaces (the plot is made by **HilbertCurve** package). Choosing a proper color space is a little bit |
|
132 |
+subjective and it depends on specific data and color theme. |
|
132 | 133 |
Sometimes you need to try several color spaces to determine one which can best reveal potential structure of your data. |
133 | 134 |
|
134 |
-```{r, fig.width = 10, fig.height = 4} |
|
135 |
-space = c("RGB", "LAB", "XYZ", "sRGB", "LUV") |
|
136 |
-x = seq(-1, 1, length = 100) |
|
137 | 135 |
|
138 |
-par(xpd = NA) |
|
139 |
-plot(NULL, xlim = c(-1, 1), ylim = c(0.5, length(space)-0.5), type = "n", axes = FALSE, ann = FALSE) |
|
136 |
+```{r, fig.width = 14, fig.height = 14/5, echo = FALSE, message = FALSE} |
|
137 |
+suppressPackageStartupMessages(library(HilbertCurve)) |
|
138 |
+space = c("RGB", "LAB", "XYZ", "sRGB", "LUV") |
|
139 |
+pushViewport(viewport(layout = grid.layout(nr = 1, nc = length(space)))) |
|
140 | 140 |
for(i in seq_along(space)) { |
141 |
- f = colorRamp2(c(-1, 0, 1), c("blue", "#EEEEEE", "red"), space = space[i]) |
|
142 |
- rect(x - 1/100, i - 0.5, x + 1/100, i + 0.5, col = f(x), border = NA) |
|
143 |
- text(1, i, space[i], adj = c(-0.2, 0.5)) |
|
141 |
+ pushViewport(viewport(layout.pos.row = 1, layout.pos.col = i)) |
|
142 |
+ hc = HilbertCurve(1, 100, level = 4, newpage = FALSE, title = space[i]) |
|
143 |
+ ir = IRanges(start = 1:99, end = 2:100) |
|
144 |
+ f = colorRamp2(c(-1, 0, 1), c("green", "black", "red"), space = space[i]) |
|
145 |
+ col = f(seq(-1, 1, length = 100)) |
|
146 |
+ hc_points(hc, ir, np = 3, gp = gpar(col = col, fill = col)) |
|
147 |
+ upViewport() |
|
144 | 148 |
} |
145 |
-axis(side = 1) |
|
149 |
+upViewport() |
|
150 |
+grid.newpage() |
|
151 |
+pushViewport(viewport(layout = grid.layout(nr = 1, nc = length(space)))) |
|
152 |
+for(i in seq_along(space)) { |
|
153 |
+ pushViewport(viewport(layout.pos.row = 1, layout.pos.col = i)) |
|
154 |
+ hc = HilbertCurve(1, 100, level = 4, newpage = FALSE, title = space[i]) |
|
155 |
+ ir = IRanges(start = 1:99, end = 2:100) |
|
156 |
+ f = colorRamp2(c(-1, 0, 1), c("blue", "white", "red"), space = space[i]) |
|
157 |
+ col = f(seq(-1, 1, length = 100)) |
|
158 |
+ hc_points(hc, ir, np = 3, gp = gpar(col = col, fill = col)) |
|
159 |
+ upViewport() |
|
160 |
+} |
|
161 |
+upViewport() |
|
162 |
+ |
|
146 | 163 |
``` |
147 | 164 |
|
148 | 165 |
## Titles |
... | ... |
@@ -150,14 +167,14 @@ axis(side = 1) |
150 | 167 |
The name of the heatmap by default is used as the title of the heatmap legend. |
151 | 168 |
The name also plays as a unique id if you plot more than one heatmaps together. |
152 | 169 |
Later we can use this name to go to the corresponding heatmap to add more graphics |
153 |
-(see [**Heatmap Decoration**](5.heatmap_decoration.html) vignette). |
|
170 |
+(see [**Heatmap Decoration**](s6.heatmap_decoration.html) vignette). |
|
154 | 171 |
|
155 | 172 |
```{r with_matrix_name} |
156 | 173 |
Heatmap(mat, name = "foo") |
157 | 174 |
``` |
158 | 175 |
|
159 | 176 |
The title of the heatmap legend can be modified by `heatmap_legend_param` |
160 |
-(see [**Heatmap and Annotation Legends**](4.legend.html) vignette |
|
177 |
+(see [**Heatmap and Annotation Legends**](s5.legend.html) vignette |
|
161 | 178 |
for more control on the legend). |
162 | 179 |
|
163 | 180 |
```{r heatmap_legend_title} |
... | ... |
@@ -348,10 +365,10 @@ Heatmap(mat, name = "foo", row_names_gp = gpar(col = c(rep("red", 4), rep("blue" |
348 | 365 |
|
349 | 366 |
Currently, rotations for column names and row names are not supported (or maybe in the future versions). Because |
350 | 367 |
after the text rotation, the dimension names will go inside other heatmap components |
351 |
-which will mess up the heatmap layout. However, as will be introduced in [**Heatmap Annotation**](3.heatmap_annotation.html) |
|
368 |
+which will mess up the heatmap layout. However, as will be introduced in [**Heatmap Annotation**](s4.heatmap_annotation.html) |
|
352 | 369 |
vignette, text rotation is allowed in the heatmap annotations. Thus, users can provide a row annotation |
353 | 370 |
or column annotation which only contains rotated text to simulate rotated row/column names (You will see the |
354 |
-example in the [**Heatmap Annotation**](3.heatmap_annotation.html) vignette). |
|
371 |
+example in the [**Heatmap Annotation**](s4.heatmap_annotation.html) vignette). |
|
355 | 372 |
|
356 | 373 |
## Split heatmap by rows |
357 | 374 |
|
... | ... |
@@ -31,7 +31,7 @@ options(width = 100) |
31 | 31 |
|
32 | 32 |
A list of heatmaps can improve visualization of the correspondence between multiple data sources. |
33 | 33 |
In this vignette, we will discuss configurations for making a list of heatmaps and you can |
34 |
-see more real-world examples in the [**Examples**](6.examples.html) vignette. |
|
34 |
+see more real-world examples in the [**Examples**](s7.examples.html) vignette. |
|
35 | 35 |
|
36 | 36 |
## Heatmap concatenation |
37 | 37 |
|
... | ... |
@@ -167,7 +167,7 @@ ht_global_opt(RESET = TRUE) |
167 | 167 |
## Heatmap list with row annotations |
168 | 168 |
|
169 | 169 |
Row annotations can also be reordered and split according to the main heatmap, |
170 |
-please see [**Heatmap Annotation**](3.heatmap_annotationhtml) for more explanations. |
|
170 |
+please see [**Heatmap Annotation**](s4.heatmap_annotation.html) for more explanations. |
|
171 | 171 |
|
172 | 172 |
## Session info |
173 | 173 |
|
... | ... |
@@ -53,18 +53,6 @@ Heatmap(expr$chr, name = "chr", col = rand_color(length(unique(expr$chr))), |
53 | 53 |
width = unit(5, "mm")) |
54 | 54 |
``` |
55 | 55 |
|
56 |
-### Show number of alterations for OncoPrint |
|
57 |
- |
|
58 |
-Following examples is <a href="http://www.cbioportal.org/faq.jsp#what-are-oncoprints">OncoPrint</a>. |
|
59 |
-The basic idea is to self define the heatmap body. Besides the default style which is |
|
60 |
-provided by <a href="http://www.cbioportal.org/index.do">cBioPortal</a>, there are |
|
61 |
-additional barplots at both sides of the heatmap which show numbers of different alterations for |
|
62 |
-each sample and for each gene. Source code is available <a href="https://github.com/jokergoo/ComplexHeatmap/blob/master/vignettes/oncoprint.R">here</a>. |
|
63 |
- |
|
64 |
-```{r, echo = FALSE, fig.width = 10, fig.height = 8} |
|
65 |
-source("oncoprint.R") |
|
66 |
-``` |
|
67 |
- |
|
68 | 56 |
### Visualize genomic regions and other correspondance |
69 | 57 |
|
70 | 58 |
Following examples visualizes correlation between methylation and expression, as well as other annotation information (data are randomly generated). In the heatmap, each row corresponds to a differentially methylated regions (DMRs). |
71 | 59 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,189 @@ |
1 |
+ |
|
2 |
+<!-- |
|
3 |
+%\VignetteEngine{knitr} |
|
4 |
+%\VignetteIndexEntry{OncoPrint} |
|
5 |
+--> |
|
6 |
+ |
|
7 |
+OncoPrint |
|
8 |
+======================================== |
|
9 |
+ |
|
10 |
+**Author**: Zuguang Gu ( z.gu@dkfz.de ) |
|
11 |
+ |
|
12 |
+**Date**: `r Sys.Date()` |
|
13 |
+ |
|
14 |
+------------------------------------------------------------- |
|
15 |
+ |
|
16 |
+```{r global_settings, echo = FALSE, message = FALSE} |
|
17 |
+library(markdown) |
|
18 |
+options(markdown.HTML.options = c(options('markdown.HTML.options')[[1]], "toc")) |
|
19 |
+ |
|
20 |
+library(knitr) |
|
21 |
+knitr::opts_chunk$set( |
|
22 |
+ error = FALSE, |
|
23 |
+ tidy = FALSE, |
|
24 |
+ message = FALSE, |
|
25 |
+ fig.align = "center", |
|
26 |
+ fig.width = 5, |
|
27 |
+ fig.height = 5) |
|
28 |
+options(markdown.HTML.stylesheet = "custom.css") |
|
29 |
+ |
|
30 |
+options(width = 100) |
|
31 |
+``` |
|
32 |
+ |
|
33 |
+<a href="http://www.cbioportal.org/faq.jsp#what-are-oncoprints">OncoPrint</a> is a way to visualize |
|
34 |
+multiple genomic alteration events by heatmap. Here the **ComplexHeatmap** package provides a `oncoPrint()` function. |
|
35 |
+Besides the default style which is provided by <a href="http://www.cbioportal.org/index.do">cBioPortal</a>, there are |
|
36 |
+additional barplots at both sides of the heatmap which show numbers of different alterations for |
|
37 |
+each sample and for each gene. Also with the functionality of **ComplexHeatmap**, you can control oncoPrint with |
|
38 |
+more flexibilities. |
|
39 |
+ |
|
40 |
+There are two different forms of input data. The first is represented as a matrix in which |
|
41 |
+element would include multiple alterations in a form of a complex string. In follow example, |
|
42 |
+'g1' in 's1' has two types of alterations which are 'snv' and 'indel'. |
|
43 |
+ |
|
44 |
+```{r} |
|
45 |
+mat = read.table(textConnection( |
|
46 |
+" s1 s2 s3 |
|
47 |
+g1 snv;indel snv indel |
|
48 |
+g2 snv;indel snv |
|
49 |
+g3 snv indel;snv"), row.names = 1, header = TRUE, sep = "\t", stringsAsFactors = FALSE) |
|
50 |
+mat = as.matrix(mat) |
|
51 |
+mat |
|
52 |
+``` |
|
53 |
+ |
|
54 |
+In this case, we need to define a function to extract different alteration types and send the function |
|
55 |
+to `get_type` argument. The function should return a vector of alteration types. |
|
56 |
+ |
|
57 |
+Since different alteration types may be drawn into one same grid in the heatmap, we need to define |
|
58 |
+graphic function to add the graphics. Here if the graphics have no transparency, orders of how to add |
|
59 |
+graphics matters. In following example, snv are first drawn and then the indel. You can see rectangles |
|
60 |
+for indels are actually smaller than that for snvs so that you can visualiza both snvs and indels if they |
|
61 |
+are in a same grid. |
|
62 |
+ |
|
63 |
+For the self-defined graphic function, there should be four arguments which are positions of the grids |
|
64 |
+on the heatmap (`x` and `y`), and widths and heights of the grids (`w` and `h`). |
|
65 |
+ |
|
66 |
+Colors for different alterations are defined in `col`. It should be a named vector for which names correspond |
|
67 |
+to alteration types. |
|
68 |
+ |
|
69 |
+ |
|
70 |
+```{r} |
|
71 |
+oncoPrint(mat, get_type = function(x) strsplit(x, ";")[[1]], |
|
72 |
+ alter_fun_list = list( |
|
73 |
+ snv = function(x, y, w, h) grid.rect(x, y, w*0.9, h*0.9, gp = gpar(fill = "red", col = NA)), |
|
74 |
+ indel = function(x, y, w, h) grid.rect(x, y, w*0.9, h*0.4, gp = gpar(fill = "blue", col = NA)) |
|
75 |
+ ), col = c(snv = "red", indel = "blue")) |
|
76 |
+``` |
|
77 |
+ |
|
78 |
+The second type of input data is a list of matrix for which each matrix contains binary value representing |
|
79 |
+whether the alteration is absent or present. The list should have names and the name corresponds to the alteration |
|
80 |
+types. |
|
81 |
+ |
|
82 |
+```{r} |
|
83 |
+mat_list = list(snv = matrix(c(1, 0, 1, 1, 1, 0, 0, 1, 1), nrow = 3), |
|
84 |
+ indel = matrix(c(1, 0, 0, 0, 1, 0, 1, 0, 1), nrow = 3)) |
|
85 |
+rownames(mat_list$snv) = rownames(mat_list$indel) = c("g1", "g2", "g3") |
|
86 |
+colnames(mat_list$snv) = colnames(mat_list$indel) = c("s1", "s2", "s3") |
|
87 |
+mat_list |
|
88 |
+``` |
|
89 |
+ |
|
90 |
+Same as the first example, but here we define `background` in `alter_fun_list` argument. This function defines |
|
91 |
+how to add graphics when there is no alteration. |
|
92 |
+ |
|
93 |
+```{r} |
|
94 |
+oncoPrint(mat_list, |
|
95 |
+ alter_fun_list = list( |
|
96 |
+ background = function(x, y, w, h) NULL, |
|
97 |
+ snv = function(x, y, w, h) grid.rect(x, y, w*0.9, h*0.9, gp = gpar(fill = "red", col = NA)), |
|
98 |
+ indel = function(x, y, w, h) grid.rect(x, y, w*0.9, h*0.4, gp = gpar(fill = "blue", col = NA)) |
|
99 |
+ ), col = c(snv = "red", indel = "blue")) |
|
100 |
+``` |
|
101 |
+ |
|
102 |
+Now we make an oncoPrint with a real-world data. The data is retrieved from [cBioPortal](http://www.cbioportal.org/). |
|
103 |
+Steps for getting the data are as follows: |
|
104 |
+ |
|
105 |
+1. go to http://www.cbioportal.org |
|
106 |
+2. search Cancer Study: "Lung Adenocarcinoma Carcinoma" and select: "Lung Adenocarcinoma Carcinoma (TCGA, Provisinal)" |
|
107 |
+3. In "Enter Gene Set" field, select: "General: Ras-Raf-MEK-Erk/JNK signaling (26 genes)" |
|
108 |
+4. submit the form |
|
109 |
+ |
|
110 |
+In the results page, |
|
111 |
+ |
|
112 |
+5. go to "Download" tab, download text in "Type of Genetic alterations across all cases" |
|
113 |
+ |
|
114 |
+The order of samples can also be downloaded from the results page, |
|
115 |
+ |
|
116 |
+6. go to "OncoPrint" tab, move the mouse above the plot, click "download" icon and click "Sample order" |
|
117 |
+ |
|
118 |
+First we read the data and do some pre-processing. |
|
119 |
+ |
|
120 |
+```{r} |
|
121 |
+mat = read.table(paste0(system.file("extdata", package = "ComplexHeatmap"), |
|
122 |
+ "/tcga_lung_adenocarcinoma_provisional_ras_raf_mek_jnk_signalling.txt"), |
|
123 |
+ header = TRUE,stringsAsFactors=FALSE, sep = "\t") |
|
124 |
+mat[is.na(mat)] = "" |
|
125 |
+rownames(mat) = mat[, 1] |
|
126 |
+mat = mat[, -1] |
|
127 |
+mat= mat[, -ncol(mat)] |
|
128 |
+mat = t(as.matrix(mat)) |
|
129 |
+``` |
|
130 |
+ |
|
131 |
+We can adjust the order of the matrix. Here cbioPortal also provides sample orders: |
|
132 |
+ |
|
133 |
+```{r} |
|
134 |
+sample_order = scan(paste0(system.file("extdata", package = "ComplexHeatmap"), |
|
135 |
+ "/sample_order.txt"), what = "character") |
|
136 |
+mat = mat[, sample_order] |
|
137 |
+``` |
|
138 |
+ |
|
139 |
+There are three different alterations in `mat`: `HOMDEL`, `AMP` and `MUT`. We first |
|
140 |
+define how to add graphics to correspond to different alterations. |
|
141 |
+ |
|
142 |
+```{r} |
|
143 |
+alter_fun_list = list( |
|
144 |
+ background = function(x, y, w, h) { |
|
145 |
+ grid.rect(x, y, w-unit(0.5, "mm"), h-unit(0.5, "mm"), gp = gpar(fill = "#CCCCCC", col = NA)) |
|
146 |
+ }, |
|
147 |
+ HOMDEL = function(x, y, w, h) { |
|
148 |
+ grid.rect(x, y, w-unit(0.5, "mm"), h-unit(0.5, "mm"), gp = gpar(fill = "blue", col = NA)) |
|
149 |
+ }, |
|
150 |
+ AMP = function(x, y, w, h) { |
|
151 |
+ grid.rect(x, y, w-unit(0.5, "mm"), h-unit(0.5, "mm"), gp = gpar(fill = "red", col = NA)) |
|
152 |
+ }, |
|
153 |
+ MUT = function(x, y, w, h) { |
|
154 |
+ grid.rect(x, y, w-unit(0.5, "mm"), h*0.33, gp = gpar(fill = "#008000", col = NA)) |
|
155 |
+ } |
|
156 |
+) |
|
157 |
+``` |
|
158 |
+ |
|
159 |
+Also colors for different alterations which will be used for barplots. |
|
160 |
+ |
|
161 |
+```{r} |
|
162 |
+col = c("MUT" = "#008000", "AMP" = "red", "HOMDEL" = "blue") |
|
163 |
+``` |
|
164 |
+ |
|
165 |
+Make the oncoPrint and adjust heatmap components such as the title and the legend. |
|
166 |
+ |
|
167 |
+```{r, fig.width = 12, fig.height = 8} |
|
168 |
+oncoPrint(mat, get_type = function(x) strsplit(x, ";")[[1]], |
|
169 |
+ alter_fun_list = alter_fun_list, col = col, |
|
170 |
+ column_title = "OncoPrint for TCGA Lung Adenocarcinoma, genes in Ras Raf MEK JNK signalling", |
|
171 |
+ heatmap_legend_param = list(title = "Alternations", at = c("AMP", "HOMDEL", "MUT"), |
|
172 |
+ labels = c("Amplification", "Deep deletion", "Mutation"))) |
|
173 |
+``` |
|
174 |
+ |
|
175 |
+`oncoPrint()` actually returns a `HeatmapList` object, so you can add more Heatmaps or row annotations |
|
176 |
+to it to visualize more complicated information. |
|
177 |
+ |
|
178 |
+Following example splits the heatmap into two halves and add a new heatmap to the right. |
|
179 |
+ |
|
180 |
+```{r, fig.width = 12, fig.height = 8} |
|
181 |
+ht_list = oncoPrint(mat, get_type = function(x) strsplit(x, ";")[[1]], |
|
182 |
+ alter_fun_list = alter_fun_list, col = col, |
|
183 |
+ column_title = "OncoPrint for TCGA Lung Adenocarcinoma, genes in Ras Raf MEK JNK signalling", |
|
184 |
+ heatmap_legend_param = list(title = "Alternations", at = c("AMP", "HOMDEL", "MUT"), |
|
185 |
+ labels = c("Amplification", "Deep deletion", "Mutation")), |
|
186 |
+ split = sample(letters[1:2], nrow(mat), replace = TRUE)) + |
|
187 |
+Heatmap(matrix(rnorm(nrow(mat)*10), ncol = 10), width = unit(4, "cm")) |
|
188 |
+draw(ht_list, row_sub_title_side = "left") |
|
189 |
+``` |