R/web-services.R
c9b073a5
 if(getRversion() >= "2.15.1") {
   utils::globalVariables("GMQL_credentials")
   utils::globalVariables("remote_url")
18697071
 }
48ab60c3
 
c9b073a5
 if(getRversion() >= "3.1.0") {
   utils::suppressForeignCheck("GMQL_credentials")
   utils::suppressForeignCheck("remote_url")
18697071
 }
 
48ab60c3
 
 #############################
 #     WEB AUTHENTICATION   #
 ############################
 
 
 #' Login to GMQL
 #'
 #' Login to GMQL REST services suite as a registered user, specifying username 
83eb0624
 #' and password, or as guest, using the proper GMQL web service available 
48ab60c3
 #' on a remote server
 #' 
 #' @import httr
 #' @importFrom rJava J
 #' 
 #' @param url string url of server: It must contain the server address 
 #' and base url; service name is added automatically
 #' @param username string name used during signup
 #' @param password string password used during signup
 #'
 #' @details
18697071
 #' If both username and password are missing, you will be logged as guest.
48ab60c3
 #' After login you will receive an authentication token.
18697071
 #' As token remains valid on server (until the next login / registration or 
 #' logout), a user can safely use a token for a previous session as a 
 #' convenience; this token is saved in R Global environment to perform 
 #' subsequent REST call even on complete R restart (if the environment has 
 #' been saved). If error occurs, a specific error is printed
48ab60c3
 #'
 #' @return None
 #'
 #' @examples
83eb0624
 #' ## Login to GMQL REST services suite as guest
 #' 
9089a38d
 #' remote_url = "http://www.gmql.eu/gmql-rest/"
48ab60c3
 #' login_gmql(remote_url)
 #' 
 #' @name login_gmql
 #' @rdname login_gmql
 #' @export
 #' 
c9b073a5
 login_gmql <- function(url, username = NULL, password = NULL) {
73652f4d
   if(!.is_login_expired(url)) {
     print("Login still valid")
     return(invisible(NULL))
   }
   
   as_guest <- TRUE
   
   if(!is.null(username) || !is.null(password))
     as_guest <- FALSE
   
03d52325
   url <- sub("/*[/]$","",url)
   
73652f4d
   if(as_guest) {
     h <- c('Accept' = "Application/json")
     URL <- paste0(url,"/guest")
     req <- httr::GET(URL,httr::add_headers(h))
   } else {
     req <- httr::GET(url)
08b4a456
     real_URL <- sub("/*[/]$","",req$url)
73652f4d
     h <- c('Accept'="Application/json",'Content-Type'='Application/json')
03d52325
     URL <- paste0(real_URL,"/login")
73652f4d
     body <- list('username' = username,'password' = password)
08b4a456
     req <- httr::POST(URL, httr::add_headers(h), body = body, encode = "json")
73652f4d
   }
   
   content <- httr::content(req)
   
   if(req$status_code != 200)
     stop(content$errorString)
   else {
     url <- paste0(url,"/")
     GMQL_remote <- list(
       "remote_url" = url, 
       "authToken" = content$authToken,
       "username" = username,
       "password" = password
     )
08b4a456
   
     assign("GMQL_credentials", GMQL_remote, .GlobalEnv)
     print(paste("your Token is", GMQL_remote$authToken))
73652f4d
   }
48ab60c3
 }
 
 #' Logout from GMQL
 #' 
 #' Logout from GMQL REST services suite
 #' using the proper GMQL web service available on a remote server
 #' 
 #' @import httr
 #' @importFrom rJava J
 #' 
 #' @param url string url of server: It must contain the server address 
 #' and base url; service name is added automatically
 #'
 #' @details
 #' After logout the authentication token will be invalidated.
83eb0624
 #' The authentication token is removed from R Global environment.
 #' If error occurs, a specific error is printed
48ab60c3
 #' 
 #' @examples
 #' 
83eb0624
 #' ## Login to GMQL REST services suite as guest, then logout
 #' 
6b6f7701
 #' remote_url = "http://www.gmql.eu/gmql-rest/"
48ab60c3
 #' login_gmql(remote_url)
 #' logout_gmql(remote_url)
 #' 
 #' @return None
 #'
 #' @name logout_gmql
 #' @rdname logout_gmql
 #' @export
 #'
03d52325
 logout_gmql <- function(url) {
73652f4d
   url <- sub("/*[/]$","",url)
   URL <- paste0(url,"/logout")
08b4a456
   
   authToken = GMQL_credentials$authToken
73652f4d
   h <- c('X-Auth-Token' = authToken)
08b4a456
   
73652f4d
   req <- httr::GET(URL, httr::add_headers(h))
   content <- httr::content(req)
   
   if(req$status_code !=200)
     stop(content$error)
03d52325
   else {
73652f4d
     #delete token from environment
     if(exists("authToken", where = GMQL_credentials))
       rm(GMQL_credentials, envir = .GlobalEnv)
48ab60c3
     
73652f4d
     print(content)
   }
48ab60c3
 }
0f1bbf8e
 #' Register into remote GMQL
13c07814
 #' 
 #' Register to GMQL REST services suite
0f1bbf8e
 #' using the proper GMQL web service available on a remote server.
13c07814
 #' 
 #' @import httr
 #' @importFrom rJava J
 #' 
 #' @param url string url of server: It must contains the server address 
 #' and base url; service name is added automatically
 #' 
 #' @param username string user name used to login in
 #' @param psw string password used to login in
 #' @param email string user email 
 #' @param first_name string user first name 
 #' @param last_name string user last name 
 #' 
 #' @details
 #' After registration you will receive an authentication token.
 #' As token remains valid on server (until the next login / registration or 
 #' logout), a user can safely use a token for a previous session as a 
 #' convenience; this token is saved in R Global environment to perform 
0f1bbf8e
 #' subsequent REST calls or batch processing even on complete R restart 
 #' (if the environment has been saved). If error occurs, a specific error 
 #' is printed.
