... | ... |
@@ -1506,8 +1506,8 @@ importTFData <- function(GRN, data, name, idColumn = "ENSEMBL", nameColumn = "TF |
1506 | 1506 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. |
1507 | 1507 |
#' @examples |
1508 | 1508 |
#' # See the Workflow vignette on the GRaNIE website for examples |
1509 |
-#' GRN = loadExampleObject() |
|
1510 |
-#' GRN = AR_classification_wrapper(GRN, outputFolder = ".", forceRerun = FALSE) |
|
1509 |
+#' # GRN = loadExampleObject() |
|
1510 |
+#' # GRN = AR_classification_wrapper(GRN, outputFolder = ".", forceRerun = FALSE) |
|
1511 | 1511 |
#' @export |
1512 | 1512 |
AR_classification_wrapper<- function (GRN, significanceThreshold_Wilcoxon = 0.05, |
1513 | 1513 |
plot_minNoTFBS_heatmap = 100, deleteIntermediateData = TRUE, |
... | ... |
@@ -2276,7 +2276,8 @@ addConnections_TF_peak <- function (GRN, plotDiagnosticPlots = TRUE, plotDetails |
2276 | 2276 |
#' @examples |
2277 | 2277 |
#' # See the Workflow vignette on the GRaNIE website for examples |
2278 | 2278 |
#' GRN = loadExampleObject() |
2279 |
-#' GRN = addConnections_peak_gene(GRN, promoterRange = 10000, outputFolder = ".") |
|
2279 |
+#' types = list(c("protein_coding")) |
|
2280 |
+#' GRN = addConnections_peak_gene(GRN, promoterRange=10000, outputFolder=".", plotGeneTypes=types) |
|
2280 | 2281 |
addConnections_peak_gene <- function(GRN, overlapTypeGene = "TSS", corMethod = "pearson", |
2281 | 2282 |
promoterRange = 250000, TADs = NULL, |
2282 | 2283 |
nCores = 4, |
... | ... |
@@ -3465,23 +3466,23 @@ add_TF_gene_correlation <- function(GRN, corMethod = "pearson", addRobustRegress |
3465 | 3466 |
res.df = suppressMessages(tibble::as_tibble(res.m) %>% |
3466 | 3467 |
dplyr::mutate(TF.ENSEMBL = getCounts(GRN, type = "rna", norm = TRUE, permuted = as.logical(permutationCur))$ENSEMBL[map_TF], |
3467 | 3468 |
gene.ENSEMBL = getCounts(GRN, type = "rna", norm = TRUE, permuted = as.logical(permutationCur))$ENSEMBL[map_gene]) %>% |
3468 |
- dplyr::filter(!is.na(gene.ENSEMBL), !is.na(TF.ENSEMBL)) %>% # For some peak-gene combinations, no RNA-Seq data was available, these NAs are filtered |
|
3469 |
+ dplyr::filter(!is.na(.data$gene.ENSEMBL), !is.na(.data$TF.ENSEMBL)) %>% # For some peak-gene combinations, no RNA-Seq data was available, these NAs are filtered |
|
3469 | 3470 |
dplyr::left_join(GRN@data$TFs$translationTable, by = c("TF.ENSEMBL")) %>% |
3470 | 3471 |
dplyr::select(tidyselect::all_of(selectColumns))) %>% |
3471 |
- dplyr::mutate(gene.ENSEMBL = as.factor(gene.ENSEMBL), |
|
3472 |
- TF.ENSEMBL = as.factor(TF.ENSEMBL), |
|
3473 |
- TF.name = as.factor(TF.name)) %>% |
|
3474 |
- dplyr::rename(TF_gene.r = r, |
|
3475 |
- TF_gene.p_raw = p.raw) %>% |
|
3472 |
+ dplyr::mutate(gene.ENSEMBL = as.factor(.data$gene.ENSEMBL), |
|
3473 |
+ TF.ENSEMBL = as.factor(.data$TF.ENSEMBL), |
|
3474 |
+ TF.name = as.factor(.data$TF.name)) %>% |
|
3475 |
+ dplyr::rename(TF_gene.r = .data$r, |
|
3476 |
+ TF_gene.p_raw = .data$p.raw) %>% |
|
3476 | 3477 |
dplyr::select(TF.name, TF.ENSEMBL, gene.ENSEMBL, tidyselect::everything()) |
3477 | 3478 |
|
3478 | 3479 |
|
3479 | 3480 |
if (addRobustRegression) { |
3480 | 3481 |
res.df = dplyr::rename(res.df, |
3481 |
- TF_gene.p_raw.robust = p_raw.robust, |
|
3482 |
- TF_gene.r_robust = r_robust, |
|
3483 |
- TF_gene.bias_M_p.raw = bias_M_p.raw, |
|
3484 |
- TF_gene.bias_LS_p.raw = bias_LS_p.raw) |
|
3482 |
+ TF_gene.p_raw.robust = .data$p_raw.robust, |
|
3483 |
+ TF_gene.r_robust = .data$r_robust, |
|
3484 |
+ TF_gene.bias_M_p.raw = .data$bias_M_p.raw, |
|
3485 |
+ TF_gene.bias_LS_p.raw = .data$bias_LS_p.raw) |
|
3485 | 3486 |
} |
3486 | 3487 |
|
3487 | 3488 |
} else { |
... | ... |
@@ -3643,7 +3644,7 @@ addSNPOverlap <- function(grn, SNPData, col_chr = "chr", col_pos = "pos", col_pe |
3643 | 3644 |
#' @examples |
3644 | 3645 |
#' # See the Workflow vignette on the GRaNIE website for examples |
3645 | 3646 |
#' GRN = loadExampleObject() |
3646 |
-#' GRN = generateStatsSummary(GRN, forceRerun = FALSE) |
|
3647 |
+#' GRN = generateStatsSummary(GRN, TF_peak.fdr = c(0.01, 0.1), peak_gene.fdr = c(0.01, 0.1)) |
|
3647 | 3648 |
#' |
3648 | 3649 |
generateStatsSummary <- function(GRN, |
3649 | 3650 |
TF_peak.fdr = c(0.001, 0.01, 0.05, 0.1, 0.2), |
... | ... |
@@ -3931,9 +3932,9 @@ loadExampleObject <- function(forceDownload = FALSE, fileURL = "https://www.embl |
3931 | 3932 |
|
3932 | 3933 |
bfc <- .get_cache() |
3933 | 3934 |
|
3934 |
- rid <- BiocFileCache::bfcquery(bfc, "geneFileV2", "rname")$rid |
|
3935 |
+ rid <- BiocFileCache::bfcquery(bfc, "GRaNIE_object_example")$rid |
|
3935 | 3936 |
if (!length(rid)) { |
3936 |
- rid <- names(BiocFileCache::bfcadd(bfc, "geneFileV2", fileURL)) |
|
3937 |
+ rid <- names(BiocFileCache::bfcadd(bfc, "GRaNIE_object_example", fileURL)) |
|
3937 | 3938 |
} |
3938 | 3939 |
if (isFALSE(BiocFileCache::bfcneedsupdate(bfc, rid)) | forceDownload) { |
3939 | 3940 |
messageStr = paste0("Downloading GRaNIE example object from ", fileURL) |
... | ... |
@@ -4237,7 +4238,7 @@ getGRNConnections <- function(GRN, type = "all.filtered", permuted = FALSE, inc |
4237 | 4238 |
#' @examples |
4238 | 4239 |
#' # See the Workflow vignette on the GRaNIE website for examples |
4239 | 4240 |
#' GRN = loadExampleObject() |
4240 |
-#' getParameters(GRN, type = "parameter", name = "all") |
|
4241 |
+#' params.l = getParameters(GRN, type = "parameter", name = "all") |
|
4241 | 4242 |
getParameters <- function (GRN, type = "parameter", name = "all") { |
4242 | 4243 |
|
4243 | 4244 |
checkmate::assertClass(GRN, "GRN") |
... | ... |
@@ -4362,12 +4363,12 @@ getBasic_metadata_visualization <- function(GRN, forceRerun = FALSE) { |
4362 | 4363 |
#' |
4363 | 4364 |
#' @export |
4364 | 4365 |
#' @template GRN |
4365 |
-#' @param outputDirectory |
|
4366 |
+#' @param outputDirectory Character. Default \code{.}. New output directory for all output files unless overwritten via the parameter \code{outputFolder}. |
|
4366 | 4367 |
#' @return The same \code{\linkS4class{GRN}} object, with the output directory being adjusted accordingly |
4367 | 4368 |
#' @examples |
4368 |
-#' # GRN = loadExampleObject() |
|
4369 |
-#' # GRN = changeOutputDirectory(GRN, ".") |
|
4370 |
-changeOutputDirectory <- function(GRN, outputDirectory) { |
|
4369 |
+#' GRN = loadExampleObject() |
|
4370 |
+#' GRN = changeOutputDirectory(GRN, outputDirectory = ".") |
|
4371 |
+changeOutputDirectory <- function(GRN, outputDirectory = ".") { |
|
4371 | 4372 |
|
4372 | 4373 |
GRN@config$directories$outputRoot = outputDirectory |
4373 | 4374 |
GRN@config$directories$output_plots = paste0(outputDirectory, "/plots/") |
... | ... |
@@ -200,8 +200,8 @@ build_eGRN_graph <- function(GRN, model_TF_gene_nodes_separately = FALSE, |
200 | 200 |
#' @export |
201 | 201 |
#' @examples |
202 | 202 |
#' # See the Workflow vignette on the GRaNIE website for examples |
203 |
-#' GRN = loadExampleObject() |
|
204 |
-#' GRN = performAllNetworkAnalyses(GRN, outputFolder = ".", forceRerun = FALSE) |
|
203 |
+#' # GRN = loadExampleObject() |
|
204 |
+#' # GRN = performAllNetworkAnalyses(GRN, outputFolder = ".", forceRerun = FALSE) |
|
205 | 205 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. |
206 | 206 |
performAllNetworkAnalyses <- function(GRN, ontology = c("GO_BP", "GO_MF"), |
207 | 207 |
algorithm = "weight01", statistic = "fisher", |
... | ... |
@@ -17,7 +17,7 @@ |
17 | 17 |
#' @examples |
18 | 18 |
#' # See the Workflow vignette on the GRaNIE website for examples |
19 | 19 |
#' GRN = loadExampleObject() |
20 |
-#' GRN = plotPCA_all(GRN, topn = 500, outputFolder = ".", forceRerun = FALSE) |
|
20 |
+#' GRN = plotPCA_all(GRN, topn = 500, outputFolder = ".", type = "rna", plotAsPDF=FALSE) |
|
21 | 21 |
#' @export |
22 | 22 |
plotPCA_all <- function(GRN, outputFolder = NULL, basenameOutput = NULL, |
23 | 23 |
type = c("rna", "peaks"), topn = c(500,1000,5000), |
... | ... |
@@ -443,22 +443,28 @@ plotPCA_all <- function(GRN, outputFolder = NULL, basenameOutput = NULL, |
443 | 443 |
|
444 | 444 |
|
445 | 445 |
#' Plot diagnostic plots for TF-peak connections for a \code{\linkS4class{GRN}} object |
446 |
+#' |
|
447 |
+#' Due to the number of plots that this functions produces, we currently provide only the option to plot as PDF. This may change in the future. |
|
446 | 448 |
#' |
447 | 449 |
#' @template GRN |
448 | 450 |
#' @template outputFolder |
449 | 451 |
#' @template basenameOutput |
450 | 452 |
#' @template plotDetails |
453 |
+#' @param plotPermuted \code{TRUE} or \code{FALSE}. Default \code{TRUE}. Also produce the diagnostic plots for permuted data? |
|
454 |
+#' @param nTFMax \code{NULL} or Integer. Default \code{NULL}. Maximum number of TFs to process. Can be used for testing purposes by setting this to a small number i(.e., 10) |
|
451 | 455 |
#' @template forceRerun |
452 | 456 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. |
453 | 457 |
#' @examples |
454 | 458 |
#' # See the Workflow vignette on the GRaNIE website for examples |
455 | 459 |
#' GRN = loadExampleObject() |
456 |
-#' GRN = plotDiagnosticPlots_TFPeaks(GRN, outputFolder = ".", forceRerun = FALSE) |
|
460 |
+#' GRN = plotDiagnosticPlots_TFPeaks(GRN, outputFolder = ".", plotPermuted = FALSE, nTFMax = 2) |
|
457 | 461 |
#' @export |
458 | 462 |
plotDiagnosticPlots_TFPeaks <- function(GRN, |
459 | 463 |
outputFolder = NULL, |
460 | 464 |
basenameOutput = NULL, |
461 | 465 |
plotDetails = FALSE, |
466 |
+ plotPermuted = TRUE, |
|
467 |
+ nTFMax = NULL, |
|
462 | 468 |
forceRerun = FALSE) { |
463 | 469 |
|
464 | 470 |
GRN = .addFunctionLogToObject(GRN) |
... | ... |
@@ -467,6 +473,8 @@ plotDiagnosticPlots_TFPeaks <- function(GRN, |
467 | 473 |
checkmate::assert(checkmate::checkNull(outputFolder), checkmate::checkCharacter(outputFolder, min.chars = 1)) |
468 | 474 |
checkmate::assert(checkmate::checkNull(basenameOutput), checkmate::checkCharacter(basenameOutput, len = 1, min.chars = 1, any.missing = FALSE)) |
469 | 475 |
checkmate::assertFlag(plotDetails) |
476 |
+ checkmate::assertFlag(plotPermuted) |
|
477 |
+ checkmate::assert(checkmate::checkNull(nTFMax), checkmate::checkIntegerish(nTFMax)) |
|
470 | 478 |
checkmate::assertFlag(forceRerun) |
471 | 479 |
|
472 | 480 |
useGCCorrection = GRN@config$parameters$useGCCorrection |
... | ... |
@@ -476,6 +484,10 @@ plotDiagnosticPlots_TFPeaks <- function(GRN, |
476 | 484 |
|
477 | 485 |
for (permutationCur in 0:.getMaxPermutation(GRN)) { |
478 | 486 |
|
487 |
+ if (!plotPermuted & permutationCur != 0) { |
|
488 |
+ next |
|
489 |
+ } |
|
490 |
+ |
|
479 | 491 |
suffixFile = .getPermutationSuffixStr(permutationCur) |
480 | 492 |
|
481 | 493 |
fileCur = paste0(outputFolder, |
... | ... |
@@ -485,7 +497,9 @@ plotDiagnosticPlots_TFPeaks <- function(GRN, |
485 | 497 |
if (!file.exists(fileCur) | forceRerun) { |
486 | 498 |
|
487 | 499 |
heightCur = 8* length(GRN@config$TF_peak_connectionTypes) |
488 |
- .plot_TF_peak_fdr(GRN, perm = permutationCur, useGCCorrection = useGCCorrection, plotDetails = plotDetails, fileCur, width = 7, height = heightCur) |
|
500 |
+ .plot_TF_peak_fdr(GRN, perm = permutationCur, useGCCorrection = useGCCorrection, |
|
501 |
+ plotDetails = plotDetails, fileCur, width = 7, height = heightCur, |
|
502 |
+ nPagesMax = nTFMax) |
|
489 | 503 |
} |
490 | 504 |
|
491 | 505 |
fileCur = paste0(outputFolder, .getOutputFileName("plot_TFPeak_fdr_GC"), suffixFile) |
... | ... |
@@ -623,20 +637,24 @@ plotDiagnosticPlots_TFPeaks <- function(GRN, |
623 | 637 |
index = 1 |
624 | 638 |
} |
625 | 639 |
|
640 |
+ # Dont take all TF, some might be missing. |
|
626 | 641 |
connections_TF_peak = GRN@connections$TF_peaks[[as.character(perm)]]$connectionStats |
642 |
+ allTF = unique(connections_TF_peak$TF.name) |
|
643 |
+ nTF = ifelse(is.null(nPagesMax), length(allTF), nPagesMax) |
|
644 |
+ futile.logger::flog.info(paste0(" Including a total of ", nTF, " TF. Preparing plots...")) |
|
627 | 645 |
|
628 |
- # TODO: Check difference between TFActivity TFs and expression TFs |
|
629 | 646 |
|
630 |
- # Dont take all TF, some might be missing. |
|
631 |
- allTF = unique(connections_TF_peak$TF.name) |
|
632 |
- futile.logger::flog.info(paste0(" Including a total of ", length(allTF), " TF. Preparing plots...")) |
|
647 |
+ # TODO: Check difference between TFActivity TFs and expression TFs |
|
633 | 648 |
|
634 |
- pb <- progress::progress_bar$new(total = length(allTF)) |
|
649 |
+ |
|
650 |
+ pb <- progress::progress_bar$new(total = nTF) |
|
635 | 651 |
|
636 | 652 |
levels_pos<-unique(as.character(cut(GRN@config$parameters$internal$stepsFDR, breaks = GRN@config$parameters$internal$stepsFDR, right = FALSE, include.lowest = TRUE ))) |
637 | 653 |
levels_neg<-unique(as.character(cut(GRN@config$parameters$internal$stepsFDR, breaks = rev(GRN@config$parameters$internal$stepsFDR), right = TRUE, include.lowest = TRUE ))) |
638 | 654 |
|
639 |
- for (i in seq_len(length(allTF))) { |
|
655 |
+ |
|
656 |
+ |
|
657 |
+ for (i in seq_len(nTF)) { |
|
640 | 658 |
pb$tick() |
641 | 659 |
TFCur = allTF[i] |
642 | 660 |
|
... | ... |
@@ -758,11 +776,7 @@ plotDiagnosticPlots_TFPeaks <- function(GRN, |
758 | 776 |
|
759 | 777 |
if (!is.null(file)) { |
760 | 778 |
futile.logger::flog.info(paste0(" Finished generating plots, start plotting to file ",file, ". This may take a few minutes.")) |
761 |
- if (!is.null(nPagesMax)) { |
|
762 |
- .printMultipleGraphsPerPage(plots.l[c(seq_len(nPagesMax))], nCol = 1, nRow = 2, pdfFile = file, height = height, width = width) |
|
763 |
- } else { |
|
764 |
- .printMultipleGraphsPerPage(plots.l, nCol = 1, nRow = 2, pdfFile = file, height = height, width = width) |
|
765 |
- } |
|
779 |
+ .printMultipleGraphsPerPage(plots.l, nCol = 1, nRow = 2, pdfFile = file, height = height, width = width) |
|
766 | 780 |
|
767 | 781 |
} |
768 | 782 |
|
... | ... |
@@ -794,7 +808,8 @@ plotDiagnosticPlots_TFPeaks <- function(GRN, |
794 | 808 |
#' @examples |
795 | 809 |
#' # See the Workflow vignette on the GRaNIE website for examples |
796 | 810 |
#' # GRN = loadExampleObject() |
797 |
-#' # GRN = plotDiagnosticPlots_peakGene(GRN, outputFolder = ".", forceRerun = FALSE) |
|
811 |
+#' # types = list(c("protein_coding")) |
|
812 |
+#' # GRN = plotDiagnosticPlots_peakGene(GRN, outputFolder=".", gene.types=types, plotAsPDF=FALSE) |
|
798 | 813 |
#' @export |
799 | 814 |
# TODO: implement forceRerun correctly |
800 | 815 |
plotDiagnosticPlots_peakGene <- function(GRN, |
... | ... |
@@ -1318,7 +1333,7 @@ plotDiagnosticPlots_peakGene <- function(GRN, |
1318 | 1333 |
#theme(axis.text.x = element_text(angle = 45, hjust = 1, size = 8), strip.background = element_blank(), strip.placement = "outside", axis.title.y = element_blank()) + |
1319 | 1334 |
# theme(axis.text.x = element_text(angle = 45, hjust = 1, size = 8) , axis.title.y = element_blank()) + |
1320 | 1335 |
theme_main + |
1321 |
- facet_wrap(~ factor(class), nrow = 2, scales = "free_y", strip.position = "left", , labeller = labeller(class=freq_class)) |
|
1336 |
+ facet_wrap(~ factor(class), nrow = 2, scales = "free_y", strip.position = "left", labeller = labeller(class=freq_class)) |
|
1322 | 1337 |
|
1323 | 1338 |
|
1324 | 1339 |
plots_all = ( ((gA3 | gB3 ) + |
... | ... |
@@ -1584,7 +1599,7 @@ plotDiagnosticPlots_peakGene <- function(GRN, |
1584 | 1599 |
#' @examples |
1585 | 1600 |
#' # See the Workflow vignette on the GRaNIE website for examples |
1586 | 1601 |
#' GRN = loadExampleObject() |
1587 |
-#' GRN = plot_stats_connectionSummary(GRN, outputFolder = ".", forceRerun = FALSE) |
|
1602 |
+#' GRN = plot_stats_connectionSummary(GRN, outputFolder = ".", forceRerun = FALSE, plotAsPDF=FALSE) |
|
1588 | 1603 |
#' @export |
1589 | 1604 |
#' @importFrom circlize colorRamp2 |
1590 | 1605 |
plot_stats_connectionSummary <- function(GRN, type = "heatmap", |
... | ... |
@@ -1613,6 +1628,7 @@ plot_stats_connectionSummary <- function(GRN, type = "heatmap", |
1613 | 1628 |
} |
1614 | 1629 |
|
1615 | 1630 |
.plot_stats_connectionSummaryHeatmap(GRN, file = file, pdf_width = pdf_width, pdf_height = pdf_height, forceRerun = forceRerun) |
1631 |
+ |
|
1616 | 1632 |
} else if (type == "boxplot") { |
1617 | 1633 |
|
1618 | 1634 |
if (plotAsPDF) { |
... | ... |
@@ -1645,7 +1661,7 @@ plot_stats_connectionSummary <- function(GRN, type = "heatmap", |
1645 | 1661 |
|
1646 | 1662 |
futile.logger::flog.info(paste0("Plotting connection summary", dplyr::if_else(is.null(file), "", paste0(" to file ", file)))) |
1647 | 1663 |
|
1648 |
- if ((!is.null(file) & !file.exists(file))| forceRerun) { |
|
1664 |
+ if ((!is.null(file) && !file.exists(file))| forceRerun) { |
|
1649 | 1665 |
|
1650 | 1666 |
if (nrow(GRN@stats$connections) == 0) { |
1651 | 1667 |
message = paste0("Statistics summary missing from object, please run the function generateStatsSummary first") |
... | ... |
@@ -1776,7 +1792,7 @@ plot_stats_connectionSummary <- function(GRN, type = "heatmap", |
1776 | 1792 |
|
1777 | 1793 |
start = Sys.time() |
1778 | 1794 |
|
1779 |
- if ((!is.null(file) & !file.exists(file))| forceRerun) { |
|
1795 |
+ if ((!is.null(file) && !file.exists(file))| forceRerun) { |
|
1780 | 1796 |
|
1781 | 1797 |
|
1782 | 1798 |
futile.logger::flog.info(paste0("Plotting diagnostic plots for network connections", dplyr::if_else(is.null(file), "", paste0(" to file ", file)))) |
... | ... |
@@ -1915,7 +1931,7 @@ plot_stats_connectionSummary <- function(GRN, type = "heatmap", |
1915 | 1931 |
#' @examples |
1916 | 1932 |
#' # See the Workflow vignette on the GRaNIE website for examples |
1917 | 1933 |
#' GRN = loadExampleObject() |
1918 |
-#' GRN = plotGeneralGraphStats(GRN, outputFolder = ".", forceRerun = FALSE) |
|
1934 |
+#' GRN = plotGeneralGraphStats(GRN, outputFolder = ".", plotAsPDF=FALSE) |
|
1919 | 1935 |
#' @export |
1920 | 1936 |
plotGeneralGraphStats <- function(GRN, outputFolder = NULL, basenameOutput = NULL, |
1921 | 1937 |
plotAsPDF = TRUE, pdf_width = 12, pdf_height = 12, |
... | ... |
@@ -2081,7 +2097,7 @@ plotGeneralGraphStats <- function(GRN, outputFolder = NULL, basenameOutput = NUL |
2081 | 2097 |
#' @examples |
2082 | 2098 |
#' # See the Workflow vignette on the GRaNIE website for examples |
2083 | 2099 |
#' GRN = loadExampleObject() |
2084 |
-#' GRN = plotGeneralEnrichment(GRN, outputFolder = ".", forceRerun = FALSE) |
|
2100 |
+#' GRN = plotGeneralEnrichment(GRN, outputFolder = ".", plotAsPDF=FALSE) |
|
2085 | 2101 |
#' @export |
2086 | 2102 |
plotGeneralEnrichment <- function(GRN, outputFolder = NULL, basenameOutput = NULL, |
2087 | 2103 |
ontology = NULL, topn_pvalue = 30, p = 0.05, |
... | ... |
@@ -2260,7 +2276,7 @@ plotGeneralEnrichment <- function(GRN, outputFolder = NULL, basenameOutput = NUL |
2260 | 2276 |
#' @examples |
2261 | 2277 |
#' # See the Workflow vignette on the GRaNIE website for examples |
2262 | 2278 |
#' GRN = loadExampleObject() |
2263 |
-#' GRN = plotCommunitiesStats(GRN, outputFolder = ".", forceRerun = FALSE) |
|
2279 |
+#' GRN = plotCommunitiesStats(GRN, outputFolder = ".", plotAsPDF=FALSE) |
|
2264 | 2280 |
#' @export |
2265 | 2281 |
plotCommunitiesStats <- function(GRN, outputFolder = NULL, basenameOutput = NULL, |
2266 | 2282 |
display = "byRank", communities = seq_len(10), |
... | ... |
@@ -2430,7 +2446,7 @@ plotCommunitiesStats <- function(GRN, outputFolder = NULL, basenameOutput = NULL |
2430 | 2446 |
#' @examples |
2431 | 2447 |
#' # See the Workflow vignette on the GRaNIE website for examples |
2432 | 2448 |
#' GRN = loadExampleObject() |
2433 |
-#' GRN = plotCommunitiesEnrichment(GRN, outputFolder = ".", forceRerun = FALSE) |
|
2449 |
+#' GRN = plotCommunitiesEnrichment(GRN, outputFolder = ".", plotAsPDF=FALSE) |
|
2434 | 2450 |
#' @export |
2435 | 2451 |
#' @import ggplot2 |
2436 | 2452 |
#' @importFrom grid gpar |
... | ... |
@@ -2520,9 +2536,9 @@ plotCommunitiesEnrichment <- function(GRN, outputFolder = NULL, basenameOutput = |
2520 | 2536 |
vertexMetadata = as.data.frame(igraph::vertex.attributes(GRN@graph$TF_gene$graph)) |
2521 | 2537 |
# Get the number of vertexes per community as additional annotation column for the heatmap |
2522 | 2538 |
geneCounts = vertexMetadata %>% |
2523 |
- dplyr::select(name, community) %>% |
|
2539 |
+ dplyr::select(.data$name, .data$community) %>% |
|
2524 | 2540 |
dplyr::distinct() %>% |
2525 |
- dplyr::count(community) |
|
2541 |
+ dplyr::count(.data$community) |
|
2526 | 2542 |
|
2527 | 2543 |
|
2528 | 2544 |
allOntologies = .checkEnrichmentCongruence_general_community(GRN, type = "community") |
... | ... |
@@ -2604,16 +2620,19 @@ plotCommunitiesEnrichment <- function(GRN, outputFolder = NULL, basenameOutput = |
2604 | 2620 |
tibble::column_to_rownames("Term") %>% |
2605 | 2621 |
as.matrix() |
2606 | 2622 |
|
2607 |
- # Common heatmap parameters for both p1 and p2 |
|
2623 |
+ |
|
2608 | 2624 |
geneCounts_communities = geneCounts %>% |
2609 |
- dplyr::filter(community %in% as.character(colnames(matrix.m))) %>% |
|
2610 |
- dplyr::slice(match(communities.order[-1], geneCounts$community)) %>% |
|
2611 |
- dplyr::pull(n) |
|
2612 |
- |
|
2625 |
+ dplyr::filter(community %in% as.character(colnames(matrix.m)), |
|
2626 |
+ community %in% geneCounts$community) %>% |
|
2627 |
+ dplyr::arrange(dplyr::desc(.data$n)) |
|
2613 | 2628 |
|
2629 |
+ # Sanity check |
|
2630 |
+ stopifnot(identical(as.character(geneCounts_communities$community), colnames(matrix.m)[-1])) |
|
2631 |
+ |
|
2632 |
+ # Common heatmap parameters for both p1 and p2 |
|
2614 | 2633 |
top_annotation = ComplexHeatmap::HeatmapAnnotation( |
2615 | 2634 |
nGenes = ComplexHeatmap::anno_barplot( |
2616 |
- x = c(sum(geneCounts$n), geneCounts_communities), |
|
2635 |
+ x = c(sum(geneCounts$n), geneCounts_communities$n), |
|
2617 | 2636 |
border = FALSE, bar_width = 0.8, gp = grid::gpar(fill = "#046C9A")), |
2618 | 2637 |
annotation_name_gp = grid::gpar(fontsize=9), annotation_name_side = "left", annotation_name_rot = 90) |
2619 | 2638 |
|
... | ... |
@@ -2634,7 +2653,7 @@ plotCommunitiesEnrichment <- function(GRN, outputFolder = NULL, basenameOutput = |
2634 | 2653 |
# Now focus on the top X only per community |
2635 | 2654 |
ID_subset = GRN@stats$Enrichment$byCommunity[["combined"]][[ontologyCur]] %>% |
2636 | 2655 |
dplyr::group_by(community) %>% |
2637 |
- dplyr::arrange(pval) %>% |
|
2656 |
+ dplyr::arrange(.data$pval) %>% |
|
2638 | 2657 |
dplyr::slice(seq_len(nID)) %>% |
2639 | 2658 |
dplyr::pull(ID) %>% as.character() |
2640 | 2659 |
|
... | ... |
@@ -2741,7 +2760,7 @@ plotCommunitiesEnrichment <- function(GRN, outputFolder = NULL, basenameOutput = |
2741 | 2760 |
#' @examples |
2742 | 2761 |
#' # See the Workflow vignette on the GRaNIE website for examples |
2743 | 2762 |
#' GRN = loadExampleObject() |
2744 |
-#' GRN = plotTFEnrichment(GRN, n = 5, outputFolder = ".", forceRerun = FALSE) |
|
2763 |
+#' GRN = plotTFEnrichment(GRN, n = 5, outputFolder = ".", plotAsPDF=FALSE) |
|
2745 | 2764 |
#' @export |
2746 | 2765 |
#' @importFrom grid gpar |
2747 | 2766 |
plotTFEnrichment <- function(GRN, rankType = "degree", n = NULL, TF.names = NULL, |
... | ... |
@@ -2904,7 +2923,7 @@ plotTFEnrichment <- function(GRN, rankType = "degree", n = NULL, TF.names = NULL |
2904 | 2923 |
# Make sure the top annotation has the same dimensionality as the resulting matrix |
2905 | 2924 |
nodeDegree_TFset_numbers = nodeDegree_TFset %>% |
2906 | 2925 |
dplyr::filter(TF.name %in% colnames(matrix.m)) %>% |
2907 |
- dplyr::arrange(desc(nodeDegree)) %>% |
|
2926 |
+ dplyr::arrange(dplyr::desc(nodeDegree)) %>% |
|
2908 | 2927 |
dplyr::pull(nodeDegree) |
2909 | 2928 |
|
2910 | 2929 |
top_annotation = ComplexHeatmap::HeatmapAnnotation( |
... | ... |
@@ -40,6 +40,6 @@ Run the activator-repressor classification for the TFs for a \code{\linkS4class{ |
40 | 40 |
} |
41 | 41 |
\examples{ |
42 | 42 |
# See the Workflow vignette on the GRaNIE website for examples |
43 |
-GRN = loadExampleObject() |
|
44 |
-GRN = AR_classification_wrapper(GRN, outputFolder = ".", forceRerun = FALSE) |
|
43 |
+# GRN = loadExampleObject() |
|
44 |
+# GRN = AR_classification_wrapper(GRN, outputFolder = ".", forceRerun = FALSE) |
|
45 | 45 |
} |
... | ... |
@@ -50,5 +50,6 @@ Add peak-gene connections to a \code{\linkS4class{GRN}} object |
50 | 50 |
\examples{ |
51 | 51 |
# See the Workflow vignette on the GRaNIE website for examples |
52 | 52 |
GRN = loadExampleObject() |
53 |
-GRN = addConnections_peak_gene(GRN, promoterRange = 10000, outputFolder = ".") |
|
53 |
+types = list(c("protein_coding")) |
|
54 |
+GRN = addConnections_peak_gene(GRN, promoterRange=10000, outputFolder=".", plotGeneTypes=types) |
|
54 | 55 |
} |
... | ... |
@@ -4,12 +4,12 @@ |
4 | 4 |
\alias{changeOutputDirectory} |
5 | 5 |
\title{Change the output directory of a GRN object} |
6 | 6 |
\usage{ |
7 |
-changeOutputDirectory(GRN, outputDirectory) |
|
7 |
+changeOutputDirectory(GRN, outputDirectory = ".") |
|
8 | 8 |
} |
9 | 9 |
\arguments{ |
10 | 10 |
\item{GRN}{Object of class \code{\linkS4class{GRN}}} |
11 | 11 |
|
12 |
-\item{outputDirectory}{} |
|
12 |
+\item{outputDirectory}{Character. Default \code{.}. New output directory for all output files unless overwritten via the parameter \code{outputFolder}.} |
|
13 | 13 |
} |
14 | 14 |
\value{ |
15 | 15 |
The same \code{\linkS4class{GRN}} object, with the output directory being adjusted accordingly |
... | ... |
@@ -18,6 +18,6 @@ The same \code{\linkS4class{GRN}} object, with the output directory being adjust |
18 | 18 |
Change the output directory of a GRN object |
19 | 19 |
} |
20 | 20 |
\examples{ |
21 |
-# GRN = loadExampleObject() |
|
22 |
-# GRN = changeOutputDirectory(GRN, ".") |
|
21 |
+GRN = loadExampleObject() |
|
22 |
+GRN = changeOutputDirectory(GRN, outputDirectory = ".") |
|
23 | 23 |
} |
... | ... |
@@ -47,6 +47,6 @@ Essentially, this functions calls \code{\link{filterGRNAndConnectGenes}} repeate |
47 | 47 |
\examples{ |
48 | 48 |
# See the Workflow vignette on the GRaNIE website for examples |
49 | 49 |
GRN = loadExampleObject() |
50 |
-GRN = generateStatsSummary(GRN, forceRerun = FALSE) |
|
50 |
+GRN = generateStatsSummary(GRN, TF_peak.fdr = c(0.01, 0.1), peak_gene.fdr = c(0.01, 0.1)) |
|
51 | 51 |
|
52 | 52 |
} |
... | ... |
@@ -22,5 +22,5 @@ Retrieve parameters for previously used function calls and general parameters fo |
22 | 22 |
\examples{ |
23 | 23 |
# See the Workflow vignette on the GRaNIE website for examples |
24 | 24 |
GRN = loadExampleObject() |
25 |
-getParameters(GRN, type = "parameter", name = "all") |
|
25 |
+params.l = getParameters(GRN, type = "parameter", name = "all") |
|
26 | 26 |
} |
... | ... |
@@ -55,6 +55,6 @@ A convenience function that calls all network-related functions in one-go, using |
55 | 55 |
} |
56 | 56 |
\examples{ |
57 | 57 |
# See the Workflow vignette on the GRaNIE website for examples |
58 |
-GRN = loadExampleObject() |
|
59 |
-GRN = performAllNetworkAnalyses(GRN, outputFolder = ".", forceRerun = FALSE) |
|
58 |
+# GRN = loadExampleObject() |
|
59 |
+# GRN = performAllNetworkAnalyses(GRN, outputFolder = ".", forceRerun = FALSE) |
|
60 | 60 |
} |
... | ... |
@@ -62,5 +62,5 @@ Similarly to \code{\link{plotGeneralEnrichment}}, the results of the community-b |
62 | 62 |
\examples{ |
63 | 63 |
# See the Workflow vignette on the GRaNIE website for examples |
64 | 64 |
GRN = loadExampleObject() |
65 |
-GRN = plotCommunitiesEnrichment(GRN, outputFolder = ".", forceRerun = FALSE) |
|
65 |
+GRN = plotCommunitiesEnrichment(GRN, outputFolder = ".", plotAsPDF=FALSE) |
|
66 | 66 |
} |
... | ... |
@@ -50,7 +50,7 @@ Similarly to the statistics produced by \code{\link{plotGeneralGraphStats}}, sum |
50 | 50 |
\examples{ |
51 | 51 |
# See the Workflow vignette on the GRaNIE website for examples |
52 | 52 |
GRN = loadExampleObject() |
53 |
-GRN = plotCommunitiesStats(GRN, outputFolder = ".", forceRerun = FALSE) |
|
53 |
+GRN = plotCommunitiesStats(GRN, outputFolder = ".", plotAsPDF=FALSE) |
|
54 | 54 |
} |
55 | 55 |
\seealso{ |
56 | 56 |
\code{\link{plotGeneralGraphStats}} |
... | ... |
@@ -9,6 +9,8 @@ plotDiagnosticPlots_TFPeaks( |
9 | 9 |
outputFolder = NULL, |
10 | 10 |
basenameOutput = NULL, |
11 | 11 |
plotDetails = FALSE, |
12 |
+ plotPermuted = TRUE, |
|
13 |
+ nTFMax = NULL, |
|
12 | 14 |
forceRerun = FALSE |
13 | 15 |
) |
14 | 16 |
} |
... | ... |
@@ -21,16 +23,20 @@ plotDiagnosticPlots_TFPeaks( |
21 | 23 |
|
22 | 24 |
\item{plotDetails}{\code{TRUE} or \code{FALSE}. Default \code{FALSE}. Print additional plots that may help for debugging and QC purposes? Note that these plots are currently less documented or not at all.} |
23 | 25 |
|
26 |
+\item{plotPermuted}{\code{TRUE} or \code{FALSE}. Default \code{TRUE}. Also produce the diagnostic plots for permuted data?} |
|
27 |
+ |
|
28 |
+\item{nTFMax}{\code{NULL} or Integer. Default \code{NULL}. Maximum number of TFs to process. Can be used for testing purposes by setting this to a small number i(.e., 10)} |
|
29 |
+ |
|
24 | 30 |
\item{forceRerun}{\code{TRUE} or \code{FALSE}. Default \code{FALSE}. Force execution, even if the GRN object already contains the result. Overwrites the old results.} |
25 | 31 |
} |
26 | 32 |
\value{ |
27 | 33 |
The same \code{\linkS4class{GRN}} object, with added data from this function. |
28 | 34 |
} |
29 | 35 |
\description{ |
30 |
-Plot diagnostic plots for TF-peak connections for a \code{\linkS4class{GRN}} object |
|
36 |
+Due to the number of plots that this functions produces, we currently provide only the option to plot as PDF. This may change in the future. |
|
31 | 37 |
} |
32 | 38 |
\examples{ |
33 | 39 |
# See the Workflow vignette on the GRaNIE website for examples |
34 | 40 |
GRN = loadExampleObject() |
35 |
-GRN = plotDiagnosticPlots_TFPeaks(GRN, outputFolder = ".", forceRerun = FALSE) |
|
41 |
+GRN = plotDiagnosticPlots_TFPeaks(GRN, outputFolder = ".", plotPermuted = FALSE, nTFMax = 2) |
|
36 | 42 |
} |
... | ... |
@@ -50,5 +50,6 @@ Plot diagnostic plots for peak-gene connections for a \code{\linkS4class{GRN}} o |
50 | 50 |
\examples{ |
51 | 51 |
# See the Workflow vignette on the GRaNIE website for examples |
52 | 52 |
# GRN = loadExampleObject() |
53 |
-# GRN = plotDiagnosticPlots_peakGene(GRN, outputFolder = ".", forceRerun = FALSE) |
|
53 |
+# types = list(c("protein_coding")) |
|
54 |
+# GRN = plotDiagnosticPlots_peakGene(GRN, outputFolder=".", gene.types=types, plotAsPDF=FALSE) |
|
54 | 55 |
} |
... | ... |
@@ -50,5 +50,5 @@ This function plots the results of the general enrichment analysis for every spe |
50 | 50 |
\examples{ |
51 | 51 |
# See the Workflow vignette on the GRaNIE website for examples |
52 | 52 |
GRN = loadExampleObject() |
53 |
-GRN = plotGeneralEnrichment(GRN, outputFolder = ".", forceRerun = FALSE) |
|
53 |
+GRN = plotGeneralEnrichment(GRN, outputFolder = ".", plotAsPDF=FALSE) |
|
54 | 54 |
} |
... | ... |
@@ -38,7 +38,7 @@ This function generates graphical summaries about the structure and connectivity |
38 | 38 |
\examples{ |
39 | 39 |
# See the Workflow vignette on the GRaNIE website for examples |
40 | 40 |
GRN = loadExampleObject() |
41 |
-GRN = plotGeneralGraphStats(GRN, outputFolder = ".", forceRerun = FALSE) |
|
41 |
+GRN = plotGeneralGraphStats(GRN, outputFolder = ".", plotAsPDF=FALSE) |
|
42 | 42 |
} |
43 | 43 |
\seealso{ |
44 | 44 |
\code{\link{plotGeneralEnrichment}} |
... | ... |
@@ -44,5 +44,5 @@ Produce a PCA plot of the data from a \code{\linkS4class{GRN}} object |
44 | 44 |
\examples{ |
45 | 45 |
# See the Workflow vignette on the GRaNIE website for examples |
46 | 46 |
GRN = loadExampleObject() |
47 |
-GRN = plotPCA_all(GRN, topn = 500, outputFolder = ".", forceRerun = FALSE) |
|
47 |
+GRN = plotPCA_all(GRN, topn = 500, outputFolder = ".", type = "rna", plotAsPDF=FALSE) |
|
48 | 48 |
} |
... | ... |
@@ -65,7 +65,7 @@ This function plots the enrichment results. The result consist of a dot plot per |
65 | 65 |
\examples{ |
66 | 66 |
# See the Workflow vignette on the GRaNIE website for examples |
67 | 67 |
GRN = loadExampleObject() |
68 |
-GRN = plotTFEnrichment(GRN, n = 5, outputFolder = ".", forceRerun = FALSE) |
|
68 |
+GRN = plotTFEnrichment(GRN, n = 5, outputFolder = ".", plotAsPDF=FALSE) |
|
69 | 69 |
} |
70 | 70 |
\seealso{ |
71 | 71 |
\code{\link{calculateTFEnrichment}} |
... | ... |
@@ -41,5 +41,5 @@ Plot various network connectivity summaries for a \code{\linkS4class{GRN}} objec |
41 | 41 |
\examples{ |
42 | 42 |
# See the Workflow vignette on the GRaNIE website for examples |
43 | 43 |
GRN = loadExampleObject() |
44 |
-GRN = plot_stats_connectionSummary(GRN, outputFolder = ".", forceRerun = FALSE) |
|
44 |
+GRN = plot_stats_connectionSummary(GRN, outputFolder = ".", forceRerun = FALSE, plotAsPDF=FALSE) |
|
45 | 45 |
} |