... | ... |
@@ -78,31 +78,29 @@ biocViews: |
78 | 78 |
Network, |
79 | 79 |
SingleCell |
80 | 80 |
Collate: |
81 |
- 'GMQLDataset-class.R' |
|
82 |
- 'Cover.R' |
|
83 |
- 'Difference.R' |
|
84 |
- 'Extend.R' |
|
81 |
+ 'AllClasses.R' |
|
82 |
+ 'AllGenerics.R' |
|
85 | 83 |
'GMQL4TFarm.R' |
86 | 84 |
'GMQLtoGRanges.R' |
87 | 85 |
'GRangesToGMQL.R' |
88 |
- 'Join.R' |
|
89 |
- 'Map.R' |
|
90 |
- 'Materialize.R' |
|
91 |
- 'Merge.R' |
|
92 |
- 'Order.R' |
|
93 |
- 'Project.R' |
|
94 |
- 'Read.R' |
|
95 |
- 'Select.R' |
|
96 |
- 'Union.R' |
|
86 |
+ 'S3Aggregates.R' |
|
87 |
+ 'S3Cover-Param.R' |
|
88 |
+ 'S3Distal.R' |
|
89 |
+ 'S3Operator.R' |
|
97 | 90 |
'Utils.R' |
98 |
- 'aggregate-class.R' |
|
99 |
- 'authOp.R' |
|
100 |
- 'browseOp.R' |
|
101 |
- 'cover_param-class.R' |
|
102 |
- 'datasetOp.R' |
|
103 |
- 'distal-class.R' |
|
104 |
- 'evaluation_functions.R' |
|
91 |
+ 'evaluation-functions.R' |
|
92 |
+ 'gmql_cover.R' |
|
93 |
+ 'gmql_difference.R' |
|
94 |
+ 'gmql_extend.R' |
|
95 |
+ 'gmql_join.R' |
|
96 |
+ 'gmql_map.R' |
|
97 |
+ 'gmql_materialize.R' |
|
98 |
+ 'gmql_merge.R' |
|
99 |
+ 'gmql_order.R' |
|
100 |
+ 'gmql_project.R' |
|
101 |
+ 'gmql_read.R' |
|
102 |
+ 'gmql_select.R' |
|
103 |
+ 'gmql_union.R' |
|
105 | 104 |
'onLoad.R' |
106 |
- 'operator-class.R' |
|
107 |
- 'ordering-class.R' |
|
108 |
- 'queryOp.R' |
|
105 |
+ 'ordering-functions.R' |
|
106 |
+ 'web-services.R' |
... | ... |
@@ -29,7 +29,6 @@ export(SQRT) |
29 | 29 |
export(STD) |
30 | 30 |
export(SUM) |
31 | 31 |
export(UP) |
32 |
-export(arrange) |
|
33 | 32 |
export(collect) |
34 | 33 |
export(compile_query) |
35 | 34 |
export(compile_query_fromfile) |
... | ... |
@@ -52,7 +51,6 @@ export(sample_metadata) |
52 | 51 |
export(sample_region) |
53 | 52 |
export(save_query) |
54 | 53 |
export(save_query_fromfile) |
55 |
-export(select) |
|
56 | 54 |
export(semijoin) |
57 | 55 |
export(show_datasets_list) |
58 | 56 |
export(show_job_log) |
... | ... |
@@ -61,7 +59,6 @@ export(show_queries_list) |
61 | 59 |
export(show_samples_list) |
62 | 60 |
export(show_schema) |
63 | 61 |
export(stop_job) |
64 |
-export(take) |
|
65 | 62 |
export(trace_job) |
66 | 63 |
export(upload_dataset) |
67 | 64 |
exportMethods(aggregate) |
68 | 65 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,34 @@ |
1 |
+#' Class GMQLDataset |
|
2 |
+#' |
|
3 |
+#' Abstract class representing GMQL dataset |
|
4 |
+#' |
|
5 |
+#' @importClassesFrom S4Vectors DataTable |
|
6 |
+#' @slot value value associated to GMQL dataset |
|
7 |
+#' @name GMQLDataset-class |
|
8 |
+#' @rdname GMQLDataset-class |
|
9 |
+#' |
|
10 |
+#' @return instance of GMQL dataset |
|
11 |
+#' |
|
12 |
+setClass("GMQLDataset", |
|
13 |
+ contains = c("DataTable"), |
|
14 |
+ representation(value = "character")) |
|
15 |
+ |
|
16 |
+#' @name GMQLDataset |
|
17 |
+#' @importFrom methods new |
|
18 |
+#' |
|
19 |
+#' @param value value associated to GMQL dataset |
|
20 |
+#' @rdname GMQLDataset-class |
|
21 |
+#' |
|
22 |
+GMQLDataset <- function(value) { |
|
23 |
+ dataset <- new("GMQLDataset",value = value) |
|
24 |
+ return(dataset) |
|
25 |
+} |
|
26 |
+ |
|
27 |
+setMethod("show", "GMQLDataset", |
|
28 |
+ function(object) |
|
29 |
+ { |
|
30 |
+ cat("GMQL Dataset \n") |
|
31 |
+ cat(" value :",paste(object@value)) |
|
32 |
+ }) |
|
33 |
+ |
|
34 |
+ |
0 | 35 |
similarity index 62% |
1 | 36 |
rename from R/GMQLDataset-class.R |
2 | 37 |
rename to R/AllGenerics.R |
... | ... |
@@ -1,44 +1,3 @@ |
1 |
-#' Class GMQLDataset |
|
2 |
-#' |
|
3 |
-#' Abstract class representing GMQL dataset |
|
4 |
-#' |
|
5 |
-#' @importClassesFrom S4Vectors DataTable |
|
6 |
-#' @slot value value associated to GMQL dataset |
|
7 |
-#' @name GMQLDataset-class |
|
8 |
-#' @rdname GMQLDataset-class |
|
9 |
-#' |
|
10 |
-#' @return instance of GMQL dataset |
|
11 |
- |
|
12 |
-setClass("GMQLDataset", |
|
13 |
- contains = c("DataTable"), |
|
14 |
- representation(value = "character")) |
|
15 |
- |
|
16 |
-#' @name GMQLDataset |
|
17 |
-#' @importFrom methods new |
|
18 |
-#' |
|
19 |
-#' @param value value associated to GMQL dataset |
|
20 |
-#' @rdname GMQLDataset-class |
|
21 |
-#' |
|
22 |
-GMQLDataset <- function(value) { |
|
23 |
- dataset <- new("GMQLDataset",value = value) |
|
24 |
- return(dataset) |
|
25 |
-} |
|
26 |
- |
|
27 |
-setMethod("show", "GMQLDataset", |
|
28 |
- function(object) |
|
29 |
- { |
|
30 |
- cat("GMQL Dataset \n") |
|
31 |
- cat(" value :",paste(object@value)) |
|
32 |
- }) |
|
33 |
- |
|
34 |
- |
|
35 |
- |
|
36 |
-# insted of GMQL order |
|
37 |
-# setGeneric("sort", function(data, metadata_ordering = NULL, |
|
38 |
-# regions_ordering = NULL, fetch_opt = NULL, |
|
39 |
-# num_fetch = 0, reg_fetch_opt = NULL, |
|
40 |
-# reg_num_fetch = 0) standardGeneric("sort")) |
|
41 |
- |
|
42 | 1 |
#' Method aggregate |
43 | 2 |
#' |
44 | 3 |
#' Wrapper to GMQL merge function |
... | ... |
@@ -71,9 +30,7 @@ setGeneric("filter", function(.data, m_predicate = NULL, r_predicate = NULL, |
71 | 30 |
#' @rdname cover-GMQLDataset-method |
72 | 31 |
#' @aliases cover |
73 | 32 |
#' |
74 |
-setGeneric("cover", function(data, min_acc, max_acc, groupBy = NULL, |
|
75 |
- variation = "cover", ...) |
|
76 |
- standardGeneric("cover")) |
|
33 |
+setGeneric("cover", function(data, ...) standardGeneric("cover")) |
|
77 | 34 |
|
78 | 35 |
#' Method map |
79 | 36 |
#' |
... | ... |
@@ -103,7 +60,6 @@ setGeneric("collect", function(x, dir_out = getwd(), name = "ds1", ...) |
103 | 60 |
#' |
104 | 61 |
#' @name take |
105 | 62 |
#' @rdname take-GMQLDataset-method |
106 |
-#' @export |
|
107 | 63 |
setGeneric("take", function(data, ...) standardGeneric("take")) |
108 | 64 |
|
109 | 65 |
|
... | ... |
@@ -114,7 +70,6 @@ setGeneric("take", function(data, ...) standardGeneric("take")) |
114 | 70 |
#' @name extend |
115 | 71 |
#' @rdname extend-GMQLDataset-method |
116 | 72 |
#' @aliases extend GMQLDataset-method |
117 |
-#' @exportMethod extend |
|
118 | 73 |
setGeneric("extend", function(.data, ...) standardGeneric("extend")) |
119 | 74 |
|
120 | 75 |
|
... | ... |
@@ -125,7 +80,6 @@ setGeneric("extend", function(.data, ...) standardGeneric("extend")) |
125 | 80 |
#' @name select |
126 | 81 |
#' @rdname select-GMQLDataset-method |
127 | 82 |
#' @aliases select |
128 |
-#' @export |
|
129 | 83 |
setGeneric("select", function(.data, ...) standardGeneric("select")) |
130 | 84 |
|
131 | 85 |
#' Method arrange |
... | ... |
@@ -135,7 +89,6 @@ setGeneric("select", function(.data, ...) standardGeneric("select")) |
135 | 89 |
#' @name arrange |
136 | 90 |
#' @rdname arrange-GMQLDataset-method |
137 | 91 |
#' @aliases arrange |
138 |
-#' @export |
|
139 | 92 |
#' |
140 | 93 |
setGeneric("arrange", function(.data, metadata_ordering = NULL, |
141 | 94 |
regions_ordering = NULL, fetch_opt = NULL, num_fetch = 0, |
4 | 9 |
similarity index 95% |
5 | 10 |
rename from R/cover_param-class.R |
6 | 11 |
rename to R/S3Cover-Param.R |
... | ... |
@@ -34,7 +34,7 @@ print.PARAMETER <- function(obj){ |
34 | 34 |
#' |
35 | 35 |
#' @examples |
36 | 36 |
#' |
37 |
-#' #' init_gmql() |
|
37 |
+#' init_gmql() |
|
38 | 38 |
#' test_path <- system.file("example", "DATASET", package = "RGMQL") |
39 | 39 |
#' exp = read_dataset(test_path) |
40 | 40 |
#' |
... | ... |
@@ -43,14 +43,14 @@ print.PARAMETER <- function(obj){ |
43 | 43 |
#' ## of two overlapping regions in the input samples, |
44 | 44 |
#' ## up to maximum amount of overlapping regions. |
45 | 45 |
#' |
46 |
-#' res = cover(exp, 2, "ALL") |
|
46 |
+#' res = cover(exp, 2, ALL()) |
|
47 | 47 |
#' |
48 | 48 |
#' ## This statement produces an output dataset with a single output sample. |
49 | 49 |
#' ## The COVER operation considers all areas defined by a minimum |
50 | 50 |
#' ## of two overlapping regions in the input samples, |
51 | 51 |
#' ## up to any amount of overlapping regions. |
52 | 52 |
#' |
53 |
-#' res = cover(exp, 2, "ANY") |
|
53 |
+#' res = cover(exp, 2, ANY()+2/3) |
|
54 | 54 |
#' |
55 | 55 |
#' @name COVER-PARAMETER |
56 | 56 |
#' @rdname cover-param-class |
63 | 63 |
deleted file mode 100644 |
... | ... |
@@ -1,133 +0,0 @@ |
1 |
-if(getRversion() >= "2.15.1") |
|
2 |
- utils::globalVariables("authToken") |
|
3 |
- |
|
4 |
-if(getRversion() >= "3.1.0") |
|
5 |
- utils::suppressForeignCheck("authToken") |
|
6 |
- |
|
7 |
-#' Login to GMQL |
|
8 |
-#' |
|
9 |
-#' Login to GMQL REST services suite as a registered user, specifying username |
|
10 |
-#' and password, or as guest using the proper GMQL web service available |
|
11 |
-#' on a remote server |
|
12 |
-#' |
|
13 |
-#' @import httr |
|
14 |
-#' @importFrom rJava J |
|
15 |
-#' |
|
16 |
-#' @param url string url of server: It must contain the server address |
|
17 |
-#' and base url; service name is added automatically |
|
18 |
-#' @param username string name used during signup |
|
19 |
-#' @param password string password used during signup |
|
20 |
-#' |
|
21 |
-#' @seealso \code{\link{logout_gmql}} |
|
22 |
-#' |
|
23 |
-#' @details |
|
24 |
-#' if both username and password are NULL you will be logged as guest |
|
25 |
-#' After login you will receive an authentication token. |
|
26 |
-#' As token remains vaild on server (until the next login / registration) |
|
27 |
-#' a user can safely use a token fora previous session as a convenience, |
|
28 |
-#' this token is saved in Global environment to perform subsequent REST call |
|
29 |
-#' even on complete R restart (if is environemnt has been saved, of course ...) |
|
30 |
-#' If error occures a specific error is printed |
|
31 |
-#' |
|
32 |
-#' @return None |
|
33 |
-#' |
|
34 |
-#' @examples |
|
35 |
-#' ## login as guest |
|
36 |
-#' remote_url = "http://130.186.13.219/gmql-rest" |
|
37 |
-#' \dontrun{ |
|
38 |
-#' login_gmql(remote_url) |
|
39 |
-#' } |
|
40 |
-#' @export |
|
41 |
- |
|
42 |
-#' |
|
43 |
-login_gmql <- function(url, username = NULL, password = NULL) |
|
44 |
-{ |
|
45 |
- if(exists("authToken",envir = .GlobalEnv)) |
|
46 |
- { |
|
47 |
- print("You are already logged") |
|
48 |
- return(invisible(NULL)) |
|
49 |
- } |
|
50 |
- as_guest <- TRUE |
|
51 |
- |
|
52 |
- if(!is.null(username) || !is.null(password)) |
|
53 |
- as_guest <- FALSE |
|
54 |
- |
|
55 |
- if(as_guest) |
|
56 |
- { |
|
57 |
- h <- c('Accept' = "Application/json") |
|
58 |
- URL <- paste0(url,"/guest") |
|
59 |
- req <- httr::GET(URL,httr::add_headers(h)) |
|
60 |
- } |
|
61 |
- else |
|
62 |
- { |
|
63 |
- h <- c('Accept'="Application/json",'Content-Type'='Application/json') |
|
64 |
- URL <- paste0(url,"/login") |
|
65 |
- body <- list('username' = username,'password' = password) |
|
66 |
- req <- httr::POST(URL,httr::add_headers(h),body = body,encode = "json") |
|
67 |
- } |
|
68 |
- |
|
69 |
- content <- httr::content(req) |
|
70 |
- |
|
71 |
- if(req$status_code !=200) |
|
72 |
- stop(content$errorString) |
|
73 |
- else |
|
74 |
- { |
|
75 |
- assign("authToken",content$authToken,.GlobalEnv) |
|
76 |
- WrappeR <- J("it/polimi/genomics/r/Wrapper") |
|
77 |
- WrappeR$save_tokenAndUrl(authToken,url) |
|
78 |
- print(paste("your Token is",authToken)) |
|
79 |
- } |
|
80 |
-} |
|
81 |
- |
|
82 |
-#' Logout from GMQL |
|
83 |
-#' |
|
84 |
-#' Logout from GMQL REST services suite |
|
85 |
-#' using the proper GMQL web service available on a remote server |
|
86 |
-#' |
|
87 |
-#' @import httr |
|
88 |
-#' @importFrom rJava J |
|
89 |
-#' |
|
90 |
-#' @param url string url of server: It must contain the server address |
|
91 |
-#' and base url; service name is added automatically |
|
92 |
-#' |
|
93 |
-#' @seealso \code{\link{login_gmql}} |
|
94 |
-#' |
|
95 |
-#' @details |
|
96 |
-#' After logout the authentication token will be invalidated. |
|
97 |
-#' The authentication token is removed from Global environment |
|
98 |
-#' If error occures a specific error is printed |
|
99 |
-#' |
|
100 |
-#' @examples |
|
101 |
-#' |
|
102 |
-#' ## login as guest, then logout |
|
103 |
-#' remote_url = "http://130.186.13.219/gmql-rest" |
|
104 |
-#' \dontrun{ |
|
105 |
-#' login_gmql(remote_url) |
|
106 |
-#' logout_gmql(remote_url) |
|
107 |
-#' } |
|
108 |
-#' @return None |
|
109 |
-#' |
|
110 |
-#' @export |
|
111 |
-#' |
|
112 |
-logout_gmql <- function(url) |
|
113 |
-{ |
|
114 |
- URL <- paste0(url,"/logout") |
|
115 |
- h <- c('X-Auth-Token' = authToken) |
|
116 |
- req <- httr::GET(URL, httr::add_headers(h)) |
|
117 |
- content <- httr::content(req) |
|
118 |
- |
|
119 |
- if(req$status_code !=200) |
|
120 |
- stop(content$error) |
|
121 |
- else |
|
122 |
- { |
|
123 |
- print(content) |
|
124 |
- #delete token from environment |
|
125 |
- WrappeR <- J("it/polimi/genomics/r/Wrapper") |
|
126 |
- WrappeR$delete_token() |
|
127 |
- if(exists("authToken",envir = .GlobalEnv)) |
|
128 |
- rm(authToken, envir = .GlobalEnv) |
|
129 |
- } |
|
130 |
-} |
|
131 |
- |
|
132 |
- |
|
133 |
- |
134 | 0 |
deleted file mode 100644 |
... | ... |
@@ -1,128 +0,0 @@ |
1 |
-#' Shows all Queries |
|
2 |
-#' |
|
3 |
-#' It shows all the GMQL query saved on repository |
|
4 |
-#' using the proper GMQL web service available on a remote server |
|
5 |
-#' |
|
6 |
-#' @import httr |
|
7 |
-#' |
|
8 |
-#' @param url string url of server: It must contain the server address |
|
9 |
-#' and base url; service name is added automatically |
|
10 |
-#' |
|
11 |
-#' @return list of queries |
|
12 |
-#' Every query in the list is identified by: |
|
13 |
-#' \itemize{ |
|
14 |
-#' \item{name: name of query} |
|
15 |
-#' \item{text: text of GMQL query} |
|
16 |
-#' } |
|
17 |
-#' @seealso \code{\link{save_query}} |
|
18 |
-#' |
|
19 |
-#' @details |
|
20 |
-#' if error occures, a specific error is printed |
|
21 |
-#' |
|
22 |
-#' @examples |
|
23 |
-#' remote_url = "http://130.186.13.219/gmql-rest" |
|
24 |
-#' |
|
25 |
-#' \dontrun{ |
|
26 |
-#' login_gmql(remote_url) |
|
27 |
-#' list <- show_queries_list(remote_url) |
|
28 |
-#' } |
|
29 |
-#' @export |
|
30 |
-#' |
|
31 |
-show_queries_list <- function(url) |
|
32 |
-{ |
|
33 |
- URL <- paste0(url,"/query") |
|
34 |
- h <- c('Accept' = 'Application/json', 'X-Auth-Token' = authToken) |
|
35 |
- req <- httr::GET(URL, httr::add_headers(h)) |
|
36 |
- content <- httr::content(req,"parsed") |
|
37 |
- if(req$status_code==200) |
|
38 |
- return(content) |
|
39 |
- else |
|
40 |
- stop(content$error) |
|
41 |
-} |
|
42 |
- |
|
43 |
-#' Save GMQL query |
|
44 |
-#' |
|
45 |
-#' It saves the GMQL query into repository |
|
46 |
-#' using the proper GMQL web service available on a remote server |
|
47 |
-#' |
|
48 |
-#' @import httr |
|
49 |
-#' |
|
50 |
-#' @param url string url of server: It must contain the server address |
|
51 |
-#' and base url; service name is added automatically |
|
52 |
-#' @param queryName string name of query |
|
53 |
-#' @param queryTxt string text of GMQL query |
|
54 |
-#' |
|
55 |
-#' @return None |
|
56 |
-#' |
|
57 |
-#' @seealso \code{\link{show_queries_list}} \code{\link{save_query_fromfile}} |
|
58 |
-#' |
|
59 |
-#' |
|
60 |
-#' @details |
|
61 |
-#' if you save a query with the same name of an other query already stored |
|
62 |
-#' in repository you will overwrite it, |
|
63 |
-#' if no error occures print "Saved" otherwise print the content error |
|
64 |
-#' |
|
65 |
-#' @examples |
|
66 |
-#' remote_url = "http://130.186.13.219/gmql-rest" |
|
67 |
-#' \dontrun{ |
|
68 |
-#' |
|
69 |
-#' login_gmql(remote_url) |
|
70 |
-#' save_query(remote_url, "dna_query", "DATASET = SELECT() HG19_TCGA_dnaseq; |
|
71 |
-#' MATERIALIZE DATASET INTO RESULT_DS;") |
|
72 |
-#' } |
|
73 |
-#' @export |
|
74 |
-#' |
|
75 |
-save_query <- function(url, queryName, queryTxt) |
|
76 |
-{ |
|
77 |
- URL <- paste0(url,"/query/",queryName,"/save") |
|
78 |
- h <- c('Accept' = 'text/plain', 'X-Auth-Token' = authToken, |
|
79 |
- 'Content-Type' = 'text/plain') |
|
80 |
- req <- httr::POST(URL, httr::add_headers(h),body = queryTxt) |
|
81 |
- content <- httr::content(req) |
|
82 |
- |
|
83 |
- if(req$status_code==200) |
|
84 |
- print(content) # print Saved |
|
85 |
- else |
|
86 |
- stop(content$error) |
|
87 |
-} |
|
88 |
- |
|
89 |
-#' Save GMQL query from file |
|
90 |
-#' |
|
91 |
-#' It saves the GMQL query into repository taken from file |
|
92 |
-#' using the proper GMQL web service available on a remote server |
|
93 |
-#' |
|
94 |
-#' |
|
95 |
-#' |
|
96 |
-#' @param url string url of server: It must contain the server address |
|
97 |
-#' and base url; service name is added automatically |
|
98 |
-#' @param queryName string name of the GMQL query |
|
99 |
-#' @param filePath string local file path of txt file containing a GMQL query |
|
100 |
-#' |
|
101 |
-#' @return None |
|
102 |
-#' |
|
103 |
-#' @seealso \code{\link{save_query}} |
|
104 |
-#' |
|
105 |
-#' @details |
|
106 |
-#' if you save a query with the same name of an other query already stored |
|
107 |
-#' in repository you will overwrite it, |
|
108 |
-#' if no error occures print "Saved" otherwise print the content error |
|
109 |
-#' |
|
110 |
-#' @examples |
|
111 |
-#' test_path <- system.file("example", package = "RGMQL") |
|
112 |
-#' test_query <- file.path(test_path, "query1.txt") |
|
113 |
-#' remote_url = "http://130.186.13.219/gmql-rest" |
|
114 |
-#' \dontrun{ |
|
115 |
-#' |
|
116 |
-#' login_gmql(remote_url) |
|
117 |
-#' save_query_fromfile(remote_url, "query1", test_query) |
|
118 |
-#' } |
|
119 |
-#' @export |
|
120 |
-#' |
|
121 |
-save_query_fromfile <- function(url, queryName, filePath) |
|
122 |
-{ |
|
123 |
- if(!file.exists(filePath)) |
|
124 |
- stop("file does not exist") |
|
125 |
- |
|
126 |
- queryTxt <- readLines(filePath) |
|
127 |
- save_query(url,queryName,queryTxt) |
|
128 |
-} |
129 | 0 |
deleted file mode 100644 |
... | ... |
@@ -1,532 +0,0 @@ |
1 |
-#' Show Dataset |
|
2 |
-#' |
|
3 |
-#' It show all GMQL dataset stored in repository using the proper GMQL |
|
4 |
-#' web service available on a remote server |
|
5 |
-#' |
|
6 |
-#' |
|
7 |
-#' @import httr |
|
8 |
-#' @param url single string url of server: It must contain the server address |
|
9 |
-#' and base url; service name is added automatically |
|
10 |
-#' |
|
11 |
-#' @return list of datasets. |
|
12 |
-#' |
|
13 |
-#' Every dataset in the list is identified by: |
|
14 |
-#' \itemize{ |
|
15 |
-#' \item{name: name of dataset} |
|
16 |
-#' \item{owner: public or name of the user} |
|
17 |
-#' } |
|
18 |
-#' |
|
19 |
-#' @seealso \code{\link{delete_dataset}} |
|
20 |
-#' |
|
21 |
-#' @details |
|
22 |
-#' If error occures a specific error is printed |
|
23 |
-#' |
|
24 |
-#' @examples |
|
25 |
-#' |
|
26 |
-#' @examples |
|
27 |
-#' remote_url = "http://130.186.13.219/gmql-rest" |
|
28 |
-#' \dontrun{ |
|
29 |
-#' login_gmql(remote_url) |
|
30 |
-#' list <- show_datasets_list(remote_url) |
|
31 |
-#' } |
|
32 |
-#' @export |
|
33 |
-#' |
|
34 |
-show_datasets_list <- function(url) |
|
35 |
-{ |
|
36 |
- URL <- paste0(url,"/datasets") |
|
37 |
- |
|
38 |
- h <- c('X-Auth-Token' = authToken) |
|
39 |
- req <- httr::GET(URL, httr::add_headers(h)) |
|
40 |
- content <- httr::content(req,"parsed") #JSON |
|
41 |
- if(req$status_code !=200) |
|
42 |
- stop(content$error) |
|
43 |
- else |
|
44 |
- return(content) |
|
45 |
-} |
|
46 |
- |
|
47 |
-#' Show dataset samples |
|
48 |
-#' |
|
49 |
-#' It show all sample from a specific GMQL dataset using the proper |
|
50 |
-#' GMQL web service available on a remote server |
|
51 |
-#' |
|
52 |
-#' @import httr |
|
53 |
-#' |
|
54 |
-#' @param url string url of server: It must contain the server address |
|
55 |
-#' and base url; service name is added automatically |
|
56 |
-#' @param datasetName name of dataset to get |
|
57 |
-#' if the dataset is a public dataset, we have to add "public." as prefix, |
|
58 |
-#' as shown in the example below otherwise no prefix is needed |
|
59 |
-#' |
|
60 |
-#' @return list of samples in dataset. |
|
61 |
-#' |
|
62 |
-#' Every sample in the list is identified by: |
|
63 |
-#' \itemize{ |
|
64 |
-#' \item{id: id of sample} |
|
65 |
-#' \item{name: name of sample} |
|
66 |
-#' \item{path: sample repository path} |
|
67 |
-#' } |
|
68 |
-#' |
|
69 |
-#' @details |
|
70 |
-#' If error occures a specific error is printed |
|
71 |
-#' |
|
72 |
-#' @examples |
|
73 |
-#' remote_url = "http://130.186.13.219/gmql-rest" |
|
74 |
-#' \dontrun{ |
|
75 |
-#' login_gmql(remote_url) |
|
76 |
-#' list <- show_samples_list(remote_url, "public.HG19_BED_ANNOTATION") |
|
77 |
-#' } |
|
78 |
-#' @export |
|
79 |
-#' |
|
80 |
-show_samples_list <- function(url,datasetName) |
|
81 |
-{ |
|
82 |
- URL <- paste0(url,"/datasets/",datasetName) |
|
83 |
- h <- c('X-Auth-Token' = authToken) |
|
84 |
- req <- httr::GET(URL, httr::add_headers(h)) |
|
85 |
- content <- httr::content(req,"parsed") |
|
86 |
- if(req$status_code !=200) |
|
87 |
- stop(content$error) |
|
88 |
- else |
|
89 |
- return(content) |
|
90 |
-} |
|
91 |
- |
|
92 |
- |
|
93 |
-#' Show dataset schema |
|
94 |
-#' |
|
95 |
-#' It shows the region attribute schema of a specific GMQL dataset using |
|
96 |
-#' the proper GMQL web service available on a remote server |
|
97 |
-#' |
|
98 |
-#' @import httr |
|
99 |
-#' @param url string url of server: It must contain the server address |
|
100 |
-#' and base url; service name is added automatically |
|
101 |
-#' @param datasetName name of dataset to get |
|
102 |
-#' if the dataset is a public dataset, we have to add "public." as prefix, |
|
103 |
-#' as shown in the example below otherwise no prefix is needed |
|
104 |
-#' |
|
105 |
-#' @return list of region schema fields. |
|
106 |
-#' |
|
107 |
-#' Every field in the list is identified by: |
|
108 |
-#' \itemize{ |
|
109 |
-#' \item{name: name of field (e.g. chr, start, end, strand ...)} |
|
110 |
-#' \item{fieldType: (e.g STRING, DOUBLE ...)} |
|
111 |
-#' } |
|
112 |
-#' |
|
113 |
-#' @details |
|
114 |
-#' If error occures a specific error is printed |
|
115 |
-#' |
|
116 |
-#' |
|
117 |
-#' @examples |
|
118 |
-#' remote_url = "http://130.186.13.219/gmql-rest" |
|
119 |
-#' \dontrun{ |
|
120 |
-#' login_gmql(remote_url) |
|
121 |
-#' list <- show_schema(remote_url, "public.HG19_BED_ANNOTATION") |
|
122 |
-#'} |
|
123 |
-#' @export |
|
124 |
-#' |
|
125 |
-show_schema <- function(url,datasetName) |
|
126 |
-{ |
|
127 |
- URL <- paste0(url,"/datasets/",datasetName,"/schema") |
|
128 |
- h <- c('X-Auth-Token' = authToken) |
|
129 |
- #req <- GET(url, add_headers(h),verbose(data_in = TRUE,info = TRUE)) |
|
130 |
- req <- httr::GET(URL, httr::add_headers(h)) |
|
131 |
- content <- httr::content(req,"parsed") |
|
132 |
- if(req$status_code != 200) |
|
133 |
- stop(content$error) |
|
134 |
- else |
|
135 |
- return(content) |
|
136 |
-} |
|
137 |
- |
|
138 |
- |
|
139 |
-#' Upload dataset |
|
140 |
-#' |
|
141 |
-#' |
|
142 |
-#' It uploads a folder (GMQL or not) containing sample files using |
|
143 |
-#' the proper GMQL web service available on a remote server: |
|
144 |
-#' a new dataset is created on repository |
|
145 |
-#' |
|
146 |
-#' @param url string url of server: It must contain the server address |
|
147 |
-#' and base url; service name is added automatically |
|
148 |
-#' @param datasetName name of dataset to get |
|
149 |
-#' @param folderPath string local path to the folder containing the samples |
|
150 |
-#' @param schemaName string name of schema used to parse the samples |
|
151 |
-#' schemaName available are: |
|
152 |
-#' \itemize{ |
|
153 |
-#' \item{NARROWPEAK} |
|
154 |
-#' \item{BROADPEAK} |
|
155 |
-#' \item{VCF} |
|
156 |
-#' \item{BED} |
|
157 |
-#' \item{BEDGRAPH} |
|
158 |
-#' } |
|
159 |
-#' if schema is NULL it's looking for a XML schema file to read |
|
160 |
-#' @param isGMQL logical value indicating whether is GMQL dataset or not |
|
161 |
-#' |
|
162 |
-#' @return None |
|
163 |
-#' |
|
164 |
-#' @details |
|
165 |
-#' If no error occures print "Upload Complete", otherwise a specific error |
|
166 |
-#' is printed |
|
167 |
-#' |
|
168 |
-#' @examples |
|
169 |
-#' |
|
170 |
-#' \dontrun{ |
|
171 |
-#' |
|
172 |
-#' ### upload of GMQL dataset with no schema selection |
|
173 |
-#' test_path <- system.file("example", "DATASET_GDM", package = "RGMQL") |
|
174 |
-#' remote_url <- "http://130.186.13.219/gmql-rest" |
|
175 |
-#' login_gmql(remote_url) |
|
176 |
-#' upload_dataset(remote_url, "dataset1", folderPath = test_path) |
|
177 |
-#' } |
|
178 |
-#' |
|
179 |
-#' @export |
|
180 |
-#' |
|
181 |
-upload_dataset <- function(url,datasetName,folderPath,schemaName=NULL, |
|
182 |
- isGMQL=TRUE) |
|
183 |
-{ |
|
184 |
- if(isGMQL) |
|
185 |
- folderPath <- paste0(folderPath,"/files") |
|
186 |
- |
|
187 |
- files <- list.files(folderPath,full.names = TRUE) |
|
188 |
- if(length(files)==0) |
|
189 |
- stop("no files present") |
|
190 |
- count = .counter(0) |
|
191 |
- |
|
192 |
- list_files <- lapply(files, function(x) { |
|
193 |
- file <- httr::upload_file(x) |
|
194 |
- }) |
|
195 |
- |
|
196 |
- list_files_names <- sapply(list_files, function(x) { |
|
197 |
- paste0("file",count()) |
|
198 |
- }) |
|
199 |
- |
|
200 |
- names(list_files) <- list_files_names |
|
201 |
- URL <- paste0(url,"/datasets/",datasetName,"/uploadSample") |
|
202 |
- h <- c('X-Auth-Token' = authToken, 'Accept:' = 'Application/json') |
|
203 |
- |
|
204 |
- schema_name <- tolower(schemaName) |
|
205 |
- |
|
206 |
- if(is.null(schemaName)) |
|
207 |
- { |
|
208 |
- schema_name <- list.files(folderPath, pattern = "*.schema$", |
|
209 |
- full.names = TRUE) |
|
210 |
- if(length(schema_name)==0) |
|
211 |
- stop("schema must be present") |
|
212 |
- |
|
213 |
- list_files <- list(list("schema" = httr::upload_file(schema_name)), |
|
214 |
- list_files) |
|
215 |
- list_files <- unlist(list_files,recursive = FALSE) |
|
216 |
- |
|
217 |
- URL <- paste0(url,"/datasets/",datasetName,"/uploadSample") |
|
218 |
- } |
|
219 |
- else |
|
220 |
- { |
|
221 |
- schema_name <- tolower(schemaName) |
|
222 |
- if(identical(schema_name,"customparser")) |
|
223 |
- { |
|
224 |
- schema_name <- list.files(folderPath, pattern = "*.schema$", |
|
225 |
- full.names = TRUE) |
|
226 |
- if(length(schema_name)==0) |
|
227 |
- stop("schema must be present") |
|
228 |
- |
|
229 |
- list_files <- list(list("schema" = httr::upload_file(schema_name)), |
|
230 |
- list_files) |
|
231 |
- list_files <- unlist(list_files,recursive = FALSE) |
|
232 |
- |
|
233 |
- URL <- paste0(url,"/datasets/",datasetName,"/uploadSample") |
|
234 |
- } |
|
235 |
- else |
|
236 |
- { |
|
237 |
- if(!identical(schema_name,"narrowpeak") && |
|
238 |
- !identical(schema_name,"vcf") && |
|
239 |
- !identical(schema_name,"broadpeak") && |
|
240 |
- !identical(schema_name,"bed") && |
|
241 |
- !identical(schema_name,"bedgraph")) |
|
242 |
- stop("schema not admissable") |
|
243 |
- |
|
244 |
- URL <- paste0(url,"/datasets/",datasetName, |
|
245 |
- "/uploadSample?schemaName=",schema_name) |
|
246 |
- } |
|
247 |
- } |
|
248 |
- |
|
249 |
- req <- httr::POST(URL, body = list_files ,httr::add_headers(h)) |
|
250 |
- content <- httr::content(req) |
|
251 |
- if(req$status_code !=200) |
|
252 |
- print(content) |
|
253 |
- else |
|
254 |
- print("upload Complete") |
|
255 |
-} |
|
256 |
- |
|
257 |
-#' Delete dataset |
|
258 |
-#' |
|
259 |
-#' It deletes single private dataset specified by name from repository |
|
260 |
-#' using the proper GMQL web service available on a remote server |
|
261 |
-#' |
|
262 |
-#' @import httr |
|
263 |
-#' |
|
264 |
-#' @param url string url of server: It must contain the server address |
|
265 |
-#' and base url; service name is added automatically |
|
266 |
-#' @param datasetName string name of dataset to delete |
|
267 |
-#' |
|
268 |
-#' @return None |
|
269 |
-#' |
|
270 |
-#' |
|
271 |
-#' @details |
|
272 |
-#' If no error occur, print "Deleted Dataset", otherwise a specific error |
|
273 |
-#' is printed |
|
274 |
-#' |
|
275 |
-#' @seealso \code{\link{download_dataset}} |
|
276 |
-#' |
|
277 |
-#' @examples |
|
278 |
-#' |
|
279 |
-#' \dontrun{ |
|
280 |
-#' |
|
281 |
-#' ## This dataset does not exist |
|
282 |
-#' |
|
283 |
-#' remote_url <- "http://130.186.13.219/gmql-rest" |
|
284 |
-#' login_gmql(remote_url) |
|
285 |
-#' delete_dataset(remote_url, "job_test1_test101_20170604_180908_RESULT_DS") |
|
286 |
-#' |
|
287 |
-#' } |
|
288 |
-#' |
|
289 |
-#' @export |
|
290 |
-#' |
|
291 |
-delete_dataset <- function(url,datasetName) |
|
292 |
-{ |
|
293 |
- URL <- paste0(url,"/datasets/",datasetName) |
|
294 |
- h <- c('X-Auth-Token' = authToken, 'Accept:' = 'application/json') |
|
295 |
- req <- httr::DELETE(URL, httr::add_headers(h)) |
|
296 |
- content <- httr::content(req,"parsed") #JSON |
|
297 |
- |
|
298 |
- if(req$status_code !=200) |
|
299 |
- stop(content$error) |
|
300 |
- else |
|
301 |
- print(content$result) |
|
302 |
-} |
|
303 |
- |
|
304 |
-#' Download Dataset |
|
305 |
-#' |
|
306 |
-#' It donwloads private dataset as zip file from repository to local path |
|
307 |
-#' specified using the proper GMQL web service available on a remote server |
|
308 |
-#' |
|
309 |
-#' @import httr |
|
310 |
-#' @importFrom utils unzip |
|
311 |
-#' |
|
312 |
-#' @param url string url of server: It must contain the server address |
|
313 |
-#' and base url; service name will be added automatically |
|
314 |
-#' @param datasetName string name of dataset we want to get |
|
315 |
-#' @param path string local path folder where store dataset, |
|
316 |
-#' by defualt is R working directory |
|
317 |
-#' @return None |
|
318 |
-#' |
|
319 |
-#' @details |
|
320 |
-#' If error occures a specific error is printed |
|
321 |
-#' |
|
322 |
-#' |
|
323 |
-#' @examples |
|
324 |
-#' |
|
325 |
-#' ## download dataset in r working directory |
|
326 |
-#' ## in this case we try to download public dataset |
|
327 |
-#' |
|
328 |
-#' \dontrun{ |
|
329 |
-#' |
|
330 |
-#' remote_url = "http://130.186.13.219/gmql-rest" |
|
331 |
-#' login_gmql(remote_url) |
|
332 |
-#' download_dataset(remote_url, "public.HG19_BED_ANNOTATION", path = getwd()) |
|
333 |
-#' } |
|
334 |
-#' @export |
|
335 |
-#' |
|
336 |
-download_dataset <- function(url,datasetName,path = getwd()) |
|
337 |
-{ |
|
338 |
- URL <- paste0(url,"/datasets/",datasetName,"/zip") |
|
339 |
- h <- c('X-Auth-Token' = authToken, 'Accept' = 'application/zip') |
|
340 |
- req <- httr::GET(URL,httr::add_headers(h)) |
|
341 |
- |
|
342 |
- content <- httr::content(req) |
|
343 |
- if(req$status_code !=200) |
|
344 |
- print(content) |
|
345 |
- else |
|
346 |
- { |
|
347 |
- zip_path <- paste0(path,"/",datasetName,".zip") |
|
348 |
- dir_out <-paste0(path,"/") |
|
349 |
- writeBin(content,zip_path) |
|
350 |
- unzip(zip_path,exdir=dir_out) |
|
351 |
- print("Download Complete") |
|
352 |
- } |
|
353 |
-} |
|
354 |
- |
|
355 |
-#' Download Dataset in GrangesList |
|
356 |
-#' |
|
357 |
-#' It donwloads private dataset from repository saving into R environemnt |
|
358 |
-#' as GrangesList |
|
359 |
-#' |
|
360 |
-#' @import httr |
|
361 |
-#' @importClassesFrom GenomicRanges GRangesList |
|
362 |
-#' @importFrom S4Vectors metadata |
|
363 |
-#' |
|
364 |
-#' @param url string url of server: It must contain the server address |
|
365 |
-#' and base url; service name is added automatically |
|
366 |
-#' @param datasetName string name of dataset we want to get |
|
367 |
-#' |
|
368 |
-#' @return GrangesList containing all GMQL sample in dataset |
|
369 |
-#' |
|
370 |
-#' @details |
|
371 |
-#' If error occures a specific error is printed |
|
372 |
-#' |
|
373 |
-#' |
|
374 |
-#' @examples |
|
375 |
-#' |
|
376 |
-#' \dontrun{ |
|
377 |
-#' ## create grangeslist from public dataset HG19_BED_ANNOTATION got |
|
378 |
-#' ## from repository |
|
379 |
-#' |
|
380 |
-#' remote_url = "http://130.186.13.219/gmql-rest" |
|
381 |
-#' login_gmql(remote_url) |
|
382 |
-#' download_as_GRangesList(remote_url, "public.HG19_BED_ANNOTATION") |
|
383 |
-#' } |
|
384 |
-#' |
|
385 |
-#' @export |
|
386 |
-#' |
|
387 |
-download_as_GRangesList <- function(url,datasetName) |
|
388 |
-{ |
|
389 |
- list <- show_samples_list(url,datasetName) |
|
390 |
- samples <- list$samples |
|
391 |
- sample_list_name <- sapply(samples, function(x){ |
|
392 |
- name <- x$name |
|
393 |
- }) |
|
394 |
- |
|
395 |
- sampleList <- lapply(samples, function(x){ |
|
396 |
- name <- x$name |
|
397 |
- range <- sample_region(url,datasetName,name) |
|
398 |
- }) |
|
399 |
- |
|
400 |
- names(sampleList) <- sample_list_name |
|
401 |
- gRange_list <- GenomicRanges::GRangesList(sampleList) |
|
402 |
- |
|
403 |
- meta_list <- lapply(samples, function(x){ |
|
404 |
- name <- x$name |
|
405 |
- meta <- sample_metadata(url,datasetName,name) |
|
406 |
- }) |
|
407 |
- names(meta_list) <- sample_list_name |
|
408 |
- S4Vectors::metadata(gRange_list) <- meta_list |
|
409 |
- return(gRange_list) |
|
410 |
-} |
|
411 |
- |
|
412 |
- |
|
413 |
- |
|
414 |
- |
|
415 |
-#' Shows metadata list from dataset sample |
|
416 |
-#' |
|
417 |
-#' It retrieves metadata for a specific sample in dataset using the proper |
|
418 |
-#' GMQL web service available on a remote server |
|
419 |
-#' |
|
420 |
-#' @import httr |
|
421 |
-#' |
|
422 |
-#' @param url string url of server: It must contain the server address |
|
423 |
-#' and base url; service name is added automatically |
|
424 |
-#' @param datasetName string name of dataset to get |
|
425 |
-#' @param sampleName string sample name to get |
|
426 |
-#' |
|
427 |
-#' @return list of metadata in the form 'key = value' |
|
428 |
-#' |
|
429 |
-#' @details |
|
430 |
-#' If error occures a specific error is printed |
|
431 |
-#' |
|
432 |
-#' @examples |
|
433 |
-#' remote_url = "http://130.186.13.219/gmql-rest" |
|
434 |
-#' \dontrun{ |
|
435 |
-#' login_gmql(remote_url) |
|
436 |
-#' sample_metadata(remote_url, "public.HG19_BED_ANNOTATION", "genes") |
|
437 |
-#'} |
|
438 |
-#' @export |
|
439 |
-#' |
|
440 |
-sample_metadata <- function(url, datasetName,sampleName) |
|
441 |
-{ |
|
442 |
- URL <- paste0(url,"/datasets/",datasetName,"/",sampleName,"/metadata") |
|
443 |
- h <- c('X-Auth-Token' = authToken, 'Accpet' = 'text/plain') |
|
444 |
- #req <- GET(url, add_headers(h),verbose(data_in = TRUE,info = TRUE)) |
|
445 |
- req <- httr::GET(URL, httr::add_headers(h)) |
|
446 |
- content <- httr::content(req, 'text',encoding = "UTF-8") |
|
447 |
- |
|
448 |
- #trasform text to list |
|
449 |
- metadata <- strsplit(content, "\n") |
|
450 |
- metadata <- strsplit(unlist(metadata), "\t") |
|
451 |
- names(metadata) <- sapply(metadata, `[[`, 1) |
|
452 |
- listMeta <- lapply(metadata, `[`, -1) |
|
453 |
- |
|
454 |
- if(req$status_code !=200) |
|
455 |
- stop(content) |
|
456 |
- else |
|
457 |
- return(listMeta) |
|
458 |
-} |
|
459 |
- |
|
460 |
- |
|
461 |
-#' Shows regions from a dataset sample |
|
462 |
-#' |
|
463 |
-#' It retrieves regions for a specific sample |
|
464 |
-#' (whose name is specified in the paramter "sampleName") |
|
465 |
-#' in a specific dataset |
|
466 |
-#' (whose name is specified in the parameter "datasetName") |
|
467 |
-#' using the proper GMQL web service available on a remote server |
|
468 |
-#' |
|
469 |
-#' @import httr |
|
470 |
-#' @importFrom rtracklayer import |
|
471 |
-#' @importFrom data.table fread |
|
472 |
-#' @importFrom GenomicRanges makeGRangesFromDataFrame |
|
473 |
-#' @importFrom utils write.table |
|
474 |
-#' |
|
475 |
-#' @param url string url of server: it must contain the server address |
|
476 |
-#' and base url; service name is added automatically |
|
477 |
-#' @param datasetName string name of dataset to get |
|
478 |
-#' @param sampleName string sample name to get |
|
479 |
-#' |
|
480 |
-#' @return Granges data containing regions of sample |
|
481 |
-#' |
|
482 |
-#' @details |
|
483 |
-#' If error occures a specific error is printed |
|
484 |
-#' |
|
485 |
-#' @examples |
|
486 |
-#' remote_url = "http://130.186.13.219/gmql-rest" |
|
487 |
-#' \dontrun{ |
|
488 |
-#' login_gmql(remote_url) |
|
489 |
-#' sample_region(remote_url, "public.HG19_BED_ANNOTATION", "genes") |
|
490 |
-#' } |
|
491 |
-#' |
|
492 |
-#' @export |
|
493 |
-#' |
|
494 |
-sample_region <- function(url, datasetName,sampleName) |
|
495 |
-{ |
|
496 |
- URL <- paste0(url,"/datasets/",datasetName,"/",sampleName,"/region") |
|
497 |
- h <- c('X-Auth-Token' = authToken, 'Accpet' = 'text/plain') |
|
498 |
- req <- httr::GET(URL, httr::add_headers(h)) |
|
499 |
- content <- httr::content(req, 'parsed',encoding = "UTF-8") |
|
500 |
- |
|
501 |
- if(req$status_code !=200) |
|
502 |
- stop(content) |
|
503 |
- else |
|
504 |
- { |
|
505 |
- list <- show_schema(url,datasetName) |
|
506 |
- schema_type <- list$type |
|
507 |
- |
|
508 |
- temp <- tempfile("temp") #use temporary files |
|
509 |
- write.table(content,temp,quote = FALSE,sep = '\t',col.names = FALSE, |
|
510 |
- row.names = FALSE) |
|
511 |
- if(schema_type=="gtf") |
|
512 |
- samples <- rtracklayer::import(temp,format = "gtf") |
|
513 |
- else |
|
514 |
- { |
|
515 |
- vector_field <- sapply(list$fields,function(x){ |
|
516 |
- name <- x$name |
|
517 |
- }) |
|
518 |
- df <- data.table::fread(temp,header = FALSE,sep = "\t") |
|
519 |
- a <- df[1,2] |
|
520 |
- if(is.na(as.numeric(a))) |
|
521 |
- df <- df[-1] |
|
522 |
- data.table::setnames(df,vector_field) |
|
523 |
- samples <- GenomicRanges::makeGRangesFromDataFrame(df, |
|
524 |
- keep.extra.columns = TRUE, |
|
525 |
- start.field = "left", |
|
526 |
- end.field = "right", |
|
527 |
- strand.field="strand") |
|
528 |
- } |
|
529 |
- unlink(temp) |
|
530 |
- return(samples) |
|
531 |
- } |
|
532 |
-} |
533 | 0 |
similarity index 97% |
534 | 1 |
rename from R/evaluation_functions.R |
535 | 2 |
rename to R/evaluation-functions.R |
... | ... |
@@ -18,7 +18,7 @@ |
18 | 18 |
#' DEFAULT evaluation: the two attributes match if both end with value.} |
19 | 19 |
#' } |
20 | 20 |
#' |
21 |
-#' @param ... string identifying name of metadata attribute |
|
21 |
+#' @param ... series of string identifying name of metadata attribute |
|
22 | 22 |
#' to be evaluated |
23 | 23 |
#' |
24 | 24 |
#' @return list of 2-D array containing method of evaluation and metadata |
... | ... |
@@ -29,7 +29,6 @@ |
29 | 29 |
#' test_path <- system.file("example", "DATASET", package = "RGMQL") |
30 | 30 |
#' r = read_dataset(test_path) |
31 | 31 |
#' |
32 |
-#' |
|
33 | 32 |
#' @name evaluation |
34 | 33 |
#' @rdname condition_eval_func |
35 | 34 |
#' @export |
36 | 35 |
similarity index 93% |
37 | 36 |
rename from R/Cover.R |
38 | 37 |
rename to R/gmql_cover.R |
... | ... |
@@ -22,7 +22,7 @@ |
22 | 22 |
#' Input samples that do not satisfy the \emph{groupby} condition |
23 | 23 |
#' are disregarded. |
24 | 24 |
#' |
25 |
-#' @include GMQLDataset-class.R |
|
25 |
+#' @include AllClasses.R |
|
26 | 26 |
#' @importFrom methods is |
27 | 27 |
#' @importFrom rJava J |
28 | 28 |
#' @importFrom rJava .jnull |
... | ... |
@@ -110,7 +110,7 @@ |
110 | 110 |
#' init_gmql() |
111 | 111 |
#' test_path <- system.file("example","DATASET",package = "RGMQL") |
112 | 112 |
#' exp = read_dataset(test_path) |
113 |
-#' res = cover(exp, 2, "ANY") |
|
113 |
+#' res = cover(exp, 2, ANY()) |
|
114 | 114 |
#' |
115 | 115 |
#' \dontrun{ |
116 | 116 |
#' ## This GMQL statement computes the result grouping the input exp samples |
... | ... |
@@ -134,8 +134,14 @@ setMethod("cover", "GMQLDataset", |
134 | 134 |
variation = "cover", ...) |
135 | 135 |
{ |
136 | 136 |
val <- data@value |
137 |
- q_max <- .check_cover_param(max_acc,FALSE) |
|
138 |
- q_min <- .check_cover_param(min_acc,FALSE) |
|
137 |
+ s_min <- substitute(min_acc) |
|
138 |
+ s_min <- .trasform_cover(deparse(s_min)) |
|
139 |
+ s_max <- substitute(max_acc) |
|
140 |
+ s_max <- .trasform_cover(deparse(s_max)) |
|
141 |
+ |
|
142 |
+ q_max <- .check_cover_param(s_max,FALSE) |
|
143 |
+ q_min <- .check_cover_param(s_min,TRUE) |
|
144 |
+ |
|
139 | 145 |
flag = toupper(variation) |
140 | 146 |
aggregates = list(...) |
141 | 147 |
gmql_cover(val, q_min, q_max, groupBy, aggregates, flag) |
... | ... |
@@ -198,14 +204,9 @@ gmql_cover <- function(data, min_acc, max_acc, groupBy = NULL, |
198 | 204 |
} |
199 | 205 |
else if(is.character(param)) |
200 | 206 |
{ |
201 |
- if(is.na(as.numeric(param))) |
|
202 |
- { |
|
203 |
- if(is_min && identical(param,"ANY")) |
|
204 |
- stop("min cannot assume ANY as value") |
|
205 |
- |
|
206 |
- if(!identical(param,"ANY") && !identical(param,"ALL")) |
|
207 |
- stop("invalid input data") |
|
208 |
- } |
|
207 |
+ if(is_min && identical(param,"ANY")) |
|
208 |
+ stop("min cannot assume ANY as value") |
|
209 |
+ |
|
209 | 210 |
return(param) |
210 | 211 |
} |
211 | 212 |
else |
239 | 240 |
similarity index 98% |
240 | 241 |
rename from R/Select.R |
241 | 242 |
rename to R/gmql_select.R |
... | ... |
@@ -14,7 +14,7 @@ |
14 | 14 |
#' @importFrom rJava .jnull |
15 | 15 |
#' @importFrom rJava .jarray |
16 | 16 |
#' @importFrom methods isClass |
17 |
-#' |
|
17 |
+#' |
|
18 | 18 |
#' @param .data GMQLDataset class object |
19 | 19 |
#' @param m_predicate logical predicate made up by R logical operation |
20 | 20 |
#' on metadata attribute. |
... | ... |
@@ -66,7 +66,7 @@ |
66 | 66 |
#' |
67 | 67 |
#' } |
68 | 68 |
#' |
69 |
-#' @aliases filter, filter-method |
|
69 |
+#' @aliases filter filter-method |
|
70 | 70 |
#' @export |
71 | 71 |
setMethod("filter", "GMQLDataset", |
72 | 72 |
function(.data, m_predicate = NULL, r_predicate = NULL, |
... | ... |
@@ -143,7 +143,7 @@ gmql_select <- function(input_data, predicate, region_predicate, s_join) |
143 | 143 |
#' if both end with value.} |
144 | 144 |
#' } |
145 | 145 |
#' |
146 |
-#' @return semijoin condition as matrix |
|
146 |
+#' @return semijoin condition as list |
|
147 | 147 |
#' @export |
148 | 148 |
#' |
149 | 149 |
semijoin <- function(data, not_in = FALSE, ...) |
7 | 7 |
deleted file mode 100644 |
... | ... |
@@ -1,341 +0,0 @@ |
1 |
-#' Show all jobs |
|
2 |
-#' |
|
3 |
-#' It show all Jobs (run, succeded or failed) invoked by user |
|
4 |
-#' @import httr |
|
5 |
-#' @param url string url of server: It must contain the server address |
|
6 |
-#' and base url; service name is added automatically |
|
7 |
-#' |
|
8 |
-#' @return list of jobs |
|
9 |
-#' Every job in the list is identified by: |
|
10 |
-#' \itemize{ |
|
11 |
-#' \item{id: unique job identifier} |
|
12 |
-#' } |
|
13 |
-#' |
|
14 |
-#' @seealso \code{\link{show_job_log}} @seealso \code{\link{stop_job}} |
|
15 |
-#' @seealso \code{\link{trace_job}} |
|
16 |
-#' |
|
17 |
-#' @details |
|
18 |
-#' If error occures a specific error is printed |
|
19 |
-#' |
|
20 |
-#' @examples |
|
21 |
-#' remote_url = "http://130.186.13.219/gmql-rest" |
|
22 |
-#' \dontrun{ |
|
23 |
-#' login_gmql(remote_url) |
|
24 |
-#' list_jobs <- show_jobs_list(remote_url) |
|
25 |
-#' } |
|
26 |
-#' @export |
|
27 |
-#' |
|
28 |
-show_jobs_list <- function(url) |
|
29 |
-{ |
|
30 |
- URL <- paste0(url,"/jobs") |
|
31 |
- h <- c('X-Auth-Token' = authToken) |
|
32 |
- req <- httr::GET(URL, httr::add_headers(h)) |
|
33 |
- content <- httr::content(req,"parsed") |
|
34 |
- if(req$status_code !=200) |
|
35 |
- stop(content$error) |
|
36 |
- else |
|
37 |
- return(content) |
|
38 |
-} |
|
39 |
- |
|
40 |
-#' Show a job log |
|
41 |
-#' |
|
42 |
-#' It show a job log for specific job |
|
43 |
-#' |
|
44 |
-#' @import httr |
|
45 |
-#' @param url string url of server: It must contain the server address |
|
46 |
-#' and base url; service name is added automatically |
|
47 |
-#' @param job_id string id of the job |
|
48 |
-#' |
|
49 |
-#' @return log text |
|
50 |
-#' |
|
51 |
-#' @details |
|
52 |
-#' If error occures a specific error is printed |
|
53 |
-#' |
|
54 |
-#' @examples |
|
55 |
-#' remote_url = "http://130.186.13.219/gmql-rest" |
|
56 |
-#' \dontrun{ |
|
57 |
-#' login_gmql(remote_url) |
|
58 |
-#' |
|
59 |
-#' ## list all jobs |
|
60 |
-#' list_jobs <- show_jobs_list(remote_url) |
|
61 |
-#' jobs_1 <- list_jobs$jobs[[1]] |
|
62 |
-#' |
|
63 |
-#' ## show log |
|
64 |
-#' show_job_log(remote_url, jobs_1) |
|
65 |
-#' |
|
66 |
-#' } |
|
67 |
-#' |
|
68 |
-#' @export |
|
69 |
-#' |
|
70 |
-show_job_log <- function(url, job_id) |
|
71 |
-{ |
|
72 |
- URL <- paste0(url,"/jobs/",job_id,"/log") |
|
73 |
- h <- c('X-Auth-Token' = authToken,'Accept'= 'Application/json') |
|
74 |
- req <- httr::GET(URL, httr::add_headers(h)) |
|
75 |
- content <- httr::content(req,"parsed") |
|
76 |
- if(req$status_code !=200) |
|
77 |
- stop(content$error) |
|
78 |
- else |
|
79 |
- print(unlist(content,use.names = FALSE)) |
|
80 |
-} |
|
81 |
- |
|
82 |
-#' Stop a job |
|
83 |
-#' |
|
84 |
-#' It stops a specific current job |
|
85 |
-#' |
|
86 |
-#' @import httr |
|
87 |
-#' @param url string url of server: It must contain the server address |
|
88 |
-#' and base url; service name is added automatically |
|
89 |
-#' @param job_id string id of the job |
|
90 |
-#' |
|
91 |
-#' @return None |
|
92 |
-#' |
|
93 |
-#' @details |
|
94 |
-#' If error occures a specific error is printed |
|
95 |
-#' |
|
96 |
-#' @examples |
|
97 |
-#' remote_url = "http://130.186.13.219/gmql-rest" |
|
98 |
-#' \dontrun{ |
|
99 |
-#' login_gmql(remote_url) |
|
100 |
-#' list_jobs <- show_jobs_list(remote_url) |
|
101 |
-#' jobs_1 <- list_jobs$jobs[[1]] |
|
102 |
-#' stop_job(remote_url, jobs_1) |
|
103 |
-#' } |
|
104 |
-#' |
|
105 |
-#' @export |
|
106 |
-#' |
|
107 |
-stop_job <- function(url, job_id) |
|
108 |
-{ |
|
109 |
- URL <- paste0(url,"/jobs/",job_id,"/stop") |
|
110 |
- h <- c('X-Auth-Token' = authToken,'Accept'= 'text/plain') |
|
111 |
- req <- httr::GET(URL, httr::add_headers(h)) |
|
112 |
- content <- httr::content(req,"parsed") |
|
113 |
- if(req$status_code !=200) |
|
114 |
- stop(content) |
|
115 |
- else |
|
116 |
- print(content) |
|
117 |
-} |
|
118 |
- |
|
119 |
-#' Trace a job |
|
120 |
-#' |
|
121 |
-#' It traces a specific current job |
|
122 |
-#' |
|
123 |
-#' @import httr |
|
124 |
-#' @param url string url of server: It must contain the server address |
|
125 |
-#' and base url; service name will be added automatically |
|
126 |
-#' @param job_id string id of the job |
|
127 |
-#' |
|
128 |
-#' @return text trace log |
|
129 |
-#' |
|
130 |
-#' @details |
|
131 |
-#' If error occures a specific error is printed |
|
132 |
-#' |
|
133 |
-#' @examples |
|
134 |
-#' remote_url = "http://130.186.13.219/gmql-rest" |
|
135 |
-#' \dontrun{ |
|
136 |
-#' login_gmql(remote_url) |
|
137 |
-#' list_jobs <- show_jobs_list(remote_url) |
|
138 |
-#' jobs_1 <- list_jobs$jobs[[1]] |
|
139 |
-#' trace_job(remote_url, jobs_1) |
|
140 |
-#' } |
|
141 |
-#' |
|
142 |
-#' |
|
143 |
-#' @export |
|
144 |
-#' |
|
145 |
-trace_job <- function(url, job_id) |
|
146 |
-{ |
|
147 |
- URL <- paste0(url,"/jobs/",job_id,"/trace") |
|
148 |
- h <- c('X-Auth-Token' = authToken,'Accept'= 'Application/json') |
|
149 |
- req <- httr::GET(URL, httr::add_headers(h)) |
|
150 |
- content <- httr::content(req,"parsed") |
|
151 |
- if(req$status_code !=200) |
|
152 |
- stop(content$error) |
|
153 |
- else |
|
154 |
- return(content) |
|
155 |
- |
|
156 |
-} |
|
157 |
- |
|
158 |
- |
|
159 |
-#' Run GMQL query |
|
160 |
-#' |
|
161 |
-#' It runs a GMQL query as single string |
|
162 |
-#' |
|
163 |
-#' @import httr |
|
164 |
-#' @param url url of server: It must contain the server address |
|
165 |
-#' and base url; service name is added automatically |
|
166 |
-#' @param fileName name of the file |
|
167 |
-#' @param query text of the query |
|
168 |
-#' @param output_gtf logical value indicating file format used for |
|
169 |
-#' storing samples generated by the query. |
|
170 |
-#' The possiblities are: |
|
171 |
-#' \itemize{ |
|
172 |
-#' \item{GTF} |
|
173 |
-#' \item{TAB} |
|
174 |
-#' } |
|
175 |
-#' |
|
176 |
-#' @return None |
|
177 |
-#' |
|
178 |
-#' @details |
|
179 |
-#' If error occures a specific error is printed |
|
180 |
-#' |
|
181 |
-#' @examples |
|
182 |
-#' remote_url = "http://130.186.13.219/gmql-rest" |
|
183 |
-#' \dontrun{ |
|
184 |
-#' login_gmql(remote_url) |
|
185 |