diff --git a/R/WebGestaltRNta.R b/R/WebGestaltRNta.R index 137b648..801d74b 100644 --- a/R/WebGestaltRNta.R +++ b/R/WebGestaltRNta.R @@ -1,86 +1,92 @@ #' @importFrom httr POST content #' @importFrom readr read_tsv cols #' @importFrom jsonlite toJSON -WebGestaltRNta <- function(organism="hsapiens", network="network_PPI_BIOGRID", method="Network_Retrieval_Prioritization", inputSeed, inputSeedFile, interestGeneType="genesymbol", neighborNum=10, highlightSeedNum=10, sigMethod="fdr", fdrThr=0.05, topThr=10, highlightType="Seeds", outputDirectory=getwd(), projectName=NULL, cache=NULL, hostName="https://www.webgestalt.org/") { - projectDir <- file.path(outputDirectory, paste0("Project_", projectName)) - # if (network == "network_FunMap") { - # network <- "network_FunMap_DenseModules" - # } - dir.create(projectDir) +WebGestaltRNta <- function(organism = "hsapiens", network = "network_PPI_BIOGRID", method = "Network_Retrieval_Prioritization", inputSeed, inputSeedFile, interestGeneType = "genesymbol", neighborNum = 10, highlightSeedNum = 10, sigMethod = "fdr", fdrThr = 0.05, topThr = 10, highlightType = "Seeds", outputDirectory = getwd(), projectName = NULL, cache = NULL, hostName = "https://www.webgestalt.org/") { + projectDir <- file.path(outputDirectory, paste0("Project_", projectName)) + # if (network == "network_FunMap") { + # network <- "network_FunMap_DenseModules" + # } + dir.create(projectDir) - if (length(network) > 1) { - stop("NTA does not support multiple databases.") - } - inputGene <- formatCheck("list", inputGeneFile=inputSeedFile, inputGene=inputSeed) - # only networks are in gene symbols - # mapping always returns gene symbol, could map to genesymbol but takes two requests - inputGene <- idMappingGene(organism=organism, dataType="list", inputGene=inputGene, sourceIdType=interestGeneType, targetIdType="entrezgene", mappingOutput=FALSE, hostName=hostName) - inputGene <- inputGene$mapped$geneSymbol - + if (length(network) > 1) { + stop("NTA does not support multiple databases.") + } + inputGene <- formatCheck("list", inputGeneFile = inputSeedFile, inputGene = inputSeed) + # only networks are in gene symbols + # mapping always returns gene symbol, could map to genesymbol but takes two requests + inputGene <- idMappingGene(organism = organism, dataType = "list", inputGene = inputGene, sourceIdType = interestGeneType, targetIdType = "entrezgene", mappingOutput = FALSE, hostName = hostName) + inputGene <- inputGene$mapped$geneSymbol - if (startsWith(hostName, "file://")) { - dagInfo <- read_tsv( - removeFileProtocol(file.path(hostName, "geneset", paste(organism, "geneontology_Biological_Process", "entrezgene.dag", sep="_"))), - col_names=c("source", "target"), col_types="cc" - ) - } else { - geneSetUrl <- file.path(hostName, "api", "geneset") - response <- cacheUrl(geneSetUrl, cache=cache, query=list(organism=organism, database="geneontology_Biological_Process", standardId="entrezgene", fileType="dag")) - dagInfo <- read_tsv(content(response), col_names=c("source", "target"), col_types="cc") - } - ## networks <- unlist(strsplit(network, ",", fixed=TRUE)) - ## May need to bring back analysis of multiple networks - fileName <- paste(projectName, network, method, sep=".") - goEnrichRes <- randomWalkEnrichment(organism=organism, network=network, method=method, highlightSeedNum=highlightSeedNum, inputSeed=inputGene, - sigMethod=sigMethod, fdrThr=fdrThr, topThr=topThr, projectDir=projectDir, - topRank=neighborNum, projectName=projectName, cache=cache, hostName=hostName) - if (is.null(goEnrichRes)) { - return(NULL) - } - enrichResFile <- file.path(projectDir, paste0(fileName, "_enrichedResult.txt")) + if (startsWith(hostName, "file://")) { + dagInfo <- read_tsv( + removeFileProtocol(file.path(hostName, "geneset", paste(organism, "geneontology_Biological_Process", "entrezgene.dag", sep = "_"))), + col_names = c("source", "target"), col_types = "cc" + ) + } else { + geneSetUrl <- file.path(hostName, "api", "geneset") + response <- cacheUrl(geneSetUrl, cache = cache, query = list(organism = organism, database = "geneontology_Biological_Process", standardId = "entrezgene", fileType = "dag")) + dagInfo <- read_tsv(content(response), col_names = c("source", "target"), col_types = "cc") + } - goTermList <- read_tsv(enrichResFile, col_types=cols())$goId - inputEndIndex <- length(goTermList) + ## networks <- unlist(strsplit(network, ",", fixed=TRUE)) + ## May need to bring back analysis of multiple networks + fileName <- paste(projectName, network, method, sep = ".") + goEnrichRes <- randomWalkEnrichment( + organism = organism, network = network, method = method, highlightSeedNum = highlightSeedNum, inputSeed = inputGene, + sigMethod = sigMethod, fdrThr = fdrThr, topThr = topThr, projectDir = projectDir, + topRank = neighborNum, projectName = projectName, cache = cache, hostName = hostName + ) + if (is.null(goEnrichRes)) { + return(NULL) + } + enrichResFile <- file.path(projectDir, paste0(fileName, "_enrichedResult.txt")) - dagTree <- expandDag(goTermList, dagInfo) - goTermList <- dagTree$allNodes - edges <- dagTree$edges - rm(dagTree) + goTermList <- read_tsv(enrichResFile, col_types = cols())$goId + inputEndIndex <- length(goTermList) - if (startsWith(hostName, "file://")) { - goId2Term <- read_tsv( - removeFileProtocol(file.path(hostName, "geneset", paste(organism, "geneontology_Biological_Process", "entrezgene.des", sep="_"))), - col_names=c("id", "name"), col_types="cc" - ) - } else { - response <- POST(geneSetUrl, body=list(organism=organism, database="geneontology_Biological_Process", - fileType="des", ids=goTermList), encode="json") - goId2Term <- read_tsv(content(response), col_names=c("id", "name"), col_types="cc") - } + dagTree <- expandDag(goTermList, dagInfo) + goTermList <- dagTree$allNodes + edges <- dagTree$edges + rm(dagTree) - jsonFile <- file.path(projectDir, paste0(fileName, ".json")); - jsonData <- vector(mode="list", length=length(goTermList)) + if (startsWith(hostName, "file://")) { + goId2Term <- read_tsv( + removeFileProtocol(file.path(hostName, "geneset", paste(organism, "geneontology_Biological_Process", "entrezgene.des", sep = "_"))), + col_names = c("id", "name"), col_types = "cc" + ) + } else { + response <- POST(geneSetUrl, body = list( + organism = organism, database = "geneontology_Biological_Process", + fileType = "des", ids = goTermList, version = "2024" + ), encode = "json") + goId2Term <- read_tsv(content(response), col_names = c("id", "name"), col_types = "cc") + } - for (i in 1:length(goTermList)) { - goId <- goTermList[[i]] - goName <- filter(goId2Term, .data$id == goId)[[1, "name"]] - dataSets <- i <= inputEndIndex - jsonData[[i]] <- list(data=list(id=goId, name=goName, datasets=dataSets)) - } - jsonData <- unname(c(jsonData, edges)) + jsonFile <- file.path(projectDir, paste0(fileName, ".json")) + jsonData <- vector(mode = "list", length = length(goTermList)) - cat(toJSON(jsonData, auto_unbox=TRUE), "\n", sep="", file=jsonFile) + for (i in 1:length(goTermList)) { + goId <- goTermList[[i]] + goName <- filter(goId2Term, .data$id == goId)[[1, "name"]] + dataSets <- i <= inputEndIndex + jsonData[[i]] <- list(data = list(id = goId, name = goName, datasets = dataSets)) + } + jsonData <- unname(c(jsonData, edges)) - createNtaReport(networkName=network, method=method, sigMethod=sigMethod, fdrThr=fdrThr, topThr=topThr, - highlightType=highlightType, outputDirectory=outputDirectory, projectDir=projectDir, - projectName=projectName, hostName=hostName) + cat(toJSON(jsonData, auto_unbox = TRUE), "\n", sep = "", file = jsonFile) - cwd <- getwd() - setwd(projectDir) - zip(paste0(projectName, ".zip"), ".", flags="-rq") - setwd(cwd) + createNtaReport( + networkName = network, method = method, sigMethod = sigMethod, fdrThr = fdrThr, topThr = topThr, + highlightType = highlightType, outputDirectory = outputDirectory, projectDir = projectDir, + projectName = projectName, hostName = hostName + ) - cat("Results can be found in the ", projectDir, "!\n", sep="") - return(goEnrichRes) + cwd <- getwd() + setwd(projectDir) + zip(paste0(projectName, ".zip"), ".", flags = "-rq") + setwd(cwd) + + cat("Results can be found in the ", projectDir, "!\n", sep = "") + return(goEnrichRes) } diff --git a/R/cacheFile.R b/R/cacheFile.R index 68e0832..746c3f8 100644 --- a/R/cacheFile.R +++ b/R/cacheFile.R @@ -1,11 +1,11 @@ urlToFile <- function(dataUrl) { - result <- sub("^http://", "", dataUrl) - result <- sub("^https://", "", result) - result <- gsub("\\?[^?]+?=", "_", result) - result <- gsub("&[^&]+?=", "_", result) - result <- gsub("[:/.]", "_", result) - result <- gsub("_+", "_", result, fixed=TRUE) - return(result) + result <- sub("^http://", "", dataUrl) + result <- sub("^https://", "", result) + result <- gsub("\\?[^?]+?=", "_", result) + result <- gsub("&[^&]+?=", "_", result) + result <- gsub("[:/.]", "_", result) + result <- gsub("_+", "_", result, fixed = TRUE) + return(result) } #' cacheUrl @@ -21,32 +21,35 @@ urlToFile <- function(dataUrl) { #' @importFrom httr GET #' @keywords internal #' -cacheUrl <- function(dataUrl, cache=NULL, query=NULL) { - if (!is.null(cache)) { - dir.create(cache, showWarnings=FALSE) - if (!is.null(query)) { - localFilePrefix <- urlToFile(paste0(dataUrl, "_", paste0(query, collapse="_"))) - } else { - localFilePrefix <- urlToFile(dataUrl) - } - localFile <- file.path(cache, paste0(localFilePrefix, ".rds")) - } - if (!is.null(cache) && file.exists(localFile)) { - #cat("Reading from cache: ", localFile, "\n") - response <- readRDS(localFile) - } else { - #cat("Reading from server: ", dataUrl, "\n") - if (!is.null(query)) { - response <- GET(dataUrl, query=query) - } else { - response <- GET(dataUrl) - } - if (response$status_code != 200) { - return(response) - } - if (!is.null(cache)) { - saveRDS(response, localFile) - } - } - return(response) +cacheUrl <- function(dataUrl, cache = NULL, query = NULL) { + if (!is.null(cache)) { + dir.create(cache, showWarnings = FALSE) + if (!is.null(query)) { + localFilePrefix <- urlToFile(paste0(dataUrl, "_", paste0(query, collapse = "_"))) + } else { + localFilePrefix <- urlToFile(dataUrl) + } + localFile <- file.path(cache, paste0(localFilePrefix, ".rds")) + } + if (!is.null(cache) && file.exists(localFile)) { + # cat("Reading from cache: ", localFile, "\n") + response <- readRDS(localFile) + } else { + # cat("Reading from server: ", dataUrl, "\n") + if (!is.null(query)) { + if (!("version" %in% names(query))) { + query[["version"]] <- "2024" + } + response <- GET(dataUrl, query = query) + } else { + response <- GET(dataUrl, query = list(version = "2024")) + } + if (response$status_code != 200) { + return(response) + } + if (!is.null(cache)) { + saveRDS(response, localFile) + } + } + return(response) } diff --git a/R/goSlimSummary.R b/R/goSlimSummary.R index abcb832..fb8ba33 100644 --- a/R/goSlimSummary.R +++ b/R/goSlimSummary.R @@ -79,7 +79,7 @@ goSlimSummary <- function(organism="hsapiens", geneList, outputFile, outputType= goSlimData <- filter(goSlimData, .data$entrezgene %in% geneList) } else { goUrl <- file.path(hostName, "api", "goslim") - response <- POST(goUrl, body=list(organism=organism, ontology=ontology, entrezgenes=geneList), encode="json") + response <- POST(goUrl, body=list(organism=organism, ontology=ontology, entrezgenes=geneList, version="2024"), encode="json") if (response$status_code != 200) { stop(webRequestError(response)) } diff --git a/R/idMappingGene.R b/R/idMappingGene.R index e377e3e..f351307 100644 --- a/R/idMappingGene.R +++ b/R/idMappingGene.R @@ -1,110 +1,120 @@ #' @importFrom httr POST content #' @importFrom dplyr inner_join select filter left_join %>% -idMappingGene <- function(organism="hsapiens", dataType="list", inputGeneFile=NULL, inputGene=NULL, sourceIdType, targetIdType, collapseMethod="mean", mappingOutput=FALSE, outputFileName="", hostName="https://www.webgestalt.org/") { +idMappingGene <- function(organism = "hsapiens", dataType = "list", inputGeneFile = NULL, inputGene = NULL, sourceIdType, targetIdType, collapseMethod = "mean", mappingOutput = FALSE, outputFileName = "", hostName = "https://www.webgestalt.org/") { + ########### Check input data type############### + inputGene <- idMappingInput(dataType = dataType, inputGeneFile = inputGeneFile, inputGene = inputGene) - ###########Check input data type############### - inputGene <- idMappingInput(dataType=dataType,inputGeneFile=inputGeneFile,inputGene=inputGene) + ########## ID Mapping Specify to gene level############### + if (dataType == "list") { + inputGeneL <- unique(inputGene) + } - ##########ID Mapping Specify to gene level############### - if(dataType=="list"){ - inputGeneL <- unique(inputGene) - } + if (dataType == "rnk") { + ###### Collapse the gene ids with multiple scores########## + x <- tapply(inputGene$score, inputGene$gene, collapseMethod) + inputGene <- data.frame(gene = names(x), score = as.numeric(x), stringsAsFactors = FALSE) + inputGeneL <- inputGene$gene + colnames(inputGene) <- c(sourceIdType, "score") + } - if(dataType=="rnk"){ - ######Collapse the gene ids with multiple scores########## - x <- tapply(inputGene$score, inputGene$gene, collapseMethod) - inputGene <- data.frame(gene=names(x),score=as.numeric(x),stringsAsFactors=FALSE) - inputGeneL <- inputGene$gene - colnames(inputGene) <- c(sourceIdType,"score") - } + if (dataType == "gmt") { + colnames(inputGene) <- c("geneSet", "description", sourceIdType) + inputGeneL <- unique(inputGene[[sourceIdType]]) + } + if (startsWith(hostName, "file://")) { + # old way of mapping with mapping files. Now only used for WebGestaltReporter when hostName is file protocol + sourceMap <- read_tsv( + removeFileProtocol(file.path(hostName, "xref", paste(organism, sourceIdType, "entrezgene.table", sep = "_"))), + col_names = c("entrezgene", "userId"), col_types = "cc", quote = "" + ) %>% filter(.data$userId %in% inputGeneL) + symbolMap <- read_tsv( + removeFileProtocol(file.path(hostName, "xref", paste(organism, "genesymbol", "entrezgene.table", sep = "_"))), + col_names = c("entrezgene", "geneSymbol"), col_types = "cc", quote = "" + ) + nameMap <- read_tsv( + removeFileProtocol(file.path(hostName, "xref", paste(organism, "genename", "entrezgene.table", sep = "_"))), + col_names = c("entrezgene", "geneName"), col_types = "cc", quote = "" + ) + sourceMap <- sourceMap %>% + left_join(symbolMap, by = c("entrezgene")) %>% + left_join(nameMap, by = c("entrezgene")) - if(dataType=="gmt"){ - colnames(inputGene) <- c("geneSet", "description", sourceIdType) - inputGeneL <- unique(inputGene[[sourceIdType]]) - } - if (startsWith(hostName, "file://")) { - # old way of mapping with mapping files. Now only used for WebGestaltReporter when hostName is file protocol - sourceMap <- read_tsv( - removeFileProtocol(file.path(hostName, "xref", paste(organism, sourceIdType, "entrezgene.table", sep="_"))), - col_names=c("entrezgene", "userId"), col_types="cc", quote="" - ) %>% filter(.data$userId %in% inputGeneL) - symbolMap <- read_tsv( - removeFileProtocol(file.path(hostName, "xref", paste(organism, "genesymbol", "entrezgene.table", sep="_"))), - col_names=c("entrezgene", "geneSymbol"), col_types="cc", quote="" - ) - nameMap <- read_tsv( - removeFileProtocol(file.path(hostName, "xref", paste(organism, "genename", "entrezgene.table", sep="_"))), - col_names=c("entrezgene", "geneName"), col_types="cc", quote="" - ) - sourceMap <- sourceMap %>% left_join(symbolMap, by=c("entrezgene")) %>% left_join(nameMap, by=c("entrezgene")) + if (targetIdType %in% c("entrezgene", sourceIdType)) { + mappedInputGene <- sourceMap + } else { + targetMap <- read_tsv(removeFileProtocol(file.path(hostName, "xref", paste(organism, targetIdType, "entrezgene.table", sep = "_"))), + col_names = c("entrezgene", targetIdType), col_types = "cc", quote = "" + ) + mappedInputGene <- inner_join(sourceMap, targetMap, by = c("entrezgene")) + } + if (nrow(mappedInputGene) == 0) { + return(idMappingError("empty")) + } + mappedInputGene <- mappedInputGene %>% + select(.data$userId, .data$geneSymbol, .data$geneName, targetIdType) + unmappedIds <- setdiff(inputGeneL, mappedInputGene$userId) + } else { + # new way uses web server API + mapR <- POST(file.path(hostName, "api", "idmapping"), + encode = "json", + body = list( + organism = organism, sourceType = sourceIdType, + targetType = targetIdType, ids = inputGeneL, version = "2024" + ) + ) - if (targetIdType %in% c("entrezgene", sourceIdType)) { - mappedInputGene <- sourceMap - } else { - targetMap <- read_tsv(removeFileProtocol(file.path(hostName, "xref", paste(organism, targetIdType, "entrezgene.table", sep="_"))), - col_names=c("entrezgene", targetIdType), col_types="cc", quote="") - mappedInputGene <- inner_join(sourceMap, targetMap, by=c("entrezgene")) - } - if (nrow(mappedInputGene) == 0) { return(idMappingError("empty")) } - mappedInputGene <- mappedInputGene %>% - select(.data$userId, .data$geneSymbol, .data$geneName, targetIdType) - unmappedIds <- setdiff(inputGeneL, mappedInputGene$userId) + if (mapR$status_code != 200) { + stop(webRequestError(mapR)) + } + mapR <- content(mapR) + if (mapR$status == 1) { + stop(webApiError(mapR)) + } - } else { - # new way uses web server API - mapR <- POST(file.path(hostName, "api", "idmapping"), encode="json", - body=list(organism=organism, sourceType=sourceIdType, - targetType=targetIdType, ids=inputGeneL) - ) + mappedIds <- mapR$mapped + unmappedIds <- unlist(mapR$unmapped) + if (is.null(targetIdType)) { + targetIdType <- mapR$standardId + } - if (mapR$status_code != 200) { - stop(webRequestError(mapR)) - } - mapR <- content(mapR) - if (mapR$status == 1) { - stop(webApiError(mapR)) - } + if (length(mappedIds) == 0) { + stop(idMappingError("empty")) + } - mappedIds <- mapR$mapped - unmappedIds <- unlist(mapR$unmapped) - if (is.null(targetIdType)) { - targetIdType <- mapR$standardId - } + names <- c("sourceId", "geneSymbol", "geneName", "targetId") + mappedInputGene <- data.frame(matrix(unlist(lapply(replace_null(mappedIds), FUN = function(x) { + x[names] + })), nrow = length(mappedIds), byrow = TRUE), stringsAsFactors = FALSE) + colnames(mappedInputGene) <- c("userId", "geneSymbol", "geneName", targetIdType) + } - if (length(mappedIds) == 0) { stop(idMappingError("empty")) } + if (dataType == "list") { + inputGene <- mappedInputGene + } else if (dataType == "rnk") { + inputGene <- inner_join(mappedInputGene, inputGene, by = c("userId" = sourceIdType)) + } else if (dataType == "gmt") { + inputGene <- inner_join(mappedInputGene, inputGene, by = c("userId" = sourceIdType)) %>% + select(.data$geneSet, .data$description, .data$userId, .data$geneSymbol, .data$geneName, targetIdType) + } - names <- c("sourceId", "geneSymbol", "geneName", "targetId") - mappedInputGene <- data.frame(matrix(unlist(lapply(replace_null(mappedIds), FUN=function(x) { x[names] })), nrow=length(mappedIds), byrow=TRUE), stringsAsFactors=FALSE) - colnames(mappedInputGene) <- c("userId", "geneSymbol", "geneName", targetIdType) - } + if (targetIdType != "entrezgene" && sourceIdType != targetIdType) { + entrezgeneMapRes <- idMappingGene(organism, dataType = "list", inputGene = inputGeneL, sourceIdType = sourceIdType, targetIdType = "entrezgene", hostName = hostName) + inputGene <- left_join(inputGene, entrezgeneMapRes$mapped, by = "userId") - if (dataType=="list") { - inputGene <- mappedInputGene - } else if (dataType=="rnk") { - inputGene <- inner_join(mappedInputGene, inputGene, by=c("userId"=sourceIdType)) - } else if (dataType=="gmt") { - inputGene <- inner_join(mappedInputGene, inputGene, by=c("userId"=sourceIdType)) %>% - select(.data$geneSet, .data$description, .data$userId, .data$geneSymbol, .data$geneName, targetIdType) - } + if (dataType == "list") { + inputGene <- select(inputGene, .data$userId, geneSymbol = .data$geneSymbol.x, geneName = .data$geneName.x, .data$entrezgene, targetIdType) + } else if (dataType == "rnk") { + inputGene <- select(inputGene, .data$userId, geneSymbol = .data$geneSymbol.x, geneName = .data$geneName.x, .data$entrezgene, targetIdType, .data$score) + } else if (dataType == "gmt") { + inputGene <- select(inputGene, .data$geneSet, .data$description, .data$userId, geneSymbol = .data$geneSymbol.x, geneName = .data$geneName.x, .data$entrezgene, targetIdType) + } + } + inputGene$gLink <- paste0("https://www.ncbi.nlm.nih.gov/gene/?term=", inputGene$entrezgene) - if (targetIdType != "entrezgene" && sourceIdType!=targetIdType) { - entrezgeneMapRes <- idMappingGene(organism, dataType="list", inputGene=inputGeneL, sourceIdType=sourceIdType, targetIdType="entrezgene", hostName=hostName) - inputGene <- left_join(inputGene, entrezgeneMapRes$mapped, by="userId") - - if (dataType=="list") { - inputGene <- select(inputGene, .data$userId, geneSymbol=.data$geneSymbol.x, geneName=.data$geneName.x, .data$entrezgene, targetIdType) - } else if (dataType=="rnk") { - inputGene <- select(inputGene, .data$userId, geneSymbol=.data$geneSymbol.x, geneName=.data$geneName.x, .data$entrezgene, targetIdType, .data$score) - } else if (dataType=="gmt") { - inputGene <- select(inputGene, .data$geneSet, .data$description, .data$userId, geneSymbol=.data$geneSymbol.x, geneName=.data$geneName.x, .data$entrezgene, targetIdType) - } - } - inputGene$gLink <- paste0("https://www.ncbi.nlm.nih.gov/gene/?term=", inputGene$entrezgene) - - #############Output####################### - if (mappingOutput) { - idMappingOutput(outputFileName, inputGene, unmappedIds, dataType, sourceIdType, targetIdType) - } - r <- list(mapped=inputGene,unmapped=unmappedIds) - return(r) + ############# Output####################### + if (mappingOutput) { + idMappingOutput(outputFileName, inputGene, unmappedIds, dataType, sourceIdType, targetIdType) + } + r <- list(mapped = inputGene, unmapped = unmappedIds) + return(r) } diff --git a/R/idMappingMetabolites.R b/R/idMappingMetabolites.R index 09ed52a..b203a18 100644 --- a/R/idMappingMetabolites.R +++ b/R/idMappingMetabolites.R @@ -46,7 +46,7 @@ idMappingMetabolites <- function(organism = "hsapiens", dataType = "list", input encode = "json", body = list( organism = organism, sourceType = sourceIdType, - targetType = targetIdType, ids = inputGeneL, standardId = standardId + targetType = targetIdType, ids = inputGeneL, standardId = standardId, version = "2024" ) ) if (response$status_code != 200) { @@ -76,7 +76,7 @@ idMappingMetabolites <- function(organism = "hsapiens", dataType = "list", input encode = "json", body = list( organism = organism, sourceType = "rampc", - targetType = "metabolite_name", ids = mappedInputGene$rampc, standardId = standardId + targetType = "metabolite_name", ids = mappedInputGene$rampc, standardId = standardId, version="2024" ) ) mapRes <- content(response) diff --git a/R/idMappingPhosphosite.R b/R/idMappingPhosphosite.R index 8946436..77c5673 100644 --- a/R/idMappingPhosphosite.R +++ b/R/idMappingPhosphosite.R @@ -43,7 +43,7 @@ idMappingPhosphosite <- function(organism="hsapiens", dataType="list", inputGene } else { response <- POST(file.path(hostName, "api", "idmapping"), encode="json", body=list(organism=organism, sourceType=sourceIdType, - targetType=targetIdType, ids=inputGeneL, standardId="phosphositeSeq") + targetType=targetIdType, ids=inputGeneL, standardId="phosphositeSeq", version="2024") ) if (response$status_code != 200) { stop(webRequestError(response)) @@ -80,7 +80,7 @@ idMappingPhosphosite <- function(organism="hsapiens", dataType="list", inputGene } else { response <- POST(file.path(hostName, "api", "idmapping"), encode="json", body=list(organism=organism, sourceType="phosphositeSeq", standardId="phosphositeSeq", - targetType="phosphositeUniprot", ids=inputGeneL) + targetType="phosphositeUniprot", ids=inputGeneL, version="2024") ) if (response$status_code != 200) { diff --git a/R/linkModification.R b/R/linkModification.R index f4d7fc7..4495c9c 100644 --- a/R/linkModification.R +++ b/R/linkModification.R @@ -105,7 +105,7 @@ simple_mapping <- function(id_list, organism, source_id, target_id, standard_id, encode = "json", body = list( organism = organism, sourceType = source_id, - targetType = target_id, ids = id_list, standardId = standard_id + targetType = target_id, ids = id_list, standardId = standard_id, version = "2024" ) ) if (response$status_code != 200) { diff --git a/R/metaLinkModification.R b/R/metaLinkModification.R index 01903ec..15d1ee2 100644 --- a/R/metaLinkModification.R +++ b/R/metaLinkModification.R @@ -448,7 +448,7 @@ full_simple_mapping <- function(id_list, organism, source_id, target_id, standar encode = "json", body = list( organism = organism, sourceType = source_id, - targetType = target_id, ids = id_list, standardId = standard_id + targetType = target_id, ids = id_list, standardId = standard_id, version="2024" ) ) if (response$status_code != 200) { diff --git a/R/randomWalkEnrichment.R b/R/randomWalkEnrichment.R index f067527..6f14bb5 100644 --- a/R/randomWalkEnrichment.R +++ b/R/randomWalkEnrichment.R @@ -154,7 +154,7 @@ randomWalkEnrichment <- function(organism, network, method, inputSeed, topRank, geneSetUrl <- file.path(hostName, "api", "geneset") response <- POST(geneSetUrl, body = list( organism = organism, database = "geneontology_Biological_Process", - fileType = "des", ids = unique(annRef$geneSet) + fileType = "des", ids = unique(annRef$geneSet), version="2024" ), encode = "json") refTermName <- read_tsv(content(response), col_names = c("id", "description"), col_types = "cc") %>% filter(.data$id %in% names(refTermCount))