diff --git a/DESCRIPTION b/DESCRIPTION index f45b65f..f591170 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,7 +1,7 @@ Package: AnnotationGx Title: AnnotationGx: A package for building, updating and querying an annotation database for pharmaco-genomic data -Version: 0.0.0.9076 +Version: 0.0.0.9080 Authors@R: c( person("Jermiah", "Joseph", role = c("aut", "cre"), email = "jermiah.joseph@gmail.com"), diff --git a/NAMESPACE b/NAMESPACE index e87eb41..7f45ab5 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -3,13 +3,18 @@ export(annotatePubchemCompound) export(getChemblMechanism) export(getChemblResourceFields) +export(getOncotreeMainTypes) +export(getOncotreeTumorTypes) +export(getOncotreeVersions) export(getPubchemAnnotationHeadings) export(getPubchemCompound) export(getPubchemProperties) export(getPubchemStatus) +export(getUnichemSources) export(mapCID2Properties) export(mapCell2Accession) export(mapCompound2CID) +export(queryUnichem) export(standardize_names) import(BiocParallel) import(data.table) diff --git a/R/GuideToPharm.R b/R/GuideToPharm.R new file mode 100644 index 0000000..40ee1b9 --- /dev/null +++ b/R/GuideToPharm.R @@ -0,0 +1,48 @@ +#' Get data from the Guide to PHARMACOLOGY Database Web Services +#' +#' @param ids `character()` or `integer()` Identifiers to query the web +#' service with. If excluded, the entire record for the specified service +#' is returned. +#' @param service `character(1)` Which Guide to PHARMACOLOGY web service +#' to query. Defaults to 'ligands'. Other options are 'targets', 'interactions', +#' 'diseases' and 'references'. +#' @param id_type `character(1)` What type of identifiers are in `ids`? Defaults +#' to 'name', for drug name. Other options are 'accession', which accepts +#' PubChem CIDs. +#' @param ... Force subsequent parameters to be named. Not used. +#' +#' @return A `data.table` of query results. +#' +#' @details +#' The API reference documentation can be found here: +#' https://www.guidetopharmacology.org/webServices.jsp +#' +#' There is also a Python interface available for querying this API. See: +#' https://github.com/samirelanduk/pygtop +#' +#' @importFrom data.table data.table as.data.table rbindlist setnames +#' @importFrom jsonlite fromJSON +#' @importFrom httr RETRY GET status_code +#' +#' @export +# getGuideToPharm <- function( +# ids = character(), +# service = c("ligands", "targets", "interactions", "diseases", "references"), +# id_type = c("name", "accession"), +# ..., +# ){ + + +# checkmate::assert_atomic(ids, any.missing = FALSE, min.len = 1) +# checkmate::assert_character(service, len = 1) +# checkmate::assert_character(id_type, len = 1) + +# url <- httr2::url_parse("https://www.guidetopharmacology.org/services") +# url$path <- .buildURL(url$path, service) + +# opts <- list() + +# opts[id_type] <- paste0(ids, collapse = ",") + +# } + diff --git a/R/oncotree.R b/R/oncotree.R new file mode 100644 index 0000000..2153184 --- /dev/null +++ b/R/oncotree.R @@ -0,0 +1,59 @@ + +#' Get data from Oncotree API +#' +#' This function retrieves data from the Oncotree API based on the specified target. +#' +#' @param target A character vector specifying the target data to retrieve. +#' Valid options are "versions", "mainTypes", and "tumorTypes". +#' +#' @return A data table containing the retrieved data. +#' +#' @noRd +#' @keywords internal +.getRequestOncotree <- function( + target = c("versions", "mainTypes", "tumorTypes") +) { + + url <- "http://oncotree.mskcc.org" + targetClean <- match.arg(target) + .buildURL(url, "api", targetClean) |> + .build_request() |> + .perform_request() |> + .parse_resp_json() |> + .asDT() +} +#' Get available Oncotree versions +#' +#' This function retrieves the available versions of Oncotree. +#' +#' @return A `data.table` containing available Oncotree versions. +#' +#' @export +getOncotreeVersions <- function() { + .getRequestOncotree(target="versions") +} + +#' Get the main types from the Oncotree database. +#' +#' This function retrieves the main types from the Oncotree database. +#' +#' @return A `data.table` containing the main types from the Oncotree database. +#' +#' @export +getOncotreeMainTypes <- function() { + res <- .getRequestOncotree(target="mainTypes") + setnames(res, "mainType") + return(res) +} + + +#' Get the tumor types from the Oncotree database. +#' +#' This function retrieves the tumor types from the Oncotree database. +#' +#' @return A `data.table` containing the tumor types from the Oncotree database. +#' +#' @export +getOncotreeTumorTypes <- function() { + .getRequestOncotree(target="tumorTypes") +} diff --git a/R/pubchem_view.R b/R/pubchem_view.R index b6881f5..4f5a969 100644 --- a/R/pubchem_view.R +++ b/R/pubchem_view.R @@ -113,5 +113,11 @@ annotatePubchemCompound <- function( ) }) - parsed_responses |> unlist() + sapply(parsed_responses, .replace_null) + } + +# helper function to replace NULL with NA +.replace_null <- function(x) { + ifelse(is.null(x), NA_character_, x) +} \ No newline at end of file diff --git a/R/unichem.R b/R/unichem.R new file mode 100644 index 0000000..82e64a6 --- /dev/null +++ b/R/unichem.R @@ -0,0 +1,126 @@ + +# Unichem API documentation: https://www.ebi.ac.uk/unichem/info/webservices + + +#' Get the list of sources in UniChem. +#' +#' Returns a `data.table` with the following columns: +#' - `CompoundCount` (integer): Total of compounds provided by that source +#' - `BaseURL` (string): Source Base URL for compounds +#' - `Description` (string): Source database description +#' - `LastUpdated` (string): Date in which the source database was last updated +#' - `Name` (string): Short name of the source database +#' - `NameLabel` (string): Machine readable label name of the source database +#' - `NameLong` (string): Full name of the source database +#' - `SourceID` (integer): Unique ID for the source database +#' - `Details` (string): Notes about the source +#' - `ReleaseDate` (string): Date in which the source database was released +#' - `ReleaseNumber` (integer): Release number of the source database data stored in UniChEM +#' - `URL` (string): Main URL for the source +#' - `UpdateComments` (string): Notes about the update process of that source to UniChEM +#' +#' +#' @return A data.table with the list of sources in UniChem. +#' +#' @export +getUnichemSources <- function() { + funContext <- .funContext("AnnotationGx::getUnichemSources") + + response <- .build_unichem_query("sources") |> + .build_request() |> + .perform_request() |> + .parse_resp_json() + + if(response$response != "Success"){ + .err(funContext, "Unichem API request failed.") + } + + .debug(funContext, sprintf("Unichem sourceCount: %s", response$totalSources)) + + sources_dt <- .asDT(response$sources) + + old_names <- c( + "UCICount", "baseIdUrl", "description", "lastUpdated", "name", + "nameLabel", "nameLong", "sourceID", "srcDetails", "srcReleaseDate", + "srcReleaseNumber", "srcUrl", "updateComments") + + new_names <- c( + "CompoundCount", "BaseURL", "Description", "LastUpdated", "Name", + "NameLabel", "NameLong", "SourceID", "Details", "ReleaseDate", + "ReleaseNumber", "URL", "UpdateComments") + + setnames(sources_dt, old_names, new_names) + + new_order <- c( + "Name", "NameLabel", "NameLong", "SourceID", "CompoundCount", + "BaseURL", "URL", "Details", + "Description", "ReleaseNumber", "ReleaseDate", "LastUpdated", + "UpdateComments" + ) + + sources_dt[, ..new_order] + +} + +#' Query UniChem for a compound. +#' +#' This function queries the UniChem API for a compound based on the provided parameters. +#' +#' @param type `character` The type of compound identifier to search for. Valid types are "uci", "inchi", "inchikey", and "sourceID". +#' @param compound `character` or `integer` The compound identifier to search for. +#' @param sourceID `integer` The source ID to search for if the type is "sourceID". Defaults to NULL. +#' @param request_only `boolean` Whether to return the request only. Defaults to FALSE. +#' @param raw `boolean` Whether to return the raw response. Defaults to FALSE. +#' @param ... Additional arguments. +#' +#' @return A list with the external mappings and the UniChem mappings. +#' +#' @examples +#' queryUnichem(type = "sourceID", compound = "444795", sourceID = 22) +#' +#' @export +queryUnichem <- function( + type, compound, sourceID = NA_integer_, request_only = FALSE, raw = FALSE, ... +){ + checkmate::assert_string(type) + checkmate::assert_atomic(compound) + checkmate::assert_integerish(sourceID) + checkmate::assertLogical(request_only) + checkmate::assertLogical(raw) + + request <- .build_unichem_compound_req(type, compound, sourceID,...) + if(request_only) return(request) + + response <- request |> + .perform_request() |> + .parse_resp_json() + + if(raw) return(response) + + if(response$response != "Success"){ + .err("Unichem API request failed.") + } + + # Mapping names to be consistent with other API calls + mapped_sources_dt <- .asDT(response$compounds$sources) + old_names <- c("compoundId", "shortName", "longName", "id", "url") + new_names <- c("compoundID", "Name", "NameLong", "sourceID", "sourcURL") + setnames(mapped_sources_dt, old = old_names, new = new_names) + + External_Mappings <- mapped_sources_dt[, ..new_names] + + UniChem_Mappings <- list( + UniChem.UCI = response$compounds$uci, + UniChem.InchiKey = response$compounds$standardInchiKey, + UniChem.Inchi = response$compounds$inchi$inchi, + UniChem.formula = response$compounds$inchi$formula, + UniChem.connections = response$compounds$inchi$connections, + UniChem.hAtoms = response$compounds$inchi$hAtoms + ) + + list( + External_Mappings = External_Mappings, + UniChem_Mappings = UniChem_Mappings + ) + +} \ No newline at end of file diff --git a/R/unichem_helpers.R b/R/unichem_helpers.R new file mode 100644 index 0000000..a27398f --- /dev/null +++ b/R/unichem_helpers.R @@ -0,0 +1,87 @@ +#' Build a UniChem query URL +#' +#' This function builds a UniChem query URL based on the specified endpoint. +#' +#' @param endpoint The UniChem endpoint to query (valid options: "compounds", "connectivity", "images", "sources") +#' @param query_only Logical indicating whether to return only the query URL without building it (default: FALSE) +#' +#' @return `httr2::httr2_url` object if `query_only` is TRUE, otherwise the built URL. +#' +#' @examples +#' .build_unichem_query("sources") +#' .build_unichem_query("connectivity", query_only = TRUE) +#' +#' @noRd +#' @keywords internal +.build_unichem_query <- function( + endpoint, query_only = FALSE +) { + funContext <- .funContext("AnnotationGx:::.build_unichem_query") + + valid_endpoints <- c("compounds", "connectivity", "images", "sources") + checkmate::assert_subset(endpoint, valid_endpoints) + + unichem_api <- "https://www.ebi.ac.uk/unichem/api/v1" + url <- httr2::url_parse(unichem_api) + url$path <- .buildURL(url$path, endpoint) + + .debug(funContext, "URL: ", capture.output(show(url))) + + if (query_only) return(url) + + return(httr2::url_build(url)) +} + + +#' Build a UniChem compound request +#' +#' This function builds a UniChem compound request based on the provided parameters. +#' +#' @param type The type of compound identifier to search for. Valid types are "uci", "inchi", "inchikey", and "sourceID". +#' @param compound The compound identifier to search for. +#' @param sourceID The source ID to search for if the type is "sourceID". Defaults to NULL. +#' @param ... Additional arguments. +#' +#' @return A `httr2_request` request object for the UniChem compound query. +#' +#' @examples +#' .build_unichem_compound_req(type = "uci", compound = "538323") +#' .build_unichem_compound_req(type = "sourceID", sourceID = 22, compound = "2244") +#' +#' @noRd +#' @keywords internal +.build_unichem_compound_req <- function( + type, compound, sourceID = NULL, ... +){ + funContext <- .funContext("AnnotationGx:::.build_unichem_compound_req") + + valid_types <- c("uci", "inchi", "inchikey", "sourceID") + checkmate::assert_subset(type, valid_types) + + base_url <- .build_unichem_query("compounds") + + .debug(funContext, "Base URL: ", capture.output(show(base_url))) + + body <- list( + type = type, + compound = compound + ) + + body$sourceID <- if (type == "sourceID") { + checkmate::assert_integerish( + x = sourceID, + lower = 1, + upper = max(getUnichemSources()$SourceID), + len = 1 + ) + sourceID + } else NULL + + + request <- base_url |> + .build_request() |> + httr2::req_body_json(body) + + .debug(funContext, "Request: ", capture.output(show(request))) + return(request) +} diff --git a/man/getOncotreeMainTypes.Rd b/man/getOncotreeMainTypes.Rd new file mode 100644 index 0000000..dd26dab --- /dev/null +++ b/man/getOncotreeMainTypes.Rd @@ -0,0 +1,14 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/oncotree.R +\name{getOncotreeMainTypes} +\alias{getOncotreeMainTypes} +\title{Get the main types from the Oncotree database.} +\usage{ +getOncotreeMainTypes() +} +\value{ +A \code{data.table} containing the main types from the Oncotree database. +} +\description{ +This function retrieves the main types from the Oncotree database. +} diff --git a/man/getOncotreeTumorTypes.Rd b/man/getOncotreeTumorTypes.Rd new file mode 100644 index 0000000..593109f --- /dev/null +++ b/man/getOncotreeTumorTypes.Rd @@ -0,0 +1,14 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/oncotree.R +\name{getOncotreeTumorTypes} +\alias{getOncotreeTumorTypes} +\title{Get the tumor types from the Oncotree database.} +\usage{ +getOncotreeTumorTypes() +} +\value{ +A \code{data.table} containing the tumor types from the Oncotree database. +} +\description{ +This function retrieves the tumor types from the Oncotree database. +} diff --git a/man/getOncotreeVersions.Rd b/man/getOncotreeVersions.Rd new file mode 100644 index 0000000..5dfcf5d --- /dev/null +++ b/man/getOncotreeVersions.Rd @@ -0,0 +1,14 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/oncotree.R +\name{getOncotreeVersions} +\alias{getOncotreeVersions} +\title{Get available Oncotree versions} +\usage{ +getOncotreeVersions() +} +\value{ +A \code{data.table} containing available Oncotree versions. +} +\description{ +This function retrieves the available versions of Oncotree. +} diff --git a/man/getUnichemSources.Rd b/man/getUnichemSources.Rd new file mode 100644 index 0000000..6822f0e --- /dev/null +++ b/man/getUnichemSources.Rd @@ -0,0 +1,29 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/unichem.R +\name{getUnichemSources} +\alias{getUnichemSources} +\title{Get the list of sources in UniChem.} +\usage{ +getUnichemSources() +} +\value{ +A data.table with the list of sources in UniChem. +} +\description{ +Returns a \code{data.table} with the following columns: +\itemize{ +\item \code{CompoundCount} (integer): Total of compounds provided by that source +\item \code{BaseURL} (string): Source Base URL for compounds +\item \code{Description} (string): Source database description +\item \code{LastUpdated} (string): Date in which the source database was last updated +\item \code{Name} (string): Short name of the source database +\item \code{NameLabel} (string): Machine readable label name of the source database +\item \code{NameLong} (string): Full name of the source database +\item \code{SourceID} (integer): Unique ID for the source database +\item \code{Details} (string): Notes about the source +\item \code{ReleaseDate} (string): Date in which the source database was released +\item \code{ReleaseNumber} (integer): Release number of the source database data stored in UniChEM +\item \code{URL} (string): Main URL for the source +\item \code{UpdateComments} (string): Notes about the update process of that source to UniChEM +} +} diff --git a/man/queryUnichem.Rd b/man/queryUnichem.Rd new file mode 100644 index 0000000..2e7b1e9 --- /dev/null +++ b/man/queryUnichem.Rd @@ -0,0 +1,38 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/unichem.R +\name{queryUnichem} +\alias{queryUnichem} +\title{Query UniChem for a compound.} +\usage{ +queryUnichem( + type, + compound, + sourceID = NA_integer_, + request_only = FALSE, + raw = FALSE, + ... +) +} +\arguments{ +\item{type}{\code{character} The type of compound identifier to search for. Valid types are "uci", "inchi", "inchikey", and "sourceID".} + +\item{compound}{\code{character} or \code{integer} The compound identifier to search for.} + +\item{sourceID}{\code{integer} The source ID to search for if the type is "sourceID". Defaults to NULL.} + +\item{request_only}{\code{boolean} Whether to return the request only. Defaults to FALSE.} + +\item{raw}{\code{boolean} Whether to return the raw response. Defaults to FALSE.} + +\item{...}{Additional arguments.} +} +\value{ +A list with the external mappings and the UniChem mappings. +} +\description{ +This function queries the UniChem API for a compound based on the provided parameters. +} +\examples{ +queryUnichem(type = "sourceID", compound = "444795", sourceID = 22) + +} diff --git a/tests/testthat/test_oncotree.R b/tests/testthat/test_oncotree.R new file mode 100644 index 0000000..7e5c46f --- /dev/null +++ b/tests/testthat/test_oncotree.R @@ -0,0 +1,36 @@ +library(testthat) +library(AnnotationGx) +library(checkmate) + +test_that("Returns data table for versions", { + result <- AnnotationGx::getOncotreeVersions() + expect_data_table( + result, + ncols = 4, + min.rows = 25, + all.missing = FALSE, + ) +}) + + +test_that("Returns data table for main types", { + result <- AnnotationGx::getOncotreeMainTypes() + expect_data_table( + result, + ncols = 1, + min.rows = 100, + all.missing = FALSE, + col.names = 'named' + ) +}) + +test_that("Returns data table for tumor types", { + result <- AnnotationGx::getOncotreeTumorTypes() + expect_data_table( + result, + ncols = 12, + min.rows = 800, + all.missing = FALSE, + col.names = 'named' + ) +}) diff --git a/tests/testthat/test_pubchem_view.R b/tests/testthat/test_pubchem_view.R index b4045dd..5deb8c2 100644 --- a/tests/testthat/test_pubchem_view.R +++ b/tests/testthat/test_pubchem_view.R @@ -44,7 +44,7 @@ test_that("AnnotationGx::annotatePubchemCompound", { response <- annotatePubchemCompound(CID, "ChEMBL ID", raw=T) expect_class(response[[1]], "httr2_response") - expected <- NULL + expected <- NA_character_ expect_equal(annotatePubchemCompound(CID, "NSC Number"), expected) expected <- "L01EB02" diff --git a/tests/testthat/test_unichem.R b/tests/testthat/test_unichem.R new file mode 100644 index 0000000..dfba62a --- /dev/null +++ b/tests/testthat/test_unichem.R @@ -0,0 +1,73 @@ +library(testthat) +library(AnnotationGx) +library(checkmate) + +test_that("getUnichemSources returns a data.table with the correct columns", { + sources <- getUnichemSources() + + expected_columns <- c( + "Name", "NameLabel", "NameLong", "SourceID", "CompoundCount", + "BaseURL", "URL", "Details", "Description", "ReleaseNumber", + "ReleaseDate", "LastUpdated", "UpdateComments" + ) + + expect_data_table( + sources, + all.missing = FALSE, + min.rows = 40, # As of March 2024 + min.cols = 13, # As of March 2024 + col.names = 'named', + info = "The data.table should have the correct columns. + The min number of rows and columns may change over time and is set on + from UniChem as of March 2024.", + ) +}) + + +test_that("queryUnichem returns the expected results", { + # Test case 1 + result1 <- queryUnichem(type = "sourceID", compound = "444795", sourceID = 22) + expect_true(is.list(result1)) + expect_true("External_Mappings" %in% names(result1)) + expect_true("UniChem_Mappings" %in% names(result1)) + + # Test case 2 + expect_error(queryUnichem(type = "inchikey", compound = "InchiKey123")) + +}) + +test_that("queryUnichem returns the expected results 2", { + # Test case 1 + result1 <- queryUnichem(type = "inchikey", compound = "BSYNRYMUTXBXSQ-UHFFFAOYSA-N", raw = T) + + expect_true(is.list(result1)) + + + checkmate::expect_names( + names(result1), + subset.of=c("compounds", "notFound", "response", "totalCompounds")) + + checkmate::expect_names( + names(result1$compounds), + subset.of=c("inchi", "sources", "standardInchiKey", "uci") + ) + + result2 <- queryUnichem(type = "inchikey", compound = "BSYNRYMUTXBXSQ-UHFFFAOYSA-N", raw = F) + + expect_true(is.list(result2)) + + checkmate::expect_names( + names(result2$External_Mappings), + subset.of = c("compoundID", "Name", "NameLong", "sourceID", "sourcURL") + ) + + checkmate::expect_names( + names(result2$UniChem_Mappings), + subset.of = c( + "UniChem.UCI", "UniChem.InchiKey", 'UniChem.Inchi', + 'UniChem.formula','UniChem.connections','UniChem.hAtoms' + ) + ) + + +}) \ No newline at end of file diff --git a/tests/testthat/test_unichem_helpers.R b/tests/testthat/test_unichem_helpers.R new file mode 100644 index 0000000..db48640 --- /dev/null +++ b/tests/testthat/test_unichem_helpers.R @@ -0,0 +1,74 @@ +library(testthat) +library(AnnotationGx) +library(checkmate) + +test_that("Valid endpoint returns correct URL", { + endpoint <- "compounds" + expected_url <- "https://www.ebi.ac.uk/unichem/api/v1/compounds" + actual_url <- .build_unichem_query(endpoint) + expect_equal(actual_url, expected_url) +}) + +test_that("Invalid endpoint throws an error", { + endpoint <- "invalid_endpoint" + expect_error(.build_unichem_query(endpoint)) +}) + +test_that("Query only option returns httr2::httr2_url object", { + endpoint <- "images" + query_only <- TRUE + expected_class <- "httr2_url" + actual_url <- .build_unichem_query(endpoint, query_only) + expect_class(actual_url, expected_class) +}) + + +test_that("Valid compound request is built correctly", { + type <- "uci" + compound <- "538323" + expected_url <- "https://www.ebi.ac.uk/unichem/api/v1/compounds" + expected_body <- list( + type = type, + compound = compound + ) + actual_request <- .build_unichem_compound_req(type, compound) + expect_equal(actual_request$url, expected_url) + expect_equal(actual_request$body$data, expected_body) +}) + +test_that("Valid sourceID compound request is built correctly", { + type <- "sourceID" + compound <- "2244" + sourceID <- 22 + expected_url <- "https://www.ebi.ac.uk/unichem/api/v1/compounds" + expected_body <- list( + type = type, + compound = compound, + sourceID = sourceID + ) + actual_request <- .build_unichem_compound_req(type, compound, sourceID) + expect_equal(actual_request$url, expected_url) + expect_equal(actual_request$body$data, expected_body) + + + response <- actual_request |> + .perform_request() |> + .parse_resp_json() + + checkmate::expect_names( + names(response), + subset.of=c("compounds", "notFound", "response", "totalCompounds")) + + checkmate::expect_names( + names(response$compounds), + subset.of=c("inchi", "sources", "standardInchiKey", "uci") + ) + + +}) + +test_that("Invalid type throws an error", { + type <- "invalid_type" + compound <- "538323" + expect_error(.build_unichem_compound_req(type, compound)) +}) diff --git a/vignettes/OncoTree.Rmd b/vignettes/OncoTree.Rmd new file mode 100644 index 0000000..413d7e0 --- /dev/null +++ b/vignettes/OncoTree.Rmd @@ -0,0 +1,65 @@ +--- +title: "Querying OncoTree" +output: rmarkdown::html_vignette +vignette: > + %\VignetteIndexEntry{Querying OncoTree} + %\VignetteEngine{knitr::rmarkdown} + %\VignetteEncoding{UTF-8} +--- + +```{r, include = FALSE} +knitr::opts_chunk$set( + collapse = TRUE, + comment = "#>" +) +``` + +# Introduction +OncoTree is a standardized classification system used in cancer research +and clinical practice to categorize different types of cancer based on +their tissue of origin, molecular characteristics, and other relevant factors. +Developed by the National Cancer Institute (NCI) within the United States, +OncoTree provides a hierarchical framework that organizes cancer types into +a structured tree-like diagram. + +- provides a standardized classification system for categorizing different + types of cancer based on their tissue of origin, molecular characteristics, + and other relevant factors. +- provides a hierarchical framework that organizes cancer types into a + structured tree-like diagram. +- useful for ensuring consistency in how cancer types are classified and + reported across different studies and clinical settings. + + +# Setup +```{r setup} +library(AnnotationGx) +``` + +# Querying OncoTree + +AnnotationGx provides a set of functions for querying OncoTree to retrieve +three types of information: +- OncoTree release versions +- Main Cancer types +- Subtypes of a specific cancer type and their relationships + +## OncoTree release versions +The `getOncotreeVersions` function retrieves the available OncoTree release. +```{r getOncotreeVersions} +getOncotreeVersions() +``` + +## Main Cancer types +The `getMainCancerTypes` function retrieves the main cancer types in OncoTree. +```{r getMainCancerTypes} +getOncotreeMainTypes() +``` + +## Subtypes of a specific cancer type +The `getCancerSubtypes` function retrieves the subtypes of a specific cancer type. +```{r getCancerSubtypes} +getOncotreeTumorTypes() +``` + + diff --git a/vignettes/PubChemAPI.Rmd b/vignettes/PubChemAPI.Rmd index 54ced6f..6011f26 100644 --- a/vignettes/PubChemAPI.Rmd +++ b/vignettes/PubChemAPI.Rmd @@ -127,12 +127,12 @@ getPubchemAnnotationHeadings(type = "Compound") ### Get annotation headings for a specific heading: ``` {r get annotation headings for a specific heading} -getPubchemAnnotationHeadings(heading = "CAS*") +getPubchemAnnotationHeadings(heading = "ChEMBL ID") ``` ### Get annotation headings for a specific type **and** heading: ``` {r get annotation headings for a specific type and heading} -getPubchemAnnotationHeadings(type = "Compound", heading = "CAS*") +getPubchemAnnotationHeadings(type = "Compound", heading = "CAS") ``` diff --git a/vignettes/treatment_pipeline.Rmd b/vignettes/treatment_pipeline.Rmd new file mode 100644 index 0000000..47bd9c4 --- /dev/null +++ b/vignettes/treatment_pipeline.Rmd @@ -0,0 +1,45 @@ +--- +title: "Annotating Treatments Pipeline" +output: rmarkdown::html_vignette +vignette: > + %\VignetteIndexEntry{Annotating Treatments Pipeline} + %\VignetteEngine{knitr::rmarkdown} + %\VignetteEncoding{UTF-8} +--- + +# THIS VIGNETTE IS A WORK IN PROGRESS + +```{r, include = FALSE} +knitr::opts_chunk$set( + collapse = TRUE, + comment = "#>" +) +``` + +```{r setup} +library(AnnotationGx) +``` + +```{r mapCompounds to CID} + +data(ctrp_treatmentIDs) +treatmentMetadata <- ctrp_treatmentIDs[1:5] +treatmentMetadata +names_to_cids <- AnnotationGx::mapCompound2CID(treatmentMetadata$CTRP.treatmentid, first = TRUE) + + +``` + + +```{r use CID in unichem} + +sources <- getUnichemSources() +response <- queryUnichem( + type = "sourceID", + compound = names_to_cids[1, cids], + sourceID = sources[Name == "pubchem", SourceID] +) + +response +``` +