Skip to content

Commit

Permalink
Merge pull request #35 from ncats/dev
Browse files Browse the repository at this point in the history
Dev
  • Loading branch information
Mathelab authored May 4, 2022
2 parents e74d21c + 29d65da commit b1fb785
Show file tree
Hide file tree
Showing 16 changed files with 136 additions and 35 deletions.
4 changes: 3 additions & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,9 @@ Imports:
stringi,
RMariaDB,
DBI,
jsonlite
jsonlite,
methods,
tibble
Encoding: UTF-8
RoxygenNote: 7.1.2
Suggests:
Expand Down
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ export(getMetabClassTypes)
export(getOntoFromMeta)
export(getOntologies)
export(getPathwayFromAnalyte)
export(getPathwayNameList)
export(getPrefixesFromAnalytes)
export(getRaMPAnalyteIntersections)
export(pathwayResultsPlot)
Expand Down
42 changes: 32 additions & 10 deletions R/ReturnAnalytes_InputPathways.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@
#'
#' @param pathway a string or a vector of strings that contains pathways of interest
#' @param analyte_type a string denoting the type of analyte to return ("gene", "metabolite", "both")
#' @param match type of matching to use, options are "exact" or "fuzzy". The default is "exact".
#' @return a data.frame that contains all search results
#' @examples
#' \dontrun{
Expand All @@ -14,7 +15,7 @@
#' "sphingolipid metabolism"))
#' }
#' @export
getAnalyteFromPathway <- function(pathway, analyte_type="both") {
getAnalyteFromPathway <- function(pathway, match="exact", analyte_type="both") {
now <- proc.time()
print("fired")
if(is.character(pathway)){
Expand All @@ -34,21 +35,42 @@ getAnalyteFromPathway <- function(pathway, analyte_type="both") {
}
list_pathway <- sapply(list_pathway,shQuote)
list_pathway <- paste(list_pathway,collapse = ",")
# Retrieve pathway RaMP id
con <- connectToRaMP()
query1 <- paste0("select * from pathway where pathwayName

# Retrieve pathway RaMP ids
if (match=='exact') {
query1 <- paste0("select * from pathway where pathwayName
in (",list_pathway,");")

df1 <- RMariaDB::dbGetQuery(con,query1)
RMariaDB::dbDisconnect(con)
con <- connectToRaMP()
df1 <- RMariaDB::dbGetQuery(con,query1)
RMariaDB::dbDisconnect(con)
} else if (match=='fuzzy') {
print("running fuzzy")
df1=c()
for (i in 1:length(pathway)) {
# note here that we are using pathway, not list_pathway which
# formats for 'exact' but not 'fuzzy'
con <- connectToRaMP()
query1 <- paste0('select * from pathway where pathwayName
like "%',pathway[i],'%";')
df1 <- rbind(df1,RMariaDB::dbGetQuery(con,query1))
RMariaDB::dbDisconnect(con)
}
} else {
stop("Please be sure to set the match parameter to 'exact' or 'fuzzy'.")
}

if(nrow(df1)==0) {
stop("None of the input pathway(s) could be found")}

# Retrieve compound id from RaMP pathway id (query1)
query2 <- paste0("select pathwayRampId,rampId from analytehaspathway where
pathwayRampId in (select pathwayRampId from pathway where
pathwayName in (",list_pathway,"));")
#query2 <- paste0("select pathwayRampId,rampId from analytehaspathway where
# pathwayRampId in (select pathwayRampId from pathway where
# pathwayName in (",list_pathway,"));")
pidlist <- sapply(df1$pathwayRampId,shQuote)
pidlist <- paste(pidlist,collapse = ",")

query2 <- paste0("select pathwayRampId, rampId from analytehaspathway
where pathwayRampId in (",pidlist,");")
con <- connectToRaMP()
df2 <- RMariaDB::dbGetQuery(con,query2)
RMariaDB::dbDisconnect(con)
Expand Down
4 changes: 3 additions & 1 deletion R/ReturnGeneMetab_SameRxn.R
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,8 @@
#' }
#' @export
rampFastCata <- function(analytes="none", NameOrIds="ids") {

rampId <- pathwayRampId <- c()
if(length(analytes)==1){
if(analytes=="none"){
stop("Please provide input analytes")}}
Expand Down Expand Up @@ -129,7 +131,7 @@ rampFastCata <- function(analytes="none", NameOrIds="ids") {
} else {
# default handling of empty result
# empty df1 requires use of tibble/tidyr add_column
df1 <- add_column(df1, 'query_relation'=NA)
df1 <- tibble::add_column(df1, 'query_relation'=NA)
result <- df1
}
}
Expand Down
9 changes: 7 additions & 2 deletions R/ReturnPathwaysEnrich_InputAnalytes.R
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,8 @@ runFisherTest <- function(analytes,
find_synonym=FALSE
)

pathwayRampId <- rampId <- c()

if (analyte_type == "metabolites") {
pathwaydf <- pathwaydf[grep("RAMP_C_", pathwaydf$rampId), ]
} else if (analyte_type == "genes") {
Expand All @@ -46,7 +48,8 @@ runFisherTest <- function(analytes,
return(NULL)
}

if(class(background_type)=="list"){
# if(class(background_type)=="list"){
if(is(background_type, "list")){
background = unlist(background)
}

Expand All @@ -57,7 +60,7 @@ runFisherTest <- function(analytes,
)
print("Custom background specified, genes will be discarded")
} else if (background_type=="file") {
userbkg <- read.table(background, header=F)[,1]
userbkg <- utils::read.table(background, header=F)[,1]
backgrounddf <- getPathwayFromAnalyte(userbkg,
includeRaMPids = TRUE,
NameOrIds = NameOrIds)
Expand Down Expand Up @@ -702,6 +705,8 @@ getPathwayFromAnalyte <- function(analytes = "none",
NameOrIds = "ids",
includeRaMPids = FALSE) {

rampId <- pathwayRampId <- c()

print("Starting getPathwayFromAnalyte()")
if (is.null(analytes) || length(analytes) == 0) {
warning("Input analyte list is NULL or empty. Aborting getPathwayFromAnalyte()")
Expand Down
19 changes: 19 additions & 0 deletions R/SourceDataFunctions.R
Original file line number Diff line number Diff line change
Expand Up @@ -120,3 +120,22 @@ getRaMPAnalyteIntersections<-function(analyteType='metabolites', format='json',



#' Retrieve list of pathway names
#' @return vector of unique pathway names (alphabetically ordered)
#' @examples
#' \dontrun{
#' pkg.globals <- setConnectionToRaMP(dbname="ramp2",username="root",conpass="",host = "localhost")
#' getPathwayNameList()
#' }
#' @export
getPathwayNameList <- function(){
con<-connectToRaMP()
query1<-"select pathwayName from pathway;"
results<-RMariaDB::dbGetQuery(con,query1)
RMariaDB::dbDisconnect(con)
return(sort(unique(results$pathwayName)))
}




3 changes: 2 additions & 1 deletion R/printingFunctions.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,8 @@ cleanup<- function(data, show_n_rows = 6) {
if (class(data) != "data.frame" & (class(data) != "list" & length(data) != 1)) {
stop("Input should be a dataframe resulting from runCombinedFishersTest, getAnalyteFromPathway, getPathwayFromAnalyte, chemicalClassSurvey, or getChemicalProperties")
}
if (class(data) == "list") {
# if (class(data) == "list") {
if (is(data, "list")){
data <- data[[1]]
}
rownames(data) <- NULL
Expand Down
4 changes: 3 additions & 1 deletion R/rampChemClassQueries.R
Original file line number Diff line number Diff line change
Expand Up @@ -67,11 +67,13 @@
#'}
#' @export
chemicalClassSurvey <- function(mets, background = "database", background_type="database", includeRaMPids = FALSE){


conn <- connectToRaMP()
print("Starting Chemical Class Survey")

if(background_type == "file") {
bkgrnd <- read.table(background, header=F)[,1]
bkgrnd <- utils::read.table(background, header=F)[,1]

filteredMets <- mets[mets %in% bkgrnd]
print(paste0("Number of input query ids: ",length(mets)))
Expand Down
3 changes: 2 additions & 1 deletion R/rampQueryHelper.R
Original file line number Diff line number Diff line change
Expand Up @@ -711,7 +711,8 @@ FilterFishersResults <- function(fishers_df, pval_type = 'fdr', pval_cutoff = 0.

for(result in names(fishers_df)) {

if(class(fishers_df[[result]]) == 'data.frame') {
#if(class(fishers_df[[result]]) == 'data.frame') {
if(is(fishers_df[[result]], 'data.frame')) {
print(result)
resultDf <- fishers_df[[result]]
resultDf <- subset(resultDf, resultDf[[criteriaCol]] <= pval_cutoff)
Expand Down
24 changes: 12 additions & 12 deletions R/writingFunctions.R
Original file line number Diff line number Diff line change
Expand Up @@ -4,14 +4,14 @@
#' @param outputfile name of output file
#' @export
writePathwaysToCSV <- function(mypathways = "none", outputfile = "none") {
if(length(mypathways) == 1){
if (mypathways == "") {
stop("Be sure to specify the output of the function getPathwayFromAnalyte() and an output file")
}}
if(length(outputfile) == 1){
if (outputfile == "") {
stop("Be sure to specify the output of the function getPathwayFromAnalyte() and an output file")
}}
if(length(mypathways) == 1){
if (mypathways == "") {
stop("Be sure to specify the output of the function getPathwayFromAnalyte() and an output file")
}}
if(length(outputfile) == 1){
if (outputfile == "") {
stop("Be sure to specify the output of the function getPathwayFromAnalyte() and an output file")
}}
if (!all(c(
"pathwayName", "pathwaySource",
"pathwayId", "inputId", "commonName"
Expand All @@ -34,10 +34,10 @@ writePathwaysToCSV <- function(mypathways = "none", outputfile = "none") {
#' @export
write_FishersResults <- function(fishResults = "none", outputfile = "none", rampid = FALSE) {

if(length(fishResults) == 1){
if (fishResults == "") {
stop("Be sure to specify the output of the function findCluster()")
}}
if(length(fishResults) == 1){
if (fishResults == "") {
stop("Be sure to specify the output of the function findCluster()")
}}
clusters <- fishResults$cluster_list
if (is.null(clusters)) {
out <- fishResults$fishresults
Expand Down
9 changes: 5 additions & 4 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,7 @@ To access, [click here](https://www.mdpi.com/2218-1989/8/1/16)
## Installation Instructions
In order to use this R package locally, you will need the following:
* The R code under this repo
* The mysql dump file that contains the RaMP database (in the folder inst/extdata/)
* The mysql dump file that contains the RaMP database. **[Download here](https://figshare.com/ndownloader/files/34990387).**

If you would like to know how to build RaMP database from scratch, please check another GitHub site at [RaMP-BackEnd](https://github.com/ncats/RaMP-BackEnd)

Expand All @@ -84,11 +84,12 @@ mysql> exit;

Here, we are naming the database "ramp" but you can use any name you'd like. It is worth noting though that the R package assumes that the name of the database is "ramp" by default. So if you change the name, remember to pass that name as arguments in the R package functions.

Second, download and unzip the latest RaMP database from the inst/extdata folder.
Second, download and unzip the latest RaMP database. **[Download here](https://figshare.com/ndownloader/files/34990387).**

Third, populate the named database with the mysql dump file (which you can get from inst/extdata/rampXXXXXX.sql, where XXXXXX denotes the latest date):
Third, populate the named database with the mysql dump file
Supply the path and file name to the unzipped sql file that you've downloaded.
```
> mysql -u root -p ramp < rampXXXX.sql
> mysql -u root -p ramp < /your/file/path/here/ramp_<current_version_id_here>.sql
```

You're done!
Expand Down
Binary file removed inst/extdata/ramp_2.0.6_20220303.sql.gz
Binary file not shown.
4 changes: 3 additions & 1 deletion man/getAnalyteFromPathway.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

20 changes: 20 additions & 0 deletions man/getPathwayNameList.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion tests/testthat/test-chemicalClassEnrichment.R
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ test_that("chemical class enrichment data is returned correctly, ChemicalClassEn
'hmdb:HMDB0000439',
'hmdb:HMDB0000479',
'hmdb:HMDB0000532',
'hmdb:HMDB0011211' )
'hmdb:HMDB0011211')



Expand Down
23 changes: 23 additions & 0 deletions tests/testthat/test-getAnalyteFromPathway.R
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,30 @@ test_that("Table returned shows correct output for multiple pathways ,getAnalyte



test_that("Fuzzy match test for TCA and Creatine",
{

library(properties)
dbpass <- properties::read.properties('../../dbprops.txt')

pkg.globals <- setConnectionToRaMP(host=dbpass$hostname, dbname=dbpass$dbname, username=dbpass$username, conpass=dbpass$conpass)
assign("pkg.globals", pkg.globals, envir = .GlobalEnv)

my_analytes <-
getAnalyteFromPathway(pathway=c(
"TCA",
"Creatine"
), match="fuzzy")

print(dim(my_analytes))
print(unique(my_analytes$pathwayName))

expect_true(
!is.null(my_analytes)
)
expect_true(
NROW(my_analytes) != 0)
})



Expand Down

0 comments on commit b1fb785

Please sign in to comment.