13c07814
 #' 
 #' @examples
 #' 
 #' ## Register to GMQL REST services suite 
 #' 
9089a38d
 #' remote_url = "http://www.gmql.eu/gmql-rest/"
13c07814
 #' \dontrun{
 #' register_gmql(remote_url,"foo","foo","foo@foo.com","foo","foo")
 #' }
 #' 
 #' @return None
 #'
 #' @name register_gmql
 #' @rdname register_gmql
 #' @export
 #'
73652f4d
 register_gmql <- function(
   url, 
   username, 
   psw, 
   email, 
   first_name, 
   last_name
 ) {
   req <- httr::GET(url)
08b4a456
   url <- sub("/*[/]$","",req$url)
73652f4d
   
08b4a456
   URL <- paste0(url,"/register")
73652f4d
   h <- c('Accept' = "Application/json")
   reg_body <- list(
     "firstName" = first_name, 
     "lastName" = last_name,
     "username" = username, 
     "email" = email, 
     "password" = psw
   )
   
   req <- httr::POST(
     URL, 
     body = reg_body, 
     httr::add_headers(h), 
     encode = "json"
   )
   
   content <- httr::content(req,"parsed")
   if(req$status_code != 200) {
     stop(content)
   } else {
     GMQL_remote <- list(
       "remote_url" = url, 
       "authToken" = content$authToken,
       "username" = username,
       "password" = psw
     )
08b4a456
     assign("GMQL_credentials", GMQL_remote, .GlobalEnv)
03d52325
     print(paste("your Token is", GMQL_remote$authToken))
73652f4d
   }
13c07814
 }
 
48ab60c3
 
 #############################
 #       WEB BROWSING       #
 ############################
 
18697071
 #' Show all queries
48ab60c3
 #'
18697071
 #' It shows all the GMQL queries saved by the user on remote repository, 
 #' using the proper GMQL web service available on a remote server
48ab60c3
 #' 
 #' @import httr
 #'
 #' @param url string url of server: It must contain the server address 
 #' and base url; service name is added automatically
 #'
18697071
 #' @return List of queries. Every query in the list is described by:
48ab60c3
 #' \itemize{
 #' \item{name: name of query}
 #' \item{text: text of GMQL query}
 #' }
 #'
 #' @details
83eb0624
 #' If error occurs, a specific error is printed
48ab60c3
 #'
dda0cfa0
 #' @examples
5b358a31
 #' 
dda0cfa0
 #' ## Login to GMQL REST services suite
9089a38d
 #' remote_url = "http://www.gmql.eu/gmql-rest/"
48ab60c3
 #' login_gmql(remote_url)
dda0cfa0
 #' 
 #' ## List all queries executed on remote GMQL system 
48ab60c3
 #' list <- show_queries_list(remote_url)
 #' 
 #' @name show_queries_list
 #' @rdname show_queries_list
 #' @export
 #'
73652f4d
 show_queries_list <- function(url) {
   url <- sub("/*[/]$","",url)
   URL <- paste0(url,"/query")
   authToken = GMQL_credentials$authToken
   h <- c('Accept' = 'Application/json', 'X-Auth-Token' = authToken)
   req <- httr::GET(URL, httr::add_headers(h))
   content <- httr::content(req,"parsed")
   if(req$status_code == 200) {
     return(content)
   } else {
     stop(content$error)
   }
48ab60c3
 }
 
 #' Save GMQL query
 #'
83eb0624
 #' It saves a GMQL query into repository, taken from file or inserted as text 
48ab60c3
 #' string, using the proper GMQL web service available on a remote server
 #' 
 #' @import httr
 #'
 #' @param url string url of server: It must contain the server address 
 #' and base url; service name is added automatically
 #' @param queryName string name of query
4bc0d16e
 #' @param queryTxt string text of GMQL query
48ab60c3
 #'
 #' @return None
 #'
 #' @details
83eb0624
 #' If you save a query with the same name of another query already stored 
dda0cfa0
 #' in repository, you will overwrite it; if no error occurs, it prints: 
18697071
 #' "Saved", otherwise it prints the error
48ab60c3
 #'
 #' @examples
 #' 
83eb0624
 #' ## Login to GMQL REST services suite as guest
 #' 
9089a38d
 #' remote_url = "http://www.gmql.eu/gmql-rest/"
48ab60c3
 #' login_gmql(remote_url)
83eb0624
 #' 
dda0cfa0
 #' ## This statement saves query written directly as input string parameter 
 #' ## with name "dna_query" 
83eb0624
 #' 
18697071
 #' save_query(remote_url, "example_query",
 #' "DATASET = SELECT() Example_Dataset_1; MATERIALIZE DATASET INTO RESULT_DS;")
48ab60c3
 #' 
dda0cfa0
 #' ## With system.file() this statement  defines the path to the folder 
 #' ## "example" of the package "RGMQL", and then it saves the query written 
 #' ## in the text file "query1.txt" into remote repository
83eb0624
 #' 
48ab60c3
 #' test_path <- system.file("example", package = "RGMQL")
 #' test_query <- file.path(test_path, "query1.txt")
 #' save_query_fromfile(remote_url, "query1", test_query)
 #' 
 #' @name save_query
 #' @rdname save_query
 #' @export
 #'
73652f4d
 save_query <- function(url, queryName, queryTxt) {
   req <- httr::GET(url)
08b4a456
   url <- sub("/*[/]$","",req$url)
   URL <- paste0(url,"/query/",queryName,"/save")
73652f4d
   authToken = GMQL_credentials$authToken
   h <- c(
     'Accept' = 'text/plain',
     'X-Auth-Token' = authToken,
     'Content-Type' = 'text/plain'
   )
   req <- httr::POST(URL, httr::add_headers(h),body = queryTxt)
   content <- httr::content(req)
   
   if(req$status_code == 200) {
     # print Saved
     print(content) 
   } else {
     stop(content$error)
   }
48ab60c3
 }
 
18697071
 #' @param filePath string local file path of a txt file containing a GMQL query
