R/S3Aggregates.R
48ab60c3
 #############################
 #       AGGREGATES         #
 ############################
 
 
73652f4d
 AGGREGATES <- function(value) {
   op_list <- list(value = value)
   ## Set the name for the class
   class(op_list) <- "AGGREGATES"
   return(op_list)
94a33e57
 }
 
73652f4d
 check.META_AGGREGATES <- function(value) {
   if(is.character(value) && length(value)>1)
     stop("value: no multiple string")
   
   if(!is.character(value))
     stop("value: is not a string")
94a33e57
 }
 
73652f4d
 META_AGGREGATES <- function(value) {
   op_list <- list(value = value)
   ## Set the name for the class
   class(op_list) <- "META_AGGREGATES"
   return(op_list)
94a33e57
 }
 
 print.META_AGGREGATES <- function(obj) {
73652f4d
   res <- as.character(obj)
   cat(res)
94a33e57
 }
 
 as.character.META_AGGREGATES <- function(obj) {
73652f4d
   class <- class(obj)[1]
   val <- obj$value
   c(class,val)
94a33e57
 }
 
 take_value.META_AGGREGATES <- function(obj){
73652f4d
   class <- class(obj)[1]
   val <- obj$value
   text <- switch(
     class,
     "SUM" = paste0("sum_",val),
     "MIN" = paste0("min_",val),
     "MAX" = paste0("max_",val),
     "COUNT" = paste0("count"),
     "BAG" = paste0("bag_",val),
     "BAGD" = paste0("bagd_",val),
     "AVG" = paste0("avg_",val),
     "STD" = paste0("std_"),
     "MEDIAN" = paste0("median_",val),
     "Q1" = paste0("q1_",val),
     "Q2" = paste0("q2_"),
     "Q3" = paste0("q3_",val)
   )
   text
94a33e57
 }
 
65260a4d
 
94a33e57
 #' AGGREGATES object class constructor
 #' 
65260a4d
 #' 
94a33e57
 #' This class constructor is used to create instances of AGGREGATES object,
 #' to be used in GMQL functions that require aggregate on value.
 #' 
65260a4d
 #' \itemize{
 #' \item{SUM: It prepares input parameter to be passed to the library 
 #' function sum, performing all the type conversions needed  }
 #' \item{COUNT: It prepares input parameter to be passed to the library 
 #' function count, performing all the type conversions needed }
40ec852b
 #' \item{COUNTSAMP: It prepares input parameter to be passed to the library 
18697071
 #' function countsamp, performing all the type conversions needed.
 #' It is used only with group_by functions}
83eb0624
 #' \item{MIN: It prepares input parameter to be passed to the library 
65260a4d
 #' function minimum, performing all the type conversions needed  }
 #' \item{MAX: It prepares input parameter to be passed to the library 
 #' function maximum, performing all the type conversions needed }
 #' \item{AVG: It prepares input parameter to be passed to the library 
 #' function mean, performing all the type conversions needed }
 #' \item{MEDIAN: It prepares input parameter to be passed to the library 
 #' function median, performing all the type conversions needed }
 #' \item{STD: It prepares input parameter to be passed to the library 
 #' function standard deviation, performing all the type conversions needed}
83eb0624
 #' \item{BAG: It prepares input parameter to be passed to the library 
 #' function bag; this function creates comma-separated strings of 
 #' attribute values, performing all the type conversions needed}
 #' \item{BAGD: It prepares input parameter to be passed to the library 
18697071
 #' function bagd; this function creates comma-separated strings of distinct 
83eb0624
 #' attribute values, performing all the type conversions needed}
65260a4d
 #' \item{Q1: It prepares input parameter to be passed to the library 
 #' function fist quartile, performing all the type conversions needed}
 #' \item{Q2: It prepares input parameter to be passed to the library 
 #' function second quartile, performing all the type conversions needed }
 #' \item{Q3: It prepares input parameter to be passed to the library 
 #' function third quartile, performing all the type conversions needed }
 #' }
94a33e57
 #' 
65260a4d
 #' @param value string identifying name of metadata or region attribute
 #'
83eb0624
 #' @return Aggregate object
94a33e57
 #' 
 #' @examples
 #' 
83eb0624
 #' ## This statement initializes and runs the GMQL server for local execution 
 #' ## and creation of results on disk. Then, with system.file() it defines 
 #' ## the path to the folder "DATASET" in the subdirectory "example"
 #' ## of the package "RGMQL" and opens such folder as a GMQL dataset 
dda0cfa0
 #' ## named "exp" using CustomParser
83eb0624
 #' 
