diff --git a/R/CST_Anomaly.R b/R/CST_Anomaly.R index c93267413c41aa336280715f389d0c540ec1e82b..205c2c600975442cf6d419faef61ef364e1254e4 100644 --- a/R/CST_Anomaly.R +++ b/R/CST_Anomaly.R @@ -9,10 +9,10 @@ #'computation is carried out independently for experimental and observational #'data products. #' -#'@param exp An object of class \code{s2dv_cube} as returned by \code{CST_Load} +#'@param exp An object of class \code{s2dv_cube} as returned by \code{CST_Start} #' function, containing the seasonal forecast experiment data in the element #' named \code{$data}. -#'@param obs An object of class \code{s2dv_cube} as returned by \code{CST_Load} +#'@param obs An object of class \code{s2dv_cube} as returned by \code{CST_Start} #' function, containing the observed data in the element named \code{$data}. #'@param dim_anom A character string indicating the name of the dimension #' along which the climatology will be computed. The default value is 'sdate'. @@ -91,13 +91,10 @@ CST_Anomaly <- function(exp = NULL, obs = NULL, dim_anom = 'sdate', any(is.null(names(dim(obs$data))))| any(nchar(names(dim(obs$data))) == 0)) { stop("Parameter 'exp' and 'obs' must have dimension names in element 'data'.") } - if (!all(names(dim(exp$data)) %in% names(dim(obs$data))) | - !all(names(dim(obs$data)) %in% names(dim(exp$data)))) { - stop("Parameter 'exp' and 'obs' must have same dimension names in element 'data'.") - } dim_exp <- dim(exp$data) dim_obs <- dim(obs$data) - dimnames_data <- names(dim_exp) + dimnames_exp <- names(dim_exp) + dimnames_obs <- names(dim_obs) # dim_anom if (!is.character(dim_anom)) { stop("Parameter 'dim_anom' must be a character string.") @@ -129,19 +126,12 @@ CST_Anomaly <- function(exp = NULL, obs = NULL, dim_anom = 'sdate', if (!is.character(memb_dim) | length(memb_dim) > 1) { stop("Parameter 'memb_dim' must be a character string.") } - if (!memb_dim %in% names(dim_exp) | !memb_dim %in% names(dim_obs)) { - stop("Parameter 'memb_dim' is not found in 'exp' or in 'obs' dimension.") - } } # dat_dim if (!is.null(dat_dim)) { if (!is.character(dat_dim)) { stop("Parameter 'dat_dim' must be a character vector.") } - if (!all(dat_dim %in% names(dim_exp)) | !all(dat_dim %in% names(dim_obs))) { - stop("Parameter 'dat_dim' is not found in 'exp' or 'obs' dimension in element 'data'. ", - "Set it as NULL if there is no dataset dimension.") - } } # filter_span if (!is.null(filter_span)) { @@ -161,7 +151,7 @@ CST_Anomaly <- function(exp = NULL, obs = NULL, dim_anom = 'sdate', if (!is.character(ftime_dim)) { stop("Parameter 'ftime_dim' must be a character string.") } - if (!ftime_dim %in% names(dim_exp) | !memb_dim %in% names(dim_obs)) { + if (!ftime_dim %in% names(dim_exp) | !ftime_dim %in% names(dim_obs)) { stop("Parameter 'ftime_dim' is not found in 'exp' or in 'obs' dimension in element 'data'.") } } @@ -206,15 +196,17 @@ CST_Anomaly <- function(exp = NULL, obs = NULL, dim_anom = 'sdate', ano <- NULL # Permuting back dimensions to original order - clim_exp <- Reorder(clim_exp, dimnames_data) - clim_obs <- Reorder(clim_obs, dimnames_data) + clim_exp <- Reorder(clim_exp, dimnames_exp) + clim_obs <- Reorder(clim_obs, dimnames_obs) ano$exp <- exp$data - clim_exp ano$obs <- obs$data - clim_obs } exp$data <- ano$exp + exp$dims <- dim(ano$exp) obs$data <- ano$obs + obs$dims <- dim(ano$obs) # Outputs # ~~~~~~~~~ diff --git a/man/CST_Anomaly.Rd b/man/CST_Anomaly.Rd index 5a2784e1dfb9387a4c5a4b70c56b9d44b55ccca8..8c037bfb12cab876d40d14a6671e8da3d96c45a0 100644 --- a/man/CST_Anomaly.Rd +++ b/man/CST_Anomaly.Rd @@ -19,11 +19,11 @@ CST_Anomaly( ) } \arguments{ -\item{exp}{An object of class \code{s2dv_cube} as returned by \code{CST_Load} +\item{exp}{An object of class \code{s2dv_cube} as returned by \code{CST_Start} function, containing the seasonal forecast experiment data in the element named \code{$data}.} -\item{obs}{An object of class \code{s2dv_cube} as returned by \code{CST_Load} +\item{obs}{An object of class \code{s2dv_cube} as returned by \code{CST_Start} function, containing the observed data in the element named \code{$data}.} \item{dim_anom}{A character string indicating the name of the dimension diff --git a/tests/testthat/test-CST_Anomaly.R b/tests/testthat/test-CST_Anomaly.R index 772352aa1e4280219b83f0dff812401731dceddb..69b548cbf6fcb95a70394dc5e6075c54c97352e3 100644 --- a/tests/testthat/test-CST_Anomaly.R +++ b/tests/testthat/test-CST_Anomaly.R @@ -58,7 +58,7 @@ test_that("1. Input checks", { ) expect_error( CST_Anomaly(exp = exp2, obs = obs), - "Parameter 'exp' and 'obs' must have same dimension names in element 'data'." + "Parameter 'dat_dim' is not found in 'exp' dimensions." ) # dim_anom expect_error( @@ -87,10 +87,6 @@ test_that("1. Input checks", { CST_Anomaly(exp = exp, obs = obs, memb_dim = 1), "Parameter 'memb_dim' must be a character string." ) - expect_error( - names(CST_Anomaly(exp4, obs4, dim_anom = 'sdates')), - "Parameter 'memb_dim' is not found in 'exp' or in 'obs' dimension." - ) # filter_span expect_warning( CST_Anomaly(exp = exp, obs = obs, filter_span = 'a'), @@ -98,8 +94,8 @@ test_that("1. Input checks", { ) # dat_dim expect_error( - names(CST_Anomaly(exp4, obs4, dim_anom = 'sdates', memb_dim = 'members')), - "Parameter 'dat_dim' is not found in 'exp' or 'obs' dimension in element 'data'. Set it as NULL if there is no dataset dimension." + CST_Anomaly(exp4, obs4, dim_anom = 'sdates', memb_dim = 'members', dat_dim = 1), + "Parameter 'dat_dim' must be a character vector." ) # ftime_dim expect_error(