48ab60c3
 #' 
 #' @name save_query_fromfile
 #' @rdname save_query
 #' @export
 #' 
73652f4d
 save_query_fromfile <- function(url, queryName, filePath) {
   if(!file.exists(filePath)) {
     stop("file does not exist")
   }
   
   queryTxt <- readLines(filePath)
   save_query(url,queryName,queryTxt)
48ab60c3
 }
 
 #############################
 #       WEB OPERATION      #
 ############################
 
 #' Run a GMQL query
 #' 
83eb0624
 #' It runs a GMQL query into repository taken from file or inserted as text 
48ab60c3
 #' string, using the proper GMQL web service available on a remote server
 #' 
 #' @import httr
 #' 
83eb0624
 #' @param url string url of server: It must contain the server address 
48ab60c3
 #' and base url; service name is added automatically
18697071
 #' @param queryName string name of the GMQL query file
83eb0624
 #' @param query string text of the GMQL query
48ab60c3
 #' @param output_gtf logical value indicating file format used for 
 #' storing samples generated by the query.
 #' The possiblities are: 
 #' \itemize{
 #' \item{GTF}
 #' \item{TAB}
 #' }
 #'
 #' @return None
 #'
 #' @details
83eb0624
 #' If error occurs, a specific error is printed
48ab60c3
 #'
 #' @examples
 #' 
 #' \dontrun{
83eb0624
 #' 
dda0cfa0
 #' ## Login to GMQL REST services suite as guest
 #' 
9089a38d
 #' remote_url = "http://www.gmql.eu/gmql-rest/"
48ab60c3
 #' login_gmql(remote_url)
dda0cfa0
 #' 
 #' ## Run query as string input parameter
 #' ## NOTE: not very suitable for long queries
 #' 
83eb0624
 #' run_query(remote_url, "query_1", "DATASET = SELECT() Example_Dataset1;
dda0cfa0
 #'     MATERIALIZE DATASET INTO RESULT_DS;", output_gtf = FALSE)
 #' 
 #' ## With system.file() this statement defines the path to the folder 
 #' ## "example" of the package "RGMQL", and then it executes the query 
 #' ## written in the text file "query1.txt"
48ab60c3
 #' 
 #' test_path <- system.file("example", package = "RGMQL")
 #' test_query <- file.path(test_path, "query1.txt")
83eb0624
 #' run_query_fromfile(remote_url, test_query, output_gtf = FALSE)
48ab60c3
 #' }
 #' 
 #' @rdname run_query
 #' @name run_query
 #' @export
 #'
73652f4d
 run_query <- function(url, queryName, query, output_gtf = TRUE) {
   if(output_gtf)
     out <- "GTF"
   else
     out <- "TAB"
   
   req <- httr::GET(url)
08b4a456
   url <- sub("/*[/]$","",req$url)
   URL <- paste0(url,"/queries/run/",queryName,"/",out)
73652f4d
   authToken = GMQL_credentials$authToken
   h <- c(
     'Accept' = "Application/json",
     'Content-Type' = 'text/plain',
     'X-Auth-Token' = authToken
   )
   
   req <- httr::POST(URL,body = query ,httr::add_headers(h),encode = "json")
   content <- httr::content(req,"parsed")
   if (req$status_code != 200) {
     stop(content$error)
   } else {
     return(content)
   }
48ab60c3
 }
 
 #' @import httr
18697071
 #' @param filePath string path of a txt file containing a GMQL query
48ab60c3
 #' 
 #' @rdname run_query
 #' @name run_query
 #' @export
 #' 
73652f4d
 run_query_fromfile <- function(url, filePath, output_gtf = TRUE) {
   if (!file.exists(filePath)) {
     stop("file does not exist")
   }
   
   query <- readLines(filePath)
   queryName <- sub('\\..*$', '', basename(filePath))
   run_query(url, queryName, query, output_gtf)
48ab60c3
 }
 
 #' Compile GMQL query
 #'
e5131ba8
 #' It compiles a GMQL query taken from file or inserted as text string, 
 #' using the proper GMQL web service available on a remote server
48ab60c3
 #' 
 #' 
 #' @import httr
 #' @param url string url of server: It must contain the server address 
 #' and base url; service name is added automatically
dda0cfa0
 #' @param query string text of a GMQL query
e5131ba8
 #' @param filePath string path of txt file containing a GMQL query
 #' 
48ab60c3
 #' @return None
 #'
 #' @examples
 #' 
e5131ba8
 #' ## Login to GMQL REST services suite as guest
 #' 
9089a38d
 #' remote_url = "http://www.gmql.eu/gmql-rest/"
48ab60c3
 #' login_gmql(remote_url)
e5131ba8
 #' 
dda0cfa0
 #' ## This statement gets the query as text string and runs the compile 
e5131ba8
 #' ## web service
 #' 
 #' compile_query(remote_url, "DATASET = SELECT() Example_Dataset_1;
dda0cfa0
 #'     MATERIALIZE DATASET INTO RESULT_DS;")
48ab60c3
 #' 
e5131ba8
 #' 
 #' ## This statement defines the path to the file "query1.txt" in the 
 #' ## subdirectory "example" of the package "RGMQL" and run the compile 
 #' ## web service
 #' 
48ab60c3
 #' test_path <- system.file("example", package = "RGMQL")
 #' test_query <- file.path(test_path, "query1.txt")
 #' compile_query_fromfile(remote_url, test_query)
18697071
 #' 
dda0cfa0
 #' ## Logout from GMQL REST services suite
18697071
 #' 
 #' logout_gmql(remote_url)
48ab60c3
 #' 
 #' @name compile_query
 #' @rdname compile_query
 #' @export
 #'
