R/TemporalExtent.R

Defines functions temporalExtent

#' An S4 class to represent the temporal extent of a dataset
#'
#' @slot from The initial time of the dataset
#' @slot to The final time of the dataset
setClass (
  Class = "TemporalExtent",
  representation = representation(
    from = "POSIXlt",
    to = "POSIXlt"
  ),
  validity = function(object){
    cat("~~~ TemporalExtent: inspector ~~~ \n")
    
    from <- object@from
    to <- object@to
    
    #TODO: Validate!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!11
    if(FALSE){
      stop ("[TemporalExtent: validation] Only one user and one password allowed")
    }else{}
    return(TRUE)
  }
)


#*******************************************************
#CONSTRUCTOR

setMethod (
  f="initialize",
  signature="TemporalExtent",
  definition=function(.Object,from,to){
    #cat ("~~~~~ TemporalExtent: initializator ~~~~~ \n")
    if(!missing(from)){
      if(!missing(to)){
        .Object@from <- from
        .Object@to <- to
        validObject(.Object)# call of the inspector
      }else{
        .Object@to<- character(0)
      }
    }else{
      .Object@from <- character(0)
    }
    return(.Object)
  }
)


#CONSTRUCTOR (USER FRIENDLY)
temporalExtent <- function(from, to){
  cat ("~~~~~ TemporalExtent: constructor ~~~~~ \n")
  new (Class="TemporalExtent", from = from, to = to)
}


#*******************************************************
#ACCESSORS

setGeneric("getFrom",function(object){standardGeneric ("getFrom")})
setMethod("getFrom","TemporalExtent",
          function(object){
            return(object@from)
          }
)

setGeneric("getTo",function(object){standardGeneric ("getTo")})
setMethod("getTo","TemporalExtent",
          function(object){
            return(object@to)
          }
)
jimjonesbr/sdd documentation built on May 19, 2019, 10:34 a.m.