Browse code

added FULL param to filter_extract function

Simone authored on 27/03/2021 14:32:41
Showing 4 changed files

... ...
@@ -61,6 +61,7 @@ Collate:
61 61
     'S3Aggregates.R'
62 62
     'S3Cover-Param.R'
63 63
     'S3Distal.R'
64
+    'S3filter_extract_param.R'
64 65
     'S3Operator.R'
65 66
     'Utils.R'
66 67
     'evaluation-functions.R'
... ...
@@ -89,30 +89,3 @@ ANY <- function() {
89 89
   return(list)
90 90
 }
91 91
 
92
-
93
-#' PARAM object class constructor
94
-#'
95
-#' This class constructor is used to create instances of PARAM object
96
-#' to be used in filter and extract function.
97
-#' 
98
-#' It is used to encompasses all the region parameters already present 
99
-#' into the dataset or GrangesList
100
-#' 
101
-#' \itemize{
102
-#' \item{FULL: It consider all the region paramter}
103
-#' }
104
-#' @param except The list of attribute to not consider
105
-#' 
106
-#' @return Param object
107
-#'
108
-#' @name filter-extract
109
-#' @aliases FULL
110
-#' @rdname filter-extract-param-class
111
-#' @export
112
-#'
113
-FULL <- function(except = NULL) {
114
-  value <- list(values = c(except))
115
-  ## Set the name for the class
116
-  class(value) <- c("FULL", "PARAMETER")
117
-  return(value)
118
-}
119 92
new file mode 100644
... ...
@@ -0,0 +1,46 @@
1
+##########################################
2
+#       PARAMETER_FILTER_EXTRACT        #
3
+#########################################
4
+
5
+PARAMETER_FILTER_EXTRACT <- function() {
6
+  op_list <- list()
7
+  ## Set the name for the class
8
+  class(op_list) <- "PARAMETER_FILTER_EXTRACT"
9
+  return(op_list)
10
+}
11
+
12
+as.character.PARAMETER_FILTER_EXTRACT <- function(obj) {
13
+  class <- class(obj)[1]
14
+}
15
+
16
+print.PARAMETER_FILTER_EXTRACT <- function(obj){
17
+  print(as.character.PARAMETER_FILTER_EXTRACT(obj))
18
+}
19
+
20
+
21
+#' PARAM object class constructor
22
+#'
23
+#' This class constructor is used to create instances of PARAM object
24
+#' to be used in filter and extract function.
25
+#' 
26
+#' It is used to encompasses all the region parameters already present 
27
+#' into the dataset or GRangesList
28
+#' 
29
+#' \itemize{
30
+#' \item{FULL: It consider all the region paramter}
31
+#' }
32
+#' @param except The list of attribute to not consider
33
+#' 
34
+#' @return Param object
35
+#'
36
+#' @name filter-extract
37
+#' @aliases FULL
38
+#' @rdname filter-extract-param-class
39
+#' @export
40
+#'
41
+FULL <- function(except = NULL) {
42
+  value <- list(values = c(except))
43
+  ## Set the name for the class
44
+  class(value) <- c("FULL", "PARAMETER_FILTER_EXTRACT")
45
+  return(value)
46
+}
0 47
\ No newline at end of file
... ...
@@ -57,10 +57,26 @@
57 57
 #' ## function makes sure that the region coordinates (chr, ranges, strand)
58 58
 #' ## of all samples are ordered correctly
59 59
 #'
60
-#'
61 60
 #' grl <- import_gmql(test_path, TRUE)
62 61
 #' sorted_grl <- sort(grl)
63 62
 #' filter_and_extract(sorted_grl, region_attributes = c("pvalue", "peak"))
63
+#' 
64
+#' ## It is also possible to define the region attributes, using the FULL() 
65
+#' ## function parameter, in order to includes every region 
66
+#' ## attributes present into the schema file
67
+#' 
68
+#' sorted_grl_full <- sort(grl)
69
+#' filter_and_extract(sorted_grl, region_attributes = FULL())
70
+#' 
71
+#' ## Also, we can inlcude a list of region attribute inside the FULL() 
72
+#' ## function to exlucde that regions
73
+#' 
74
+#' sorted_grl_full_except <- sort(grl)
75
+#' filter_and_extract(
76
+#'  sorted_grl_full_except, 
77
+#'  region_attributes = FULL("jaccard", "score")
78
+#' )
79
+#' 
64 80
 #' @export
65 81
 #'
66 82
 filter_and_extract <- function(
... ...
@@ -147,8 +163,7 @@ filter_and_extract <- function(
147 163
       vector_field, 
148 164
       samples_to_read, 
149 165
       regions,
150
-      suffix_vec,
151
-      vector_field
166
+      suffix_vec
152 167
     )
153 168
     
154 169
   } else {
... ...
@@ -362,6 +377,24 @@ filter_and_extract <- function(
362 377
   col_names <- names(df)
363 378
   df <- subset(df, TRUE, c("chr", "left", "right", "strand"))
364 379
   
380
+  # check if we used a FULL parameter instead of char array containing
381
+  # the region parameters
382
+  if(is.object(regions) && ("FULL" %in% class(regions))) {
383
+    all_values <- vector_field[!vector_field %in% c(
384
+      "chr", 
385
+      "left", 
386
+      "right",
387
+      "strand"
388
+      )
389
+    ]
390
+    except_values <- regions$values
391
+    regions <- if (is.null(except_values))
392
+      all_values
393
+    else
394
+      all_values[!all_values %in% except_values]
395
+    names(regions) <- NULL
396
+  }
397
+  
365 398
   if (!is.null(regions)) {
366 399
     df_list <- lapply(gdm_region_files, function(x, regions, vector_field) {
367 400
       region_frame <- data.table::fread(