Update graphsummary
... | ... |
@@ -1,13 +1,17 @@ |
1 | 1 |
Package: GeneTonic |
2 | 2 |
Title: Enjoy Analyzing And Integrating The Results From Differential Expression |
3 | 3 |
Analysis And Functional Enrichment Analysis |
4 |
-Version: 1.3.1 |
|
5 |
-Date: 2020-10-21 |
|
4 |
+Version: 1.3.2 |
|
5 |
+Date: 2021-02-19 |
|
6 | 6 |
Authors@R: |
7 | 7 |
c( |
8 | 8 |
person( |
9 | 9 |
given = "Federico", family = "Marini", role = c("aut", "cre"), |
10 | 10 |
email = "marinif@uni-mainz.de", comment = c(ORCID = "0000-0003-3252-7758") |
11 |
+ ), |
|
12 |
+ person( |
|
13 |
+ given = "Annekathrin", family = "Ludt", role = c("aut"), |
|
14 |
+ email = "anneludt@uni-mainz.de", comment = c(ORCID = "0000-0002-2475-4945") |
|
11 | 15 |
) |
12 | 16 |
) |
13 | 17 |
Description: This package provides a Shiny application that aims to combine at |
... | ... |
@@ -24,6 +28,7 @@ Imports: |
24 | 28 |
backbone, |
25 | 29 |
bs4Dash, |
26 | 30 |
colorspace, |
31 |
+ colourpicker, |
|
27 | 32 |
ComplexHeatmap, |
28 | 33 |
dendextend, |
29 | 34 |
DESeq2, |
... | ... |
@@ -46,6 +46,7 @@ export(shake_enrichrResult) |
46 | 46 |
export(shake_fgseaResult) |
47 | 47 |
export(shake_gprofilerResult) |
48 | 48 |
export(shake_topGOtableResult) |
49 |
+export(signature_volcano) |
|
49 | 50 |
export(styleColorBar_divergent) |
50 | 51 |
import(GO.db) |
51 | 52 |
import(SummarizedExperiment) |
... | ... |
@@ -98,6 +99,7 @@ importFrom(bs4Dash,bs4ValueBoxOutput) |
98 | 99 |
importFrom(bs4Dash,renderbs4InfoBox) |
99 | 100 |
importFrom(bs4Dash,renderbs4ValueBox) |
100 | 101 |
importFrom(colorspace,rainbow_hcl) |
102 |
+importFrom(colourpicker,colourInput) |
|
101 | 103 |
importFrom(dendextend,branches_attr_by_clusters) |
102 | 104 |
importFrom(dendextend,set) |
103 | 105 |
importFrom(dplyr,"%>%") |
... | ... |
@@ -2,11 +2,16 @@ |
2 | 2 |
|
3 | 3 |
## New features |
4 | 4 |
|
5 |
-* The main function `GeneTonic()` gains an extra parameter, `gtl` - this can be used to provided a named list object where a single parameter is passed (e.g. after loading in a single seralized object), while the functionality stays unaltered. |
|
5 |
+* The main function `GeneTonic()` gains an extra parameter, `gtl` - this can be used to provided a named list object where a single parameter is passed (e.g. after loading in a single serialized object), while the functionality stays unaltered. |
|
6 | 6 |
The same `gtl` parameter is also exposed in other functions of the package - see the vignette for some examples, or check the documentation of each specific function. |
7 | 7 |
|
8 | 8 |
* A new function to perform fuzzy clustering (following the implementation of DAVID) is added - see `gs_fuzzyclustering()`. It returns a table with additional information on the cluster of genesets and the status of each set in the group. |
9 | 9 |
|
10 |
+* A new function, `signature_volcano()`, adds a signature volcano plot to the `Gene-Geneset` panel. This plot displays the genes of a chosen geneset in color, while the remaining genes of the data are shown as shaded dots in the background. |
|
11 |
+ The color and transparency of the displayed genes can be chosen by the user, as well as the option to display the gene names of all genes in the geneset. |
|
12 |
+ |
|
13 |
+* `gs_summary_overview` can also generate bar plots instead of the default segment-dot (lollipop) plots |
|
14 |
+ |
|
10 | 15 |
# GeneTonic 1.2.0 |
11 | 16 |
|
12 | 17 |
## New features |
... | ... |
@@ -14,6 +14,7 @@ |
14 | 14 |
#' bs4ValueBoxOutput renderbs4InfoBox renderbs4ValueBox |
15 | 15 |
#' bs4TabPanel bs4TabCard |
16 | 16 |
#' @importFrom colorspace rainbow_hcl |
17 |
+#' @importFrom colourpicker colourInput |
|
17 | 18 |
#' @importFrom ComplexHeatmap Heatmap HeatmapAnnotation draw |
18 | 19 |
#' @importFrom dendextend branches_attr_by_clusters set |
19 | 20 |
#' @importFrom DESeq2 vst counts estimateSizeFactors normalizationFactors sizeFactors |
... | ... |
@@ -58,6 +58,7 @@ |
58 | 58 |
#' row.names = rownames(dds_macrophage) |
59 | 59 |
#' ) |
60 | 60 |
#' |
61 |
+#' |
|
61 | 62 |
#' # res object |
62 | 63 |
#' data(res_de_macrophage, package = "GeneTonic") |
63 | 64 |
#' res_de <- res_macrophage_IFNg_vs_naive |
... | ... |
@@ -706,7 +707,11 @@ GeneTonic <- function(dds, |
706 | 707 |
label = "Number of genesets", |
707 | 708 |
value = 15, min = 1, max = nrow(res_enrich)), |
708 | 709 |
selectInput("exp_condition", label = "Group/color by: ", |
709 |
- choices = c(NULL, names(colData(dds))), selected = NULL, multiple = TRUE) |
|
710 |
+ choices = c(NULL, names(colData(dds))), selected = NULL, multiple = TRUE), |
|
711 |
+ colourInput("col", "Select colour for volcano plot", "#1a81c2", |
|
712 |
+ returnName = TRUE, |
|
713 |
+ allowTransparent = TRUE), |
|
714 |
+ checkboxInput("labels", label = "Display all labels", value = FALSE) |
|
710 | 715 |
), |
711 | 716 |
|
712 | 717 |
# footer definition ------------------------------------------------------- |
... | ... |
@@ -918,6 +923,7 @@ GeneTonic <- function(dds, |
918 | 923 |
tagList( |
919 | 924 |
# verbatimTextOutput("netnode"), |
920 | 925 |
plotOutput("net_sigheatplot"), |
926 |
+ plotOutput("sig_volcano"), |
|
921 | 927 |
uiOutput("ggs_geneset_info") |
922 | 928 |
) |
923 | 929 |
}) |
... | ... |
@@ -964,6 +970,38 @@ GeneTonic <- function(dds, |
964 | 970 |
} |
965 | 971 |
}) |
966 | 972 |
|
973 |
+ output$sig_volcano <- renderPlot({ |
|
974 |
+ g <- reactive_values$ggs_graph() |
|
975 |
+ cur_sel <- input$ggsnetwork_selected |
|
976 |
+ cur_node <- match(cur_sel, V(g)$name) |
|
977 |
+ cur_nodetype <- V(g)$nodetype[cur_node] |
|
978 |
+ validate(need(cur_nodetype == "GeneSet", |
|
979 |
+ message = "Please select a gene set from the Gene-Geneset Graph." |
|
980 |
+ )) |
|
981 |
+ cur_gsid <- res_enrich$gs_id[match(input$ggsnetwork_selected, res_enrich$gs_description)] |
|
982 |
+ |
|
983 |
+ if (input$labels) { |
|
984 |
+ signature_volcano( |
|
985 |
+ res_de, |
|
986 |
+ res_enrich, |
|
987 |
+ annotation_obj = annotation_obj, |
|
988 |
+ geneset_id = cur_gsid, |
|
989 |
+ FDR = input$de_fdr, |
|
990 |
+ color = input$col, |
|
991 |
+ volcano_labels = Inf |
|
992 |
+ ) |
|
993 |
+ } else { |
|
994 |
+ signature_volcano( |
|
995 |
+ res_de, |
|
996 |
+ res_enrich, |
|
997 |
+ annotation_obj = annotation_obj, |
|
998 |
+ geneset_id = cur_gsid, |
|
999 |
+ FDR = input$de_fdr, |
|
1000 |
+ color = input$col |
|
1001 |
+ ) |
|
1002 |
+ } |
|
1003 |
+ }) |
|
1004 |
+ |
|
967 | 1005 |
output$ggs_geneset_info <- renderUI({ |
968 | 1006 |
g <- reactive_values$ggs_graph() |
969 | 1007 |
cur_sel <- input$ggsnetwork_selected |
... | ... |
@@ -245,7 +245,7 @@ shake_davidResult <- function(david_output_file) { |
245 | 245 |
#' # "Reactome_2016", |
246 | 246 |
#' # "WikiPathways_2019_Human") |
247 | 247 |
#' # degenes <- (deseqresult2df(res_macrophage_IFNg_vs_naive, FDR = 0.01)$SYMBOL) |
248 |
-#' # if called directly withÃn R... |
|
248 |
+#' # if called directly within R... |
|
249 | 249 |
#' # enrichr_output_macrophage <- enrichr(degenes, dbs) |
250 | 250 |
#' # or alternatively, if downloaded from the website in tabular format |
251 | 251 |
#' enrichr_output_file <- system.file("extdata", |
... | ... |
@@ -13,6 +13,8 @@ |
13 | 13 |
#' p-value - have been specified). |
14 | 14 |
#' @param color_by Character, specifying the column of `res_enrich` to be used |
15 | 15 |
#' for coloring the plotted gene sets. Defaults sensibly to `z_score`. |
16 |
+#' @param return_barchart Logical, whether to return a barchart (instead of the |
|
17 |
+#' default dot-segment plot); defaults to FALSE. |
|
16 | 18 |
#' |
17 | 19 |
#' @return A `ggplot` object |
18 | 20 |
#' |
... | ... |
@@ -54,18 +56,23 @@ |
54 | 56 |
#' res_enrich <- get_aggrscores(res_enrich, res_de, anno_df) |
55 | 57 |
#' |
56 | 58 |
#' gs_summary_overview(res_enrich) |
57 |
-#' |
|
59 |
+#' |
|
60 |
+#' # if desired, it can also be shown as a barplot |
|
61 |
+#' gs_summary_overview(res_enrich, 30, return_barchart = TRUE) |
|
58 | 62 |
gs_summary_overview <- function(res_enrich, |
59 | 63 |
n_gs = 20, |
60 | 64 |
p_value_column = "gs_pvalue", |
61 |
- color_by = "z_score" |
|
65 |
+ color_by = "z_score", |
|
66 |
+ return_barchart = FALSE |
|
62 | 67 |
# , size_by = "gs_de_count" |
63 | 68 |
) { |
64 |
- if (!(color_by %in% colnames(res_enrich))) { |
|
65 |
- stop("Your res_enrich object does not contain the ", |
|
66 |
- color_by, |
|
67 |
- " column.\n", |
|
68 |
- "Compute this first or select another column to use for the color.") |
|
69 |
+ if (!is.null(color_by)) { |
|
70 |
+ if (!(color_by %in% colnames(res_enrich))) { |
|
71 |
+ stop("Your res_enrich object does not contain the ", |
|
72 |
+ color_by, |
|
73 |
+ " column.\n", |
|
74 |
+ "Compute this first or select another column to use for the color.") |
|
75 |
+ } |
|
69 | 76 |
} |
70 | 77 |
|
71 | 78 |
re <- res_enrich |
... | ... |
@@ -75,17 +82,44 @@ gs_summary_overview <- function(res_enrich, |
75 | 82 |
re_sorted <- re %>% |
76 | 83 |
arrange(.data$logp10) %>% |
77 | 84 |
mutate(gs_description = factor(.data$gs_description, .data$gs_description)) |
78 |
- p <- ggplot(re_sorted, (aes_string(x = "gs_description", y = "logp10"))) + |
|
79 |
- geom_segment(aes_string(x = "gs_description", xend = "gs_description", y = 0, yend = "logp10"), color = "grey") + |
|
80 |
- geom_point(aes(col = .data[[color_by]]), size = 4) + |
|
81 |
- # geom_point(aes(col = .data[[color_by]], size = .data[[size_by]])) + |
|
82 |
- scale_color_gradient2(low = "#313695", mid = "#FFFFE5", high = "#A50026") + |
|
83 |
- coord_flip() + |
|
84 |
- labs(x = "Gene set description", |
|
85 |
- y = "-log10 p-value", |
|
86 |
- col = color_by) + |
|
87 |
- theme_minimal() |
|
88 |
- |
|
85 |
+ |
|
86 |
+ if (return_barchart) { |
|
87 |
+ p <- ggplot(re_sorted, (aes_string(x = "gs_description", y = "logp10"))) |
|
88 |
+ |
|
89 |
+ if (is.null(color_by)) { |
|
90 |
+ p <- p + geom_col() |
|
91 |
+ } else { |
|
92 |
+ p <- p + geom_col(aes(fill = .data[[color_by]])) + |
|
93 |
+ scale_fill_gradient2(low = "#313695", mid = "#FFFFE5", high = "#A50026") |
|
94 |
+ } |
|
95 |
+ |
|
96 |
+ p <- p + |
|
97 |
+ coord_flip() + |
|
98 |
+ labs(x = "Gene set description", |
|
99 |
+ y = "-log10 p-value", |
|
100 |
+ col = color_by) + |
|
101 |
+ theme_minimal() |
|
102 |
+ } else { |
|
103 |
+ p <- ggplot(re_sorted, (aes_string(x = "gs_description", y = "logp10"))) + |
|
104 |
+ geom_segment(aes_string(x = "gs_description", |
|
105 |
+ xend = "gs_description", |
|
106 |
+ y = 0, |
|
107 |
+ yend = "logp10"), color = "grey") |
|
108 |
+ |
|
109 |
+ if (is.null(color_by)) { |
|
110 |
+ p <- p + geom_point(size = 4) |
|
111 |
+ } else { |
|
112 |
+ p <- p + geom_point(aes(col = .data[[color_by]]), size = 4) + |
|
113 |
+ scale_color_gradient2(low = "#313695", mid = "#FFFFE5", high = "#A50026") |
|
114 |
+ } |
|
115 |
+ |
|
116 |
+ p <- p + |
|
117 |
+ coord_flip() + |
|
118 |
+ labs(x = "Gene set description", |
|
119 |
+ y = "-log10 p-value", |
|
120 |
+ col = color_by) + |
|
121 |
+ theme_minimal() |
|
122 |
+ } |
|
89 | 123 |
return(p) |
90 | 124 |
} |
91 | 125 |
|
... | ... |
@@ -208,8 +242,8 @@ gs_summary_overview_pair <- function(res_enrich, |
208 | 242 |
geom_point(aes(fill = .data[[color_by]]), size = 4, pch = 21) + |
209 | 243 |
geom_point(aes_string(y = "logp10_2", col = paste0(color_by, "_2")), |
210 | 244 |
size = 4, alpha = alpha_set2) + |
211 |
- scale_color_gradient2(low = "#313695", mid = "#FFFFE5", high = "#A50026") + |
|
212 |
- scale_fill_gradient2(low = "#313695", mid = "#FFFFE5", high = "#A50026", guide = FALSE) + |
|
245 |
+ scale_color_gradient2(low = "#313695", mid = "#FFFFE5", high = "#A50026", name = paste0(color_by, " set 2")) + |
|
246 |
+ scale_fill_gradient2(low = "#313695", mid = "#FFFFE5", high = "#A50026", name = paste0(color_by, " set 1")) + |
|
213 | 247 |
coord_flip() + |
214 | 248 |
labs(x = "Gene set description", |
215 | 249 |
y = "-log10 p-value", |
216 | 250 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,206 @@ |
1 |
+#' Plot a volcano plot of a geneset |
|
2 |
+#' |
|
3 |
+#' Plot a volcano plot for the geneset of the provided data, with the remaining |
|
4 |
+#' genes as shaded dots in the background of the plot. |
|
5 |
+#' |
|
6 |
+#' @param res_de A `DESeqResults` object. |
|
7 |
+#' @param res_enrich A `data.frame` object, storing the result of the functional |
|
8 |
+#' enrichment analysis. See more in the main function, [GeneTonic()], to check the |
|
9 |
+#' formatting requirements (a minimal set of columns should be present). |
|
10 |
+#' @param annotation_obj A `data.frame` object with the feature annotation |
|
11 |
+#' information, with at least two columns, `gene_id` and `gene_name`. |
|
12 |
+#' @param gtl A `GeneTonic`-list object, containing in its slots the arguments |
|
13 |
+#' specified above: `dds`, `res_de`, `res_enrich`, and `annotation_obj` - the names |
|
14 |
+#' of the list _must_ be specified following the content they are expecting. |
|
15 |
+#' @param geneset_id Character specifying the gene set identifier to be plotted. |
|
16 |
+#' @param genelist A vector of character strings, specifying the identifiers |
|
17 |
+#' contained in the `rownames` of the `res_de` input object. |
|
18 |
+#' @param FDR Numeric value, specifying the significance level for thresholding |
|
19 |
+#' adjusted p-values. Defaults to 0.05. |
|
20 |
+#' @param color Character string to specify color of filtered points in the plot. |
|
21 |
+#' Defaults to #1a81c2 (shade of blue). |
|
22 |
+#' @param volcano_labels Integer, maximum number of labels for the gene sets to be |
|
23 |
+#' plotted as labels on the volcano scatter plot. Defaults to 25. |
|
24 |
+#' @param plot_title Character string, to specify the title of the plot, |
|
25 |
+#' displayed over the volcano plot. If left to `NULL` as by default, it tries to use |
|
26 |
+#' the information on the geneset identifier provided. |
|
27 |
+#' |
|
28 |
+#' @return A plot returned by the [ggplot()] function |
|
29 |
+#' @export |
|
30 |
+#' |
|
31 |
+#' @examples |
|
32 |
+#' library("macrophage") |
|
33 |
+#' library("DESeq2") |
|
34 |
+#' library("org.Hs.eg.db") |
|
35 |
+#' library("AnnotationDbi") |
|
36 |
+#' |
|
37 |
+#' # dds object |
|
38 |
+#' data("gse", package = "macrophage") |
|
39 |
+#' dds_macrophage <- DESeqDataSet(gse, design = ~line + condition) |
|
40 |
+#' rownames(dds_macrophage) <- substr(rownames(dds_macrophage), 1, 15) |
|
41 |
+#' dds_macrophage <- estimateSizeFactors(dds_macrophage) |
|
42 |
+#' |
|
43 |
+#' |
|
44 |
+#' # annotation object |
|
45 |
+#' anno_df <- data.frame( |
|
46 |
+#' gene_id = rownames(dds_macrophage), |
|
47 |
+#' gene_name = mapIds(org.Hs.eg.db, |
|
48 |
+#' keys = rownames(dds_macrophage), |
|
49 |
+#' column = "SYMBOL", |
|
50 |
+#' keytype = "ENSEMBL"), |
|
51 |
+#' stringsAsFactors = FALSE, |
|
52 |
+#' row.names = rownames(dds_macrophage) |
|
53 |
+#' ) |
|
54 |
+#' |
|
55 |
+#' # res object |
|
56 |
+#' data(res_de_macrophage, package = "GeneTonic") |
|
57 |
+#' res_de <- res_macrophage_IFNg_vs_naive |
|
58 |
+#' |
|
59 |
+#' # res_enrich object |
|
60 |
+#' data(res_enrich_macrophage, package = "GeneTonic") |
|
61 |
+#' res_enrich <- shake_topGOtableResult(topgoDE_macrophage_IFNg_vs_naive) |
|
62 |
+#' res_enrich <- get_aggrscores(res_enrich, res_de, anno_df) |
|
63 |
+#' |
|
64 |
+#' signature_volcano(res_de, |
|
65 |
+#' res_enrich, |
|
66 |
+#' anno_df, |
|
67 |
+#' geneset_id = res_enrich$gs_id[1] |
|
68 |
+#' ) |
|
69 |
+#' |
|
70 |
+#' # alternatively |
|
71 |
+#' |
|
72 |
+#' chemokine_list <- c("ENSG00000108702", |
|
73 |
+#' "ENSG00000172156", |
|
74 |
+#' "ENSG00000181374", |
|
75 |
+#' "ENSG00000276409" |
|
76 |
+#' ) |
|
77 |
+#' |
|
78 |
+#' signature_volcano(res_de, |
|
79 |
+#' res_enrich, |
|
80 |
+#' anno_df, |
|
81 |
+#' genelist = chemokine_list |
|
82 |
+#' ) |
|
83 |
+#' |
|
84 |
+signature_volcano <- function(res_de, |
|
85 |
+ res_enrich, |
|
86 |
+ annotation_obj = NULL, |
|
87 |
+ gtl = NULL, |
|
88 |
+ geneset_id = NULL, |
|
89 |
+ genelist = NULL, |
|
90 |
+ FDR = 0.05, |
|
91 |
+ color = "#1a81c2", |
|
92 |
+ volcano_labels = 25, |
|
93 |
+ plot_title = NULL |
|
94 |
+) { |
|
95 |
+ |
|
96 |
+ if (!is.null(gtl)) { |
|
97 |
+ checkup_gtl(gtl) |
|
98 |
+ dds <- gtl$dds |
|
99 |
+ res_de <- gtl$res_de |
|
100 |
+ res_enrich <- gtl$res_enrich |
|
101 |
+ annotation_obj <- gtl$annotation_obj |
|
102 |
+ } |
|
103 |
+ |
|
104 |
+ # Retrieve information about genes in geneset gs_id |
|
105 |
+ if (!is.null(geneset_id)) { |
|
106 |
+ if (geneset_id %in% res_enrich[["gs_id"]]) { |
|
107 |
+ thisset_name <- res_enrich[geneset_id, "gs_description"] |
|
108 |
+ thisset_members <- |
|
109 |
+ unlist(strsplit(res_enrich[geneset_id, "gs_genes"], ",")) |
|
110 |
+ thisset_members_ids <- |
|
111 |
+ annotation_obj$gene_id[match(thisset_members, annotation_obj$gene_name)] |
|
112 |
+ } |
|
113 |
+ } else { |
|
114 |
+ # overwritable via a list |
|
115 |
+ if (!all(genelist %in% rownames(res_de))) { |
|
116 |
+ not_there <- genelist[!(genelist %in% rownames(res_de))] |
|
117 |
+ warning( |
|
118 |
+ "Some of the provided gene ids were not found in the SummarizedExperiment", |
|
119 |
+ "\nNot found: ", |
|
120 |
+ not_there |
|
121 |
+ ) |
|
122 |
+ } |
|
123 |
+ thisset_members_ids <- intersect(rownames(res_de), genelist) |
|
124 |
+ thisset_name <- "Custom list" |
|
125 |
+ } |
|
126 |
+ |
|
127 |
+ |
|
128 |
+ # Prepare the data |
|
129 |
+ complete_genes_ids <- rownames(res_de) |
|
130 |
+ complete_genes <- |
|
131 |
+ annotation_obj$gene_name[match(complete_genes_ids, annotation_obj$gene_id)] |
|
132 |
+ |
|
133 |
+ padj_complete <- res_de[complete_genes_ids, "padj"] |
|
134 |
+ filter_info_complete <-sapply(padj_complete, function(x) x <= FDR) |
|
135 |
+ padj_complete <- sapply(padj_complete, function(x) -log10(x)) |
|
136 |
+ |
|
137 |
+ log2FoldChange_complete <- res_de[complete_genes_ids, "log2FoldChange"] |
|
138 |
+ |
|
139 |
+ gene_set_belong <- complete_genes_ids %in% thisset_members_ids |
|
140 |
+ filter_info_complete <- filter_info_complete & gene_set_belong |
|
141 |
+ |
|
142 |
+ |
|
143 |
+ thisset_complete_data <- data.frame( |
|
144 |
+ complete_genes_ids, |
|
145 |
+ padj_complete, |
|
146 |
+ log2FoldChange_complete, |
|
147 |
+ filter_info_complete, |
|
148 |
+ gene_set_belong |
|
149 |
+ ) |
|
150 |
+ |
|
151 |
+ colnames(thisset_complete_data) <- c("genes", |
|
152 |
+ "logTransformedpvalue", |
|
153 |
+ "log2FoldChange", |
|
154 |
+ "significant", |
|
155 |
+ "belonging") |
|
156 |
+ |
|
157 |
+ |
|
158 |
+ # Prepare plotting |
|
159 |
+ volcano_df_complete <- thisset_complete_data |
|
160 |
+ volcano_df_complete$genes_name <- complete_genes |
|
161 |
+ max_x <- max(abs(range(thisset_complete_data["log2FoldChange"]))) |
|
162 |
+ limit_x <- max_x * c(-1, 1) |
|
163 |
+ |
|
164 |
+ |
|
165 |
+ # Prepare plot title |
|
166 |
+ if (is.null(plot_title)) { |
|
167 |
+ title <- paste0("Signature Volcano Plot - ", thisset_name, " - ", geneset_id) |
|
168 |
+ } else { |
|
169 |
+ title <- plot_title |
|
170 |
+ } |
|
171 |
+ |
|
172 |
+ |
|
173 |
+ # Plot data |
|
174 |
+ p <- ggplot(volcano_df_complete, |
|
175 |
+ aes_string(x = "log2FoldChange", y = "logTransformedpvalue")) + |
|
176 |
+ geom_point(aes_string(color = "significant", |
|
177 |
+ alpha = "belonging")) + |
|
178 |
+ labs(x = "log2Fold Change", |
|
179 |
+ y = "-log10 p-value", |
|
180 |
+ color = "p-value <= FDR") + |
|
181 |
+ scale_x_continuous(limits = limit_x) + |
|
182 |
+ scale_color_manual( |
|
183 |
+ labels = c("significant", "not significant"), |
|
184 |
+ breaks = c("TRUE", "FALSE"), |
|
185 |
+ values = c(color, "grey25")) + |
|
186 |
+ scale_alpha_manual(breaks = c("TRUE", "FALSE"), |
|
187 |
+ values = c(1, 1 / 10)) + |
|
188 |
+ theme_bw() + |
|
189 |
+ theme(legend.title = element_text(size = 11, face = "bold"), |
|
190 |
+ legend.text = element_text(size = 10)) |
|
191 |
+ |
|
192 |
+ |
|
193 |
+ # adding labels to the significant points of the geneset |
|
194 |
+ p <- p + geom_text_repel( |
|
195 |
+ data = subset(volcano_df_complete, filter_info_complete), |
|
196 |
+ aes_string(label = "genes_name"), |
|
197 |
+ size = 4, |
|
198 |
+ max.overlaps = volcano_labels |
|
199 |
+ ) |
|
200 |
+ |
|
201 |
+ |
|
202 |
+ # handling the title |
|
203 |
+ p <- p + ggtitle(title) |
|
204 |
+ p <- p + guides(alpha = FALSE) |
|
205 |
+ return(p) |
|
206 |
+} |
... | ... |
@@ -8,11 +8,13 @@ element;intro |
8 | 8 |
#controlbar-toggle;Close back the controlbar. |
9 | 9 |
#ggsnetwork;You can interact with the network visualization, either by clicking on a desired node (you can zoom in with the mouse wheel of with the trackpad)... |
10 | 10 |
#nodeSelectggsnetwork;... or by selecting one here - first the gene sets are displayed, then the genes. Now select a gene set of interest. |
11 |
-#ui_ggs_genesetbox;Whenever you select something, some additional content gets displayed in the boxes on the right side. If you selected a gene set, you should see some summary information on the geneset, referred to the inputs you provided, below a signature heatmap including all the genes annotated to the gene set. |
|
11 |
+#ui_ggs_genesetbox;Whenever you select something, some additional content gets displayed in the boxes on the right side. If you selected a gene set, you should see some summary information on the geneset, referred to the inputs you provided, below a signature heatmap and a signature volcano plot including all the genes annotated to the gene set. |
|
12 | 12 |
#ggsnetwork;You can go back to the main network view, and select a gene now. |
13 | 13 |
#ui_ggs_genebox;See how some links to the selected gene get automatically generated as action buttons - to the NCBI and the GeneCards databases. |
14 | 14 |
#controlbar-toggle;Toggle again the control bar... |
15 |
-#exp_condition + .selectize-control;... and select for example 'condition' from the dropdown select input. |
|
15 |
+#exp_condition + .selectize-control;... and select for example 'condition' from the dropdown select input... |
|
16 |
+#col; ... or you use the <b> Select color for volcano plot </b> option. With this you can change the color and transparency and the genes of the chosen geneset will be displayed accordingly. |
|
17 |
+#labels; Also you can decide to check the <b> Display all labels </b> box. This will add the names of all genes in the geneset to the signature volcano plot - otherwise only a small number is displayed to keep a clearly represented plot. |
|
16 | 18 |
#controlbar-toggle;Close back the control bar. |
17 | 19 |
#ui_ggs_genebox;You can see how the gene infobox also added a plot on the selected gene, split by the factor you specified in the select widget. |
18 | 20 |
#ggsnetwork;You can be interested in a number of genes and gene sets. <code>GeneTonic</code> supports functions for bookmarking all these entities and combine them together in an HTML report. Select any node now... |
... | ... |
@@ -8,7 +8,8 @@ gs_summary_overview( |
8 | 8 |
res_enrich, |
9 | 9 |
n_gs = 20, |
10 | 10 |
p_value_column = "gs_pvalue", |
11 |
- color_by = "z_score" |
|
11 |
+ color_by = "z_score", |
|
12 |
+ return_barchart = FALSE |
|
12 | 13 |
) |
13 | 14 |
} |
14 | 15 |
\arguments{ |
... | ... |
@@ -26,6 +27,9 @@ p-value - have been specified).} |
26 | 27 |
|
27 | 28 |
\item{color_by}{Character, specifying the column of \code{res_enrich} to be used |
28 | 29 |
for coloring the plotted gene sets. Defaults sensibly to \code{z_score}.} |
30 |
+ |
|
31 |
+\item{return_barchart}{Logical, whether to return a barchart (instead of the |
|
32 |
+default dot-segment plot); defaults to FALSE.} |
|
29 | 33 |
} |
30 | 34 |
\value{ |
31 | 35 |
A \code{ggplot} object |
... | ... |
@@ -69,6 +73,8 @@ res_enrich <- get_aggrscores(res_enrich, res_de, anno_df) |
69 | 73 |
|
70 | 74 |
gs_summary_overview(res_enrich) |
71 | 75 |
|
76 |
+# if desired, it can also be shown as a barplot |
|
77 |
+gs_summary_overview(res_enrich, 30, return_barchart = TRUE) |
|
72 | 78 |
} |
73 | 79 |
\seealso{ |
74 | 80 |
\code{\link[=gs_summary_overview_pair]{gs_summary_overview_pair()}}, \code{\link[=gs_horizon]{gs_horizon()}} |
... | ... |
@@ -29,7 +29,7 @@ Convert the output of Enrichr for straightforward use in \code{\link[=GeneTonic] |
29 | 29 |
# "Reactome_2016", |
30 | 30 |
# "WikiPathways_2019_Human") |
31 | 31 |
# degenes <- (deseqresult2df(res_macrophage_IFNg_vs_naive, FDR = 0.01)$SYMBOL) |
32 |
-# if called directly withÃn R... |
|
32 |
+# if called directly within R... |
|
33 | 33 |
# enrichr_output_macrophage <- enrichr(degenes, dbs) |
34 | 34 |
# or alternatively, if downloaded from the website in tabular format |
35 | 35 |
enrichr_output_file <- system.file("extdata", |
36 | 36 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,112 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/signature_volcano.R |
|
3 |
+\name{signature_volcano} |
|
4 |
+\alias{signature_volcano} |
|
5 |
+\title{Plot a volcano plot of a geneset} |
|
6 |
+\usage{ |
|
7 |
+signature_volcano( |
|
8 |
+ res_de, |
|
9 |
+ res_enrich, |
|
10 |
+ annotation_obj = NULL, |
|
11 |
+ gtl = NULL, |
|
12 |
+ geneset_id = NULL, |
|
13 |
+ genelist = NULL, |
|
14 |
+ FDR = 0.05, |
|
15 |
+ color = "#1a81c2", |
|
16 |
+ volcano_labels = 25, |
|
17 |
+ plot_title = NULL |
|
18 |
+) |
|
19 |
+} |
|
20 |
+\arguments{ |
|
21 |
+\item{res_de}{A \code{DESeqResults} object.} |
|
22 |
+ |
|
23 |
+\item{res_enrich}{A \code{data.frame} object, storing the result of the functional |
|
24 |
+enrichment analysis. See more in the main function, \code{\link[=GeneTonic]{GeneTonic()}}, to check the |
|
25 |
+formatting requirements (a minimal set of columns should be present).} |
|
26 |
+ |
|
27 |
+\item{annotation_obj}{A \code{data.frame} object with the feature annotation |
|
28 |
+information, with at least two columns, \code{gene_id} and \code{gene_name}.} |
|
29 |
+ |
|
30 |
+\item{gtl}{A \code{GeneTonic}-list object, containing in its slots the arguments |
|
31 |
+specified above: \code{dds}, \code{res_de}, \code{res_enrich}, and \code{annotation_obj} - the names |
|
32 |
+of the list \emph{must} be specified following the content they are expecting.} |
|
33 |
+ |
|
34 |
+\item{geneset_id}{Character specifying the gene set identifier to be plotted.} |
|
35 |
+ |
|
36 |
+\item{genelist}{A vector of character strings, specifying the identifiers |
|
37 |
+contained in the \code{rownames} of the \code{res_de} input object.} |
|
38 |
+ |
|
39 |
+\item{FDR}{Numeric value, specifying the significance level for thresholding |
|
40 |
+adjusted p-values. Defaults to 0.05.} |
|
41 |
+ |
|
42 |
+\item{color}{Character string to specify color of filtered points in the plot. |
|
43 |
+Defaults to #1a81c2 (shade of blue).} |
|
44 |
+ |
|
45 |
+\item{volcano_labels}{Integer, maximum number of labels for the gene sets to be |
|
46 |
+plotted as labels on the volcano scatter plot. Defaults to 25.} |
|
47 |
+ |
|
48 |
+\item{plot_title}{Character string, to specify the title of the plot, |
|
49 |
+displayed over the volcano plot. If left to \code{NULL} as by default, it tries to use |
|
50 |
+the information on the geneset identifier provided.} |
|
51 |
+} |
|
52 |
+\value{ |
|
53 |
+A plot returned by the \code{\link[=ggplot]{ggplot()}} function |
|
54 |
+} |
|
55 |
+\description{ |
|
56 |
+Plot a volcano plot for the geneset of the provided data, with the remaining |
|
57 |
+genes as shaded dots in the background of the plot. |
|
58 |
+} |
|
59 |
+\examples{ |
|
60 |
+library("macrophage") |
|
61 |
+library("DESeq2") |
|
62 |
+library("org.Hs.eg.db") |
|
63 |
+library("AnnotationDbi") |
|
64 |
+ |
|
65 |
+# dds object |
|
66 |
+data("gse", package = "macrophage") |
|
67 |
+dds_macrophage <- DESeqDataSet(gse, design = ~line + condition) |
|
68 |
+rownames(dds_macrophage) <- substr(rownames(dds_macrophage), 1, 15) |
|
69 |
+dds_macrophage <- estimateSizeFactors(dds_macrophage) |
|
70 |
+ |
|
71 |
+ |
|
72 |
+# annotation object |
|
73 |
+anno_df <- data.frame( |
|
74 |
+ gene_id = rownames(dds_macrophage), |
|
75 |
+ gene_name = mapIds(org.Hs.eg.db, |
|
76 |
+ keys = rownames(dds_macrophage), |
|
77 |
+ column = "SYMBOL", |
|
78 |
+ keytype = "ENSEMBL"), |
|
79 |
+ stringsAsFactors = FALSE, |
|
80 |
+ row.names = rownames(dds_macrophage) |
|
81 |
+) |
|
82 |
+ |
|
83 |
+# res object |
|
84 |
+data(res_de_macrophage, package = "GeneTonic") |
|
85 |
+res_de <- res_macrophage_IFNg_vs_naive |
|
86 |
+ |
|
87 |
+# res_enrich object |
|
88 |
+data(res_enrich_macrophage, package = "GeneTonic") |
|
89 |
+res_enrich <- shake_topGOtableResult(topgoDE_macrophage_IFNg_vs_naive) |
|
90 |
+res_enrich <- get_aggrscores(res_enrich, res_de, anno_df) |
|
91 |
+ |
|
92 |
+signature_volcano(res_de, |
|
93 |
+ res_enrich, |
|
94 |
+ anno_df, |
|
95 |
+ geneset_id = res_enrich$gs_id[1] |
|
96 |
+ ) |
|
97 |
+ |
|
98 |
+# alternatively |
|
99 |
+ |
|
100 |
+chemokine_list <- c("ENSG00000108702", |
|
101 |
+ "ENSG00000172156", |
|
102 |
+ "ENSG00000181374", |
|
103 |
+ "ENSG00000276409" |
|
104 |
+ ) |
|
105 |
+ |
|
106 |
+signature_volcano(res_de, |
|
107 |
+ res_enrich, |
|
108 |
+ anno_df, |
|
109 |
+ genelist = chemokine_list |
|
110 |
+ ) |
|
111 |
+ |
|
112 |
+} |
... | ... |
@@ -34,8 +34,15 @@ test_that("summary plots are generated", { |
34 | 34 |
res_enrich2$aggr_score <- res_enrich2$aggr_score[shuffled_ones] |
35 | 35 |
|
36 | 36 |
p1 <- gs_summary_overview(res_enrich_withscores) |
37 |
+ p1_bar <- gs_summary_overview(res_enrich_withscores, return_barchart = TRUE) |
|
38 |
+ p1_nocol <- gs_summary_overview(res_enrich_withscores, color_by = NULL) |
|
39 |
+ p1_bar_nocol <- gs_summary_overview(res_enrich_withscores, color_by = NULL, |
|
40 |
+ return_barchart = TRUE) |
|
37 | 41 |
expect_is(p1, "gg") |
38 |
- |
|
42 |
+ expect_is(p1_bar, "gg") |
|
43 |
+ expect_is(p1_nocol, "gg") |
|
44 |
+ expect_is(p1_bar_nocol, "gg") |
|
45 |
+ |
|
39 | 46 |
p2 <- gs_summary_overview_pair(res_enrich_withscores, res_enrich2) |
40 | 47 |
expect_is(p2, "gg") |
41 | 48 |
|
42 | 49 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,62 @@ |
1 |
+context("Testing gene set signature volcano and related functionality") |
|
2 |
+ |
|
3 |
+test_that("Geneset signature volcano is created", { |
|
4 |
+ cur_gsid <- res_enrich_IFNg_vs_naive$gs_id[1] |
|
5 |
+ p <- signature_volcano(res_de = res_macrophage_IFNg_vs_naive, |
|
6 |
+ res_enrich = res_enrich_IFNg_vs_naive, |
|
7 |
+ annotation_obj = anno_df, |
|
8 |
+ geneset_id = cur_gsid, |
|
9 |
+ FDR = 0.05, |
|
10 |
+ ) |
|
11 |
+ expect_is(p, "gg") |
|
12 |
+ p2 <- signature_volcano(res_de = res_macrophage_IFNg_vs_naive, |
|
13 |
+ res_enrich = res_enrich_IFNg_vs_naive, |
|
14 |
+ annotation_obj = anno_df, |
|
15 |
+ geneset_id = cur_gsid, |
|
16 |
+ color = "red" |
|
17 |
+ ) |
|
18 |
+ expect_is(p2, "gg") |
|
19 |
+ p3 <- signature_volcano(res_de = res_macrophage_IFNg_vs_naive, |
|
20 |
+ res_enrich = res_enrich_IFNg_vs_naive, |
|
21 |
+ annotation_obj = anno_df, |
|
22 |
+ geneset_id = cur_gsid, |
|
23 |
+ FDR = 0.05, |
|
24 |
+ plot_title = "Random Title" |
|
25 |
+ ) |
|
26 |
+ expect_is(p3, "gg") |
|
27 |
+ |
|
28 |
+ gtl_macrophage <- list(dds = dds_macrophage, |
|
29 |
+ res_de = res_macrophage_IFNg_vs_naive, |
|
30 |
+ res_enrich = res_enrich_IFNg_vs_naive, |
|
31 |
+ annotation_obj = anno_df) |
|
32 |
+ p4 <- signature_volcano(gtl = gtl_macrophage, |
|
33 |
+ geneset_id = cur_gsid, |
|
34 |
+ ) |
|
35 |
+ expect_is(p4, "gg") |
|
36 |
+ |
|
37 |
+ p5 <- signature_volcano(res_de = res_macrophage_IFNg_vs_naive, |
|
38 |
+ res_enrich = res_enrich_IFNg_vs_naive, |
|
39 |
+ annotation_obj = anno_df, |
|
40 |
+ geneset_id = cur_gsid, |
|
41 |
+ FDR = 0.05, |
|
42 |
+ volcano_labels = 35 |
|
43 |
+ ) |
|
44 |
+ expect_is(p5, "gg") |
|
45 |
+ |
|
46 |
+ # enforcing id not present in the object |
|
47 |
+ mycustomlist <- c( |
|
48 |
+ rownames(vst_macrophage)[1:10], |
|
49 |
+ "ENSmadeUPid" |
|
50 |
+ ) |
|
51 |
+ |
|
52 |
+ expect_warning( |
|
53 |
+ p6 <- signature_volcano( |
|
54 |
+ res_de = res_macrophage_IFNg_vs_naive, |
|
55 |
+ res_enrich = res_enrich_IFNg_vs_naive, |
|
56 |
+ annotation_obj = anno_df, |
|
57 |
+ genelist = mycustomlist, |
|
58 |
+ ) |
|
59 |
+ ) |
|
60 |
+ |
|
61 |
+ file.remove("Rplots.pdf") |
|
62 |
+}) |
... | ... |
@@ -777,6 +777,18 @@ go_2_html("GO:0060337", |
777 | 777 |
res_enrich = res_enrich_macrophage) |
778 | 778 |
``` |
779 | 779 |
|
780 |
+Plot a signature volcano plot for a gene set, with the genes of the geneset highlighted in color and the remaining genes shown shaded in the background: |
|
781 |
+ |
|
782 |
+```{r signaturevolcano} |
|
783 |
+signature_volcano(res_de = res_macrophage_IFNg_vs_naive, |
|
784 |
+ res_enrich = res_enrich_macrophage, |
|
785 |
+ annotation_obj = anno_df, |
|
786 |
+ geneset_id = "GO:0060337", |
|
787 |
+ FDR = 0.05, |
|
788 |
+ color = "#1a81c2" |
|
789 |
+) |
|
790 |
+``` |
|
791 |
+ |
|
780 | 792 |
Some functions are just to ensure that the input objects are conform with the format expected by `GeneTonic`: |
781 | 793 |
|
782 | 794 |
```{r shakers, eval=FALSE} |