Browse code

fixed url

Simone authored on 16/08/2018 09:03:55
Showing 36 changed files

... ...
@@ -1,7 +1,7 @@
1 1
 Package: RGMQL
2 2
 Type: Package
3 3
 Title: GenoMetric Query Language for R/Bioconductor
4
-Version: 0.99.12
4
+Version: 1.0.1
5 5
 Author: Simone Pallotta, Marco Masseroli
6 6
 Maintainer: Simone Pallotta <simonepallotta@hotmail.com>
7 7
 Description: This package brings the GenoMetric Query Language (GMQL)
... ...
@@ -23,7 +23,7 @@ License: Artistic-2.0
23 23
 URL: http://www.bioinformatics.deib.polimi.it/genomic_computing/GMQL/
24 24
 Encoding: UTF-8
25 25
 LazyData: true
26
-RoxygenNote: 6.0.1
26
+RoxygenNote: 6.1.0
27 27
 Imports:
28 28
     httr,
29 29
     rJava,
... ...
@@ -98,27 +98,21 @@ export_gmql <- function(samples, dir_out, is_gtf)
98 98
     files_sub_dir <- file.path(dir_out,"files")
99 99
     dir.create(files_sub_dir)
100 100
     cnt = .counter()
101
+    file_ext = ""
101 102
     #col_names <- .get_schema_names(samples)
102 103
     if(to_GTF)
103 104
     {
104 105
         #write region
105 106
         lapply(samples,function(x,dir){
106
-            anonymusFile <- file()
107
+            #anonymusFile <- file()
107 108
             sample_name <- file.path(dir,paste0("S_",cnt(),".gtf"))
108
-            g <- rtracklayer::export(x,sample_name,format = "gtf")
109
-            lines <- readLines(anonymusFile)
110
-            lines <- lines[-(1:3)] #delete first 3 lines
109
+            g <- rtracklayer::export(x,format = "gtf",is.na)
110
+            #lines <- readLines(sample_name)
111
+            lines <- g[-(1:3)] #delete first 3 lines
111 112
             writeLines(lines,sample_name)
112
-            close(anonymusFile)
113
-        },files_sub_dir)
114
-        cnt = .counter(0)
115
-        meta <- metadata(samples)
116
-
117
-        #write metadata
118
-        lapply(meta,function(x,dir){
119
-            sample_name <- file.path(dir,paste0("S_",cnt(),".gtf"))
120
-            .write_metadata(x,sample_name)
113
+            #close(anonymusFile)
121 114
         },files_sub_dir)
115
+        file_ext = ".gtf"
122 116
     }
123 117
     else
124 118
     {
... ...
@@ -126,20 +120,23 @@ export_gmql <- function(samples, dir_out, is_gtf)
126 120
         lapply(samples,function(x,dir){
127 121
             sample_name <- file.path(dir,paste0("S_",cnt(),".gdm"))
128 122
             region_frame <- data.frame(x)
123
+            region_frame <- region_frame[-4] # delete width column
129 124
             region_frame$start = region_frame$start - 1
130 125
             write.table(region_frame,sample_name,col.names = FALSE,
131 126
                             row.names = FALSE, sep = '\t',quote = FALSE)
132 127
         },files_sub_dir)
133
-
134
-        cnt = .counter(0)
135
-        meta <- metadata(samples)
136
-
137
-        #write metadata
138
-        lapply(meta,function(x,dir){
139
-            sample_name <- file.path(dir,paste0("S_",cnt(),".gdm"))
140
-            .write_metadata(x,sample_name)
141
-        },files_sub_dir)
128
+        file_ext = ".gdm"
142 129
     }
130
+    
131
+    cnt = .counter(0)
132
+    meta <- metadata(samples)
133
+    
134
+    #write metadata
135
+    lapply(meta,function(x,dir){
136
+        sample_name <- file.path(dir,paste0("S_",cnt(),file_ext))
137
+        .write_metadata(x,sample_name)
138
+    },files_sub_dir)
139
+    
143 140
     # first regions to get column names
144 141
     col_names <- vapply(elementMetadata(samples[[1]]),class,character(1)) 
145 142
     # write schema XML
... ...
@@ -148,7 +145,6 @@ export_gmql <- function(samples, dir_out, is_gtf)
148 145
 }
149 146
 
150 147
 
