Browse code

S4 methods and change help

Simone authored on 17/11/2017 14:45:18
Showing 79 changed files

... ...
@@ -98,10 +98,10 @@ Collate:
98 98
     'aggregate-class.R'
99 99
     'authOp.R'
100 100
     'browseOp.R'
101
-    'condition-class.R'
102 101
     'cover_param-class.R'
103 102
     'datasetOp.R'
104 103
     'distal-class.R'
104
+    'evaluation_functions.R'
105 105
     'onLoad.R'
106 106
     'operator-class.R'
107 107
     'ordering-class.R'
... ...
@@ -8,13 +8,14 @@ export(BAG)
8 8
 export(BAGD)
9 9
 export(COUNT)
10 10
 export(DESC)
11
+export(DF)
11 12
 export(DG)
12 13
 export(DGE)
13 14
 export(DL)
14 15
 export(DLE)
15 16
 export(DOWN)
16
-export(EXACT)
17
-export(FULL)
17
+export(EX)
18
+export(FN)
18 19
 export(MAX)
19 20
 export(MD)
20 21
 export(MEDIAN)
... ...
@@ -50,6 +51,7 @@ export(sample_metadata)
50 51
 export(sample_region)
51 52
 export(save_query)
52 53
 export(save_query_fromfile)
54
+export(semijoin)
53 55
 export(show_datasets_list)
54 56
 export(show_job_log)
55 57
 export(show_jobs_list)
... ...
@@ -70,6 +72,7 @@ exportMethods(materialize)
70 72
 exportMethods(setdiff)
71 73
 exportMethods(sort)
72 74
 exportMethods(subset)
75
+exportMethods(take)
73 76
 exportMethods(union)
74 77
 import(GenomicRanges)
75 78
 import(httr)
... ...
@@ -51,24 +51,20 @@
51 51
 #' \item{and expression built using PARAMETER object: (ALL() + N) / K or
52 52
 #' ALL() / K }
53 53
 #' }
54
-#' @param groupBy list of CONDITION objects where every object contains 
55
-#' the name of metadata to be used in semijoin, or simple string concatenation 
56
-#' of name of metadata, e.g. c("cell_type", "attribute_tag", "size") 
57
-#' without declaring condition.
58
-#' The CONDITION's available are:
54
+#' @param groupBy list of evalation function to define condition 
55
+#' evaluation on metadata:
59 56
 #' \itemize{
60
-#' \item{\code{\link{FULL}}: Fullname evaluation, two attributes match 
57
+#' \item{\code{\link{FN}}: Fullname evaluation, two attributes match 
61 58
 #' if they both end with value and, if they have a further prefixes,
62 59
 #' the two prefix sequence are identical}
63
-#' \item{\code{\link{EXACT}}: Exact evaluation, only attributes exactly 
60
+#' \item{\code{\link{EX}}: Exact evaluation, only attributes exactly 
64 61
 #' as value will match; no further prefixes are allowed. }
62
+#' \item{\code{\link{DF}}: Default evaluation, the two attributes match 
63
+#' if both end with value.}
65 64
 #' }
66
-#' Every condition accepts only one string value. (e.g. FULL("cell_type") )
67
-#' In case of single concatenation with no CONDITION or list with some value 
68
-#' without conditon, the metadata are considered having default 
69
-#' evaluation: the two attributes match if both end with value.
65
+#' @param ... Additional arguments for use in specific methods.
70 66
 #' 
71
-#' @param aggregates list of element in the form \emph{key} = \emph{aggregate}.
67
+#' In this case a series of element in the form \emph{key} = \emph{aggregate}.
72 68
 #' The \emph{aggregate} is an object of class AGGREGATES
73 69
 #' The aggregate functions available are: \code{\link{SUM}}, 
74 70
 #' \code{\link{COUNT}}, \code{\link{MIN}}, \code{\link{MAX}}, 
... ...
@@ -100,7 +96,6 @@
100 96
 #' the AccIndex region attribute.}
101 97
 #' \item{cover: default value.}
102 98
 #' }
103
-#' @param ... Additional arguments for use in specific methods.
104 99
 #' 
105 100
 #' @return GMQLDataset class object. It contains the value to use as input 
106 101
 #' for the subsequent GMQL function
... ...
@@ -128,26 +123,28 @@
128 123
 #' 
129 124
 #' test_path <- system.file("example", "DATASET", package = "RGMQL")
130 125
 #' exp = read_dataset(test_path)
131
-#' res = cover(exp, 2, 3, c("cell"), list(min_pValue = MIN("pvalue")))
126
+#' res = cover(exp, 2, 3, groupBy = list(DF("cell")), 
127
+#' min_pValue = MIN("pvalue"))
132 128
 #' }
133 129
 #' 
134 130
 #' @aliases cover, cover-method
135 131
 #' @export
136 132
 setMethod("cover", "GMQLDataset",
137
-            function(data, min_acc, max_acc, groupBy = NULL, aggregates = NULL, 
138
-                        variation = "cover")
133
+            function(data, min_acc, max_acc, groupBy = NULL, 
134
+                    variation = "cover", ...)
139 135
             {
140 136
                 val <- data@value
141 137
                 q_max <- .check_cover_param(max_acc,FALSE)
142 138
                 q_min <- .check_cover_param(min_acc,FALSE)
143 139
                 flag = toupper(variation)
140
+                aggregates = list(...)
144 141
                 gmql_cover(val, q_min, q_max, groupBy, aggregates, flag)
145 142
             })
146 143
 
147 144
 
148 145
 
