From 4138eab8a20bc95fcddcdf52fa2bd2d893998780 Mon Sep 17 00:00:00 2001 From: Jorge Date: Wed, 25 Apr 2018 13:21:39 +0200 Subject: [PATCH 01/15] fix std field scaleGrid --- R/scaleGrid.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/scaleGrid.R b/R/scaleGrid.R index c317ad8..092d668 100644 --- a/R/scaleGrid.R +++ b/R/scaleGrid.R @@ -264,7 +264,7 @@ gridScale. <- function(grid, base, ref, clim.fun, by.member, type, parallel, max base.m$Data <- array(data = apply(base.m$Data, MARGIN = -ind, FUN = function(Z) {mean(Z,na.rm = TRUE)}),dim = dim(base.m$Data)) attr(base.m$Data,"dimensions") <- getDim.base if ((type == "standardize")) { - base.std <- array(data = apply(grid$Data, MARGIN = -ind, FUN = function(Z) {mean(sd,na.rm = TRUE)}),dim = dim(base.m$Data)) + base.std <- array(data = apply(grid$Data, MARGIN = -ind, FUN = function(Z) {sd(Z,na.rm = TRUE)}),dim = dim(base.m$Data)) } } From 74e0fd8f4d118191c0fc80039c38dc2993dbb604 Mon Sep 17 00:00:00 2001 From: Jorge Date: Wed, 25 Apr 2018 13:40:23 +0200 Subject: [PATCH 02/15] conflict solved --- R/scaleGrid.R | 84 +++++++++++++++++++++++++-------------------------- 1 file changed, 42 insertions(+), 42 deletions(-) diff --git a/R/scaleGrid.R b/R/scaleGrid.R index 60b13d3..7e6d22c 100644 --- a/R/scaleGrid.R +++ b/R/scaleGrid.R @@ -246,7 +246,6 @@ scaleGrid <- function(grid, #' @author J Bedia gridScale. <- function(grid, base, ref, clim.fun, by.member, type, parallel, max.ncores, ncores, spatial.frame) { -<<<<<<< HEAD grid <- redim(grid) if (is.null(base)) { base.m <- suppressMessages({ @@ -291,47 +290,48 @@ gridScale. <- function(grid, base, ref, clim.fun, by.member, type, parallel, max base.std <- array(data = apply(redim(base)$Data, MARGIN = -ind, FUN = function(Z) {sd(Z,na.rm = TRUE)}),dim = dim(base.m$Data)) } } - if (!is.null(ref)) { - checkDim(grid, ref, dimensions = c("lat", "lon")) - checkSeason(grid, ref) - ref.m <- suppressMessages({ - climatology(ref, clim.fun, by.member, parallel, max.ncores,ncores) - }) %>% redim() - if (type == "standardize") { - ref.std <- suppressMessages({ - climatology(ref, clim.fun = list(FUN = "sd", na.rm = TRUE), by.member, parallel, max.ncores, ncores) - }) %>% redim() - ref.std <- ref.std$Data} - if (spatial.frame == "field") { - getDim.ref <- attr(ref.m$Data, "dimensions") - ind <- c(which(getDim(ref.m) == "time"), which(getDim(ref.m) == "lat"), which(getDim(ref.m) == "lon")) - ref.m$Data <- array(data = apply(ref.m$Data, MARGIN = -ind, FUN = function(Z) {mean(Z,na.rm = TRUE)}),dim = dim(ref.m$Data)) - attr(ref.m$Data,"dimensions") <- getDim.ref - if (type == "standardize") { - ref.std <- array(data = apply(redim(ref)$Data, MARGIN = -ind, FUN = function(Z) {sd(Z,na.rm = TRUE)}),dim = dim(ref.m$Data)) - } - } - ref <- ref.m - } else { - ref <- list() - ref[["Data"]] <- array(0, getShape(base.m)) - attr(ref[["Data"]], "dimensions") <- getDim(base.m) - } - parallel.pars <- parallelCheck(parallel, max.ncores, ncores) - lapply_fun <- selectPar.pplyFun(parallel.pars, .pplyFUN = "lapply") - if (parallel.pars$hasparallel) on.exit(parallel::stopCluster(parallel.pars$cl)) - clim <- grid[["Data"]] - dimNames <- getDim(grid) - ind.time <- grep("^time", dimNames) - n.times <- getShape(grid, "time") - Xc <- base.m[["Data"]] - Xref <- ref[["Data"]] - aux.list <- gridScale.type(clim, n.times, ind.time, Xc, Xref, type, lapply_fun, base.std, ref.std) - Xc <- Xref <- base <- base.m <- base.std <- ref <- ref.std <- NULL - grid[["Data"]] <- do.call("abind", c(aux.list, along = ind.time)) %>% unname() - aux.list <- NULL - attr(grid[["Data"]], "dimensions") <- dimNames - return(grid) + } + if (!is.null(ref)) { + checkDim(grid, ref, dimensions = c("lat", "lon")) + checkSeason(grid, ref) + ref.m <- suppressMessages({ + climatology(ref, clim.fun, by.member, parallel, max.ncores,ncores) + }) %>% redim() + if (type == "standardize") { + ref.std <- suppressMessages({ + climatology(ref, clim.fun = list(FUN = "sd", na.rm = TRUE), by.member, parallel, max.ncores, ncores) + }) %>% redim() + ref.std <- ref.std$Data} + if (spatial.frame == "field") { + getDim.ref <- attr(ref.m$Data, "dimensions") + ind <- c(which(getDim(ref.m) == "time"), which(getDim(ref.m) == "lat"), which(getDim(ref.m) == "lon")) + ref.m$Data <- array(data = apply(ref.m$Data, MARGIN = -ind, FUN = function(Z) {mean(Z,na.rm = TRUE)}),dim = dim(ref.m$Data)) + attr(ref.m$Data,"dimensions") <- getDim.ref + if (type == "standardize") { + ref.std <- array(data = apply(redim(ref)$Data, MARGIN = -ind, FUN = function(Z) {sd(Z,na.rm = TRUE)}),dim = dim(ref.m$Data)) + } + } + ref <- ref.m + } else { + ref <- list() + ref[["Data"]] <- array(0, getShape(base.m)) + attr(ref[["Data"]], "dimensions") <- getDim(base.m) + } + parallel.pars <- parallelCheck(parallel, max.ncores, ncores) + lapply_fun <- selectPar.pplyFun(parallel.pars, .pplyFUN = "lapply") + if (parallel.pars$hasparallel) on.exit(parallel::stopCluster(parallel.pars$cl)) + clim <- grid[["Data"]] + dimNames <- getDim(grid) + ind.time <- grep("^time", dimNames) + n.times <- getShape(grid, "time") + Xc <- base.m[["Data"]] + Xref <- ref[["Data"]] + aux.list <- gridScale.type(clim, n.times, ind.time, Xc, Xref, type, lapply_fun, base.std, ref.std) + Xc <- Xref <- base <- base.m <- base.std <- ref <- ref.std <- NULL + grid[["Data"]] <- do.call("abind", c(aux.list, along = ind.time)) %>% unname() + aux.list <- NULL + attr(grid[["Data"]], "dimensions") <- dimNames + return(grid) } #' @title Local scaling type internal From 1c77cee09f316bb35bf2c45b331bffc56447a6fc Mon Sep 17 00:00:00 2001 From: Jorge Date: Wed, 25 Apr 2018 16:46:37 +0200 Subject: [PATCH 03/15] comentar check season --- R/scaleGrid.R | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/R/scaleGrid.R b/R/scaleGrid.R index 7e6d22c..473bef8 100644 --- a/R/scaleGrid.R +++ b/R/scaleGrid.R @@ -269,7 +269,7 @@ gridScale. <- function(grid, base, ref, clim.fun, by.member, type, parallel, max } } else { - checkSeason(grid, base) + # checkSeason(grid, base) checkDim(grid, base, dimensions = c("lat", "lon")) base.m <- suppressMessages({ climatology(base, clim.fun, by.member, parallel, max.ncores, ncores) @@ -293,7 +293,7 @@ gridScale. <- function(grid, base, ref, clim.fun, by.member, type, parallel, max } if (!is.null(ref)) { checkDim(grid, ref, dimensions = c("lat", "lon")) - checkSeason(grid, ref) + # checkSeason(grid, ref) ref.m <- suppressMessages({ climatology(ref, clim.fun, by.member, parallel, max.ncores,ncores) }) %>% redim() From 377402bf39f89ad601d4ef2743a456057eaa8def Mon Sep 17 00:00:00 2001 From: Your Name Date: Thu, 3 May 2018 13:53:57 +0200 Subject: [PATCH 04/15] bug fix in bindGrid --- NAMESPACE | 1 + R/bindGrid.R | 7 ++++--- 2 files changed, 5 insertions(+), 3 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index 65e247f..44a6e17 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -6,6 +6,7 @@ export(array3Dto2Dmat) export(binaryGrid) export(bindGrid) export(bindGrid.member) +export(bindGrid.spatial) export(bindGrid.time) export(checkDim) export(checkSeason) diff --git a/R/bindGrid.R b/R/bindGrid.R index dbfbd35..061e751 100644 --- a/R/bindGrid.R +++ b/R/bindGrid.R @@ -59,8 +59,8 @@ bindGrid <- function(..., dimension = c("member", "time", "lat", "lon"), bindGrid.member(..., spatial.tolerance = spatial.tolerance) } else if (dimension == "time") { bindGrid.time(..., spatial.tolerance = spatial.tolerance) - } else if (dimension == "lat") { - bindGrid.spatial(..., dimesnion = dimension, spatial.tolerance = spatial.tolerance) + } else if (dimension == "lat" | dimension == "lon") { + bindGrid.spatial(..., dimension = dimension, spatial.tolerance = spatial.tolerance) } } #end @@ -232,12 +232,13 @@ bindGrid.member <- function(..., spatial.tolerance = 1e-3) { #' @importFrom abind abind #' @family internal.helpers #' @author M Iturbide +#' @export bindGrid.spatial <- function(..., dimension = c("lat", "lon"), spatial.tolerance = 1e-3) { dimension <- match.arg(dimension, choices = c("lat", "lon")) dimsort <- "y" - if(dimension == "lon") dimsort <- "x" + if (dimension == "lon") dimsort <- "x" grid.list <- list(...) if (length(grid.list) == 1) { grid.list <- unlist(grid.list, recursive = FALSE) From 39f05544843f5dd6b4165740a663d3bb48a291f5 Mon Sep 17 00:00:00 2001 From: Jorge Date: Fri, 18 May 2018 10:23:46 +0200 Subject: [PATCH 05/15] bug fixed in members binaryGrid --- R/binaryGrid.R | 13 +++++++------ man/binaryGrid.Rd | 2 +- 2 files changed, 8 insertions(+), 7 deletions(-) diff --git a/R/binaryGrid.R b/R/binaryGrid.R index adf3381..bed5203 100644 --- a/R/binaryGrid.R +++ b/R/binaryGrid.R @@ -41,7 +41,7 @@ #' ybin2 <- binaryGrid(VALUE_Iberia_pr,threshold = 1, partial = TRUE) #' head(ybin2$Data) -binaryGrid <- function(x, condition = "GE", threshold = 1, partial = FALSE, ref.obs = NULL, ref.pred = NULL) { +binaryGrid <- function(x, condition = "GE", threshold = NULL, partial = FALSE, ref.obs = NULL, ref.pred = NULL) { condition <- match.arg(condition, choices = c("GT", "GE", "LT", "LE")) dimNames <- getDim(x) loc <- FALSE @@ -49,14 +49,15 @@ binaryGrid <- function(x, condition = "GE", threshold = 1, partial = FALSE, ref. x <- redim(x, loc = loc) for (j in 1:dim(x$Data)[which(getDim(x) == "member")]) { if (is.null(threshold)) { + ref.obs <- redim(ref.obs, loc = loc) if (isRegular(x)) { - xx <- suppressWarnings(array3Dto2Dmat(subsetGrid(x,members = 1)$Data)) + xx <- suppressWarnings(array3Dto2Dmat(subsetGrid(x,members = j)$Data)) xx.obs <- suppressWarnings(array3Dto2Dmat(subsetGrid(ref.obs,members = 1)$Data)) if (is.null(ref.pred)) {xx.pred <- xx} else {xx.pred <- suppressWarnings(array3Dto2Dmat(subsetGrid(ref.pred,members = 1)$Data))} } else { - xx <- x$Data[1,,] + xx <- x$Data[j,,] xx.obs <- ref.obs$Data[1,,] - if (is.null(ref.pred)) {xx.pred <- xx} else {xx.pred <- ref.pred$Data[1,,]} + if (is.null(ref.pred)) {xx.pred <- xx} else {xx.pred <- redim(ref.pred, loc = loc)$Data[1,,]} } frec <- apply(X = xx.obs, MARGIN = 2, function(X) { @@ -71,9 +72,9 @@ binaryGrid <- function(x, condition = "GE", threshold = 1, partial = FALSE, ref. } else { if (isRegular(x)) { - xx <- suppressWarnings(array3Dto2Dmat(subsetGrid(x,members = 1)$Data)) + xx <- suppressWarnings(array3Dto2Dmat(subsetGrid(x,members = j)$Data)) } else { - xx <- subsetGrid(x,members = 1)$Data + xx <- subsetGrid(x,members = j)$Data } xbin <- binaryGrid.(xx, condition = condition, threshold = threshold, partial = partial) } diff --git a/man/binaryGrid.Rd b/man/binaryGrid.Rd index 3590825..6755427 100644 --- a/man/binaryGrid.Rd +++ b/man/binaryGrid.Rd @@ -4,7 +4,7 @@ \alias{binaryGrid} \title{Convert grid values to a binary variable} \usage{ -binaryGrid(x, condition = "GE", threshold = 1, partial = FALSE, +binaryGrid(x, condition = "GE", threshold = NULL, partial = FALSE, ref.obs = NULL, ref.pred = NULL) } \arguments{ From 9391992117d6a64d557a07b5135d1193650dec37 Mon Sep 17 00:00:00 2001 From: "Jose M. Gutierrez" Date: Tue, 22 May 2018 12:14:53 +0200 Subject: [PATCH 06/15] Update README.md --- README.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/README.md b/README.md index d30ab23..65f5a09 100644 --- a/README.md +++ b/README.md @@ -14,6 +14,8 @@ devtools::install_github("SantanderMetGroup/transformeR") --- Reference and further information: +Iturbide et al. (2018) climate4R: An R-based Framework for Climate Data Access, Post-processing and Bias Correction. Submitted to **Environmental Modeling and Software***, http://www.meteo.unican.es/climate4r_paper + CofiƱo et al. (2018) The ECOMS User Data Gateway: Towards seasonal forecast data provision and research reproducibility in the era of Climate Services. **Climate Services**, http://dx.doi.org/10.1016/j.cliser.2017.07.001. From 041b1675fad12d49517e75f2ff80fb2915228bad Mon Sep 17 00:00:00 2001 From: Jorge Date: Fri, 25 May 2018 19:05:06 +0200 Subject: [PATCH 07/15] subset station (more than 1 simultaneously) --- R/subsetGrid.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/subsetGrid.R b/R/subsetGrid.R index 66b5af5..9e6b75a 100644 --- a/R/subsetGrid.R +++ b/R/subsetGrid.R @@ -495,7 +495,7 @@ subsetSeason <- function(grid, season = NULL) { subsetStation <- function(grid, station.id = NULL) { station0 <- grid$Metadata$station_id if (!all(station.id %in% station0)) stop("Station ID selection does not exist in the data") - id.ind <- which(station0 == station.id) + id.ind <- sapply(1:length(station.id),FUN = function(z) {which(station0 == station.id[z])}) grid %<>% subsetDimension(dimension = "loc", indices = id.ind) if ("Metadata" %in% names(grid)) { if ("station_id" %in% names(grid$Metadata)) grid$Metadata$station_id <- grid$Metadata$station_id[id.ind] From e1c79ea3589b843840a0dc6a39dd5e0f5786dba1 Mon Sep 17 00:00:00 2001 From: Your Name Date: Mon, 28 May 2018 17:32:50 +0200 Subject: [PATCH 08/15] add condition to isRegular --- R/helpers.R | 2 ++ 1 file changed, 2 insertions(+) diff --git a/R/helpers.R b/R/helpers.R index c7e471f..c3c2a43 100644 --- a/R/helpers.R +++ b/R/helpers.R @@ -567,6 +567,8 @@ isRegular <- function(grid) { y <- sort(gr$y) if (length(x) == 1 && length(y) == 1) { FALSE + } else if (attr(gr, "resX") == 0 && attr(gr, "resY") == 0) { + FALSE } else { xdists <- lapply(1:(length(x) - 1), function(l) { x[l + 1] - x[l] From f85bc1e702265f19ce1c0657fef211e43c10291d Mon Sep 17 00:00:00 2001 From: Your Name Date: Mon, 28 May 2018 17:52:21 +0200 Subject: [PATCH 09/15] transform conditions in isRegular --- R/helpers.R | 38 ++++++++++++++++++++++---------------- 1 file changed, 22 insertions(+), 16 deletions(-) diff --git a/R/helpers.R b/R/helpers.R index c3c2a43..4d01033 100644 --- a/R/helpers.R +++ b/R/helpers.R @@ -565,24 +565,30 @@ isRegular <- function(grid) { gr <- tryCatch({getGrid(grid)}, error = function(err) {grid}) x <- sort(gr$x) y <- sort(gr$y) - if (length(x) == 1 && length(y) == 1) { - FALSE - } else if (attr(gr, "resX") == 0 && attr(gr, "resY") == 0) { - FALSE + if (!is.null(attr(gr, "resX")) && !is.null(attr(gr, "resY"))) { + if (attr(gr, "resX") == 0 && attr(gr, "resY") == 0) { + FALSE + } else { + TRUE + } } else { - xdists <- lapply(1:(length(x) - 1), function(l) { - x[l + 1] - x[l] - }) - ydists <- lapply(1:(length(y) - 1), function(l) { - y[l + 1] - y[l] - }) - xa <- sum(unlist(xdists) - unlist(xdists)[1]) - ya <- sum(unlist(ydists) - unlist(ydists)[1]) - if (any(abs(c(xa, ya)) > 1e-05)) { - FALSE + if (length(x) == 1 && length(y) == 1) { + FALSE } else { - TRUE - } + xdists <- lapply(1:(length(x) - 1), function(l) { + x[l + 1] - x[l] + }) + ydists <- lapply(1:(length(y) - 1), function(l) { + y[l + 1] - y[l] + }) + xa <- sum(unlist(xdists) - unlist(xdists)[1]) + ya <- sum(unlist(ydists) - unlist(ydists)[1]) + if (any(abs(c(xa, ya)) > 1e-05)) { + FALSE + } else { + TRUE + } + } } } From 46f6c0b588abb21c86cff0d3f55b27f0a08d9ff6 Mon Sep 17 00:00:00 2001 From: Your Name Date: Thu, 31 May 2018 10:51:13 +0200 Subject: [PATCH 10/15] enhancement --- R/redim.R | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/R/redim.R b/R/redim.R index d3819cd..5a8c82f 100644 --- a/R/redim.R +++ b/R/redim.R @@ -54,7 +54,11 @@ redim <- function(grid, # grid$Data <- unname(abind(grid$Data, NULL, along = 2)) # attr(grid$Data, "dimensions") <- dimNames # } else - if (!"loc" %in% dimNames & getShape(grid)["lon"] == 1) { + if (!"loc" %in% dimNames & !"lon" %in% dimNames & !"lat" %in% dimNames) { + dimNames <- c("loc", dimNames) + grid$Data <- unname(abind(grid$Data, NULL, along = 0)) + attr(grid$Data, "dimensions") <- dimNames + } esle if (!"loc" %in% dimNames & getShape(grid)["lon"] == 1) { # recover loc dimension ind <- match("lat", dimNames) dimNames <- c(dimNames[-c(ind,ind + 1)], "loc") From aad1dd756ae94fdfdaac4fa669c0e101c49cab93 Mon Sep 17 00:00:00 2001 From: Your Name Date: Thu, 31 May 2018 12:45:43 +0200 Subject: [PATCH 11/15] enhancement --- R/redim.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/redim.R b/R/redim.R index 5a8c82f..00f5cc7 100644 --- a/R/redim.R +++ b/R/redim.R @@ -58,7 +58,7 @@ redim <- function(grid, dimNames <- c("loc", dimNames) grid$Data <- unname(abind(grid$Data, NULL, along = 0)) attr(grid$Data, "dimensions") <- dimNames - } esle if (!"loc" %in% dimNames & getShape(grid)["lon"] == 1) { + } else if (!"loc" %in% dimNames & getShape(grid)["lon"] == 1) { # recover loc dimension ind <- match("lat", dimNames) dimNames <- c(dimNames[-c(ind,ind + 1)], "loc") From 9b078826e8a9e215350ba70ca3e1c6a29b895ed8 Mon Sep 17 00:00:00 2001 From: Your Name Date: Thu, 31 May 2018 14:45:10 +0200 Subject: [PATCH 12/15] create function intersectGrid.spatial add helper isMultigrid --- R/helpers.R | 21 ++++++++++ R/intersectGrid.time.R | 87 +++++++++++++++++++++++++++++++++++++++++- 2 files changed, 106 insertions(+), 2 deletions(-) diff --git a/R/helpers.R b/R/helpers.R index 4d01033..94bec16 100644 --- a/R/helpers.R +++ b/R/helpers.R @@ -899,3 +899,24 @@ isGrid <- function(grid) { } } + +#' Check if object is a multigrid +#' +#' +#' @param grid Input object. +#' @return Logical. +#' @keywords internal +#' @export +#' @author M. Iturbide + +isMultigrid <- function(grid) { + if (is.list(grid)) { + if (all(c("Variable", "Data", "xyCoords", "Dates") %in% names(grid))) { + gridDepth(grid$Dates) > 1 + } else { + FALSE + } + } else { + FALSE + } +} diff --git a/R/intersectGrid.time.R b/R/intersectGrid.time.R index 51c6b14..a7427aa 100644 --- a/R/intersectGrid.time.R +++ b/R/intersectGrid.time.R @@ -1,4 +1,32 @@ +#' @title Intersection of multiple grids +#' @description Takes multiple input grids and crops the overlapping part along time dimension +#' @param ... Input grids +#' @param type Character. Options are "temporal" (default) or "spatial". +#' @param which.return Integer of the index to specify which grids in "..." are to be returned. +#' @return The grids indicated in \code{which.return}, encompassing the overlapping time period. +#' @author M Iturbide +#' @family subsetting +#' @seealso \code{\link{subsetGrid}} +#' @export +#' @example { +# data("EOBS_Iberia_tas") +# a <- subsetGrid(EOBS_Iberia_tas, lonLim = c(-8,-1), latLim = c(37, 40)) +# b <- subsetGrid(EOBS_Iberia_tas, lonLim = c(-4,3), latLim = c(39, 43)) +# z <- intersectGrid(a, b, type = "spatial", which.return = 1) +# } +intersectGrid <- function(..., type = c("temporal", "spatial"), which.return = 1) { + type <- match.arg(type, choices = c("temporal", "spatial")) + if (type == "temporal") { + outgrid <- intersectGrid.time(..., which.return = which.return) + } else if (type == "spatial") { + outgrid <- intersectGrid.spatial(..., which.return = which.return) + } else { + stop("Invalid option for argument 'type'.") + } + return(outgrid) +} + #' @title Temporal intersection of multiple grids #' @description Takes multiple input grids and crops the overlapping part along time dimension #' @param ... Input grids @@ -11,8 +39,8 @@ #' @export intersectGrid.time <- function(..., which.return = 1) { - grid.list <- (...) - if(length(grid.list) < length(which.return)) stop("Wrong value for argument which.return") + grid.list <- list(...) + if (length(grid.list) < length(which.return)) stop("Wrong value for argument which.return") ref.dates <- lapply(1:length(grid.list), function(x){ getRefDates(grid.list[[x]]) %>% as.Date(tz = "GMT", format = "%Y-%m-%d") }) @@ -32,3 +60,58 @@ intersectGrid.time <- function(..., which.return = 1) { if (length(out) == 1) out <- out[[1]] return(out) } + + + +#' @title Temporal intersection of multiple grids +#' @description Takes multiple input grids and crops the overlapping part along time longitude and latitude dimensions +#' @param ... Input grids +#' @param which.return Integer of the index to specify which grids in "..." are to be returned. +#' @return The grids indicated in \code{which.return}, encompassing the overlapping time period. +#' @importFrom magrittr %<>% %>% +#' @author M Iturbide +#' @family subsetting +#' @seealso \code{\link{checkDim}}, \code{\link{checkSeason}}, \code{\link{getYearsAsINDEX}}, \code{\link{getSeason}}, for other time dimension helpers +#' @export + +intersectGrid.spatial <- function(..., which.return = 1) { + grid.list <- list(...) + if (length(grid.list) < length(which.return)) stop("Wrong value for argument which.return") + # longitudes + ref.lons <- lapply(1:length(grid.list), function(x){ + getCoordinates(grid.list[[x]])$x + }) + auxLons <- ref.lons[[1]] + for (i in 2:length(grid.list)) { + auxLons <- intersect(auxLons, ref.lons[[i]]) + } + if (length(auxLons) == 0) { + message("Longitude intersection skipped. There are not intersecting longitudes") + } else { + ind <- lapply(ref.lons, function(x) which(is.element(x, auxLons))) + out <- lapply(1:length(grid.list), function(x) { + subsetDimension(grid.list[[x]], dimension = "lon", indices = ind[[x]]) + }) + grid.list <- out + } + #latitudes + ref.lats <- lapply(1:length(grid.list), function(x){ + getCoordinates(grid.list[[x]])$y + }) + auxLats <- ref.lats[[1]] + for (i in 2:length(grid.list)) { + auxLats <- intersect(auxLats, ref.lats[[i]]) + } + if (length(auxLats) == 0) { + message("Latitude intersection skipped. There are not intersecting latitudes") + out <- grid.list + } else { + ind <- lapply(ref.lats, function(x) which(is.element(x, auxLats))) + out <- lapply(1:length(grid.list), function(x) { + subsetDimension(grid.list[[x]], dimension = "lat", indices = ind[[x]]) + }) + } + out <- out[which.return] + if (length(out) == 1) out <- out[[1]] + return(out) +} From f939e15d27eada63d1b76ab65f134d6fb2451a56 Mon Sep 17 00:00:00 2001 From: Your Name Date: Thu, 31 May 2018 17:04:10 +0200 Subject: [PATCH 13/15] create function intersectGrid allow single grid in makeMultigrid --- NAMESPACE | 3 + R/intersectGrid.time.R | 2 +- R/makeMultiGrid.R | 177 ++++++++++++++++++--------------- man/getTemporalIntersection.Rd | 4 +- man/intersectGrid.Rd | 36 +++++++ man/intersectGrid.spatial.Rd | 34 +++++++ man/intersectGrid.time.Rd | 2 + man/isMultigrid.Rd | 21 ++++ man/subsetDimension.Rd | 10 +- man/subsetGrid.Rd | 2 + man/subsetMembers.Rd | 2 + man/subsetRuntime.Rd | 2 + man/subsetSeason.Rd | 2 + man/subsetSpatial.Rd | 2 + man/subsetStation.Rd | 2 + man/subsetVar.Rd | 2 + man/subsetYears.Rd | 2 + 17 files changed, 220 insertions(+), 85 deletions(-) create mode 100644 man/intersectGrid.Rd create mode 100644 man/intersectGrid.spatial.Rd create mode 100644 man/isMultigrid.Rd diff --git a/NAMESPACE b/NAMESPACE index 44a6e17..edd7592 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -42,8 +42,11 @@ export(gridArithmetics) export(gridDepth) export(gridFromPCA) export(interpGrid) +export(intersectGrid) +export(intersectGrid.spatial) export(intersectGrid.time) export(isGrid) +export(isMultigrid) export(isRegular) export(localScaling) export(makeMultiGrid) diff --git a/R/intersectGrid.time.R b/R/intersectGrid.time.R index a7427aa..ed45ec9 100644 --- a/R/intersectGrid.time.R +++ b/R/intersectGrid.time.R @@ -1,5 +1,5 @@ #' @title Intersection of multiple grids -#' @description Takes multiple input grids and crops the overlapping part along time dimension +#' @description Takes multiple input grids and crops the overlapping part #' @param ... Input grids #' @param type Character. Options are "temporal" (default) or "spatial". #' @param which.return Integer of the index to specify which grids in "..." are to be returned. diff --git a/R/makeMultiGrid.R b/R/makeMultiGrid.R index 8e26b53..5aad2a2 100644 --- a/R/makeMultiGrid.R +++ b/R/makeMultiGrid.R @@ -93,85 +93,104 @@ #' # plotClimatology(climatology(tas), backdrop.theme = "coastline" makeMultiGrid <- function(..., spatial.tolerance = 1e-3, skip.temporal.check = FALSE) { - field.list <- list(...) - stopifnot(is.logical(skip.temporal.check)) - if (length(field.list) == 1) { - field.list <- unlist(field.list, recursive = FALSE) - } - if (length(field.list) < 2) { - stop("The input must be a list of at least two grids", call. = FALSE) - } - ## Climatologies ---------- - climfun <- attr(field.list[[1]]$Data, "climatology:fun") - field.list <- lapply(1:length(field.list), function(x) redim(field.list[[x]], drop = TRUE)) - field.list <- lapply(1:length(field.list), function(x) redim(field.list[[x]], var = TRUE)) - ### check var dimension position - varind <- unique(lapply(1:length(field.list), function(x) which(getDim(field.list[[x]]) == "var"))) - if (length(varind) > 1) stop("Input grids have different dimensions")#hay que discutir esto - varind <- unlist(varind) - ### - tol <- spatial.tolerance - for (i in 2:length(field.list)) { - # Spatial test - if (!all.equal(field.list[[1]]$xyCoords, field.list[[i]]$xyCoords, - check.attributes = FALSE, tolerance = tol)) { - stop("Input data are not spatially consistent") - } - # temporal test - if (!skip.temporal.check) { - if (!identical(as.POSIXlt(field.list[[1]]$Dates$start)$yday, - as.POSIXlt(field.list[[i]]$Dates$start)$yday) | !identical(as.POSIXlt(field.list[[1]]$Dates$start)$year, - as.POSIXlt(field.list[[i]]$Dates$start)$year)) { - stop("Input data are not temporally consistent.\nMaybe the 'skip.temporal.check' argument should be set to TRUE?") - } - } - # data dimensionality - suppressMessages(checkDim(field.list[[1]], field.list[[i]])) - } - # Atributos de la variable ---------------- - # Lista de todos los atributos de todos los grids, menos el primero ('names') - aux.attr.list <- lapply(1:length(field.list), function(x) attributes(field.list[[x]]$Variable)) - auxl <- lapply(1:length(aux.attr.list), function(x) names(aux.attr.list[[x]])) - all.attrs <- Reduce(union, auxl)[-1] - aux.attr.list <- NULL - l <- vector("list", length(all.attrs)) - names(l) <- all.attrs - for (i in 1:length(field.list)) { - attrnames <- names(attributes(field.list[[i]]$Variable))[-1] - for (j in 1:length(all.attrs)) { - atributo.ind <- unlist(lapply(attrnames, function(x) identical(x, all.attrs[j]))) - atributo <- attrnames[atributo.ind] - if (length(atributo) != 0) { - expr <- attr(field.list[[i]]$Variable, which = atributo) - tryCatch({l[[j]][(length(l[[j]]) + 1):((length(l[[j]])) + length(atributo))] <- - deparse(expr)}, error = function(err){deparse(expr)}) + field.list <- list(...) + stopifnot(is.logical(skip.temporal.check)) + checkgrid <- unlist(lapply(field.list, function(x) isGrid(x))) + if (any(!checkgrid)) { + field.list <- unlist(field.list, recursive = FALSE) + checkgrid <- unlist(lapply(field.list, function(x) isGrid(x))) + } + if (any(!checkgrid)) { + stop("Input data is not valid in '...'") + } else { + climfun <- attr(field.list[[1]]$Data, "climatology:fun") + if (length(checkgrid) == 1) { + warning("The input is a single grid") + field.list[[1]]$Dates <- list(field.list[[1]]$Dates) } else { - l[[j]][(length(l[[j]]) + 1):((length(l[[j]])) + length(atributo))] <- NA + # + # if (length(field.list) == 1) { + # field.list <- unlist(field.list, recursive = FALSE) + # } + # if (length(field.list) < 2) { + # stop("The input must be a list of at least two grids", call. = FALSE) + # } + ## Climatologies ---------- + field.list <- lapply(1:length(field.list), function(x) redim(field.list[[x]], drop = TRUE)) + field.list <- lapply(1:length(field.list), function(x) redim(field.list[[x]], var = TRUE)) + ### check var dimension position + varind <- unique(lapply(1:length(field.list), function(x) which(getDim(field.list[[x]]) == "var"))) + if (length(varind) > 1) stop("Input grids have different dimensions")#hay que discutir esto + varind <- unlist(varind) + ### + tol <- spatial.tolerance + for (i in 2:length(field.list)) { + # Spatial test + + + + if (!all.equal(field.list[[1]]$xyCoords, field.list[[i]]$xyCoords, + check.attributes = FALSE, tolerance = tol)) { + stop("Input data are not spatially consistent") + } + # temporal test + if (!skip.temporal.check) { + if (!identical(as.POSIXlt(field.list[[1]]$Dates$start)$yday, + as.POSIXlt(field.list[[i]]$Dates$start)$yday) | !identical(as.POSIXlt(field.list[[1]]$Dates$start)$year, + as.POSIXlt(field.list[[i]]$Dates$start)$year)) { + stop("Input data are not temporally consistent.\nMaybe the 'skip.temporal.check' argument should be set to TRUE?") + } + } + # data dimensionality + suppressMessages(checkDim(field.list[[1]], field.list[[i]])) + } + # Atributos de la variable ---------------- + # Lista de todos los atributos de todos los grids, menos el primero ('names') + aux.attr.list <- lapply(1:length(field.list), function(x) attributes(field.list[[x]]$Variable)) + auxl <- lapply(1:length(aux.attr.list), function(x) names(aux.attr.list[[x]])) + all.attrs <- Reduce(union, auxl)[-1] + aux.attr.list <- NULL + l <- vector("list", length(all.attrs)) + names(l) <- all.attrs + for (i in 1:length(field.list)) { + attrnames <- names(attributes(field.list[[i]]$Variable))[-1] + for (j in 1:length(all.attrs)) { + atributo.ind <- unlist(lapply(attrnames, function(x) identical(x, all.attrs[j]))) + atributo <- attrnames[atributo.ind] + if (length(atributo) != 0) { + expr <- attr(field.list[[i]]$Variable, which = atributo) + tryCatch({l[[j]][(length(l[[j]]) + 1):((length(l[[j]])) + length(atributo))] <- + deparse(expr)}, error = function(err){deparse(expr)}) + } else { + l[[j]][(length(l[[j]]) + 1):((length(l[[j]])) + length(atributo))] <- NA + } + } + } + # varName and levels + levs <- unname(sapply(field.list, "getGridVerticalLevels")) + varnames <- sapply(field.list, "getVarNames") + for (i in 1:length(varnames)) { + if (!is.na(levs[i])) varnames[i] <- paste(varnames[i], levs[i], sep = "@") + } + attributes(field.list[[1]]$Variable) <- l + names(field.list[[1]]$Variable) <- c("varName","level") + field.list[[1]]$Variable[["varName"]] <- varnames + field.list[[1]]$Variable[["level"]] <- levs + ## $Dates ------------------- + field.list[[1]]$Dates <- lapply(1:length(field.list), function(x) field.list[[x]]$Dates) + ## Select larger string of dim names ------------- + dimNames <- lapply(1:length(field.list), function(x) getDim(field.list[[x]])) + dimNames <- dimNames[[which(lengths(dimNames) == max(lengths(dimNames)))[1]]] + ## Bind data ---------- + field.list[[1]]$Data <- unname(do.call("abind", + c(lapply(1:length(field.list), + function(x) field.list[[x]]$Data), + along = varind))) + attr(field.list[[1]]$Data, "dimensions") <- dimNames } - } - } - # varName and levels - levs <- unname(sapply(field.list, "getGridVerticalLevels")) - varnames <- sapply(field.list, "getVarNames") - for (i in 1:length(varnames)) { - if (!is.na(levs[i])) varnames[i] <- paste(varnames[i], levs[i], sep = "@") - } - attributes(field.list[[1]]$Variable) <- l - names(field.list[[1]]$Variable) <- c("varName","level") - field.list[[1]]$Variable[["varName"]] <- varnames - field.list[[1]]$Variable[["level"]] <- levs - ## $Dates ------------------- - field.list[[1]]$Dates <- lapply(1:length(field.list), function(x) field.list[[x]]$Dates) - ## Select larger string of dim names ------------- - dimNames <- lapply(1:length(field.list), function(x) getDim(field.list[[x]])) - dimNames <- dimNames[[which(lengths(dimNames) == max(lengths(dimNames)))[1]]] - ## Bind data ---------- - field.list[[1]]$Data <- unname(do.call("abind", - c(lapply(1:length(field.list), - function(x) field.list[[x]]$Data), - along = varind))) - attr(field.list[[1]]$Data, "dimensions") <- dimNames - if (!is.null(climfun)) attr(field.list[[1]]$Data, "climatology:fun") <- climfun - return(field.list[[1]]) + if (!is.null(climfun)) attr(field.list[[1]]$Data, "climatology:fun") <- climfun + return(field.list[[1]]) + } } -# End + # End + \ No newline at end of file diff --git a/man/getTemporalIntersection.Rd b/man/getTemporalIntersection.Rd index 0907565..e03292e 100644 --- a/man/getTemporalIntersection.Rd +++ b/man/getTemporalIntersection.Rd @@ -46,7 +46,9 @@ checkDim(predictor.adj, predictand.adj, dimensions = "time") # perfect \seealso{ \code{\link{checkDim}}, \code{\link{checkSeason}}, \code{\link{getYearsAsINDEX}}, \code{\link{getSeason}}, for other time dimension helpers -Other subsetting: \code{\link{intersectGrid.time}}, +Other subsetting: \code{\link{intersectGrid.spatial}}, + \code{\link{intersectGrid.time}}, + \code{\link{intersectGrid}}, \code{\link{subsetDimension}}, \code{\link{subsetGrid}}, \code{\link{subsetMembers}}, \code{\link{subsetRuntime}}, \code{\link{subsetSeason}}, \code{\link{subsetSpatial}}, diff --git a/man/intersectGrid.Rd b/man/intersectGrid.Rd new file mode 100644 index 0000000..b28efb3 --- /dev/null +++ b/man/intersectGrid.Rd @@ -0,0 +1,36 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/intersectGrid.time.R +\name{intersectGrid} +\alias{intersectGrid} +\title{Intersection of multiple grids} +\usage{ +intersectGrid(..., type = c("temporal", "spatial"), which.return = 1) +} +\arguments{ +\item{...}{Input grids} + +\item{type}{Character. Options are "temporal" (default) or "spatial".} + +\item{which.return}{Integer of the index to specify which grids in "..." are to be returned.} +} +\value{ +The grids indicated in \code{which.return}, encompassing the overlapping time period. +} +\description{ +Takes multiple input grids and crops the overlapping part +} +\seealso{ +\code{\link{subsetGrid}} + +Other subsetting: \code{\link{getTemporalIntersection}}, + \code{\link{intersectGrid.spatial}}, + \code{\link{intersectGrid.time}}, + \code{\link{subsetDimension}}, \code{\link{subsetGrid}}, + \code{\link{subsetMembers}}, \code{\link{subsetRuntime}}, + \code{\link{subsetSeason}}, \code{\link{subsetSpatial}}, + \code{\link{subsetStation}}, \code{\link{subsetVar}}, + \code{\link{subsetYears}} +} +\author{ +M Iturbide +} diff --git a/man/intersectGrid.spatial.Rd b/man/intersectGrid.spatial.Rd new file mode 100644 index 0000000..466cbe8 --- /dev/null +++ b/man/intersectGrid.spatial.Rd @@ -0,0 +1,34 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/intersectGrid.time.R +\name{intersectGrid.spatial} +\alias{intersectGrid.spatial} +\title{Temporal intersection of multiple grids} +\usage{ +intersectGrid.spatial(..., which.return = 1) +} +\arguments{ +\item{...}{Input grids} + +\item{which.return}{Integer of the index to specify which grids in "..." are to be returned.} +} +\value{ +The grids indicated in \code{which.return}, encompassing the overlapping time period. +} +\description{ +Takes multiple input grids and crops the overlapping part along time longitude and latitude dimensions +} +\seealso{ +\code{\link{checkDim}}, \code{\link{checkSeason}}, \code{\link{getYearsAsINDEX}}, \code{\link{getSeason}}, for other time dimension helpers + +Other subsetting: \code{\link{getTemporalIntersection}}, + \code{\link{intersectGrid.time}}, + \code{\link{intersectGrid}}, + \code{\link{subsetDimension}}, \code{\link{subsetGrid}}, + \code{\link{subsetMembers}}, \code{\link{subsetRuntime}}, + \code{\link{subsetSeason}}, \code{\link{subsetSpatial}}, + \code{\link{subsetStation}}, \code{\link{subsetVar}}, + \code{\link{subsetYears}} +} +\author{ +M Iturbide +} diff --git a/man/intersectGrid.time.Rd b/man/intersectGrid.time.Rd index 7bc9161..f07d434 100644 --- a/man/intersectGrid.time.Rd +++ b/man/intersectGrid.time.Rd @@ -21,6 +21,8 @@ Takes multiple input grids and crops the overlapping part along time dimension \code{\link{checkDim}}, \code{\link{checkSeason}}, \code{\link{getYearsAsINDEX}}, \code{\link{getSeason}}, for other time dimension helpers Other subsetting: \code{\link{getTemporalIntersection}}, + \code{\link{intersectGrid.spatial}}, + \code{\link{intersectGrid}}, \code{\link{subsetDimension}}, \code{\link{subsetGrid}}, \code{\link{subsetMembers}}, \code{\link{subsetRuntime}}, \code{\link{subsetSeason}}, \code{\link{subsetSpatial}}, diff --git a/man/isMultigrid.Rd b/man/isMultigrid.Rd new file mode 100644 index 0000000..8a88172 --- /dev/null +++ b/man/isMultigrid.Rd @@ -0,0 +1,21 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/helpers.R +\name{isMultigrid} +\alias{isMultigrid} +\title{Check if object is a multigrid} +\usage{ +isMultigrid(grid) +} +\arguments{ +\item{grid}{Input object.} +} +\value{ +Logical. +} +\description{ +Check if object is a multigrid +} +\author{ +M. Iturbide +} +\keyword{internal} diff --git a/man/subsetDimension.Rd b/man/subsetDimension.Rd index d22da0b..e39d55a 100644 --- a/man/subsetDimension.Rd +++ b/man/subsetDimension.Rd @@ -38,11 +38,13 @@ plotClimatology(climatology(sub), backdrop.theme = "coastline") } \seealso{ Other subsetting: \code{\link{getTemporalIntersection}}, + \code{\link{intersectGrid.spatial}}, \code{\link{intersectGrid.time}}, - \code{\link{subsetGrid}}, \code{\link{subsetMembers}}, - \code{\link{subsetRuntime}}, \code{\link{subsetSeason}}, - \code{\link{subsetSpatial}}, \code{\link{subsetStation}}, - \code{\link{subsetVar}}, \code{\link{subsetYears}} + \code{\link{intersectGrid}}, \code{\link{subsetGrid}}, + \code{\link{subsetMembers}}, \code{\link{subsetRuntime}}, + \code{\link{subsetSeason}}, \code{\link{subsetSpatial}}, + \code{\link{subsetStation}}, \code{\link{subsetVar}}, + \code{\link{subsetYears}} } \author{ J. Bedia and S. Herrera diff --git a/man/subsetGrid.Rd b/man/subsetGrid.Rd index 2473a62..ddb388c 100644 --- a/man/subsetGrid.Rd +++ b/man/subsetGrid.Rd @@ -100,7 +100,9 @@ getVarNames(sub2) } \seealso{ Other subsetting: \code{\link{getTemporalIntersection}}, + \code{\link{intersectGrid.spatial}}, \code{\link{intersectGrid.time}}, + \code{\link{intersectGrid}}, \code{\link{subsetDimension}}, \code{\link{subsetMembers}}, \code{\link{subsetRuntime}}, \code{\link{subsetSeason}}, \code{\link{subsetSpatial}}, diff --git a/man/subsetMembers.Rd b/man/subsetMembers.Rd index 137316a..528d613 100644 --- a/man/subsetMembers.Rd +++ b/man/subsetMembers.Rd @@ -25,7 +25,9 @@ An attribute 'subset' with value 'subsetMembers' is added to the Members slot of } \seealso{ Other subsetting: \code{\link{getTemporalIntersection}}, + \code{\link{intersectGrid.spatial}}, \code{\link{intersectGrid.time}}, + \code{\link{intersectGrid}}, \code{\link{subsetDimension}}, \code{\link{subsetGrid}}, \code{\link{subsetRuntime}}, \code{\link{subsetSeason}}, \code{\link{subsetSpatial}}, \code{\link{subsetStation}}, diff --git a/man/subsetRuntime.Rd b/man/subsetRuntime.Rd index 192eb8b..b6c13d3 100644 --- a/man/subsetRuntime.Rd +++ b/man/subsetRuntime.Rd @@ -23,7 +23,9 @@ An attribute 'subset' with value 'subsetRuntime' is added to the Runtime slot of } \seealso{ Other subsetting: \code{\link{getTemporalIntersection}}, + \code{\link{intersectGrid.spatial}}, \code{\link{intersectGrid.time}}, + \code{\link{intersectGrid}}, \code{\link{subsetDimension}}, \code{\link{subsetGrid}}, \code{\link{subsetMembers}}, \code{\link{subsetSeason}}, \code{\link{subsetSpatial}}, \code{\link{subsetStation}}, diff --git a/man/subsetSeason.Rd b/man/subsetSeason.Rd index d4e6dfe..3219229 100644 --- a/man/subsetSeason.Rd +++ b/man/subsetSeason.Rd @@ -23,7 +23,9 @@ An attribute 'subset' with value 'time' is added to the Variable slot of the out } \seealso{ Other subsetting: \code{\link{getTemporalIntersection}}, + \code{\link{intersectGrid.spatial}}, \code{\link{intersectGrid.time}}, + \code{\link{intersectGrid}}, \code{\link{subsetDimension}}, \code{\link{subsetGrid}}, \code{\link{subsetMembers}}, \code{\link{subsetRuntime}}, \code{\link{subsetSpatial}}, \code{\link{subsetStation}}, diff --git a/man/subsetSpatial.Rd b/man/subsetSpatial.Rd index 8a9f119..1662986 100644 --- a/man/subsetSpatial.Rd +++ b/man/subsetSpatial.Rd @@ -31,7 +31,9 @@ component of the output grid. } \seealso{ Other subsetting: \code{\link{getTemporalIntersection}}, + \code{\link{intersectGrid.spatial}}, \code{\link{intersectGrid.time}}, + \code{\link{intersectGrid}}, \code{\link{subsetDimension}}, \code{\link{subsetGrid}}, \code{\link{subsetMembers}}, \code{\link{subsetRuntime}}, \code{\link{subsetSeason}}, \code{\link{subsetStation}}, diff --git a/man/subsetStation.Rd b/man/subsetStation.Rd index a26702e..c83fb13 100644 --- a/man/subsetStation.Rd +++ b/man/subsetStation.Rd @@ -23,7 +23,9 @@ An attribute 'subset' with value 'time' is added to the Variable slot of the out } \seealso{ Other subsetting: \code{\link{getTemporalIntersection}}, + \code{\link{intersectGrid.spatial}}, \code{\link{intersectGrid.time}}, + \code{\link{intersectGrid}}, \code{\link{subsetDimension}}, \code{\link{subsetGrid}}, \code{\link{subsetMembers}}, \code{\link{subsetRuntime}}, \code{\link{subsetSeason}}, \code{\link{subsetSpatial}}, diff --git a/man/subsetVar.Rd b/man/subsetVar.Rd index 34b89fc..7cb5975 100644 --- a/man/subsetVar.Rd +++ b/man/subsetVar.Rd @@ -28,7 +28,9 @@ An attribute 'subset' with value 'subsetVar' is added to the Variable slot of th } \seealso{ Other subsetting: \code{\link{getTemporalIntersection}}, + \code{\link{intersectGrid.spatial}}, \code{\link{intersectGrid.time}}, + \code{\link{intersectGrid}}, \code{\link{subsetDimension}}, \code{\link{subsetGrid}}, \code{\link{subsetMembers}}, \code{\link{subsetRuntime}}, \code{\link{subsetSeason}}, \code{\link{subsetSpatial}}, diff --git a/man/subsetYears.Rd b/man/subsetYears.Rd index a89e366..8c05e98 100644 --- a/man/subsetYears.Rd +++ b/man/subsetYears.Rd @@ -23,7 +23,9 @@ An attribute 'subset' with value 'subsetYears' is added to the Dates slot of the } \seealso{ Other subsetting: \code{\link{getTemporalIntersection}}, + \code{\link{intersectGrid.spatial}}, \code{\link{intersectGrid.time}}, + \code{\link{intersectGrid}}, \code{\link{subsetDimension}}, \code{\link{subsetGrid}}, \code{\link{subsetMembers}}, \code{\link{subsetRuntime}}, \code{\link{subsetSeason}}, \code{\link{subsetSpatial}}, From 90c5fe7548f708a33b253ff916aaf5eeaf189895 Mon Sep 17 00:00:00 2001 From: Your Name Date: Thu, 31 May 2018 17:05:25 +0200 Subject: [PATCH 14/15] rename .R file for intersectGrid --- R/{intersectGrid.time.R => intersectGrid.R} | 0 1 file changed, 0 insertions(+), 0 deletions(-) rename R/{intersectGrid.time.R => intersectGrid.R} (100%) diff --git a/R/intersectGrid.time.R b/R/intersectGrid.R similarity index 100% rename from R/intersectGrid.time.R rename to R/intersectGrid.R From 321caf1981c54d06d5706e9c54b8c73d3e5bdbd0 Mon Sep 17 00:00:00 2001 From: Your Name Date: Thu, 31 May 2018 17:32:50 +0200 Subject: [PATCH 15/15] update documentation --- man/intersectGrid.Rd | 2 +- man/intersectGrid.spatial.Rd | 2 +- man/intersectGrid.time.Rd | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/man/intersectGrid.Rd b/man/intersectGrid.Rd index b28efb3..cb3c24c 100644 --- a/man/intersectGrid.Rd +++ b/man/intersectGrid.Rd @@ -1,5 +1,5 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/intersectGrid.time.R +% Please edit documentation in R/intersectGrid.R \name{intersectGrid} \alias{intersectGrid} \title{Intersection of multiple grids} diff --git a/man/intersectGrid.spatial.Rd b/man/intersectGrid.spatial.Rd index 466cbe8..3234ed4 100644 --- a/man/intersectGrid.spatial.Rd +++ b/man/intersectGrid.spatial.Rd @@ -1,5 +1,5 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/intersectGrid.time.R +% Please edit documentation in R/intersectGrid.R \name{intersectGrid.spatial} \alias{intersectGrid.spatial} \title{Temporal intersection of multiple grids} diff --git a/man/intersectGrid.time.Rd b/man/intersectGrid.time.Rd index f07d434..f34ade2 100644 --- a/man/intersectGrid.time.Rd +++ b/man/intersectGrid.time.Rd @@ -1,5 +1,5 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/intersectGrid.time.R +% Please edit documentation in R/intersectGrid.R \name{intersectGrid.time} \alias{intersectGrid.time} \title{Temporal intersection of multiple grids}