... | ... |
@@ -5,7 +5,7 @@ |
5 | 5 |
#' defined as input. |
6 | 6 |
#' The metadata and metadata_prefix are used to filter the data and choose |
7 | 7 |
#' only the samples that match at least one metdatata with its prefix. |
8 |
-#' The regions are shown for each sample obtained from filtering. |
|
8 |
+#' The input regions are shown for each sample obtained from filtering. |
|
9 | 9 |
#' |
10 | 10 |
#' @import xml2 |
11 | 11 |
#' @importFrom dplyr bind_cols |
... | ... |
@@ -36,7 +36,6 @@ |
36 | 36 |
#' |
37 | 37 |
#' @examples |
38 | 38 |
#' |
39 |
-#' \dontrun{ |
|
40 | 39 |
#' library(GenomicRanges) |
41 | 40 |
#' gr1 <- GRanges(seqnames = "chr2", ranges = IRanges(3, 6), strand = "+", |
42 | 41 |
#' score = 5L, GC = 0.45) |
... | ... |
@@ -46,7 +45,8 @@ |
46 | 45 |
#' grl = GRangesList(gr1, gr2) |
47 | 46 |
#' test_out_path <- system.file("example", package = "RGMQL") |
48 | 47 |
#' export_gmql(grl, test_out_path,TRUE) |
49 |
-#' } |
|
48 |
+#' |
|
49 |
+#' |
|
50 | 50 |
#' @export |
51 | 51 |
#' |
52 | 52 |
export_gmql <- function(samples, dir_out, is_gtf) |
... | ... |
@@ -158,7 +158,8 @@ take_value.META_AGGREGATES <- function(obj){ |
158 | 158 |
#' res = extend(exp, m_score = MEDIAN("score")) |
159 | 159 |
#' |
160 | 160 |
#' |
161 |
-#' @name AGGREGATES |
|
161 |
+#' @name SUM |
|
162 |
+#' @aliases SUM |
|
162 | 163 |
#' @rdname aggr-class |
163 | 164 |
#' @export |
164 | 165 |
#' |
... | ... |
@@ -172,7 +173,8 @@ SUM <- function(value) |
172 | 173 |
return(list) |
173 | 174 |
} |
174 | 175 |
|
175 |
-#' @name AGGREGATES |
|
176 |
+#' @name MIN |
|
177 |
+#' @aliases MIN |
|
176 | 178 |
#' @rdname aggr-class |
177 | 179 |
#' @export |
178 | 180 |
#' |
... | ... |
@@ -187,7 +189,8 @@ MIN <- function(value) |
187 | 189 |
} |
188 | 190 |
|
189 | 191 |
|
190 |
-#' @name AGGREGATES |
|
192 |
+#' @name MAX |
|
193 |
+#' @aliases MAX |
|
191 | 194 |
#' @rdname aggr-class |
192 | 195 |
#' @export |
193 | 196 |
#' |
... | ... |
@@ -201,7 +204,8 @@ MAX <- function(value) |
201 | 204 |
return(list) |
202 | 205 |
} |
203 | 206 |
|
204 |
-#' @name AGGREGATES |
|
207 |
+#' @name AVG |
|
208 |
+#' @aliases AVG |
|
205 | 209 |
#' @rdname aggr-class |
206 | 210 |
#' @export |
207 | 211 |
#' |
... | ... |
@@ -215,7 +219,8 @@ AVG <- function(value) |
215 | 219 |
return(list) |
216 | 220 |
} |
217 | 221 |
|
218 |
-#' @name AGGREGATES |
|
222 |
+#' @name BAG |
|
223 |
+#' @aliases BAG |
|
219 | 224 |
#' @rdname aggr-class |
220 | 225 |
#' @export |
221 | 226 |
#' |
... | ... |
@@ -229,7 +234,8 @@ BAG <- function(value) |
229 | 234 |
return(list) |
230 | 235 |
} |
231 | 236 |
|
232 |
-#' @name AGGREGATES |
|
237 |
+#' @name COUNT |
|
238 |
+#' @aliases COUNT |
|
233 | 239 |
#' @rdname aggr-class |
234 | 240 |
#' @export |
235 | 241 |
#' |
... | ... |
@@ -246,7 +252,8 @@ as.character.COUNT <- function(obj) { |
246 | 252 |
} |
247 | 253 |
check.COUNT <- function(obj){} |
248 | 254 |
|
249 |
-#' @name AGGREGATES |
|
255 |
+#' @name STD |
|
256 |
+#' @aliases STD |
|
250 | 257 |
#' @rdname aggr-class |
251 | 258 |
#' @export |
252 | 259 |
#' |
... | ... |
@@ -261,7 +268,8 @@ STD <- function(value) |
261 | 268 |
} |
262 | 269 |
|
263 | 270 |
|
264 |
-#' @name AGGREGATES |
|
271 |
+#' @name MEDIAN |
|
272 |
+#' @aliases MEDIAN |
|
265 | 273 |
#' @rdname aggr-class |
266 | 274 |
#' @export |
267 | 275 |
#' |
... | ... |
@@ -275,7 +283,8 @@ MEDIAN <- function(value) |
275 | 283 |
return(list) |
276 | 284 |
} |
277 | 285 |
|
278 |
-#' @name AGGREGATES |
|
286 |
+#' @name Q1 |
|
287 |
+#' @aliases Q1 |
|
279 | 288 |
#' @rdname aggr-class |
280 | 289 |
#' @export |
281 | 290 |
#' |
... | ... |
@@ -289,7 +298,8 @@ Q1 <- function(value) |
289 | 298 |
return(list) |
290 | 299 |
} |
291 | 300 |
|
292 |
-#' @name AGGREGATES |
|
301 |
+#' @name Q2 |
|
302 |
+#' @aliases Q2 |
|
293 | 303 |
#' @rdname aggr-class |
294 | 304 |
#' @export |
295 | 305 |
#' |
... | ... |
@@ -302,7 +312,8 @@ Q2 <- function(value) |
302 | 312 |
return(list) |
303 | 313 |
} |
304 | 314 |
|
305 |
-#' @name AGGREGATES |
|
315 |
+#' @name Q3 |
|
316 |
+#' @aliases Q3 |
|
306 | 317 |
#' @rdname aggr-class |
307 | 318 |
#' @export |
308 | 319 |
#' |
... | ... |
@@ -316,7 +327,8 @@ Q3 <- function(value) |
316 | 327 |
return(list) |
317 | 328 |
} |
318 | 329 |
|
319 |
-#' @name AGGREGATES |
|
330 |
+#' @name BAGD |
|
331 |
+#' @aliases BAGD |
|
320 | 332 |
#' @rdname aggr-class |
321 | 333 |
#' @export |
322 | 334 |
#' |
... | ... |
@@ -52,7 +52,8 @@ print.PARAMETER <- function(obj){ |
52 | 52 |
#' |
53 | 53 |
#' res = cover(exp, 2, ANY()+2/3) |
54 | 54 |
#' |
55 |
-#' @name COVER-PARAMETER |
|
55 |
+#' @name ALL |
|
56 |
+#' @aliases ALL |
|
56 | 57 |
#' @rdname cover-param-class |
57 | 58 |
#' @export |
58 | 59 |
#' |
... | ... |
@@ -64,7 +65,8 @@ ALL <- function() |
64 | 65 |
return(list) |
65 | 66 |
} |
66 | 67 |
|
67 |
-#' @name COVER-PARAMETER |
|
68 |
+#' @name ANY |
|
69 |
+#' @aliases ANY |
|
68 | 70 |
#' @rdname cover-param-class |
69 | 71 |
#' @export |
70 | 72 |
#' |
... | ... |
@@ -101,7 +101,8 @@ check.DISTAL <- function(value) |
101 | 101 |
#' genometric_predicate = list(list(MD(1), DGE(12000), DOWN())), |
102 | 102 |
#' DF("provider"), region_output = "RIGHT") |
103 | 103 |
#' |
104 |
-#' @name DISTAL |
|
104 |
+#' @name DL |
|
105 |
+#' @aliases DL |
|
105 | 106 |
#' @rdname distal-class |
106 | 107 |
#' @export |
107 | 108 |
#' |
... | ... |
@@ -114,7 +115,8 @@ DL <- function(value) |
114 | 115 |
return(list) |
115 | 116 |
} |
116 | 117 |
|
117 |
-#' @name DISTAL |
|
118 |
+#' @name DG |
|
119 |
+#' @aliases DG |
|
118 | 120 |
#' @rdname distal-class |
119 | 121 |
#' @export |
120 | 122 |
#' |
... | ... |
@@ -127,7 +129,8 @@ DG <- function(value) |
127 | 129 |
return(list) |
128 | 130 |
} |
129 | 131 |
|
130 |
-#' @name DISTAL |
|
132 |
+#' @name DLE |
|
133 |
+#' @aliases DLE |
|
131 | 134 |
#' @rdname distal-class |
132 | 135 |
#' @export |
133 | 136 |
#' |
... | ... |
@@ -140,7 +143,8 @@ DLE <- function(value) |
140 | 143 |
return(list) |
141 | 144 |
} |
142 | 145 |
|
143 |
-#' @name DISTAL |
|
146 |
+#' @name DGE |
|
147 |
+#' @aliases DGE |
|
144 | 148 |
#' @rdname distal-class |
145 | 149 |
#' @export |
146 | 150 |
#' |
... | ... |
@@ -153,7 +157,8 @@ DGE <- function(value) |
153 | 157 |
return(list) |
154 | 158 |
} |
155 | 159 |
|
156 |
-#' @name DISTAL |
|
160 |
+#' @name MD |
|
161 |
+#' @aliases MD |
|
157 | 162 |
#' @rdname distal-class |
158 | 163 |
#' @export |
159 | 164 |
#' |
... | ... |
@@ -167,7 +172,8 @@ MD <- function(value) |
167 | 172 |
} |
168 | 173 |
|
169 | 174 |
|
170 |
-#' @name DISTAL |
|
175 |
+#' @name UP |
|
176 |
+#' @aliases UP |
|
171 | 177 |
#' @rdname distal-class |
172 | 178 |
#' @export |
173 | 179 |
#' |
... | ... |
@@ -184,7 +190,8 @@ as.character.UP <- function(obj) { |
184 | 190 |
} |
185 | 191 |
|
186 | 192 |
|
187 |
-#' @name DISTAL |
|
193 |
+#' @name DOWN |
|
194 |
+#' @aliases DOWN |
|
188 | 195 |
#' @rdname distal-class |
189 | 196 |
#' @export |
190 | 197 |
#' |
... | ... |
@@ -87,7 +87,8 @@ as.character.OPERATOR <- function(obj) { |
87 | 87 |
#' exp = read_dataset(test_path) |
88 | 88 |
#' out = select(exp, metadata_update = list(concSq = SQRT("concentration"))) |
89 | 89 |
#' |
90 |
-#' @name OPERATORS |
|
90 |
+#' @name META |
|
91 |
+#' @aliases META |
|
91 | 92 |
#' @rdname operator-class |
92 | 93 |
#' @export |
93 | 94 |
#' |
... | ... |
@@ -122,7 +123,8 @@ check.META <- function(type) |
122 | 123 |
} |
123 | 124 |
|
124 | 125 |
|
125 |
-#' @name OPERATORS |
|
126 |
+#' @name NIL |
|
127 |
+#' @aliases NIL |
|
126 | 128 |
#' @rdname operator-class |
127 | 129 |
#' @export |
128 | 130 |
#' |
... | ... |
@@ -145,7 +147,8 @@ check.NIL <- function(value) |
145 | 147 |
|
146 | 148 |
} |
147 | 149 |
|
148 |
-#' @name OPERATORS |
|
150 |
+#' @name SQRT |
|
151 |
+#' @aliases SQRT |
|
149 | 152 |
#' @rdname operator-class |
150 | 153 |
#' @export |
151 | 154 |
#' |
... | ... |
@@ -29,7 +29,8 @@ |
29 | 29 |
#' test_path <- system.file("example", "DATASET", package = "RGMQL") |
30 | 30 |
#' r = read_dataset(test_path) |
31 | 31 |
#' |
32 |
-#' @name evaluation |
|
32 |
+#' @name FN |
|
33 |
+#' @aliases FN |
|
33 | 34 |
#' @rdname condition_eval_func |
34 | 35 |
#' @export |
35 | 36 |
FN <- function(...) |
... | ... |
@@ -49,7 +50,8 @@ FN <- function(...) |
49 | 50 |
join_condition_matrix |
50 | 51 |
} |
51 | 52 |
|
52 |
-#' @name evaluation |
|
53 |
+#' @name EX |
|
54 |
+#' @aliases EX |
|
53 | 55 |
#' @rdname condition_eval_func |
54 | 56 |
#' @export |
55 | 57 |
EX <- function(...) |
... | ... |
@@ -69,7 +71,8 @@ EX <- function(...) |
69 | 71 |
join_condition_matrix |
70 | 72 |
} |
71 | 73 |
|
72 |
-#' @name evaluation |
|
74 |
+#' @name DF |
|
75 |
+#' @aliases DF |
|
73 | 76 |
#' @rdname condition_eval_func |
74 | 77 |
#' @export |
75 | 78 |
DF <- function(...) |
... | ... |
@@ -1,4 +1,4 @@ |
1 |
-#' GMQL Operation: COVER |
|
1 |
+#' Method cover |
|
2 | 2 |
#' |
3 | 3 |
#' It takes as input a dataset containing one or more samples and returns |
4 | 4 |
#' another dataset (with a single sample, if no \emph{groupby} option is |
... | ... |
@@ -84,21 +84,21 @@ |
84 | 84 |
#' @param variation string identifying the cover GMQL function variation. |
85 | 85 |
#' The admissible string are: |
86 | 86 |
#' \itemize{ |
87 |
-#' \item{flat: returns the contiguous region that starts from the first end |
|
87 |
+#' \item{FLAT: returns the contiguous region that starts from the first end |
|
88 | 88 |
#' and stops at the last end of the regions which would contribute |
89 | 89 |
#' to each region of the \emph{cover}.} |
90 |
-#' \item{summit: returns regions that start from a position |
|
90 |
+#' \item{SUMMIT: returns regions that start from a position |
|
91 | 91 |
#' where the number of intersecting regions is not increasing afterwards and |
92 | 92 |
#' stops at a position where either the number of intersecting regions |
93 | 93 |
#' decreases, or it violates the max accumulation index.} |
94 |
-#' \item{histogram: returns the non-overlapping regions contributing to |
|
94 |
+#' \item{HISTOGRAM: returns the non-overlapping regions contributing to |
|
95 | 95 |
#' the cover, each with its accumulation index value, which is assigned to |
96 | 96 |
#' the AccIndex region attribute.} |
97 |
-#' \item{cover: default value.} |
|
97 |
+#' \item{COVER: default value.} |
|
98 | 98 |
#' } |
99 | 99 |
#' |
100 |
-#' @return GMQLDataset class object. It contains the value to use as input |
|
101 |
-#' for the subsequent GMQL function |
|
100 |
+#' @return GMQLDataset object. It contains the value to use as input |
|
101 |
+#' for the subsequent GMQLDataset method |
|
102 | 102 |
#' |
103 | 103 |
#' @examples |
104 | 104 |
#' |
... | ... |
@@ -1,11 +1,11 @@ |
1 | 1 |
#' Method setdiff |
2 | 2 |
#' |
3 |
-#' Wrapper to GMQL difference function |
|
3 |
+#' @description Wrapper to GMQL difference function |
|
4 | 4 |
#' |
5 |
-#' It produces one sample in the result for each sample of the left operand, |
|
6 |
-#' by keeping the same metadata of the left input sample and only those |
|
7 |
-#' regions (with their schema and values) of the left input sample which |
|
8 |
-#' do not intersect with any region in the right operand sample. |
|
5 |
+#' @description It produces one sample in the result for each sample of the |
|
6 |
+#' left operand, by keeping the same metadata of the left input sample |
|
7 |
+#' and only those regions (with their schema and values) of the left input |
|
8 |
+#' sample which do not intersect with any region in the right operand sample. |
|
9 | 9 |
#' The optional \emph{joinby} clause is used to extract a subset of couples |
10 | 10 |
#' from the cartesian product of two dataset \emph{x} and \emph{y} |
11 | 11 |
#' on which to apply the DIFFERENCE operator: |
... | ... |
@@ -38,8 +38,8 @@ |
38 | 38 |
#' left_input_data that overlap with at least one region in right_input_data |
39 | 39 |
#' (even just one base). |
40 | 40 |
#' |
41 |
-#' @return GMQLDataset class object. It contains the value to use as input |
|
42 |
-#' for the subsequent GMQL function |
|
41 |
+#' @return GMQLDataset object. It contains the value to use as input |
|
42 |
+#' for the subsequent GMQLDataset method |
|
43 | 43 |
#' |
44 | 44 |
#' |
45 | 45 |
#' @examples |
... | ... |
@@ -1,8 +1,8 @@ |
1 |
-#' GMQL Operation: EXTEND |
|
1 |
+#' Method extend |
|
2 | 2 |
#' |
3 |
-#' It generates new metadata attributes as result of aggregate functions |
|
4 |
-#' applied to sample region attributes and adds them to the existing metadata |
|
5 |
-#' attributes of the sample. |
|
3 |
+#' For each sample in an input dataset, it generates new metadata attributes |
|
4 |
+#' as result of aggregate functions applied to sample region attributes |
|
5 |
+#' and adds them to the existing metadata attributes of the sample. |
|
6 | 6 |
#' Aggregate functions are applied sample by sample. |
7 | 7 |
#' |
8 | 8 |
#' @importFrom rJava .jnull |
... | ... |
@@ -11,8 +11,7 @@ |
11 | 11 |
#' |
12 | 12 |
#' @param .data GMQLDataset class object |
13 | 13 |
#' @param ... Additional arguments for use in specific methods. |
14 |
-#' |
|
15 |
-#' This method accept a series of aggregate function on region attribute. |
|
14 |
+#' It accept a series of aggregate function on region attribute. |
|
16 | 15 |
#' All the element in the form \emph{key} = \emph{aggregate}. |
17 | 16 |
#' The \emph{aggregate} is an object of class AGGREGATES |
18 | 17 |
#' The aggregate functions available are: \code{\link{SUM}}, |
... | ... |
@@ -30,8 +29,8 @@ |
30 | 29 |
#' } |
31 | 30 |
#' "mixed style" is not allowed |
32 | 31 |
#' |
33 |
-#' @return GMQLDataset class object. It contains the value to use as input |
|
34 |
-#' for the subsequent GMQL function |
|
32 |
+#' @return GMQLDataset object. It contains the value to use as input |
|
33 |
+#' for the subsequent GMQLDataset method |
|
35 | 34 |
#' |
36 | 35 |
#' @examples |
37 | 36 |
#' |
... | ... |
@@ -1,6 +1,4 @@ |
1 | 1 |
#' Method merge |
2 |
-#' |
|
3 |
-#' Wrapper to GMQL join function |
|
4 | 2 |
#' |
5 | 3 |
#' It takes in input two datasets, respectively known as nchor (left) |
6 | 4 |
#' and experiment (right) and returns a dataset of samples consisting of |
... | ... |
@@ -57,8 +55,8 @@ |
57 | 55 |
#' the genometric predicate)} |
58 | 56 |
#' } |
59 | 57 |
#' |
60 |
-#' @return GMQLDataset class object. It contains the value to use as input |
|
61 |
-#' for the subsequent GMQL function |
|
58 |
+#' @return GMQLDataset object. It contains the value to use as input |
|
59 |
+#' for the subsequent GMQLDataset method |
|
62 | 60 |
#' |
63 | 61 |
#' @examples |
64 | 62 |
#' |
... | ... |
@@ -1,4 +1,4 @@ |
1 |
-#' GMQL Operation: MAP |
|
1 |
+#' Method map |
|
2 | 2 |
#' |
3 | 3 |
#' It computes, for each sample in the right dataset, aggregates over the |
4 | 4 |
#' values of the right regions that intersect with a region in a left sample, |
... | ... |
@@ -52,8 +52,8 @@ |
52 | 52 |
#' if both end with value.} |
53 | 53 |
#' } |
54 | 54 |
#' |
55 |
-#' @return GMQLDataset class object. It contains the value to use as input |
|
56 |
-#' for the subsequent GMQL function |
|
55 |
+#' @return GMQLDataset object. It contains the value to use as input |
|
56 |
+#' for the subsequent GMQLDataset method |
|
57 | 57 |
#' |
58 | 58 |
#' @examples |
59 | 59 |
#' |
... | ... |
@@ -1,7 +1,7 @@ |
1 | 1 |
#' GMQL Function: EXECUTE |
2 | 2 |
#' |
3 | 3 |
#' Execute GMQL query. |
4 |
-#' The function works only after invoking at least one materialize |
|
4 |
+#' The function works only after invoking at least one collect |
|
5 | 5 |
#' |
6 | 6 |
#' @importFrom rJava J |
7 | 7 |
#' |
... | ... |
@@ -67,7 +67,9 @@ execute <- function() |
67 | 67 |
|
68 | 68 |
|
69 | 69 |
|
70 |
-#' GMQL Operation: MATERIALIZE |
|
70 |
+#' Method collect |
|
71 |
+#' |
|
72 |
+#' Wrapper to GMQL materialize function |
|
71 | 73 |
#' |
72 | 74 |
#' It saves the contents of a dataset that contains samples metadata and |
73 | 75 |
#' samples regions. |
... | ... |
@@ -124,12 +126,12 @@ gmql_materialize <- function(input_data, dir_out, name) |
124 | 126 |
} |
125 | 127 |
|
126 | 128 |
|
127 |
-#' GMQL Operation: TAKE |
|
129 |
+#' Method take |
|
128 | 130 |
#' |
129 | 131 |
#' It saves the contents of a dataset that contains samples metadata |
130 |
-#' and samples regions. |
|
131 |
-#' It is normally used to store in memoery the contents of any dataset |
|
132 |
-#' generated during a GMQL query. the operation can be very time-consuming. |
|
132 |
+#' and samples regions as GrangesList. |
|
133 |
+#' It is normally used to store in memory the contents of any dataset |
|
134 |
+#' generated during a GMQL query. The operation can be very time-consuming. |
|
133 | 135 |
#' If you have invoked any materialization before take function, |
134 | 136 |
#' all those dataset will be materialized as folder. |
135 | 137 |
#' |
... | ... |
@@ -1,13 +1,14 @@ |
1 |
-#' GMQL Operation: MERGE |
|
2 |
-#' |
|
1 |
+#' Method aggregate |
|
2 |
+#' |
|
3 | 3 |
#' It builds a dataset consisting of a single sample having as many regions as |
4 | 4 |
#' the number of regions of the input data and as many metadata as the union of |
5 |
-#' the 'attribute-value' tuples of the input samples. A groupby clause can be |
|
6 |
-#' specified on metadata: the samples are then partitioned in groups, each with |
|
7 |
-#' a distinct value of the grouping metadata attributes. The operation is |
|
8 |
-#' separately applied to each group, yielding one sample in the result for each |
|
9 |
-#' group. Samples whose names are not present in the grouping metadata |
|
10 |
-#' parameter are disregarded. |
|
5 |
+#' the 'attribute-value' tuples of the input samples. |
|
6 |
+#' If at least one evaluation function is specified: the samples are then |
|
7 |
+#' partitioned in groups, each with a distinct value of the grouping metadata |
|
8 |
+#' attributes. The operation is separately applied to each group, yielding |
|
9 |
+#' one sample in the result for each group. |
|
10 |
+#' Samples whose names are not present in the grouping metadata parameter |
|
11 |
+#' are disregarded. |
|
11 | 12 |
#' |
12 | 13 |
#' @importFrom rJava J |
13 | 14 |
#' @importFrom rJava .jnull |
... | ... |
@@ -15,8 +16,7 @@ |
15 | 16 |
#' |
16 | 17 |
#' @param x GMQLDataset class object |
17 | 18 |
#' @param ... Additional arguments for use in specific methods. |
18 |
-#' |
|
19 |
-#' list of evalation function to define condition evaluation on metadata: |
|
19 |
+#' It accepts a list of evalation function to define evaluation on metadata: |
|
20 | 20 |
#' \itemize{ |
21 | 21 |
#' \item{\code{\link{FN}}: Fullname evaluation, two attributes match |
22 | 22 |
#' if they both end with value and, if they have a further prefixes, |
... | ... |
@@ -27,8 +27,8 @@ |
27 | 27 |
#' if both end with value.} |
28 | 28 |
#' } |
29 | 29 |
#' |
30 |
-#' @return DataSet class object. It contains the value to use as input for the |
|
31 |
-#' subsequent GMQL function |
|
30 |
+#' @return GMQLDataset object. It contains the value to use as input |
|
31 |
+#' for the subsequent GMQLDataset method |
|
32 | 32 |
#' |
33 | 33 |
#' @examples |
34 | 34 |
#' |
... | ... |
@@ -1,28 +1,22 @@ |
1 |
-#' GMQL operation: ORDER |
|
1 |
+#' Method arrange |
|
2 | 2 |
#' |
3 | 3 |
#' It is used to order either samples or sample regions or both, according to |
4 | 4 |
#' a set of metadata and/or region attributes, and/or region coordinates. |
5 | 5 |
#' Order can be specified as ascending / descending for every attribute |
6 | 6 |
#' The number of samples and their regions remain the same |
7 |
-#' (unless mtop/rtop parameters specified) but a new ordering metadata |
|
7 |
+#' (unless fetching options are specified) but a new ordering metadata |
|
8 | 8 |
#' and/or region attribute is added. |
9 | 9 |
#' Sorted samples or regions have a new attribute "order", |
10 |
-#' added to either metadata, or regions, or both of them as specified in input |
|
11 |
-#' The input mtop = k and rtop = m extracts the first k samples |
|
12 |
-#' and m regions respectively, the clause mtopg = k and rtopg = m |
|
13 |
-#' performs grouping operation, grouping by identical values |
|
14 |
-#' of ordering attributes and then selects the first k samples |
|
15 |
-#' or regions of each group |
|
10 |
+#' added to either metadata, or regions, or both of them as specified in inputs |
|
16 | 11 |
#' |
17 | 12 |
#' @importFrom rJava J |
18 | 13 |
#' @importFrom rJava .jnull |
19 | 14 |
#' @importFrom rJava .jarray |
20 | 15 |
#' |
21 | 16 |
#' @param .data GMQLDataset class object |
22 |
-#' @param metadata_ordering list of order objects where every object |
|
23 |
-#' contains the name of metadata. |
|
24 |
-#' The ORDER's available are: \code{\link{ASC}}, \code{\link{DESC}} |
|
25 |
-#' Every condition accepts only one string value. (e.g. ASC("cell_type") ) |
|
17 |
+#' @param metadata_ordering list of ordering function contains name of |
|
18 |
+#' metadata. |
|
19 |
+#' The function available are: \code{\link{ASC}}, \code{\link{DESC}} |
|
26 | 20 |
#' |
27 | 21 |
#' @param fetch_opt string indicating the option used to fetch the |
28 | 22 |
#' first k sample: |
... | ... |
@@ -36,10 +30,9 @@ |
36 | 30 |
#' @param num_fetch integer value identifying the number of region to fetch |
37 | 31 |
#' by default is 0, that's means all sample are fetched |
38 | 32 |
#' s |
39 |
-#' @param regions_ordering list of ORDER objects where every object contains |
|
40 |
-#' the name of region schema value. |
|
41 |
-#' The ORDER's available are: \code{\link{ASC}}, \code{\link{DESC}}. |
|
42 |
-#' Every condition accepts only one string value. (e.g. DESC("pvalue") ) |
|
33 |
+#' @param regions_ordering list of ordering function contains |
|
34 |
+#' name of region schema value. |
|
35 |
+#' The function available are: \code{\link{ASC}}, \code{\link{DESC}}. |
|
43 | 36 |
#' |
44 | 37 |
#' @param reg_fetch_opt string indicating the option used to fetch the |
45 | 38 |
#' first k regions: |
... | ... |
@@ -54,10 +47,8 @@ |
54 | 47 |
#' by default is 0, that's means all regions are fetched |
55 | 48 |
#' @param ... Additional arguments for use in specific methods. |
56 | 49 |
#' |
57 |
-#' |
|
58 |
-#' @return DataSet class object. It contains the value to use as input |
|
59 |
-#' for the subsequent GMQL function |
|
60 |
-#' |
|
50 |
+#' @return GMQLDataset object. It contains the value to use as input |
|
51 |
+#' for the subsequent GMQLDataset method |
|
61 | 52 |
#' |
62 | 53 |
#' @examples |
63 | 54 |
#' |
... | ... |
@@ -1,16 +1,15 @@ |
1 |
-#' GMQL Operation: PROJECT |
|
1 |
+#' Method select |
|
2 | 2 |
#' |
3 | 3 |
#' It creates, from an existing dataset, a new dataset with all the samples |
4 | 4 |
#' from input dataset, but keeping for each sample in the input dataset |
5 |
-#' only those metadata and/or region attributes expressed in the operator |
|
6 |
-#' parameter list. |
|
5 |
+#' only those metadata and/or region attributes expressed. |
|
7 | 6 |
#' Region coordinates and values of the remaining metadata remain equal to |
8 | 7 |
#' those in the input dataset. It allows to: |
9 | 8 |
#' \itemize{ |
10 | 9 |
#' \item{Remove existing metadata and/or region attributes from a dataset} |
11 |
-#' \item{Create new metadata and/or region attributes in the result} |
|
10 |
+#' \item{Update new metadata and/or region attributes in the result} |
|
12 | 11 |
#' } |
13 |
-#' |
|
12 |
+#' |
|
14 | 13 |
#' @importFrom rJava J |
15 | 14 |
#' @importFrom rJava .jnull |
16 | 15 |
#' @importFrom rJava .jarray |
... | ... |
@@ -48,8 +47,8 @@ |
48 | 47 |
#' |
49 | 48 |
#' @param ... Additional arguments for use in specific methods. |
50 | 49 |
#' |
51 |
-#' @return GMQLDataset class object. It contains the value to use as input |
|
52 |
-#' for the subsequent GMQL function |
|
50 |
+#' @return GMQLDataset object. It contains the value to use as input |
|
51 |
+#' for the subsequent GMQLDataset method |
|
53 | 52 |
#' |
54 | 53 |
#' @examples |
55 | 54 |
#' |
... | ... |
@@ -94,7 +93,7 @@ |
94 | 93 |
setMethod("select", "GMQLDataset", |
95 | 94 |
function(.data, metadata = NULL, metadata_update = NULL, |
96 | 95 |
all_but_meta = FALSE, regions = NULL, |
97 |
- regions_update = NULL, all_but_reg=FALSE) |
|
96 |
+ regions_update = NULL, all_but_reg = FALSE, ...) |
|
98 | 97 |
{ |
99 | 98 |
data = .data@value |
100 | 99 |
r_update <- substitute(regions_update) |
... | ... |
@@ -22,7 +22,7 @@ |
22 | 22 |
#' You can always perform it, calling the function \code{\link{login_gmql}} |
23 | 23 |
#' explicitly |
24 | 24 |
#' |
25 |
-#' @param username string name used during signup |
|
25 |
+#' @param username string name used during signup |
|
26 | 26 |
#' @param password string password used during signup |
27 | 27 |
#' |
28 | 28 |
#' @return None |
... | ... |
@@ -62,10 +62,10 @@ init_gmql <- function(output_format = "gtf", remote_processing = FALSE, |
62 | 62 |
WrappeR$initGMQL(out_format,remote_processing) |
63 | 63 |
} |
64 | 64 |
|
65 |
-#' GMQL Function: READ |
|
65 |
+#' Function read |
|
66 | 66 |
#' |
67 |
-#' Read a GMQL dataset or any other folder containig some homogenus sample |
|
68 |
-#' from disk, saving in Scala memory that can be referenced in R |
|
67 |
+#' Read a GMQL dataset, folder containig some homogenus sample from disk |
|
68 |
+#' or GrangesList saving in Scala memory that can be referenced in R. |
|
69 | 69 |
#' Also used to read a repository dataset in case of remote processing. |
70 | 70 |
#' |
71 | 71 |
#' @importFrom rJava .jnull |
... | ... |
@@ -89,8 +89,8 @@ init_gmql <- function(output_format = "gtf", remote_processing = FALSE, |
89 | 89 |
#' @param is_local logical value indicating local or remote dataset |
90 | 90 |
#' @param is_GMQL logical value indicating if is a GMQL dataset or not |
91 | 91 |
#' |
92 |
-#' @return DataSet class object. It contains the value to use as input |
|
93 |
-#' for the subsequent GMQL function |
|
92 |
+#' @return GMQLDataset object. It contains the value to use as input |
|
93 |
+#' for the subsequent GMQLDataset method |
|
94 | 94 |
#' |
95 | 95 |
#' @details |
96 | 96 |
#' Normally a GMQL dataset contains an XML schema file that contains |
... | ... |
@@ -98,6 +98,13 @@ init_gmql <- function(output_format = "gtf", remote_processing = FALSE, |
98 | 98 |
#' The CustomParser read this XML schema; |
99 | 99 |
#' if you already know what kind of schema your files are, use one of the |
100 | 100 |
#' parser defined without reading any XML schema |
101 |
+#' |
|
102 |
+#' If GrangesList has no metadata: i.e. metadata() is empty, two metadata are |
|
103 |
+#' generated. |
|
104 |
+#' \itemize{ |
|
105 |
+#' \item{"Provider" = "Polimi"} |
|
106 |
+#' \item{"Application" = "RGMQL"} |
|
107 |
+#' } |
|
101 | 108 |
#' |
102 | 109 |
#' @examples |
103 | 110 |
#' |
... | ... |
@@ -114,7 +121,7 @@ init_gmql <- function(output_format = "gtf", remote_processing = FALSE, |
114 | 121 |
#' r = read_dataset(test_path,"ANNParser") |
115 | 122 |
#' |
116 | 123 |
#' ## read remote public dataset stored into GMQL system repository |
117 |
-#' |
|
124 |
+#' ## If public dataset a prefix "public." is needed before dataset name |
|
118 | 125 |
#' r2 = read_dataset("public.HG19_TCGA_dnaseq",is_local = FALSE) |
119 | 126 |
#' |
120 | 127 |
#' } |
... | ... |
@@ -179,17 +186,13 @@ read_dataset <- function(dataset, parser = "CustomParser", is_local=TRUE, |
179 | 186 |
GMQLDataset(data) |
180 | 187 |
} |
181 | 188 |
|
182 |
-#' GMQL Function: READ |
|
183 |
-#' |
|
184 |
-#' Read a GrangesList saving in scala memory that can be referenced in R |
|
185 |
-#' |
|
189 |
+ |
|
186 | 190 |
#' @importFrom S4Vectors metadata |
187 | 191 |
#' @importFrom rJava J |
188 | 192 |
#' @importFrom rJava .jarray |
189 | 193 |
#' |
190 | 194 |
#' @param samples GrangesList |
191 | 195 |
#' |
192 |
-#' |
|
193 | 196 |
#' @name read |
194 | 197 |
#' @rdname read-function |
195 | 198 |
#' @export |
... | ... |
@@ -274,11 +277,11 @@ We provide two metadata for you") |
274 | 277 |
|
275 | 278 |
#' Disable or Enable remote processing |
276 | 279 |
#' |
277 |
-#' It allows to enable or disable remote processing |
|
280 |
+#' It allows to enable or disable remote processing |
|
278 | 281 |
#' |
279 | 282 |
#' @details |
280 | 283 |
#' The invocation of this function allow to change mode of processing. |
281 |
-#' after materialization is not possbile to switch the processing mode, |
|
284 |
+#' after invoking collect() is not possbile to switch the processing mode, |
|
282 | 285 |
#' |
283 | 286 |
#' @importFrom rJava J |
284 | 287 |
#' |
... | ... |
@@ -290,7 +293,7 @@ We provide two metadata for you") |
290 | 293 |
#' @examples |
291 | 294 |
#' |
292 | 295 |
#' # initialize with remote processing off |
293 |
-#' init_gmql("tab",remote_processing=FALSE) |
|
296 |
+#' init_gmql("tab",remote_processing = FALSE) |
|
294 | 297 |
#' |
295 | 298 |
#' # change processing mode to remote |
296 | 299 |
#' remote_processing(TRUE) |
... | ... |
@@ -1,13 +1,13 @@ |
1 |
-#' GMQL Operation: SELECT |
|
2 |
-#' |
|
3 |
-#' It returns all the samples satisfying the predicate on metadata. |
|
4 |
-#' If regions are specified, returns regions satisfying the predicate |
|
5 |
-#' on regions. |
|
6 |
-#' If semijoin clauses are specified they are applied, too. |
|
7 |
-#' When semijoin is defined, it extracts those samples containing all metadata |
|
8 |
-#' attribute defined in semijoin clause with at least one metadata value |
|
9 |
-#' in common with semi join dataset. |
|
10 |
-#' If no metadata in common between input dataset and semi join dataset, |
|
1 |
+#' Method filter |
|
2 |
+#' |
|
3 |
+#' It creates a new dataset from an existing one by extracting a subset of |
|
4 |
+#' samples and/or regions from the input dataset according to their predicate. |
|
5 |
+#' each sample in the output dataset has the same region attributes, |
|
6 |
+#' values, and metadata as in the input dataset. |
|
7 |
+#' When semijoin function is defined, it extracts those samples containing |
|
8 |
+#' all metadata attribute defined in semijoin clause with at least |
|
9 |
+#' one metadata value in common with semijoin dataset. |
|
10 |
+#' If no metadata in common between input dataset and semijoin dataset, |
|
11 | 11 |
#' no sample is extracted. |
12 | 12 |
#' |
13 | 13 |
#' @importFrom rJava J |
... | ... |
@@ -20,16 +20,15 @@ |
20 | 20 |
#' on metadata attribute. |
21 | 21 |
#' Only !, |, ||, &, && are admitted. |
22 | 22 |
#' @param r_predicate logical predicate made up by R logical operation |
23 |
-#' on chema region values. |
|
23 |
+#' on schema region values. |
|
24 | 24 |
#' Only !, |, ||, &, && are admitted. |
25 | 25 |
#' @param ... Additional arguments for use in specific methods. |
26 |
-#' |
|
27 |
-#' @param semijoin \code{\link{semijoin}} function |
|
26 |
+#' It is also accept \code{\link{semijoin}} function |
|
28 | 27 |
#' to define filter method with semijoin condition (see examples). |
29 | 28 |
#' |
30 | 29 |
#' |
31 |
-#' @return GMQLDataset class object. It contains the value to use as input |
|
32 |
-#' for the subsequent GMQL function |
|
30 |
+#' @return GMQLDataset object. It contains the value to use as input |
|
31 |
+#' for the subsequent GMQLDataset method |
|
33 | 32 |
#' |
34 | 33 |
#' @examples |
35 | 34 |
#' |
... | ... |
@@ -43,17 +42,17 @@ |
43 | 42 |
#' |
44 | 43 |
#' \dontrun{ |
45 | 44 |
#' |
46 |
-#' It creates a new dataset called 'jun_tf' by selecting those samples and |
|
47 |
-#' their regions from the existing 'data' dataset such that: |
|
48 |
-#' Each output sample has a metadata attribute called antibody_target |
|
49 |
-#' with value JUN. |
|
50 |
-#' Each output sample also has not a metadata attribute called "cell" |
|
51 |
-#' that has the same value of at least one of the values that a metadata |
|
52 |
-#' attribute equally called cell has in at least one sample |
|
53 |
-#' of the 'join_data' dataset. |
|
54 |
-#' For each sample satisfying previous condition,only its regions that |
|
55 |
-#' have a region attribute called pValue with the associated value |
|
56 |
-#' less than 0.01 are conserved in output |
|
45 |
+#' # It creates a new dataset called 'jun_tf' by selecting those samples and |
|
46 |
+#' # their regions from the existing 'data' dataset such that: |
|
47 |
+#' # Each output sample has a metadata attribute called antibody_target |
|
48 |
+#' # with value JUN. |
|
49 |
+#' # Each output sample also has not a metadata attribute called "cell" |
|
50 |
+#' # that has the same value of at least one of the values that a metadata |
|
51 |
+#' # attribute equally called cell has in at least one sample |
|
52 |
+#' # of the 'join_data' dataset. |
|
53 |
+#' # For each sample satisfying previous condition,only its regions that |
|
54 |
+#' # have a region attribute called pValue with the associated value |
|
55 |
+#' # less than 0.01 are conserved in output |
|
57 | 56 |
#' |
58 | 57 |
#' |
59 | 58 |
#' init_gmql() |
... | ... |
@@ -131,8 +130,7 @@ gmql_select <- function(input_data, predicate, region_predicate, s_join) |
131 | 130 |
#' considering semi_join IN semi_join_dataset |
132 | 131 |
#' |
133 | 132 |
#' @param ... Additional arguments for use in specific methods. |
134 |
-#' |
|
135 |
-#' This method accept a function to define condition evaluation on metadata. |
|
133 |
+#' It is also accpet a functions to define condition evaluation on metadata. |
|
136 | 134 |
#' \itemize{ |
137 | 135 |
#' \item{\code{\link{FN}}: Fullname evaluation, two attributes match |
138 | 136 |
#' if they both end with value and, if they have a further prefixes, |
... | ... |
@@ -143,9 +141,30 @@ gmql_select <- function(input_data, predicate, region_predicate, s_join) |
143 | 141 |
#' if both end with value.} |
144 | 142 |
#' } |
145 | 143 |
#' |
144 |
+#' @examples |
|
145 |
+#' |
|
146 |
+#' # It creates a new dataset called 'jun_tf' by selecting those samples and |
|
147 |
+#' # their regions from the existing 'data' dataset such that: |
|
148 |
+#' # Each output sample has a metadata attribute called antibody_target |
|
149 |
+#' # with value JUN. |
|
150 |
+#' # Each output sample also has not a metadata attribute called "cell" |
|
151 |
+#' # that has the same value of at least one of the values that a metadata |
|
152 |
+#' # attribute equally called cell has in at least one sample |
|
153 |
+#' # of the 'join_data' dataset. |
|
154 |
+#' # For each sample satisfying previous condition,only its regions that |
|
155 |
+#' # have a region attribute called pValue with the associated value |
|
156 |
+#' # less than 0.01 are conserved in output |
|
157 |
+#' |
|
158 |
+#' |
|
159 |
+#' init_gmql() |
|
160 |
+#' test_path <- system.file("example", "DATASET", package = "RGMQL") |
|
161 |
+#' test_path2 <- system.file("example", "DATASET_GDM", package = "RGMQL") |
|
162 |
+#' data <- read_dataset(test_path) |
|
163 |
+#' join_data <- read_dataset(test_path2) |
|
164 |
+#' jun_tf <- filter(data,NULL,NULL, semijoin(join_data, TRUE, DF("cell"))) |
|
165 |
+#' |
|
146 | 166 |
#' @return semijoin condition as list |
147 | 167 |
#' @export |
148 |
-#' |
|
149 | 168 |
semijoin <- function(data, not_in = FALSE, ...) |
150 | 169 |
{ |
151 | 170 |
semij_cond = list(...) |
... | ... |
@@ -1,10 +1,10 @@ |
1 | 1 |
#' Method union |
2 | 2 |
#' |
3 |
-#' Wrapper to GMQL union function |
|
3 |
+#' @description Wrapper to GMQL union function |
|
4 | 4 |
#' |
5 |
-#' It is used to integrate homogeneous or heterogeneous samples of two datasets |
|
6 |
-#' within a single dataset; for each sample of either input dataset, |
|
7 |
-#' a result sample is created as follows: |
|
5 |
+#' @description It is used to integrate homogeneous or heterogeneous samples |
|
6 |
+#' of two datasets within a single dataset; for each sample of either input |
|
7 |
+#' dataset, a result sample is created as follows: |
|
8 | 8 |
#' \itemize{ |
9 | 9 |
#' \item {Metadata are the same as in the original sample.} |
10 | 10 |
#' \item {Resulting schema is obtained by projecting the schema |
... | ... |
@@ -23,11 +23,11 @@ |
23 | 23 |
#' |
24 | 24 |
#' @importFrom rJava J |
25 | 25 |
#' |
26 |
-#' @param x GMQLDataset class object |
|
27 |
-#' @param y GMQLDataset class object |
|
26 |
+#' @param x GMQLDataset object |
|
27 |
+#' @param y GMQLDataset object |
|
28 | 28 |
#' |
29 |
-#' @return GMQLDataset class object. It contains the value to use as input |
|
30 |
-#' for the subsequent GMQL function |
|
29 |
+#' @return GMQLDataset object. It contains the value to use as input |
|
30 |
+#' for the subsequent GMQLDataset method |
|
31 | 31 |
#' |
32 | 32 |
#' @examples |
33 | 33 |
#' |
... | ... |
@@ -6,14 +6,15 @@ |
6 | 6 |
#' Ordering functions |
7 | 7 |
#' |
8 | 8 |
#' These functions is used to create a series of metadata as string |
9 |
-#' that require ordering on value. |
|
9 |
+#' that require ordering on value; is used only in arrange method. |
|
10 |
+#' (see example) |
|
10 | 11 |
#' |
11 | 12 |
#' \itemize{ |
12 | 13 |
#' \item{ASC: It defines a ascending order for input value} |
13 | 14 |
#' \item{DESC: It defines a descending order for input value} |
14 | 15 |
#' } |
15 | 16 |
#' |
16 |
-#' @param ... Additional arguments for use in specific methods. |
|
17 |
+#' @param ... series of metatdata as string |
|
17 | 18 |
#' |
18 | 19 |
#' @return ordering object |
19 | 20 |
#' |
... | ... |
@@ -33,7 +34,8 @@ |
33 | 34 |
#' fetch_opt = "mtop", num_fetch = 5, reg_fetch_opt = "rtop", |
34 | 35 |
#' reg_num_fetch = 7) |
35 | 36 |
#' |
36 |
-#' @name ORDERING |
|
37 |
+#' @name DESC |
|
38 |
+#' @aliases DESC |
|
37 | 39 |
#' @rdname ordering-class |
38 | 40 |
#' @export |
39 | 41 |
#' |
... | ... |
@@ -54,7 +56,8 @@ DESC <- function(...) |
54 | 56 |
order_matrix |
55 | 57 |
} |
56 | 58 |
|
57 |
-#' @name ORDERING |
|
59 |
+#' @name ASC |
|
60 |
+#' @aliases ASC |
|
58 | 61 |
#' @rdname ordering-class |
59 | 62 |
#' @export |
60 | 63 |
#' |
... | ... |
@@ -24,15 +24,13 @@ if(getRversion() >= "3.1.0") |
24 | 24 |
#' @param username string name used during signup |
25 | 25 |
#' @param password string password used during signup |
26 | 26 |
#' |
27 |
-#' @seealso \code{\link{logout_gmql}} |
|
28 |
-#' |
|
29 | 27 |
#' @details |
30 | 28 |
#' if both username and password are NULL you will be logged as guest |
31 | 29 |
#' After login you will receive an authentication token. |
32 | 30 |
#' As token remains vaild on server (until the next login / registration) |
33 | 31 |
#' a user can safely use a token fora previous session as a convenience, |
34 | 32 |
#' this token is saved in Global environment to perform subsequent REST call |
35 |
-#' even on complete R restart (if is environemnt has been saved, of course ...) |
|
33 |
+#' even on complete R restart (if is environemnt has been saved) |
|
36 | 34 |
#' If error occures a specific error is printed |
37 | 35 |
#' |
38 | 36 |
#' @return None |
... | ... |
@@ -149,8 +147,8 @@ logout_gmql <- function(url) |
149 | 147 |
|
150 | 148 |
#' Shows all Queries |
151 | 149 |
#' |
152 |
-#' It shows all the GMQL query saved on repository |
|
153 |
-#' using the proper GMQL web service available on a remote server |
|
150 |
+#' It shows all the GMQL query saved on repository using the proper GMQL |
|
151 |
+#' web service available on a remote server |
|
154 | 152 |
#' |
155 | 153 |
#' @import httr |
156 | 154 |
#' |
... | ... |
@@ -168,6 +166,7 @@ logout_gmql <- function(url) |
168 | 166 |
#' if error occures, a specific error is printed |
169 | 167 |
#' |
170 | 168 |
#' @examples |
169 |
+#' |
|
171 | 170 |
#' remote_url = "http://genomic.elet.polimi.it/gmql-rest-r" |
172 | 171 |
#' login_gmql(remote_url) |
173 | 172 |
#' list <- show_queries_list(remote_url) |
... | ... |
@@ -460,12 +459,14 @@ stop_job <- function(url, job_id) |
460 | 459 |
#' If error occures a specific error is printed |
461 | 460 |
#' |
462 | 461 |
#' @examples |
463 |
-#' \dontrun{ |
|
462 |
+#' |
|
464 | 463 |
#' remote_url = "http://genomic.elet.polimi.it/gmql-rest-r" |
465 | 464 |
#' login_gmql(remote_url) |
466 | 465 |
#' |
467 | 466 |
#' ## list all jobs |
468 | 467 |
#' list_jobs <- show_jobs_list(remote_url) |
468 |
+#' |
|
469 |
+#' \dontrun{ |
|
469 | 470 |
#' jobs_1 <- list_jobs$jobs[[1]] |
470 | 471 |
#' |
471 | 472 |
#' ## show job log |
... | ... |
@@ -518,7 +519,9 @@ trace_job <- function(url, job_id) |
518 | 519 |
|
519 | 520 |
#' Show all jobs |
520 | 521 |
#' |
521 |
-#' It show all Jobs (run, succeded or failed) invoked by user |
|
522 |
+#' It show all Jobs (run, succeded or failed) invoked by user using the proper |
|
523 |
+#' GMQL web service available on a remote server |
|
524 |
+#' |
|
522 | 525 |
#' @import httr |
523 | 526 |
#' @param url string url of server: It must contain the server address |
524 | 527 |
#' and base url; service name is added automatically |
... | ... |
@@ -832,9 +835,7 @@ upload_dataset <- function(url,datasetName,folderPath,schemaName=NULL, |
832 | 835 |
#' @details |
833 | 836 |
#' If no error occur, print "Deleted Dataset", otherwise a specific error |
834 | 837 |
#' is printed |
835 |
-#' |
|
836 |
-#' @seealso \code{\link{download_dataset}} |
|
837 |
-#' |
|
838 |
+#' |
|
838 | 839 |
#' @examples |
839 | 840 |
#' |
840 | 841 |
#' \dontrun{ |
... | ... |
@@ -885,7 +886,6 @@ delete_dataset <- function(url,datasetName) |
885 | 886 |
#' @details |
886 | 887 |
#' If error occures a specific error is printed |
887 | 888 |
#' |
888 |
-#' |
|
889 | 889 |
#' @examples |
890 | 890 |
#' |
891 | 891 |
#' ## download dataset in r working directory |
... | ... |
@@ -1,29 +1,17 @@ |
1 | 1 |
% Generated by roxygen2: do not edit by hand |
2 | 2 |
% Please edit documentation in R/S3Aggregates.R |
3 |
-\name{AGGREGATES} |
|
4 |
-\alias{AGGREGATES} |
|
3 |
+\name{SUM} |
|
5 | 4 |
\alias{SUM} |
6 |
-\alias{AGGREGATES} |
|
7 | 5 |
\alias{MIN} |
8 |
-\alias{AGGREGATES} |
|
9 | 6 |
\alias{MAX} |
10 |
-\alias{AGGREGATES} |
|
11 | 7 |
\alias{AVG} |
12 |
-\alias{AGGREGATES} |
|
13 | 8 |
\alias{BAG} |
14 |
-\alias{AGGREGATES} |
|
15 | 9 |
\alias{COUNT} |
16 |
-\alias{AGGREGATES} |
|
17 | 10 |
\alias{STD} |
18 |
-\alias{AGGREGATES} |
|
19 | 11 |
\alias{MEDIAN} |
20 |
-\alias{AGGREGATES} |
|
21 | 12 |
\alias{Q1} |
22 |
-\alias{AGGREGATES} |
|
23 | 13 |
\alias{Q2} |
24 |
-\alias{AGGREGATES} |
|
25 | 14 |
\alias{Q3} |
26 |
-\alias{AGGREGATES} |
|
27 | 15 |
\alias{BAGD} |
28 | 16 |
\title{AGGREGATES object class constructor} |
29 | 17 |
\usage{ |
... | ... |
@@ -15,8 +15,7 @@ aggregate(x, ...) |
15 | 15 |
\item{x}{GMQLDataset class object} |
16 | 16 |
|
17 | 17 |
\item{...}{Additional arguments for use in specific methods. |
18 |
- |
|
19 |
-list of evalation function to define condition evaluation on metadata: |
|
18 |
+It accepts a list of evalation function to define evaluation on metadata: |
|
20 | 19 |
\itemize{ |
21 | 20 |
\item{\code{\link{FN}}: Fullname evaluation, two attributes match |
22 | 21 |
if they both end with value and, if they have a further prefixes, |
... | ... |
@@ -28,20 +27,21 @@ if both end with value.} |
28 | 27 |
}} |
29 | 28 |
} |
30 | 29 |
\value{ |
31 |
-DataSet class object. It contains the value to use as input for the |
|
32 |
- subsequent GMQL function |
|
30 |
+GMQLDataset object. It contains the value to use as input |
|
31 |
+for the subsequent GMQLDataset method |
|
33 | 32 |
} |
34 | 33 |
\description{ |
35 | 34 |
Wrapper to GMQL merge function |
36 | 35 |
|
37 | 36 |
It builds a dataset consisting of a single sample having as many regions as |
38 | 37 |
the number of regions of the input data and as many metadata as the union of |
39 |
-the 'attribute-value' tuples of the input samples. A groupby clause can be |
|
40 |
-specified on metadata: the samples are then partitioned in groups, each with |
|
41 |
-a distinct value of the grouping metadata attributes. The operation is |
|
42 |
-separately applied to each group, yielding one sample in the result for each |
|
43 |
-group. Samples whose names are not present in the grouping metadata |
|
44 |
-parameter are disregarded. |
|
38 |
+the 'attribute-value' tuples of the input samples. |
|
39 |
+If at least one evaluation function is specified: the samples are then |
|
40 |
+partitioned in groups, each with a distinct value of the grouping metadata |
|
41 |
+attributes. The operation is separately applied to each group, yielding |
|
42 |
+one sample in the result for each group. |
|
43 |
+Samples whose names are not present in the grouping metadata parameter |
|
44 |
+are disregarded. |
|
45 | 45 |
} |
46 | 46 |
\examples{ |
47 | 47 |
|
... | ... |
@@ -18,15 +18,13 @@ arrange(.data, metadata_ordering = NULL, regions_ordering = NULL, |
18 | 18 |
\arguments{ |
19 | 19 |
\item{.data}{GMQLDataset class object} |
20 | 20 |
|
21 |
-\item{metadata_ordering}{list of order objects where every object |
|
22 |
-contains the name of metadata. |
|
23 |
-The ORDER's available are: \code{\link{ASC}}, \code{\link{DESC}} |
|
24 |
-Every condition accepts only one string value. (e.g. ASC("cell_type") )} |
|
21 |
+\item{metadata_ordering}{list of ordering function contains name of |
|
22 |
+metadata. |
|
23 |
+The function available are: \code{\link{ASC}}, \code{\link{DESC}}} |
|
25 | 24 |
|
26 |
-\item{regions_ordering}{list of ORDER objects where every object contains |
|
27 |
-the name of region schema value. |
|
28 |
-The ORDER's available are: \code{\link{ASC}}, \code{\link{DESC}}. |
|
29 |
-Every condition accepts only one string value. (e.g. DESC("pvalue") )} |
|
25 |
+\item{regions_ordering}{list of ordering function contains |
|
26 |
+name of region schema value. |
|
27 |
+The function available are: \code{\link{ASC}}, \code{\link{DESC}}.} |
|
30 | 28 |
|
31 | 29 |
\item{fetch_opt}{string indicating the option used to fetch the |
32 | 30 |
first k sample: |
... | ... |
@@ -56,8 +54,8 @@ by default is 0, that's means all regions are fetched} |
56 | 54 |
\item{...}{Additional arguments for use in specific methods.} |
57 | 55 |
} |
58 | 56 |
\value{ |
59 |
-DataSet class object. It contains the value to use as input |
|
60 |
-for the subsequent GMQL function |
|
57 |
+GMQLDataset object. It contains the value to use as input |
|
58 |
+for the subsequent GMQLDataset method |
|
61 | 59 |
} |
62 | 60 |
\description{ |
63 | 61 |
Wrapper to GMQL order function |
... | ... |
@@ -66,15 +64,10 @@ It is used to order either samples or sample regions or both, according to |
66 | 64 |
a set of metadata and/or region attributes, and/or region coordinates. |
67 | 65 |
Order can be specified as ascending / descending for every attribute |
68 | 66 |
The number of samples and their regions remain the same |
69 |
-(unless mtop/rtop parameters specified) but a new ordering metadata |
|
67 |
+(unless fetching options are specified) but a new ordering metadata |
|
70 | 68 |
and/or region attribute is added. |
71 | 69 |
Sorted samples or regions have a new attribute "order", |
72 |
-added to either metadata, or regions, or both of them as specified in input |
|
73 |
-The input mtop = k and rtop = m extracts the first k samples |
|
74 |
-and m regions respectively, the clause mtopg = k and rtopg = m |
|
75 |
-performs grouping operation, grouping by identical values |
|
76 |
-of ordering attributes and then selects the first k samples |
|
77 |
-or regions of each group |
|
70 |
+added to either metadata, or regions, or both of them as specified in inputs |
|
78 | 71 |
} |
79 | 72 |
\examples{ |
80 | 73 |
|
... | ... |
@@ -27,6 +27,9 @@ None |
27 | 27 |
\description{ |
28 | 28 |
Wrapper to GMQL materialize function |
29 | 29 |
|
30 |
+Wrapper to GMQL materialize function |
|
31 |
+} |
|
32 |
+\details{ |
|
30 | 33 |
It saves the contents of a dataset that contains samples metadata and |
31 | 34 |
samples regions. |
32 | 35 |
It is normally used to persist the contents of any dataset generated |
... | ... |
@@ -1,11 +1,8 @@ |
1 | 1 |
% Generated by roxygen2: do not edit by hand |
2 | 2 |
% Please edit documentation in R/evaluation-functions.R |
3 |
-\name{evaluation} |
|
4 |
-\alias{evaluation} |
|
3 |
+\name{FN} |
|
5 | 4 |
\alias{FN} |
6 |
-\alias{evaluation} |
|
7 | 5 |
\alias{EX} |
8 |
-\alias{evaluation} |
|
9 | 6 |
\alias{DF} |
10 | 7 |
\title{Condition evaluation functions} |
11 | 8 |
\usage{ |
... | ... |
@@ -74,22 +74,22 @@ if both end with value.} |
74 | 74 |
\item{variation}{string identifying the cover GMQL function variation. |
75 | 75 |
The admissible string are: |
76 | 76 |
\itemize{ |
77 |
-\item{flat: returns the contiguous region that starts from the first end |
|
77 |
+\item{FLAT: returns the contiguous region that starts from the first end |
|
78 | 78 |
and stops at the last end of the regions which would contribute |
79 | 79 |
to each region of the \emph{cover}.} |
80 |
-\item{summit: returns regions that start from a position |
|
80 |
+\item{SUMMIT: returns regions that start from a position |
|
81 | 81 |
where the number of intersecting regions is not increasing afterwards and |
82 | 82 |
stops at a position where either the number of intersecting regions |
83 | 83 |
decreases, or it violates the max accumulation index.} |
84 |
-\item{histogram: returns the non-overlapping regions contributing to |
|
84 |
+\item{HISTOGRAM: returns the non-overlapping regions contributing to |
|
85 | 85 |
the cover, each with its accumulation index value, which is assigned to |
86 | 86 |
the AccIndex region attribute.} |
87 |
-\item{cover: default value.} |
|
87 |
+\item{COVER: default value.} |
|
88 | 88 |
}} |
89 | 89 |
} |
90 | 90 |
\value{ |
91 |
-GMQLDataset class object. It contains the value to use as input |
|
92 |
-for the subsequent GMQL function |
|
91 |
+GMQLDataset object. It contains the value to use as input |
|
92 |
+for the subsequent GMQLDataset method |
|
93 | 93 |
} |
94 | 94 |
\description{ |
95 | 95 |
Wrapper to GMQL cover function |
... | ... |
@@ -1,9 +1,7 @@ |
1 | 1 |
% Generated by roxygen2: do not edit by hand |
2 | 2 |
% Please edit documentation in R/S3Cover-Param.R |
3 |
-\name{COVER-PARAMETER} |
|
4 |
-\alias{COVER-PARAMETER} |
|
3 |
+\name{ALL} |
|
5 | 4 |
\alias{ALL} |
6 |
-\alias{COVER-PARAMETER} |
|
7 | 5 |
\alias{ANY} |
8 | 6 |
\title{PARAM object class constructor} |
9 | 7 |
\usage{ |
... | ... |
@@ -1,19 +1,12 @@ |
1 | 1 |
% Generated by roxygen2: do not edit by hand |
2 | 2 |
% Please edit documentation in R/S3Distal.R |
3 |
-\name{DISTAL} |
|
4 |
-\alias{DISTAL} |
|
3 |
+\name{DL} |
|
5 | 4 |
\alias{DL} |
6 |
-\alias{DISTAL} |
|
7 | 5 |
\alias{DG} |
8 |
-\alias{DISTAL} |
|
9 | 6 |
\alias{DLE} |
10 |
-\alias{DISTAL} |
|
11 | 7 |
\alias{DGE} |
12 |
-\alias{DISTAL} |
|
13 | 8 |
\alias{MD} |
14 |
-\alias{DISTAL} |
|
15 | 9 |
\alias{UP} |
16 |
-\alias{DISTAL} |
|
17 | 10 |
\alias{DOWN} |
18 | 11 |
\title{DISTAL object class constructor} |
19 | 12 |
\usage{ |
... | ... |
@@ -36,7 +36,6 @@ its metadata file |
36 | 36 |
} |
37 | 37 |
\examples{ |
38 | 38 |
|
39 |
-\dontrun{ |
|
40 | 39 |
library(GenomicRanges) |
41 | 40 |
gr1 <- GRanges(seqnames = "chr2", ranges = IRanges(3, 6), strand = "+", |
42 | 41 |
score = 5L, GC = 0.45) |
... | ... |
@@ -46,7 +45,8 @@ score = 3:4, GC = c(0.3, 0.5)) |
46 | 45 |
grl = GRangesList(gr1, gr2) |
47 | 46 |
test_out_path <- system.file("example", package = "RGMQL") |
48 | 47 |
export_gmql(grl, test_out_path,TRUE) |
49 |
-} |
|
48 |
+ |
|
49 |
+ |
|
50 | 50 |
} |
51 | 51 |
\seealso{ |
52 | 52 |
\code{\link{import_gmql}} |
... | ... |
@@ -16,8 +16,7 @@ extend(.data, ...) |
16 | 16 |
\item{.data}{GMQLDataset class object} |
17 | 17 |
|
18 | 18 |
\item{...}{Additional arguments for use in specific methods. |
19 |
- |
|
20 |
-This method accept a series of aggregate function on region attribute. |
|
19 |
+It accept a series of aggregate function on region attribute. |
|
21 | 20 |
All the element in the form \emph{key} = \emph{aggregate}. |
22 | 21 |
The \emph{aggregate} is an object of class AGGREGATES |
23 | 22 |
The aggregate functions available are: \code{\link{SUM}}, |
... | ... |
@@ -36,15 +35,15 @@ attributes. Two style are allowed: |
36 | 35 |
"mixed style" is not allowed} |
37 | 36 |
} |
38 | 37 |
\value{ |
39 |
-GMQLDataset class object. It contains the value to use as input |
|
40 |
-for the subsequent GMQL function |
|
38 |
+GMQLDataset object. It contains the value to use as input |
|
39 |
+for the subsequent GMQLDataset method |
|
41 | 40 |
} |
42 | 41 |
\description{ |
43 | 42 |
Wrapper to GMQL extend function |
44 | 43 |
|
45 |
-It generates new metadata attributes as result of aggregate functions |
|
46 |
-applied to sample region attributes and adds them to the existing metadata |
|
47 |
-attributes of the sample. |
|
44 |
+For each sample in an input dataset, it generates new metadata attributes |
|
45 |
+as result of aggregate functions applied to sample region attributes |
|
46 |
+and adds them to the existing metadata attributes of the sample. |
|
48 | 47 |
Aggregate functions are applied sample by sample. |
49 | 48 |
} |
50 | 49 |
\examples{ |
... | ... |
@@ -22,29 +22,28 @@ on metadata attribute. |
22 | 22 |
Only !, |, ||, &, && are admitted.} |
23 | 23 |
|
24 | 24 |
\item{r_predicate}{logical predicate made up by R logical operation |
25 |
-on chema region values. |
|
25 |
+on schema region values. |
|
26 | 26 |
Only !, |, ||, &, && are admitted.} |
27 | 27 |
|
28 |
-\item{semijoin}{\code{\link{semijoin}} function |
|
28 |
+\item{...}{Additional arguments for use in specific methods. |
|
29 |
+It is also accept \code{\link{semijoin}} function |
|
29 | 30 |
to define filter method with semijoin condition (see examples).} |
30 |
- |
|
31 |
-\item{...}{Additional arguments for use in specific methods.} |
|
32 | 31 |
} |
33 | 32 |
\value{ |
34 |
-GMQLDataset class object. It contains the value to use as input |
|
35 |
-for the subsequent GMQL function |
|
33 |
+GMQLDataset object. It contains the value to use as input |
|
34 |
+for the subsequent GMQLDataset method |
|
36 | 35 |
} |
37 | 36 |
\description{ |
38 | 37 |
Wrapper to GMQL select function |
39 | 38 |
|
40 |
-It returns all the samples satisfying the predicate on metadata. |
|
41 |
-If regions are specified, returns regions satisfying the predicate |
|
42 |
-on regions. |
|
43 |
-If semijoin clauses are specified they are applied, too. |
|
44 |
-When semijoin is defined, it extracts those samples containing all metadata |
|
45 |
-attribute defined in semijoin clause with at least one metadata value |
|
46 |
-in common with semi join dataset. |
|
47 |
-If no metadata in common between input dataset and semi join dataset, |
|
39 |
+It creates a new dataset from an existing one by extracting a subset of |
|
40 |
+samples and/or regions from the input dataset according to their predicate. |
|
41 |
+each sample in the output dataset has the same region attributes, |
|
42 |
+values, and metadata as in the input dataset. |
|
43 |
+When semijoin function is defined, it extracts those samples containing |
|
44 |
+all metadata attribute defined in semijoin clause with at least |
|
45 |
+one metadata value in common with semijoin dataset. |
|
46 |
+If no metadata in common between input dataset and semijoin dataset, |
|
48 | 47 |
no sample is extracted. |
49 | 48 |
} |
50 | 49 |
\examples{ |
... | ... |
@@ -59,17 +58,17 @@ s <- filter(input, Patient_age < 70) |
59 | 58 |
|
60 | 59 |
\dontrun{ |
61 | 60 |
|
62 |
-It creates a new dataset called 'jun_tf' by selecting those samples and |
|
63 |
-their regions from the existing 'data' dataset such that: |
|
64 |
-Each output sample has a metadata attribute called antibody_target |
|
65 |
-with value JUN. |
|
66 |
-Each output sample also has not a metadata attribute called "cell" |
|
67 |
-that has the same value of at least one of the values that a metadata |
|
68 |
-attribute equally called cell has in at least one sample |
|
69 |
-of the 'join_data' dataset. |
|
70 |
-For each sample satisfying previous condition,only its regions that |
|
71 |
-have a region attribute called pValue with the associated value |
|
72 |
-less than 0.01 are conserved in output |
|
61 |
+# It creates a new dataset called 'jun_tf' by selecting those samples and |
|
62 |
+# their regions from the existing 'data' dataset such that: |
|
63 |
+# Each output sample has a metadata attribute called antibody_target |
|
64 |
+# with value JUN. |
|
65 |
+# Each output sample also has not a metadata attribute called "cell" |
|
66 |
+# that has the same value of at least one of the values that a metadata |
|
67 |
+# attribute equally called cell has in at least one sample |
|
68 |
+# of the 'join_data' dataset. |
|
69 |
+# For each sample satisfying previous condition,only its regions that |
|
70 |
+# have a region attribute called pValue with the associated value |
|
71 |
+# less than 0.01 are conserved in output |
|
73 | 72 |
|
74 | 73 |
|
75 | 74 |
init_gmql() |
... | ... |
@@ -36,7 +36,7 @@ seqnames,ranges ans strand and a variable part made up by the regions |
36 | 36 |
defined as input. |
37 | 37 |
The metadata and metadata_prefix are used to filter the data and choose |
38 | 38 |
only the samples that match at least one metdatata with its prefix. |
39 |
-The regions are shown for each sample obtained from filtering. |
|
39 |
+The input regions are shown for each sample obtained from filtering. |
|
40 | 40 |
} |
41 | 41 |
\details{ |
42 | 42 |
This function works only with datatset or Grangeslist that have the same |
... | ... |
@@ -26,12 +26,14 @@ It show a job log or traces a specific job |
26 | 26 |
If error occures a specific error is printed |
27 | 27 |
} |
28 | 28 |
\examples{ |
29 |
-\dontrun{ |
|
29 |
+ |
|
30 | 30 |
remote_url = "http://genomic.elet.polimi.it/gmql-rest-r" |
31 | 31 |
login_gmql(remote_url) |
32 | 32 |
|
33 | 33 |
## list all jobs |
34 | 34 |
list_jobs <- show_jobs_list(remote_url) |
35 |
+ |
|
36 |
+\dontrun{ |
|
35 | 37 |
jobs_1 <- list_jobs$jobs[[1]] |
36 | 38 |
|
37 | 39 |
## show job log |
... | ... |
@@ -28,7 +28,7 @@ After login you will receive an authentication token. |
28 | 28 |
As token remains vaild on server (until the next login / registration) |
29 | 29 |
a user can safely use a token fora previous session as a convenience, |
30 | 30 |
this token is saved in Global environment to perform subsequent REST call |
31 |
-even on complete R restart (if is environemnt has been saved, of course ...) |
|
31 |
+even on complete R restart (if is environemnt has been saved) |
|
32 | 32 |
If error occures a specific error is printed |
33 | 33 |
} |
34 | 34 |
\examples{ |
... | ... |
@@ -37,6 +37,3 @@ remote_url = "http://genomic.elet.polimi.it/gmql-rest-r" |
37 | 37 |
login_gmql(remote_url) |
38 | 38 |
|
39 | 39 |
} |
40 |
-\seealso{ |
|
41 |
-\code{\link{logout_gmql}} |
|
42 |
-} |
... | ... |
@@ -47,8 +47,8 @@ if both end with value.} |
47 | 47 |
}} |
48 | 48 |
} |
49 | 49 |
\value{ |
50 |
-GMQLDataset class object. It contains the value to use as input |
|
51 |
-for the subsequent GMQL function |
|
50 |
+GMQLDataset object. It contains the value to use as input |
|
51 |
+for the subsequent GMQLDataset method |
|
52 | 52 |
} |
53 | 53 |
\description{ |
54 | 54 |
Wrapper to GMQL map function |
... | ... |
@@ -53,13 +53,10 @@ if both end with value.} |
53 | 53 |
}} |
54 | 54 |
} |
55 | 55 |
\value{ |
56 |
-GMQLDataset class object. It contains the value to use as input |
|
57 |
-for the subsequent GMQL function |
|
56 |
+GMQLDataset object. It contains the value to use as input |
|
57 |
+for the subsequent GMQLDataset method |
|
58 | 58 |
} |
59 | 59 |
\description{ |
60 |
-Wrapper to GMQL join function |
|
61 |
-} |
|
62 |
-\details{ |
|
63 | 60 |
It takes in input two datasets, respectively known as nchor (left) |
64 | 61 |
and experiment (right) and returns a dataset of samples consisting of |
65 | 62 |
regions extracted from the operands according to the specified condition |
... | ... |
@@ -1,11 +1,8 @@ |
1 | 1 |
% Generated by roxygen2: do not edit by hand |
2 | 2 |
% Please edit documentation in R/S3Operator.R |
3 |
-\name{OPERATORS} |
|
4 |
-\alias{OPERATORS} |
|
3 |
+\name{META} |
|
5 | 4 |
\alias{META} |
6 |
-\alias{OPERATORS} |
|
7 | 5 |
\alias{NIL} |
8 |
-\alias{OPERATORS} |
|
9 | 6 |
\alias{SQRT} |
10 | 7 |
\title{OPERATOR object class constructor} |
11 | 8 |
\usage{ |
... | ... |
@@ -1,9 +1,7 @@ |
1 | 1 |
% Generated by roxygen2: do not edit by hand |
2 | 2 |
% Please edit documentation in R/ordering-functions.R |
3 |
-\name{ORDERING} |
|
4 |
-\alias{ORDERING} |
|
3 |
+\name{DESC} |
|
5 | 4 |
\alias{DESC} |
6 |
-\alias{ORDERING} |
|
7 | 5 |
\alias{ASC} |
8 | 6 |
\title{Ordering functions} |
9 | 7 |
\usage{ |
... | ... |
@@ -12,14 +10,15 @@ DESC(...) |
12 | 10 |
ASC(...) |
13 | 11 |
} |
14 | 12 |
\arguments{ |
15 |
-\item{...}{Additional arguments for use in specific methods.} |
|
13 |
+\item{...}{series of metatdata as string} |
|
16 | 14 |
} |
17 | 15 |
\value{ |
18 | 16 |
ordering object |
19 | 17 |
} |
20 | 18 |
\description{ |
21 | 19 |
These functions is used to create a series of metadata as string |
22 |
-that require ordering on value. |
|
20 |
+that require ordering on value; is used only in arrange method. |
|
21 |
+(see example) |
|
23 | 22 |
} |
24 | 23 |
\details{ |
25 | 24 |
\itemize{ |
... | ... |
@@ -4,7 +4,7 @@ |
4 | 4 |
\alias{read} |
5 | 5 |
\alias{read_dataset} |
6 | 6 |
\alias{read} |
7 |
-\title{GMQL Function: READ} |
|
7 |
+\title{Function read} |
|
8 | 8 |
\usage{ |
9 | 9 |
read_dataset(dataset, parser = "CustomParser", is_local = TRUE, |
10 | 10 |
is_GMQL = TRUE) |
... | ... |
@@ -34,15 +34,13 @@ Default is CustomParser.} |
34 | 34 |
\item{samples}{GrangesList} |
35 | 35 |
} |
36 | 36 |
\value{ |
37 |
-DataSet class object. It contains the value to use as input |
|
38 |
-for the subsequent GMQL function |
|
37 |
+GMQLDataset object. It contains the value to use as input |
|
38 |
+for the subsequent GMQLDataset method |
|
39 | 39 |
} |
40 | 40 |
\description{ |
41 |
-Read a GMQL dataset or any other folder containig some homogenus sample |
|
42 |
-from disk, saving in Scala memory that can be referenced in R |
|
41 |
+Read a GMQL dataset, folder containig some homogenus sample from disk |
|
42 |
+or GrangesList saving in Scala memory that can be referenced in R. |
|
43 | 43 |
Also used to read a repository dataset in case of remote processing. |
44 |
- |
|
45 |
-Read a GrangesList saving in scala memory that can be referenced in R |
|
46 | 44 |
} |
47 | 45 |
\details{ |
48 | 46 |
Normally a GMQL dataset contains an XML schema file that contains |
... | ... |
@@ -50,6 +48,13 @@ name of column header. (e.g chr, start, stop, strand) |
50 | 48 |
The CustomParser read this XML schema; |
51 | 49 |
if you already know what kind of schema your files are, use one of the |
52 | 50 |
parser defined without reading any XML schema |
51 |
+ |
|
52 |
+If GrangesList has no metadata: i.e. metadata() is empty, two metadata are |
|
53 |
+generated. |
|
54 |
+\itemize{ |
|
55 |
+\item{"Provider" = "Polimi"} |
|
56 |
+\item{"Application" = "RGMQL"} |
|
57 |
+} |
|
53 | 58 |
} |
54 | 59 |
\examples{ |
55 | 60 |
|
... | ... |
@@ -66,7 +71,7 @@ test_path <- system.file("example", "DATASET", package = "RGMQL") |
66 | 71 |
r = read_dataset(test_path,"ANNParser") |
67 | 72 |
|
68 | 73 |
## read remote public dataset stored into GMQL system repository |
69 |
- |
|
74 |
+## If public dataset a prefix "public." is needed before dataset name |
|
70 | 75 |
r2 = read_dataset("public.HG19_TCGA_dnaseq",is_local = FALSE) |
71 | 76 |
|
72 | 77 |
} |
... | ... |
@@ -18,12 +18,12 @@ It allows to enable or disable remote processing |
18 | 18 |
} |
19 | 19 |
\details{ |
20 | 20 |
The invocation of this function allow to change mode of processing. |
21 |
-after materialization is not possbile to switch the processing mode, |
|
21 |
+after invoking collect() is not possbile to switch the processing mode, |
|
22 | 22 |
} |
23 | 23 |
\examples{ |
24 | 24 |
|
25 | 25 |
# initialize with remote processing off |
26 |
-init_gmql("tab",remote_processing=FALSE) |
|
26 |
+init_gmql("tab",remote_processing = FALSE) |
|
27 | 27 |
|
28 | 28 |
# change processing mode to remote |
29 | 29 |
remote_processing(TRUE) |
... | ... |
@@ -12,7 +12,7 @@ select(.data, ...) |
12 | 12 |
|
13 | 13 |
\S4method{select}{GMQLDataset}(.data, metadata = NULL, |
14 | 14 |
metadata_update = NULL, all_but_meta = FALSE, regions = NULL, |
15 |
- regions_update = NULL, all_but_reg = FALSE) |
|
15 |
+ regions_update = NULL, all_but_reg = FALSE, ...) |
|
16 | 16 |
} |
17 | 17 |
\arguments{ |
18 | 18 |
\item{.data}{GMQLDataset class object} |
... | ... |
@@ -54,21 +54,20 @@ are all except ones include in region parameter. |
54 | 54 |
if regions is not defined \emph{all_but_reg} is not considerd.} |
55 | 55 |
} |
56 | 56 |
\value{ |
57 |
-GMQLDataset class object. It contains the value to use as input |
|
58 |
-for the subsequent GMQL function |
|
57 |
+GMQLDataset object. It contains the value to use as input |
|
58 |
+for the subsequent GMQLDataset method |
|
59 | 59 |
} |
60 | 60 |
\description{ |
61 | 61 |
Wrapper to GMQL project function |
62 | 62 |
|
63 | 63 |
It creates, from an existing dataset, a new dataset with all the samples |
64 | 64 |
from input dataset, but keeping for each sample in the input dataset |
65 |
-only those metadata and/or region attributes expressed in the operator |
|
66 |
-parameter list. |
|
65 |
+only those metadata and/or region attributes expressed. |
|
67 | 66 |
Region coordinates and values of the remaining metadata remain equal to |
68 | 67 |
those in the input dataset. It allows to: |
69 | 68 |
\itemize{ |
70 | 69 |
\item{Remove existing metadata and/or region attributes from a dataset} |
71 |
-\item{Create new metadata and/or region attributes in the result} |
|
70 |
+\item{Update new metadata and/or region attributes in the result} |
|
72 | 71 |
} |
73 | 72 |
} |
74 | 73 |
\examples{ |
... | ... |
@@ -14,8 +14,7 @@ considering semi_join NOT IN semi_join_dataset, F => semijoin is performed |
14 | 14 |
considering semi_join IN semi_join_dataset} |
15 | 15 |
|
16 | 16 |
\item{...}{Additional arguments for use in specific methods. |
17 |
- |
|
18 |
-This method accept a function to define condition evaluation on metadata. |
|
17 |
+It is also accpet a functions to define condition evaluation on metadata. |
|
19 | 18 |
\itemize{ |
20 | 19 |
\item{\code{\link{FN}}: Fullname evaluation, two attributes match |
21 | 20 |
if they both end with value and, if they have a further prefixes, |
... | ... |
@@ -33,3 +32,26 @@ semijoin condition as list |
33 | 32 |
This function is use as support to filter method to define |
34 | 33 |
semijoin conditions on metadata |
35 | 34 |
} |
35 |
+\examples{ |
|
36 |
+ |
|
37 |
+# It creates a new dataset called 'jun_tf' by selecting those samples and |
|
38 |
+# their regions from the existing 'data' dataset such that: |
|
39 |
+# Each output sample has a metadata attribute called antibody_target |
|
40 |
+# with value JUN. |
|
41 |
+# Each output sample also has not a metadata attribute called "cell" |
|
42 |
+# that has the same value of at least one of the values that a metadata |
|
43 |
+# attribute equally called cell has in at least one sample |
|
44 |
+# of the 'join_data' dataset. |
|
45 |
+# For each sample satisfying previous condition,only its regions that |
|
46 |
+# have a region attribute called pValue with the associated value |
|
47 |
+# less than 0.01 are conserved in output |
|
48 |
+ |
|
49 |
+ |
|
50 |
+init_gmql() |
|
51 |
+test_path <- system.file("example", "DATASET", package = "RGMQL") |
|
52 |
+test_path2 <- system.file("example", "DATASET_GDM", package = "RGMQL") |
|
53 |
+data <- read_dataset(test_path) |
|
54 |
+join_data <- read_dataset(test_path2) |
|
55 |
+jun_tf <- filter(data,NULL,NULL, semijoin(join_data, TRUE, DF("cell"))) |
|
56 |
+ |
|
57 |
+} |
... | ... |
@@ -34,17 +34,16 @@ left_input_data that overlap with at least one region in right_input_data |
34 | 34 |
(even just one base).} |
35 | 35 |
} |
36 | 36 |
\value{ |
37 |
-GMQLDataset class object. It contains the value to use as input |
|
38 |
-for the subsequent GMQL function |
|
37 |
+GMQLDataset object. It contains the value to use as input |
|
38 |
+for the subsequent GMQLDataset method |
|
39 | 39 |
} |
40 | 40 |
\description{ |
41 | 41 |
Wrapper to GMQL difference function |
42 |
-} |
|
43 |
-\details{ |
|
44 |
-It produces one sample in the result for each sample of the left operand, |
|
45 |
-by keeping the same metadata of the left input sample and only those |
|
46 |
-regions (with their schema and values) of the left input sample which |
|
47 |
-do not intersect with any region in the right operand sample. |
|
42 |
+ |
|
43 |
+It produces one sample in the result for each sample of the |
|
44 |
+left operand, by keeping the same metadata of the left input sample |
|
45 |
+and only those regions (with their schema and values) of the left input |
|
46 |
+sample which do not intersect with any region in the right operand sample. |
|
48 | 47 |
The optional \emph{joinby} clause is used to extract a subset of couples |
49 | 48 |
from the cartesian product of two dataset \emph{x} and \emph{y} |
50 | 49 |
on which to apply the DIFFERENCE operator: |
... | ... |
@@ -18,7 +18,8 @@ Every job in the list is identified by: |
18 | 18 |
} |
19 | 19 |
} |
20 | 20 |
\description{ |
21 |
-It show all Jobs (run, succeded or failed) invoked by user |
|
21 |
+It show all Jobs (run, succeded or failed) invoked by user using the proper |
|
22 |
+GMQL web service available on a remote server |
|
22 | 23 |
} |
23 | 24 |
\details{ |
24 | 25 |
If error occures a specific error is printed |
... | ... |
@@ -19,13 +19,14 @@ Every query in the list is identified by: |
19 | 19 |
} |
20 | 20 |
} |
21 | 21 |
\description{ |
22 |
-It shows all the GMQL query saved on repository |
|
23 |
-using the proper GMQL web service available on a remote server |
|
22 |
+It shows all the GMQL query saved on repository using the proper GMQL |
|
23 |
+web service available on a remote server |
|
24 | 24 |
} |
25 | 25 |
\details{ |
26 | 26 |
if error occures, a specific error is printed |
27 | 27 |
} |
28 | 28 |
\examples{ |
29 |
+ |
|
29 | 30 |
remote_url = "http://genomic.elet.polimi.it/gmql-rest-r" |
30 | 31 |
login_gmql(remote_url) |
31 | 32 |
list <- show_queries_list(remote_url) |
... | ... |
@@ -27,9 +27,9 @@ GrangesList with associated metadata |
27 | 27 |
GMQL Operation: TAKE |
28 | 28 |
|
29 | 29 |
It saves the contents of a dataset that contains samples metadata |
30 |
-and samples regions. |
|
31 |
-It is normally used to store in memoery the contents of any dataset |
|
32 |
-generated during a GMQL query. the operation can be very time-consuming. |
|
30 |
+and samples regions as GrangesList. |
|
31 |
+It is normally used to store in memory the contents of any dataset |
|
32 |
+generated during a GMQL query. The operation can be very time-consuming. |
|
33 | 33 |
If you have invoked any materialization before take function, |
34 | 34 |
all those dataset will be materialized as folder. |
35 | 35 |
} |
... | ... |
@@ -9,21 +9,20 @@ |
9 | 9 |
\S4method{union}{GMQLDataset,GMQLDataset}(x, y) |
10 | 10 |
} |
11 | 11 |
\arguments{ |
12 |
-\item{x}{GMQLDataset class object} |
|
12 |
+\item{x}{GMQLDataset object} |
|
13 | 13 |
|
14 |
-\item{y}{GMQLDataset class object} |
|
14 |
+\item{y}{GMQLDataset object} |
|
15 | 15 |
} |
16 | 16 |
\value{ |
17 |
-GMQLDataset class object. It contains the value to use as input |
|
18 |
-for the subsequent GMQL function |
|
17 |
+GMQLDataset object. It contains the value to use as input |
|
18 |
+for the subsequent GMQLDataset method |
|
19 | 19 |
} |
20 | 20 |
\description{ |
21 | 21 |
Wrapper to GMQL union function |
22 |
-} |
|
23 |
-\details{ |
|
24 |
-It is used to integrate homogeneous or heterogeneous samples of two datasets |
|
25 |
-within a single dataset; for each sample of either input dataset, |
|
26 |
-a result sample is created as follows: |
|
22 |
+ |
|
23 |
+It is used to integrate homogeneous or heterogeneous samples |
|
24 |
+of two datasets within a single dataset; for each sample of either input |
|
25 |
+dataset, a result sample is created as follows: |
|
27 | 26 |
\itemize{ |
28 | 27 |
\item {Metadata are the same as in the original sample.} |
29 | 28 |
\item {Resulting schema is obtained by projecting the schema |