... | ... |
@@ -245,11 +245,12 @@ setMethod("show", |
245 | 245 |
#' |
246 | 246 |
#' @template GRN |
247 | 247 |
#' @param filter TRUE or FALSE. Default TRUE. Should peaks marked as filtered be included in the count? |
248 |
-#' @return Integer. Number of peaks hat 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} (see method TODO) |
|
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 |
-#' GRN = loadExampleObject() |
|
251 |
-#' nPeaks(GRN, filter = TRUE) |
|
252 |
-#' nPeaks(GRN, filter = FALSE) |
|
250 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
251 |
+#' # GRN = loadExampleObject() |
|
252 |
+#' # nPeaks(GRN, filter = TRUE) |
|
253 |
+#' # nPeaks(GRN, filter = FALSE) |
|
253 | 254 |
#' @export |
254 | 255 |
#' @aliases peaks |
255 | 256 |
#' @rdname peaks-methods |
... | ... |
@@ -279,11 +280,12 @@ nPeaks <- function(GRN, filter = TRUE) { |
279 | 280 |
#' |
280 | 281 |
#' @template GRN |
281 | 282 |
#' @param filter TRUE or FALSE. Default TRUE. Should genes marked as filtered be included in the count? |
282 |
-#' @return Integer. Number of genes hat 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} (see method TODO) |
|
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}. |
|
283 | 284 |
#' @examples |
284 |
-#' GRN = loadExampleObject() |
|
285 |
-#' nGenes(GRN, filter = TRUE) |
|
286 |
-#' nGenes(GRN, filter = FALSE) |
|
285 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
286 |
+#' # GRN = loadExampleObject() |
|
287 |
+#' # nGenes(GRN, filter = TRUE) |
|
288 |
+#' # nGenes(GRN, filter = FALSE) |
|
287 | 289 |
#' @export |
288 | 290 |
#' @aliases genes |
289 | 291 |
#' @rdname genes-methods |
... | ... |
@@ -112,13 +112,14 @@ initializeGRN <- function(objectMetadata = list(), |
112 | 112 |
#' @template forceRerun |
113 | 113 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. |
114 | 114 |
#' @examples |
115 |
-#' library(tidyverse) |
|
116 |
-#' rna.df = read_tsv("https://www.embl.de/download/zaugg/GRaNIE/rna.tsv.gz") |
|
117 |
-#' peaks.df = read_tsv("https://www.embl.de/download/zaugg/GRaNIE/peaks.tsv.gz") |
|
118 |
-#' meta.df = read_tsv("https://www.embl.de/download/zaugg/GRaNIE/sampleMetadata.tsv.gz") |
|
119 |
-#' GRN = loadExampleObject() |
|
115 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
116 |
+#' # library(tidyverse) |
|
117 |
+#' # rna.df = read_tsv("https://www.embl.de/download/zaugg/GRaNIE/rna.tsv.gz") |
|
118 |
+#' # peaks.df = read_tsv("https://www.embl.de/download/zaugg/GRaNIE/peaks.tsv.gz") |
|
119 |
+#' # meta.df = read_tsv("https://www.embl.de/download/zaugg/GRaNIE/sampleMetadata.tsv.gz") |
|
120 |
+#' # GRN = loadExampleObject() |
|
120 | 121 |
#' # We omit sampleMetadata = meta.df here, lines becomes too long otherwise |
121 |
-#' 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) |
|
122 | 123 |
|
123 | 124 |
addData <- function(GRN, counts_peaks, normalization_peaks = "DESeq_sizeFactor", idColumn_peaks = "peakID", |
124 | 125 |
counts_rna, normalization_rna = "quantile", idColumn_RNA = "ENSEMBL", sampleMetadata = NULL, |
... | ... |
@@ -600,8 +601,9 @@ addData <- function(GRN, counts_peaks, normalization_peaks = "DESeq_sizeFactor", |
600 | 601 |
#' @template forceRerun |
601 | 602 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. |
602 | 603 |
#' @examples |
603 |
-#' GRN = loadExampleObject() |
|
604 |
-#' GRN = filterData(GRN, forceRerun = FALSE) |
|
604 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
605 |
+#' # GRN = loadExampleObject() |
|
606 |
+#' # GRN = filterData(GRN, forceRerun = FALSE) |
|
605 | 607 |
#' @export |
606 | 608 |
filterData <- function (GRN, |
607 | 609 |
minNormalizedMean_peaks = 5, maxNormalizedMean_peaks = NULL, |
... | ... |
@@ -850,7 +852,7 @@ filterData <- function (GRN, |
850 | 852 |
#' @template forceRerun |
851 | 853 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. |
852 | 854 |
#' @examples |
853 |
-#' # see workflow vignette for an example on how to add TFBS |
|
855 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
854 | 856 |
#' @export |
855 | 857 |
addTFBS <- function(GRN, motifFolder, TFs = "all", nTFMax = NULL, filesTFBSPattern = "_TFBS", fileEnding = ".bed", forceRerun = FALSE) { |
856 | 858 |
|
... | ... |
@@ -967,8 +969,9 @@ addTFBS <- function(GRN, motifFolder, TFs = "all", nTFMax = NULL, filesTFBSPatte |
967 | 969 |
#' @template forceRerun |
968 | 970 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. |
969 | 971 |
#' @examples |
970 |
-#' GRN = loadExampleObject() |
|
971 |
-#' GRN = overlapPeaksAndTFBS(GRN, nCores = 2, forceRerun = FALSE) |
|
972 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
973 |
+#' # GRN = loadExampleObject() |
|
974 |
+#' # GRN = overlapPeaksAndTFBS(GRN, nCores = 2, forceRerun = FALSE) |
|
972 | 975 |
#' @export |
973 | 976 |
overlapPeaksAndTFBS <- function(GRN, nCores = 2, forceRerun = FALSE) { |
974 | 977 |
|
... | ... |
@@ -1502,8 +1505,9 @@ importTFData <- function(GRN, data, name, idColumn = "ENSEMBL", nameColumn = "TF |
1502 | 1505 |
#' @template forceRerun |
1503 | 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, |
1504 | 1507 |
#' @examples |
1505 |
-#' GRN = loadExampleObject() |
|
1506 |
-#' GRN = AR_classification_wrapper(GRN, forceRerun = FALSE) |
|
1508 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
1509 |
+#' # GRN = loadExampleObject() |
|
1510 |
+#' # GRN = AR_classification_wrapper(GRN, forceRerun = FALSE) |
|
1507 | 1511 |
#' @export |
1508 | 1512 |
AR_classification_wrapper<- function (GRN, significanceThreshold_Wilcoxon = 0.05, |
1509 | 1513 |
plot_minNoTFBS_heatmap = 100, deleteIntermediateData = TRUE, |
... | ... |
@@ -1710,17 +1714,18 @@ AR_classification_wrapper<- function (GRN, significanceThreshold_Wilcoxon = 0.05 |
1710 | 1714 |
#' @template plotDetails |
1711 | 1715 |
#' @template outputFolder |
1712 | 1716 |
#' @template corMethod |
1713 |
-#' @param connectionTypes TODO describe |
|
1717 |
+#' @param connectionTypes Character vector. Default \code{expression}. Vector of connection types to include for the TF-peak connections. If an additional connection type is specified here, it has to be available already within the object (EXPERIMENTAL). See the function \code{addData_TFActivity} for details. |
|
1714 | 1718 |
#' @param removeNegativeCorrelation \code{TRUE} or \code{FALSE} (vector). Default \code{FALSE}. EXPERIMENTAL. Must be a logical vector of the same length as the parameter \code{connectionType}. Should negatively correlated TF-peak connections be removed for the specific connection type? For connection type expression, the default is FALSE, while for any TF Activity related connection type, we recommend setting this to \code{TRUE}. |
1715 | 1719 |
#' @param maxFDRToStore Numeric. Default 0.3. Maximum TF-peak FDR value to permanently store a particular TF-peak connection in the object? This parameter has a large influence on the overall memory size of the object, and we recommend not storing connections with a high FDR due to their sheer number. |
1716 | 1720 |
#' @param useGCCorrection \code{TRUE} or \code{FALSE}. Default \code{FALSE}. EXPERIMENTAL. Should a GC-matched background be used when calculating FDRs? |
1717 |
-#' @param percBackground_size Numeric (0 to 100). Default 75. EXPERIMENTAL. Description will follow TODO. Only relevant if \code{useGCCorrection} is set to \code{TRUE}, ignored otherwise. |
|
1721 |
+#' @param percBackground_size Numeric (0 to 100). Default 75. EXPERIMENTAL. Description will follow. Only relevant if \code{useGCCorrection} is set to \code{TRUE}, ignored otherwise. |
|
1718 | 1722 |
#' @param percBackground_resample \code{TRUE} or \code{FALSE}. Default \code{TRUE}. EXPERIMENTAL. Should resampling be enabled for those GC bins for which not enough background peaks are available?. Only relevant if \code{useGCCorrection} is set to \code{TRUE}, ignored otherwise. |
1719 | 1723 |
#' @template forceRerun |
1720 | 1724 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. TF_peak.fdrCurves_perm{o,1}.pdf |
1721 | 1725 |
#' @examples |
1722 |
-#' GRN = loadExampleObject() |
|
1723 |
-#' GRN = addConnections_TF_peak(GRN, forceRerun = FALSE) |
|
1726 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
1727 |
+#' # GRN = loadExampleObject() |
|
1728 |
+#' # GRN = addConnections_TF_peak(GRN, forceRerun = FALSE) |
|
1724 | 1729 |
#' @export |
1725 | 1730 |
addConnections_TF_peak <- function (GRN, plotDiagnosticPlots = TRUE, plotDetails = FALSE, outputFolder = NULL, |
1726 | 1731 |
corMethod = "pearson", |
... | ... |
@@ -2264,8 +2269,9 @@ addConnections_TF_peak <- function (GRN, plotDiagnosticPlots = TRUE, plotDetails |
2264 | 2269 |
#' @template forceRerun |
2265 | 2270 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function in different flavors. |
2266 | 2271 |
#' @examples |
2267 |
-#' GRN = loadExampleObject() |
|
2268 |
-#' GRN = addConnections_peak_gene(GRN, promoterRange = 10000, nCores = 2, forceRerun = FALSE) |
|
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) |
|
2269 | 2275 |
addConnections_peak_gene <- function(GRN, overlapTypeGene = "TSS", corMethod = "pearson", |
2270 | 2276 |
promoterRange = 250000, TADs = NULL, |
2271 | 2277 |
nCores = 4, |
... | ... |
@@ -2805,8 +2811,9 @@ addConnections_peak_gene <- function(GRN, overlapTypeGene = "TSS", corMethod = " |
2805 | 2811 |
#' @template outputFolder |
2806 | 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 |
2807 | 2813 |
#' @examples |
2808 |
-#' GRN = loadExampleObject() |
|
2809 |
-#' GRN = filterGRNAndConnectGenes(GRN) |
|
2814 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
2815 |
+#' # GRN = loadExampleObject() |
|
2816 |
+#' # GRN = filterGRNAndConnectGenes(GRN) |
|
2810 | 2817 |
#' @seealso \code{\link{visualizeGRN}} |
2811 | 2818 |
#' @seealso \code{\link{addConnections_TF_peak}} |
2812 | 2819 |
#' @seealso \code{\link{addConnections_peak_gene}} |
... | ... |
@@ -3379,8 +3386,9 @@ filterGRNAndConnectGenes <- function(GRN, |
3379 | 3386 |
#' @template forceRerun |
3380 | 3387 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. |
3381 | 3388 |
#' @examples |
3382 |
-#' GRN = loadExampleObject() |
|
3383 |
-#' GRN = add_TF_gene_correlation(GRN, forceRerun = FALSE) |
|
3389 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
3390 |
+#' # GRN = loadExampleObject() |
|
3391 |
+#' # GRN = add_TF_gene_correlation(GRN, forceRerun = FALSE) |
|
3384 | 3392 |
add_TF_gene_correlation <- function(GRN, corMethod = "pearson", addRobustRegression = FALSE, nCores = 1, forceRerun = FALSE) { |
3385 | 3393 |
|
3386 | 3394 |
GRN = .addFunctionLogToObject(GRN) |
... | ... |
@@ -3628,8 +3636,9 @@ addSNPOverlap <- function(grn, SNPData, col_chr = "chr", col_pos = "pos", col_pe |
3628 | 3636 |
#' @template forceRerun |
3629 | 3637 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. |
3630 | 3638 |
#' @examples |
3631 |
-#' GRN = loadExampleObject() |
|
3632 |
-#' GRN = generateStatsSummary(GRN, forceRerun = FALSE) |
|
3639 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
3640 |
+#' # GRN = loadExampleObject() |
|
3641 |
+#' # GRN = generateStatsSummary(GRN, forceRerun = FALSE) |
|
3633 | 3642 |
#' |
3634 | 3643 |
generateStatsSummary <- function(GRN, |
3635 | 3644 |
TF_peak.fdr = c(0.001, 0.01, 0.05, 0.1, 0.2), |
... | ... |
@@ -3919,9 +3928,10 @@ loadExampleObject <- function() { |
3919 | 3928 |
#' @export |
3920 | 3929 |
#' @import tibble |
3921 | 3930 |
#' @examples |
3922 |
-#' GRN = loadExampleObject() |
|
3923 |
-#' GRN = getCounts(GRN, type = "peaks", norm = TRUE, permuted = FALSE) |
|
3924 |
-#' @return Counts. TODO MORE |
|
3931 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
3932 |
+#' # GRN = loadExampleObject() |
|
3933 |
+#' # GRN = getCounts(GRN, type = "peaks", norm = TRUE, permuted = FALSE) |
|
3934 |
+#' @return Data frame of counts, with the type as indicated by the function parameters. |
|
3925 | 3935 |
#' getCounts(GRN, type = "peaks", norm = TRUE) |
3926 | 3936 |
getCounts <- function(GRN, type, norm, permuted = FALSE) { |
3927 | 3937 |
|
... | ... |
@@ -4009,8 +4019,9 @@ getCounts <- function(GRN, type, norm, permuted = FALSE) { |
4009 | 4019 |
#' @param include_TF_gene_correlations Logical. \code{TRUE} or \code{FALSE}. Should TFs and gene correlations be returned as well? If set to \code{TRUE}, they must have been computed beforehand with \code{\link{add_TF_gene_correlation}}. |
4010 | 4020 |
#' @return A data frame with the connections. Importantly, this function does NOT return a \code{\linkS4class{GRN}} object. |
4011 | 4021 |
#' @examples |
4012 |
-#' GRN = loadExampleObject() |
|
4013 |
-#' GRN_con.all = getGRNConnections(GRN, include_TF_gene_correlations = TRUE) |
|
4022 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
4023 |
+#' # GRN = loadExampleObject() |
|
4024 |
+#' # GRN_con.all = getGRNConnections(GRN, include_TF_gene_correlations = TRUE) |
|
4014 | 4025 |
getGRNConnections <- function(GRN, type = "all.filtered", permuted = FALSE, include_TF_gene_correlations = FALSE) { |
4015 | 4026 |
|
4016 | 4027 |
GRN = .addFunctionLogToObject(GRN) |
... | ... |
@@ -4182,41 +4193,42 @@ getGRNConnections <- function(GRN, type = "all.filtered", permuted = FALSE, inc |
4182 | 4193 |
#' |
4183 | 4194 |
#' @export |
4184 | 4195 |
#' @template GRN |
4185 |
-#' @param name Character. Name of parameter or function name to retrieve. Ignored if \code{type} == \code{all}. |
|
4186 |
-#' @param type Character. Default \code{function}. Either \code{function}, \code{parameter}, or \code{all}. When set to \code{function}, a valid \code{GRaNIE} function name must be given that has been run before. \code{parameter} indicates a particular parameter name is returned (as specified in \code{GRN@config})), while \code{all} returns all parameters. |
|
4196 |
+#' @param name Character. Default \code{all}. Name of parameter or function name to retrieve. Set to the special keyword \code{all} to retrieve all parameters. |
|
4197 |
+#' @param type Character. Default \code{parameter}. Either \code{function} or \code{parameter}. When set to \code{function}, a valid \code{GRaNIE} function name must be given that has been run before. When set to \code{parameter}, in combination with \code{name}, returns a specific parameter (as specified in \code{GRN@config})). |
|
4187 | 4198 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. |
4188 | 4199 |
#' @examples |
4189 |
-#' GRN = loadExampleObject() |
|
4190 |
-#' getParameters(GRN, type = "function") |
|
4200 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
4201 |
+#' # GRN = loadExampleObject() |
|
4202 |
+#' # getParameters(GRN, type = "parameter", name = "all") |
|
4191 | 4203 |
#' |
4192 |
-getParameters <- function (GRN, type = "function", name = NULL) { |
|
4204 |
+getParameters <- function (GRN, type = "parameter", name = "all") { |
|
4193 | 4205 |
|
4194 | 4206 |
checkmate::assertClass(GRN, "GRN") |
4195 |
- checkmate::assertCharacter(name, any.missing = FALSE, len = 1) |
|
4196 |
- checkmate::assertSubset(type, c("function", "parameter", "all")) |
|
4207 |
+ checkmate::assertSubset(type, c("function", "parameter")) |
|
4197 | 4208 |
|
4198 | 4209 |
if (type == "function") { |
4199 | 4210 |
|
4211 |
+ checkmate::assertCharacter(name, any.missing = FALSE, len = 1) |
|
4200 | 4212 |
functionParameters = GRN@config$functionParameters[[name]] |
4201 | 4213 |
if (is.null(functionParameters)) { |
4202 | 4214 |
checkmate::assertSubset(name, ls(paste0("package:", utils::packageName()))) |
4203 |
- } else { |
|
4204 |
- return(functionParameters) |
|
4205 |
- } |
|
4206 |
- |
|
4207 |
- } else if (type == "all") { |
|
4208 |
- |
|
4209 |
- return(GRN@config) |
|
4215 |
+ } |
|
4210 | 4216 |
|
4217 |
+ return(functionParameters) |
|
4218 |
+ |
|
4211 | 4219 |
} else { |
4212 | 4220 |
|
4213 |
- parameters = GRN@config[[name]] |
|
4214 |
- if (is.null(parameters)) { |
|
4215 |
- checkmate::assertSubset(name, names(GRN@config$parameters)) |
|
4216 |
- } else { |
|
4217 |
- return(parameters) |
|
4218 |
- } |
|
4219 |
- |
|
4221 |
+ if (name == "all") { |
|
4222 |
+ return(GRN@config) |
|
4223 |
+ } else { |
|
4224 |
+ parameters = GRN@config[[name]] |
|
4225 |
+ if (is.null(parameters)) { |
|
4226 |
+ checkmate::assertSubset(name, names(GRN@config$parameters)) |
|
4227 |
+ } |
|
4228 |
+ |
|
4229 |
+ return(parameters) |
|
4230 |
+ } |
|
4231 |
+ |
|
4220 | 4232 |
} |
4221 | 4233 |
|
4222 | 4234 |
} |
... | ... |
@@ -4236,7 +4248,7 @@ getParameters <- function (GRN, type = "function", name = NULL) { |
4236 | 4248 |
#' Optional convenience function to delete intermediate data from the function \link{AR_classification_wrapper} and summary statistics that may occupy a lot of space |
4237 | 4249 |
#' @export |
4238 | 4250 |
#' @template GRN |
4239 |
-#' @return TODO |
|
4251 |
+#' @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}) |
|
4240 | 4252 |
deleteIntermediateData <- function(GRN) { |
4241 | 4253 |
|
4242 | 4254 |
|
... | ... |
@@ -6,10 +6,12 @@ |
6 | 6 |
#' @param allowLoops \code{TRUE} or \code{FALSE}. Default \code{FALSE}. Allow loops in the network (i.e., a TF that regulates itself) |
7 | 7 |
#' @param removeMultiple \code{TRUE} or \code{FALSE}. Default \code{FALSE}. Remove loops with the same start and end point? This can happen if multiple TF originate from the same gene, for example. |
8 | 8 |
#' @param directed \code{TRUE} or \code{FALSE}. Default \code{FALSE}. Should the network be directed? |
9 |
+#' @template forceRerun |
|
9 | 10 |
#' @export |
10 | 11 |
#' @examples |
11 |
-#' GRN = loadExampleObject() |
|
12 |
-#' GRN = build_eGRN_graph(GRN, forceRerun = FALSE) |
|
12 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
13 |
+#' # GRN = loadExampleObject() |
|
14 |
+#' # GRN = build_eGRN_graph(GRN, forceRerun = FALSE) |
|
13 | 15 |
#' @return The same \code{\linkS4class{GRN}} object. |
14 | 16 |
build_eGRN_graph <- function(GRN, model_TF_gene_nodes_separately = FALSE, |
15 | 17 |
allowLoops = FALSE, removeMultiple = FALSE, directed = FALSE, forceRerun = FALSE) { |
... | ... |
@@ -197,8 +199,9 @@ build_eGRN_graph <- function(GRN, model_TF_gene_nodes_separately = FALSE, |
197 | 199 |
#' @inheritParams calculateCommunitiesStats |
198 | 200 |
#' @export |
199 | 201 |
#' @examples |
200 |
-#' GRN = loadExampleObject() |
|
201 |
-#' GRN = performAllNetworkAnalyses(GRN, forceRerun = FALSE) |
|
202 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
203 |
+#' # GRN = loadExampleObject() |
|
204 |
+#' # GRN = performAllNetworkAnalyses(GRN, forceRerun = FALSE) |
|
202 | 205 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. |
203 | 206 |
performAllNetworkAnalyses <- function(GRN, ontology = c("GO_BP", "GO_MF"), |
204 | 207 |
algorithm = "weight01", statistic = "fisher", |
... | ... |
@@ -293,8 +296,9 @@ performAllNetworkAnalyses <- function(GRN, ontology = c("GO_BP", "GO_MF"), |
293 | 296 |
#' @seealso \code{\link{calculateCommunitiesEnrichment}} |
294 | 297 |
#' @seealso \code{\link{plotCommunitiesEnrichment}} |
295 | 298 |
#' @examples |
296 |
-#' GRN = loadExampleObject() |
|
297 |
-#' GRN = calculateGeneralEnrichment(GRN, ontology = "GO_BP", forceRerun = FALSE) |
|
299 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
300 |
+#' # GRN = loadExampleObject() |
|
301 |
+#' # GRN = calculateGeneralEnrichment(GRN, ontology = "GO_BP", forceRerun = FALSE) |
|
298 | 302 |
#' @export |
299 | 303 |
#' @import topGO |
300 | 304 |
#' @import BiocManager |
... | ... |
@@ -722,8 +726,9 @@ calculateGeneralEnrichment <- function(GRN, ontology = c("GO_BP", "GO_MF"), |
722 | 726 |
#' @return The same \code{\linkS4class{GRN}} object, with a table that consists of the connections clustered into communities stored in the \code{stats$communities} slot. |
723 | 727 |
#' @import patchwork |
724 | 728 |
#' @examples |
725 |
-#' GRN = loadExampleObject() |
|
726 |
-#' GRN = calculateCommunitiesStats(GRN, forceRerun = FALSE) |
|
729 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
730 |
+#' # GRN = loadExampleObject() |
|
731 |
+#' # GRN = calculateCommunitiesStats(GRN, forceRerun = FALSE) |
|
727 | 732 |
#' @export |
728 | 733 |
calculateCommunitiesStats <- function(GRN, clustering = "louvain", forceRerun = FALSE, ...){ |
729 | 734 |
|
... | ... |
@@ -781,46 +786,7 @@ calculateCommunitiesStats <- function(GRN, clustering = "louvain", forceRerun = |
781 | 786 |
futile.logger::flog.info(paste0(" Community ", names(communities_count)[clusterCur], ": ", communities_count[clusterCur], " nodes")) |
782 | 787 |
} |
783 | 788 |
|
784 |
- # communityVertices = tibble::tibble(vertex = communities_cluster$names, |
|
785 |
- # community = factor(communities_cluster$membership, levels = names(communities_count))) |
|
786 |
- # |
|
787 |
- # # identify the TFs |
|
788 |
- # allTF_genes = GRN@graph$TF_gene$table %>% dplyr::filter(connectionType == "tf-gene") %>% dplyr::pull(V1) %>% unique() |
|
789 |
- # communityVertices$Class[which(communityVertices$vertex %in% allTF_genes)] = "TF" |
|
790 |
- |
|
791 |
- # TODO: All the code is deactivated as it seems redundant |
|
792 |
- # GRN@stats$communityVertices = communityVertices |
|
793 |
- |
|
794 |
- |
|
795 | 789 |
|
796 |
- # |
|
797 |
- # communityGraphs = dplyr::tribble(~V1, ~V2, ~V1_name, ~V2_name, ~connectionType, ~community) |
|
798 |
- # # matrix(ncol=3, nrow =0, dimnames = list(c(), c("V1", "V2", "community"))) |
|
799 |
- # |
|
800 |
- # # Assign a subgraph / GRN per community, consisting of all vertices that belong to the particular community |
|
801 |
- # # If a link is between two communities, it will be shared? |
|
802 |
- # for (communityCur in stats::na.omit(names(communities_count))){ # change this to select communities |
|
803 |
- # |
|
804 |
- # community_subgraph.df = |
|
805 |
- # igraph::induced_subgraph(graph = GRN@graph$TF_gene$graph, |
|
806 |
- # vids = communityVertices$vertex[communityVertices$community==communityCur]) %>% |
|
807 |
- # igraph::as_long_data_frame() %>% |
|
808 |
- # dplyr::rename(V1 = `ver[el[, 1], ]`, V2 = `ver2[el[, 2], ]`) %>% |
|
809 |
- # dplyr::select(V1, V2, V1_name, V2_name, connectionType) %>% |
|
810 |
- # dplyr::mutate(community = communityCur) |
|
811 |
- # |
|
812 |
- # communityGraphs = rbind(communityGraphs, community_subgraph.df[,c("V1", "V2", "V1_name", "V2_name", "connectionType", "community")]) |
|
813 |
- # |
|
814 |
- # } |
|
815 |
- # |
|
816 |
- # |
|
817 |
- # GRN@stats$communities = communityGraphs %>% |
|
818 |
- # dplyr::mutate(community = as.factor(community), |
|
819 |
- # V1 = as.factor(V1), |
|
820 |
- # V2 = as.factor(V2), |
|
821 |
- # V1_name = as.factor(V1_name), |
|
822 |
- # V2_name = as.factor(V2_name), |
|
823 |
- # connectionType = as.factor(connectionType)) |
|
824 | 790 |
|
825 | 791 |
} else { |
826 | 792 |
|
... | ... |
@@ -843,8 +809,9 @@ calculateCommunitiesStats <- function(GRN, clustering = "louvain", forceRerun = |
843 | 809 |
#' @seealso \code{\link{plotGeneralEnrichment}} |
844 | 810 |
#' @seealso \code{\link{calculateGeneralEnrichment}} |
845 | 811 |
#' @examples |
846 |
-#' GRN = loadExampleObject() |
|
847 |
-#' GRN = calculateCommunitiesEnrichment(GRN, ontology = c("GO_BP"), forceRerun = FALSE) |
|
812 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
813 |
+#' # GRN = loadExampleObject() |
|
814 |
+#' # GRN = calculateCommunitiesEnrichment(GRN, ontology = c("GO_BP"), forceRerun = FALSE) |
|
848 | 815 |
#' @export |
849 | 816 |
calculateCommunitiesEnrichment <- function(GRN, |
850 | 817 |
ontology = c("GO_BP", "GO_MF"), algorithm = "weight01", |
... | ... |
@@ -969,9 +936,10 @@ calculateCommunitiesEnrichment <- function(GRN, |
969 | 936 |
#' @param use_TF_gene_network \code{TRUE} or \code{FALSE}. Default \code{TRUE}. Should the TF-gene network be used (\code{TRUE}) or the TF-peak-gene network (\code{FALSE})? |
970 | 937 |
#' @return A dataframe with the node names and the corresponding scores used to rank them |
971 | 938 |
#' @examples |
972 |
-#' GRN = loadExampleObject() |
|
973 |
-#' topGenes = getTopNodes(GRN, nodeType = "gene", rankType = "degree", n = 3) |
|
974 |
-#' topTFs = getTopNodes(GRN, nodeType = "TF", rankType = "EV", n = 5) |
|
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) |
|
975 | 943 |
#' @export |
976 | 944 |
getTopNodes <- function(GRN, nodeType, rankType, n = 0.1, use_TF_gene_network = TRUE) { # }, |
977 | 945 |
# TFConnectionType = "tf-gene", geneConnectionType = "peak-gene"){ |
... | ... |
@@ -997,9 +965,6 @@ getTopNodes <- function(GRN, nodeType, rankType, n = 0.1, use_TF_gene_network = |
997 | 965 |
|
998 | 966 |
graphType = dplyr::if_else(use_TF_gene_network, "TF_gene", "TF_peak_gene") |
999 | 967 |
|
1000 |
- #slot = dplyr::if_else(nodeType == "gene", "gene.ENSEMBL", "TF.name")# todo |
|
1001 |
- #link = dplyr::if_else(nodeType == "gene", geneConnectionType, TFConnectionType) |
|
1002 |
- #graphType = dplyr::if_else(stringr::str_detect(link, ".*peak.*"), "TF_peak_gene", "TF_gene") |
|
1003 | 968 |
|
1004 | 969 |
if(n<1){ |
1005 | 970 |
# Get the total number of distinct nodes and calculate a percentage of that irrespective of ndoe degree |
... | ... |
@@ -1057,9 +1022,10 @@ getTopNodes <- function(GRN, nodeType, rankType, n = 0.1, use_TF_gene_network = |
1057 | 1022 |
#' @param TF.names Character vector. If the rank type is set to "custom", a vector of TF names for which the GO enrichment should be calculated should be passed to this parameter. |
1058 | 1023 |
#' @return The same \code{\linkS4class{GRN}} object, with the enrichment results stored in the \code{stats$Enrichment$byTF} slot. |
1059 | 1024 |
#' @examples |
1060 |
-#' GRN = loadExampleObject() |
|
1061 |
-#' GRN = calculateTFEnrichment(GRN, rankType = "degree", n = 5, ontology = "GO_BP", forceRerun = FALSE) |
|
1062 |
-#' GRN = calculateTFEnrichment(GRN, rankType = "EV", n = 5, ontology = "GO_BP", forceRerun = FALSE) |
|
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) |
|
1063 | 1029 |
#' @export |
1064 | 1030 |
calculateTFEnrichment <- function(GRN, rankType = "degree", n = 0.1, TF.names = NULL, |
1065 | 1031 |
ontology = c("GO_BP", "GO_MF"), algorithm = "weight01", |
... | ... |
@@ -15,8 +15,9 @@ |
15 | 15 |
#' @template pdf_height |
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 |
-#' GRN = loadExampleObject() |
|
19 |
-#' GRN = plotPCA_all(GRN, type = c("rna", "peaks"), topn = 500, forceRerun = FALSE) |
|
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) |
|
20 | 21 |
#' @export |
21 | 22 |
plotPCA_all <- function(GRN, outputFolder = NULL, basenameOutput = NULL, |
22 | 23 |
type = c("rna", "peaks"), topn = c(500,1000,5000), |
... | ... |
@@ -448,8 +449,9 @@ plotPCA_all <- function(GRN, outputFolder = NULL, basenameOutput = NULL, |
448 | 449 |
#' @template forceRerun |
449 | 450 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. |
450 | 451 |
#' @examples |
451 |
-#' GRN = loadExampleObject() |
|
452 |
-#' GRN = plotDiagnosticPlots_TFPeaks(GRN, forceRerun = FALSE) |
|
452 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
453 |
+#' # GRN = loadExampleObject() |
|
454 |
+#' # GRN = plotDiagnosticPlots_TFPeaks(GRN, forceRerun = FALSE) |
|
453 | 455 |
#' @export |
454 | 456 |
plotDiagnosticPlots_TFPeaks <- function(GRN, |
455 | 457 |
outputFolder = NULL, |
... | ... |
@@ -788,8 +790,9 @@ plotDiagnosticPlots_TFPeaks <- function(GRN, |
788 | 790 |
#' @template forceRerun |
789 | 791 |
#' @return The same \code{\linkS4class{GRN}} object, with added data from this function. |
790 | 792 |
#' @examples |
791 |
-#' GRN = loadExampleObject() |
|
792 |
-#' GRN = plotDiagnosticPlots_peakGene(GRN, forceRerun = FALSE) |
|
793 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
794 |
+#' # GRN = loadExampleObject() |
|
795 |
+#' # GRN = plotDiagnosticPlots_peakGene(GRN, forceRerun = FALSE) |
|
793 | 796 |
#' @export |
794 | 797 |
plotDiagnosticPlots_peakGene <- function(GRN, |
795 | 798 |
outputFolder = NULL, |
... | ... |
@@ -1560,8 +1563,9 @@ plotDiagnosticPlots_peakGene <- function(GRN, |
1560 | 1563 |
#' @template forceRerun |
1561 | 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. |
1562 | 1565 |
#' @examples |
1563 |
-#' GRN = loadExampleObject() |
|
1564 |
-#' GRN = plot_stats_connectionSummary(GRN, type = "heatmap", forceRerun = FALSE) |
|
1566 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
1567 |
+#' # GRN = loadExampleObject() |
|
1568 |
+#' # GRN = plot_stats_connectionSummary(GRN, type = "heatmap", forceRerun = FALSE) |
|
1565 | 1569 |
#' @export |
1566 | 1570 |
#' @importFrom circlize colorRamp2 |
1567 | 1571 |
plot_stats_connectionSummary <- function(GRN, type = "heatmap", |
... | ... |
@@ -1888,8 +1892,9 @@ plot_stats_connectionSummary <- function(GRN, type = "heatmap", |
1888 | 1892 |
#' @seealso \code{\link{plotCommunitiesStats}} |
1889 | 1893 |
#' @seealso \code{\link{plotCommunitiesEnrichment}} |
1890 | 1894 |
#' @examples |
1891 |
-#' GRN = loadExampleObject() |
|
1892 |
-#' GRN = plotGeneralGraphStats(GRN, forceRerun = FALSE) |
|
1895 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
1896 |
+#' # GRN = loadExampleObject() |
|
1897 |
+#' # GRN = plotGeneralGraphStats(GRN, forceRerun = FALSE) |
|
1893 | 1898 |
#' @export |
1894 | 1899 |
plotGeneralGraphStats <- function(GRN, outputFolder = NULL, basenameOutput = NULL, |
1895 | 1900 |
plotAsPDF = TRUE, pdf_width = 12, pdf_height = 12, |
... | ... |
@@ -2052,8 +2057,9 @@ plotGeneralGraphStats <- function(GRN, outputFolder = NULL, basenameOutput = NUL |
2052 | 2057 |
#' @param display_pAdj Boolean. Default FALSE. Is the p-value being displayed in the plots the adjusted p-value? This parameter is relevant for KEGG, Disease Ontology, and Reactome enrichments, and does not affect GO enrichments. |
2053 | 2058 |
#' @return The same \code{\linkS4class{GRN}} object, without modifications. A single PDF file is produced with the results. |
2054 | 2059 |
#' @examples |
2055 |
-#' GRN = loadExampleObject() |
|
2056 |
-#' GRN = plotGeneralEnrichment(GRN, topn_pvalue = 30, forceRerun = FALSE) |
|
2060 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
2061 |
+#' # GRN = loadExampleObject() |
|
2062 |
+#' # GRN = plotGeneralEnrichment(GRN, topn_pvalue = 30, forceRerun = FALSE) |
|
2057 | 2063 |
#' @export |
2058 | 2064 |
plotGeneralEnrichment <- function(GRN, outputFolder = NULL, basenameOutput = NULL, |
2059 | 2065 |
ontology = NULL, topn_pvalue = 30, p = 0.05, |
... | ... |
@@ -2229,8 +2235,9 @@ plotGeneralEnrichment <- function(GRN, outputFolder = NULL, basenameOutput = NUL |
2229 | 2235 |
#' @seealso \code{\link{calculateCommunitiesStats}} |
2230 | 2236 |
#' @seealso \code{\link{calculateCommunitiesEnrichment}} |
2231 | 2237 |
#' @examples |
2232 |
-#' GRN = loadExampleObject() |
|
2233 |
-#' GRN = plotCommunitiesStats(GRN, display = byRank, forceRerun = FALSE) |
|
2238 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
2239 |
+#' # GRN = loadExampleObject() |
|
2240 |
+#' # GRN = plotCommunitiesStats(GRN, display = "byRank", forceRerun = FALSE) |
|
2234 | 2241 |
#' @export |
2235 | 2242 |
plotCommunitiesStats <- function(GRN, outputFolder = NULL, basenameOutput = NULL, |
2236 | 2243 |
display = "byRank", communities = seq_len(10), |
... | ... |
@@ -2397,8 +2404,9 @@ plotCommunitiesStats <- function(GRN, outputFolder = NULL, basenameOutput = NULL |
2397 | 2404 |
#' @param maxWidth_nchar_plot Integer (>=10). Default 100. Maximum number of characters for a term before it is truncated. |
2398 | 2405 |
#' @return The same \code{\linkS4class{GRN}} object, without modifications. A single PDF file is produced with the results. |
2399 | 2406 |
#' @examples |
2400 |
-#' GRN = loadExampleObject() |
|
2401 |
-#' GRN = plotCommunitiesEnrichment(GRN, forceRerun = FALSE) |
|
2407 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
2408 |
+#' # GRN = loadExampleObject() |
|
2409 |
+#' # GRN = plotCommunitiesEnrichment(GRN, forceRerun = FALSE) |
|
2402 | 2410 |
#' @export |
2403 | 2411 |
#' @import ggplot2 |
2404 | 2412 |
#' @importFrom grid gpar |
... | ... |
@@ -2697,8 +2705,9 @@ plotCommunitiesEnrichment <- function(GRN, outputFolder = NULL, basenameOutput = |
2697 | 2705 |
#' @return The same \code{\linkS4class{GRN}} object, without modifications. A single PDF file is produced with the results. |
2698 | 2706 |
#' @seealso \code{\link{calculateTFEnrichment}} |
2699 | 2707 |
#' @examples |
2700 |
-#' GRN = loadExampleObject() |
|
2701 |
-#' GRN = plotTFEnrichment(GRN, rankType = "degree", n = 5, forceReun = FALSE) |
|
2708 |
+#' # See the Workflow vignette on the GRaNIE website for examples |
|
2709 |
+#' # GRN = loadExampleObject() |
|
2710 |
+#' # GRN = plotTFEnrichment(GRN, rankType = "degree", n = 5, forceRerun = FALSE) |
|
2702 | 2711 |
#' @export |
2703 | 2712 |
#' @importFrom grid gpar |
2704 | 2713 |
plotTFEnrichment <- function(GRN, rankType = "degree", n = NULL, TF.names = NULL, |
... | ... |
@@ -39,6 +39,7 @@ The same \code{\linkS4class{GRN}} object, with added data from this function. T |
39 | 39 |
Run the activator-repressor classification for the TFs for a \code{\linkS4class{GRN}} object |
40 | 40 |
} |
41 | 41 |
\examples{ |
42 |
-GRN = loadExampleObject() |
|
43 |
-GRN = AR_classification_wrapper(GRN, forceRerun = FALSE) |
|
42 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
43 |
+# GRN = loadExampleObject() |
|
44 |
+# GRN = AR_classification_wrapper(GRN, forceRerun = FALSE) |
|
44 | 45 |
} |
... | ... |
@@ -30,7 +30,7 @@ addConnections_TF_peak( |
30 | 30 |
|
31 | 31 |
\item{corMethod}{Character. \code{pearson} or \code{spearman}. Default \code{pearson}. Method for calculating the correlation coefficient. See \link{cor} for details.} |
32 | 32 |
|
33 |
-\item{connectionTypes}{TODO describe} |
|
33 |
+\item{connectionTypes}{Character vector. Default \code{expression}. Vector of connection types to include for the TF-peak connections. If an additional connection type is specified here, it has to be available already within the object (EXPERIMENTAL). See the function \code{addData_TFActivity} for details.} |
|
34 | 34 |
|
35 | 35 |
\item{removeNegativeCorrelation}{\code{TRUE} or \code{FALSE} (vector). Default \code{FALSE}. EXPERIMENTAL. Must be a logical vector of the same length as the parameter \code{connectionType}. Should negatively correlated TF-peak connections be removed for the specific connection type? For connection type expression, the default is FALSE, while for any TF Activity related connection type, we recommend setting this to \code{TRUE}.} |
36 | 36 |
|
... | ... |
@@ -38,7 +38,7 @@ addConnections_TF_peak( |
38 | 38 |
|
39 | 39 |
\item{useGCCorrection}{\code{TRUE} or \code{FALSE}. Default \code{FALSE}. EXPERIMENTAL. Should a GC-matched background be used when calculating FDRs?} |
40 | 40 |
|
41 |
-\item{percBackground_size}{Numeric (0 to 100). Default 75. EXPERIMENTAL. Description will follow TODO. Only relevant if \code{useGCCorrection} is set to \code{TRUE}, ignored otherwise.} |
|
41 |
+\item{percBackground_size}{Numeric (0 to 100). Default 75. EXPERIMENTAL. Description will follow. Only relevant if \code{useGCCorrection} is set to \code{TRUE}, ignored otherwise.} |
|
42 | 42 |
|
43 | 43 |
\item{percBackground_resample}{\code{TRUE} or \code{FALSE}. Default \code{TRUE}. EXPERIMENTAL. Should resampling be enabled for those GC bins for which not enough background peaks are available?. Only relevant if \code{useGCCorrection} is set to \code{TRUE}, ignored otherwise.} |
44 | 44 |
|
... | ... |
@@ -51,6 +51,7 @@ The same \code{\linkS4class{GRN}} object, with added data from this function. T |
51 | 51 |
Add TF-peak connections to a \code{\linkS4class{GRN}} object |
52 | 52 |
} |
53 | 53 |
\examples{ |
54 |
-GRN = loadExampleObject() |
|
55 |
-GRN = addConnections_TF_peak(GRN, forceRerun = FALSE) |
|
54 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
55 |
+# GRN = loadExampleObject() |
|
56 |
+# GRN = addConnections_TF_peak(GRN, forceRerun = FALSE) |
|
56 | 57 |
} |
... | ... |
@@ -48,6 +48,7 @@ The same \code{\linkS4class{GRN}} object, with added data from this function in |
48 | 48 |
Add peak-gene connections to a \code{\linkS4class{GRN}} object |
49 | 49 |
} |
50 | 50 |
\examples{ |
51 |
-GRN = loadExampleObject() |
|
52 |
-GRN = addConnections_peak_gene(GRN, promoterRange = 10000, nCores = 2, forceRerun = FALSE) |
|
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) |
|
53 | 54 |
} |
... | ... |
@@ -45,11 +45,12 @@ The same \code{\linkS4class{GRN}} object, with added data from this function. |
45 | 45 |
Add data to a \code{\linkS4class{GRN}} object |
46 | 46 |
} |
47 | 47 |
\examples{ |
48 |
-library(tidyverse) |
|
49 |
-rna.df = read_tsv("https://www.embl.de/download/zaugg/GRaNIE/rna.tsv.gz") |
|
50 |
-peaks.df = read_tsv("https://www.embl.de/download/zaugg/GRaNIE/peaks.tsv.gz") |
|
51 |
-meta.df = read_tsv("https://www.embl.de/download/zaugg/GRaNIE/sampleMetadata.tsv.gz") |
|
52 |
-GRN = loadExampleObject() |
|
48 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
49 |
+# library(tidyverse) |
|
50 |
+# rna.df = read_tsv("https://www.embl.de/download/zaugg/GRaNIE/rna.tsv.gz") |
|
51 |
+# peaks.df = read_tsv("https://www.embl.de/download/zaugg/GRaNIE/peaks.tsv.gz") |
|
52 |
+# meta.df = read_tsv("https://www.embl.de/download/zaugg/GRaNIE/sampleMetadata.tsv.gz") |
|
53 |
+# GRN = loadExampleObject() |
|
53 | 54 |
# We omit sampleMetadata = meta.df here, lines becomes too long otherwise |
54 |
-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) |
|
55 | 56 |
} |
... | ... |
@@ -36,5 +36,5 @@ The same \code{\linkS4class{GRN}} object, with added data from this function. |
36 | 36 |
Add TFBS to a \code{\linkS4class{GRN}} object |
37 | 37 |
} |
38 | 38 |
\examples{ |
39 |
-# see workflow vignette for an example on how to add TFBS |
|
39 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
40 | 40 |
} |
... | ... |
@@ -30,6 +30,7 @@ The same \code{\linkS4class{GRN}} object, with added data from this function. |
30 | 30 |
Add TF-gene correlations to a \code{\linkS4class{GRN}} object. The information is currently stored in \code{GRN@connections$TF_genes.filtered}. Note that raw p-values are not adjusted. |
31 | 31 |
} |
32 | 32 |
\examples{ |
33 |
-GRN = loadExampleObject() |
|
34 |
-GRN = add_TF_gene_correlation(GRN, forceRerun = FALSE) |
|
33 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
34 |
+# GRN = loadExampleObject() |
|
35 |
+# GRN = add_TF_gene_correlation(GRN, forceRerun = FALSE) |
|
35 | 36 |
} |
... | ... |
@@ -23,6 +23,8 @@ build_eGRN_graph( |
23 | 23 |
\item{removeMultiple}{\code{TRUE} or \code{FALSE}. Default \code{FALSE}. Remove loops with the same start and end point? This can happen if multiple TF originate from the same gene, for example.} |
24 | 24 |
|
25 | 25 |
\item{directed}{\code{TRUE} or \code{FALSE}. Default \code{FALSE}. Should the network be directed?} |
26 |
+ |
|
27 |
+\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.} |
|
26 | 28 |
} |
27 | 29 |
\value{ |
28 | 30 |
The same \code{\linkS4class{GRN}} object. |
... | ... |
@@ -31,6 +33,7 @@ The same \code{\linkS4class{GRN}} object. |
31 | 33 |
Builds a graph out of a set of connections |
32 | 34 |
} |
33 | 35 |
\examples{ |
34 |
-GRN = loadExampleObject() |
|
35 |
-GRN = build_eGRN_graph(GRN, forceRerun = FALSE) |
|
36 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
37 |
+# GRN = loadExampleObject() |
|
38 |
+# GRN = build_eGRN_graph(GRN, forceRerun = FALSE) |
|
36 | 39 |
} |
... | ... |
@@ -42,8 +42,9 @@ The same \code{\linkS4class{GRN}} object, with the enrichment results stored in |
42 | 42 |
After the vertices of the filtered GRN are clustered into communities using \code{\link{calculateCommunitiesStats}}, this function will run a per-community enrichment analysis. |
43 | 43 |
} |
44 | 44 |
\examples{ |
45 |
-GRN = loadExampleObject() |
|
46 |
-GRN = calculateCommunitiesEnrichment(GRN, ontology = c("GO_BP"), forceRerun = FALSE) |
|
45 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
46 |
+# GRN = loadExampleObject() |
|
47 |
+# GRN = calculateCommunitiesEnrichment(GRN, ontology = c("GO_BP"), forceRerun = FALSE) |
|
47 | 48 |
} |
48 | 49 |
\seealso{ |
49 | 50 |
\code{\link{plotCommunitiesEnrichment}} |
... | ... |
@@ -22,6 +22,7 @@ The same \code{\linkS4class{GRN}} object, with a table that consists of the conn |
22 | 22 |
This function generates the TF-gene graph from the filtered GRN object, and clusters its vertices into communities using established community detection algorithms. |
23 | 23 |
} |
24 | 24 |
\examples{ |
25 |
-GRN = loadExampleObject() |
|
26 |
-GRN = calculateCommunitiesStats(GRN, forceRerun = FALSE) |
|
25 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
26 |
+# GRN = loadExampleObject() |
|
27 |
+# GRN = calculateCommunitiesStats(GRN, forceRerun = FALSE) |
|
27 | 28 |
} |
... | ... |
@@ -36,8 +36,9 @@ The same \code{\linkS4class{GRN}} object, with the enrichment results stored in |
36 | 36 |
This function runs an enrichment analysis for the genes in the filtered network. |
37 | 37 |
} |
38 | 38 |
\examples{ |
39 |
-GRN = loadExampleObject() |
|
40 |
-GRN = calculateGeneralEnrichment(GRN, ontology = "GO_BP", forceRerun = FALSE) |
|
39 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
40 |
+# GRN = loadExampleObject() |
|
41 |
+# GRN = calculateGeneralEnrichment(GRN, ontology = "GO_BP", forceRerun = FALSE) |
|
41 | 42 |
} |
42 | 43 |
\seealso{ |
43 | 44 |
\code{\link{plotGeneralEnrichment}} |
... | ... |
@@ -45,7 +45,8 @@ The same \code{\linkS4class{GRN}} object, with the enrichment results stored in |
45 | 45 |
This function calculates the GO enrichment per TF, i.e. for the set of genes a given TF is connected to in the filtered \code{\linkS4class{GRN}}. |
46 | 46 |
} |
47 | 47 |
\examples{ |
48 |
-GRN = loadExampleObject() |
|
49 |
-GRN = calculateTFEnrichment(GRN, rankType = "degree", n = 5, ontology = "GO_BP", forceRerun = FALSE) |
|
50 |
-GRN = calculateTFEnrichment(GRN, rankType = "EV", n = 5, ontology = "GO_BP", forceRerun = FALSE) |
|
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) |
|
51 | 52 |
} |
... | ... |
@@ -10,7 +10,7 @@ deleteIntermediateData(GRN) |
10 | 10 |
\item{GRN}{Object of class \code{\linkS4class{GRN}}} |
11 | 11 |
} |
12 | 12 |
\value{ |
13 |
-TODO |
|
13 |
+The same \code{\linkS4class{GRN}} object, with some slots being deleted (\code{GRN@data$TFs$classification} as well as \code{GRN@stats$connectionDetails.l}) |
|
14 | 14 |
} |
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 |
... | ... |
@@ -54,6 +54,7 @@ The same \code{\linkS4class{GRN}} object, with added data from this function. |
54 | 54 |
Filter data from a \code{\linkS4class{GRN}} object |
55 | 55 |
} |
56 | 56 |
\examples{ |
57 |
-GRN = loadExampleObject() |
|
58 |
-GRN = filterData(GRN, forceRerun = FALSE) |
|
57 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
58 |
+# GRN = loadExampleObject() |
|
59 |
+# GRN = filterData(GRN, forceRerun = FALSE) |
|
59 | 60 |
} |
... | ... |
@@ -79,8 +79,9 @@ This is one of the main integrative functions of the \code{GRN} package. It has |
79 | 79 |
Internally, first, the TF-peak are filtered before the peak-gene connections are added for reasons of memory and computational efficacy: It takes a lot of time and particularly space to connect the full GRN with all peak-gene connections - as most of the links have weak support (i.e., high FDR), first filtering out unwanted links dramatically reduces the memory needed for the combined GRN |
80 | 80 |
} |
81 | 81 |
\examples{ |
82 |
-GRN = loadExampleObject() |
|
83 |
-GRN = filterGRNAndConnectGenes(GRN) |
|
82 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
83 |
+# GRN = loadExampleObject() |
|
84 |
+# GRN = filterGRNAndConnectGenes(GRN) |
|
84 | 85 |
} |
85 | 86 |
\seealso{ |
86 | 87 |
\code{\link{visualizeGRN}} |
... | ... |
@@ -45,7 +45,8 @@ The same \code{\linkS4class{GRN}} object, with added data from this function. |
45 | 45 |
Essentially, this functions calls \code{filterGRNAndConnectGenes} repeatedly and stores the total number of connections and other statistics each time to summarize them afterwards. All arguments are identical to the ones in \code{filterGRNAndConnectGenes}, see the help for this function for details. |
46 | 46 |
} |
47 | 47 |
\examples{ |
48 |
-GRN = loadExampleObject() |
|
49 |
-GRN = generateStatsSummary(GRN, forceRerun = FALSE) |
|
48 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
49 |
+# GRN = loadExampleObject() |
|
50 |
+# GRN = generateStatsSummary(GRN, forceRerun = FALSE) |
|
50 | 51 |
|
51 | 52 |
} |
... | ... |
@@ -13,13 +13,14 @@ nGenes(GRN, filter = TRUE) |
13 | 13 |
\item{filter}{TRUE or FALSE. Default TRUE. Should genes marked as filtered be included in the count?} |
14 | 14 |
} |
15 | 15 |
\value{ |
16 |
-Integer. Number of genes hat 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} (see method TODO) |
|
16 |
+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}. |
|
17 | 17 |
} |
18 | 18 |
\description{ |
19 | 19 |
Return the number of genes (all or only non-filtered ones) that are defined in the \code{\linkS4class{GRN}} object. |
20 | 20 |
} |
21 | 21 |
\examples{ |
22 |
-GRN = loadExampleObject() |
|
23 |
-nGenes(GRN, filter = TRUE) |
|
24 |
-nGenes(GRN, filter = FALSE) |
|
22 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
23 |
+# GRN = loadExampleObject() |
|
24 |
+# nGenes(GRN, filter = TRUE) |
|
25 |
+# nGenes(GRN, filter = FALSE) |
|
25 | 26 |
} |
... | ... |
@@ -16,13 +16,14 @@ getCounts(GRN, type, norm, permuted = FALSE) |
16 | 16 |
\item{permuted}{\code{TRUE} or \code{FALSE}. Default \code{FALSE}. Should the permuted data be taken (\code{TRUE}) or the non-permuted, original one (\code{FALSE})?} |
17 | 17 |
} |
18 | 18 |
\value{ |
19 |
-Counts. TODO MORE |
|
19 |
+Data frame of counts, with the type as indicated by the function parameters. |
|
20 | 20 |
getCounts(GRN, type = "peaks", norm = TRUE) |
21 | 21 |
} |
22 | 22 |
\description{ |
23 | 23 |
Get counts for the various data defined in a \code{\linkS4class{GRN}} object. |
24 | 24 |
} |
25 | 25 |
\examples{ |
26 |
-GRN = loadExampleObject() |
|
27 |
-GRN = getCounts(GRN, type = "peaks", norm = TRUE, permuted = FALSE) |
|
26 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
27 |
+# GRN = loadExampleObject() |
|
28 |
+# GRN = getCounts(GRN, type = "peaks", norm = TRUE, permuted = FALSE) |
|
28 | 29 |
} |
... | ... |
@@ -27,6 +27,7 @@ A data frame with the connections. Importantly, this function does NOT return a |
27 | 27 |
Extract connections from a \code{\linkS4class{GRN}} object |
28 | 28 |
} |
29 | 29 |
\examples{ |
30 |
-GRN = loadExampleObject() |
|
31 |
-GRN_con.all = getGRNConnections(GRN, include_TF_gene_correlations = TRUE) |
|
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) |
|
32 | 33 |
} |
... | ... |
@@ -4,14 +4,14 @@ |
4 | 4 |
\alias{getParameters} |
5 | 5 |
\title{Retrieve parameters for previously used function calls and general parameters for a \code{\linkS4class{GRN}} object.} |
6 | 6 |
\usage{ |
7 |
-getParameters(GRN, type = "function", name = NULL) |
|
7 |
+getParameters(GRN, type = "parameter", name = "all") |
|
8 | 8 |
} |
9 | 9 |
\arguments{ |
10 | 10 |
\item{GRN}{Object of class \code{\linkS4class{GRN}}} |
11 | 11 |
|
12 |
-\item{type}{Character. Default \code{function}. Either \code{function}, \code{parameter}, or \code{all}. When set to \code{function}, a valid \code{GRaNIE} function name must be given that has been run before. \code{parameter} indicates a particular parameter name is returned (as specified in \code{GRN@config})), while \code{all} returns all parameters.} |
|
12 |
+\item{type}{Character. Default \code{parameter}. Either \code{function} or \code{parameter}. When set to \code{function}, a valid \code{GRaNIE} function name must be given that has been run before. When set to \code{parameter}, in combination with \code{name}, returns a specific parameter (as specified in \code{GRN@config})).} |
|
13 | 13 |
|
14 |
-\item{name}{Character. Name of parameter or function name to retrieve. Ignored if \code{type} == \code{all}.} |
|
14 |
+\item{name}{Character. Default \code{all}. Name of parameter or function name to retrieve. Set to the special keyword \code{all} to retrieve all parameters.} |
|
15 | 15 |
} |
16 | 16 |
\value{ |
17 | 17 |
The same \code{\linkS4class{GRN}} object, with added data from this function. |
... | ... |
@@ -20,7 +20,8 @@ The same \code{\linkS4class{GRN}} object, with added data from this function. |
20 | 20 |
Retrieve parameters for previously used function calls and general parameters for a \code{\linkS4class{GRN}} object. |
21 | 21 |
} |
22 | 22 |
\examples{ |
23 |
-GRN = loadExampleObject() |
|
24 |
-getParameters(GRN, type = "function") |
|
23 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
24 |
+# GRN = loadExampleObject() |
|
25 |
+# getParameters(GRN, type = "parameter", name = "all") |
|
25 | 26 |
|
26 | 27 |
} |
... | ... |
@@ -24,7 +24,8 @@ A dataframe with the node names and the corresponding scores used to rank them |
24 | 24 |
Retrieve top Nodes in the filtered \code{\linkS4class{GRN}} |
25 | 25 |
} |
26 | 26 |
\examples{ |
27 |
-GRN = loadExampleObject() |
|
28 |
-topGenes = getTopNodes(GRN, nodeType = "gene", rankType = "degree", n = 3) |
|
29 |
-topTFs = getTopNodes(GRN, nodeType = "TF", rankType = "EV", n = 5) |
|
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) |
|
30 | 31 |
} |
... | ... |
@@ -20,6 +20,7 @@ The same \code{\linkS4class{GRN}} object, with added data from this function. |
20 | 20 |
Overlap peaks and TFBS for a \code{\linkS4class{GRN}} object |
21 | 21 |
} |
22 | 22 |
\examples{ |
23 |
-GRN = loadExampleObject() |
|
24 |
-GRN = overlapPeaksAndTFBS(GRN, nCores = 2, forceRerun = FALSE) |
|
23 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
24 |
+# GRN = loadExampleObject() |
|
25 |
+# GRN = overlapPeaksAndTFBS(GRN, nCores = 2, forceRerun = FALSE) |
|
25 | 26 |
} |
... | ... |
@@ -13,13 +13,14 @@ nPeaks(GRN, filter = TRUE) |
13 | 13 |
\item{filter}{TRUE or FALSE. Default TRUE. Should peaks marked as filtered be included in the count?} |
14 | 14 |
} |
15 | 15 |
\value{ |
16 |
-Integer. Number of peaks hat 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} (see method TODO) |
|
16 |
+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}. |
|
17 | 17 |
} |
18 | 18 |
\description{ |
19 | 19 |
Return the number of peaks (all or only non-filtered ones) that are defined in the \code{\linkS4class{GRN}} object. |
20 | 20 |
} |
21 | 21 |
\examples{ |
22 |
-GRN = loadExampleObject() |
|
23 |
-nPeaks(GRN, filter = TRUE) |
|
24 |
-nPeaks(GRN, filter = FALSE) |
|
22 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
23 |
+# GRN = loadExampleObject() |
|
24 |
+# nPeaks(GRN, filter = TRUE) |
|
25 |
+# nPeaks(GRN, filter = FALSE) |
|
25 | 26 |
} |
... | ... |
@@ -54,6 +54,7 @@ The same \code{\linkS4class{GRN}} object, with added data from this function. |
54 | 54 |
A convenience function that calls all network-related functions in one-go, using selected default parameters and a set of adjustable ones also. For full adjustment, run the individual functions separately. |
55 | 55 |
} |
56 | 56 |
\examples{ |
57 |
-GRN = loadExampleObject() |
|
58 |
-GRN = performAllNetworkAnalyses(GRN, forceRerun = FALSE) |
|
57 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
58 |
+# GRN = loadExampleObject() |
|
59 |
+# GRN = performAllNetworkAnalyses(GRN, forceRerun = FALSE) |
|
59 | 60 |
} |
... | ... |
@@ -60,6 +60,7 @@ The same \code{\linkS4class{GRN}} object, without modifications. A single PDF fi |
60 | 60 |
Similarly to \code{\link{plotGeneralEnrichment}}, the results of the community-based enrichment analysis are plotted.. By default, the results for the 10 largest communities are displayed. Additionally, if a general enrichment analysis was previously generated, this function plots an additional heatmap to compare the general enrichment with the community based enrichment. A reduced version of this heatmap is also produced where terms are filtered out to improve visibility and display and highlight the most significant terms. |
61 | 61 |
} |
62 | 62 |
\examples{ |
63 |
-GRN = loadExampleObject() |
|
64 |
-GRN = plotCommunitiesEnrichment(GRN, forceRerun = FALSE) |
|
63 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
64 |
+# GRN = loadExampleObject() |
|
65 |
+# GRN = plotCommunitiesEnrichment(GRN, forceRerun = FALSE) |
|
65 | 66 |
} |
... | ... |
@@ -48,8 +48,9 @@ The same \code{\linkS4class{GRN}} object, without modifications. A single PDF fi |
48 | 48 |
Similarly to the statistics produced by \code{\link{plotGeneralGraphStats}}, summaries regarding the vertex degrees and the most important vertices per community are generated. Note that the communities need to first be calculated using the \code{\link{calculateCommunitiesStats}} function |
49 | 49 |
} |
50 | 50 |
\examples{ |
51 |
-GRN = loadExampleObject() |
|
52 |
-GRN = plotCommunitiesStats(GRN, display = byRank, forceRerun = FALSE) |
|
51 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
52 |
+# GRN = loadExampleObject() |
|
53 |
+# GRN = plotCommunitiesStats(GRN, display = "byRank", forceRerun = FALSE) |
|
53 | 54 |
} |
54 | 55 |
\seealso{ |
55 | 56 |
\code{\link{plotGeneralGraphStats}} |
... | ... |
@@ -30,6 +30,7 @@ The same \code{\linkS4class{GRN}} object, with added data from this function. |
30 | 30 |
Plot diagnostic plots for TF-peak connections for a \code{\linkS4class{GRN}} object |
31 | 31 |
} |
32 | 32 |
\examples{ |
33 |
-GRN = loadExampleObject() |
|
34 |
-GRN = plotDiagnosticPlots_TFPeaks(GRN, forceRerun = FALSE) |
|
33 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
34 |
+# GRN = loadExampleObject() |
|
35 |
+# GRN = plotDiagnosticPlots_TFPeaks(GRN, forceRerun = FALSE) |
|
35 | 36 |
} |
... | ... |
@@ -48,6 +48,7 @@ The same \code{\linkS4class{GRN}} object, with added data from this function. |
48 | 48 |
Plot diagnostic plots for peak-gene connections for a \code{\linkS4class{GRN}} object |
49 | 49 |
} |
50 | 50 |
\examples{ |
51 |
-GRN = loadExampleObject() |
|
52 |
-GRN = plotDiagnosticPlots_peakGene(GRN, forceRerun = FALSE) |
|
51 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
52 |
+# GRN = loadExampleObject() |
|
53 |
+# GRN = plotDiagnosticPlots_peakGene(GRN, forceRerun = FALSE) |
|
53 | 54 |
} |
... | ... |
@@ -48,6 +48,7 @@ The same \code{\linkS4class{GRN}} object, without modifications. A single PDF fi |
48 | 48 |
This function plots the results of the general enrichment analysis for every specified ontology. |
49 | 49 |
} |
50 | 50 |
\examples{ |
51 |
-GRN = loadExampleObject() |
|
52 |
-GRN = plotGeneralEnrichment(GRN, topn_pvalue = 30, forceRerun = FALSE) |
|
51 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
52 |
+# GRN = loadExampleObject() |
|
53 |
+# GRN = plotGeneralEnrichment(GRN, topn_pvalue = 30, forceRerun = FALSE) |
|
53 | 54 |
} |
... | ... |
@@ -36,8 +36,9 @@ The same \code{\linkS4class{GRN}} object with no changes. The results are output |
36 | 36 |
This function generates graphical summaries about the structure and connectivity of the TF-peak-gene and TF-gene graphs. These include, distribution of vertex types (TF, peak, gene) and edge types (tf-peak, peak-gene), the distribution of vertex degrees, and the most "important" vertices according to degree centrality and eigenvector centrality scores. |
37 | 37 |
} |
38 | 38 |
\examples{ |
39 |
-GRN = loadExampleObject() |
|
40 |
-GRN = plotGeneralGraphStats(GRN, forceRerun = FALSE) |
|
39 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
40 |
+# GRN = loadExampleObject() |
|
41 |
+# GRN = plotGeneralGraphStats(GRN, forceRerun = FALSE) |
|
41 | 42 |
} |
42 | 43 |
\seealso{ |
43 | 44 |
\code{\link{plotGeneralEnrichment}} |
... | ... |
@@ -42,6 +42,7 @@ The same \code{\linkS4class{GRN}} object, without modifications. In addition, fo |
42 | 42 |
Produce a PCA plot of the data from a \code{\linkS4class{GRN}} object |
43 | 43 |
} |
44 | 44 |
\examples{ |
45 |
-GRN = loadExampleObject() |
|
46 |
-GRN = plotPCA_all(GRN, type = c("rna", "peaks"), topn = 500, forceRerun = FALSE) |
|
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) |
|
47 | 48 |
} |
... | ... |
@@ -63,8 +63,9 @@ The same \code{\linkS4class{GRN}} object, without modifications. A single PDF fi |
63 | 63 |
This function plots the enrichment results. The result consist of a dot plot per specified TF, as well as two comparative heatmaps. The first heatmap displays the p value for each GO term across the TFs. Terms that The second heatmap is a subset of the first, where select terms are kept or filtered out for better visibility and display. |
64 | 64 |
} |
65 | 65 |
\examples{ |
66 |
-GRN = loadExampleObject() |
|
67 |
-GRN = plotTFEnrichment(GRN, rankType = "degree", n = 5, forceReun = FALSE) |
|
66 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
67 |
+# GRN = loadExampleObject() |
|
68 |
+# GRN = plotTFEnrichment(GRN, rankType = "degree", n = 5, forceRerun = FALSE) |
|
68 | 69 |
} |
69 | 70 |
\seealso{ |
70 | 71 |
\code{\link{calculateTFEnrichment}} |
... | ... |
@@ -39,6 +39,7 @@ The same \code{\linkS4class{GRN}} object, without modifications. In addition, fo |
39 | 39 |
Plot various network connectivity summaries for a \code{\linkS4class{GRN}} object |
40 | 40 |
} |
41 | 41 |
\examples{ |
42 |
-GRN = loadExampleObject() |
|
43 |
-GRN = plot_stats_connectionSummary(GRN, type = "heatmap", forceRerun = FALSE) |
|
42 |
+# See the Workflow vignette on the GRaNIE website for examples |
|
43 |
+# GRN = loadExampleObject() |
|
44 |
+# GRN = plot_stats_connectionSummary(GRN, type = "heatmap", forceRerun = FALSE) |
|
44 | 45 |
} |