94a33e57
 #' init_gmql()
 #' test_path <- system.file("example", "DATASET", package = "RGMQL")
18697071
 #' exp = read_gmql(test_path)
94a33e57
 #' 
83eb0624
 #' ## This statement copies all samples of exp dataset into res dataset, and 
dda0cfa0
 #' ## then calculates new metadata attribute sum_score for each of them: 
18697071
 #' ## sum_score is the sum of score values of the sample regions.
94a33e57
 #' 
b3e9c8a8
 #' res = extend(exp, sum_score = SUM("score"))
94a33e57
 #' 
83eb0624
 #' ## This statement copies all samples of exp dataset into res dataset, 
dda0cfa0
 #' ## and then calculates new metadata attribute min_pvalue for each of them: 
83eb0624
 #' ## min_pvalue is the minimum pvalue of the sample regions.
65260a4d
 #' 
83eb0624
 #' res = extend(exp, min_pvalue = MIN("pvalue"))
65260a4d
 #' 
83eb0624
 #' ## This statement copies all samples of exp dataset into res dataset, 
dda0cfa0
 #' ## and then calculates new metadata attribute max_score for each of them: 
65260a4d
 #' ## max_score is the maximum score of the sample regions.
 #' 
 #' res = extend(exp, max_score = MAX("score"))
 #' 
 #' ## The following cover operation produces output regions where at least 2 
83eb0624
 #' ## and at most 3 regions of exp dataset overlap, having as resulting region 
 #' ## attribute the average signal of the overlapping regions; 
18697071
 #' ## the result has one sample for each input cell value.
65260a4d
 #' 
4bc0d16e
 #' res = cover(exp, 2, 3, groupBy = conds("cell"), avg_signal = AVG("signal"))
65260a4d
 #' 
18697071
 #' ## This statement copies all samples of 'exp' dataset into 'out' dataset, 
 #' ## and then for each of them it adds another metadata attribute, allScore, 
65260a4d
 #' ## which is the aggregation comma-separated list of all the values 
 #' ## that the region attribute score takes in the sample.
 #' 
 #' out = extend(exp, allScore = BAG("score"))
 #' 
83eb0624
 #' ## This statement counts the regions in each sample and stores their number 
dda0cfa0
 #' ## as value of the new metadata RegionCount attribute of the sample.
65260a4d
 #' 
 #' out = extend(exp, RegionCount = COUNT())
 #' 
83eb0624
 #' ## This statement copies all samples of exp dataset into res dataset, 
dda0cfa0
 #' ## and then calculates new metadata attribute std_score for each of them: 
18697071
 #' ## std_score is the standard deviation of the score values of the sample 
 #' ## regions.
65260a4d
 #' 
 #' res = extend(exp, std_score = STD("score"))
 #' 
83eb0624
 #' ## This statement copies all samples of exp dataset into res dataset, 
dda0cfa0
 #' ## and then calculates new metadata attribute m_score for each of them: 
65260a4d
 #' ## m_score is the median score of the sample regions.
 #' 
 #' res = extend(exp, m_score = MEDIAN("score"))
 #' 
 #' 
e5131ba8
 #' @name AGGREGATES-Object
5b358a31
 #' @aliases SUM
65260a4d
 #' @rdname aggr-class
94a33e57
 #' @export
 #'
73652f4d
 SUM <- function(value) {
   check.META_AGGREGATES(value)
   
   list <- list(value = value)
   ## Set the name for the class
   class(list) <- c("SUM","AGGREGATES","META_AGGREGATES")
   return(list)
94a33e57
 }
 
83eb0624
 #' @name AGGREGATES-Object
 #' @aliases COUNT
 #' @rdname aggr-class
 #' @export
 #'
73652f4d
 COUNT <- function() {
   list <- list()
   ## Set the name for the class
   class(list) <- c("COUNT","AGGREGATES","META_AGGREGATES")
   return(list)
83eb0624
 }
 as.character.COUNT <- function(obj) {
73652f4d
   class <- class(obj)[1]
   c(class,"")
83eb0624
 }
 check.COUNT <- function(obj){}
 
 
40ec852b
 #' @name AGGREGATES-Object
 #' @aliases COUNTSAMP
 #' @rdname aggr-class
 #' @export
 #'
73652f4d
 COUNTSAMP <- function() {
   list <- list()
   ## Set the name for the class
   class(list) <- c("COUNTSAMP","AGGREGATES","META_AGGREGATES")
   return(list)
40ec852b
 }
 as.character.COUNTSAMP <- function(obj) {
73652f4d
   class <- class(obj)[1]
   c(class,"")
40ec852b
 }
 check.COUNTSAMP <- function(obj){}
 
 