149 146
 gmql_cover <- function(data, min_acc, max_acc, groupBy = NULL, 
150
-                        aggregates = NULL, flag)
147
+                            aggregates = NULL, flag)
151 148
 {
152 149
     
153 150
     if(!is.null(groupBy))
... ...
@@ -156,7 +153,7 @@ gmql_cover <- function(data, min_acc, max_acc, groupBy = NULL,
156 153
     else
157 154
         join_condition_matrix <- .jnull("java/lang/String")
158 155
 
159
-    if(!is.null(aggregates))
156
+    if(!is.null(aggregates) && !length(aggregates) == 0)
160 157
         metadata_matrix <- .jarray(.aggregates(aggregates,"AGGREGATES"),
161 158
                                     dispatch = TRUE)
162 159
     else
... ...
@@ -1,5 +1,7 @@
1
-#' GMQL Operation: DIFFERENCE
2
-#'
1
+#' Method setdiff
2
+#' 
3
+#' Wrapper to GMQL difference function
4
+#' 
3 5
 #' It produces one sample in the result for each sample of the left operand,
4 6
 #' by keeping the same metadata of the left input sample and only those 
5 7
 #' regions (with their schema and values) of the left input sample which 
... ...
@@ -17,22 +19,18 @@
17 19
 #' 
18 20
 #' @param x GMQLDataset class object
19 21
 #' @param y GMQLDataset class object
20
-#' @param joinBy vector of CONDITION objects where every object contains 
21
-#' the name of metadata to be used in semijoin, or string concatenation 
22
-#' of name of metadata, e.g. c("cell_type", "attribute_tag", "size") 
23
-#' without declaring condition.
24
-#' The CONDITION's available are:
22
+#' @param ... Additional arguments for use in specific methods.
23
+#' 
24
+#' This method accept a function to define condition evaluation on metadata.
25 25
 #' \itemize{
26
-#' \item{\code{\link{FULL}}: Fullname evaluation, two attributes match 
26
+#' \item{\code{\link{FN}}: Fullname evaluation, two attributes match 
27 27
 #' if they both end with value and, if they have a further prefixes,
28 28
 #' the two prefix sequence are identical}
29
-#' \item{\code{\link{EXACT}}: Exact evaluation, only attributes exactly 
29
+#' \item{\code{\link{EX}}: Exact evaluation, only attributes exactly 
30 30
 #' as value will match; no further prefixes are allowed. }
31
+#' \item{\code{\link{DF}}: Default evaluation, the two attributes match 
32
+#' if both end with value.}
31 33
 #' }
32
-#' Every condition accepts only one string value. (e.g. FULL("cell_type") )
33
-#' In case of single concatenation with no CONDITION the metadata are 
34
-#' considered having default evaluation: 
35
-#' the two attributes match if both end with value.
36 34
 #' 
37 35
 #' @param is_exact single logical value: TRUE means that the region difference 
38 36
 #' is executed only on regions in left_input_data with exactly the same 
... ...
@@ -40,7 +38,7 @@
40 38
 #' if is_exact = FALSE, the difference is executed on all regions in 
41 39
 #' left_input_data that overlap with at least one region in right_input_data 
42 40
 #' (even just one base).
43
-#'
41
+#' 
44 42
 #' @return GMQLDataset class object. It contains the value to use as input 
45 43
 #' for the subsequent GMQL function
46 44
 #' 
... ...
@@ -69,25 +67,29 @@
69 67
 #' test_path2 <- system.file("example", "DATASET_GDM", package = "RGMQL")
70 68
 #' exp1 = read_dataset(test_path)
71 69
 #' exp2 = read_dataset(test_path2)
72
-#' out = setdiff(exp1, exp2, joinBy = c("antibody_target"))
70
+#' out = setdiff(exp1, exp2, DF("antibody_target"))
73 71
 #'
74 72
 #' }
75
-#' 
76
-#' @aliases setdiff, setdiff-method
73
+#' @name setdiff
74
+#' @aliases setdiff,GMQLDataset,GMQLDataset-method
75
+#' @aliases setdiff-method
77 76
 #' @export
78 77
 setMethod("setdiff", c("GMQLDataset","GMQLDataset"),
79
-            function(x, y, is_exact = FALSE, joinBy = NULL)
78
+            function(x, y, ..., is_exact = FALSE)
80 79
             {
81
-                val_x = x@value
82
-                val_y = y@value
83
-                gmql_difference(val_x, val_y, is_exact, joinBy)
80
+                ptr_data_x = x@value
81
+                ptr_data_y = y@value
82
+                joinBy = list(...)
83
+                gmql_difference(ptr_data_x, ptr_data_y, is_exact, joinBy)
84 84
             })
85 85
 
86 86
 gmql_difference <- function(left_data, right_data, is_exact, joinBy)
87 87
 {
88
-    if(!is.null(joinBy))
89
-        join_condition_matrix <- .jarray(.join_condition(joinBy),
90
-                                            dispatch = TRUE)
88
+    if(!is.null(joinBy) && !length(joinBy) == 0)
89
+    {
90
+        cond <- .join_condition(joinBy)
91
+        join_condition_matrix <- .jarray(cond, dispatch = TRUE)
92
+    }
91 93
     else
92 94
         join_condition_matrix <- .jnull("java/lang/String")
93 95
     
... ...
@@ -1,11 +1,3 @@
1
-#' @name extend
2
-#' @rdname extend-GMQLDataset-method
3
-#' @aliases extend, GMQLDataset-method
4
-#' @exportMethod extend
5
-setGeneric("extend", function(.data, ...) 
6
-    standardGeneric("extend"))
7
-
8
-
9 1
 #' GMQL Operation: EXTEND
10 2
 #'
11 3
 #' It generates new metadata attributes as result of aggregate functions 
... ...
@@ -20,7 +12,8 @@ setGeneric("extend", function(.data, ...)
20 12
 #' @param .data GMQLDataset class object 
21 13
 #' @param ... Additional arguments for use in specific methods.
22 14
 #' 
23
-#' In this case a series of element in the form \emph{key} = \emph{aggregate}.
15
+#' This method accept a series of aggregate function on region attribute.
16
+#' All the element in the form \emph{key} = \emph{aggregate}.
24 17
 #' The \emph{aggregate} is an object of class AGGREGATES
25 18
 #' The aggregate functions available are: \code{\link{SUM}}, 
26 19
 #' \code{\link{COUNT}}, \code{\link{MIN}}, \code{\link{MAX}}, 
... ...
@@ -60,31 +53,32 @@ setGeneric("extend", function(.data, ...)
60 53
 #' init_gmql()
61 54
 #' test_path <- system.file("example", "DATASET", package = "RGMQL")
62 55
 #' exp = read_dataset(test_path)
63
-#' res = extend(exp, RegionCount = COUNT(), MinP = MIN("pvalue")))
56
+#' res = extend(exp, RegionCount = COUNT(), MinP = MIN("pvalue"))
64 57
 #' 
65 58
 #' }
66 59
 
67 60
 #' @aliases extend-method
68 61
 #' @export
69
-setMethod("extend", "GMQLDataset",
70
-            function(.data, ...)
62
+setMethod("extend", "GMQLDataset", function(.data, ...)
71 63
             {
72
-                val_x = .data@value
64
+                ptr_data = .data@value
73 65
                 meta <- list(...)
74
-                gmql_extend(val_x, meta)
66
+                gmql_extend(ptr_data, meta)
75 67
             })
76 68
 
77 69
 
78 70
 gmql_extend <-function(input_data, meta)
79 71
 {
80
-    if(!is.null(meta) && !length(meta)==0)
81
-        metadata_matrix <- .jarray(.aggregates(meta,"META_AGGREGATES"),
82
-                                    dispatch = TRUE)
72
+    if(!is.null(meta) && !length(meta) == 0)
73
+    {
74
+        aggr <- .aggregates(meta, "META_AGGREGATES")
75
+        metadata_matrix <- .jarray(aggr, dispatch = TRUE)
76
+    }
83 77
     else
84 78
         metadata_matrix <- .jnull("java/lang/String")
85 79
     
86 80
     WrappeR <- J("it/polimi/genomics/r/Wrapper")
87
-    response <- WrappeR$extend(metadata_matrix,input_data)
81
+    response <- WrappeR$extend(metadata_matrix, input_data)
88 82
     error <- strtoi(response[1])
89 83
     data <- response[2]
90 84
     if(error!=0)
... ...
@@ -39,7 +39,7 @@ setMethod("show", "GMQLDataset",
39 39
 # num_fetch = 0, reg_fetch_opt = NULL, 
40 40
 # reg_num_fetch = 0) standardGeneric("sort"))
41 41
 
42
-#' Method mutate
42
+#' Method aggregate
43 43
 #' 
44 44
 #' Wrapper to GMQL merge function
45 45
 #' 
... ...
@@ -47,7 +47,7 @@ setMethod("show", "GMQLDataset",
47 47
 #' @rdname aggregate-GMQLDataset-method
48 48
 #' @aliases aggregate
49 49
 #'  
50
-setGeneric("aggregate", function(data, groupBy = NULL) 
50
+setGeneric("aggregate", function(data, ...) 
51 51
                                     standardGeneric("aggregate"))
52 52
 
53 53
 
... ...
@@ -59,7 +59,7 @@ setGeneric("aggregate", function(data, groupBy = NULL)
59 59
 #' @rdname join-GMQLDataset-method
60 60
 #' @aliases join
61 61
 #' 
62
-setGeneric("join", function(x, y, by = NULL,...) standardGeneric("join"))
62
+setGeneric("join", function(x, y, ...) standardGeneric("join"))
63 63
 
64 64
 
65 65
 #' Method filter
... ...
@@ -70,7 +70,7 @@ setGeneric("join", function(x, y, by = NULL,...) standardGeneric("join"))
70 70
 #' @rdname filter-GMQLDataset-method
71 71
 #' @aliases filter
72 72
 #' 
73
-setGeneric("filter", function(.data,...) standardGeneric("filter"))
73
+setGeneric("filter", function(.data, ...) standardGeneric("filter"))
74 74
 
75 75
 #' Method cover
76 76
 #' 
... ...
@@ -80,7 +80,8 @@ setGeneric("filter", function(.data,...) standardGeneric("filter"))
80 80
 #' @rdname cover-GMQLDataset-method
81 81
 #' @aliases cover
82 82
 #' 
83
-setGeneric("cover", function(data, ...) standardGeneric("cover"))
83
+setGeneric("cover", function(data, min_acc, max_acc, ...)
84
+                        standardGeneric("cover"))
84 85
 
85 86
 #' Method map
86 87
 #' 
... ...
@@ -93,5 +94,35 @@ setGeneric("cover", function(data, ...) standardGeneric("cover"))
93 94
 setGeneric("map", function(x, y, ...) standardGeneric("map"))
94 95
 
95 96
 
97
+#' Method materialize
98
+#' 
99
+#' Wrapper to GMQL materialize function
100
+#' 
101
+#' @name materialize
102
+#' @rdname materialize-GMQLDataset-method
103
+#' @export
104
+setGeneric("materialize", function(data, ...) standardGeneric("materialize"))
105
+
106
+
107
+#' Method take
108
+#' 
109
+#' GMQL Operation: TAKE
110
+#' 
111
+#' @name take
112
+#' @rdname take-GMQLDataset-method
113
+#' @export
114
+setGeneric("take", function(data, ...) standardGeneric("take"))
115
+
116
+
117
+#' Method extend
118
+#' 
119
+#' Wrapper to GMQL extend function
120
+#' 
121
+#' @name extend
122
+#' @rdname extend-GMQLDataset-method
123
+#' @aliases extend, GMQLDataset-method
124
+#' @exportMethod extend
125
+setGeneric("extend", function(.data, ...) standardGeneric("extend"))
126
+
96 127
 
97 128
 
... ...
@@ -35,7 +35,8 @@
35 35
 #'
36 36
 #'
37 37
 #' @examples
38
-#'
38
+#' 
39
+#' \dontrun{
39 40
 #' library(GenomicRanges)
40 41
 #' gr1 <- GRanges(seqnames = "chr2", ranges = IRanges(3, 6), strand = "+", 
41 42
 #' score = 5L, GC = 0.45)
... ...
@@ -45,7 +46,7 @@
45 46
 #' grl = GRangesList(gr1, gr2)
46 47
 #' test_out_path <- system.file("example", package = "RGMQL")
47 48
 #' export_gmql(grl, test_out_path,TRUE)
48
-#'
49
+#' }
49 50
 #' @export
50 51
 #'
51 52
 export_gmql <- function(samples, dir_out, is_gtf)
... ...
@@ -69,7 +70,7 @@ export_gmql <- function(samples, dir_out, is_gtf)
69 70
 }
70 71
 
71 72
 
72
-.exportGMQL <- function(samples, dir_out,to_GTF)
73
+.exportGMQL <- function(samples, dir_out, to_GTF)
73 74
 {
74 75
     if(!is(samples,"GRangesList"))
75 76
         stop("samples must be a GrangesList")
... ...
@@ -18,28 +18,24 @@
18 18
 #' 
19 19
 #' @param x GMQLDataset class object
20 20
 #' @param y GMQLDataset class object
21
+
21 22
 #' @param genometric_predicate is a list of lists of DISTAL object
22 23
 #' For details of DISTAL objects see:
23 24
 #' \code{\link{DLE}}, \code{\link{DGE}}, \code{\link{DL}}, \code{\link{DG}},
24 25
 #' \code{\link{MD}}, \code{\link{UP}}, \code{\link{DOWN}}
26
+#' 
25 27
 #' @param ... Additional arguments for use in specific methods.
26
-#' @param by list of CONDITION objects where every object contains 
27
-#' the name of metadata to be used in semijoin, or simple string concatenation 
28
-#' of name of metadata, e.g. c("cell_type", "attribute_tag", "size") 
29
-#' without declaring condition.
30
-#' The CONDITION's available are:
28
+#' 
29
+#' This method accept a function to define condition evaluation on metadata.
31 30
 #' \itemize{
32
-#' \item{\code{\link{FULL}}: Fullname evaluation, two attributes match 
31
+#' \item{\code{\link{FN}}: Fullname evaluation, two attributes match 
33 32
 #' if they both end with value and, if they have a further prefixes,
34 33
 #' the two prefix sequence are identical}
35
-#' \item{\code{\link{EXACT}}: Exact evaluation, only attributes exactly 
34
+#' \item{\code{\link{EX}}: Exact evaluation, only attributes exactly 
36 35
 #' as value will match; no further prefixes are allowed. }
36
+#' \item{\code{\link{DF}}: Default evaluation, the two attributes match 
37
+#' if both end with value.}
37 38
 #' }
38
-#' Every condition accepts only one string value. (e.g. FULL("cell_type") )
39
-#' In case of single concatenation with no CONDITION, or list with some value 
40
-#' without conditon, the metadata are considered having default 
41
-#' evaluation: the two attributes match if both end with value.
42
-#' 
43 39
 #' 
44 40
 #' @param region_output single string that declare which region is given in 
45 41
 #' output for each input pair of left dataset right dataset regions 
... ...
@@ -63,8 +59,7 @@
63 59
 #'
64 60
 #' @return GMQLDataset class object. It contains the value to use as input 
65 61
 #' for the subsequent GMQL function
66
-#'
67
-#'
62
+#' 
68 63
 #' @examples
69 64
 #' 
70 65
 #' # Given a dataset 'hm' and one called 'tss' with a sample including 
... ...
@@ -80,20 +75,21 @@
80 75
 #' TSS = read_dataset(test_path)
81 76
 #' HM = read_dataset(test_path2)
82 77
 #' join_data = join(TSS, HM, 
83
-#' genometric_predicate = list(list(MD(1), DLE(120000))), by = c("provider"), 
84
-#' region_output="RIGHT")
78
+#' genometric_predicate = list(list(MD(1), DLE(120000))), DF("provider"), 
79
+#' region_output = "RIGHT")
85 80
 #' 
86 81
 
87 82
 #' @aliases join-method
88 83
 #' @export
89 84
 setMethod("join", "GMQLDataset",
90
-                function(x, y, by = NULL, genometric_predicate = NULL, 
91
-                    region_output="contig")
85
+                function(x, y, genometric_predicate = NULL, 
86
+                    region_output = "contig", ...)
92 87
                 {
93
-                    r_data <- x@value
94
-                    l_data <- y@value
95
-                    gmql_join(r_data, l_data, genometric_predicate, by, 
96
-                            region_output="contig")
88
+                    ptr_data_x <- x@value
89
+                    ptr_data_y <- y@value
90
+                    joinBy = list(...)
91
+                    gmql_join(ptr_data_x, ptr_data_y, genometric_predicate, 
92
+                                joinBy, region_output="contig")
97 93
                 })
98 94
 
99 95
 
... ...
@@ -40,27 +40,21 @@
40 40
 #' }
41 41
 #' "mixed style" is not allowed
42 42
 #'
43
-#' @param joinBy list of CONDITION objects where every object contains 
44
-#' the name of metadata to be used in semijoin, or simple string concatenation 
45
-#' of name of metadata, e.g. c("cell_type", "attribute_tag", "size") 
46
-#' without declaring condition.
47
-#' The CONDITION's available are:
43
+#' @param joinBy list of evalation function to define condition 
44
+#' evaluation on metadata:
48 45
 #' \itemize{
49
-#' \item{\code{\link{FULL}}: Fullname evaluation, two attributes match 
46
+#' \item{\code{\link{FN}}: Fullname evaluation, two attributes match 
50 47
 #' if they both end with value and, if they have a further prefixes,
51 48
 #' the two prefix sequence are identical}
52
-#' \item{\code{\link{EXACT}}: Exact evaluation, only attributes exactly 
49
+#' \item{\code{\link{EX}}: Exact evaluation, only attributes exactly 
53 50
 #' as value will match; no further prefixes are allowed. }
51
+#' \item{\code{\link{DF}}: Default evaluation, the two attributes match 
52
+#' if both end with value.}
54 53
 #' }
55
-#' Every condition accepts only one string value. (e.g. FULL("cell_type") )
56
-#' In case of single concatenation with no CONDITION, or list with some value 
57
-#' without conditon, the metadata are considered having default 
58
-#' evaluation: the two attributes match if both end with value.
59 54
 #' 
60 55
 #' @return GMQLDataset class object. It contains the value to use as input 
61 56
 #' for the subsequent GMQL function
62 57
 #' 
63
-#'
64 58
 #' @examples
65 59
 #'
66 60
 #' # It counts the number of regions in each sample from exp that overlap with 
... ...
@@ -77,7 +71,8 @@
77 71
 #' test_path2 <- system.file("example", "DATASET_GDM", package = "RGMQL")
78 72
 #' exp = read_dataset(test_path)
79 73
 #' ref = read_dataset(test_path2)
80
-#' out = map(ref,exp, minScore = MIN("score"), joinBy = c("cell_tissue"))
74
+#' out = map(ref,exp, minScore = MIN("score"), 
75
+#' joinBy = list(DF("cell_tissue")))
81 76
 #' 
82 77
 #' @aliases map-method
83 78
 #' @export
... ...
@@ -11,10 +11,10 @@
11 11
 #'
12 12
 #' init_gmql()
13 13
 #' test_path <- system.file("example","DATASET",package = "RGMQL")
14
-#' r = read_dataset(test_path)
15
-#' s = filter(r)
16
-#' m = aggregate(s, groupBy = c("antibody_targer","cell_karyotype"))
17
-#' materialize(m, dir_out = test_path)
14
+#' rd = read_dataset(test_path)
15
+#' filtered = filter(rd)
16
+#' aggr = aggregate(filtered, DF("antibody_targer","cell_karyotype"))
17
+#' materialize(aggr, dir_out = test_path)
18 18
 #' 
19 19
 #' \dontrun{
20 20
 #' execute()
... ...
@@ -65,9 +65,6 @@ execute <- function()
65 65
     }
66 66
 }
67 67
 
68
-#' @rdname materialize-GMQLDataset-method
69
-#' @export
70
-setGeneric("materialize", function(data, ...) standardGeneric("materialize"))
71 68
 
72 69
 
73 70
 #' GMQL Operation: MATERIALIZE
... ...
@@ -84,7 +81,9 @@ setGeneric("materialize", function(data, ...) standardGeneric("materialize"))
84 81
 #' @param data GMQLDataset class object
85 82
 #' @param dir_out destination folder path.
86 83
 #' by default is current working directory of the R process
87
-#' @param ... Additional arguments for use in specific methods.
84
+#' 
85
+#' @param ... Additional arguments for use in specific methods
86
+#' 
88 87
 #' @return None
89 88
 #'
90 89
 #' @examples
... ...
@@ -93,7 +92,7 @@ setGeneric("materialize", function(data, ...) standardGeneric("materialize"))
93 92
 #' test_path <- system.file("example","DATASET",package = "RGMQL")
94 93
 #' r = read_dataset(test_path)
95 94
 #' s = filter(r)
96
-#' m = aggregate(s, groupBy = c("antibody_targer","cell_karyotype"))
95
+#' m = aggregate(s, DF("antibody_targer","cell_karyotype"))
97 96
 #' materialize(m, dir_out = test_path)
98 97
 #' 
99 98
 #' @aliases materialize-method
... ...
@@ -101,14 +100,14 @@ setGeneric("materialize", function(data, ...) standardGeneric("materialize"))
101 100
 setMethod("materialize", "GMQLDataset",
102 101
             function(data, dir_out = getwd())
103 102
             {
104
-                gmql_materialize(data, dir_out)
103
+                ptr_data <- data@value
104
+                gmql_materialize(ptr_data, dir_out)
105 105
             })
106 106
 
107
-
108
-gmql_materialize <- function(data, dir_out)
107
+gmql_materialize <- function(input_data, dir_out)
109 108
 {
110 109
     WrappeR <- J("it/polimi/genomics/r/Wrapper")
111
-    response <- WrappeR$materialize(data@value,dir_out)
110
+    response <- WrappeR$materialize(input_data, dir_out)
112 111
     error <- strtoi(response[1])
113 112
     data <- response[2]
114 113
     if(error!=0)
... ...
@@ -132,31 +131,41 @@ gmql_materialize <- function(data, dir_out)
132 131
 #' @importFrom rJava J
133 132
 #' @importFrom rJava .jevalArray
134 133
 #' 
135
-#' @param input_data returned object from any GMQL function
134
+#' @param data returned object from any GMQL function
136 135
 #' @param rows number of rows for each sample regions that you want to 
137 136
 #' retrieve and stored in memory.
138 137
 #' by default is 0 that means take all rows for each sample
139
-#'
138
+#' 
139
+#' @param ... Additional arguments for use in specific methods
140
+#' 
140 141
 #' @return GrangesList with associated metadata
141 142
 #'
142 143
 #' @examples
143 144
 #'
144 145
 #' init_gmql()
145 146
 #' test_path <- system.file("example", "DATASET", package = "RGMQL")
146
-#' r = read_dataset(test_path)
147
-#' m = aggregate(r, groupBy = c("antibody_target", "cell_karyotype"))
148
-#' g <- take(m, rows = 45)
147
+#' rd = read_dataset(test_path)
148
+#' aggr = aggregate(rd, DF("antibody_target", "cell_karyotype"))
149
+#' taken <- take(aggr, rows = 45)
149 150
 #' 
151
+#' @aliases take-method
150 152
 #' @export
151
-#'
152
-take <- function(input_data, rows=0L)
153
+setMethod("take", "GMQLDataset",
154
+            function(data, rows = 0L)
155
+            {
156
+                ptr_data <- data@value
157
+                gmql_take(ptr_data, rows)
158
+            })
159
+
160
+
161
+gmql_take <- function(input_data, rows = 0L)
153 162
 {
154 163
     rows <- as.integer(rows[1])
155 164
     if(rows<0)
156 165
         stop("rows cannot be negative")
157 166
     
158 167
     WrappeR <- J("it/polimi/genomics/r/Wrapper")
159
-    response <- WrappeR$take(input_data@value,rows)
168
+    response <- WrappeR$take(input_data, rows)
160 169
     error <- strtoi(response[1])
161 170
     data <- response[2]
162 171
     if(error!=0)
... ...
@@ -16,22 +16,19 @@
16 16
 #' @importFrom rJava .jarray
17 17
 #'  
18 18
 #' @param data GMQLDataset class object 
19
-#' @param groupBy list of CONDITION objects where every object contains 
20
-#' the name of metadata to be used in semijoin, or simple string concatenation 
21
-#' of name of metadata, e.g. c("cell_type", "attribute_tag", "size") 
22
-#' without declaring condition.
23
-#' The CONDITION's available are:
19
+#' @param ... Additional arguments for use in specific methods.
20
+#' 
21
+#' 
22
+#' This method accept a function to define condition evaluation on metadata.
24 23
 #' \itemize{
25
-#' \item{\code{\link{FULL}}: Fullname evaluation, two attributes match 
24
+#' \item{\code{\link{FN}}: Fullname evaluation, two attributes match 
26 25
 #' if they both end with value and, if they have a further prefixes,
27 26
 #' the two prefix sequence are identical}
28
-#' \item{\code{\link{EXACT}}: Exact evaluation, only attributes exactly 
27
+#' \item{\code{\link{EX}}: Exact evaluation, only attributes exactly 
29 28
 #' as value will match; no further prefixes are allowed. }
29
+#' \item{\code{\link{DF}}: Default evaluation, the two attributes match 
30
+#' if both end with value.}
30 31
 #' }
31
-#' Every condition accepts only one string value. (e.g. FULL("cell_type") )
32
-#' In case of single concatenation with no CONDITION, or list with some value 
33
-#' without conditon, the metadata are considered having default 
34
-#' evaluation: the two attributes match if both end with value.
35 32
 #' 
36 33
 #' @return DataSet class object. It contains the value to use as input 
37 34
 #' for the subsequent GMQL function
... ...
@@ -41,33 +38,37 @@
41 38
 #' # It creates a dataset called merged which contains one sample for each 
42 39
 #' # antibody_target value found within the metadata of the exp dataset sample; 
43 40
 #' # each created sample contains all regions from all 'exp' samples 
44
-#' # with a specific value for their antibody_target metadata attribute.
41
+#' # with a specific value for their antibody_target and cell metadata 
42
+#' # attributes.
45 43
 #' 
46 44
 #' init_gmql()
47 45
 #' test_path <- system.file("example","DATASET",package = "RGMQL")
48 46
 #' exp = read_dataset(test_path)
49
-#' merged = aggregate(exp, groupBy = c("antibody_target"))
47
+#' merged = aggregate(exp, DF("antibody_target","cell"))
50 48
 #' 
51 49
 #' @aliases aggregate-method
52 50
 #' @export
53 51
 #' 
54 52
 setMethod("aggregate", "GMQLDataset",
55
-            function(data, groupBy = NULL)
53
+            function(data, ...)
56 54
             {
57
-                val = data@value
58
-                gmql_merge(val, groupBy)
55
+                ptr_data = data@value
56
+                groupBy = list(...)
57
+                gmql_merge(ptr_data, groupBy)
59 58
             })
60 59
 
61
-gmql_merge <- function(data, groupBy = NULL)
60
+gmql_merge <- function(input_data, groupBy)
62 61
 {
63
-    if(!is.null(groupBy))
64
-        join_condition_matrix <- .jarray(.join_condition(groupBy), 
65
-                                            dispatch = TRUE)
62
+    if(!is.null(groupBy) && !length(groupBy) == 0)
63
+    {
64
+        cond <- .join_condition(groupBy)
65
+        join_condition_matrix <- .jarray(cond, dispatch = TRUE)
66
+    }
66 67
     else
67 68
         join_condition_matrix <- .jnull("java/lang/String")
68 69
     
69 70
     WrappeR <- J("it/polimi/genomics/r/Wrapper")
70
-    response <- WrappeR$merge(join_condition_matrix,data)
71
+    response <- WrappeR$merge(join_condition_matrix, input_data)
71 72
     error <- strtoi(response[1])
72 73
     data <- response[2]
73 74
     if(error!=0)
... ...
@@ -42,7 +42,7 @@
42 42
 #' \itemize{
43 43
 #' \item{All aggregation functions already defined by AGGREGATES object}
44 44
 #' \item{All basic mathematical operations (+, -, *, /), including parenthesis}
45
-#' \item{SQRT, META, NULLABLE constructor object defined by OPERATOR object}
45
+#' \item{SQRT, META, NIL constructor object defined by OPERATOR object}
46 46
 #' }
47 47
 #' @return GMQLDataset class object. It contains the value to use as input 
48 48
 #' for the subsequent GMQL function
... ...
@@ -73,7 +73,7 @@
73 73
 #' ## the four basic coordinates (chr, left, right, strand) and the specified 
74 74
 #' ## region attributes 'variant_classification' and 'variant_type', 
75 75
 #' ## and as metadata attributes only the specified ones, 
76
-#' ## i.e. manually_curated__tissue_status and manually_curated__tumor_tag.
76
+#' ## i.e. manually_curated_tissue_status and manually_curated_tumor_tag.
77 77
 #' 
78 78
 #' init_gmql()
79 79
 #' test_path <- system.file("example", "DATASET", package = "RGMQL")
... ...
@@ -118,7 +118,8 @@ init_gmql <- function(output_format = "gtf", remote_processing = FALSE,
118 118
 #' r2 = read_dataset("public.HG19_TCGA_dnaseq",is_local = FALSE)
119 119
 #' 
120 120
 #' }
121
-#' 
121
+#' @name read
122
+#' @rdname read-function
122 123
 #' @export
123 124
 #'
124 125
 read_dataset <- function(dataset, parser = "CustomParser", is_local=TRUE, 
... ...
@@ -137,6 +138,11 @@ read_dataset <- function(dataset, parser = "CustomParser", is_local=TRUE,
137 138
         if(basename(dataset) !="files")
138 139
             dataset <- paste0(dataset,"/files")
139 140
         
141
+        schema_XML <- list.files(dataset, pattern = "*.schema$",
142
+                                    full.names = TRUE)
143
+        if(length(schema_XML) == 0)
144
+            stop("schema must be present")
145
+        
140 146
         schema_matrix <- .jnull("java/lang/String")
141 147
         url <- .jnull("java/lang/String")
142 148
     }
... ...
@@ -159,11 +165,12 @@ read_dataset <- function(dataset, parser = "CustomParser", is_local=TRUE,
159 165
             schema_matrix <- .jnull("java/lang/String")
160 166
         else
161 167
             schema_matrix <- .jarray(schema_matrix, dispatch = TRUE)
168
+        schema_XML <- .jnull("java/lang/String")
162 169
     }
163 170
 
164 171
     parser_name <- .check_parser(parser)
165 172
     response <- WrappeR$readDataset(dataset,parser_name, is_local, is_GMQL, 
166
-                                        schema_matrix)
173
+                                        schema_matrix,schema_XML)
167 174
     error <- strtoi(response[1])
168 175
     data <- response[2]
169 176
     if(error!=0)
... ...
@@ -182,21 +189,9 @@ read_dataset <- function(dataset, parser = "CustomParser", is_local=TRUE,
182 189
 #' 
183 190
 #' @param samples GrangesList
184 191
 #' 
185
-#' @return DataSet class object. It contains the value to use as input 
186
-#' for the subsequent GMQL function
187 192
 #' 
188
-#' @examples
189
-#' 
190
-#' library("GenomicRanges")
191
-#' gr1 <- GRanges(seqnames = "chr2", ranges = IRanges(103, 106),
192
-#' strand = "+", score = 5L, GC = 0.45)
193
-#' gr2 <- GRanges(seqnames = c("chr1", "chr1"), ranges = IRanges(c(107, 113), 
194
-#' width = 3), strand = c("+", "-"), score = 3:4, GC = c(0.3, 0.5))
195
-#' 
196
-#' grl <- GRangesList("txA" = gr1, "txB" = gr2)
197
-#' 
198
-#' data_out <- read(grl)
199
-#'
193
+#' @name read
194
+#' @rdname read-function
200 195
 #' @export
201 196
 #'
202 197
 read <- function(samples)
... ...
@@ -22,29 +22,11 @@
22 22
 #' @param r_predicate logical predicate made up by R logical operation 
23 23
 #' on chema region values. 
24 24
 #' Only !, |, ||, &, && are admitted.
25
-#' @param semi_join vector of CONDITION objects where every object contains 
26
-#' the name of metadata to be used in semijoin, or simple string concatenation 
27
-#' of name of metadata, e.g. c("cell_type", "attribute_tag", "size") 
28
-#' without declaring condition.
29
-#' The CONDITION's available are:
30
-#' \itemize{
31
-#' \item{\code{\link{FULL}}: Fullname evaluation, two attributes match 
32
-#' if they both end with value and, if they have a further prefixes,
33
-#' the two prefix sequence are identical}
34
-#' \item{\code{\link{EXACT}}: Exact evaluation, only attributes exactly 
35
-#' as value will match; no further prefixes are allowed. }
36
-#' }
37
-#' Every condition accepts only one string value. (e.g. FULL("cell_type") )
38
-#' In case of single concatenation with no CONDITION the metadata are 
39
-#' considered having default evaluation: 
40
-#' the two attributes match if both end with value.
25
+#' @param ... Additional arguments for use in specific methods.
41 26
 #' 
42
-#' @param not_in logical value: T => semijoin is perfomed 
43
-#' considering semi_join NOT IN semi_join_dataset, F => semijoin is performed 
44
-#' considering semi_join IN semi_join_dataset
27
+#' @param semijoin \code{\link{semijoin}} function 
28
+#' to define filter method with semijoin condition (see examples).
45 29
 #' 
46
-#' @param semi_join_dataset GMQLDataset class object
47
-#' @param ... Additional arguments for use in specific methods.
48 30
 #' 
49 31
 #' @return GMQLDataset class object. It contains the value to use as input 
50 32
 #' for the subsequent GMQL function
... ...
@@ -59,7 +41,6 @@
59 41
 #' input <- read_dataset(test_path)
60 42
 #' s <- filter(input, Patient_age < 70)
61 43
 #' 
62
-#' 
63 44
 #' \dontrun{
64 45
 #' 
65 46
 #' It creates a new dataset called 'jun_tf' by selecting those samples and 
... ...
@@ -80,8 +61,8 @@
80 61
 #' test_path2 <- system.file("example", "DATASET_GDM", package = "RGMQL")
81 62
 #' data <- read_dataset(test_path)
82 63
 #' join_data <-  read_dataset(test_path2)
83
-#' jun_tf <- filter(data, antibody_target == 'JUN', pValue < 0.01, c("cell"), 
84
-#' TRUE, semi_join_dataset = join_data )
64
+#' jun_tf <- filter(data, antibody_target == 'JUN', pValue < 0.01, 
65
+#' semijoin(join_data, TRUE, DF("cell")))
85 66
 #' 
86 67
 #' }
87 68
 #' 
... ...
@@ -89,8 +70,7 @@
89 70
 #' @export
90 71
 setMethod("filter", "GMQLDataset",
91 72
             function(.data, m_predicate = NULL, r_predicate = NULL, 
92
-                    semi_join = NULL, not_in = FALSE, 
93
-                    semi_join_dataset = NULL)
73
+                        semijoin = NULL, ...)
94 74
             {
95 75
                 val <- .data@value
96 76
                 meta_pred <- substitute(m_predicate)
... ...
@@ -110,44 +90,20 @@ setMethod("filter", "GMQLDataset",
110 90
                 }
111 91
                 else
112 92
                     region_predicate <- .jnull("java/lang/String")
113
-            
114
-                gmql_select(val, predicate, region_predicate, 
115
-                        semi_join, not_in, semi_join_dataset)
93
+
94
+                gmql_select(val, predicate, region_predicate, semijoin)
116 95
             })
117 96
 
118
-gmql_select <- function(input_data, predicate, region_predicate, semi_join, 
119
-                            semi_join_negation, semi_join_dataset)
97
+gmql_select <- function(input_data, predicate, region_predicate, s_join)
120 98
 {
121
-    if(is.null(semi_join) && is.null(semi_join_dataset))
122
-    {
123
-        join_condition_matrix <- .jnull("java/lang/String")
124
-        semi_join_dataset <- .jnull("java/lang/String")
125
-        semi_join_negation <- FALSE
126
-    }
127
-    else if(is.null(semi_join) || is.null(semi_join_dataset) ||
128
-            is.null(semi_join_negation)) 
129
-    {
130
-        warning("All semijoin parameters have to be set.
131
-Function will be invoked with these parameters as NULL")
132
-        semi_join_dataset <- .jnull("java/lang/String")
133
-        semi_join_negation <- FALSE
134
-        join_condition_matrix <- .jnull("java/lang/String")
135
-    }
99
+    if("semijoin" %in% names(s_join))
100
+        semijoin_data <- s_join$semijoin
136 101
     else
137
-    {
138
-        if(!isClass("GMQLDataset", semi_join_dataset))
139
-            stop("semi_join_dataset: Must be a GMQLDataset object")
140
-        
141
-        semi_join_dataset <- semi_join_dataset@value
142
-        .check_input(semi_join_dataset)
143
-        .check_logical(semi_join_negation)
144
-        join_condition_matrix <- .jarray(.join_condition(semi_join),
145
-                                            dispatch = TRUE)
146
-    }
102
+        semijoin_data <- .jnull("java/lang/String")
103
+    
147 104
     WrappeR <- J("it/polimi/genomics/r/Wrapper")
148
-    response <- WrappeR$select(predicate,region_predicate, 
149
-                                join_condition_matrix, semi_join_dataset, 
150
-                                semi_join_negation, input_data)
105
+    response <- WrappeR$select(predicate,region_predicate, semijoin_data, 
106
+                                    input_data)
151 107
     error <- strtoi(response[1])
152 108
     data <- response[2]
153 109
     if(error!=0)
... ...
@@ -157,6 +113,52 @@ Function will be invoked with these parameters as NULL")
157 113
         
158 114
 }
159 115
 
116
+#' Semijoin Condtion
117
+#' 
118
+#' 
119
+#' @param data GMQLDataset class object
120
+#' 
121
+#' @param not_in logical value: T => semijoin is perfomed 
122
+#' considering semi_join NOT IN semi_join_dataset, F => semijoin is performed 
123
+#' considering semi_join IN semi_join_dataset
124
+#' 
125
+#' @param ... Additional arguments for use in specific methods.
126
+#' 
127
+#' This method accept a function to define condition evaluation on metadata.
128
+#' \itemize{
129
+#' \item{\code{\link{FN}}: Fullname evaluation, two attributes match 
130
+#' if they both end with value and, if they have a further prefixes,
131
+#' the two prefix sequence are identical}
132
+#' \item{\code{\link{EX}}: Exact evaluation, only attributes exactly 
133
+#' as value will match; no further prefixes are allowed. }
134
+#' \item{\code{\link{DF}}: Default evaluation, the two attributes match 
135
+#' if both end with value.}
136
+#' }
137
+#' 
138
+#' @return semijoin condition
139
+#' @export
140
+#' 
141
+semijoin <- function(data, not_in = FALSE, ...)
142
+{
143
+    semij_cond = list(...)
144
+    if(is.null(data))
145
+        stop("data cannot be NULL")
146
+    
147
+    if(!isClass("GMQLDataset", data))
148
+        stop("data: Must be a GMQLDataset object") 
149
+    
150
+    .check_logical(not_in)
151
+    ptr_data <- data@value
152
+    
153
+    data_cond <- cbind(ptr_data,not_in)
154
+    cond <- .join_condition(semij_cond)
155
+    cond <- rbind(data_cond,cond)
156
+    join_condition_matrix <- .jarray(cond, dispatch = TRUE)
157
+    
158
+    semijoin <- list("semijoin" = join_condition_matrix)
159
+}
160
+
161
+
160 162
 .trasform <- function(predicate=NULL)
161 163
 {
162 164
     predicate <- gsub("&|&&","AND",predicate)
... ...
@@ -1,5 +1,7 @@
1
-#' GMQL Operation: UNION
2
-#'
1
+#' Method union
2
+#' 
3
+#' Wrapper to GMQL union function
4
+#' 
3 5
 #' It is used to integrate homogeneous or heterogeneous samples of two datasets 
4 6
 #' within a single dataset; for each sample of either input dataset, 
5 7
 #' a result sample is created as follows:
... ...
@@ -42,22 +44,23 @@
42 44
 #' 
43 45
 #' res <- union(data1, data2)
44 46
 #' 
45
-#' @rdname union-GMQLDataset-method
46
-#' @aliases union, union-method, 
47
-#' @export 
48 47
 #' 
48
+#' @name union
49
+#' @aliases union,GMQLDataset,GMQLDataset-method
50
+#' @aliases union-method
51
+#' @export
49 52
 setMethod("union", c("GMQLDataset","GMQLDataset"),
50 53
             function(x, y)
51 54
             {
52
-                val_x = x@value
53
-                val_y = y@value
54
-                gmql_union(val_x, val_y)
55
+                ptr_data_x = x@value
56
+                ptr_data_y = y@value
57
+                gmql_union(ptr_data_x, ptr_data_y)
55 58
             })
56 59
 
57 60
 gmql_union <- function(left_data, right_data)
58 61
 {
59 62
     WrappeR <- J("it/polimi/genomics/r/Wrapper")
60
-    response <- WrappeR$union(left_data,right_data)
63
+    response <- WrappeR$union(left_data, right_data)
61 64
     error <- strtoi(response[1])
62 65
     data <- response[2]
63 66
     if(error!=0)
... ...
@@ -61,34 +61,8 @@
61 61
 # meta join condition
62 62
 .join_condition <- function(cond)
63 63
 {
64
-    if(is.list(cond))
65
-    {
66
-        join_condition_matrix <- t(sapply(cond, function(x) {
67
-            new_value = as.character(x)
68
-            if(length(new_value)==1)
69
-                new_value = c("DEF",new_value)
70
-            else if(!identical("FULL",new_value[1]) && 
71
-                    !identical("EXACT",new_value[1]))
72
-                stop("no valid condition")
73
-            matrix <- matrix(new_value)
74
-        }))
75
-    }
76
-    else if(is.character(cond))
77
-    {
78
-        cond = cond[!cond %in% ""]
79
-        cond = cond[!duplicated(cond)]
80
-        if(length(cond)<=0)
81
-            join_condition_matrix <- ""
82
-        else
83
-        {
84
-            join_condition_matrix <- t(sapply(cond, function(x) {
85
-                new_value = c("DEF",x)
86
-                matrix <- matrix(new_value)
87
-            }))
88
-        }
89
-    }
90
-    else
91
-        stop("only list or character")
64
+    join_condition_matrix <- do.call(rbind, cond)
65
+    join_condition_matrix
92 66
 }
93 67
 
94 68
 .check_input <- function(value)
... ...
@@ -1,7 +1,3 @@
1
-#############################
2
-#       AGGREGATES          #
3
-#############################
4
-
5 1
 AGGREGATES <- function(value)
6 2
 {
7 3
     op_list <- list(value = value)
... ...
@@ -54,30 +50,54 @@ take_value.META_AGGREGATES <- function(obj){
54 50
                 "Q1" = paste0("q1_",val),
55 51
                 "Q2" = paste0("q2_"),
56 52
                 "Q3" = paste0("q3_",val)
57
-                )
53
+    )
58 54
     text
59 55
 }
60 56
 
57
+
58
+
61 59
 #' AGGREGATES object class constructor
62 60
 #' 
61
+#' 
63 62
 #' This class constructor is used to create instances of AGGREGATES object,
64 63
 #' to be used in GMQL functions that require aggregate on value.
65
-#' It prepares input parameter to be passed to the library function sum,
66
-#' performing all the type conversions needed
67
-#' 
68
-#' @param value string identifying name of region attribute
69
-#'
70
-#' @return SUM aggregate object
71 64
 #' 
72
-#' @seealso \code{\link{COUNT}} \code{\link{MIN}} \code{\link{MAX}} 
73
-#' \code{\link{AVG}} \code{\link{MEDIAN}} \code{\link{STD}} 
74
-#' \code{\link{BAG}} \code{\link{BAGD}}
75
-#' \code{\link{Q1}} \code{\link{Q2}} \code{\link{Q3}}
65
+#' \itemize{
66
+#' \item{SUM: It prepares input parameter to be passed to the library 
67
+#' function sum, performing all the type conversions needed  }
68
+#' \item{COUNT: It prepares input parameter to be passed to the library 
69
+#' function count, performing all the type conversions needed }
70
+#' \item{MIN:It prepares input parameter to be passed to the library 
71
+#' function minimum, performing all the type conversions needed  }
72
+#' \item{MAX: It prepares input parameter to be passed to the library 
73
+#' function maximum, performing all the type conversions needed }
74
+#' \item{BAG: It prepares input parameter to be passed to the library 
75
+#' function bag, this function creates comma-separated strings of 
76
+#' attribute values, performing all the types conversions needed}
77
+#' \item{BAGD: It prepares input parameter to be passed to the library 
78
+#' function bag, this function creates comma-separated strings of distinct 
79
+#' attribute values, performing all the types conversions needed}
80
+#' \item{AVG: It prepares input parameter to be passed to the library 
81
+#' function mean, performing all the type conversions needed }
82
+#' \item{MEDIAN: It prepares input parameter to be passed to the library 
83
+#' function median, performing all the type conversions needed }
84
+#' \item{STD: It prepares input parameter to be passed to the library 
85
+#' function standard deviation, performing all the type conversions needed}
86
+#' \item{Q1: It prepares input parameter to be passed to the library 
87
+#' function fist quartile, performing all the type conversions needed}
88
+#' \item{Q2: It prepares input parameter to be passed to the library 
89
+#' function second quartile, performing all the type conversions needed }
90
+#' \item{Q3: It prepares input parameter to be passed to the library 
91
+#' function third quartile, performing all the type conversions needed }
92
+#' }
76 93
 #' 
94
+#' @param value string identifying name of metadata or region attribute
95
+#'
96
+#' @return aggregate object
77 97
 #' 
78 98
 #' @examples
79 99
 #' 
80
-#' ### local with CustomParser
100
+#' ## local with CustomParser
81 101
 #' init_gmql()
82 102
 #' test_path <- system.file("example", "DATASET", package = "RGMQL")
83 103
 #' exp = read_dataset(test_path)
... ...
@@ -88,217 +108,124 @@ take_value.META_AGGREGATES <- function(obj){
88 108
 #' 
89 109
 #' res = extend(exp, sum_score = SUM("score"))
90 110
 #' 
111
+#' ## This statement copies all samples of exp into res dataset, 
112
+#' ## and then calculates new metadata attributes for each of them: 
113
+#' ## MinP is the minimum pvalue of the sample regions.
114
+#' 
115
+#' res = extend(exp, minP = MIN("pvalue"))
116
+#' 
117
+#' ## This statement copies all samples of exp into res dataset, 
118
+#' ## and then calculates new metadata attributes for each of them: 
119
+#' ## max_score is the maximum score of the sample regions.
120
+#' 
121
+#' res = extend(exp, max_score = MAX("score"))
122
+#' 
123
+#' ## The following cover operation produces output regions where at least 2 
124
+#' ## and at most 3 regions ofexp overlap, having as resulting region 
125
+#' ## attributes the average signal of the overlapping regions; 
126
+#' ## the result has one sample for each input cell.
127
+#' 
128
+#' res = cover(exp, 2, 3, groupBy = list(DF("cell")), 
129
+#' avg_signal = AVG("signal") )
130
+#' 
131
+#' ## It copies all samples of DATA into OUT dataset, and then for each of 
132
+#' ## them it adds another metadata attribute, allScores, 
133
+#' ## which is the aggregation comma-separated list of all the values 
134
+#' ## that the region attribute score takes in the sample.
135
+#' 
136
+#' out = extend(exp, allScore = BAG("score"))
137
+#' 
138
+#' ## counts the regions in each sample and stores their number as value 
139
+#' ## of the new metadata RegionCount attribute of the sample.
140
+#' 
141
+#' out = extend(exp, RegionCount = COUNT())
142
+#' 
143
+#' ## This statement copies all samples of exp into res dataset, 
144
+#' ## and then calculates new metadata attributes for each of them: 
145
+#' ## std_score is the standard deviation score of the sample regions.
146
+#' 
147
+#' res = extend(exp, std_score = STD("score"))
148
+#' 
149
+#' ## This statement copies all samples of exp into res dataset, 
150
+#' ## and then calculates new metadata attributes for each of them: 
151
+#' ## m_score is the median score of the sample regions.
152
+#' 
153
+#' res = extend(exp, m_score = MEDIAN("score"))
154
+#' 
155
+#' 
156
+#' @name AGGREGATES
157
+#' @rdname aggr-class
91 158
 #' @export
92 159
 #'
93 160
 SUM <- function(value)
94 161
 {
95 162
     check.META_AGGREGATES(value)
96
-
163
+    
97 164
     list <- list(value = value)
98 165
     ## Set the name for the class
99 166
     class(list) <- c("SUM","AGGREGATES","META_AGGREGATES")
100 167
     return(list)
101 168
 }
102 169
 
103
-#' AGGREGATES object class constructor
104
-#'
105
-#' This class constructor is used to create instances of AGGREGATES object,
106
-#' to be used in GMQL functions that require aggregate on value.
107
-#' It prepares input parameter to be passed to the library function minimum,
108
-#' performing all the type conversions needed
109
-#' 
110
-#' @param value string identifying name of region attribute
111
-#'
112
-#' @return MIN aggregate object
113
-#' 
114
-#' @seealso \code{\link{SUM}} \code{\link{COUNT}} \code{\link{MAX}} 
115
-#' \code{\link{AVG}} \code{\link{MEDIAN}} \code{\link{STD}} 
116
-#' \code{\link{BAG}} \code{\link{BAGD}}
117
-#' \code{\link{Q1}} \code{\link{Q2}} \code{\link{Q3}}
118
-#' 
119
-#' 
120
-#' @examples
121
-#' 
122
-#' ### local with CustomParser
123
-#' init_gmql()
124
-#' test_path <- system.file("example", "DATASET", package = "RGMQL")
125
-#' exp = read_dataset(test_path)
126
-#' 
127
-#' ## This statement copies all samples of exp into res dataset, 
128
-#' ## and then calculates new metadata attributes for each of them: 
129
-#' ## MinP is the minimum pvalue of the sample regions.
130
-#' 
131
-#' res = extend(exp, minP = MIN("pvalue"))
132
-#' 
170
+#' @name AGGREGATES
171
+#' @rdname aggr-class
133 172
 #' @export
134 173
 #'
135 174
 MIN <- function(value)
136 175
 {
137 176
     check.META_AGGREGATES(value)
138
-
177
+    
139 178
     list <- list(value = value)
140 179
     ## Set the name for the class
141 180
     class(list) <- c("MIN","AGGREGATES","META_AGGREGATES")
142 181
     return(list)
143 182
 }
144 183
 
145
-#' AGGREGATES object class constructor
146
-#'
147
-#' This class constructor is used to create instances of AGGREGATES object,
148
-#' to be used in GMQL functions that require aggregate on value.
149
-#' It prepares input parameter to be passed to the library function maximum,
150
-#' performing all the type conversions needed
151
-#' 
152
-#' @param value string identifying name of region attribute
153
-#'
154
-#' @return MAX aggregate object
155
-#' 
156
-#' @seealso \code{\link{SUM}} \code{\link{COUNT}} \code{\link{MIN}} 
157
-#' \code{\link{AVG}} \code{\link{MEDIAN}} \code{\link{STD}} 
158
-#' \code{\link{BAG}} \code{\link{BAGD}}
159
-#' \code{\link{Q1}} \code{\link{Q2}} \code{\link{Q3}}
160
-#' 
161
-#' 
162
-#' 
163
-#' @examples
164
-#' 
165
-#' ### local with CustomParser
166
-#' init_gmql()
167
-#' test_path <- system.file("example", "DATASET", package = "RGMQL")
168
-#' exp = read_dataset(test_path)
169
-#' 
170
-#' ## This statement copies all samples of exp into res dataset, 
171
-#' ## and then calculates new metadata attributes for each of them: 
172
-#' ## max_score is the maximum score of the sample regions.
173
-#' 
174
-#' res = extend(exp, max_score = MAX("score"))
175
-#' 
176
-#' 
184
+
185
+#' @name AGGREGATES 
186
+#' @rdname aggr-class 
177 187
 #' @export
178 188
 #'
179 189
 MAX <- function(value)
180 190
 {
181 191
     check.META_AGGREGATES(value)
182
-
192
+    
183 193
     list <- list(value = value)
184 194
     ## Set the name for the class
185 195
     class(list) <- c("MAX","AGGREGATES","META_AGGREGATES")
186 196
     return(list)
187 197
 }
188 198
 
189
-#' AGGREGATES object class constructor
190
-#'
191
-#' This class constructor is used to create instances of AGGREGATES object,
192
-#' to be used in GMQL functions that require aggregate on value.
193
-#' It prepares input parameter to be passed to the library function aritmetic
194
-#' mean, performing all the type conversions needed
195
-#' 
196
-#' @param value string identifying name of metadata or region attribute
197
-#'
198
-#' @return AVG aggregate object
199
-#' 
200
-#' @seealso \code{\link{SUM}} \code{\link{COUNT}} \code{\link{MIN}} 
201
-#' \code{\link{MAX}} \code{\link{MEDIAN}} \code{\link{STD}} 
202
-#' \code{\link{BAG}} \code{\link{BAGD}}
203
-#' \code{\link{Q1}} \code{\link{Q2}} \code{\link{Q3}}
204
-#'
205
-#' 
206
-#' @examples
207
-#' 
208
-#' ### local with CustomParser
209
-#' init_gmql()
210
-#' test_path <- system.file("example", "DATASET", package = "RGMQL")
211
-#' exp = read_dataset(test_path)
212
-#' 
213
-#' ## The following cover operation produces output regions where at least 2 
214
-#' ## and at most 3 regions ofexp overlap, having as resulting region 
215
-#' ## attributes the average signal of the overlapping regions; 
216
-#' ## the result has one sample for each input cell.
217
-#' 
218
-#' res = cover(exp, 2, 3, c("cell"), 
219
-#' list(avg_signal = AVG("signal")))
220
-#'
199
+#' @name AGGREGATES
200
+#' @rdname aggr-class
221 201
 #' @export
222 202
 #'
223 203
 AVG <- function(value)
224 204
 {
225 205
     check.META_AGGREGATES(value)
226
-
206
+    
227 207
     list <- list(value = value)
228 208
     ## Set the name for the class
229 209
     class(list) <- c("AVG","AGGREGATES","META_AGGREGATES")
230 210
     return(list)
231 211
 }
232 212
 
233
-#' AGGREGATES object class constructor
234
-#'
235
-#' This class constructor is used to create instances of AGGREGATES object,
236
-#' to be used in GMQL functions that require aggregate on value.
237
-#' It prepares input parameter to be passed to the library function bag,
238
-#' this function creates comma-separated strings of distinct attribute values,
239
-#' performing all the types conversions needed
240
-#' 
241
-#' @param value string identifying name of metadata or region attribute
242
-#'
243
-#' @return BAG aggregate object
244
-#' 
245
-#' @seealso \code{\link{SUM}} \code{\link{COUNT}} \code{\link{MIN}} 
246
-#' \code{\link{MAX}} \code{\link{AVG}} \code{\link{MEDIAN}} 
247
-#' \code{\link{STD}} \code{\link{BAGD}}
248
-#' \code{\link{Q1}} \code{\link{Q2}} \code{\link{Q3}}
249
-#' 
250
-#' @examples
251
-#' 
252
-#' ## local with CustomParser
253
-#' init_gmql()
254
-#' test_path <- system.file("example", "DATASET", package = "RGMQL")
255
-#' data = read_dataset(test_path)
256
-#' 
257
-#' ## It copies all samples of DATA into OUT dataset, and then for each of 
258
-#' ## them it adds another metadata attribute, allScores, 
259
-#' ## which is the aggregation comma-separated list of all the values 
260
-#' ## that the region attribute score takes in the sample.
261
-#' 
262
-#' out = extend(data, allScore = BAG("score"))
263
-#'
213
+#' @name AGGREGATES
214
+#' @rdname aggr-class
264 215
 #' @export
265 216
 #'
266 217
 BAG <- function(value)
267 218
 {
268 219
     check.META_AGGREGATES(value)
269
-
220
+    
270 221
     list <- list(value = value)
271 222
     ## Set the name for the class
272 223
     class(list) <- c("BAG","AGGREGATES","META_AGGREGATES")
273 224
     return(list)
274 225
 }
275 226
 
276
-#' AGGREGATES object class constructor
277
-#'
278
-#' This class constructor is used to create instances of AGGREGATES object,
279
-#' to be used in GMQL functions that require aggregate on value.
280
-#' It prepares input parameter to be passed to the library function count,
281
-#' performing all the type conversions needed
282
-#'
283
-#' @return COUNT aggregate object
284
-#' 
285
-#' @seealso \code{\link{SUM}} \code{\link{MIN}} 
286
-#' \code{\link{MAX}} \code{\link{AVG}} \code{\link{MEDIAN}} 
287
-#' \code{\link{STD}} \code{\link{BAG}} \code{\link{BAGD}}
288
-#' \code{\link{Q1}} \code{\link{Q2}} \code{\link{Q3}}
289
-#' 
290
-#' @examples
291
-#' 
292
-#' ## local with CustomParser
293
-#' init_gmql()
294
-#' test_path <- system.file("example", "DATASET", package = "RGMQL")
295
-#' exp = read_dataset(test_path)
296
-#' 
297
-#' ## counts the regions in each sample and stores their number as value 
298
-#' ## of the new metadata RegionCount attribute of the sample.
299
-#' 
300
-#' out = extend(exp, RegionCount = COUNT())
301
-#'
227
+#' @name AGGREGATES
228
+#' @rdname aggr-class
302 229
 #' @export
303 230
 #'
304 231
 COUNT <- function()
... ...
@@ -314,160 +241,51 @@ as.character.COUNT <- function(obj) {
314 241
 }
315 242
 check.COUNT <- function(obj){}
316 243
 
317
-#' AGGREGATES object class constructor
318