73652f4d
 compile_query <- function(url, query) {
   authToken = GMQL_credentials$authToken
   h <- c(
     'Accept' = "Application/json",
     'Content-Type' = 'text/plain',
     'X-Auth-Token' = authToken
   )
   req <- httr::GET(url)
08b4a456
   url <- sub("/*[/]$","",req$url)
   URL <- paste0(url, "/queries/compile")
73652f4d
   req <- httr::POST(
     URL, 
     body = query ,
     httr::add_headers(h), 
     encode = "json"
   )
   content <- httr::content(req, "parsed")
   if (req$status_code != 200) {
     stop(content$error)
   } else {
     return(content)
   }
48ab60c3
 }
 
 #' @name compile_query
 #' @rdname compile_query
 #' @export
 #'
73652f4d
 compile_query_fromfile <- function(url ,filePath) {
   if (!file.exists(filePath)) {
     stop("file does not exist")
   }
   
   query <- readLines(filePath)
   compile_query(url, query)
48ab60c3
 }
 
 #' Stop a job
 #'
 #' It stops a specific current query job
 #' 
 #' @import httr
 #' @param url string url of server: It must contain the server address 
 #' and base url; service name is added automatically
 #' @param job_id string id of the job
 #'
 #' @return None
 #'
 #' @details
18697071
 #' If error occurs, a specific error is printed
48ab60c3
 #'
 #' @examples
 #' 
 #' \dontrun{
 #' 
18697071
 #' ## Login to GMQL REST services suite at remote url
83eb0624
 #' 
9089a38d
 #' remote_url = "http://www.gmql.eu/gmql-rest/"
48ab60c3
 #' login_gmql(remote_url)
83eb0624
 #' 
dda0cfa0
 #' ## This statement shows all jobs at GMQL remote system and selects one 
 #' ## running job, saving it into 'jobs_1' (in this case is the first of the 
 #' ## list), and then stop it
83eb0624
 #' 
48ab60c3
 #' list_jobs <- show_jobs_list(remote_url)
 #' jobs_1 <- list_jobs$jobs[[1]]
 #' stop_job(remote_url, jobs_1)
 #' }
 #' 
 #' @name stop_job
 #' @rdname stop_job
 #' @export
 #'
73652f4d
 stop_job <- function(url, job_id) {
   url <- sub("/*[/]$", "", url)
   URL <- paste0(url, "/jobs/", job_id, "/stop")
   authToken = GMQL_credentials$authToken
   h <- c('X-Auth-Token' = authToken, 'Accept' = 'text/plain')
   req <- httr::GET(URL, httr::add_headers(h))
   content <- httr::content(req, "parsed")
   if (req$status_code != 200) {
     stop(content)
   } else {
     print(content)
   }
48ab60c3
 }
 
 #' Show a job log or trace
 #'
83eb0624
 #' It shows a job log or traces a specific job
48ab60c3
 #'
 #' @import httr
 #' @param url string url of server: It must contain the server address
 #' and base url; service name is added automatically
 #' @param job_id string id of the job
 #'
83eb0624
 #' @return Log or trace text
48ab60c3
 #'
 #' @details
18697071
 #' If error occurs, a specific error is printed
48ab60c3
 #'
 #' @examples
18697071
 #' ## Login to GMQL REST services suite as guest
5b358a31
 #' 
9089a38d
 #' remote_url = "http://www.gmql.eu/gmql-rest/"
48ab60c3
 #' login_gmql(remote_url)
 #' 
83eb0624
 #' ## List all jobs
48ab60c3
 #' list_jobs <- show_jobs_list(remote_url)
5b358a31
 #' 
 #' \dontrun{
48ab60c3
 #' jobs_1 <- list_jobs$jobs[[1]]
 #' 
dda0cfa0
 #' ## Show jobs_1 log
48ab60c3
 #' show_job_log(remote_url, jobs_1)
 #' 
dda0cfa0
 #' ## Trace jobs_1
48ab60c3
 #' trace_job(remote_url, jobs_1)
 #' 
 #' }
 #' 
 #' @name log_job
 #' @rdname log_job
 #' @export
 #'
73652f4d
 show_job_log <- function(url, job_id) {
   url <- sub("/*[/]$", "", url)
   URL <- paste0(url, "/jobs/", job_id, "/log")
   authToken = GMQL_credentials$authToken
   h <- c('X-Auth-Token' = authToken, 'Accept' = 'Application/json')
   req <- httr::GET(URL, httr::add_headers(h))
   content <- httr::content(req, "parsed")
   
   if (req$status_code != 200) {
     stop(content$error)
   } else {
     print(unlist(content, use.names = FALSE))
   }
48ab60c3
 }
 
 
 
 #' @import httr
 #' 
 #' @name trace_job
 #' @rdname log_job
 #' @export
 #'
73652f4d
 trace_job <- function(url, job_id) {
   url <- sub("/*[/]$", "", url)
   URL <- paste0(url, "/jobs/", job_id, "/trace")
   authToken = GMQL_credentials$authToken
   h <- c('X-Auth-Token' = authToken, 'Accept' = 'Application/json')
   req <- httr::GET(URL, httr::add_headers(h))
   content <- httr::content(req, "parsed")
  
    if (req$status_code != 200) {
     stop(content$error)
   } else {
     return(content)
   }
48ab60c3
 }
 
 #' Show all jobs
 #'
18697071
 #' It shows all jobs (run, succeded or failed) invoked by the user on remote 
 #' server using, the proper GMQL web service available on a remote server
5b358a31
 #' 
48ab60c3
 #' @import httr
 #' @param url string url of server: It must contain the server address 
 #' and base url; service name is added automatically
 #'
18697071
 #' @return List of jobs. Every job in the list is described by:
48ab60c3
 #' \itemize{
 #' \item{id: unique job identifier}
 #' }
 #'
 #' @details
83eb0624
 #' If error occurs, a specific error is printed
48ab60c3
 #'
 #' @examples
dda0cfa0
 #' ## Login to GMQL REST services suite as guest
 #' 
9089a38d
 #' remote_url = "http://www.gmql.eu/gmql-rest/"
48ab60c3
 #' login_gmql(remote_url)
dda0cfa0
 #' 
 #' ## List all jobs
48ab60c3
 #' list_jobs <- show_jobs_list(remote_url)
 #' 
 #' @rdname show_jobs_list
 #' @name show_jobs_list
 #' @export
 #' 