151
-
152 148
 .write_metadata <- function(meta_list,sample_name)
153 149
 {
154 150
     #create my own list if metadata empty
... ...
@@ -189,19 +185,18 @@ export_gmql <- function(samples, dir_out, is_gtf)
189 185
     xml2::xml_attr(root,"name") <- "DatasetName_SCHEMAS"
190 186
     xml2::xml_attr(root,"xmlns") <- "http://genomic.elet.polimi.it/entities"
191 187
     xml2::xml_add_child(root,"gmqlSchema")
188
+    gmqlSchema <- xml2::xml_child(root,1) #gmqlSchema
192 189
     if(to_GTF)
193 190
     {
194
-        xml2::xml_attr(root,"type") <- "gtf"
195
-        xml2::xml_attr(root,"coordinate_system") <- "1-based"
191
+        xml2::xml_attr(gmqlSchema,"type") <- "gtf"
192
+        xml2::xml_attr(gmqlSchema,"coordinate_system") <- "1-based"
196 193
     }
197 194
     else
198 195
     {
199
-        xml2::xml_attr(root,"type") <- "tab"
200
-        xml2::xml_attr(root,"coordinate_system") <- "0-based"
196
+        xml2::xml_attr(gmqlSchema,"type") <- "tab"
197
+        xml2::xml_attr(gmqlSchema,"coordinate_system") <- "0-based"
201 198
     }
202 199
     
203
-    gmqlSchema <- xml2::xml_child(root,1)
204
-
205 200
     names_node <- names(node_list)
206 201
 
207 202
     mapply(function(type,text){
... ...
@@ -37,7 +37,7 @@
37 37
 #' 
38 38
 #' ## This statement initializes GMQL with remote processing
39 39
 #' 
40
-#' remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
40
+#' remote_url = "http://www.gmql.eu/gmql-rest/"
41 41
 #' init_gmql(remote_processing = TRUE, url = remote_url)
42 42
 #' 
43 43
 #' @export
... ...
@@ -58,7 +58,7 @@
58 58
 #' ## repository. For a public dataset in a (remote) GMQL repository the 
59 59
 #' ## prefix "public." is needed before dataset name
60 60
 #' 
61
-#' remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
61
+#' remote_url = "http://www.gmql.eu/gmql-rest/"
62 62
 #' login_gmql(remote_url)
63 63
 #' data1 = read_gmql("public.Example_Dataset_1", is_local = FALSE)
64 64
 #' 
... ...
@@ -45,7 +45,7 @@ if(getRversion() >= "3.1.0")
45 45
 #' @examples
46 46
 #' ## Login to GMQL REST services suite as guest
47 47
 #' 
48
-#' remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
48
+#' remote_url = "http://www.gmql.eu/gmql-rest/"
49 49
 #' login_gmql(remote_url)
50 50
 #' 
51 51
 #' @name login_gmql
... ...
@@ -120,7 +120,7 @@ login_gmql <- function(url, username = NULL, password = NULL)
120 120
 #' 
121 121
 #' ## Login to GMQL REST services suite as guest, then logout
122 122
 #' 
123
-#' remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
123
+#' remote_url = "http://www.gmql.eu/gmql-rest/
124 124
 #' login_gmql(remote_url)
125 125
 #' logout_gmql(remote_url)
126 126
 #' 
... ...
@@ -183,7 +183,7 @@ logout_gmql <- function(url)
183 183
 #' 
184 184
 #' ## Register to GMQL REST services suite 
185 185
 #' 
186
-#' remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
186
+#' remote_url = "http://www.gmql.eu/gmql-rest/"
187 187
 #' \dontrun{
188 188
 #' register_gmql(remote_url,"foo","foo","foo@foo.com","foo","foo")
189 189
 #' }
... ...
@@ -251,7 +251,7 @@ register_gmql <- function(url, username, psw, email,
251 251
 #' @examples
252 252
 #' 
253 253
 #' ## Login to GMQL REST services suite
254
-#' remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
254
+#' remote_url = "http://www.gmql.eu/gmql-rest/"
255 255
 #' login_gmql(remote_url)
256 256
 #' 
257 257
 #' ## List all queries executed on remote GMQL system 
... ...
@@ -300,7 +300,7 @@ show_queries_list <- function(url)
300 300
 #' 
301 301
 #' ## Login to GMQL REST services suite as guest
302 302
 #' 
303
-#' remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
303
+#' remote_url = "http://www.gmql.eu/gmql-rest/"
304 304
 #' login_gmql(remote_url)
305 305
 #' 
306 306
 #' ## This statement saves query written directly as input string parameter 
... ...
@@ -388,7 +388,7 @@ save_query_fromfile <- function(url, queryName, filePath)
388 388
 #' 
389 389
 #' ## Login to GMQL REST services suite as guest
390 390
 #' 
391
-#' remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
391
+#' remote_url = "http://www.gmql.eu/gmql-rest/"
392 392
 #' login_gmql(remote_url)
393 393
 #' 
394 394
 #' ## Run query as string input parameter
... ...
@@ -468,7 +468,7 @@ run_query_fromfile <- function(url, filePath, output_gtf = TRUE)
468 468
 #' 
469 469
 #' ## Login to GMQL REST services suite as guest
470 470
 #' 
471
-#' remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
471
+#' remote_url = "http://www.gmql.eu/gmql-rest/"
472 472
 #' login_gmql(remote_url)
473 473
 #' 
474 474
 #' ## This statement gets the query as text string and runs the compile 
... ...
@@ -544,7 +544,7 @@ compile_query_fromfile <- function(url ,filePath)
544 544
 #' 
545 545
 #' ## Login to GMQL REST services suite at remote url
546 546
 #' 
547
-#' remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
547
+#' remote_url = "http://www.gmql.eu/gmql-rest/"
548 548
 #' login_gmql(remote_url)
549 549
 #' 
550 550
 #' ## This statement shows all jobs at GMQL remote system and selects one 
... ...
@@ -591,7 +591,7 @@ stop_job <- function(url, job_id)
591 591
 #' @examples
592 592
 #' ## Login to GMQL REST services suite as guest
593 593
 #' 
594
-#' remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
594
+#' remote_url = "http://www.gmql.eu/gmql-rest/"
595 595
 #' login_gmql(remote_url)
596 596
 #' 
597 597
 #' ## List all jobs
... ...
@@ -670,7 +670,7 @@ trace_job <- function(url, job_id)
670 670
 #' @examples
671 671
 #' ## Login to GMQL REST services suite as guest
672 672
 #' 
673
-#' remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
673
+#' remote_url = "http://www.gmql.eu/gmql-rest/"
674 674
 #' login_gmql(remote_url)
675 675
 #' 
676 676
 #' ## List all jobs
... ...
@@ -721,7 +721,7 @@ show_jobs_list <- function(url)
721 721
 #' 
722 722
 #' ## Login to GMQL REST services suite as guest
723 723
 #' 
724
-#' remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
724
+#' remote_url = "http://www.gmql.eu/gmql-rest/"
725 725
 #' login_gmql(remote_url)
726 726
 #' 
727 727
 #' ## List all datasets
... ...
@@ -775,7 +775,7 @@ show_datasets_list <- function(url)
775 775
 #' 
776 776
 #' ## Login to GMQL REST services suite as guest
777 777
 #' 
778
-#' remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
778
+#' remote_url = "http://www.gmql.eu/gmql-rest/"
779 779
 #' login_gmql(remote_url)
780 780
 #' 
781 781
 #' ## This statement shows all samples present into public dataset 
... ...
@@ -825,7 +825,7 @@ show_samples_list <- function(url,datasetName)
825 825
 #' @examples
826 826
 #' ## Login to GMQL REST services suite as guest
827 827
 #' 
828
-#' remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
828
+#' remote_url = "http://www.gmql.eu/gmql-rest/"
829 829
 #' login_gmql(remote_url)
830 830
 #' 
831 831
 #' ## Show schema of public dataset 'Example_Dataset_1'
... ...
@@ -894,7 +894,7 @@ show_schema <- function(url,datasetName)
894 894
 #' 
895 895
 #' ## Login to GMQL REST services suite at remote url
896 896
 #' 
897
-#' remote_url <- "http://genomic.deib.polimi.it/gmql-rest-r/"
897
+#' remote_url <- "http://www.gmql.eu/gmql-rest/"
898 898
 #' login_gmql(remote_url)
899 899
 #' 
900 900
 #' ## Upload of GMQL dataset with "dataset1" as name, without specifying any 
... ...
@@ -1005,7 +1005,7 @@ upload_dataset <- function(url, datasetName, folderPath, schemaName = NULL,
1005 1005
 #' 
1006 1006
 #' ## This dataset does not exist
1007 1007
 #' 
1008
-#' remote_url <- "http://genomic.deib.polimi.it/gmql-rest-r/"
1008
+#' remote_url <- "http://www.gmql.eu/gmql-rest/"
1009 1009
 #' login_gmql(remote_url)
1010 1010
 #' delete_dataset(remote_url, "test1_20170604_180908_RESULT_DS")
1011 1011
 #' 
... ...
@@ -1058,7 +1058,7 @@ delete_dataset <- function(url,datasetName)
1058 1058
 #' 
1059 1059
 #' \dontrun{
1060 1060
 #' 
1061
-#' remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
1061
+#' remote_url = "http://www.gmql.eu/gmql-rest/"
1062 1062
 #' login_gmql(remote_url)
1063 1063
 #' download_dataset(remote_url, "Example_Dataset_1", path = getwd())
1064 1064
 #' 
... ...
@@ -1149,7 +1149,7 @@ download_as_GRangesList <- function(url,datasetName)
1149 1149
 #' @examples
1150 1150
 #' ## Login to GMQL REST services suite as guest
1151 1151
 #' 
1152
-#' remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
1152
+#' remote_url = "http://www.gmql.eu/gmql-rest/"
1153 1153
 #' login_gmql(remote_url)
1154 1154
 #' 
1155 1155
 #' ## This statement retrieves metadata of sample 'S_00000' from public 
... ...
@@ -1213,7 +1213,7 @@ sample_metadata <- function(url, datasetName,sampleName)
1213 1213
 #' 
1214 1214
 #' ## Login to GMQL REST services suite as guest
1215 1215
 #' 
1216
-#' remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
1216
+#' remote_url = "http://www.gmql.eu/gmql-rest/"
1217 1217
 #' login_gmql(remote_url)
1218 1218
 #' 
1219 1219
 #' ## This statement retrieves regions data of sample "S_00000" from public 
... ...
@@ -3,29 +3,17 @@
3 3
 \name{AGGREGATES-Object}
4 4
 \alias{AGGREGATES-Object}
5 5
 \alias{SUM}
6
-\alias{AGGREGATES-Object}
7 6
 \alias{COUNT}
8
-\alias{AGGREGATES-Object}
9 7
 \alias{COUNTSAMP}
10
-\alias{AGGREGATES-Object}
11 8
 \alias{MIN}
12
-\alias{AGGREGATES-Object}
13 9
 \alias{MAX}
14
-\alias{AGGREGATES-Object}
15 10
 \alias{AVG}
16
-\alias{AGGREGATES-Object}
17 11
 \alias{MEDIAN}
18
-\alias{AGGREGATES-Object}
19 12
 \alias{STD}
20
-\alias{AGGREGATES-Object}
21 13
 \alias{BAG}
22
-\alias{AGGREGATES-Object}
23 14
 \alias{BAGD}
24
-\alias{AGGREGATES-Object}
25 15
 \alias{Q1}
26
-\alias{AGGREGATES-Object}
27 16
 \alias{Q2}
28
-\alias{AGGREGATES-Object}
29 17
 \alias{Q3}
30 18
 \title{AGGREGATES object class constructor}
31 19
 \usage{
... ...
@@ -2,7 +2,6 @@
2 2
 % Please edit documentation in R/web-services.R
3 3
 \name{compile_query}
4 4
 \alias{compile_query}
5
-\alias{compile_query}
6 5
 \alias{compile_query_fromfile}
7 6
 \title{Compile GMQL query}
8 7
 \usage{
... ...
@@ -29,7 +28,7 @@ using the proper GMQL web service available on a remote server
29 28
 
30 29
 ## Login to GMQL REST services suite as guest
31 30
 
32
-remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
31
+remote_url = "http://www.gmql.eu/gmql-rest/"
33 32
 login_gmql(remote_url)
34 33
 
35 34
 ## This statement gets the query as text string and runs the compile 
... ...
@@ -3,7 +3,6 @@
3 3
 \name{Cover-Param}
4 4
 \alias{Cover-Param}
5 5
 \alias{ALL}
6
-\alias{Cover-Param}
7 6
 \alias{ANY}
8 7
 \title{PARAM object class constructor}
9 8
 \usage{
... ...
@@ -3,7 +3,6 @@
3 3
 \docType{methods}
4 4
 \name{cover}
5 5
 \alias{cover}
6
-\alias{cover}
7 6
 \alias{cover,GMQLDataset-method}
8 7
 \title{Method cover}
9 8
 \usage{
... ...
@@ -29,7 +29,7 @@ is printed
29 29
 
30 30
 ## This dataset does not exist
31 31
 
32
-remote_url <- "http://genomic.deib.polimi.it/gmql-rest-r/"
32
+remote_url <- "http://www.gmql.eu/gmql-rest/"
33 33
 login_gmql(remote_url)
34 34
 delete_dataset(remote_url, "test1_20170604_180908_RESULT_DS")
35 35
 
... ...
@@ -4,15 +4,10 @@
4 4
 \alias{DISTAL-Object}
5 5
 \alias{DL}
6 6
 \alias{DG}
7
-\alias{DISTAL-Object}
8 7
 \alias{DLE}
9
-\alias{DISTAL-Object}
10 8
 \alias{DGE}
11
-\alias{DISTAL-Object}
12 9
 \alias{MD}
13
-\alias{DISTAL-Object}
14 10
 \alias{UP}
15
-\alias{DISTAL-Object}
16 11
 \alias{DOWN}
17 12
 \title{DISTAL object class constructor}
18 13
 \usage{
... ...
@@ -39,7 +39,7 @@ If error occurs, a specific error is printed
39 39
 
40 40
 \dontrun{
41 41
 
42
-remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
42
+remote_url = "http://www.gmql.eu/gmql-rest/"
43 43
 login_gmql(remote_url)
44 44
 download_dataset(remote_url, "Example_Dataset_1", path = getwd())
45 45
 
... ...
@@ -4,7 +4,6 @@
4 4
 \name{extend}
5 5
 \alias{extend}
6 6
 \alias{extend,GMQLDataset-method}
7
-\alias{extend}
8 7
 \alias{extend-method}
9 8
 \title{Method extend}
10 9
 \usage{
... ...
@@ -4,8 +4,8 @@
4 4
 \alias{init_gmql}
5 5
 \title{Init GMQL server}
6 6
 \usage{
7
-init_gmql(output_format = "GTF", remote_processing = FALSE, url = NULL,
8
-  username = NULL, password = NULL)
7
+init_gmql(output_format = "GTF", remote_processing = FALSE,
8
+  url = NULL, username = NULL, password = NULL)
9 9
 }
10 10
 \arguments{
11 11
 \item{output_format}{string that identifies the output format of all sample 
... ...
@@ -47,7 +47,7 @@ init_gmql("tab", FALSE)
47 47
 
48 48
 ## This statement initializes GMQL with remote processing
49 49
 
50
-remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
50
+remote_url = "http://www.gmql.eu/gmql-rest/"
51 51
 init_gmql(remote_processing = TRUE, url = remote_url)
52 52
 
53 53
 }
... ...
@@ -28,7 +28,7 @@ If error occurs, a specific error is printed
28 28
 \examples{
29 29
 ## Login to GMQL REST services suite as guest
30 30
 
31
-remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
31
+remote_url = "http://www.gmql.eu/gmql-rest/"
32 32
 login_gmql(remote_url)
33 33
 
34 34
 ## List all jobs
... ...
@@ -34,7 +34,7 @@ been saved). If error occurs, a specific error is printed
34 34
 \examples{
35 35
 ## Login to GMQL REST services suite as guest
36 36
 
37
-remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
37
+remote_url = "http://www.gmql.eu/gmql-rest/"
38 38
 login_gmql(remote_url)
39 39
 
40 40
 }
... ...
@@ -22,12 +22,3 @@ After logout the authentication token will be invalidated.
22 22
 The authentication token is removed from R Global environment.
23 23
 If error occurs, a specific error is printed
24 24
 }
25
-\examples{
26
-
27
-## Login to GMQL REST services suite as guest, then logout
28
-
29
-remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
30
-login_gmql(remote_url)
31
-logout_gmql(remote_url)
32
-
33
-}
... ...
@@ -4,13 +4,13 @@
4 4
 \name{map}
5 5
 \alias{map}
6 6
 \alias{map,GMQLDataset-method}
7
-\alias{map}
8 7
 \alias{map-method}
9 8
 \title{Method map}
10 9
 \usage{
11 10
 map(x, y, ...)
12 11
 
13
-\S4method{map}{GMQLDataset}(x, y, ..., joinBy = conds(), count_name = "")
12
+\S4method{map}{GMQLDataset}(x, y, ..., joinBy = conds(),
13
+  count_name = "")
14 14
 }
15 15
 \arguments{
16 16
 \item{x}{GMQLDataset class object}
... ...
@@ -6,8 +6,9 @@
6 6
 \alias{merge,GMQLDataset,GMQLDataset-method}
7 7
 \title{Method merge}
8 8
 \usage{
9
-\S4method{merge}{GMQLDataset,GMQLDataset}(x, y, genometric_predicate = NULL,
10
-  region_output = "CAT", joinBy = conds(), reg_attr = c(""))
9
+\S4method{merge}{GMQLDataset,GMQLDataset}(x, y,
10
+  genometric_predicate = NULL, region_output = "CAT",
11
+  joinBy = conds(), reg_attr = c(""))
11 12
 }
12 13
 \arguments{
13 14
 \item{x}{GMQLDataset class object}
... ...
@@ -3,9 +3,7 @@
3 3
 \name{OPERATOR-Object}
4 4
 \alias{OPERATOR-Object}
5 5
 \alias{META}
6
-\alias{OPERATOR-Object}
7 6
 \alias{NIL}
8
-\alias{OPERATOR-Object}
9 7
 \alias{SQRT}
10 8
 \title{OPERATOR object class constructor}
11 9
 \usage{
... ...
@@ -3,7 +3,6 @@
3 3
 \name{Ordering-Functions}
4 4
 \alias{Ordering-Functions}
5 5
 \alias{DESC}
6
-\alias{Ordering-Functions}
7 6
 \alias{ASC}
8 7
 \title{Ordering functions}
9 8
 \usage{
... ...
@@ -2,7 +2,6 @@
2 2
 % Please edit documentation in R/gmql_read.R
3 3
 \name{read_gmql}
4 4
 \alias{read_gmql}
5
-\alias{read_gmql}
6 5
 \alias{read_GRangesList}
7 6
 \title{Function read}
8 7
 \usage{
... ...
@@ -74,7 +73,7 @@ dataPeak = read_gmql(test_path,"NarrowPeakParser")
74 73
 ## repository. For a public dataset in a (remote) GMQL repository the 
75 74
 ## prefix "public." is needed before dataset name
76 75
 
77
-remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
76
+remote_url = "http://www.gmql.eu/gmql-rest/"
78 77
 login_gmql(remote_url)
79 78
 data1 = read_gmql("public.Example_Dataset_1", is_local = FALSE)
80 79
 
... ...
@@ -40,7 +40,7 @@ is printed.
40 40
 
41 41
 ## Register to GMQL REST services suite 
42 42
 
43
-remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
43
+remote_url = "http://www.gmql.eu/gmql-rest/"
44 44
 \dontrun{
45 45
 register_gmql(remote_url,"foo","foo","foo@foo.com","foo","foo")
46 46
 }
... ...
@@ -2,7 +2,6 @@
2 2
 % Please edit documentation in R/web-services.R
3 3
 \name{run_query}
4 4
 \alias{run_query}
5
-\alias{run_query}
6 5
 \alias{run_query_fromfile}
7 6
 \title{Run a GMQL query}
8 7
 \usage{
... ...
@@ -44,7 +43,7 @@ If error occurs, a specific error is printed
44 43
 
45 44
 ## Login to GMQL REST services suite as guest
46 45
 
47
-remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
46
+remote_url = "http://www.gmql.eu/gmql-rest/"
48 47
 login_gmql(remote_url)
49 48
 
50 49
 ## Run query as string input parameter
... ...
@@ -27,7 +27,7 @@ If error occurs, a specific error is printed
27 27
 \examples{
28 28
 ## Login to GMQL REST services suite as guest
29 29
 
30
-remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
30
+remote_url = "http://www.gmql.eu/gmql-rest/"
31 31
 login_gmql(remote_url)
32 32
 
33 33
 ## This statement retrieves metadata of sample 'S_00000' from public 
... ...
@@ -32,7 +32,7 @@ If error occurs, a specific error is printed
32 32
 
33 33
 ## Login to GMQL REST services suite as guest
34 34
 
35
-remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
35
+remote_url = "http://www.gmql.eu/gmql-rest/"
36 36
 login_gmql(remote_url)
37 37
 
38 38
 ## This statement retrieves regions data of sample "S_00000" from public 
... ...
@@ -35,7 +35,7 @@ in repository, you will overwrite it; if no error occurs, it prints:
35 35
 
36 36
 ## Login to GMQL REST services suite as guest
37 37
 
38
-remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
38
+remote_url = "http://www.gmql.eu/gmql-rest/"
39 39
 login_gmql(remote_url)
40 40
 
41 41
 ## This statement saves query written directly as input string parameter 
... ...
@@ -28,7 +28,7 @@ If error occurs, a specific error is printed
28 28
 
29 29
 ## Login to GMQL REST services suite as guest
30 30
 
31
-remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
31
+remote_url = "http://www.gmql.eu/gmql-rest/"
32 32
 login_gmql(remote_url)
33 33
 
34 34
 ## List all datasets
... ...
@@ -26,7 +26,7 @@ If error occurs, a specific error is printed
26 26
 \examples{
27 27
 ## Login to GMQL REST services suite as guest
28 28
 
29
-remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
29
+remote_url = "http://www.gmql.eu/gmql-rest/"
30 30
 login_gmql(remote_url)
31 31
 
32 32
 ## List all jobs
... ...
@@ -27,7 +27,7 @@ If error occurs, a specific error is printed
27 27
 \examples{
28 28
 
29 29
 ## Login to GMQL REST services suite
30
-remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
30
+remote_url = "http://www.gmql.eu/gmql-rest/"
31 31
 login_gmql(remote_url)
32 32
 
33 33
 ## List all queries executed on remote GMQL system 
... ...
@@ -34,7 +34,7 @@ If error occurs, a specific error is printed
34 34
 
35 35
 ## Login to GMQL REST services suite as guest
36 36
 
37
-remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
37
+remote_url = "http://www.gmql.eu/gmql-rest/"
38 38
 login_gmql(remote_url)
39 39
 
40 40
 ## This statement shows all samples present into public dataset 
... ...
@@ -32,7 +32,7 @@ If error occurs, a specific error is printed
32 32
 \examples{
33 33
 ## Login to GMQL REST services suite as guest
34 34
 
35
-remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
35
+remote_url = "http://www.gmql.eu/gmql-rest/"
36 36
 login_gmql(remote_url)
37 37
 
38 38
 ## Show schema of public dataset 'Example_Dataset_1'
... ...
@@ -27,7 +27,7 @@ If error occurs, a specific error is printed
27 27
 
28 28
 ## Login to GMQL REST services suite at remote url
29 29
 
30
-remote_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
30
+remote_url = "http://www.gmql.eu/gmql-rest/"
31 31
 login_gmql(remote_url)
32 32
 
33 33
 ## This statement shows all jobs at GMQL remote system and selects one 
... ...
@@ -4,7 +4,6 @@
4 4
 \name{take}
5 5
 \alias{take}
6 6
 \alias{take,GMQLDataset-method}
7
-\alias{take}
8 7
 \alias{take-method}
9 8
 \title{Method take}
10 9
 \usage{
... ...
@@ -54,7 +54,7 @@ test_path <- system.file("example", "DATASET_GDM", package = "RGMQL")
54 54
 
55 55
 ## Login to GMQL REST services suite at remote url
56 56
 
57
-remote_url <- "http://genomic.deib.polimi.it/gmql-rest-r/"
57
+remote_url <- "http://www.gmql.eu/gmql-rest/"
58 58
 login_gmql(remote_url)
59 59
 
60 60
 ## Upload of GMQL dataset with "dataset1" as name, without specifying any 
... ...
@@ -428,7 +428,7 @@ Upon successful logon, you get a request token that you must use
428 428
 in every subsequent REST call.
429 429
 Login can be performed using the *login_gmql()* function:
430 430
 ```{r, init with login}
431
-test_url = "http://genomic.deib.polimi.it/gmql-rest-r/"
431
+test_url = "http://www.gmql.eu/gmql-rest/"
432 432
 login_gmql(test_url)
433 433
 ```
434 434
 It saves the token in the Global R environment within the variable