R/S3Distal.R
43d9e4a1
 ##########################
 #       DISTAL          #
 #########################
 
73652f4d
 DISTAL <- function(value) {
9212b326
     op_list <- list(value = value)
     ## Set the name for the class
     class(op_list) <- "DISTAL"
     return(op_list)
43d9e4a1
 }
 
 print.DISTAL <- function(obj) {
9212b326
     print(as.character.DISTAL(obj))
43d9e4a1
 }
 
 as.character.DISTAL <- function(obj) {
9212b326
     class <- class(obj)[1]
     val <- obj$value
     c(class,val)
43d9e4a1
 }
 
73652f4d
 check.DISTAL <- function(value) {
9212b326
     if(!is.numeric(value))
         stop("value: is not a numeric")
     
     if(is.numeric(value) && length(value)>1)
         stop("value: no multiple string")
43d9e4a1
 }
 #' DISTAL object class constructor
 #'
 #' This class constructor is used to create instances of DISTAL object
83eb0624
 #' to be used in GMQL JOIN operations (RGMQL merge functions) that use 
 #' genometric predicate parameter requiring distal condition on value
65260a4d
 #' 
 #' \itemize{
 #' \item{DL: It denotes the less distance clause, 
83eb0624
 #' which selects all the regions of a joined experiment dataset sample such 
18697071
 #' that their distance from the anchor region of the joined reference dataset 
83eb0624
 #' sample is less than 'value' bases.}
18697071
 #' \item{DLE: It denotes the less equal distance clause, 
83eb0624
 #' which selects all the regions of a joined experiment dataset sample such 
18697071
 #' that their distance from the anchor region of the joined reference dataset 
83eb0624
 #' sample is less than, or equal to, 'value' bases.}
18697071
 #' \item{DG: It denotes the great distance clause, 
83eb0624
 #' which selects all the regions of a joined experiment dataset sample such 
18697071
 #' that their distance from the anchor region of the joined reference dataset 
83eb0624
 #' sample is greater than 'value' bases. }
18697071
 #' \item{DGE: It denotes the great equal distance clause, 
83eb0624
 #' which selects all the regions of a joined experiment dataset sample such 
18697071
 #' that their distance from the anchor region of the joined reference dataset 
83eb0624
 #' sample is greater than, or equal to, 'value' bases.}
65260a4d
 #' \item{MD: It denotes the minimum distance clause, which selects 
18697071
 #' the first 'value' regions of the joined experiment at minimial distance 
 #' from the anchor region of the joined reference dataset sample.}
65260a4d
 #' \item{UP: It denotes the upstream direction of the genome.
18697071
 #' It makes predicates to be hold on the upstream of the regions of the joined 
 #' reference dataset sample.
 #' UP is true when region of the joined experiment dataset sample is in the
 #' upstream genome of the anchor region of the joined reference dataset sample.
65260a4d
 #' When this clause is not present, distal conditions apply to both 
83eb0624
 #' directions of the genome.}
 #' \item{DOWN:  It denotes the downstream direction of the genome.
18697071
 #' It makes predicates to be hold on the downstream of the regions of the 
 #' joined reference dataset sample.
 #' DOWN is true when region of the joined experiment dataset sample is in the
 #' downstream genome of the anchor region of the joined reference dataset 
 #' sample. When this clause is not present, distal conditions apply to both 
83eb0624
 #' directions of the genome.}
65260a4d
 #' }
43d9e4a1
 #' 
94a33e57
 #' @param value string identifying distance between genomic regions 
18697071
 #' in base pair
43d9e4a1
 #'
83eb0624
 #' @return Distal object
43d9e4a1
 #' 
 #' @examples
18697071
 #' ## This statement initializes and runs the GMQL server for local execution 
83eb0624
 #' ## and creation of results on disk. Then, with system.file() it defines 
 #' ## the path to the folders "DATASET" and "DATASET_GDM" in the subdirectory 
18697071
 #' ## "example" of the package "RGMQL", and opens such folders as a GMQL 
dda0cfa0
 #' ## datasets named "TSS" and "HM", respectively, using CustomParser
43d9e4a1
 #' 
65260a4d
 #' init_gmql()
83eb0624
 #' test_path <- system.file("example", "DATASET", package = "RGMQL")
 #' test_path2 <- system.file("example", "DATASET_GDM", package = "RGMQL")
18697071
 #' TSS = read_gmql(test_path)
 #' HM = read_gmql(test_path2)
65260a4d
 #' 
4f1ecbce
 #' ## Given a dataset HM and one called TSS with a sample including 