73652f4d
 show_jobs_list <- function(url) {
   url <- sub("/*[/]$", "", url)
   URL <- paste0(url, "/jobs")
   authToken = GMQL_credentials$authToken
   h <- c('X-Auth-Token' = authToken)
   req <- httr::GET(URL, httr::add_headers(h))
   content <- httr::content(req, "parsed")
   
   if (req$status_code != 200) {
     stop(content$error)
   } else {
     return(content)
   }
48ab60c3
 }
 
 #############################
 #       WEB DATASET        #
 ############################
 
83eb0624
 #' Show datasets
48ab60c3
 #'
18697071
 #' It shows all GMQL datasets stored by the user or public in remote 
 #' repository, using the proper GMQL web service available on a remote server
48ab60c3
 #' 
 #' @import httr
 #' @param url single string url of server: It must contain the server address 
 #' and base url; service name is added automatically
 #'
18697071
 #' @return List of datasets. Every dataset in the list is described by:
48ab60c3
 #' \itemize{
 #' \item{name: name of dataset}
 #' \item{owner: public or name of the user}
 #' }
 #'
 #' @details
83eb0624
 #' If error occurs, a specific error is printed
48ab60c3
 #'
 #' @examples
 #' 
dda0cfa0
 #' ## Login to GMQL REST services suite as guest
 #' 
9089a38d
 #' remote_url = "http://www.gmql.eu/gmql-rest/"
48ab60c3
 #' login_gmql(remote_url)
dda0cfa0
 #' 
 #' ## List all datasets
 #' 
48ab60c3
 #' list <- show_datasets_list(remote_url)
dda0cfa0
 #' 
18697071
 #' @name show_datasets_list
48ab60c3
 #' @rdname show_dataset
 #' @export
 #'
73652f4d
 show_datasets_list <- function(url) {
   url <- sub("/*[/]$", "", url)
   URL <- paste0(url, "/datasets")
   authToken = GMQL_credentials$authToken
   h <- c('X-Auth-Token' = authToken)
   req <- httr::GET(URL, httr::add_headers(h))
   content <- httr::content(req, "parsed") #JSON
   
   if (req$status_code != 200) {
     stop(content$error)
   } else {
     return(content)
   }
48ab60c3
 }
 
 
 #' Show dataset samples
 #'
18697071
 #' It show all samples from a specific GMQL dataset on remote repository, 
 #' using the proper GMQL web service available on a remote server
48ab60c3
 #' 
 #' @import httr
 #'
 #' @param url string url of server: It must contain the server address 
 #' and base url; service name is added automatically
18697071
 #' @param datasetName name of dataset containing the samples whose list we 
 #' like to get; if the dataset is a public dataset, we have to add "public." 
 #' as prefix, as shown in the example below, otherwise no prefix is needed
48ab60c3
 #'
18697071
 #' @return List of samples in dataset. Every sample in the list is described 
83eb0624
 #' by:
48ab60c3
 #' \itemize{
 #' \item{id: id of sample}
 #' \item{name: name of sample}
 #' \item{path: sample repository path}
 #' }
 #'
 #' @details
83eb0624
 #' If error occurs, a specific error is printed
48ab60c3
 #'
 #' @examples
 #' 
83eb0624
 #' ## Login to GMQL REST services suite as guest
 #' 
9089a38d
 #' remote_url = "http://www.gmql.eu/gmql-rest/"
48ab60c3
 #' login_gmql(remote_url)
83eb0624
 #' 
dda0cfa0
 #' ## This statement shows all samples present into public dataset 
 #' ## 'Example_Dataset_1'
83eb0624
 #' 
2f53c9a7
 #' list <- show_samples_list(remote_url, "public.Example_Dataset_1")
48ab60c3
 #' 
 #' @name show_samples_list
 #' @rdname show_samples_list
 #' @export
73652f4d
 show_samples_list <- function(url, datasetName) {
   url <- sub("/*[/]$", "", url)
   URL <- paste0(url, "/datasets/", datasetName)
   authToken = GMQL_credentials$authToken
   h <- c('X-Auth-Token' = authToken)
   req <- httr::GET(URL, httr::add_headers(h))
   content <- httr::content(req, "parsed")
   
   if (req$status_code != 200) {
     stop(content$error)
   } else {
     return(content)
   }
48ab60c3
 }
 
 #' Show dataset schema
 #'
18697071
 #' It shows the region attribute schema of a specific GMQL dataset on remote 
 #' repository, using the proper GMQL web service available on a remote server
48ab60c3
 #' 
 #' @import httr
 #' @param url string url of server: It must contain the server address 
 #' and base url; service name is added automatically
18697071
 #' @param datasetName name of dataset to get the schema;
48ab60c3
 #' if the dataset is a public dataset, we have to add "public." as prefix, 
18697071
 #' as shown in the example below, otherwise no prefix is needed
48ab60c3
 #'
18697071
 #' @return List of region schema fields. Every field in the list is described 
83eb0624
 #' by:
48ab60c3
 #' \itemize{
dda0cfa0
 #' \item{name: name of field (e.g. chr, start, end, strand, ...)}
83eb0624
 #' \item{fieldType: (e.g. STRING, DOUBLE, ...)}
48ab60c3
 #' }
 #'
 #' @details
83eb0624
 #' If error occurs, a specific error is printed
48ab60c3
 #' 
 #' @examples
83eb0624
 #' ## Login to GMQL REST services suite as guest
48ab60c3
 #' 
9089a38d
 #' remote_url = "http://www.gmql.eu/gmql-rest/"
48ab60c3
 #' login_gmql(remote_url)
83eb0624
 #' 
18697071
 #' ## Show schema of public dataset 'Example_Dataset_1'
83eb0624
 #' 
2f53c9a7
 #' list <- show_schema(remote_url, "public.Example_Dataset_1")
48ab60c3
 #' 
 #' @name show_schema
 #' @rdname show_schema
 #' @export
 #'
