... | ... |
@@ -6,7 +6,7 @@ |
6 | 6 |
#' @rdname cover |
7 | 7 |
#' @aliases cover |
8 | 8 |
#' |
9 |
-setGeneric("cover", function(data, ...) standardGeneric("cover")) |
|
9 |
+setGeneric("cover", function(.data, ...) standardGeneric("cover")) |
|
10 | 10 |
|
11 | 11 |
#' Method map |
12 | 12 |
#' |
... | ... |
@@ -27,7 +27,7 @@ setGeneric("map", function(x, y, ...) standardGeneric("map")) |
27 | 27 |
#' @rdname take |
28 | 28 |
#' @aliases take,GMQLDataset-method |
29 | 29 |
#' |
30 |
-setGeneric("take", function(data, ...) standardGeneric("take")) |
|
30 |
+setGeneric("take", function(.data, ...) standardGeneric("take")) |
|
31 | 31 |
|
32 | 32 |
|
33 | 33 |
#' Method extend |
... | ... |
@@ -4,29 +4,27 @@ |
4 | 4 |
|
5 | 5 |
#' Condition evaluation functions |
6 | 6 |
#' |
7 |
-#' These functions are used to support joinBy and/or groupBy function parameter. |
|
8 |
-#' They create a 2-D array made up by two coloumn: |
|
9 |
-#' type of condition evaluation and the metadata attribute name |
|
7 |
+#' This function is used to support joinBy and/or groupBy function parameter. |
|
10 | 8 |
#' |
11 |
-#' |
|
12 |
-#' @param default series of string identifying a name of metadata attribute |
|
13 |
-#' to be evaluated. |
|
14 |
-#' It defines a DEFAULT evaluation of the input values. |
|
9 |
+#' @param default concatenation of string identifying a name of metadata |
|
10 |
+#' attribute to be evaluated. |
|
11 |
+#' It defines a DEFAULT evaluation of the input values. |
|
15 | 12 |
#' DEFAULT evaluation: the two attributes match if both end with value. |
16 | 13 |
#' |
17 |
-#' @param full series of string identifying a name of metadata attribute |
|
18 |
-#' to be evaluated. |
|
14 |
+#' @param full concatenation of string identifying a name of metadata |
|
15 |
+#' attribute to be evaluated. |
|
19 | 16 |
#' It defines a FULL (FULLNAME) evaluation of the input values. |
20 | 17 |
#' FULL evaluation: two attributes match if they both end with value and, |
21 | 18 |
#' if they have further prefixes, the two prefix sequences are identical. |
22 | 19 |
#' |
23 |
-#' @param exact series of string identifying a name of metadata attribute |
|
24 |
-#' to be evaluated. |
|
20 |
+#' @param exact concatenation of string identifying a name of metadata |
|
21 |
+#' attribute to be evaluated. |
|
25 | 22 |
#' It defines a EXACT evaluation of the input values. |
26 | 23 |
#' EXACT evaluation: only attributes exactly as value match; |
27 | 24 |
#' no further prefixes are allowed. |
28 | 25 |
#' |
29 |
-#' @return list of 2-D array containing method of evaluation and metadata |
|
26 |
+#' @return list of 2-D array containing method of evaluation and metadata |
|
27 |
+#' attribute name |
|
30 | 28 |
#' |
31 | 29 |
#' @examples |
32 | 30 |
#' |
... | ... |
@@ -41,7 +39,7 @@ condition_evaluation <- function(default = c(""), full = c(""), exact = c("")) |
41 | 39 |
df <- .condition("DEF",default) |
42 | 40 |
fn <- .condition("FULL",full) |
43 | 41 |
ex <- .condition("EXACT",exact) |
44 |
- list("def" = df, "full" = fn, "exact" = ex) |
|
42 |
+ list("condition" = list("def" = df, "full" = fn, "exact" = ex)) |
|
45 | 43 |
} |
46 | 44 |
|
47 | 45 |
.condition <- function(cond, array) |
... | ... |
@@ -21,7 +21,7 @@ |
21 | 21 |
#' if NULL no filtering action occures |
22 | 22 |
#' (i.e every sample is taken for region filtering) |
23 | 23 |
#' @param metadata_prefix vector of strings that will support the metadata |
24 |
-#' filtering. If defined every defined 'metadata' are concatenated with the |
|
24 |
+#' filtering. If defined, each 'metadata' are concatenated with the |
|
25 | 25 |
#' corresponding prefix. |
26 | 26 |
#' @param regions vector of strings that extracts only region attribute |
27 | 27 |
#' specified; if NULL no regions attribute is taken and the output is only |
... | ... |
@@ -27,7 +27,7 @@ |
27 | 27 |
#' @importFrom methods is |
28 | 28 |
#' @importFrom rJava J .jnull .jarray |
29 | 29 |
#' |
30 |
-#' @param data GMQLDataset class object |
|
30 |
+#' @param .data GMQLDataset class object |
|
31 | 31 |
#' @param min_acc minimum number of overlapping regions to be considered |
32 | 32 |
#' during execution. It is an integer number, declared also as string. |
33 | 33 |
#' minAcc accepts also: |
... | ... |
@@ -124,10 +124,10 @@ |
124 | 124 |
#' @aliases cover-method |
125 | 125 |
#' @export |
126 | 126 |
setMethod("cover", "GMQLDataset", |
127 |
- function(data, min_acc, max_acc, groupBy = NULL, |
|
127 |
+ function(.data, min_acc, max_acc, groupBy = NULL, |
|
128 | 128 |
variation = "cover", ...) |
129 | 129 |
{ |
130 |
- val <- data@value |
|
130 |
+ val <- value(.data) |
|
131 | 131 |
s_min <- substitute(min_acc) |
132 | 132 |
s_min <- .trasform_cover(deparse(s_min)) |
133 | 133 |
s_max <- substitute(max_acc) |
... | ... |
@@ -143,19 +143,23 @@ setMethod("cover", "GMQLDataset", |
143 | 143 |
|
144 | 144 |
|
145 | 145 |
|
146 |
-gmql_cover <- function(data, min_acc, max_acc, groupBy, aggregates, flag) |
|
146 |
+gmql_cover <- function(input_data, min_acc, max_acc, groupBy, aggregates, flag) |
|
147 | 147 |
{ |
148 |
- |
|
149 | 148 |
if(!is.null(groupBy)) |
150 | 149 |
{ |
151 |
- cond <- .join_condition(groupBy) |
|
152 |
- if(is.null(cond)) |
|
153 |
- join_condition_matrix <- .jnull("java/lang/String") |
|
150 |
+ if("condition" %in% names(groupBy)) |
|
151 |
+ { |
|
152 |
+ cond <- .join_condition(groupBy) |
|
153 |
+ if(is.null(cond)) |
|
154 |
+ join_matrix <- .jnull("java/lang/String") |
|
155 |
+ else |
|
156 |
+ join_matrix <- .jarray(cond, dispatch = TRUE) |
|
157 |
+ } |
|
154 | 158 |
else |
155 |
- join_condition_matrix <- .jarray(cond, dispatch = TRUE) |
|
159 |
+ stop("use function condition_evaluation()") |
|
156 | 160 |
} |
157 | 161 |
else |
158 |
- join_condition_matrix <- .jnull("java/lang/String") |
|
162 |
+ join_matrix <- .jnull("java/lang/String") |
|
159 | 163 |
|
160 | 164 |
if(!is.null(aggregates) && length(aggregates)) |
161 | 165 |
{ |
... | ... |
@@ -167,33 +171,33 @@ gmql_cover <- function(data, min_acc, max_acc, groupBy, aggregates, flag) |
167 | 171 |
|
168 | 172 |
WrappeR <- J("it/polimi/genomics/r/Wrapper") |
169 | 173 |
response <- switch(flag, |
170 |
- "COVER" = WrappeR$cover(min_acc, max_acc, join_condition_matrix, |
|
171 |
- metadata_matrix, data), |
|
172 |
- "FLAT" = WrappeR$flat(min_acc, max_acc, join_condition_matrix, |
|
173 |
- metadata_matrix, data), |
|
174 |
- "SUMMIT" = WrappeR$summit(min_acc,max_acc, join_condition_matrix, |
|
175 |
- metadata_matrix, data), |
|
176 |
- "HISTOGRAM" = WrappeR$histogram(min_acc, max_acc, |
|
177 |
- join_condition_matrix, metadata_matrix, data)) |
|
174 |
+ "COVER" = WrappeR$cover(min_acc, max_acc, join_matrix, |
|
175 |
+ metadata_matrix, input_data), |
|
176 |
+ "FLAT" = WrappeR$flat(min_acc, max_acc, join_matrix, |
|
177 |
+ metadata_matrix, input_data), |
|
178 |
+ "SUMMIT" = WrappeR$summit(min_acc,max_acc, join_matrix, |
|
179 |
+ metadata_matrix, input_data), |
|
180 |
+ "HISTOGRAM" = WrappeR$histogram(min_acc, max_acc, join_matrix, |
|
181 |
+ metadata_matrix, input_data)) |
|
178 | 182 |
if(is.null(response)) |
179 | 183 |
stop("no admissible variation: cover, flat, summit, histogram") |
180 | 184 |
|
181 | 185 |
error <- strtoi(response[1]) |
182 |
- data <- response[2] |
|
186 |
+ val <- response[2] |
|
183 | 187 |
if(error!=0) |
184 |
- stop(data) |
|
188 |
+ stop(val) |
|
185 | 189 |
else |
186 |
- GMQLDataset(data) |
|
190 |
+ GMQLDataset(val) |
|
187 | 191 |
} |
188 | 192 |
|
189 | 193 |
.check_cover_param <- function(param, is_min) |
190 | 194 |
{ |
191 |
- if(length(param)>1) |
|
195 |
+ if(length(param)) |
|
192 | 196 |
stop("length > 1") |
193 | 197 |
|
194 | 198 |
if(is.numeric(param)) |
195 | 199 |
{ |
196 |
- if(param<=0) |
|
200 |
+ if(param <= 0) |
|
197 | 201 |
stop("No negative value") |
198 | 202 |
else |
199 | 203 |
return(as.character(param)) |
... | ... |
@@ -17,16 +17,9 @@ |
17 | 17 |
#' |
18 | 18 |
#' @param x GMQLDataset class object |
19 | 19 |
#' @param y GMQLDataset class object |
20 |
-#' @param joinBy list of evalation functions to define evaluation on metadata: |
|
21 |
-#' \itemize{ |
|
22 |
-#' \item{\code{\link{FN}}(value): Fullname evaluation, two attributes match |
|
23 |
-#' if they both end with \emph{value} and, if they have further prefixes, |
|
24 |
-#' the two prefix sequence are identical} |
|
25 |
-#' \item{\code{\link{EX}}(value): Exact evaluation, only attributes exactly |
|
26 |
-#' as \emph{value} match; no further prefixes are allowed. } |
|
27 |
-#' \item{\code{\link{DF}}(value): Default evaluation, the two attributes match |
|
28 |
-#' if both end with \emph{value}.} |
|
29 |
-#' } |
|
20 |
+#' @param joinBy \code{\link{condition_evaluation}} function to support |
|
21 |
+#' methods with groupBy or JoinBy input paramter |
|
22 |
+#' |
|
30 | 23 |
#' @param is_exact single logical value: TRUE means that the region difference |
31 | 24 |
#' is executed only on regions in left_input_data with exactly the same |
32 | 25 |
#' coordinates of at least one region present in right_input_data; |
... | ... |
@@ -62,7 +55,7 @@ |
62 | 55 |
#' ## do not overlap any region in s2; |
63 | 56 |
#' ## metadata of the result are the same as the metadata of s1. |
64 | 57 |
#' |
65 |
-#' out_t = setdiff(data1, data2, DF("antibody_target")) |
|
58 |
+#' out_t = setdiff(data1, data2, condition_evaluation(c("cell"))) |
|
66 | 59 |
#' |
67 | 60 |
#' @name setdiff |
68 | 61 |
#' @aliases setdiff,GMQLDataset,GMQLDataset-method |
... | ... |
@@ -71,33 +64,33 @@ |
71 | 64 |
setMethod("setdiff", c("GMQLDataset","GMQLDataset"), |
72 | 65 |
function(x, y, joinBy = NULL, is_exact = FALSE) |
73 | 66 |
{ |
74 |
- ptr_data_x = x@value |
|
75 |
- ptr_data_y = y@value |
|
67 |
+ ptr_data_x = value(x) |
|
68 |
+ ptr_data_y = value(y) |
|
76 | 69 |
gmql_difference(ptr_data_x, ptr_data_y, is_exact, joinBy) |
77 | 70 |
}) |
78 | 71 |
|
79 | 72 |
gmql_difference <- function(left_data, right_data, is_exact, joinBy) |
80 | 73 |
{ |
81 |
- if(!is.list(joinBy)) |
|
82 |
- stop("joinBy: must be a list") |
|
83 |
- |
|
84 |
- if(!is.null(joinBy) && !length(joinBy) == 0) |
|
74 |
+ if(!is.null(joinBy)) |
|
85 | 75 |
{ |
86 | 76 |
cond <- .join_condition(joinBy) |
87 |
- join_condition_matrix <- .jarray(cond, dispatch = TRUE) |
|
77 |
+ if(is.null(cond)) |
|
78 |
+ join_matrix <- .jnull("java/lang/String") |
|
79 |
+ else |
|
80 |
+ join_matrix <- .jarray(cond, dispatch = TRUE) |
|
88 | 81 |
} |
89 | 82 |
else |
90 |
- join_condition_matrix <- .jnull("java/lang/String") |
|
83 |
+ join_matrix <- .jnull("java/lang/String") |
|
91 | 84 |
|
92 | 85 |
WrappeR <- J("it/polimi/genomics/r/Wrapper") |
93 |
- response <- WrappeR$difference(join_condition_matrix, right_data, |
|
94 |
- left_data, is_exact) |
|
86 |
+ response <- WrappeR$difference(join_matrix, left_data, right_data, |
|
87 |
+ is_exact) |
|
95 | 88 |
error <- strtoi(response[1]) |
96 |
- data <- response[2] |
|
89 |
+ val <- response[2] |
|
97 | 90 |
if(error!=0) |
98 |
- stop(data) |
|
91 |
+ stop(val) |
|
99 | 92 |
else |
100 |
- GMQLDataset(data) |
|
93 |
+ GMQLDataset(val) |
|
101 | 94 |
} |
102 | 95 |
|
103 | 96 |
|
... | ... |
@@ -59,7 +59,7 @@ |
59 | 59 |
#' @export |
60 | 60 |
setMethod("extend", "GMQLDataset", function(.data, ...) |
61 | 61 |
{ |
62 |
- ptr_data = .data@value |
|
62 |
+ ptr_data = value(.data) |
|
63 | 63 |
meta <- list(...) |
64 | 64 |
gmql_extend(ptr_data, meta) |
65 | 65 |
}) |
... | ... |
@@ -67,7 +67,7 @@ setMethod("extend", "GMQLDataset", function(.data, ...) |
67 | 67 |
|
68 | 68 |
gmql_extend <-function(input_data, meta) |
69 | 69 |
{ |
70 |
- if(!is.null(meta) && !length(meta) == 0) |
|
70 |
+ if(!is.null(meta) && length(meta)) |
|
71 | 71 |
{ |
72 | 72 |
aggr <- .aggregates(meta, "META_AGGREGATES") |
73 | 73 |
metadata_matrix <- .jarray(aggr, dispatch = TRUE) |
... | ... |
@@ -78,9 +78,9 @@ gmql_extend <-function(input_data, meta) |
78 | 78 |
WrappeR <- J("it/polimi/genomics/r/Wrapper") |
79 | 79 |
response <- WrappeR$extend(metadata_matrix, input_data) |
80 | 80 |
error <- strtoi(response[1]) |
81 |
- data <- response[2] |
|
81 |
+ val <- response[2] |
|
82 | 82 |
if(error!=0) |
83 |
- stop(data) |
|
83 |
+ stop(val) |
|
84 | 84 |
else |
85 |
- GMQLDataset(data) |
|
85 |
+ GMQLDataset(val) |
|
86 | 86 |
} |
... | ... |
@@ -80,11 +80,20 @@ gmql_group <- function(input_data, group_meta, group_reg, region_aggregates, |
80 | 80 |
{ |
81 | 81 |
if(!is.null(group_meta)) |
82 | 82 |
{ |
83 |
- cond <- .join_condition(group_meta) |
|
84 |
- join_condition_matrix <- .jarray(cond, dispatch = TRUE) |
|
83 |
+ if("condition" %in% names(group_meta)) |
|
84 |
+ { |
|
85 |
+ cond <- .join_condition(group_meta) |
|
86 |
+ if(is.null(cond)) |
|
87 |
+ join_matrix <- .jnull("java/lang/String") |
|
88 |
+ else |
|
89 |
+ join_matrix <- .jarray(cond, dispatch = TRUE) |
|
90 |
+ } |
|
91 |
+ else |
|
92 |
+ stop("use function condition_evaluation()") |
|
85 | 93 |
} |
86 | 94 |
else |
87 |
- join_condition_matrix <- .jnull("java/lang/String") |
|
95 |
+ join_matrix <- .jnull("java/lang/String") |
|
96 |
+ |
|
88 | 97 |
|
89 | 98 |
if(!is.null(group_reg)) |
90 | 99 |
{ |
... | ... |
@@ -94,7 +103,7 @@ gmql_group <- function(input_data, group_meta, group_reg, region_aggregates, |
94 | 103 |
group_reg <- group_reg[!group_reg %in% ""] |
95 | 104 |
group_reg <- group_reg[!duplicated(group_reg)] |
96 | 105 |
|
97 |
- if(length(group_reg)==0) |
|
106 |
+ if(!length(group_reg)) |
|
98 | 107 |
group_reg <- .jnull("java/lang/String") |
99 | 108 |
|
100 | 109 |
group_reg <- .jarray(metadata) |
... | ... |
@@ -102,7 +111,7 @@ gmql_group <- function(input_data, group_meta, group_reg, region_aggregates, |
102 | 111 |
else |
103 | 112 |
group_reg <- .jnull("java/lang/String") |
104 | 113 |
|
105 |
- if(!is.null(meta_aggregates) && !length(meta_aggregates) == 0) |
|
114 |
+ if(!is.null(meta_aggregates) && length(meta_aggregates)) |
|
106 | 115 |
{ |
107 | 116 |
aggr <- .aggregates(meta_aggregates,"AGGREGATES") |
108 | 117 |
metadata_matrix <- .jarray(aggr, dispatch = TRUE) |
... | ... |
@@ -110,7 +119,7 @@ gmql_group <- function(input_data, group_meta, group_reg, region_aggregates, |
110 | 119 |
else |
111 | 120 |
metadata_matrix <- .jnull("java/lang/String") |
112 | 121 |
|
113 |
- if(!is.null(region_aggregates) && !length(region_aggregates) == 0) |
|
122 |
+ if(!is.null(region_aggregates) && length(region_aggregates)) |
|
114 | 123 |
{ |
115 | 124 |
aggr <- .aggregates(region_aggregates,"AGGREGATES") |
116 | 125 |
region_matrix <- .jarray(aggr, dispatch = TRUE) |
... | ... |
@@ -119,12 +128,12 @@ gmql_group <- function(input_data, group_meta, group_reg, region_aggregates, |
119 | 128 |
region_matrix <- .jnull("java/lang/String") |
120 | 129 |
|
121 | 130 |
WrappeR <- J("it/polimi/genomics/r/Wrapper") |
122 |
- response <- WrappeR$group(join_condition_matrix, metadata_matrix, |
|
123 |
- group_reg, region_matrix, input_data) |
|
131 |
+ response <- WrappeR$group(join_matrix, metadata_matrix, group_reg, |
|
132 |
+ region_matrix, input_data) |
|
124 | 133 |
error <- strtoi(response[1]) |
125 |
- data <- response[2] |
|
134 |
+ val <- response[2] |
|
126 | 135 |
if(error!=0) |
127 |
- stop(data) |
|
136 |
+ stop(val) |
|
128 | 137 |
else |
129 |
- GMQLDataset(data) |
|
138 |
+ GMQLDataset(val) |
|
130 | 139 |
} |
... | ... |
@@ -45,9 +45,9 @@ init_gmql <- function(output_format = "GTF", remote_processing = FALSE, |
45 | 45 |
url = NULL, username = NULL, password = NULL) |
46 | 46 |
{ |
47 | 47 |
out_format <- toupper(output_format) |
48 |
- if(!identical(out_format,"TAB") && !identical(out_format,"GTF") && |
|
49 |
- !identical(out_format,"COLLECT")) |
|
50 |
- stop("output_format must be TAB, GTF or COLLECT") |
|
48 |
+ if(!out_format %in% c("TAB", "GTF", "COLLECT")) |
|
49 |
+ stop("output_format: must be TAB, GTF or COLLECT") |
|
50 |
+ |
|
51 | 51 |
.check_logical(remote_processing) |
52 | 52 |
|
53 | 53 |
# mettere attesa da input keyboard, controllare se token già esiste |
... | ... |
@@ -81,10 +81,10 @@ |
81 | 81 |
#' @export |
82 | 82 |
setMethod("merge", c("GMQLDataset","GMQLDataset"), |
83 | 83 |
function(x, y, genometric_predicate = NULL, |
84 |
- region_output = "contig", joinBy = NULL) |
|
84 |
+ region_output = "CAT", joinBy = NULL) |
|
85 | 85 |
{ |
86 |
- ptr_data_x <- x@value |
|
87 |
- ptr_data_y <- y@value |
|
86 |
+ ptr_data_x <- value(x) |
|
87 |
+ ptr_data_y <- value(y) |
|
88 | 88 |
gmql_join(ptr_data_x, ptr_data_y, genometric_predicate, |
89 | 89 |
joinBy, region_output) |
90 | 90 |
}) |
... | ... |
@@ -118,12 +118,12 @@ gmql_join <- function(left_data, right_data, genometric_predicate, joinBy, |
118 | 118 |
{ |
119 | 119 |
cond <- .join_condition(joinBy) |
120 | 120 |
if(is.null(cond)) |
121 |
- join_condition_matrix <- .jnull("java/lang/String") |
|
121 |
+ join_matrix <- .jnull("java/lang/String") |
|
122 | 122 |
else |
123 |
- join_condition_matrix <- .jarray(cond, dispatch = TRUE) |
|
123 |
+ join_matrix <- .jarray(cond, dispatch = TRUE) |
|
124 | 124 |
} |
125 | 125 |
else |
126 |
- join_condition_matrix <- .jnull("java/lang/String") |
|
126 |
+ join_matrix <- .jnull("java/lang/String") |
|
127 | 127 |
|
128 | 128 |
ouput <- toupper(region_output) |
129 | 129 |
if(!ouput %in% c("CAT", "LEFT", "RIGHT", "INT", "BOTH", "RIGHT_DIST", |
... | ... |
@@ -132,12 +132,12 @@ gmql_join <- function(left_data, right_data, genometric_predicate, joinBy, |
132 | 132 |
or int (intersection)") |
133 | 133 |
|
134 | 134 |
WrappeR <- J("it/polimi/genomics/r/Wrapper") |
135 |
- response <- WrappeR$join(genomatrix,join_condition_matrix, |
|
136 |
- ouput,right_data, left_data) |
|
135 |
+ response <- WrappeR$join(genomatrix, join_matrix, ouput, left_data, |
|
136 |
+ right_data) |
|
137 | 137 |
error <- strtoi(response[1]) |
138 |
- data <- response[2] |
|
138 |
+ val <- response[2] |
|
139 | 139 |
if(error!=0) |
140 |
- stop(data) |
|
140 |
+ stop(val) |
|
141 | 141 |
else |
142 |
- GMQLDataset(data) |
|
142 |
+ GMQLDataset(val) |
|
143 | 143 |
} |
... | ... |
@@ -86,34 +86,40 @@ |
86 | 86 |
setMethod("map", "GMQLDataset", |
87 | 87 |
function(x, y, ..., joinBy = NULL) |
88 | 88 |
{ |
89 |
- r_data <- x@value |
|
90 |
- l_data <- y@value |
|
89 |
+ left_data <- value(x) |
|
90 |
+ right_data <- value(y) |
|
91 | 91 |
aggregates = list(...) |
92 |
- gmql_map(r_data, l_data, aggregates, joinBy) |
|
92 |
+ gmql_map(left_data, right_data, aggregates, joinBy) |
|
93 | 93 |
}) |
94 | 94 |
|
95 | 95 |
|
96 |
-gmql_map <- function(l_data, r_data, aggregates, joinBy) |
|
96 |
+gmql_map <- function(left_data, right_data, aggregates, joinBy) |
|
97 | 97 |
{ |
98 |
- if(!is.null(aggregates) && !length(aggregates) == 0) |
|
99 |
- metadata_matrix <- .jarray(.aggregates(aggregates,"AGGREGATES"), |
|
100 |
- dispatch = TRUE) |
|
98 |
+ if(!is.null(aggregates) && length(aggregates)) |
|
99 |
+ { |
|
100 |
+ aggr <- .aggregates(aggregates, "META_AGGREGATES") |
|
101 |
+ metadata_matrix <- .jarray(aggr, dispatch = TRUE) |
|
102 |
+ } |
|
101 | 103 |
else |
102 |
- metadata_matrix = .jnull("java/lang/String") |
|
104 |
+ metadata_matrix <- .jnull("java/lang/String") |
|
103 | 105 |
|
104 | 106 |
if(!is.null(joinBy)) |
105 |
- join_condition_matrix <- .jarray(.join_condition(joinBy), |
|
106 |
- dispatch = TRUE) |
|
107 |
+ { |
|
108 |
+ cond <- .join_condition(joinBy) |
|
109 |
+ if(is.null(cond)) |
|
110 |
+ join_matrix <- .jnull("java/lang/String") |
|
111 |
+ else |
|
112 |
+ join_matrix <- .jarray(cond, dispatch = TRUE) |
|
113 |
+ } |
|
107 | 114 |
else |
108 |
- join_condition_matrix <- .jnull("java/lang/String") |
|
115 |
+ join_matrix <- .jnull("java/lang/String") |
|
109 | 116 |
|
110 | 117 |
WrappeR <- J("it/polimi/genomics/r/Wrapper") |
111 |
- response<-WrappeR$map(join_condition_matrix, metadata_matrix, l_data, |
|
112 |
- r_data) |
|
118 |
+ response<-WrappeR$map(join_matrix, metadata_matrix, left_data, right_data) |
|
113 | 119 |
error <- strtoi(response[1]) |
114 |
- data <- response[2] |
|
120 |
+ val <- response[2] |
|
115 | 121 |
if(error!=0) |
116 |
- stop(data) |
|
122 |
+ stop(val) |
|
117 | 123 |
else |
118 |
- GMQLDataset(data) |
|
124 |
+ GMQLDataset(val) |
|
119 | 125 |
} |
... | ... |
@@ -39,16 +39,16 @@ execute <- function() |
39 | 39 |
|
40 | 40 |
response <- WrappeR$execute() |
41 | 41 |
error <- strtoi(response[1]) |
42 |
- data <- response[2] |
|
42 |
+ val <- response[2] |
|
43 | 43 |
if(error!=0) |
44 |
- stop(data) |
|
44 |
+ stop(val) |
|
45 | 45 |
else |
46 | 46 |
{ |
47 | 47 |
if(remote_proc) |
48 | 48 |
{ |
49 | 49 |
url <- WrappeR$get_url() |
50 | 50 |
.download_or_upload() |
51 |
- res <- serialize_query(url,FALSE,data) |
|
51 |
+ res <- serialize_query(url,FALSE,val) |
|
52 | 52 |
} |
53 | 53 |
} |
54 | 54 |
} |
... | ... |
@@ -56,8 +56,8 @@ execute <- function() |
56 | 56 |
.download_or_upload <- function() |
57 | 57 |
{ |
58 | 58 |
WrappeR <- J("it/polimi/genomics/r/Wrapper") |
59 |
- data <- .jevalArray(WrappeR$get_dataset_list(),simplify = TRUE) |
|
60 |
- data_list <- apply(data, 1, as.list) |
|
59 |
+ datasets <- .jevalArray(WrappeR$get_dataset_list(),simplify = TRUE) |
|
60 |
+ data_list <- apply(datasets, 1, as.list) |
|
61 | 61 |
url <- WrappeR$get_url() |
62 | 62 |
remote <- WrappeR$is_remote_processing() |
63 | 63 |
if(remote) |
... | ... |
@@ -76,7 +76,7 @@ execute <- function() |
76 | 76 |
|
77 | 77 |
collect.GMQLDataset <- function(x, dir_out = getwd(), name = "ds1") |
78 | 78 |
{ |
79 |
- ptr_data <- x@value |
|
79 |
+ ptr_data <- value(x) |
|
80 | 80 |
gmql_materialize(ptr_data, dir_out, name) |
81 | 81 |
} |
82 | 82 |
|
... | ... |
@@ -146,9 +146,9 @@ gmql_materialize <- function(input_data, dir_out, name) |
146 | 146 |
|
147 | 147 |
response <- WrappeR$materialize(input_data, res_dir_out) |
148 | 148 |
error <- strtoi(response[1]) |
149 |
- data <- response[2] |
|
149 |
+ val <- response[2] |
|
150 | 150 |
if(error!=0) |
151 |
- stop(data) |
|
151 |
+ stop(val) |
|
152 | 152 |
else |
153 | 153 |
invisible(NULL) |
154 | 154 |
} |
... | ... |
@@ -169,7 +169,7 @@ gmql_materialize <- function(input_data, dir_out, name) |
169 | 169 |
#' @importFrom rJava J .jevalArray |
170 | 170 |
#' @importFrom GenomicRanges GRangesList |
171 | 171 |
#' |
172 |
-#' @param data returned object from any GMQL function |
|
172 |
+#' @param .data returned object from any GMQL function |
|
173 | 173 |
#' @param rows number of rows for each sample regions that you want to |
174 | 174 |
#' retrieve and store in memory. |
175 | 175 |
#' By default it is 0 that means take all rows for each sample |
... | ... |
@@ -198,9 +198,9 @@ gmql_materialize <- function(input_data, dir_out, name) |
198 | 198 |
#' @aliases take-method |
199 | 199 |
#' @export |
200 | 200 |
setMethod("take", "GMQLDataset", |
201 |
- function(data, rows = 0L) |
|
201 |
+ function(.data, rows = 0L) |
|
202 | 202 |
{ |
203 |
- ptr_data <- data@value |
|
203 |
+ ptr_data <- value(.data) |
|
204 | 204 |
gmql_take(ptr_data, rows) |
205 | 205 |
}) |
206 | 206 |
|
... | ... |
@@ -229,11 +229,11 @@ gmql_take <- function(input_data, rows = 0L) |
229 | 229 |
|
230 | 230 |
reg_data_frame <- as.data.frame(reg) |
231 | 231 |
list <- split(reg_data_frame, reg_data_frame[1]) |
232 |
- names <- c("seqname","start","end","strand",schema) |
|
232 |
+ seq_name <- c("seqname","start","end","strand",schema) |
|
233 | 233 |
|
234 | 234 |
sampleList <- lapply(list, function(x){ |
235 | 235 |
x <- x[-1] |
236 |
- names(x) <- names |
|
236 |
+ names(x) <- seq_name |
|
237 | 237 |
g <- GenomicRanges::makeGRangesFromDataFrame(x, |
238 | 238 |
keep.extra.columns = TRUE, |
239 | 239 |
start.field = "start", |
... | ... |
@@ -51,7 +51,7 @@ |
51 | 51 |
setMethod("aggregate", "GMQLDataset", |
52 | 52 |
function(x, groupBy = NULL) |
53 | 53 |
{ |
54 |
- ptr_data = x@value |
|
54 |
+ ptr_data = value(x) |
|
55 | 55 |
gmql_merge(ptr_data, groupBy) |
56 | 56 |
}) |
57 | 57 |
|
... | ... |
@@ -61,20 +61,20 @@ gmql_merge <- function(input_data, groupBy) |
61 | 61 |
{ |
62 | 62 |
cond <- .join_condition(groupBy) |
63 | 63 |
if(is.null(cond)) |
64 |
- join_condition_matrix <- .jnull("java/lang/String") |
|
64 |
+ join_matrix <- .jnull("java/lang/String") |
|
65 | 65 |
else |
66 |
- join_condition_matrix <- .jarray(cond, dispatch = TRUE) |
|
66 |
+ join_matrix <- .jarray(cond, dispatch = TRUE) |
|
67 | 67 |
} |
68 | 68 |
else |
69 |
- join_condition_matrix <- .jnull("java/lang/String") |
|
69 |
+ join_matrix <- .jnull("java/lang/String") |
|
70 | 70 |
|
71 | 71 |
WrappeR <- J("it/polimi/genomics/r/Wrapper") |
72 |
- response <- WrappeR$merge(join_condition_matrix, input_data) |
|
72 |
+ response <- WrappeR$merge(join_matrix, input_data) |
|
73 | 73 |
error <- strtoi(response[1]) |
74 |
- data <- response[2] |
|
74 |
+ val <- response[2] |
|
75 | 75 |
if(error!=0) |
76 |
- stop(data) |
|
76 |
+ stop(val) |
|
77 | 77 |
else |
78 |
- GMQLDataset(data) |
|
78 |
+ GMQLDataset(val) |
|
79 | 79 |
} |
80 | 80 |
|
... | ... |
@@ -1,8 +1,8 @@ |
1 | 1 |
arrange.GMQLDataset <- function(.data, metadata_ordering = NULL, |
2 |
- regions_ordering = NULL, fetch_opt = NULL, num_fetch = 0, |
|
3 |
- reg_fetch_opt = NULL, reg_num_fetch = 0) |
|
2 |
+ regions_ordering = NULL, fetch_opt = NULL, num_fetch = 0L, |
|
3 |
+ reg_fetch_opt = NULL, reg_num_fetch = 0L) |
|
4 | 4 |
{ |
5 |
- ptr_data <- .data@value |
|
5 |
+ ptr_data <- value(.data) |
|
6 | 6 |
gmql_order(ptr_data, metadata_ordering, regions_ordering, |
7 | 7 |
fetch_opt, num_fetch, reg_fetch_opt, reg_num_fetch) |
8 | 8 |
} |
... | ... |
@@ -85,7 +85,7 @@ arrange.GMQLDataset <- function(.data, metadata_ordering = NULL, |
85 | 85 |
#' @export |
86 | 86 |
setMethod("arrange", "GMQLDataset", arrange.GMQLDataset) |
87 | 87 |
|
88 |
-gmql_order <- function(data, metadata_ordering, regions_ordering, |
|
88 |
+gmql_order <- function(input_data, metadata_ordering, regions_ordering, |
|
89 | 89 |
fetch_opt, num_fetch, reg_fetch_opt, reg_num_fetch) |
90 | 90 |
{ |
91 | 91 |
if(!is.null(fetch_opt)) |
... | ... |
@@ -96,12 +96,12 @@ gmql_order <- function(data, metadata_ordering, regions_ordering, |
96 | 96 |
if(!is.null(num_fetch)) |
97 | 97 |
.check_opt_value(num_fetch) |
98 | 98 |
else |
99 |
- num_fetch <- 0 |
|
99 |
+ num_fetch <- 0L |
|
100 | 100 |
|
101 | 101 |
if(!is.null(reg_num_fetch)) |
102 | 102 |
.check_opt_value(reg_num_fetch) |
103 | 103 |
else |
104 |
- reg_num_fetch <- 0 |
|
104 |
+ reg_num_fetch <- 0L |
|
105 | 105 |
|
106 | 106 |
if(!is.null(reg_fetch_opt)) |
107 | 107 |
reg_fetch_opt <- .check_option(reg_fetch_opt) |
... | ... |
@@ -127,13 +127,13 @@ gmql_order <- function(data, metadata_ordering, regions_ordering, |
127 | 127 |
WrappeR <- J("it/polimi/genomics/r/Wrapper") |
128 | 128 |
response <- WrappeR$order(meta_matrix, fetch_opt, as.integer(num_fetch), |
129 | 129 |
reg_fetch_opt, as.integer(reg_num_fetch), |
130 |
- region_matrix, data) |
|
130 |
+ region_matrix, input_data) |
|
131 | 131 |
error <- strtoi(response[1]) |
132 |
- data <- response[2] |
|
132 |
+ val <- response[2] |
|
133 | 133 |
if(error!=0) |
134 |
- stop(data) |
|
134 |
+ stop(val) |
|
135 | 135 |
else |
136 |
- GMQLDataset(data) |
|
136 |
+ GMQLDataset(val) |
|
137 | 137 |
} |
138 | 138 |
|
139 | 139 |
|
... | ... |
@@ -146,9 +146,7 @@ gmql_order <- function(data, metadata_ordering, regions_ordering, |
146 | 146 |
.check_option <- function(opt) |
147 | 147 |
{ |
148 | 148 |
opt <- tolower(opt) |
149 |
- if(!identical("mtop",opt) && !identical("mtopp",opt) && |
|
150 |
- !identical("mtopg",opt) && !identical("rtop",opt) && |
|
151 |
- !identical("rtopp",opt) && !identical("rtopg",opt)) |
|
149 |
+ if(!opt %in% c("mtop", "mtopp", "mtopg", "rtop", "rtopp", "rtopg")) |
|
152 | 150 |
stop("option not admissable") |
153 | 151 |
opt |
154 | 152 |
} |
... | ... |
@@ -170,11 +170,11 @@ gmql_project <-function(input_data, metadata, metadata_update, all_but_meta, |
170 | 170 |
response <- WrappeR$project(metadata, metadata_update, all_but_meta, |
171 | 171 |
regions, regions_update, all_but_reg, input_data) |
172 | 172 |
error <- strtoi(response[1]) |
173 |
- data <- response[2] |
|
173 |
+ val <- response[2] |
|
174 | 174 |
if(error!=0) |
175 |
- stop(data) |
|
175 |
+ stop(val) |
|
176 | 176 |
else |
177 |
- GMQLDataset(data) |
|
177 |
+ GMQLDataset(val) |
|
178 | 178 |
} |
179 | 179 |
|
180 | 180 |
.trasform_update <- function(predicate=NULL) |
... | ... |
@@ -112,8 +112,8 @@ read_dataset <- function(dataset, parser = "CustomParser", is_local=TRUE, |
112 | 112 |
} |
113 | 113 |
|
114 | 114 |
parser_name <- .check_parser(parser) |
115 |
- response <- WrappeR$readDataset(dataset,parser_name, is_local, is_GMQL, |
|
116 |
- schema_matrix,schema_XML) |
|
115 |
+ response <- WrappeR$readDataset(dataset, parser_name, is_local, is_GMQL, |
|
116 |
+ schema_matrix, schema_XML) |
|
117 | 117 |
error <- strtoi(response[1]) |
118 | 118 |
data <- response[2] |
119 | 119 |
if(error!=0) |
... | ... |
@@ -142,11 +142,10 @@ read <- function(samples) |
142 | 142 |
{ |
143 | 143 |
#repeat meta for each sample in samples list |
144 | 144 |
len <- length(samples) |
145 |
- warning("GrangesList has no metadata. |
|
146 |
-We provide two metadata for you") |
|
147 |
- index_meta <- rep(1:len,each = len) |
|
145 |
+ warning("No metadata.\nWe provide two metadata for you") |
|
146 |
+ index_meta <- rep(seq_len(len),each = len) |
|
148 | 147 |
rep_meta <- rep(c("provider","PoliMi", "application", "RGMQL"), |
149 |
- times=len) |
|
148 |
+ times = len) |
|
150 | 149 |
meta_matrix <- matrix(rep_meta,ncol = 2,byrow = TRUE) |
151 | 150 |
meta_matrix <- cbind(index_meta,meta_matrix) |
152 | 151 |
} |
... | ... |
@@ -199,12 +198,8 @@ We provide two metadata for you") |
199 | 198 |
.check_parser <- function(parser) |
200 | 199 |
{ |
201 | 200 |
parser <- toupper(parser) |
202 |
- if(!identical(parser,"BEDPARSER") && !identical(parser,"ANNPARSER") && |
|
203 |
- !identical(parser,"BROADPROJPARSER") && |
|
204 |
- !identical(parser,"BASICPARSER") && |
|
205 |
- !identical(parser,"NARROWPEAKPARSER") && |
|
206 |
- !identical(parser,"RNASEQPARSER") && |
|
207 |
- !identical(parser,"CUSTOMPARSER")) |
|
201 |
+ if(!parser %in% c("BEDPARSER","ANNPARSER","BROADPROJPARSER","BASICPARSER", |
|
202 |
+ "NARROWPEAKPARSER","RNASEQPARSER","CUSTOMPARSER")) |
|
208 | 203 |
stop("parser not defined") |
209 | 204 |
|
210 | 205 |
parser |
... | ... |
@@ -137,7 +137,7 @@ gmql_select <- function(input_data, predicate, region_predicate, s_join) |
137 | 137 |
#' This function is used as support to the filter method to define |
138 | 138 |
#' semijoin conditions on metadata |
139 | 139 |
#' |
140 |
-#' @param data GMQLDataset class object |
|
140 |
+#' @param .data GMQLDataset class object |
|
141 | 141 |
#' |
142 | 142 |
#' @param not_in logical value: TRUE => for a given sample of input dataset |
143 | 143 |
#' ".data" in \code{\link{filter}} method if and only if there exists at |
... | ... |
@@ -189,7 +189,7 @@ gmql_select <- function(input_data, predicate, region_predicate, s_join) |
189 | 189 |
#' @return semijoin condition as list |
190 | 190 |
#' @export |
191 | 191 |
#' |
192 |
-semijoin <- function(data, not_in = FALSE, groupBy = NULL) |
|
192 |
+semijoin <- function(.data, not_in = FALSE, groupBy = NULL) |
|
193 | 193 |
{ |
194 | 194 |
if(!is.list(groupBy)) |
195 | 195 |
stop("groupBy: must be a list") |
... | ... |
@@ -203,7 +203,7 @@ semijoin <- function(data, not_in = FALSE, groupBy = NULL) |
203 | 203 |
stop("data: Must be a GMQLDataset object") |
204 | 204 |
|
205 | 205 |
.check_logical(not_in) |
206 |
- ptr_data <- data@value |
|
206 |
+ ptr_data <- value(.data) |
|
207 | 207 |
|
208 | 208 |
data_cond <- cbind(ptr_data,not_in) |
209 | 209 |
cond <- .join_condition(semij_cond) |
... | ... |
@@ -53,7 +53,6 @@ |
53 | 53 |
setMethod("union", c("GMQLDataset","GMQLDataset"), |
54 | 54 |
function(x, y) |
55 | 55 |
{ |
56 |
- |
|
57 | 56 |
ptr_data_x = value(x) |
58 | 57 |
ptr_data_y = value(y) |
59 | 58 |
gmql_union(ptr_data_x, ptr_data_y) |
... | ... |
@@ -64,9 +63,9 @@ gmql_union <- function(left_data, right_data) |
64 | 63 |
WrappeR <- J("it/polimi/genomics/r/Wrapper") |
65 | 64 |
response <- WrappeR$union(left_data, right_data) |
66 | 65 |
error <- strtoi(response[1]) |
67 |
- data <- response[2] |
|
66 |
+ val <- response[2] |
|
68 | 67 |
if(error!=0) |
69 |
- stop(data) |
|
68 |
+ stop(val) |
|
70 | 69 |
else |
71 |
- GMQLDataset(data) |
|
70 |
+ GMQLDataset(val) |
|
72 | 71 |
} |
... | ... |
@@ -11,16 +11,8 @@ |
11 | 11 |
\arguments{ |
12 | 12 |
\item{x}{GMQLDataset class object} |
13 | 13 |
|
14 |
-\item{groupBy}{list of evalation functions to define evaluation on metadata: |
|
15 |
-\itemize{ |
|
16 |
-\item{\code{\link{FN}}(value): Fullname evaluation, two attributes match |
|
17 |
-if they both end with \emph{value} and, if they have further prefixes, |
|
18 |
-the two prefix sequences are identical} |
|
19 |
-\item{\code{\link{EX}}(value): Exact evaluation, only attributes exactly |
|
20 |
-as \emph{value} match; no further prefixes are allowed. } |
|
21 |
-\item{\code{\link{DF}}(value): Default evaluation, the two attributes match |
|
22 |
-if both end with \emph{value}.} |
|
23 |
-}} |
|
14 |
+\item{groupBy}{\code{\link{condition_evaluation}} function to support |
|
15 |
+methods with groupBy or JoinBy input paramter} |
|
24 | 16 |
} |
25 | 17 |
\value{ |
26 | 18 |
GMQLDataset object. It contains the value to use as input |
... | ... |
@@ -57,6 +49,6 @@ exp = read_dataset(test_path) |
57 | 49 |
## antibody_target and cell metadata |
58 | 50 |
## attributes. |
59 | 51 |
|
60 |
-merged = aggregate(exp, list(DF("antibody_target","cell"))) |
|
52 |
+merged = aggregate(exp, condition_evaluation(c("antibody_target","cell"))) |
|
61 | 53 |
|
62 | 54 |
} |
... | ... |
@@ -2,46 +2,35 @@ |
2 | 2 |
% Please edit documentation in R/evaluation-functions.R |
3 | 3 |
\name{Evaluation-Function} |
4 | 4 |
\alias{Evaluation-Function} |
5 |
-\alias{FN} |
|
6 |
-\alias{Evaluation-Function} |
|
7 |
-\alias{EX} |
|
8 |
-\alias{Evaluation-Function} |
|
9 |
-\alias{DF} |
|
10 |
-\alias{Evaluation-Function} |
|
11 | 5 |
\alias{condition_evaluation} |
12 | 6 |
\title{Condition evaluation functions} |
13 | 7 |
\usage{ |
14 |
-FN(...) |
|
15 |
- |
|
16 |
-EX(...) |
|
17 |
- |
|
18 |
-DF(...) |
|
19 |
- |
|
20 |
-condition_evaluation(...) |
|
8 |
+condition_evaluation(default = c(""), full = c(""), exact = c("")) |
|
21 | 9 |
} |
22 | 10 |
\arguments{ |
23 |
-\item{...}{series of string identifying a name of metadata attribute |
|
24 |
-to be evaluated} |
|
11 |
+\item{default}{series of string identifying a name of metadata attribute |
|
12 |
+to be evaluated. |
|
13 |
+It defines a DEFAULT evaluation of the input values. |
|
14 |
+DEFAULT evaluation: the two attributes match if both end with value.} |
|
15 |
+ |
|
16 |
+\item{full}{series of string identifying a name of metadata attribute |
|
17 |
+to be evaluated. |
|
18 |
+It defines a FULL (FULLNAME) evaluation of the input values. |
|
19 |
+FULL evaluation: two attributes match if they both end with value and, |
|
20 |
+if they have further prefixes, the two prefix sequences are identical.} |
|
21 |
+ |
|
22 |
+\item{exact}{series of string identifying a name of metadata attribute |
|
23 |
+to be evaluated. |
|
24 |
+It defines a EXACT evaluation of the input values. |
|
25 |
+EXACT evaluation: only attributes exactly as value match; |
|
26 |
+no further prefixes are allowed.} |
|
25 | 27 |
} |
26 | 28 |
\value{ |
27 |
-2-D array containing method of evaluation and metadata |
|
29 |
+list of 2-D array containing method of evaluation and metadata |
|
30 |
+attribute name |
|
28 | 31 |
} |
29 | 32 |
\description{ |
30 |
-These functions are used to support joinBy and/or groupBy function parameter. |
|
31 |
-They create a 2-D array made up by two coloumn: |
|
32 |
-type of condition evaluation and the metadata attribute name |
|
33 |
-} |
|
34 |
-\details{ |
|
35 |
-\itemize{ |
|
36 |
-\item{FN: It defines a FULL (FULLNAME) evaluation of the input values. |
|
37 |
-FULL evaluation: two attributes match if they both end with value and, |
|
38 |
-if they have further prefixes, the two prefix sequences are identical} |
|
39 |
-\item{EX: It defines a EXACT evaluation of the input values. |
|
40 |
-EXACT evaluation: only attributes exactly as value match; |
|
41 |
-no further prefixes are allowed. } |
|
42 |
-\item{DF: It defines a DEFAULT evaluation of the input values. |
|
43 |
-DEFAULT evaluation: the two attributes match if both end with value.} |
|
44 |
-} |
|
33 |
+This function is used to support joinBy and/or groupBy function parameter. |
|
45 | 34 |
} |
46 | 35 |
\examples{ |
47 | 36 |
|
... | ... |
@@ -54,16 +54,8 @@ considering any amount of overlapping regions. |
54 | 54 |
ALL() / K, with N and K integer values } |
55 | 55 |
}} |
56 | 56 |
|
57 |
-\item{groupBy}{list of evalation functions to define evaluation on metadata: |
|
58 |
-\itemize{ |
|
59 |
-\item{\code{\link{FN}}(value): Fullname evaluation, two attributes match |
|
60 |
-if they both end with \emph{value} and, if they have further prefixes, |
|
61 |
-the two prefix sequence are identical} |
|
62 |
-\item{\code{\link{EX}}(value): Exact evaluation, only attributes exactly |
|
63 |
-as \emph{value} match; no further prefixes are allowed. } |
|
64 |
-\item{\code{\link{DF}}(value): Default evaluation, the two attributes match |
|
65 |
-if both end with \emph{value}.} |
|
66 |
-}} |
|
57 |
+\item{groupBy}{\code{\link{condition_evaluation}} function to support |
|
58 |
+methods with groupBy or JoinBy input paramter} |
|
67 | 59 |
|
68 | 60 |
\item{variation}{string identifying the cover GMQL operator variation. |
69 | 61 |
The admissible strings are: |
... | ... |
@@ -139,7 +131,7 @@ res = cover(exp, 2, ANY()) |
139 | 131 |
## regions the minimum pvalue of the overlapping regions (min_pvalue) |
140 | 132 |
## and their Jaccard indexes (JaccardIntersect and JaccardResult). |
141 | 133 |
|
142 |
-res = cover(exp, 2, 3, groupBy = list(DF("cell")), |
|
134 |
+res = cover(exp, 2, 3, groupBy = condition_evaluation(c("cell")), |
|
143 | 135 |
min_pValue = MIN("pvalue")) |
144 | 136 |
|
145 | 137 |
} |
... | ... |
@@ -19,7 +19,7 @@ if NULL no filtering action occures |
19 | 19 |
(i.e every sample is taken for region filtering)} |
20 | 20 |
|
21 | 21 |
\item{metadata_prefix}{vector of strings that will support the metadata |
22 |
-filtering. If defined every defined 'metadata' are concatenated with the |
|
22 |
+filtering. If defined, each 'metadata' are concatenated with the |
|
23 | 23 |
corresponding prefix.} |
24 | 24 |
|
25 | 25 |
\item{regions}{vector of strings that extracts only region attribute |
... | ... |
@@ -37,16 +37,8 @@ corresponding coordinate values in the 'x' and 'y' regions satisfying |
37 | 37 |
the genometric predicate)} |
38 | 38 |
}} |
39 | 39 |
|
40 |
-\item{joinBy}{list of evalation functions to define evaluation on metadata: |
|
41 |
-\itemize{ |
|
42 |
-\item{ \code{\link{FN}}(value): Fullname evaluation, two attributes match |
|
43 |
-if they both end with \emph{value} and, if they have further prefixes, |
|
44 |
-the two prefix sequence are identical.} |
|
45 |
-\item{ \code{\link{EX}}(value): Exact evaluation, only attributes exactly |
|
46 |
-as \emph{value} match; no further prefixes are allowed.} |
|
47 |
-\item{ \code{\link{DF}}(value): Default evaluation, the two attributes match |
|
48 |
-if both end with \emph{value}.} |
|
49 |
-}} |
|
40 |
+\item{joinBy}{\code{\link{condition_evaluation}} function to support |
|
41 |
+methods with groupBy or JoinBy input paramter} |
|
50 | 42 |
} |
51 | 43 |
\value{ |
52 | 44 |
GMQLDataset object. It contains the value to use as input |
... | ... |
@@ -14,16 +14,8 @@ |
14 | 14 |
|
15 | 15 |
\item{y}{GMQLDataset class object} |
16 | 16 |
|
17 |
-\item{joinBy}{list of evalation functions to define evaluation on metadata: |
|
18 |
-\itemize{ |
|
19 |
-\item{\code{\link{FN}}(value): Fullname evaluation, two attributes match |
|
20 |
-if they both end with \emph{value} and, if they have further prefixes, |
|
21 |
-the two prefix sequence are identical} |
|
22 |
-\item{\code{\link{EX}}(value): Exact evaluation, only attributes exactly |
|
23 |
-as \emph{value} match; no further prefixes are allowed. } |
|
24 |
-\item{\code{\link{DF}}(value): Default evaluation, the two attributes match |
|
25 |
-if both end with \emph{value}.} |
|
26 |
-}} |
|
17 |
+\item{joinBy}{\code{\link{condition_evaluation}} function to support |
|
18 |
+methods with groupBy or JoinBy input paramter} |
|
27 | 19 |
|
28 | 20 |
\item{is_exact}{single logical value: TRUE means that the region difference |
29 | 21 |
is executed only on regions in left_input_data with exactly the same |
... | ... |
@@ -73,6 +65,6 @@ out = setdiff(data1, data2) |
73 | 65 |
## do not overlap any region in s2; |
74 | 66 |
## metadata of the result are the same as the metadata of s1. |
75 | 67 |
|
76 |
-out_t = setdiff(data1, data2, DF("antibody_target")) |
|
68 |
+out_t = setdiff(data1, data2, condition_evaluation(c("cell"))) |
|
77 | 69 |
|
78 | 70 |
} |