18697071
 #' ## Transcription Start Site annotations, this statement  searches for those 
 #' ## regions of HM that are at a minimal distance from a transcription 
 #' ## start site (TSS) and takes the first/closest one for each TSS, provided 
 #' ## that such distance is lesser than 1200 bases and joined TSS and HM 
 #' ## samples are obtained from the same provider (joinby clause).
94a33e57
 #' 
fce655ee
 #' join_data = merge(TSS, HM, 
dda0cfa0
 #'     genometric_predicate = list(MD(1), DL(1200)), conds("provider"), 
 #'     region_output = "RIGHT")
43d9e4a1
 #'
18697071
 #' ## Given a dataset HM and one called TSS with a sample including 
 #' ## Transcription Start Site annotations, this statement searches for those 
 #' ## regions of HM that are downstream and at a minimal distance from a 
 #' ## transcription start site (TSS) and takes the first/closest one for each 
 #' ## TSS, provided that such distance is greater than 12K bases and joined 
 #' ## TSS and HM samples are obtained from the same provider (joinby clause).
65260a4d
 #' 
fce655ee
 #' join_data = merge(TSS, HM, 
dda0cfa0
 #'     genometric_predicate = list(MD(1), DGE(12000), DOWN()), 
 #'     conds("provider"), region_output = "RIGHT")
43d9e4a1
 #'
e5131ba8
 #' @name DISTAL-Object
5b358a31
 #' @aliases DL
65260a4d
 #' @rdname distal-class
 #' @export
 #' 
73652f4d
 DL <- function(value) {
9212b326
     check.DISTAL(value)
     list <- list(value = as.integer(value))
     ## Set the name for the class
     class(list) <- c("DL","DISTAL")
     return(list)
43d9e4a1
 }
65260a4d
 
5b358a31
 #' @name DG
 #' @aliases DG
65260a4d
 #' @rdname distal-class
43d9e4a1
 #' @export
65260a4d
 #' 
73652f4d
 DG <- function(value) {
9212b326
     check.DISTAL(value)
     list <- list(value = as.integer(value))
     ## Set the name for the class
     class(list) <- c("DG","DISTAL")
     return(list)
43d9e4a1
 }
 
e5131ba8
 #' @name DISTAL-Object
5b358a31
 #' @aliases DLE
65260a4d
 #' @rdname distal-class
43d9e4a1
 #' @export
65260a4d
 #' 
73652f4d
 DLE <- function(value) {
9212b326
     check.DISTAL(value)
     list <- list(value = as.integer(value))
     ## Set the name for the class
     class(list) <- c("DLE","DISTAL")
     return(list)
43d9e4a1
 }
 
e5131ba8
 #' @name DISTAL-Object
5b358a31
 #' @aliases DGE
65260a4d
 #' @rdname distal-class
43d9e4a1
 #' @export
65260a4d
 #' 
73652f4d
 DGE <- function(value) {
9212b326
     check.DISTAL(value)
     list <- list(value = as.integer(value))
     ## Set the name for the class
     class(list) <- c("DGE","DISTAL")
     return(list)
43d9e4a1
 }
 
e5131ba8
 #' @name DISTAL-Object
5b358a31
 #' @aliases MD
65260a4d
 #' @rdname distal-class
43d9e4a1
 #' @export
65260a4d
 #' 
73652f4d
 MD <- function(value) {
9212b326
     check.DISTAL(value)
     list <- list(value = as.integer(value))
     ## Set the name for the class
     class(list) <- c("MD","DISTAL")
     return(list)
43d9e4a1
 }
 
 
e5131ba8
 #' @name DISTAL-Object
5b358a31
 #' @aliases UP
65260a4d
 #' @rdname distal-class
43d9e4a1
 #' @export
65260a4d
 #' 
73652f4d
 UP <- function() {
9212b326
     list <- list()
     ## Set the name for the class
     class(list) <- c("UP","DISTAL")
     return(list)
43d9e4a1
 }
 as.character.UP <- function(obj) {
9212b326
     class <- class(obj)[1]
     c(class,"")
43d9e4a1
 }
 
65260a4d
 
e5131ba8
 #' @name DISTAL-Object
5b358a31
 #' @aliases DOWN
65260a4d
 #' @rdname distal-class
43d9e4a1
 #' @export
65260a4d
 #' 
73652f4d
 DOWN <- function() {
9212b326
     list <- list()
     ## Set the name for the class
     class(list) <- c("DOWN","DISTAL")
     return(list)
43d9e4a1
 }
 as.character.DOWN <- function(obj) {
9212b326
     class <- class(obj)[1]
     c(class,"")
43d9e4a1
 }