73652f4d
 show_schema <- function(url, datasetName) {
   url <- sub("/*[/]$", "", url)
   URL <- paste0(url, "/datasets/", datasetName, "/schema")
   authToken = GMQL_credentials$authToken
   h <- c('X-Auth-Token' = authToken)
   req <- httr::GET(URL, httr::add_headers(h))
   content <- httr::content(req, "parsed")
   
   if (req$status_code != 200) {
     stop(content$error)
   } else {
     return(content)
   }
48ab60c3
 }
 
 #' Upload dataset
 #'
 #'
 #' It uploads a folder (GMQL or not) containing sample files using 
 #' the proper GMQL web service available on a remote server: 
83eb0624
 #' a new dataset is created on remote repository
48ab60c3
 #' 
 #' @param url string url of server: It must contain the server address 
 #' and base url; service name is added automatically
83eb0624
 #' @param datasetName name of dataset to create in repository
 #' @param folderPath string local path to the folder containing the samples 
 #' files
 #' @param schemaName string name of schema used to parse the samples;
48ab60c3
 #' schemaName available are:
 #' \itemize{
 #' \item{NARROWPEAK}
 #' \item{BROADPEAK}
 #' \item{VCF}
 #' \item{BED}
 #' \item{BEDGRAPH}
 #' }
dda0cfa0
 #' if schemaName is NULL, it looks for a XML schema file to read in the 
18697071
 #' folderPath
83eb0624
 #' @param isGMQL logical value indicating whether it is uploaded a GMQL 
 #' dataset or not
48ab60c3
 #'
 #' @return None
 #'
 #' @details
83eb0624
 #' If no error occurs, it prints "Upload Complete", otherwise a specific error 
48ab60c3
 #' is printed
03d52325
 #' 
 #' NOTE: 
 #' The folder layout must obey the following rules and adopt 
 #' the following layout:
 #' The dataset folder can have any name, but must contains the 
 #' sub-folders named: "files".
 #' The sub-folder "files" contains the dataset files and 
 #' the schema xml file.
 #' The schema files adopt the following the naming conventions:
 #' 
 #' - "schema.xml"
 #' - "test.schema"
 #' 
 #' The names must be in LOWERCASE. Any other schema file 
 #' will not be conisdered, if both are present, "test.schema" will be used. 
 #' 
48ab60c3
 #' @examples
 #'
 #' \dontrun{
 #' 
83eb0624
 #' ## This statement defines the path to the folder "DATASET_GDM" in the 
 #' ## subdirectory "example" of the package "RGMQL"
 #' 
48ab60c3
 #' test_path <- system.file("example", "DATASET_GDM", package = "RGMQL")
83eb0624
 #' 
dda0cfa0
 #' ## Login to GMQL REST services suite at remote url
83eb0624
 #' 
9089a38d
 #' remote_url <- "http://www.gmql.eu/gmql-rest/"
48ab60c3
 #' login_gmql(remote_url)
83eb0624
 #' 
dda0cfa0
 #' ## Upload of GMQL dataset with "dataset1" as name, without specifying any 
83eb0624
 #' ## schema 
 #' 
48ab60c3
 #' upload_dataset(remote_url, "dataset1", folderPath = test_path)
83eb0624
 #' 
48ab60c3
 #' }
 #' @name upload_dataset
 #' @rdname upload_dataset
 #' @export
 #'
73652f4d
 upload_dataset <- function(
   url,
   datasetName,
   folderPath,
   schemaName = NULL
 ) {
   
03d52325
   folderPath <- sub("/*[/]$","",folderPath)
73652f4d
   if(basename(folderPath) !="files")
     folderPath <- file.path(folderPath,"files")
   
03d52325
   files <- list.files(folderPath, pattern = "*(.gtf|.gdm)", full.names = TRUE)
73652f4d
   if (!length(files)) {
     stop("no files present")
   }
   
   count = .counter(0)
03d52325
   
73652f4d
   list_files <- lapply(files, function(x) {
     file <- httr::upload_file(x)
   })
   
   list_files_names <- vapply(list_files, function(x) {
     paste0("file", count())
   }, character(1))
   
   names(list_files) <- list_files_names
   req <- httr::GET(url)
08b4a456
   real_URL <- sub("/*[/]$","",req$url)
   URL <- paste0(real_URL, "/datasets/", datasetName, "/uploadSample")
73652f4d
   authToken = GMQL_credentials$authToken
   h <- c('X-Auth-Token' = authToken, 'Accept:' = 'Application/json')
   
   schema_name <- tolower(schemaName)
   
03d52325
   if (is.null(schemaName) || identical(schema_name, "customparser")) {
73652f4d
     schema <- .retrieve_schema(folderPath)
48ab60c3
     
73652f4d
     list_files <- list(
       list("schema" = httr::upload_file(schema)),
       list_files
     )
     list_files <- unlist(list_files, recursive = FALSE)
08b4a456
     URL <- paste0(real_URL, "/datasets/", datasetName, "/uploadSample")
73652f4d
   } else {
03d52325
     schemaList <- c(
       "narrowpeak",
       "vcf",
       "broadpeak",
       "bed",
       "bedgraph"
     )
     if (!schema_name %in% schemaList) {
       stop("schema not admissable")
48ab60c3
     }
03d52325
     
     URL <- paste0(
       real_URL,
08b4a456
       "/datasets/",
03d52325
       datasetName,
       "/uploadSample?schemaName=",
       schema_name
     )
73652f4d
   }
   
   req <- httr::POST(URL, body = list_files , httr::add_headers(h))
   content <- httr::content(req)
   if (req$status_code != 200)
     stop(content)
   else
     print("upload Complete")
48ab60c3
 }
 
 #' Delete dataset
 #'
83eb0624
 #' It deletes single private dataset specified by name from remote repository 
48ab60c3
 #' using the proper GMQL web service available on a remote server
 #' 
 #' @import httr
 #'
 #' @param url string url of server: It must contain the server address 
 #' and base url; service name is added automatically
 #' @param datasetName string name of dataset to delete
 #'
 #' @return None
 #' 
 #' @details
