... | ... |
@@ -1,6 +1,6 @@ |
1 | 1 |
Package: fenr |
2 | 2 |
Title: Fast functional enrichment for interactive applications |
3 |
-Version: 1.1.2 |
|
3 |
+Version: 1.1.3 |
|
4 | 4 |
Authors@R: person( |
5 | 5 |
given = "Marek", |
6 | 6 |
family = "Gierlinski", |
... | ... |
@@ -12,9 +12,10 @@ Description: Perform fast functional enrichment on feature lists (like genes |
12 | 12 |
or proteins) using the hypergeometric distribution. Tailored for speed, |
13 | 13 |
this package is ideal for interactive platforms such as Shiny. It supports |
14 | 14 |
the retrieval of functional data from sources like GO, KEGG, Reactome, |
15 |
- and WikiPathways. By downloading and preparing data first, it allows for |
|
16 |
- rapid successive tests on various feature selections without the need |
|
17 |
- for repetitive, time-consuming preparatory steps typical of other packages. |
|
15 |
+ Bioplanet and WikiPathways. By downloading and preparing data first, it |
|
16 |
+ allows for rapid successive tests on various feature selections without |
|
17 |
+ the need for repetitive, time-consuming preparatory steps typical of other |
|
18 |
+ packages. |
|
18 | 19 |
URL: https://github.com/bartongroup/fenr |
19 | 20 |
BugReports: https://github.com/bartongroup/fenr/issues |
20 | 21 |
Depends: R (>= 4.3.0) |
132 | 137 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,48 @@ |
1 |
+#' URL of Bioplanet pathway file |
|
2 |
+#' |
|
3 |
+#' @return A string with URL. |
|
4 |
+#' @noRd |
|
5 |
+get_bioplanet_pathway_file <- function() { |
|
6 |
+ getOption("BIOPLANET_PATHWAY_FILE", "https://tripod.nih.gov/bioplanet/download/pathway.csv") |
|
7 |
+} |
|
8 |
+ |
|
9 |
+#' Get functional term data from BioPlanet |
|
10 |
+#' |
|
11 |
+#' Download term information (term ID and name) and gene-pathway mapping |
|
12 |
+#' (NCBI gene ID, gene symbol and pathway ID) from BioPlanet. |
|
13 |
+#' |
|
14 |
+#' @param use_cache Logical, if TRUE, the remote file will be cached locally. |
|
15 |
+#' @param on_error A character vector specifying the error handling method. It |
|
16 |
+#' can take values `"stop"` or `"warn"`. The default is `"stop"`. `"stop"` |
|
17 |
+#' will halt the function execution and throw an error, while `"warn"` will |
|
18 |
+#' issue a warning and return `NULL`. |
|
19 |
+#' @return A list with \code{terms} and \code{mapping} tibbles. |
|
20 |
+#' @export |
|
21 |
+#' @examples |
|
22 |
+#' bioplanet_data <- fetch_bp(on_error = "warn") |
|
23 |
+fetch_bp <- function(use_cache = TRUE, on_error = c("stop", "warn")) { |
|
24 |
+ on_error <- match.arg(on_error) |
|
25 |
+ |
|
26 |
+ # Binding variables from non-standard evaluation locally |
|
27 |
+ PATHWAY_ID <- PATHWAY_NAME <- GENE_ID <- GENE_SYMBOL <- NULL |
|
28 |
+ |
|
29 |
+ pathway_file <- get_bioplanet_pathway_file() |
|
30 |
+ if(!assert_url_path(pathway_file, on_error)) |
|
31 |
+ return(NULL) |
|
32 |
+ |
|
33 |
+ lpath <- cached_url_path("bioplanet_pathway", pathway_file, use_cache) |
|
34 |
+ paths <- readr::read_csv(lpath, show_col_types = FALSE) |
|
35 |
+ |
|
36 |
+ terms <- paths |> |
|
37 |
+ dplyr::select(term_id = PATHWAY_ID, term_name = PATHWAY_NAME) |> |
|
38 |
+ dplyr::distinct() |
|
39 |
+ |
|
40 |
+ mapping <- paths |> |
|
41 |
+ dplyr::select(term_id = PATHWAY_ID, ncbi_id = GENE_ID, gene_symbol = GENE_SYMBOL) |> |
|
42 |
+ dplyr::distinct() |
|
43 |
+ |
|
44 |
+ list( |
|
45 |
+ terms = terms, |
|
46 |
+ mapping = mapping |
|
47 |
+ ) |
|
48 |
+} |
... | ... |
@@ -20,6 +20,8 @@ get_kegg_url <- function() { |
20 | 20 |
#' @examples |
21 | 21 |
#' spe <- fetch_kegg_species(on_error = "warn") |
22 | 22 |
fetch_kegg_species <- function(on_error = c("stop", "warn")) { |
23 |
+ on_error <- match.arg(on_error) |
|
24 |
+ |
|
23 | 25 |
qry <- api_query(get_kegg_url(), "list/organism") |
24 | 26 |
if(qry$is_error) |
25 | 27 |
return(catch_error("KEGG", qry$response, on_error)) |
... | ... |
@@ -176,6 +178,8 @@ fetch_kegg_mapping <- function(pathways, batch_size, on_error = "stop") { |
176 | 178 |
#' @examples |
177 | 179 |
#' kegg_data <- fetch_kegg("mge", on_error = "warn") |
178 | 180 |
fetch_kegg <- function(species, batch_size = 10, on_error = c("stop", "warn")) { |
181 |
+ on_error <- match.arg(on_error) |
|
182 |
+ |
|
179 | 183 |
assert_that(!missing(species), msg = "Argument 'species' is missing.") |
180 | 184 |
assert_that(is.count(batch_size)) |
181 | 185 |
assert_that(batch_size <= 10, msg = "batch_size needs to be between 1 and 10") |
... | ... |
@@ -33,6 +33,8 @@ get_reactome_gaf_file <- function() { |
33 | 33 |
#' @examples |
34 | 34 |
#' re <- fetch_reactome_species(on_error = "warn") |
35 | 35 |
fetch_reactome_species <- function(on_error = c("stop", "warn")) { |
36 |
+ on_error <- match.arg(on_error) |
|
37 |
+ |
|
36 | 38 |
# Binding variables from non-standard evaluation locally |
37 | 39 |
dbId <- displayName <- taxId <- NULL |
38 | 40 |
|
39 | 41 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,26 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/bioplanet.R |
|
3 |
+\name{fetch_bp} |
|
4 |
+\alias{fetch_bp} |
|
5 |
+\title{Get functional term data from BioPlanet} |
|
6 |
+\usage{ |
|
7 |
+fetch_bp(use_cache = TRUE, on_error = c("stop", "warn")) |
|
8 |
+} |
|
9 |
+\arguments{ |
|
10 |
+\item{use_cache}{Logical, if TRUE, the remote file will be cached locally.} |
|
11 |
+ |
|
12 |
+\item{on_error}{A character vector specifying the error handling method. It |
|
13 |
+can take values `"stop"` or `"warn"`. The default is `"stop"`. `"stop"` |
|
14 |
+will halt the function execution and throw an error, while `"warn"` will |
|
15 |
+issue a warning and return `NULL`.} |
|
16 |
+} |
|
17 |
+\value{ |
|
18 |
+A list with \code{terms} and \code{mapping} tibbles. |
|
19 |
+} |
|
20 |
+\description{ |
|
21 |
+Download term information (term ID and name) and gene-pathway mapping |
|
22 |
+(NCBI gene ID, gene symbol and pathway ID) from BioPlanet. |
|
23 |
+} |
|
24 |
+\examples{ |
|
25 |
+bioplanet_data <- fetch_bp(on_error = "warn") |
|
26 |
+} |
0 | 27 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,31 @@ |
1 |
+expected_mapping <- tibble::tribble( |
|
2 |
+ ~term_id, ~gene_symbol, |
|
3 |
+ "bioplanet_1025", "CDK1", |
|
4 |
+ "bioplanet_120", "IL1A", |
|
5 |
+ "bioplanet_1755", "RPL6", |
|
6 |
+ "bioplanet_1121", "POLR1A" |
|
7 |
+) |
|
8 |
+ |
|
9 |
+test_that("Bioplanet mapping makes sense", { |
|
10 |
+ bp <- fetch_bp(on_error = "warn") |
|
11 |
+ if(!is.null(bp)) { |
|
12 |
+ expect_is(bp, "list") |
|
13 |
+ expect_setequal(names(bp), c("terms", "mapping")) |
|
14 |
+ mapping <- bp$mapping |
|
15 |
+ |
|
16 |
+ merged <- expected_mapping |> |
|
17 |
+ dplyr::left_join(mapping, by = c("term_id", "gene_symbol")) |> |
|
18 |
+ tidyr::drop_na() |
|
19 |
+ |
|
20 |
+ expect_equal(nrow(expected_mapping), nrow(merged)) |
|
21 |
+ } |
|
22 |
+}) |
|
23 |
+ |
|
24 |
+ |
|
25 |
+test_that("Expected behaviour from a non-responsive server", { |
|
26 |
+ httr2::with_mocked_responses( |
|
27 |
+ mock = mocked_500, |
|
28 |
+ code = { |
|
29 |
+ test_unresponsive_server(fetch_bp, use_cache = FALSE) |
|
30 |
+ }) |
|
31 |
+}) |