... | ... |
@@ -10,7 +10,6 @@ setGeneric("aggregate", function(x, ...) |
10 | 10 |
standardGeneric("aggregate")) |
11 | 11 |
|
12 | 12 |
|
13 |
- |
|
14 | 13 |
#' Method filter |
15 | 14 |
#' |
16 | 15 |
#' Wrapper to GMQL select function |
... | ... |
@@ -56,7 +55,7 @@ setGeneric("collect", function(x, dir_out = getwd(), name = "ds1", ...) |
56 | 55 |
|
57 | 56 |
#' Method take |
58 | 57 |
#' |
59 |
-#' GMQL Operation: TAKE |
|
58 |
+#' Wrapper to take function |
|
60 | 59 |
#' |
61 | 60 |
#' @name take |
62 | 61 |
#' @rdname take-GMQLDataset-method |
... | ... |
@@ -4,8 +4,9 @@ |
4 | 4 |
|
5 | 5 |
#' Condition evaluation functions |
6 | 6 |
#' |
7 |
-#' These functions is used to create a series of metadata as string |
|
8 |
-#' that require evaluation on value. |
|
7 |
+#' These functions is used to support joinBy and/or groupBy function parameter. |
|
8 |
+#' It create a list of one element: matrix containing the two coloumn: |
|
9 |
+#' type of condition evaluation and the metadata attribute |
|
9 | 10 |
#' |
10 | 11 |
#' \itemize{ |
11 | 12 |
#' \item{FN: It defines a FULL (FULLNAME) evaluation of the input values. |
... | ... |
@@ -149,8 +149,7 @@ setMethod("cover", "GMQLDataset", |
149 | 149 |
|
150 | 150 |
|
151 | 151 |
|
152 |
-gmql_cover <- function(data, min_acc, max_acc, groupBy = NULL, |
|
153 |
- aggregates = NULL, flag) |
|
152 |
+gmql_cover <- function(data, min_acc, max_acc, groupBy, aggregates, flag) |
|
154 | 153 |
{ |
155 | 154 |
|
156 | 155 |
if(!is.null(groupBy)) |
... | ... |
@@ -62,7 +62,7 @@ |
62 | 62 |
#' data <- read_dataset(test_path) |
63 | 63 |
#' join_data <- read_dataset(test_path2) |
64 | 64 |
#' jun_tf <- filter(data, antibody_target == "JUN", pValue < 0.01, |
65 |
-#' semijoin(join_data, TRUE, DF("cell"))) |
|
65 |
+#' semijoin(join_data, TRUE, list(DF("cell")))) |
|
66 | 66 |
#' |
67 | 67 |
#' } |
68 | 68 |
#' |
... | ... |
@@ -130,8 +130,7 @@ gmql_select <- function(input_data, predicate, region_predicate, s_join) |
130 | 130 |
#' considering semi_join NOT IN semi_join_dataset, F => semijoin is performed |
131 | 131 |
#' considering semi_join IN semi_join_dataset |
132 | 132 |
#' |
133 |
-#' @param ... Additional arguments for use in specific methods and functions |
|
134 |
-#' to define condition evaluation on metadata. |
|
133 |
+#' @param groupBy it define condition evaluation on metadata. |
|
135 | 134 |
#' \itemize{ |
136 | 135 |
#' \item{\code{\link{FN}}: Fullname evaluation, two attributes match |
137 | 136 |
#' if they both end with value and, if they have a further prefixes, |
... | ... |
@@ -162,13 +161,18 @@ gmql_select <- function(input_data, predicate, region_predicate, s_join) |
162 | 161 |
#' test_path2 <- system.file("example", "DATASET_GDM", package = "RGMQL") |
163 | 162 |
#' data <- read_dataset(test_path) |
164 | 163 |
#' join_data <- read_dataset(test_path2) |
165 |
-#' jun_tf <- filter(data,NULL,NULL, semijoin(join_data, TRUE, DF("cell"))) |
|
164 |
+#' jun_tf <- filter(data,NULL,NULL, semijoin(join_data, TRUE, |
|
165 |
+#' list(DF("cell")))) |
|
166 | 166 |
#' |
167 | 167 |
#' @return semijoin condition as list |
168 | 168 |
#' @export |
169 |
-semijoin <- function(data, not_in = FALSE, ...) |
|
169 |
+semijoin <- function(data, not_in = FALSE, groupBy = NULL) |
|
170 | 170 |
{ |
171 |
- semij_cond = list(...) |
|
171 |
+ if(!is.list(groupBy)) |
|
172 |
+ stop("groupBy: must be a list") |
|
173 |
+ |
|
174 |
+ semij_cond = groupBy |
|
175 |
+ |
|
172 | 176 |
if(is.null(data)) |
173 | 177 |
stop("data cannot be NULL") |
174 | 178 |
|
... | ... |
@@ -907,7 +907,7 @@ delete_dataset <- function(url,datasetName) |
907 | 907 |
#' @rdname download_dataset |
908 | 908 |
#' @export |
909 | 909 |
#' |
910 |
-download_dataset <- function(url,datasetName,path = getwd()) |
|
910 |
+download_dataset <- function(url, datasetName, path = getwd()) |
|
911 | 911 |
{ |
912 | 912 |
url <- sub("/*[/]$","",url) |
913 | 913 |
URL <- paste0(url,"/datasets/",datasetName,"/zip") |
... | ... |
@@ -920,9 +920,9 @@ download_dataset <- function(url,datasetName,path = getwd()) |
920 | 920 |
else |
921 | 921 |
{ |
922 | 922 |
zip_path <- paste0(path,"/",datasetName,".zip") |
923 |
- dir_out <-paste0(path,"/") |
|
924 |
- writeBin(content,zip_path) |
|
925 |
- unzip(zip_path,exdir=dir_out) |
|
923 |
+ dir_out <- paste0(path,"/") |
|
924 |
+ writeBin(content, zip_path) |
|
925 |
+ unzip(zip_path,exdir = dir_out) |
|
926 | 926 |
print("Download Complete") |
927 | 927 |
} |
928 | 928 |
} |
... | ... |
@@ -27,9 +27,6 @@ None |
27 | 27 |
\description{ |
28 | 28 |
Wrapper to GMQL materialize function |
29 | 29 |
|
30 |
-Wrapper to GMQL materialize function |
|
31 |
-} |
|
32 |
-\details{ |
|
33 | 30 |
It saves the contents of a dataset that contains samples metadata and |
34 | 31 |
samples regions. |
35 | 32 |
It is normally used to persist the contents of any dataset generated |
... | ... |
@@ -20,8 +20,9 @@ to be evaluated} |
20 | 20 |
list of 2-D array containing method of evaluation and metadata |
21 | 21 |
} |
22 | 22 |
\description{ |
23 |
-These functions is used to create a series of metadata as string |
|
24 |
-that require evaluation on value. |
|
23 |
+These functions is used to support joinBy and/or groupBy function parameter. |
|
24 |
+It create a list of one element: matrix containing the two coloumn: |
|
25 |
+type of condition evaluation and the metadata attribute |
|
25 | 26 |
} |
26 | 27 |
\details{ |
27 | 28 |
\itemize{ |
... | ... |
@@ -59,25 +59,25 @@ s <- filter(input, Patient_age < 70) |
59 | 59 |
|
60 | 60 |
\dontrun{ |
61 | 61 |
|
62 |
-# It creates a new dataset called 'jun_tf' by selecting those samples and |
|
63 |
-# their regions from the existing 'data' dataset such that: |
|
64 |
-# Each output sample has a metadata attribute called antibody_target |
|
65 |
-# with value JUN. |
|
66 |
-# Each output sample also has not a metadata attribute called "cell" |
|
67 |
-# that has the same value of at least one of the values that a metadata |
|
68 |
-# attribute equally called cell has in at least one sample |
|
69 |
-# of the 'join_data' dataset. |
|
70 |
-# For each sample satisfying previous condition,only its regions that |
|
71 |
-# have a region attribute called pValue with the associated value |
|
72 |
-# less than 0.01 are conserved in output |
|
62 |
+## It creates a new dataset called 'jun_tf' by selecting those samples and |
|
63 |
+## their regions from the existing 'data' dataset such that: |
|
64 |
+## Each output sample has a metadata attribute called antibody_target |
|
65 |
+## with value JUN. |
|
66 |
+## Each output sample also has not a metadata attribute called "cell" |
|
67 |
+## that has the same value of at least one of the values that a metadata |
|
68 |
+## attribute equally called cell has in at least one sample |
|
69 |
+## of the 'join_data' dataset. |
|
70 |
+## For each sample satisfying previous condition,only its regions that |
|
71 |
+## have a region attribute called pValue with the associated value |
|
72 |
+## less than 0.01 are conserved in output |
|
73 | 73 |
|
74 | 74 |
|
75 | 75 |
init_gmql() |
76 | 76 |
test_path <- system.file("example", "DATASET", package = "RGMQL") |
77 | 77 |
test_path2 <- system.file("example", "DATASET_GDM", package = "RGMQL") |
78 | 78 |
data <- read_dataset(test_path) |
79 |
-join_data <- read_dataset(test_path2) |
|
80 |
-jun_tf <- filter(data, antibody_target == 'JUN', pValue < 0.01, |
|
79 |
+join_data <- read_dataset(test_path2) |
|
80 |
+jun_tf <- filter(data, antibody_target == "JUN", pValue < 0.01, |
|
81 | 81 |
semijoin(join_data, TRUE, DF("cell"))) |
82 | 82 |
|
83 | 83 |
} |
... | ... |
@@ -14,7 +14,7 @@ |
14 | 14 |
|
15 | 15 |
\item{y}{GMQLDataset class object} |
16 | 16 |
|
17 |
-\item{genometric_predicate}{is a list of lists of DISTAL object |
|
17 |
+\item{genometric_predicate}{is a list of DISTAL object |
|
18 | 18 |
For details of DISTAL objects see: |
19 | 19 |
\code{\link{DLE}}, \code{\link{DGE}}, \code{\link{DL}}, \code{\link{DG}}, |
20 | 20 |
\code{\link{MD}}, \code{\link{UP}}, \code{\link{DOWN}}} |
... | ... |
@@ -82,7 +82,7 @@ test_path2 <- system.file("example", "DATASET_GDM", package = "RGMQL") |
82 | 82 |
TSS = read_dataset(test_path) |
83 | 83 |
HM = read_dataset(test_path2) |
84 | 84 |
join_data = merge(TSS, HM, |
85 |
-genometric_predicate = list(list(MD(1), DLE(120000))), DF("provider"), |
|
85 |
+genometric_predicate = list(MD(1), DLE(120000)), DF("provider"), |
|
86 | 86 |
region_output = "RIGHT") |
87 | 87 |
|
88 | 88 |
|
... | ... |
@@ -4,7 +4,7 @@ |
4 | 4 |
\alias{semijoin} |
5 | 5 |
\title{Semijoin Condtion} |
6 | 6 |
\usage{ |
7 |
-semijoin(data, not_in = FALSE, ...) |
|
7 |
+semijoin(data, not_in = FALSE, groupBy = NULL) |
|
8 | 8 |
} |
9 | 9 |
\arguments{ |
10 | 10 |
\item{data}{GMQLDataset class object} |
... | ... |
@@ -13,8 +13,7 @@ semijoin(data, not_in = FALSE, ...) |
13 | 13 |
considering semi_join NOT IN semi_join_dataset, F => semijoin is performed |
14 | 14 |
considering semi_join IN semi_join_dataset} |
15 | 15 |
|
16 |
-\item{...}{Additional arguments for use in specific methods. |
|
17 |
-It is also accpet a functions to define condition evaluation on metadata. |
|
16 |
+\item{groupBy}{it define condition evaluation on metadata. |
|
18 | 17 |
\itemize{ |
19 | 18 |
\item{\code{\link{FN}}: Fullname evaluation, two attributes match |
20 | 19 |
if they both end with value and, if they have a further prefixes, |
... | ... |
@@ -24,7 +24,7 @@ by default is 0 that means take all rows for each sample} |
24 | 24 |
GrangesList with associated metadata |
25 | 25 |
} |
26 | 26 |
\description{ |
27 |
-GMQL Operation: TAKE |
|
27 |
+Wrapper to take function |
|
28 | 28 |
|
29 | 29 |
It saves the contents of a dataset that contains samples metadata |
30 | 30 |
and samples regions as GrangesList. |
... | ... |
@@ -270,8 +270,8 @@ In this example we show how versatile RGMQL package are. |
270 | 270 |
As specified above, we can directly read a list of GRanges previously created |
271 | 271 |
starting from two GRanges. |
272 | 272 |
Both *read()* and *read_dataset()* functions returns a result object, |
273 |
-in this case *data_out* containing an internal R representation of the dataset |
|
274 |
-used as input for executing the subsequent GMQL operation. |
|
273 |
+in this case *data_out*: an instance of GMQLDataset class used as input |
|
274 |
+for executing the subsequent GMQL operation. |
|
275 | 275 |
|
276 | 276 |
### Queries |
277 | 277 |
|
... | ... |
@@ -330,7 +330,8 @@ specific path defined as input parameter. |
330 | 330 |
## Materialize the result dataset on disk |
331 | 331 |
collect(exon_res) |
332 | 332 |
``` |
333 |
-by default *collect()* has R workig directoy as stored path. |
|
333 |
+by default *collect()* has R workig directoy as stored path and *ds1* as name |
|
334 |
+of resulted dataset folder |
|
334 | 335 |
|
335 | 336 |
### Execution |
336 | 337 |
|