18697071
 #' If no error occurs, it prints "Deleted Dataset", otherwise a specific error 
48ab60c3
 #' is printed
5b358a31
 #' 
48ab60c3
 #' @examples
 #'
 #' \dontrun{
 #' 
 #' ## This dataset does not exist
 #' 
9089a38d
 #' remote_url <- "http://www.gmql.eu/gmql-rest/"
48ab60c3
 #' login_gmql(remote_url)
e5131ba8
 #' delete_dataset(remote_url, "test1_20170604_180908_RESULT_DS")
48ab60c3
 #' 
 #' }
 #' 
 #' @name delete_dataset
 #' @rdname delete_dataset
 #' @export
 #'
73652f4d
 delete_dataset <- function(url, datasetName) {
   req <- httr::GET(url)
08b4a456
   real_URL <- sub("/*[/]$","",req$url)
   URL <- paste0(real_URL, "/datasets/", datasetName)
73652f4d
   authToken = GMQL_credentials$authToken
   h <- c('X-Auth-Token' = authToken, 'Accept:' = 'application/json')
   req <- httr::DELETE(URL, httr::add_headers(h))
   content <- httr::content(req, "parsed") #JSON
   
   if (req$status_code != 200) {
     stop(content$error)
   } else {
     print(content$result)
   }
48ab60c3
 }
 
 #' Download Dataset
 #'
83eb0624
 #' It donwloads private dataset as zip file from remote repository to local 
18697071
 #' path, or donwloads and saves it into R environment as GRangesList, using 
83eb0624
 #' the proper GMQL web service available on a remote server
48ab60c3
 #' 
 #' @import httr
 #' @importFrom utils unzip
 #'
 #' @param url string url of server: It must contain the server address 
18697071
 #' and base url; service name is added automatically
 #' @param datasetName string name of dataset to download
83eb0624
 #' @param path string local path folder where to store dataset,
 #' by default it is R working directory
48ab60c3
 #' @return None
 #'
 #' @details
83eb0624
 #' If error occurs, a specific error is printed
48ab60c3
 #'
 #' @examples
 #'
18697071
 #' ## Download dataset in R working directory
dda0cfa0
 #' ## In this case we try to download a dataset of the user 
 #' ## (public datasets from remote repository cannot be downloaded)
48ab60c3
 #' 
 #' \dontrun{
 #' 
9089a38d
 #' remote_url = "http://www.gmql.eu/gmql-rest/"
48ab60c3
 #' login_gmql(remote_url)
dda0cfa0
 #' download_dataset(remote_url, "Example_Dataset_1", path = getwd())
48ab60c3
 #' 
dda0cfa0
 #' ## Create GRangesList from user dataset Example_Dataset1 got 
48ab60c3
 #' ## from repository
 #' 
dda0cfa0
 #' download_as_GRangesList(remote_url, "Example_Dataset_1")
48ab60c3
 #' }
 #' 
 #' @name download_dataset
 #' @rdname download_dataset
 #' @export
 #'
73652f4d
 download_dataset <- function(url, datasetName, path = getwd()) {
   url <- sub("/*[/]$", "", url)
   URL <- paste0(url, "/datasets/", datasetName, "/zip")
   authToken = GMQL_credentials$authToken
   h <- c('X-Auth-Token' = authToken, 'Accept' = 'application/zip')
   req <- httr::GET(URL, httr::add_headers(h))
   
   content <- httr::content(req)
   if (req$status_code != 200) {
     stop(content)
   } else {
     zip_path <- file.path(path, paste0(datasetName, ".zip"))
     dir_out <- file.path(path, "")
     writeBin(content, zip_path)
     unzip(zip_path, exdir = dir_out)
     print("Download Complete")
   }
48ab60c3
 }
 
 #' @import httr
 #' @importClassesFrom GenomicRanges GRangesList
 #' @importFrom S4Vectors metadata
 #' 
18697071
 #' @return GRangesList containing all GMQL samples in dataset
48ab60c3
 #' 
 #' @name download_as_GRangesList
 #' @rdname download_dataset
 #' @export
 #'
73652f4d
 download_as_GRangesList <- function(url,datasetName) {
   list <- show_samples_list(url, datasetName)
   samples <- list$samples
   sample_list_name <- vapply(samples, function(x) x$name, character(1))
   
   sampleList <- lapply(samples, function(x) {
     name <- x$name
     range <- sample_region(url, datasetName, name)
   })
   
   names(sampleList) <- sample_list_name
   gRange_list <- GenomicRanges::GRangesList(sampleList)
   
   meta_list <- lapply(samples, function(x) {
     name <- x$name
     meta <- sample_metadata(url, datasetName, name)
   })
   names(meta_list) <- sample_list_name
   S4Vectors::metadata(gRange_list) <- meta_list
   return(gRange_list)
48ab60c3
 }
 
18697071
 #' Show metadata list from dataset sample
48ab60c3
 #'
18697071
 #' It retrieves metadata of a specific sample in dataset using the proper 
48ab60c3
 #' GMQL web service available on a remote server
 #' 
 #' @import httr
 #'
 #' @param url string url of server: It must contain the server address 
 #' and base url; service name is added automatically
18697071
 #' @param datasetName string name of dataset of interest
 #' @param sampleName string name of sample of interest
48ab60c3
 #'
83eb0624
 #' @return List of metadata in the form 'key = value'
48ab60c3
 #'
 #' @details
83eb0624
 #' If error occurs, a specific error is printed
48ab60c3
 #'
 #' @examples
83eb0624
 #' ## Login to GMQL REST services suite as guest
48ab60c3
 #' 
9089a38d
 #' remote_url = "http://www.gmql.eu/gmql-rest/"
48ab60c3
 #' login_gmql(remote_url)
83eb0624
 #' 
18697071
 #' ## This statement retrieves metadata of sample 'S_00000' from public 
 #' ## dataset 'Example_Dataset_1'
83eb0624
 #' 