e5131ba8
 #' @name AGGREGATES-Object
5b358a31
 #' @aliases MIN
65260a4d
 #' @rdname aggr-class
94a33e57
 #' @export
 #'
73652f4d
 MIN <- function(value) {
   check.META_AGGREGATES(value)
   
   list <- list(value = value)
   ## Set the name for the class
   class(list) <- c("MIN","AGGREGATES","META_AGGREGATES")
   return(list)
94a33e57
 }
 
e5131ba8
 #' @name AGGREGATES-Object
5b358a31
 #' @aliases MAX
65260a4d
 #' @rdname aggr-class 
94a33e57
 #' @export
 #'
73652f4d
 MAX <- function(value) {
   check.META_AGGREGATES(value)
   
   list <- list(value = value)
   ## Set the name for the class
   class(list) <- c("MAX","AGGREGATES","META_AGGREGATES")
   return(list)
94a33e57
 }
 
e5131ba8
 #' @name AGGREGATES-Object
5b358a31
 #' @aliases AVG
65260a4d
 #' @rdname aggr-class
94a33e57
 #' @export
 #'
73652f4d
 AVG <- function(value) {
   check.META_AGGREGATES(value)
   
   list <- list(value = value)
   ## Set the name for the class
   class(list) <- c("AVG","AGGREGATES","META_AGGREGATES")
   return(list)
94a33e57
 }
 
e5131ba8
 #' @name AGGREGATES-Object
83eb0624
 #' @aliases MEDIAN
65260a4d
 #' @rdname aggr-class
94a33e57
 #' @export
 #'
73652f4d
 MEDIAN <- function(value) {
   check.META_AGGREGATES(value)
   
   list <- list(value = value)
   ## Set the name for the class
   class(list) <- c("MEDIAN","AGGREGATES","META_AGGREGATES")
   return(list)
94a33e57
 }
 
83eb0624
 
e5131ba8
 #' @name AGGREGATES-Object
83eb0624
 #' @aliases STD
65260a4d
 #' @rdname aggr-class
94a33e57
 #' @export
 #'
73652f4d
 STD <- function(value) {
   check.META_AGGREGATES(value)
   
   list <- list(value = value)
   ## Set the name for the class
   class(list) <- c("STD","META_AGGREGATES")
   return(list)
94a33e57
 }
 
e5131ba8
 #' @name AGGREGATES-Object
83eb0624
 #' @aliases BAG
65260a4d
 #' @rdname aggr-class
94a33e57
 #' @export
 #'
73652f4d
 BAG <- function(value) {
   check.META_AGGREGATES(value)
   
   list <- list(value = value)
   ## Set the name for the class
   class(list) <- c("BAG","AGGREGATES","META_AGGREGATES")
   return(list)
94a33e57
 }
 
e5131ba8
 #' @name AGGREGATES-Object
83eb0624
 #' @aliases BAGD
65260a4d
 #' @rdname aggr-class
94a33e57
 #' @export
 #'
73652f4d
 BAGD <- function(value) {
   check.META_AGGREGATES(value)
   
   list <- list(value = value)
   ## Set the name for the class
   class(list) <- c("BAGD","AGGREGATES","META_AGGREGATES")
   return(list)
94a33e57
 }
 
e5131ba8
 #' @name AGGREGATES-Object
5b358a31
 #' @aliases Q1
65260a4d
 #' @rdname aggr-class
94a33e57
 #' @export
 #'
73652f4d
 Q1 <- function(value) {
   check.META_AGGREGATES(value)
   
   list <- list(value = value)
   ## Set the name for the class
   class(list) <- c("Q1","META_AGGREGATES")
   return(list)
94a33e57
 }
 
e5131ba8
 #' @name AGGREGATES-Object
5b358a31
 #' @aliases Q2
65260a4d
 #' @rdname aggr-class
94a33e57
 #' @export
 #'
73652f4d
 Q2 <- function(value) {
   check.META_AGGREGATES(value)
   list <- list(value = value)
   ## Set the name for the class
   class(list) <- c("Q2","META_AGGREGATES")
   return(list)
94a33e57
 }
 
e5131ba8
 #' @name AGGREGATES-Object
5b358a31
 #' @aliases Q3
65260a4d
 #' @rdname aggr-class
94a33e57
 #' @export
 #'
73652f4d
 Q3 <- function(value) {
   check.META_AGGREGATES(value)
   
   list <- list(value = value)
   ## Set the name for the class
   class(list) <- c("Q3","META_AGGREGATES")
   return(list)
94a33e57
 }