... | ... |
@@ -248,9 +248,9 @@ setMethod("show", |
248 | 248 |
#' @return Integer. Number of peaks that are defined in the \code{\linkS4class{GRN}} object, either by excluding (filter = TRUE) or including (filter = FALSE) peaks that are currently marked as \emph{filtered}. |
249 | 249 |
#' @examples |
250 | 250 |
#' # See the Workflow vignette on the GRaNIE website for examples |
251 |
-#' # GRN = loadExampleObject() |
|
252 |
-#' # nPeaks(GRN, filter = TRUE) |
|
253 |
-#' # nPeaks(GRN, filter = FALSE) |
|
251 |
+#' GRN = loadExampleObject() |
|
252 |
+#' nPeaks(GRN, filter = TRUE) |
|
253 |
+#' nPeaks(GRN, filter = FALSE) |
|
254 | 254 |
#' @export |
255 | 255 |
#' @aliases peaks |
256 | 256 |
#' @rdname peaks-methods |
... | ... |
@@ -283,9 +283,9 @@ nPeaks <- function(GRN, filter = TRUE) { |
283 | 283 |
#' @return Integer. Number of genes that are defined in the \code{\linkS4class{GRN}} object, either by excluding (filter = TRUE) or including (filter = FALSE) genes that are currently marked as \emph{filtered}. |
284 | 284 |
#' @examples |
285 | 285 |
#' # See the Workflow vignette on the GRaNIE website for examples |
286 |
-#' # GRN = loadExampleObject() |
|
287 |
-#' # nGenes(GRN, filter = TRUE) |
|
288 |
-#' # nGenes(GRN, filter = FALSE) |
|
286 |
+#' GRN = loadExampleObject() |
|
287 |
+#' nGenes(GRN, filter = TRUE) |
|
288 |
+#' nGenes(GRN, filter = FALSE) |
|
289 | 289 |
#' @export |
290 | 290 |
#' @aliases genes |
291 | 291 |
#' @rdname genes-methods |
... | ... |
@@ -117,9 +117,9 @@ initializeGRN <- function(objectMetadata = list(), |
117 | 117 |
#' # rna.df = read_tsv("https://www.embl.de/download/zaugg/GRaNIE/rna.tsv.gz") |
118 | 118 |
#' # peaks.df = read_tsv("https://www.embl.de/download/zaugg/GRaNIE/peaks.tsv.gz") |
119 | 119 |
#' # meta.df = read_tsv("https://www.embl.de/download/zaugg/GRaNIE/sampleMetadata.tsv.gz") |
120 |
-#' # GRN = loadExampleObject() |
|
120 |
+#' GRN = loadExampleObject() |
|
121 | 121 |
#' # We omit sampleMetadata = meta.df here, lines becomes too long otherwise |
122 |
-#' # GRN = addData(GRN, counts_peaks = peaks.df, counts_rna = rna.df, forceRerun = FALSE) |
|
122 |
+#' GRN = addData(GRN, counts_peaks = peaks.df, counts_rna = rna.df, forceRerun = FALSE) |
|
123 | 123 |
|
124 | 124 |
addData <- function(GRN, counts_peaks, normalization_peaks = "DESeq_sizeFactor", idColumn_peaks = "peakID", |
125 | 125 |
counts_rna, normalization_rna = "quantile", idColumn_RNA = "ENSEMBL", sampleMetadata = NULL, |
... | ... |
@@ -602,8 +602,8 @@ addData <- function(GRN, counts_peaks, normalization_peaks = "DESeq_sizeFactor", |
602 | 602 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. |
603 | 603 |
#' @examples |
604 | 604 |
#' # See the Workflow vignette on the GRaNIE website for examples |
605 |
-#' # GRN = loadExampleObject() |
|
606 |
-#' # GRN = filterData(GRN, forceRerun = FALSE) |
|
605 |
+#' GRN = loadExampleObject() |
|
606 |
+#' GRN = filterData(GRN, forceRerun = FALSE) |
|
607 | 607 |
#' @export |
608 | 608 |
filterData <- function (GRN, |
609 | 609 |
minNormalizedMean_peaks = 5, maxNormalizedMean_peaks = NULL, |
... | ... |
@@ -970,8 +970,8 @@ addTFBS <- function(GRN, motifFolder, TFs = "all", nTFMax = NULL, filesTFBSPatte |
970 | 970 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. |
971 | 971 |
#' @examples |
972 | 972 |
#' # See the Workflow vignette on the GRaNIE website for examples |
973 |
-#' # GRN = loadExampleObject() |
|
974 |
-#' # GRN = overlapPeaksAndTFBS(GRN, nCores = 2, forceRerun = FALSE) |
|
973 |
+#' GRN = loadExampleObject() |
|
974 |
+#' GRN = overlapPeaksAndTFBS(GRN, nCores = 2, forceRerun = FALSE) |
|
975 | 975 |
#' @export |
976 | 976 |
overlapPeaksAndTFBS <- function(GRN, nCores = 2, forceRerun = FALSE) { |
977 | 977 |
|
... | ... |
@@ -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. TF_classification_densityPlotsForegroundBackground_expression_perm{0,1}.pdf, TF_classification_stringencyThresholds_expression_perm0.pdf, TF_classification_summaryHeatmap_expression_perm0.pdf, |
1507 | 1507 |
#' @examples |
1508 | 1508 |
#' # See the Workflow vignette on the GRaNIE website for examples |
1509 |
-#' # GRN = loadExampleObject() |
|
1510 |
-#' # GRN = AR_classification_wrapper(GRN, forceRerun = FALSE) |
|
1509 |
+#' GRN = loadExampleObject() |
|
1510 |
+#' GRN = AR_classification_wrapper(GRN, forceRerun = FALSE) |
|
1511 | 1511 |
#' @export |
1512 | 1512 |
AR_classification_wrapper<- function (GRN, significanceThreshold_Wilcoxon = 0.05, |
1513 | 1513 |
plot_minNoTFBS_heatmap = 100, deleteIntermediateData = TRUE, |
... | ... |
@@ -1724,8 +1724,8 @@ AR_classification_wrapper<- function (GRN, significanceThreshold_Wilcoxon = 0.05 |
1724 | 1724 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. TF_peak.fdrCurves_perm{o,1}.pdf |
1725 | 1725 |
#' @examples |
1726 | 1726 |
#' # See the Workflow vignette on the GRaNIE website for examples |
1727 |
-#' # GRN = loadExampleObject() |
|
1728 |
-#' # GRN = addConnections_TF_peak(GRN, forceRerun = FALSE) |
|
1727 |
+#' GRN = loadExampleObject() |
|
1728 |
+#' GRN = addConnections_TF_peak(GRN, forceRerun = FALSE) |
|
1729 | 1729 |
#' @export |
1730 | 1730 |
addConnections_TF_peak <- function (GRN, plotDiagnosticPlots = TRUE, plotDetails = FALSE, outputFolder = NULL, |
1731 | 1731 |
corMethod = "pearson", |
... | ... |
@@ -2270,8 +2270,8 @@ addConnections_TF_peak <- function (GRN, plotDiagnosticPlots = TRUE, plotDetails |
2270 | 2270 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function in different flavors. |
2271 | 2271 |
#' @examples |
2272 | 2272 |
#' # See the Workflow vignette on the GRaNIE website for examples |
2273 |
-#' # GRN = loadExampleObject() |
|
2274 |
-#' # GRN = addConnections_peak_gene(GRN, promoterRange = 10000, nCores = 2, forceRerun = FALSE) |
|
2273 |
+#' GRN = loadExampleObject() |
|
2274 |
+#' GRN = addConnections_peak_gene(GRN, promoterRange = 10000, nCores = 2, forceRerun = FALSE) |
|
2275 | 2275 |
addConnections_peak_gene <- function(GRN, overlapTypeGene = "TSS", corMethod = "pearson", |
2276 | 2276 |
promoterRange = 250000, TADs = NULL, |
2277 | 2277 |
nCores = 4, |
... | ... |
@@ -2812,8 +2812,8 @@ addConnections_peak_gene <- function(GRN, overlapTypeGene = "TSS", corMethod = " |
2812 | 2812 |
#' @return The same \code{\linkS4class{GRN}} object, with the filtered and merged TF-peak and peak-gene connections in the slot connections$all.filtered. The filtered |
2813 | 2813 |
#' @examples |
2814 | 2814 |
#' # See the Workflow vignette on the GRaNIE website for examples |
2815 |
-#' # GRN = loadExampleObject() |
|
2816 |
-#' # GRN = filterGRNAndConnectGenes(GRN) |
|
2815 |
+#' GRN = loadExampleObject() |
|
2816 |
+#' GRN = filterGRNAndConnectGenes(GRN) |
|
2817 | 2817 |
#' @seealso \code{\link{visualizeGRN}} |
2818 | 2818 |
#' @seealso \code{\link{addConnections_TF_peak}} |
2819 | 2819 |
#' @seealso \code{\link{addConnections_peak_gene}} |
... | ... |
@@ -3387,8 +3387,8 @@ filterGRNAndConnectGenes <- function(GRN, |
3387 | 3387 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. |
3388 | 3388 |
#' @examples |
3389 | 3389 |
#' # See the Workflow vignette on the GRaNIE website for examples |
3390 |
-#' # GRN = loadExampleObject() |
|
3391 |
-#' # GRN = add_TF_gene_correlation(GRN, forceRerun = FALSE) |
|
3390 |
+#' GRN = loadExampleObject() |
|
3391 |
+#' GRN = add_TF_gene_correlation(GRN, forceRerun = FALSE) |
|
3392 | 3392 |
add_TF_gene_correlation <- function(GRN, corMethod = "pearson", addRobustRegression = FALSE, nCores = 1, forceRerun = FALSE) { |
3393 | 3393 |
|
3394 | 3394 |
GRN = .addFunctionLogToObject(GRN) |
... | ... |
@@ -3637,8 +3637,8 @@ addSNPOverlap <- function(grn, SNPData, col_chr = "chr", col_pos = "pos", col_pe |
3637 | 3637 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. |
3638 | 3638 |
#' @examples |
3639 | 3639 |
#' # See the Workflow vignette on the GRaNIE website for examples |
3640 |
-#' # GRN = loadExampleObject() |
|
3641 |
-#' # GRN = generateStatsSummary(GRN, forceRerun = FALSE) |
|
3640 |
+#' GRN = loadExampleObject() |
|
3641 |
+#' GRN = generateStatsSummary(GRN, forceRerun = FALSE) |
|
3642 | 3642 |
#' |
3643 | 3643 |
generateStatsSummary <- function(GRN, |
3644 | 3644 |
TF_peak.fdr = c(0.001, 0.01, 0.05, 0.1, 0.2), |
... | ... |
@@ -3905,18 +3905,39 @@ generateStatsSummary <- function(GRN, |
3905 | 3905 |
#' Load example GRN dataset |
3906 | 3906 |
#' |
3907 | 3907 |
#' @export |
3908 |
+#' @param forceDownload \code{TRUE} or \code{FALSE}. Default \code{FALSE}. Should the download be enforced even if the local cached file is already present? |
|
3909 |
+#' @param fileURL Character. Default https://www.embl.de/download/zaugg/GRaNIE/GRN.rds. URL to the GRN example object in rds format. |
|
3908 | 3910 |
#' @examples |
3909 | 3911 |
#' GRN = loadExampleObject() |
3910 | 3912 |
#' @return |
3911 | 3913 |
#' An example \code{\linkS4class{GRN}} object |
3912 |
-loadExampleObject <- function() { |
|
3914 |
+#' @import BiocFileCache |
|
3915 |
+loadExampleObject <- function(forceDownload = FALSE, fileURL = "https://www.embl.de/download/zaugg/GRaNIE/GRN.rds") { |
|
3913 | 3916 |
|
3914 |
- GRN_obj = "https://www.embl.de/download/zaugg/GRaNIE/GRN.rds" |
|
3915 |
- GRN = readRDS(url(GRN_obj)) |
|
3917 |
+ checkmate::assertFlag(forceDownload) |
|
3918 |
+ # Taken and modified from https://www.bioconductor.org/packages/release/bioc/vignettes/BiocFileCache/inst/doc/BiocFileCache.html |
|
3919 |
+ |
|
3920 |
+ bfc <- .get_cache() |
|
3921 |
+ |
|
3922 |
+ rid <- BiocFileCache::bfcquery(bfc, "geneFileV2", "rname")$rid |
|
3923 |
+ if (!length(rid)) { |
|
3924 |
+ rid <- names(BiocFileCache::bfcadd(bfc, "geneFileV2", fileURL)) |
|
3925 |
+ } |
|
3926 |
+ if (isFALSE(BiocFileCache::bfcneedsupdate(bfc, rid)) | forceDownload) { |
|
3927 |
+ messageStr = paste0("Downloading GRaNIE example object from ", fileURL) |
|
3928 |
+ message(messageStr) |
|
3929 |
+ filePath = BiocFileCache::bfcdownload(bfc, rid, ask = FALSE) |
|
3930 |
+ } |
|
3931 |
+ |
|
3932 |
+ |
|
3933 |
+ filePath = BiocFileCache::bfcrpath(bfc, rids = rid) |
|
3934 |
+ |
|
3935 |
+ # Now we can read in the locally stored file |
|
3936 |
+ readRDS(filePath) |
|
3916 | 3937 |
|
3917 |
- GRN |
|
3918 | 3938 |
} |
3919 | 3939 |
|
3940 |
+ |
|
3920 | 3941 |
#' Get counts for the various data defined in a \code{\linkS4class{GRN}} object |
3921 | 3942 |
#' |
3922 | 3943 |
#' Get counts for the various data defined in a \code{\linkS4class{GRN}} object. |
... | ... |
@@ -3929,8 +3950,8 @@ loadExampleObject <- function() { |
3929 | 3950 |
#' @import tibble |
3930 | 3951 |
#' @examples |
3931 | 3952 |
#' # See the Workflow vignette on the GRaNIE website for examples |
3932 |
-#' # GRN = loadExampleObject() |
|
3933 |
-#' # GRN = getCounts(GRN, type = "peaks", norm = TRUE, permuted = FALSE) |
|
3953 |
+#' GRN = loadExampleObject() |
|
3954 |
+#' GRN = getCounts(GRN, type = "peaks", norm = TRUE, permuted = FALSE) |
|
3934 | 3955 |
#' @return Data frame of counts, with the type as indicated by the function parameters. |
3935 | 3956 |
#' getCounts(GRN, type = "peaks", norm = TRUE) |
3936 | 3957 |
getCounts <- function(GRN, type, norm, permuted = FALSE) { |
... | ... |
@@ -4020,8 +4041,8 @@ getCounts <- function(GRN, type, norm, permuted = FALSE) { |
4020 | 4041 |
#' @return A data frame with the connections. Importantly, this function does NOT return a \code{\linkS4class{GRN}} object. |
4021 | 4042 |
#' @examples |
4022 | 4043 |
#' # See the Workflow vignette on the GRaNIE website for examples |
4023 |
-#' # GRN = loadExampleObject() |
|
4024 |
-#' # GRN_con.all = getGRNConnections(GRN, include_TF_gene_correlations = TRUE) |
|
4044 |
+#' GRN = loadExampleObject() |
|
4045 |
+#' GRN_con.all.df = getGRNConnections(GRN) |
|
4025 | 4046 |
getGRNConnections <- function(GRN, type = "all.filtered", permuted = FALSE, include_TF_gene_correlations = FALSE) { |
4026 | 4047 |
|
4027 | 4048 |
GRN = .addFunctionLogToObject(GRN) |
... | ... |
@@ -4198,7 +4219,7 @@ getGRNConnections <- function(GRN, type = "all.filtered", permuted = FALSE, inc |
4198 | 4219 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. |
4199 | 4220 |
#' @examples |
4200 | 4221 |
#' # See the Workflow vignette on the GRaNIE website for examples |
4201 |
-#' # GRN = loadExampleObject() |
|
4222 |
+#' GRN = loadExampleObject() |
|
4202 | 4223 |
#' # getParameters(GRN, type = "parameter", name = "all") |
4203 | 4224 |
#' |
4204 | 4225 |
getParameters <- function (GRN, type = "parameter", name = "all") { |
... | ... |
@@ -4249,6 +4270,10 @@ getParameters <- function (GRN, type = "parameter", name = "all") { |
4249 | 4270 |
#' @export |
4250 | 4271 |
#' @template GRN |
4251 | 4272 |
#' @return The same \code{\linkS4class{GRN}} object, with some slots being deleted (\code{GRN@data$TFs$classification} as well as \code{GRN@stats$connectionDetails.l}) |
4273 |
+#' @examples |
|
4274 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
4275 |
+#' GRN = loadExampleObject() |
|
4276 |
+#' GRN = deleteIntermediateData(GRN) |
|
4252 | 4277 |
deleteIntermediateData <- function(GRN) { |
4253 | 4278 |
|
4254 | 4279 |
|
... | ... |
@@ -4273,23 +4298,6 @@ deleteIntermediateData <- function(GRN) { |
4273 | 4298 |
|
4274 | 4299 |
} |
4275 | 4300 |
|
4276 |
-updateGRNObject <- function(GRN) { |
|
4277 |
- |
|
4278 |
- # Recently created internal slot |
|
4279 |
- if (is.null(GRN@config$parameters$internal)) { |
|
4280 |
- |
|
4281 |
- futile.logger::flog.info(paste0("Creating GRN@config$parameters$internal slot")) |
|
4282 |
- GRN@config$parameters$internal = list() |
|
4283 |
- GRN@config$parameters$internal$plot_minNoTFBS_heatmap = GRN@config$parameters$plot_minNoTFBS_heatmap |
|
4284 |
- GRN@config$parameters$internal$nPermutations = GRN@config$parameters$nPermutations |
|
4285 |
- GRN@config$parameters$internal$stepsFDR = GRN@config$parameters$stepsFDR |
|
4286 |
- GRN@config$parameters$internal$allClassificationThresholds = GRN@config$parameters$allClassificationThresholds |
|
4287 |
- GRN@config$parameters$internal$colorCategories = GRN@config$parameters$colorCategories |
|
4288 |
- } |
|
4289 |
- |
|
4290 |
- GRN |
|
4291 |
-} |
|
4292 |
- |
|
4293 | 4301 |
.checkForbiddenNames <- function(name, forbiddenNames) { |
4294 | 4302 |
|
4295 | 4303 |
if (name %in% forbiddenNames) { |
... | ... |
@@ -703,4 +703,11 @@ match.call.defaults <- function(asList = TRUE, ...) { |
703 | 703 |
#' @import utils |
704 | 704 |
is.installed <- function(mypkg){ |
705 | 705 |
is.element(mypkg, installed.packages()[,1]) |
706 |
-} |
|
707 | 706 |
\ No newline at end of file |
707 |
+} |
|
708 |
+ |
|
709 |
+# Taken from https://www.bioconductor.org/packages/release/bioc/vignettes/BiocFileCache/inst/doc/BiocFileCache.html |
|
710 |
+.get_cache <- function() { |
|
711 |
+ # cache <- tools::R_user_dir(utils::packageName(), which="cache") |
|
712 |
+ cache <- tools::R_user_dir("GRaNIE", which="cache") |
|
713 |
+ BiocFileCache::BiocFileCache(cache, ask = FALSE) |
|
714 |
+} |
... | ... |
@@ -10,8 +10,8 @@ |
10 | 10 |
#' @export |
11 | 11 |
#' @examples |
12 | 12 |
#' # See the Workflow vignette on the GRaNIE website for examples |
13 |
-#' # GRN = loadExampleObject() |
|
14 |
-#' # GRN = build_eGRN_graph(GRN, forceRerun = FALSE) |
|
13 |
+#' GRN = loadExampleObject() |
|
14 |
+#' GRN = build_eGRN_graph(GRN, forceRerun = FALSE) |
|
15 | 15 |
#' @return The same \code{\linkS4class{GRN}} object. |
16 | 16 |
build_eGRN_graph <- function(GRN, model_TF_gene_nodes_separately = FALSE, |
17 | 17 |
allowLoops = FALSE, removeMultiple = FALSE, directed = FALSE, forceRerun = FALSE) { |
... | ... |
@@ -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, forceRerun = FALSE) |
|
203 |
+#' GRN = loadExampleObject() |
|
204 |
+#' GRN = performAllNetworkAnalyses(GRN, 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", |
... | ... |
@@ -297,8 +297,8 @@ performAllNetworkAnalyses <- function(GRN, ontology = c("GO_BP", "GO_MF"), |
297 | 297 |
#' @seealso \code{\link{plotCommunitiesEnrichment}} |
298 | 298 |
#' @examples |
299 | 299 |
#' # See the Workflow vignette on the GRaNIE website for examples |
300 |
-#' # GRN = loadExampleObject() |
|
301 |
-#' # GRN = calculateGeneralEnrichment(GRN, ontology = "GO_BP", forceRerun = FALSE) |
|
300 |
+#' GRN = loadExampleObject() |
|
301 |
+#' GRN = calculateGeneralEnrichment(GRN, ontology = "GO_BP", forceRerun = FALSE) |
|
302 | 302 |
#' @export |
303 | 303 |
#' @import topGO |
304 | 304 |
#' @import BiocManager |
... | ... |
@@ -727,8 +727,8 @@ calculateGeneralEnrichment <- function(GRN, ontology = c("GO_BP", "GO_MF"), |
727 | 727 |
#' @import patchwork |
728 | 728 |
#' @examples |
729 | 729 |
#' # See the Workflow vignette on the GRaNIE website for examples |
730 |
-#' # GRN = loadExampleObject() |
|
731 |
-#' # GRN = calculateCommunitiesStats(GRN, forceRerun = FALSE) |
|
730 |
+#' GRN = loadExampleObject() |
|
731 |
+#' GRN = calculateCommunitiesStats(GRN, forceRerun = FALSE) |
|
732 | 732 |
#' @export |
733 | 733 |
calculateCommunitiesStats <- function(GRN, clustering = "louvain", forceRerun = FALSE, ...){ |
734 | 734 |
|
... | ... |
@@ -810,8 +810,8 @@ calculateCommunitiesStats <- function(GRN, clustering = "louvain", forceRerun = |
810 | 810 |
#' @seealso \code{\link{calculateGeneralEnrichment}} |
811 | 811 |
#' @examples |
812 | 812 |
#' # See the Workflow vignette on the GRaNIE website for examples |
813 |
-#' # GRN = loadExampleObject() |
|
814 |
-#' # GRN = calculateCommunitiesEnrichment(GRN, ontology = c("GO_BP"), forceRerun = FALSE) |
|
813 |
+#' GRN = loadExampleObject() |
|
814 |
+#' GRN = calculateCommunitiesEnrichment(GRN, ontology = c("GO_BP"), forceRerun = FALSE) |
|
815 | 815 |
#' @export |
816 | 816 |
calculateCommunitiesEnrichment <- function(GRN, |
817 | 817 |
ontology = c("GO_BP", "GO_MF"), algorithm = "weight01", |
... | ... |
@@ -937,9 +937,9 @@ calculateCommunitiesEnrichment <- function(GRN, |
937 | 937 |
#' @return A dataframe with the node names and the corresponding scores used to rank them |
938 | 938 |
#' @examples |
939 | 939 |
#' # See the Workflow vignette on the GRaNIE website for examples |
940 |
-#' # GRN = loadExampleObject() |
|
941 |
-#' # topGenes = getTopNodes(GRN, nodeType = "gene", rankType = "degree", n = 3) |
|
942 |
-#' # topTFs = getTopNodes(GRN, nodeType = "TF", rankType = "EV", n = 5) |
|
940 |
+#' GRN = loadExampleObject() |
|
941 |
+#' topGenes = getTopNodes(GRN, nodeType = "gene", rankType = "degree", n = 3) |
|
942 |
+#' topTFs = getTopNodes(GRN, nodeType = "TF", rankType = "EV", n = 5) |
|
943 | 943 |
#' @export |
944 | 944 |
getTopNodes <- function(GRN, nodeType, rankType, n = 0.1, use_TF_gene_network = TRUE) { # }, |
945 | 945 |
# TFConnectionType = "tf-gene", geneConnectionType = "peak-gene"){ |
... | ... |
@@ -1023,9 +1023,9 @@ getTopNodes <- function(GRN, nodeType, rankType, n = 0.1, use_TF_gene_network = |
1023 | 1023 |
#' @return The same \code{\linkS4class{GRN}} object, with the enrichment results stored in the \code{stats$Enrichment$byTF} slot. |
1024 | 1024 |
#' @examples |
1025 | 1025 |
#' # See the Workflow vignette on the GRaNIE website for examples |
1026 |
-#' # GRN = loadExampleObject() |
|
1027 |
-#' # GRN = calculateTFEnrichment(GRN, n = 5, ontology = "GO_BP", forceRerun = FALSE) |
|
1028 |
-#' # GRN = calculateTFEnrichment(GRN, n = 5, ontology = "GO_BP", forceRerun = FALSE) |
|
1026 |
+#' GRN = loadExampleObject() |
|
1027 |
+#' GRN = calculateTFEnrichment(GRN, n = 5, ontology = "GO_BP", forceRerun = FALSE) |
|
1028 |
+#' GRN = calculateTFEnrichment(GRN, n = 5, ontology = "GO_BP", forceRerun = FALSE) |
|
1029 | 1029 |
#' @export |
1030 | 1030 |
calculateTFEnrichment <- function(GRN, rankType = "degree", n = 0.1, TF.names = NULL, |
1031 | 1031 |
ontology = c("GO_BP", "GO_MF"), algorithm = "weight01", |
... | ... |
@@ -16,8 +16,8 @@ |
16 | 16 |
#' @return The same \code{\linkS4class{GRN}} object, without modifications. In addition, for each specified \code{type}, a PDF file is produced with a PCA. We refer to the Vignettes for details and further explanations. |
17 | 17 |
#' @examples |
18 | 18 |
#' # See the Workflow vignette on the GRaNIE website for examples |
19 |
-#' # GRN = loadExampleObject() |
|
20 |
-#' # GRN = plotPCA_all(GRN, type = c("rna", "peaks"), topn = 500, forceRerun = FALSE) |
|
19 |
+#' GRN = loadExampleObject() |
|
20 |
+#' GRN = plotPCA_all(GRN, type = c("rna", "peaks"), topn = 500, forceRerun = 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), |
... | ... |
@@ -450,8 +450,8 @@ plotPCA_all <- function(GRN, outputFolder = NULL, basenameOutput = NULL, |
450 | 450 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. |
451 | 451 |
#' @examples |
452 | 452 |
#' # See the Workflow vignette on the GRaNIE website for examples |
453 |
-#' # GRN = loadExampleObject() |
|
454 |
-#' # GRN = plotDiagnosticPlots_TFPeaks(GRN, forceRerun = FALSE) |
|
453 |
+#' GRN = loadExampleObject() |
|
454 |
+#' GRN = plotDiagnosticPlots_TFPeaks(GRN, forceRerun = FALSE) |
|
455 | 455 |
#' @export |
456 | 456 |
plotDiagnosticPlots_TFPeaks <- function(GRN, |
457 | 457 |
outputFolder = NULL, |
... | ... |
@@ -791,8 +791,8 @@ plotDiagnosticPlots_TFPeaks <- function(GRN, |
791 | 791 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. |
792 | 792 |
#' @examples |
793 | 793 |
#' # See the Workflow vignette on the GRaNIE website for examples |
794 |
-#' # GRN = loadExampleObject() |
|
795 |
-#' # GRN = plotDiagnosticPlots_peakGene(GRN, forceRerun = FALSE) |
|
794 |
+#' GRN = loadExampleObject() |
|
795 |
+#' GRN = plotDiagnosticPlots_peakGene(GRN, forceRerun = FALSE) |
|
796 | 796 |
#' @export |
797 | 797 |
plotDiagnosticPlots_peakGene <- function(GRN, |
798 | 798 |
outputFolder = NULL, |
... | ... |
@@ -1564,8 +1564,8 @@ plotDiagnosticPlots_peakGene <- function(GRN, |
1564 | 1564 |
#' @return The same \code{\linkS4class{GRN}} object, without modifications. In addition, for the specified \code{type}, a PDF file (default filename is GRN.connectionSummary_{type}.pdf) is produced with a connection summary. We refer to the Vignettes for details and further explanations. |
1565 | 1565 |
#' @examples |
1566 | 1566 |
#' # See the Workflow vignette on the GRaNIE website for examples |
1567 |
-#' # GRN = loadExampleObject() |
|
1568 |
-#' # GRN = plot_stats_connectionSummary(GRN, type = "heatmap", forceRerun = FALSE) |
|
1567 |
+#' GRN = loadExampleObject() |
|
1568 |
+#' GRN = plot_stats_connectionSummary(GRN, type = "heatmap", forceRerun = FALSE) |
|
1569 | 1569 |
#' @export |
1570 | 1570 |
#' @importFrom circlize colorRamp2 |
1571 | 1571 |
plot_stats_connectionSummary <- function(GRN, type = "heatmap", |
... | ... |
@@ -1893,8 +1893,8 @@ plot_stats_connectionSummary <- function(GRN, type = "heatmap", |
1893 | 1893 |
#' @seealso \code{\link{plotCommunitiesEnrichment}} |
1894 | 1894 |
#' @examples |
1895 | 1895 |
#' # See the Workflow vignette on the GRaNIE website for examples |
1896 |
-#' # GRN = loadExampleObject() |
|
1897 |
-#' # GRN = plotGeneralGraphStats(GRN, forceRerun = FALSE) |
|
1896 |
+#' GRN = loadExampleObject() |
|
1897 |
+#' GRN = plotGeneralGraphStats(GRN, forceRerun = FALSE) |
|
1898 | 1898 |
#' @export |
1899 | 1899 |
plotGeneralGraphStats <- function(GRN, outputFolder = NULL, basenameOutput = NULL, |
1900 | 1900 |
plotAsPDF = TRUE, pdf_width = 12, pdf_height = 12, |
... | ... |
@@ -2058,8 +2058,8 @@ plotGeneralGraphStats <- function(GRN, outputFolder = NULL, basenameOutput = NUL |
2058 | 2058 |
#' @return The same \code{\linkS4class{GRN}} object, without modifications. A single PDF file is produced with the results. |
2059 | 2059 |
#' @examples |
2060 | 2060 |
#' # See the Workflow vignette on the GRaNIE website for examples |
2061 |
-#' # GRN = loadExampleObject() |
|
2062 |
-#' # GRN = plotGeneralEnrichment(GRN, topn_pvalue = 30, forceRerun = FALSE) |
|
2061 |
+#' GRN = loadExampleObject() |
|
2062 |
+#' GRN = plotGeneralEnrichment(GRN, topn_pvalue = 30, forceRerun = FALSE) |
|
2063 | 2063 |
#' @export |
2064 | 2064 |
plotGeneralEnrichment <- function(GRN, outputFolder = NULL, basenameOutput = NULL, |
2065 | 2065 |
ontology = NULL, topn_pvalue = 30, p = 0.05, |
... | ... |
@@ -2236,8 +2236,8 @@ plotGeneralEnrichment <- function(GRN, outputFolder = NULL, basenameOutput = NUL |
2236 | 2236 |
#' @seealso \code{\link{calculateCommunitiesEnrichment}} |
2237 | 2237 |
#' @examples |
2238 | 2238 |
#' # See the Workflow vignette on the GRaNIE website for examples |
2239 |
-#' # GRN = loadExampleObject() |
|
2240 |
-#' # GRN = plotCommunitiesStats(GRN, display = "byRank", forceRerun = FALSE) |
|
2239 |
+#' GRN = loadExampleObject() |
|
2240 |
+#' GRN = plotCommunitiesStats(GRN, display = "byRank", forceRerun = FALSE) |
|
2241 | 2241 |
#' @export |
2242 | 2242 |
plotCommunitiesStats <- function(GRN, outputFolder = NULL, basenameOutput = NULL, |
2243 | 2243 |
display = "byRank", communities = seq_len(10), |
... | ... |
@@ -2405,8 +2405,8 @@ plotCommunitiesStats <- function(GRN, outputFolder = NULL, basenameOutput = NULL |
2405 | 2405 |
#' @return The same \code{\linkS4class{GRN}} object, without modifications. A single PDF file is produced with the results. |
2406 | 2406 |
#' @examples |
2407 | 2407 |
#' # See the Workflow vignette on the GRaNIE website for examples |
2408 |
-#' # GRN = loadExampleObject() |
|
2409 |
-#' # GRN = plotCommunitiesEnrichment(GRN, forceRerun = FALSE) |
|
2408 |
+#' GRN = loadExampleObject() |
|
2409 |
+#' GRN = plotCommunitiesEnrichment(GRN, forceRerun = FALSE) |
|
2410 | 2410 |
#' @export |
2411 | 2411 |
#' @import ggplot2 |
2412 | 2412 |
#' @importFrom grid gpar |
... | ... |
@@ -2706,8 +2706,8 @@ plotCommunitiesEnrichment <- function(GRN, outputFolder = NULL, basenameOutput = |
2706 | 2706 |
#' @seealso \code{\link{calculateTFEnrichment}} |
2707 | 2707 |
#' @examples |
2708 | 2708 |
#' # See the Workflow vignette on the GRaNIE website for examples |
2709 |
-#' # GRN = loadExampleObject() |
|
2710 |
-#' # GRN = plotTFEnrichment(GRN, rankType = "degree", n = 5, forceRerun = FALSE) |
|
2709 |
+#' GRN = loadExampleObject() |
|
2710 |
+#' GRN = plotTFEnrichment(GRN, rankType = "degree", n = 5, forceRerun = FALSE) |
|
2711 | 2711 |
#' @export |
2712 | 2712 |
#' @importFrom grid gpar |
2713 | 2713 |
plotTFEnrichment <- function(GRN, rankType = "degree", n = NULL, TF.names = NULL, |
... | ... |
@@ -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, forceRerun = FALSE) |
|
43 |
+GRN = loadExampleObject() |
|
44 |
+GRN = AR_classification_wrapper(GRN, forceRerun = FALSE) |
|
45 | 45 |
} |
... | ... |
@@ -52,6 +52,6 @@ Add TF-peak connections to a \code{\linkS4class{GRN}} object |
52 | 52 |
} |
53 | 53 |
\examples{ |
54 | 54 |
# See the Workflow vignette on the GRaNIE website for examples |
55 |
-# GRN = loadExampleObject() |
|
56 |
-# GRN = addConnections_TF_peak(GRN, forceRerun = FALSE) |
|
55 |
+GRN = loadExampleObject() |
|
56 |
+GRN = addConnections_TF_peak(GRN, forceRerun = FALSE) |
|
57 | 57 |
} |
... | ... |
@@ -49,6 +49,6 @@ Add peak-gene connections to a \code{\linkS4class{GRN}} object |
49 | 49 |
} |
50 | 50 |
\examples{ |
51 | 51 |
# See the Workflow vignette on the GRaNIE website for examples |
52 |
-# GRN = loadExampleObject() |
|
53 |
-# GRN = addConnections_peak_gene(GRN, promoterRange = 10000, nCores = 2, forceRerun = FALSE) |
|
52 |
+GRN = loadExampleObject() |
|
53 |
+GRN = addConnections_peak_gene(GRN, promoterRange = 10000, nCores = 2, forceRerun = FALSE) |
|
54 | 54 |
} |
... | ... |
@@ -50,7 +50,7 @@ Add data to a \code{\linkS4class{GRN}} object |
50 | 50 |
# rna.df = read_tsv("https://www.embl.de/download/zaugg/GRaNIE/rna.tsv.gz") |
51 | 51 |
# peaks.df = read_tsv("https://www.embl.de/download/zaugg/GRaNIE/peaks.tsv.gz") |
52 | 52 |
# meta.df = read_tsv("https://www.embl.de/download/zaugg/GRaNIE/sampleMetadata.tsv.gz") |
53 |
-# GRN = loadExampleObject() |
|
53 |
+GRN = loadExampleObject() |
|
54 | 54 |
# We omit sampleMetadata = meta.df here, lines becomes too long otherwise |
55 |
-# GRN = addData(GRN, counts_peaks = peaks.df, counts_rna = rna.df, forceRerun = FALSE) |
|
55 |
+GRN = addData(GRN, counts_peaks = peaks.df, counts_rna = rna.df, forceRerun = FALSE) |
|
56 | 56 |
} |
... | ... |
@@ -31,6 +31,6 @@ Add TF-gene correlations to a \code{\linkS4class{GRN}} object. The information i |
31 | 31 |
} |
32 | 32 |
\examples{ |
33 | 33 |
# See the Workflow vignette on the GRaNIE website for examples |
34 |
-# GRN = loadExampleObject() |
|
35 |
-# GRN = add_TF_gene_correlation(GRN, forceRerun = FALSE) |
|
34 |
+GRN = loadExampleObject() |
|
35 |
+GRN = add_TF_gene_correlation(GRN, forceRerun = FALSE) |
|
36 | 36 |
} |
... | ... |
@@ -34,6 +34,6 @@ Builds a graph out of a set of connections |
34 | 34 |
} |
35 | 35 |
\examples{ |
36 | 36 |
# See the Workflow vignette on the GRaNIE website for examples |
37 |
-# GRN = loadExampleObject() |
|
38 |
-# GRN = build_eGRN_graph(GRN, forceRerun = FALSE) |
|
37 |
+GRN = loadExampleObject() |
|
38 |
+GRN = build_eGRN_graph(GRN, forceRerun = FALSE) |
|
39 | 39 |
} |
... | ... |
@@ -43,8 +43,8 @@ After the vertices of the filtered GRN are clustered into communities using \cod |
43 | 43 |
} |
44 | 44 |
\examples{ |
45 | 45 |
# See the Workflow vignette on the GRaNIE website for examples |
46 |
-# GRN = loadExampleObject() |
|
47 |
-# GRN = calculateCommunitiesEnrichment(GRN, ontology = c("GO_BP"), forceRerun = FALSE) |
|
46 |
+GRN = loadExampleObject() |
|
47 |
+GRN = calculateCommunitiesEnrichment(GRN, ontology = c("GO_BP"), forceRerun = FALSE) |
|
48 | 48 |
} |
49 | 49 |
\seealso{ |
50 | 50 |
\code{\link{plotCommunitiesEnrichment}} |
... | ... |
@@ -23,6 +23,6 @@ This function generates the TF-gene graph from the filtered GRN object, and clus |
23 | 23 |
} |
24 | 24 |
\examples{ |
25 | 25 |
# See the Workflow vignette on the GRaNIE website for examples |
26 |
-# GRN = loadExampleObject() |
|
27 |
-# GRN = calculateCommunitiesStats(GRN, forceRerun = FALSE) |
|
26 |
+GRN = loadExampleObject() |
|
27 |
+GRN = calculateCommunitiesStats(GRN, forceRerun = FALSE) |
|
28 | 28 |
} |
... | ... |
@@ -37,8 +37,8 @@ This function runs an enrichment analysis for the genes in the filtered network. |
37 | 37 |
} |
38 | 38 |
\examples{ |
39 | 39 |
# See the Workflow vignette on the GRaNIE website for examples |
40 |
-# GRN = loadExampleObject() |
|
41 |
-# GRN = calculateGeneralEnrichment(GRN, ontology = "GO_BP", forceRerun = FALSE) |
|
40 |
+GRN = loadExampleObject() |
|
41 |
+GRN = calculateGeneralEnrichment(GRN, ontology = "GO_BP", forceRerun = FALSE) |
|
42 | 42 |
} |
43 | 43 |
\seealso{ |
44 | 44 |
\code{\link{plotGeneralEnrichment}} |
... | ... |
@@ -46,7 +46,7 @@ This function calculates the GO enrichment per TF, i.e. for the set of genes a g |
46 | 46 |
} |
47 | 47 |
\examples{ |
48 | 48 |
# See the Workflow vignette on the GRaNIE website for examples |
49 |
-# GRN = loadExampleObject() |
|
50 |
-# GRN = calculateTFEnrichment(GRN, n = 5, ontology = "GO_BP", forceRerun = FALSE) |
|
51 |
-# GRN = calculateTFEnrichment(GRN, n = 5, ontology = "GO_BP", forceRerun = FALSE) |
|
49 |
+GRN = loadExampleObject() |
|
50 |
+GRN = calculateTFEnrichment(GRN, n = 5, ontology = "GO_BP", forceRerun = FALSE) |
|
51 |
+GRN = calculateTFEnrichment(GRN, n = 5, ontology = "GO_BP", forceRerun = FALSE) |
|
52 | 52 |
} |
... | ... |
@@ -15,3 +15,8 @@ The same \code{\linkS4class{GRN}} object, with some slots being deleted (\code{G |
15 | 15 |
\description{ |
16 | 16 |
Optional convenience function to delete intermediate data from the function \link{AR_classification_wrapper} and summary statistics that may occupy a lot of space |
17 | 17 |
} |
18 |
+\examples{ |
|
19 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
20 |
+GRN = loadExampleObject() |
|
21 |
+GRN = deleteIntermediateData(GRN) |
|
22 |
+} |
... | ... |
@@ -55,6 +55,6 @@ Filter data from a \code{\linkS4class{GRN}} object |
55 | 55 |
} |
56 | 56 |
\examples{ |
57 | 57 |
# See the Workflow vignette on the GRaNIE website for examples |
58 |
-# GRN = loadExampleObject() |
|
59 |
-# GRN = filterData(GRN, forceRerun = FALSE) |
|
58 |
+GRN = loadExampleObject() |
|
59 |
+GRN = filterData(GRN, forceRerun = FALSE) |
|
60 | 60 |
} |
... | ... |
@@ -80,8 +80,8 @@ Internally, first, the TF-peak are filtered before the peak-gene connections are |
80 | 80 |
} |
81 | 81 |
\examples{ |
82 | 82 |
# See the Workflow vignette on the GRaNIE website for examples |
83 |
-# GRN = loadExampleObject() |
|
84 |
-# GRN = filterGRNAndConnectGenes(GRN) |
|
83 |
+GRN = loadExampleObject() |
|
84 |
+GRN = filterGRNAndConnectGenes(GRN) |
|
85 | 85 |
} |
86 | 86 |
\seealso{ |
87 | 87 |
\code{\link{visualizeGRN}} |
... | ... |
@@ -46,7 +46,7 @@ Essentially, this functions calls \code{filterGRNAndConnectGenes} repeatedly and |
46 | 46 |
} |
47 | 47 |
\examples{ |
48 | 48 |
# See the Workflow vignette on the GRaNIE website for examples |
49 |
-# GRN = loadExampleObject() |
|
50 |
-# GRN = generateStatsSummary(GRN, forceRerun = FALSE) |
|
49 |
+GRN = loadExampleObject() |
|
50 |
+GRN = generateStatsSummary(GRN, forceRerun = FALSE) |
|
51 | 51 |
|
52 | 52 |
} |
... | ... |
@@ -20,7 +20,7 @@ Return the number of genes (all or only non-filtered ones) that are defined in t |
20 | 20 |
} |
21 | 21 |
\examples{ |
22 | 22 |
# See the Workflow vignette on the GRaNIE website for examples |
23 |
-# GRN = loadExampleObject() |
|
24 |
-# nGenes(GRN, filter = TRUE) |
|
25 |
-# nGenes(GRN, filter = FALSE) |
|
23 |
+GRN = loadExampleObject() |
|
24 |
+nGenes(GRN, filter = TRUE) |
|
25 |
+nGenes(GRN, filter = FALSE) |
|
26 | 26 |
} |
... | ... |
@@ -24,6 +24,6 @@ Get counts for the various data defined in a \code{\linkS4class{GRN}} object. |
24 | 24 |
} |
25 | 25 |
\examples{ |
26 | 26 |
# See the Workflow vignette on the GRaNIE website for examples |
27 |
-# GRN = loadExampleObject() |
|
28 |
-# GRN = getCounts(GRN, type = "peaks", norm = TRUE, permuted = FALSE) |
|
27 |
+GRN = loadExampleObject() |
|
28 |
+GRN = getCounts(GRN, type = "peaks", norm = TRUE, permuted = FALSE) |
|
29 | 29 |
} |
... | ... |
@@ -28,6 +28,6 @@ Extract connections from a \code{\linkS4class{GRN}} object |
28 | 28 |
} |
29 | 29 |
\examples{ |
30 | 30 |
# See the Workflow vignette on the GRaNIE website for examples |
31 |
-# GRN = loadExampleObject() |
|
32 |
-# GRN_con.all = getGRNConnections(GRN, include_TF_gene_correlations = TRUE) |
|
31 |
+GRN = loadExampleObject() |
|
32 |
+GRN_con.all.df = getGRNConnections(GRN) |
|
33 | 33 |
} |
... | ... |
@@ -21,7 +21,7 @@ Retrieve parameters for previously used function calls and general parameters fo |
21 | 21 |
} |
22 | 22 |
\examples{ |
23 | 23 |
# See the Workflow vignette on the GRaNIE website for examples |
24 |
-# GRN = loadExampleObject() |
|
24 |
+GRN = loadExampleObject() |
|
25 | 25 |
# getParameters(GRN, type = "parameter", name = "all") |
26 | 26 |
|
27 | 27 |
} |
... | ... |
@@ -25,7 +25,7 @@ Retrieve top Nodes in the filtered \code{\linkS4class{GRN}} |
25 | 25 |
} |
26 | 26 |
\examples{ |
27 | 27 |
# See the Workflow vignette on the GRaNIE website for examples |
28 |
-# GRN = loadExampleObject() |
|
29 |
-# topGenes = getTopNodes(GRN, nodeType = "gene", rankType = "degree", n = 3) |
|
30 |
-# topTFs = getTopNodes(GRN, nodeType = "TF", rankType = "EV", n = 5) |
|
28 |
+GRN = loadExampleObject() |
|
29 |
+topGenes = getTopNodes(GRN, nodeType = "gene", rankType = "degree", n = 3) |
|
30 |
+topTFs = getTopNodes(GRN, nodeType = "TF", rankType = "EV", n = 5) |
|
31 | 31 |
} |
... | ... |
@@ -4,7 +4,15 @@ |
4 | 4 |
\alias{loadExampleObject} |
5 | 5 |
\title{Load example GRN dataset} |
6 | 6 |
\usage{ |
7 |
-loadExampleObject() |
|
7 |
+loadExampleObject( |
|
8 |
+ forceDownload = FALSE, |
|
9 |
+ fileURL = "https://www.embl.de/download/zaugg/GRaNIE/GRN.rds" |
|
10 |
+) |
|
11 |
+} |
|
12 |
+\arguments{ |
|
13 |
+\item{forceDownload}{\code{TRUE} or \code{FALSE}. Default \code{FALSE}. Should the download be enforced even if the local cached file is already present?} |
|
14 |
+ |
|
15 |
+\item{fileURL}{Character. Default https://www.embl.de/download/zaugg/GRaNIE/GRN.rds. URL to the GRN example object in rds format.} |
|
8 | 16 |
} |
9 | 17 |
\value{ |
10 | 18 |
An example \code{\linkS4class{GRN}} object |
... | ... |
@@ -21,6 +21,6 @@ Overlap peaks and TFBS for a \code{\linkS4class{GRN}} object |
21 | 21 |
} |
22 | 22 |
\examples{ |
23 | 23 |
# See the Workflow vignette on the GRaNIE website for examples |
24 |
-# GRN = loadExampleObject() |
|
25 |
-# GRN = overlapPeaksAndTFBS(GRN, nCores = 2, forceRerun = FALSE) |
|
24 |
+GRN = loadExampleObject() |
|
25 |
+GRN = overlapPeaksAndTFBS(GRN, nCores = 2, forceRerun = FALSE) |
|
26 | 26 |
} |
... | ... |
@@ -20,7 +20,7 @@ Return the number of peaks (all or only non-filtered ones) that are defined in t |
20 | 20 |
} |
21 | 21 |
\examples{ |
22 | 22 |
# See the Workflow vignette on the GRaNIE website for examples |
23 |
-# GRN = loadExampleObject() |
|
24 |
-# nPeaks(GRN, filter = TRUE) |
|
25 |
-# nPeaks(GRN, filter = FALSE) |
|
23 |
+GRN = loadExampleObject() |
|
24 |
+nPeaks(GRN, filter = TRUE) |
|
25 |
+nPeaks(GRN, filter = FALSE) |
|
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, forceRerun = FALSE) |
|
58 |
+GRN = loadExampleObject() |
|
59 |
+GRN = performAllNetworkAnalyses(GRN, forceRerun = FALSE) |
|
60 | 60 |
} |
... | ... |
@@ -61,6 +61,6 @@ Similarly to \code{\link{plotGeneralEnrichment}}, the results of the community-b |
61 | 61 |
} |
62 | 62 |
\examples{ |
63 | 63 |
# See the Workflow vignette on the GRaNIE website for examples |
64 |
-# GRN = loadExampleObject() |
|
65 |
-# GRN = plotCommunitiesEnrichment(GRN, forceRerun = FALSE) |
|
64 |
+GRN = loadExampleObject() |
|
65 |
+GRN = plotCommunitiesEnrichment(GRN, forceRerun = FALSE) |
|
66 | 66 |
} |
... | ... |
@@ -49,8 +49,8 @@ Similarly to the statistics produced by \code{\link{plotGeneralGraphStats}}, sum |
49 | 49 |
} |
50 | 50 |
\examples{ |
51 | 51 |
# See the Workflow vignette on the GRaNIE website for examples |
52 |
-# GRN = loadExampleObject() |
|
53 |
-# GRN = plotCommunitiesStats(GRN, display = "byRank", forceRerun = FALSE) |
|
52 |
+GRN = loadExampleObject() |
|
53 |
+GRN = plotCommunitiesStats(GRN, display = "byRank", forceRerun = FALSE) |
|
54 | 54 |
} |
55 | 55 |
\seealso{ |
56 | 56 |
\code{\link{plotGeneralGraphStats}} |
... | ... |
@@ -31,6 +31,6 @@ Plot diagnostic plots for TF-peak connections for a \code{\linkS4class{GRN}} obj |
31 | 31 |
} |
32 | 32 |
\examples{ |
33 | 33 |
# See the Workflow vignette on the GRaNIE website for examples |
34 |
-# GRN = loadExampleObject() |
|
35 |
-# GRN = plotDiagnosticPlots_TFPeaks(GRN, forceRerun = FALSE) |
|
34 |
+GRN = loadExampleObject() |
|
35 |
+GRN = plotDiagnosticPlots_TFPeaks(GRN, forceRerun = FALSE) |
|
36 | 36 |
} |
... | ... |
@@ -49,6 +49,6 @@ Plot diagnostic plots for peak-gene connections for a \code{\linkS4class{GRN}} o |
49 | 49 |
} |
50 | 50 |
\examples{ |
51 | 51 |
# See the Workflow vignette on the GRaNIE website for examples |
52 |
-# GRN = loadExampleObject() |
|
53 |
-# GRN = plotDiagnosticPlots_peakGene(GRN, forceRerun = FALSE) |
|
52 |
+GRN = loadExampleObject() |
|
53 |
+GRN = plotDiagnosticPlots_peakGene(GRN, forceRerun = FALSE) |
|
54 | 54 |
} |
... | ... |
@@ -49,6 +49,6 @@ This function plots the results of the general enrichment analysis for every spe |
49 | 49 |
} |
50 | 50 |
\examples{ |
51 | 51 |
# See the Workflow vignette on the GRaNIE website for examples |
52 |
-# GRN = loadExampleObject() |
|
53 |
-# GRN = plotGeneralEnrichment(GRN, topn_pvalue = 30, forceRerun = FALSE) |
|
52 |
+GRN = loadExampleObject() |
|
53 |
+GRN = plotGeneralEnrichment(GRN, topn_pvalue = 30, forceRerun = FALSE) |
|
54 | 54 |
} |
... | ... |
@@ -37,8 +37,8 @@ This function generates graphical summaries about the structure and connectivity |
37 | 37 |
} |
38 | 38 |
\examples{ |
39 | 39 |
# See the Workflow vignette on the GRaNIE website for examples |
40 |
-# GRN = loadExampleObject() |
|
41 |
-# GRN = plotGeneralGraphStats(GRN, forceRerun = FALSE) |
|
40 |
+GRN = loadExampleObject() |
|
41 |
+GRN = plotGeneralGraphStats(GRN, forceRerun = FALSE) |
|
42 | 42 |
} |
43 | 43 |
\seealso{ |
44 | 44 |
\code{\link{plotGeneralEnrichment}} |
... | ... |
@@ -43,6 +43,6 @@ Produce a PCA plot of the data from a \code{\linkS4class{GRN}} object |
43 | 43 |
} |
44 | 44 |
\examples{ |
45 | 45 |
# See the Workflow vignette on the GRaNIE website for examples |
46 |
-# GRN = loadExampleObject() |
|
47 |
-# GRN = plotPCA_all(GRN, type = c("rna", "peaks"), topn = 500, forceRerun = FALSE) |
|
46 |
+GRN = loadExampleObject() |
|
47 |
+GRN = plotPCA_all(GRN, type = c("rna", "peaks"), topn = 500, forceRerun = FALSE) |
|
48 | 48 |
} |
... | ... |
@@ -64,8 +64,8 @@ This function plots the enrichment results. The result consist of a dot plot per |
64 | 64 |
} |
65 | 65 |
\examples{ |
66 | 66 |
# See the Workflow vignette on the GRaNIE website for examples |
67 |
-# GRN = loadExampleObject() |
|
68 |
-# GRN = plotTFEnrichment(GRN, rankType = "degree", n = 5, forceRerun = FALSE) |
|
67 |
+GRN = loadExampleObject() |
|
68 |
+GRN = plotTFEnrichment(GRN, rankType = "degree", n = 5, forceRerun = FALSE) |
|
69 | 69 |
} |
70 | 70 |
\seealso{ |
71 | 71 |
\code{\link{calculateTFEnrichment}} |
... | ... |
@@ -40,6 +40,6 @@ Plot various network connectivity summaries for a \code{\linkS4class{GRN}} objec |
40 | 40 |
} |
41 | 41 |
\examples{ |
42 | 42 |
# See the Workflow vignette on the GRaNIE website for examples |
43 |
-# GRN = loadExampleObject() |
|
44 |
-# GRN = plot_stats_connectionSummary(GRN, type = "heatmap", forceRerun = FALSE) |
|
43 |
+GRN = loadExampleObject() |
|
44 |
+GRN = plot_stats_connectionSummary(GRN, type = "heatmap", forceRerun = FALSE) |
|
45 | 45 |
} |