2f53c9a7
 #' sample_metadata(remote_url, "public.Example_Dataset_1", "S_00000")
48ab60c3
 #' 
 #'
 #' @name sample_metadata
 #' @rdname sample_metadata
 #' @export
 #'
73652f4d
 sample_metadata <- function(url, datasetName,sampleName) {
   url <- sub("/*[/]$", "", url)
   URL <- paste0(url, "/datasets/", datasetName, "/", sampleName, "/metadata")
   authToken = GMQL_credentials$authToken
   h <- c('X-Auth-Token' = authToken, 'Accpet' = 'text/plain')
   req <- httr::GET(URL, httr::add_headers(h))
   content <- httr::content(req, 'text', encoding = "UTF-8")
   
   #trasform text to list
   metadata <- strsplit(content, "\n")
   metadata <- strsplit(unlist(metadata), "\t")
   names(metadata) <- vapply(metadata, `[[`, character(1), 1)
   listMeta <- lapply(metadata, `[`,-1)
   
   if (req$status_code != 200) {
     stop(content)
   } else {
     return(listMeta)
   }
48ab60c3
 }
 
dda0cfa0
 #' Show regions data from a dataset sample
48ab60c3
 #' 
18697071
 #' It retrieves regions data of a specific sample (whose name is specified in 
 #' the parameter "sampleName") in a specific dataset (whose name is specified 
 #' in the parameter "datasetName") using the proper GMQL web service 
 #' available on a remote server
48ab60c3
 #' 
 #' @import httr
 #' @importFrom rtracklayer import
 #' @importFrom data.table fread
 #' @importFrom GenomicRanges makeGRangesFromDataFrame
 #' @importFrom utils write.table
 #'
18697071
 #' @param url string url of server. It must contain the server address
48ab60c3
 #' and base url; service name is added automatically
18697071
 #' @param datasetName string name of dataset of interest
 #' @param sampleName string name of sample of interest
48ab60c3
 #'
83eb0624
 #' @return GRanges data containing regions of sample
48ab60c3
 #'
 #' @details
83eb0624
 #' If error occurs, a specific error is printed
48ab60c3
 #'
 #' @examples
 #' 
 #' \dontrun{
83eb0624
 #' 
 #' ## Login to GMQL REST services suite as guest
 #' 
9089a38d
 #' remote_url = "http://www.gmql.eu/gmql-rest/"
48ab60c3
 #' login_gmql(remote_url)
83eb0624
 #' 
18697071
 #' ## This statement retrieves regions data of sample "S_00000" from public 
 #' ## dataset "Example_Dataset_1"
83eb0624
 #'  
2f53c9a7
 #' sample_region(remote_url, "public.Example_Dataset_1", "S_00000")
83eb0624
 #' 
48ab60c3
 #' }
 #' 
 #' @name sample_region
 #' @rdname sample_region
 #' @export
 #'
73652f4d
 sample_region <- function(url, datasetName,sampleName) {
   url <- sub("/*[/]$","",url)
   URL <- paste0(url,"/datasets/",datasetName,"/",sampleName,"/region")
   authToken = GMQL_credentials$authToken
   h <- c('X-Auth-Token' = authToken, 'Accpet' = 'text/plain')
   req <- httr::GET(URL, httr::add_headers(h))
   content <- httr::content(req, 'parsed',encoding = "UTF-8")
   
   if(req$status_code != 200) {
     stop(content)
   } else {
     list <- show_schema(url,datasetName)
     schema_type <- list$type
c7602281
     
73652f4d
     temp <- tempfile("temp") #use temporary files
     write.table(
       content,
       temp,
       quote = FALSE,
       sep = '\t',
       col.names = FALSE,
       row.names = FALSE
     )
     if (identical(schema_type, "gtf")) {
       samples <- rtracklayer::import(temp, format = "gtf")
     } else {
       vector_field <- vapply(list$fields, function(x) x$name, character(1))
       df <- data.table::fread(temp, header = FALSE, sep = "\t")
       a <- df[1, 2]
       if(is.na(as.numeric(a)))
         df <- df[-1]
       data.table::setnames(df,vector_field)
       samples <- GenomicRanges::makeGRangesFromDataFrame(
         df,
         keep.extra.columns = TRUE,
         start.field = "left",
         end.field = "right",
         strand.field="strand"
       )
48ab60c3
     }
73652f4d
     unlink(temp)
     return(samples)
   }
48ab60c3
 }
 
 #############################
 #        WEB UTILS         #
 ############################
 
 # no export
73652f4d
 serialize_query <- function(url,output_gtf,base64) {
   if(output_gtf) {
     out <- "gtf"
   } else {
     out <- "tab"
   }
   url <- sub("/*[/]$","",url)
   req <- httr::GET(url)
08b4a456
   real_URL <- sub("/*[/]$","",req$url)
73652f4d
   authToken = GMQL_credentials$authToken
08b4a456
   URL <- paste0(real_URL,"/queries/dag/",out)
73652f4d
   h <- c(
     'Accept' = "Application/json",
     'Content-Type' = 'text/plain',
     'X-Auth-Token' = authToken
   )
   
   req <- httr::POST(URL,body = base64 ,httr::add_headers(h),encode = "json")
   content <- httr::content(req,"parsed")
   if (req$status_code != 200) {
     stop(content$error)
   } else {
     return(content)
   }
 }
 
 
03d52325
 .retrieve_schema <- function(folderPath, duringReading = F) {
73652f4d
   schema_SCHEMA <- list.files(
     folderPath, pattern = "test.schema$", full.names = TRUE
   )
   
   xml_schema <- list.files(
     folderPath, pattern = "schema.xml$", full.names = TRUE
   )
   
   if(!length(schema_SCHEMA) && !length(xml_schema))
     stop("schema not present")
   
   schema <- if(!length(schema_SCHEMA)) 
     xml_schema 
   else
03d52325
     if(!duringReading) {
       schema_SCHEMA
     } else {
       folderPath
     }
73652f4d
   
   schema
48ab60c3
 }