diff --git a/NEWS.md b/NEWS.md index e50ff106d5cbd58460601d85fd0fccbc5adebb67..1352407ed748c3bd6d8843bb90b809cedda7023c 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ -# startR v0.1.5 (Release date:) +# startR v1.0.0 (Release date: 2020-03-23) - Bugfixes of lat and lon assigned by 'values' in Start(). In v0.1.4 it is incorrect when assigned from big to small values. +- Compatiblity break: Develop longitude and latitude reorder convention. +The reordering functions (i.e., Sort() and CircularSort()) are well-functioning now. + # startR v0.1.4 (Release date: 2020-02-10) - Bugfixes of transform in Start(). Change the default value of param 'extra_cells' to 2. (issue37) - Bugfixes of chunk function in Utils.R (issue23) diff --git a/R/SelectorChecker.R b/R/SelectorChecker.R index 141cae2178fb7c25f18d1171f470f4bf3cdc15ad..14bae7edc40ef2bb921567a0b932517a13594d78 100644 --- a/R/SelectorChecker.R +++ b/R/SelectorChecker.R @@ -52,7 +52,7 @@ SelectorChecker <- function(selectors, var = NULL, return_indices = TRUE, } } else if (is.numeric(selectors[[i]])) { if (is.numeric(var)) { - val <- selectors[[i]] + tol <- 0 if (!is.null(tolerance)) { if (!any(class(tolerance) %in% "numeric")) { @@ -60,28 +60,52 @@ SelectorChecker <- function(selectors, var = NULL, return_indices = TRUE, } tol <- tolerance } + + val <- selectors[[i]] + if (i == 1) { if (crescent_selectors) { val <- val - tol - selectors[[i]] <- which(var >= val)[1] + if (var[1] < var[2]) { + selectors[[i]] <- which(var >= val)[1] + } else if (var[1] > var[2]) { + selectors[[i]] <- rev(which(var >= val))[1] + } + } else { val <- val + tol - selectors[[i]] <- rev(which(var <= val))[1] + if (var[1] < var[2]) { + selectors[[i]] <- rev(which(var <= val))[1] + } else if (var[1] > var[2]) { + selectors[[i]] <- which(var <= val)[1] + } } } - else { + else if (i == 2) { if (crescent_selectors) { val <- val + tol - selectors[[i]] <- rev(which(var <= val))[1] + if (var[1] < var[2]) { + selectors[[i]] <- rev(which(var <= val))[1] + } else if (var[1] > var[2]) { + selectors[[i]] <- which(var <= val)[1] + } + } else { val <- val - tol - selectors[[i]] <- which(var >= val)[1] + if (var[1] < var[2]) { + selectors[[i]] <- which(var >= val)[1] + } else if (var[1] > var[2]) { + selectors[[i]] <- rev(which(var >= val))[1] + } } } + + } else { stop("Numeric selectors provided but possible values in 'var' are not numeric.") } } else if (any(c("POSIXct", "POSIXlt", "POSIXt", "Date") %in% class(selectors[[i]]))) { + # TODO: Here, change to as above (numeric part). if (any(c("POSIXct", "POSIXlt", "POSIXt", "Date") %in% class(var))) { val <- selectors[[i]] tol <- 0 @@ -114,6 +138,7 @@ SelectorChecker <- function(selectors, var = NULL, return_indices = TRUE, } } } + # The checker is returning a list of two indices. ##selectors[[1]]:selectors[[2]] selectors diff --git a/R/Start.R b/R/Start.R index c3422bbfdc32b13ae18304036a19c9c045604242..0076e9aa1236daa438573a94ccde57b93cab4fa5 100644 --- a/R/Start.R +++ b/R/Start.R @@ -1408,21 +1408,32 @@ debug <- TRUE picked_vars_to_transform <- names(picked_vars[[i]])[picked_vars_to_transform] new_vars_to_transform <- picked_vars[[i]][picked_vars_to_transform] which_are_ordered <- which(!sapply(picked_vars_ordered[[i]][picked_vars_to_transform], is.null)) + +##NOTE: The following 'if' replaces the original with reordering vector if (length(which_are_ordered) > 0) { - new_vars_to_transform[which_are_ordered] <- picked_vars_ordered[[i]][which_are_ordered] + tmp <- which(!is.na(match(names(picked_vars_ordered[[i]]), names(which_are_ordered)))) + new_vars_to_transform[which_are_ordered] <- picked_vars_ordered[[i]][tmp] + } vars_to_transform <- c(vars_to_transform, new_vars_to_transform) } + +##NOTE: Above is non-common vars, here is common vars (ie, return_vars = NULL). picked_common_vars_to_transform <- which(names(picked_common_vars) %in% transform_vars) if (length(picked_common_vars_to_transform) > 0) { picked_common_vars_to_transform <- names(picked_common_vars)[picked_common_vars_to_transform] - new_vars_to_transform <- picked_common_vars[[i]][picked_common_vars_to_transform] - which_are_ordered <- which(!sapply(picked_common_vars_ordered[[i]][picked_common_vars_to_transform], is.null)) + + new_vars_to_transform <- picked_common_vars[picked_common_vars_to_transform] + which_are_ordered <- which(!sapply(picked_common_vars_ordered[picked_common_vars_to_transform], is.null)) + if (length(which_are_ordered) > 0) { - new_vars_to_transform[which_are_ordered] <- picked_common_vars_ordered[[i]][which_are_ordered] + + tmp <- which(!is.na(match(names(picked_common_vars_ordered), names(which_are_ordered)))) + new_vars_to_transform[which_are_ordered] <- picked_common_vars_ordered[tmp] } vars_to_transform <- c(vars_to_transform, new_vars_to_transform) } + # Transform the variables transformed_data <- do.call(transform, c(list(data_array = NULL, variables = vars_to_transform, @@ -1955,33 +1966,120 @@ print("-> THE INNER DIMENSION DOES NOT GO ACROSS ANY FILE DIMENSION OR IT DOES B if (!is.null(var_ordered) && !selectors_are_indices) { if (!is.null(dim_reorder_params[[inner_dim]])) { if (is.list(sub_array_of_selectors)) { - sub_array_reordered <- dim_reorder_params[[inner_dim]](unlist(sub_array_of_selectors)) - sub_array_unorder <- sort(sub_array_reordered$ix, index.return = TRUE)$ix - sub_array_of_selectors <- as.list(sub_array_reordered$x[sub_array_unorder]) - is_circular_dim <- attr(dim_reorder_params[[inner_dim]], 'circular') - if (!is.null(is_circular_dim)) { - if (is_circular_dim) { - goes_across_prime_meridian <- abs(sub_array_of_selectors[[1]]) > abs(sub_array_of_selectors[[2]]) - ## TODO: if (bounds[1] > bounds[2]) goes_across_prime_meridian <- !goes_across_prime_meridian + +## NOTE: The check of 'goes_across_prime_meridian' is moved forward to here. + is_circular_dim <- attr(dim_reorder_params[[inner_dim]], "circular") + if (!is.null(is_circular_dim)) { + if (is_circular_dim) { + +# NOTE: Use CircularSort() to put the values in the assigned range, and get the order. +# For example, [-10, 20] in CircularSort(0, 360) is [350, 20]. The $ix list is [2, 1]. +# 'goes_across_prime_meridian' means the selector range across the border. For example, +# CircularSort(-180, 180) with selector [170, 190] -> goes_across_prime_meridian = TRUE. + tmp <- dim_reorder_params[[inner_dim]](unlist(sub_array_of_selectors))$ix + goes_across_prime_meridian <- tmp[1] > tmp[2] + } } - } + + # HERE change to the same code as below (under 'else'). Not sure why originally + #it uses additional lines, which make reorder not work. + sub_array_of_selectors <- as.list(dim_reorder_params[[inner_dim]](unlist(sub_array_of_selectors))$x) + #sub_array_reordered <- dim_reorder_params[[inner_dim]](unlist(sub_array_of_selectors)) + #sub_array_unorder <- sort(sub_array_reordered$ix, index.return = TRUE)$ix + #sub_array_of_selectors <- as.list(sub_array_reordered$x[sub_array_unorder]) + +# Add warning if the boundary is out of range + if (sub_array_of_selectors[1] < range(var_ordered)[1] | sub_array_of_selectors[1] > range(var_ordered)[2]) { + .warning(paste0("The lower boundary of selector of ", + inner_dim, + " is out of range [", + min(var_ordered), ", ", max(var_ordered), "]. ", + "Check if the desired range is all included.")) + } + if (sub_array_of_selectors[2] < range(var_ordered)[1] | sub_array_of_selectors[2] > range(var_ordered)[2]) { + .warning(paste0("The upper boundary of selector of ", + inner_dim, + " is out of range [", + min(var_ordered), ", ", max(var_ordered), "]. ", + "Check if the desired range is all included.")) + } + + } else { sub_array_of_selectors <- dim_reorder_params[[inner_dim]](sub_array_of_selectors)$x } } + +# NOTE: The ideal solution for selecting indices in goes_across_prime_meridian case +# is modified SelectorCheckor.R. But now SelectorCheckor doesn't know the info of +#goes_across_prime_meridian, so I do the adjustion after calling SelectorCheckor(). sub_array_of_indices <- selector_checker(sub_array_of_selectors, var_ordered, tolerance = if (aiat) { NULL } else { tolerance_params[[inner_dim]] }) + + if (goes_across_prime_meridian & sub_array_of_indices[[1]] < sub_array_of_indices[[2]]) { + if (!(sub_array_of_selectors[[1]] %in% var_ordered)){ + sub_array_of_indices[[1]] <- sub_array_of_indices[[1]] - 1 + } + + if (!(sub_array_of_selectors[[2]] %in% var_ordered)){ + sub_array_of_indices[[2]] <- sub_array_of_indices[[2]] + 1 + } + } + +#NOTE: the possible case? + if (goes_across_prime_meridian & sub_array_of_indices[[1]] > sub_array_of_indices[[2]]) { + .stop("The case is goes_across_prime_meridian but no adjustion for the indices!") + } + + if (any(is.na(sub_array_of_indices))) { + + stop(paste0("The selectors of ", inner_dim, + " are out of range [", min(var_ordered), + ", ", max(var_ordered), "].")) + } + } else { + +# Add warning if the boundary is out of range + if (is.list(sub_array_of_selectors)) { + if (sub_array_of_selectors[1] < + min(sub_array_of_values) | sub_array_of_selectors[1] > + max(sub_array_of_values)) { + .warning(paste0("The lower boundary of selector of ", + inner_dim, " is out of range [", + min(sub_array_of_values), ", ", + max(sub_array_of_values), "]. ", + "Check if the desired range is all included.")) + } + if (sub_array_of_selectors[2] < + min(sub_array_of_values) | sub_array_of_selectors[2] > + max(sub_array_of_values)) { + .warning(paste0("The upper boundary of selector of ", + inner_dim, " is out of range [", + min(sub_array_of_values), ", ", + max(sub_array_of_values), "]. ", + "Check if the desired range is all included.")) + } + } + sub_array_of_indices <- selector_checker(sub_array_of_selectors, sub_array_of_values, tolerance = if (aiat) { NULL } else { tolerance_params[[inner_dim]] }) + + if (any(is.na(sub_array_of_indices))) { + + stop(paste0("The selectors of ", inner_dim, + " are out of range [", min(sub_array_of_values), + ", ", max(sub_array_of_values), "].")) + } + } ## This 'if' runs in both Start() and Compute(). In Start(), it doesn't have any effect (no chunk). ## In Compute(), it creates the indices for each chunk. For example, if 'sub_array_of_indices' @@ -2038,8 +2136,16 @@ if (inner_dim %in% dims_to_check) { print("-> SELECTORS REQUESTED BEFORE TRANSFORM.") } } + +###NOTE: Here, the transform, is different from the below part of non-transform. +# search 'if (goes_across_prime_meridian' to find the lines below. if (goes_across_prime_meridian) { - sub_array_of_fri <- 1:n +# NOTE: before changing, the return is already correct. sub_array_of_fri is defined +# again afterward. Not sure if here is redundant. + sub_array_of_fri <- c(1:min(unlist(sub_array_of_indices)), + max(unlist(sub_array_of_indices)):n) + + #gap_width <- sub_array_of_indices[[1]] - sub_array_of_indices[[2]] - 1 #sub_array_of_fri <- c((1:(sub_array_of_indices[[2]] + min(gap_width, beta))), # (sub_array_of_indices[[1]] - min(gap_width, beta)):n) @@ -2049,24 +2155,46 @@ print("-> SELECTORS REQUESTED BEFORE TRANSFORM.") } first_index <- min(unlist(sub_array_of_indices)) last_index <- max(unlist(sub_array_of_indices)) - if (first_index - beta <= 0 | last_index + beta > n) { - sub_array_of_fri <- 1:n - .warning(paste0("Adding the parameter transform_extra_cells = ", - transform_extra_cells, " to the transformed index excesses ", - "the border. Use the whole index instead.")) - } else { - sub_array_of_fri <- (first_index - beta):(last_index + beta) - } - #start_padding <- min(beta, first_index - 1) - #end_padding <- min(beta, n - last_index) - #sub_array_of_fri <- (first_index - start_padding):(last_index + end_padding) + + start_padding <- min(beta, first_index - 1) + end_padding <- min(beta, n - last_index) + sub_array_of_fri <- (first_index - start_padding):(last_index + end_padding) + if (start_padding != beta | end_padding != beta) { + .warning(paste0("Adding parameter transform_extra_cells = ", + transform_extra_cells, " to the transformed index excesses ", + "the border. The border index is used for transformation.")) + } + } subset_vars_to_transform <- vars_to_transform if (!is.null(var_ordered)) { + +##NOTE: if var_ordered is common_vars, it doesn't have attributes and it is a vector. +## Turn it into array and add dimension name. + if (!is.array(var_ordered)) { + var_ordered <- as.array(var_ordered) + names(dim(var_ordered)) <- inner_dim + } + subset_vars_to_transform[[var_with_selectors_name]] <- Subset(var_ordered, inner_dim, sub_array_of_fri) } else { +##NOTE: It should be redundant because without reordering the var should remain array +## But just stay same with above... + if (!is.array(sub_array_of_values)) { + sub_array_of_values <- as.array(sub_array_of_values) + names(dim(sub_array_of_values)) <- inner_dim + } + subset_vars_to_transform[[var_with_selectors_name]] <- Subset(sub_array_of_values, inner_dim, sub_array_of_fri) } +## NOTE: Remove 'crop' from transform_params if no reorder. It causes error. +## But 'crop' has effect on reorder cases... need further investigation + if (is.null(dim_reorder_params[[inner_dim]])) { + if ('crop' %in% names(transform_params)) { + transform_params <- transform_params[-which(names(transform_params) == 'crop')] + } + } + transformed_subset_var <- do.call(transform, c(list(data_array = NULL, variables = subset_vars_to_transform, file_selectors = selectors_of_first_files_with_data[[i]]), @@ -2085,9 +2213,24 @@ print("-> SELECTORS REQUESTED BEFORE TRANSFORM.") } else { NULL }) + +# Check if selectors fall out of the range of the transform grid +# It may happen when original lon is [-180, 180] while want to regrid to +# [0, 360], and lon selector = [-20, -10]. + if (any(is.na(sub_array_of_sri))) { + stop(paste0("The selectors of ", + inner_dim, " are out of range of transform grid '", + transform_params$grid, "'. Use parameter '", + inner_dim, "_reorder' or change ", inner_dim, + " selectors.")) + } + if (goes_across_prime_meridian) { - sub_array_of_sri <- c(1:sub_array_of_sri[[2]], sub_array_of_sri[[1]]:length(transformed_subset_var)) - #sub_array_of_sri <- c(sub_array_of_sri[[1]]:length(transformed_subset_var), 1:sub_array_of_sri[[2]]) + # Because sub_array_of_sri order is exchanged due to + # previous development, here [[1]] and [[2]] should exchange + sub_array_of_sri <- c(1:sub_array_of_sri[[1]], + sub_array_of_sri[[2]]:length(transformed_subset_var)) + } else if (is.list(sub_array_of_sri)) { sub_array_of_sri <- sub_array_of_sri[[1]]:sub_array_of_sri[[2]] } @@ -2142,8 +2285,9 @@ print(str(tvi)) list(value = sub_array_of_sri))) } else { if (goes_across_prime_meridian) { - #sub_array_of_fri <- 1:n - sub_array_of_fri <- c(1:sub_array_of_indices[[2]], sub_array_of_indices[[1]]:n) + sub_array_of_fri <- c(1:min(unlist(sub_array_of_indices)), + max(unlist(sub_array_of_indices)):n) + } else if (is.list(sub_array_of_indices)) { sub_array_of_fri <- sub_array_of_indices[[1]]:sub_array_of_indices[[2]] } else { diff --git a/inst/doc/faq.md b/inst/doc/faq.md index 572bff8260a990ac035ae3c2d5d9f4d270c3041d..08c5d984c600fd298d669061e0f159e3d8b8e133 100644 --- a/inst/doc/faq.md +++ b/inst/doc/faq.md @@ -14,6 +14,8 @@ This document intends to be the first reference for any doubts that you may have 8. [Define a path with multiple dependencies](#8-define-a-path-with-multiple-dependencies) 9. [Use CDORemap() in function](#9-use-cdoremap-in-function) 10. [The number of members depends on the start date](#10-the-number-of-members-depends-on-the-start-date) + 11. [Select the longitude/latitude region](#11-select-the-longitudelatitude-region) + 12. [What will happen if reorder function is not used](#12-what-will-happen-if-reorder-function-is-not-used) 2. **Something goes wrong...** @@ -400,6 +402,43 @@ When trying to load both start dates at once using Start(), the order in which t The code to reproduce this behaviour could be found in the Use Cases section, [example 1.4](/inst/doc/usecase/ex1_4_variable_nmember.R). +### 11. Select the longitude/latitude region + +There are three ways to specify the dimension selectors: special keywords('all', 'first', 'last'), indices, or values (find more details in [pratical guide](inst/doc/practical_guide.md)). +The parameter 'xxx_reorder' is only effective when using **values**. + +There are two reorder functions in startR package, **Sort()** for latitude and **CircularSort()** for longitude. +Sort() is a wrapper function of base function sort(), rearranging the values from low to high (decreasing = TRUE, default) or +from high to low (decreasing = FALSE). For example, if you want to sort latitude from 90 to -90, use `latitude_reorder = Sort(decreasing = TRUE)`. +By this means, the result will always from big to small value no matter how the original order is. + +On the other hand, the concept of CircularSort() is different. It is used for a circular region, putting the out-of-region values back to the region. +It requires two input numbers defining the borders of the whole region, which are usually [0, 360] or [-180, 180]. For example, +`longitude_reorder = CircularSort(0, 360)` means that the left border is 0 and the right border is 360, so 360 will be put back to 0, 361 will be put back to 1, +and -1 will become 359. After circulating values, CircularSort() also sorts the values from small to big. It may cause the discontinous sub-region, +but the problem can be solved by assigning the borders correctly. + +The following chart helps you to decide how to use CircularSort() to get the desired region. +The first row represents the longitude border of the requested region, e.g., `values(list(lon.min, lon.max))`. +Note that this chart only provides the idea. The real numbers may slightly differ depending on the original/transform values. + + + +Find the usecases here [ex1_5_latlon_reorder.R](inst/doc/usecase/ex1_5_latlon_reorder.R) + +### 12. What will happen if reorder function is not used + +The reorder functions (i.e., Sort() and CircularSort()) are always recommended to adopt in Start() so you can ensure the result is in line +with your expectation (find more details at [how-to-11](#11-select-the-longitudelatitude-region) above). If the functions are not used, the situation will be more complicated and easier to +get unexpected results. + +Without reorder functions, the longitude and latitude selectors must be within the respective range in the original file, and the result order +will be the same order as how you request. If transformation is performed simultaneously, you need to consider the latitude/longitude range of +the transform grid too. The requested region values cannot fall out of both the original and the transformed region. + +The following chart shows some examples. + + ## Something goes wrong... diff --git a/inst/doc/figures/lon-2.PNG b/inst/doc/figures/lon-2.PNG new file mode 100644 index 0000000000000000000000000000000000000000..570151241b7b54a7fba28166cd7e75b64f0a6017 Binary files /dev/null and b/inst/doc/figures/lon-2.PNG differ diff --git a/inst/doc/figures/lon-3.PNG b/inst/doc/figures/lon-3.PNG new file mode 100644 index 0000000000000000000000000000000000000000..da29a4c4f6f49f9f34dc03aa6e1d9f81dafc03b4 Binary files /dev/null and b/inst/doc/figures/lon-3.PNG differ diff --git a/inst/doc/usecase.md b/inst/doc/usecase.md index fcaa7823d585a1237a447a81642d5cc3f2bc669a..1dac948604c43c034a50d36cbc88aadf1aeda3b5 100644 --- a/inst/doc/usecase.md +++ b/inst/doc/usecase.md @@ -22,6 +22,11 @@ In this document, you can link to the example scripts for various demands. For t 4. [Checking impact of start date order in the number of members](inst/doc/usecase/ex1_4_variable_nmember.R) Mixing start dates of different months can lead to load different number of members, check the code provided and the [FAQ 10](/inst/doc/faq.md). + 5. [Use reorder functions to get desired lat/lon region](inst/doc/usecase/ex1_5_latlon_reorder.R) + This script shows you how to use reorder function (`Sort()`, `CircularSort()`) to +get the desired longitude and latitude region. See [FAQ How-to-#11] (/inst/doc/faq.md#11-read-latitude-and-longitude-with-the-usage-of-parameter-xxx_reorder) +for more explanation. + 2. **Execute computation (use `Compute()`)** 1. [Function working on time dimension](inst/doc/usecase/ex2_1_timedim.R) diff --git a/inst/doc/usecase/ex1_5_latlon_reorder.R b/inst/doc/usecase/ex1_5_latlon_reorder.R new file mode 100644 index 0000000000000000000000000000000000000000..c54314f5f7a2da70c2d7f1672eb7cc1c3578ae6d --- /dev/null +++ b/inst/doc/usecase/ex1_5_latlon_reorder.R @@ -0,0 +1,170 @@ +#--------------------------------------------------------------------- +# This script shows you how to use reorder function (Sort, CircularSort) +# to get the desired longitude and latitude region. + +# Note that the information of the lon/lat system in the original file is +# provided in order to illustrate a clearer picture, but it doesn't affect +# the results as long as the reorder functions are used. + +# Also, whether transformation is used or not, the range results remain the same. + +# See faq.md How-to-#11 for more explanation. + +#--------------------------------------------------------------------- + +library(startR) + +#---------------------------- +# CASE 1: +# Original file: lon [0:360]; lat [90:-90] +# Desired region: lon [-10, 10] in [-180, 180] system; lat [-20, 20] from south to north +# transformation: No +#---------------------------- +# tips: +# 1. Use 'latitude_reorder = Sort()' to sort latitude from south to north. +# The default of the hidden parameter 'decreasing' is TRUE. +# 2. Use 'longitude_reorder = CircularSort(-180, 180). It helps put the longitude values +# in [-180:180] system, so you can get the continuous region across 0 degree. +# 3. With reorder functions, the original file range does not affect the results. +#---------------------------- + +path_exp <- paste0('/esarchive/exp/ecmwf/system5_m1/daily_mean/', + '$var$_f6h/$var$_$sdate$.nc') +var <- 'psl' +sdate <- '19821201' + +lons.min <- -10 +lons.max <- 10 +lats.min <- -20 +lats.max <- 20 + + +res <- Start(dat = path_exp, + var = var, + ensemble = 'first', + sdate = sdate, + time = indices(1), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + +# Check the longitude and latitude +as.vector(attr(res, 'Variables')$dat1$latitude) +# [1] -19.8126401 ...... [142] 19.8126401 +as.vector(attr(res, 'Variables')$dat1$longitude) +# [1] -10.0000000 ...... [73] 10.0000000 + + + +#---------------------------- +# CASE 2: +# Original file: lon [0:360]; lat [90:-90] +# Desired region: lon [-10, 10] in [-180, 180] system; lat [20, -20] from north to south +# transformation: Yes, to 'r360x181' +#---------------------------- +# tips: +# 1. Use 'latitude_reorder = Sort(decreasing = TRUE)' to sort latitude from north to south. +# 2. Use 'longitude_reorder = CircularSort(-180, 180). It helps put the longitude values +# in [-180:180] system, so you can get the continuous region across 0 degree. +# 3. With the usage of reorder functions, transformation does not affect the results. +# 4. With reorder functions, the original file range does not affect the results. +#---------------------------- + +path_exp <- paste0('/esarchive/exp/ecmwf/system5_m1/daily_mean/', + '$var$_f6h/$var$_$sdate$.nc') +var <- 'psl' +sdate <- '19821201' + +lons.min <- -10 +lons.max <- 10 +lats.min <- 20 +lats.max <- -20 + +res <- Start(dat = path_exp, + var = var, + ensemble = 'first', + sdate = sdate, + time = indices(1), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(decreasing = TRUE), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min, lons.max, + lats.min, lats.max)), + transform_vars = c('longitude', 'latitude'), + synonims = list(latitude=c('lat', 'latitude'), + longitude=c('lon', 'longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + +# Check the longitude and latitude +as.vector(attr(res, 'Variables')$dat1$latitude) +# [1] 20 ...... [41] -20 +as.vector(attr(res, 'Variables')$dat1$longitude) +# [1] -10 ...... [21] 10 + + + +#---------------------------- +# CASE 3: +# Original file: lon [-180:180]; lat [90:-90] +# Desired region: lon [300, 320] in [0, 360] system; lat [-10, -20] from north to south +# transformation: Yes, to 'r360x181' +#---------------------------- +# tips: +# 1. Use 'latitude_reorder = Sort(decreasing = TRUE)' to sort latitude from north to south. +# 2. Use 'longitude_reorder = CircularSort(0, 360). It helps put the longitude values +# in [-180:180] system, so you can get the continuous region across 0 degree. +# 3. With the usage of reorder functions, transformation does not affect the results. +# 4. With reorder functions, the original file range does not affect the results. +#---------------------------- + +path_exp <- paste0('/esarchive/recon/ecmwf/era5/original_files/', + 'reorder/daily_mean/$var$/$var$_$sdate$.nc') +var <- 'tas' +sdate <- '199212' + +lons.min <- 300 +lons.max <- 320 +lats.min <- -10 +lats.max <- -20 + +res <- Start(dat = path_exp, + var = var, + sdate = sdate, + time = indices(1), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(decreasing = TRUE), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min, lons.max, + lats.min, lats.max)), + transform_vars = c('longitude', 'latitude'), + synonims = list(latitude=c('lat', 'latitude'), + longitude=c('lon', 'longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + +# Check the longitude and latitude +as.vector(attr(res, 'Variables')$dat1$latitude) +# [1] -10 ...... [11] -20 +as.vector(attr(res, 'Variables')$dat1$longitude) +# [1] 300 ...... [21] 320 + diff --git a/tests/testthat.R b/tests/testthat.R new file mode 100644 index 0000000000000000000000000000000000000000..d424073d93d066a0a8c2bf330e87c67a34fbf0c8 --- /dev/null +++ b/tests/testthat.R @@ -0,0 +1,5 @@ +library(testthat) +library(startR) + +test_check("startR") + diff --git a/tests/testthat/test-Start-reorder-lat.R b/tests/testthat/test-Start-reorder-lat.R new file mode 100644 index 0000000000000000000000000000000000000000..f53a9ec12cfcc1ed39df7791330fd95fca79c2b8 --- /dev/null +++ b/tests/testthat/test-Start-reorder-lat.R @@ -0,0 +1,872 @@ +context("Start() lat Reorder test") + +#1 selector type 1-values(list) 2-values(vector) 3-indices 4-'all' 5-mix +#2 selector range 1-[10, 20] 2-[20, 10] 3-[-10, -20] 4-[-20, -10] +#3 resolution 1-1 2-<1 3->1 +#4 returns_var 1-NULL 2-'dat' +#5 lat_reorder/Sort() 1-No 2-Yes,decreasing = F 3-Yes,decreasing = T +#6 lon_reorder/CircularSort() 1-No 2-Yes,(0, 360) 3-Yes,(-180, 180) +#7 transform 1-NO 2-YES +#8 transform_crop 1-T 2-F 3-region + +############################################## +path_exp <- '/esarchive/exp/ecmwf/system5_m1/daily_mean/$var$_f6h/$var$_$sdate$.nc' + +## Origin longitude in file: [0:360] + +############################################## +test_that("1-1-2-2-1-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(10.25761, 19.81264), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 35 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) + +# lon + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(40, 45), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 19 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) + +}) + +############################################## +test_that("1-2-2-2-1-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 20 +lats.max <- 10 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(10.25761, 19.81264), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 35 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) + +}) + +############################################## +test_that("1-3-2-2-1-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- -10 +lats.max <- -20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(-19.81264, -10.25761), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 35 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) +############################################## +test_that("1-4-2-2-1-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- -20 +lats.max <- -10 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(-19.81264, -10.25761), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 35 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) + +############################################## +test_that("2-1-2-2-1-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(9.976578, 20.093670), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) + +# lon + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(40, 45), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 19 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) + +}) + +############################################## +test_that("2-2-2-2-1-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 20 +lats.max <- 10 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(9.976578, 20.093670), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) +############################################## +test_that("2-3-2-2-1-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- -10 +lats.max <- -20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(-20.093670, -9.976578), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) +############################################## +test_that("2-4-2-2-1-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- -20 +lats.max <- -10 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(-20.093670, -9.976578), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) +############################################## +test_that("1-1-2-3-1-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = NULL, + longitude = NULL, + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$common$latitude)), + c(10.25761, 19.81264), + tolerance = 0.0001 + ) + expect_equal( + attr(res, 'Variables')$dat1$latitude, + NULL + ) + expect_equal( + (attr(res, 'Variables')$common$latitude)[1] < (attr(res, 'Variables')$common$latitude)[2], + TRUE + ) + expect_equal( + class(attr(res, 'Variables')$common$latitude), + 'array' + ) +}) + +############################################## +test_that("2-1-2-3-1-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = NULL, + longitude = NULL, + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$common$latitude)), + c(9.976578, 20.093670), + tolerance = 0.0001 + ) + expect_equal( + attr(res, 'Variables')$dat1$latitude, + NULL + ) + expect_equal( + (attr(res, 'Variables')$common$latitude)[1] < (attr(res, 'Variables')$common$latitude)[2], + TRUE + ) + expect_equal( + class(attr(res, 'Variables')$common$latitude), + 'array' + ) +}) +############################################## +############################################## +test_that("1-1-2-2-2-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(10.25761, 19.81264), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 35 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) + +# lon + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(40, 45), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 19 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) + +}) +############################################## +test_that("1-2-2-2-2-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 20 +lats.max <- 10 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(10.25761, 19.81264), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 35 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) +############################################## +test_that("1-1-2-2-2-3-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(decreasing = T), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(10.25761, 19.81264), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 35 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) +############################################## +test_that("2-1-2-2-2-3-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + latitude_reorder = Sort(decreasing = T), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(9.976578, 20.093670), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) + + +############################################## +#1 selector type 1-values(list) 2-values(vector) 3-indices 4-'all' 5-mix +#2 selector range 1-[10, 20] 2-[20, 10] 3-[-10, -20] 4-[-20, -10] +#3 resolution 1-1 2-<1 3->1 +#4 returns_var 1-NULL 2-'dat' +#5 lat_reorder/Sort() 1-No 2-Yes,decreasing = F 3-Yes,decreasing = T +#6 lon_reorder/CircularSort() 1-No 2-Yes,(0, 360) 3-Yes,(-180, 180) +#7 transform 1-NO 2-YES +#8 transform_crop 1-T 2-F 3-region + + +############################################## +test_that("1-1-2-2-1-1-2-3", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) + +############################################## +test_that("1-1-2-2-3-1-2-3", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(decreasing = T), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) +############################################## +test_that("1-1-2-2-3-2-2-3", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(decreasing = T), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) +############################################## +test_that("1-1-2-2-3-1-2-1", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(decreasing = T), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = T), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) + +############################################## +test_that("1-3. Selector type: indices(list)", { + +}) +############################################## +test_that("1-4. Selector type: indices(vector)", { + +}) +############################################## +test_that("1-4. Selector type: indices(vector)", { + +}) + diff --git a/tests/testthat/test-Start-reorder-latCoarse.R b/tests/testthat/test-Start-reorder-latCoarse.R new file mode 100644 index 0000000000000000000000000000000000000000..bc6f480a8af702e354584345e34cc9ff3acc771e --- /dev/null +++ b/tests/testthat/test-Start-reorder-latCoarse.R @@ -0,0 +1,874 @@ +context("Start() lat Reorder test") + +#1 selector type 1-values(list) 2-values(vector) 3-indices 4-'all' 5-mix +#2 selector range 1-[10, 20] 2-[20, 10] 3-[-10, -20] 4-[-20, -10] +#3 resolution 1-1 2-<1 3->1 4-> mixed +#4 returns_var 1-NULL 2-'dat' +#5 lat_reorder/Sort() 1-No 2-Yes,decreasing = F 3-Yes,decreasing = T +#6 lon_reorder/CircularSort() 1-No 2-Yes,(0, 360) 3-Yes,(-180, 180) +#7 transform 1-NO 2-YES +#8 transform_crop 1-T 2-F 3-region + + +## mixed resolution indicates lower than 1 degree resolution for longitude and higer for latitude. +############################################## +#path_exp <- '/esarchive/exp/ecmwf/system5_m1/daily_mean/$var$_f6h/$var$_$sdate$.nc' +path_exp <- '/esarchive/exp/ncar/cesm-dple/monthly_mean/$var$/$var$_$sdate$.nc' +## Origin longitude in file: [0:358.75] step 1.25 degrees #288 values +## latitude: -90 o 90 {-90, -89.05759 ...} #192 values +############################################## +test_that("1-1-4-2-1-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path = path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(10.83770, 19.31937), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 10 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) + +# lon + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(40, 45), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 5 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) + +}) + +############################################## +test_that("1-2-4-2-1-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 20 +lats.max <- 10 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(10.83770, 19.31937), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 10 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) + +}) + +############################################## +test_that("1-3-4-2-1-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- -10 +lats.max <- -20 + +res <- Start(dat = list(list(path = path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(-19.31937, -10.83770), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 10 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) +############################################## +test_that("1-4-4-2-1-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- -20 +lats.max <- -10 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(-19.31937, -10.83770), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 10 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) + +############################################## +test_that("2-1-4-2-1-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(9.895288, 20.261780), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) + +# lon + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(40, 45), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 5 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) + +}) + +############################################## +test_that("2-2-4-2-1-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 20 +lats.max <- 10 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(9.895288, 20.261780), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) +############################################## +test_that("2-3-4-2-1-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- -10 +lats.max <- -20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(-20.261780, -9.895288), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) +############################################## +test_that("2-4-4-2-1-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- -20 +lats.max <- -10 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(-20.261780, -9.895288), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) +############################################## +test_that("1-1-4-3-1-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = NULL, + longitude = NULL, + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$common$latitude)), + c(10.83770, 19.31937), + tolerance = 0.0001 + ) + expect_equal( + attr(res, 'Variables')$dat1$latitude, + NULL + ) + expect_equal( + (attr(res, 'Variables')$common$latitude)[1] < (attr(res, 'Variables')$common$latitude)[2], + TRUE + ) + expect_equal( + class(attr(res, 'Variables')$common$latitude), + 'array' + ) +}) + +############################################## +test_that("2-1-4-3-1-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = NULL, + longitude = NULL, + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$common$latitude)), + c(9.895288, 20.261780), + tolerance = 0.0001 + ) + expect_equal( + attr(res, 'Variables')$dat1$latitude, + NULL + ) + expect_equal( + (attr(res, 'Variables')$common$latitude)[1] < (attr(res, 'Variables')$common$latitude)[2], + TRUE + ) + expect_equal( + class(attr(res, 'Variables')$common$latitude), + 'array' + ) +}) +############################################## +############################################## +test_that("1-1-4-2-2-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(10.83770, 19.31937), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 10 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) + +# lon + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(40, 45), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 5 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) + +}) +############################################## +test_that("1-2-4-2-2-1-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 20 +lats.max <- 10 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(10.83770, 19.31937), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 10 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) +############################################## +test_that("1-1-4-2-2-3-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(decreasing = T), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(10.83770, 19.31937), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 10 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) +############################################## +test_that("2-1-4-2-2-3-1-x", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + latitude_reorder = Sort(decreasing = T), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(9.895288, 20.261780), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) + + +############################################## +#1 selector type 1-values(list) 2-values(vector) 3-indices 4-'all' 5-mix +#2 selector range 1-[10, 20] 2-[20, 10] 3-[-10, -20] 4-[-20, -10] +#3 resolution 1-1 2-<1 3->1 4 -> mixed4 -> mixed4 -> mixed4 -> mixed +#4 returns_var 1-NULL 2-'dat' +#5 lat_reorder/Sort() 1-No 2-Yes,decreasing = F 3-Yes,decreasing = T +#6 lon_reorder/CircularSort() 1-No 2-Yes,(0, 360) 3-Yes,(-180, 180) +#7 transform 1-NO 2-YES +#8 transform_crop 1-T 2-F 3-region + + +############################################## +test_that("1-1-4-2-1-1-2-3", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) + +############################################## +test_that("1-1-4-2-3-1-2-3", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(decreasing = T), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) +############################################## +test_that("1-1-4-2-3-2-2-3", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(decreasing = T), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) +############################################## +test_that("1-1-4-2-3-1-2-1", { +lons.min <- 40 +lons.max <- 45 +lats.min <- 10 +lats.max <- 20 + +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(decreasing = T), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = T), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) +# lat + expect_equal( + range((attr(res, 'Variables')$dat1$latitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$latitude)[1] < (attr(res, 'Variables')$dat1$latitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$latitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$latitude), + 'array' + ) +}) + +############################################## +test_that("1-3. Selector type: indices(list)", { + +}) +############################################## +test_that("1-4. Selector type: indices(vector)", { + +}) +############################################## +test_that("1-4. Selector type: indices(vector)", { + +}) + diff --git a/tests/testthat/test-Start-reorder-lon-transform_-180to180.R b/tests/testthat/test-Start-reorder-lon-transform_-180to180.R new file mode 100644 index 0000000000000000000000000000000000000000..1b8a96b44f3ae49c4b32a3d53f4975e9e271cc62 --- /dev/null +++ b/tests/testthat/test-Start-reorder-lon-transform_-180to180.R @@ -0,0 +1,919 @@ +context("Start() lon Reorder transform -180to180 test") +#1 selector type 1-values(list) 2-values(vector) 3-indices 4-'all' 5-mix +#2 selector range 1-[10, 20] 2-[20, 10] 3-[-10, -20] 4-[-20, -10] 5-[-10, 10] 6-[10, -10] 7-[300, 350] 8-[170, 190] +#3 resolution 1-1 2-<1 3->1 +#4 returns_var 1-NULL 2-'dat' +#5 lat_reorder/Sort() 1-No 2-Yes,decreasing = F 3-Yes,decreasing = T +#6 lon_reorder/CircularSort() 1-No 2-Yes,(0, 360) 3-Yes,(-180, 180) +#7 transform 1-NO 2-'r360x181' +#8 transform_crop 1-T 2-F 3-region 4-x + +############################################## +# 3-2 +## Origin longitude in file: [-179.71875:180] +path_exp <- '/esarchive/recon/ecmwf/era5/original_files/reorder/daily_mean/$var$/$var$_$sdate$.nc' +variable <- 'tas' +sdate <- '199212' + +############################################## +test_that("1-1-2-2-1-1-2-4", { +lons.min <- 10 +lons.max <- 20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con'), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) +}) + +############################################## +test_that("1-2-2-2-1-1-2-4", { +lons.min <- 20 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con'), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) +}) + +############################################## +test_that("1-5-2-2-1-1-2-4", { +lons.min <- -10 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con'), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-10, 10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) +}) + +############################################## +test_that("1-6-2-2-1-1-2-4", { +lons.min <- 10 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con'), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-10, 10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) +}) +############################################## +test_that("1-8-2-2-1-1-2-4", { +lons.min <- 170 +lons.max <- 190 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con'), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(170, 180), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) +}) +############################################## +############################################## +############################################## +test_that("1-1-2-2-2-2-2-3", { +lons.min <- 10 +lons.max <- 20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) +}) +############################################## +test_that("1-2-2-2-2-2-2-3", { +lons.min <- 20 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 359), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 351 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[11:12], + c(10, 20), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-3-2-2-2-2-2-3", { +lons.min <- -10 +lons.max <- -20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 359), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 351 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[341:342], + c(340, 350), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-4-2-2-2-2-2-3", { +lons.min <- -20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(340, 350), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) +}) +############################################## +test_that("1-5-2-2-2-2-2-3", { +lons.min <- -10 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 359), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[11:12], + c(10, 350), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-6-2-2-2-2-2-3", { +lons.min <- 20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(20, 350), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 331 + ) +}) +############################################## +test_that("1-7-2-2-2-2-2-3", { +lons.min <- 330 +lons.max <- 350 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(330, 350), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) +}) +############################################## +test_that("1-8-2-2-2-2-2-3", { +lons.min <- 350 +lons.max <- 370 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 359), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[11:12], + c(10, 350), + tolerance = 0.0001 + ) +}) +############################################## +############################################## +############################################## +test_that("1-1-2-2-2-3-2-3", { +lons.min <- 10 +lons.max <- 20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) +}) +############################################## +test_that("1-2-2-2-2-3-2-3", { +lons.min <- 20 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-180, 179), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 351 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[191:192], + c(10, 20), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-3-2-2-2-3-2-3", { +lons.min <- -10 +lons.max <- -20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-180, 179), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 351 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[161:162], + c(-20, -10), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-4-2-2-2-3-2-3", { +lons.min <- -20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-20, -10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) +}) + +############################################## +test_that("1-5-2-2-2-3-2-3", { +lons.min <- -10 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-10, 10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) +}) +############################################## +test_that("1-6-2-2-2-3-2-3", { +lons.min <- 20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-180, 179), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 331 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[171:172], + c(-10, 20), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-7-2-2-2-3-2-3", { +lons.min <- 330 +lons.max <- 350 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-30, -10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) +}) +############################################## +test_that("1-8-2-2-2-3-2-3", { +lons.min <- 350 +lons.max <- 370 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-10, 10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) +}) diff --git a/tests/testthat/test-Start-reorder-lon-transform_0to360.R b/tests/testthat/test-Start-reorder-lon-transform_0to360.R new file mode 100644 index 0000000000000000000000000000000000000000..5ef55769fd4ce52f0b1a06a450547910be785664 --- /dev/null +++ b/tests/testthat/test-Start-reorder-lon-transform_0to360.R @@ -0,0 +1,999 @@ +context("Start() lon Reorder transform 0to360 test") +#1 selector type 1-values(list) 2-values(vector) 3-indices 4-'all' 5-mix +#2 selector range 1-[10, 20] 2-[20, 10] 3-[-10, -20] 4-[-20, -10] 5-[-10, 10] 6-[10, -10] 7-[300, 350] 8-[350, 370] +#3 resolution 1-1 2-<1 3->1 +#4 returns_var 1-NULL 2-'dat' +#5 lat_reorder/Sort() 1-No 2-Yes,decreasing = F 3-Yes,decreasing = T +#6 lon_reorder/CircularSort() 1-No 2-Yes,(0, 360) 3-Yes,(-180, 180) +#7 transform 1-NO 2-'r360x181' +#8 transform_crop 1-T 2-F 3-region 4-x + +############################################## +# 3-2 +## Origin longitude in file: [0:360] +path_exp <- '/esarchive/exp/ecmwf/system5_m1/daily_mean/$var$_f6h/$var$_$sdate$.nc' +variable <- 'psl' +sdate <- '19821201' + +############################################## +test_that("1-1-2-2-1-1-2-4", { +lons.min <- 10 +lons.max <- 20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con'), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) +}) + +############################################## +test_that("1-2-2-2-1-1-2-4", { +lons.min <- 20 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con'), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) +}) +############################################## +test_that("1-5-2-2-1-1-2-4", { +lons.min <- -10 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con'), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) +}) + +############################################## +test_that("1-6-2-2-1-1-2-4", { +lons.min <- 10 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con'), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) +}) +############################################## +test_that("1-7-2-2-1-1-2-4", { +lons.min <- 330 +lons.max <- 350 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con'), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(330, 350), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) +}) +############################################## +test_that("1-8-2-2-1-1-2-4", { +lons.min <- 350 +lons.max <- 370 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con'), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(350, 359), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 10 + ) +}) +############################################## +############################################## +############################################## +test_that("1-1-2-2-2-2-2-3", { +lons.min <- 10 +lons.max <- 20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) +}) +############################################## +test_that("1-2-2-2-2-2-2-3", { +lons.min <- 20 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 359), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 351 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[11:12], + c(10, 20), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-3-2-2-2-2-2-3", { +lons.min <- -10 +lons.max <- -20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 359), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 351 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[341:342], + c(340, 350), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-4-2-2-2-2-2-3", { +lons.min <- -20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(340, 350), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) +}) +############################################## +test_that("1-5-2-2-2-2-2-3", { +lons.min <- -10 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 359), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[11:12], + c(10, 350), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-6-2-2-2-2-2-3", { +lons.min <- 20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(20, 350), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 331 + ) +}) +############################################## +test_that("1-7-2-2-2-2-2-3", { +lons.min <- 330 +lons.max <- 350 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(330, 350), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) +}) +############################################## +test_that("1-8-2-2-2-2-2-3", { +lons.min <- 350 +lons.max <- 370 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 359), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[11:12], + c(10, 350), + tolerance = 0.0001 + ) +}) +############################################## +############################################## +############################################## +test_that("1-1-2-2-2-3-2-3", { +lons.min <- 10 +lons.max <- 20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) +}) +############################################## +test_that("1-2-2-2-2-3-2-3", { +lons.min <- 20 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-180, 179), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 351 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[191:192], + c(10, 20), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-3-2-2-2-3-2-3", { +lons.min <- -10 +lons.max <- -20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-180, 179), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 351 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[161:162], + c(-20, -10), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-4-2-2-2-3-2-3", { +lons.min <- -20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-20, -10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) +}) + +############################################## +test_that("1-5-2-2-2-3-2-3", { +lons.min <- -10 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-10, 10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) +}) +############################################## +test_that("1-6-2-2-2-3-2-3", { +lons.min <- 20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-180, 179), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 331 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[171:172], + c(-10, 20), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-7-2-2-2-3-2-3", { +lons.min <- 330 +lons.max <- 350 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-30, -10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) +}) +############################################## +test_that("1-8-2-2-2-3-2-3", { +lons.min <- 350 +lons.max <- 370 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-10, 10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) +}) diff --git a/tests/testthat/test-Start-reorder-lon-transform_0to360Coarse.R b/tests/testthat/test-Start-reorder-lon-transform_0to360Coarse.R new file mode 100644 index 0000000000000000000000000000000000000000..262673bd1cf7f11961d37c584b143b960dfbcb2e --- /dev/null +++ b/tests/testthat/test-Start-reorder-lon-transform_0to360Coarse.R @@ -0,0 +1,1003 @@ +context("Start() lon Reorder transform 0to360 test") +#1 selector type 1-values(list) 2-values(vector) 3-indices 4-'all' 5-mix +#2 selector range 1-[10, 20] 2-[20, 10] 3-[-10, -20] 4-[-20, -10] 5-[-10, 10] 6-[10, -10] 7-[300, 350] 8-[350, 370] +#3 resolution 1-1 2-<1 3->1 4 -> mixed +#4 returns_var 1-NULL 2-'dat' +#5 lat_reorder/Sort() 1-No 2-Yes,decreasing = F 3-Yes,decreasing = T +#6 lon_reorder/CircularSort() 1-No 2-Yes,(0, 360) 3-Yes,(-180, 180) +#7 transform 1-NO 2-'r360x181' +#8 transform_crop 1-T 2-F 3-region 4-x + +############################################## +# 3-2 +## Origin longitude in file: [0:360] +path_exp <- '/esarchive/exp/ncar/cesm-dple/monthly_mean/$var$/$var$_$sdate$.nc' + +## Origin longitude in file: [0:358.75] step 1.25 degrees #288 values +## latitude: -90 o 90 {-90, -89.05759 ...} #192 values + +variable <- 'psl' +sdate <- '20001101' + +############################################## +test_that("1-1-2-2-1-1-2-4", { +lons.min <- 10 +lons.max <- 20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con'), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) +}) + +############################################## +test_that("1-2-2-2-1-1-2-4", { +lons.min <- 20 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con'), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) +}) +############################################## +test_that("1-5-2-2-1-1-2-4", { +lons.min <- -10 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con'), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) +}) + +############################################## +test_that("1-6-2-2-1-1-2-4", { +lons.min <- 10 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con'), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + FALSE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) +}) +############################################## +test_that("1-7-2-2-1-1-2-4", { +lons.min <- 330 +lons.max <- 350 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con'), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(330, 350), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) +}) +############################################## +test_that("1-8-2-2-1-1-2-4", { +lons.min <- 350 +lons.max <- 370 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con'), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(350, 359), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 10 + ) +}) +############################################## +############################################## +############################################## +test_that("1-1-2-2-2-2-2-3", { +lons.min <- 10 +lons.max <- 20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) +}) +############################################## +test_that("1-2-2-2-2-2-2-3", { +lons.min <- 20 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 359), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 351 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[11:12], + c(10, 20), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-3-2-2-2-2-2-3", { +lons.min <- -10 +lons.max <- -20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 359), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 351 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[341:342], + c(340, 350), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-4-2-2-2-2-2-3", { +lons.min <- -20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(340, 350), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) +}) +############################################## +test_that("1-5-2-2-2-2-2-3", { +lons.min <- -10 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 359), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[11:12], + c(10, 350), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-6-2-2-2-2-2-3", { +lons.min <- 20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(20, 350), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 331 + ) +}) +############################################## +test_that("1-7-2-2-2-2-2-3", { +lons.min <- 330 +lons.max <- 350 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(330, 350), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) +}) +############################################## +test_that("1-8-2-2-2-2-2-3", { +lons.min <- 350 +lons.max <- 370 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 359), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[11:12], + c(10, 350), + tolerance = 0.0001 + ) +}) +############################################## +############################################## +############################################## +test_that("1-1-2-2-2-3-2-3", { +lons.min <- 10 +lons.max <- 20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) +}) +############################################## +test_that("1-2-2-2-2-3-2-3", { +lons.min <- 20 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-180, 179), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 351 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[191:192], + c(10, 20), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-3-2-2-2-3-2-3", { +lons.min <- -10 +lons.max <- -20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-180, 179), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 351 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[161:162], + c(-20, -10), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-4-2-2-2-3-2-3", { +lons.min <- -20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-20, -10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 11 + ) +}) + +############################################## +test_that("1-5-2-2-2-3-2-3", { +lons.min <- -10 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-10, 10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) +}) +############################################## +test_that("1-6-2-2-2-3-2-3", { +lons.min <- 20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-180, 179), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 331 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[171:172], + c(-10, 20), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-7-2-2-2-3-2-3", { +lons.min <- 330 +lons.max <- 350 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-30, -10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) +}) +############################################## +test_that("1-8-2-2-2-3-2-3", { +lons.min <- 350 +lons.max <- 370 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + member = indices(1), + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + transform = CDORemapper, + transform_params = list(grid ='r360x181', + method = 'con', + crop = c(lons.min,lons.max, + lats.min,lats.max)), + transform_vars = c('longitude', 'latitude'), + transform_extra_cells = 2, + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-10, 10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 21 + ) +}) diff --git a/tests/testthat/test-Start-reorder-lon0to360Coarse.R b/tests/testthat/test-Start-reorder-lon0to360Coarse.R new file mode 100644 index 0000000000000000000000000000000000000000..461042a83acf74b77bab87d9d3e3519f224fd32e --- /dev/null +++ b/tests/testthat/test-Start-reorder-lon0to360Coarse.R @@ -0,0 +1,622 @@ +context("Start() lon Reorder non-transform 0to360 test") +#1 selector type 1-values(list) 2-values(vector) 3-indices 4-'all' 5-mix +#2 selector range 1-[10, 20] 2-[20, 10] 3-[-10, -20] 4-[-20, -10] 5-[-10, 10] 6-[10, -10] 7-[300, 350] 8-[350, 370] +#3 resolution 1-1 2-<1 3->1 4-> mixed +#4 returns_var 1-NULL 2-'dat' +#5 lat_reorder/Sort() 1-No 2-Yes,decreasing = F 3-Yes,decreasing = T +#6 lon_reorder/CircularSort() 1-No 2-Yes,(0, 360) 3-Yes,(-180, 180) +#7 transform 1-NO 2-YES +#8 transform_crop 1-T 2-F 3-region 4-x + +############################################## +# 3-2 +path_exp <- '/esarchive/exp/ncar/cesm-dple/monthly_mean/$var$/$var$_$sdate$.nc' + +## Origin longitude in file: [0:358.75] step 1.25 degrees #288 values +## latitude: -90 o 90 {-90, -89.05759 ...} #192 values +############################################## +test_that("1-1-4-2-1-1-1-x", { +lons.min <- 10 +lons.max <- 20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + +# lon + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 9 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) +}) + +############################################## +test_that("1-2-4-2-1-1-1-x", { +lons.min <- 20 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + FALSE + ) +}) +############################################## +test_that("1-5-4-2-1-1-1-x", { +lons.min <- -10 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + +}) + +############################################## +test_that("1-6-4-2-1-1-1-x", { +lons.min <- 10 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + FALSE + ) +}) + +############################################## +test_that("1-7-4-2-1-1-1-x", { +lons.min <- 330 +lons.max <- 350 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(330, 350), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) +############################################## +test_that("1-8-4-2-1-1-1-x", { +lons.min <- 350 +lons.max <- 370 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(350, 358.75), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) +############################################## +############################################## +############################################## +test_that("1-1-4-2-2-2-1-x", { +lons.min <- 10 +lons.max <- 20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(0, 360), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 9 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) +}) +############################################## +test_that("1-1-4-2-2-3-1-x", { +lons.min <- 10 +lons.max <- 20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(-180, 180), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 9 + ) +}) +############################################## +test_that("1-2-4-2-2-2-1-x", { +lons.min <- 20 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(0, 360), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + length((attr(res, 'Variables')$dat1$longitude)), + c(281) + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[9:10], + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) +############################################## +test_that("1-2-4-2-2-3-1-x", { +lons.min <- 20 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(-180, 180), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + length((attr(res, 'Variables')$dat1$longitude)), + c(281) + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[153:154], + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) + +############################################## +test_that("1-3-4-2-2-2-1-x", { +lons.min <- -10 +lons.max <- -20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(0, 360), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + length((attr(res, 'Variables')$dat1$longitude)), + c(281) + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[273:274], + c(340, 350), + tolerance = 0.0001 + ) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 358.75), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-3-4-2-2-3-1-x", { +lons.min <- -10 +lons.max <- -20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(-180, 180), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + length((attr(res, 'Variables')$dat1$longitude)), + c(281) + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[129:130], + c(-20, -10), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-4-4-2-2-2-1-x", { +lons.min <- -20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(0, 360), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(340, 350), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) +############################################## +test_that("1-4-4-2-2-3-1-x", { +lons.min <- -20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(-180, 180), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-20, -10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) + +############################################## +test_that("1-5-4-2-2-2-1-x", { +lons.min <- 330 +lons.max <- 350 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(0, 360), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(330, 350), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-5-4-2-2-3-1-x", { +lons.min <- 330 +lons.max <- 350 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(-180, 180), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-30, -10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) + +############################################## +test_that("1-6-4-2-2-2-1-x", { +lons.min <- 350 +lons.max <- 370 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(0, 360), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + length((attr(res, 'Variables')$dat1$longitude)), + c(17), + tolerance = 0.0001 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[9:10], + c(10, 350), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-6-4-2-2-3-1-x", { +lons.min <- 350 +lons.max <- 370 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '20001101', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(-180, 180), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + length((attr(res, 'Variables')$dat1$longitude)), + c(17), + tolerance = 0.0001 + ) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-10, 10), + tolerance = 0.0001 + ) +}) diff --git a/tests/testthat/test-Start-reorder-lon_-180to180.R b/tests/testthat/test-Start-reorder-lon_-180to180.R new file mode 100644 index 0000000000000000000000000000000000000000..38cd6b8efbe7c3ec9442e637ed4597ffab6ed390 --- /dev/null +++ b/tests/testthat/test-Start-reorder-lon_-180to180.R @@ -0,0 +1,774 @@ +context("Start() lon Reorder non-transform -180to180 test") +#1 selector type 1-values(list) 2-values(vector) 3-indices 4-'all' 5-mix +#2 selector range 1-[10, 20] 2-[20, 10] 3-[-10, -20] 4-[-20, -10] 5-[-10, 10] 6-[10, -10] 7-[300, 350] 8-[170, 190] +#3 resolution 1-1 2-<1 3->1 +#4 returns_var 1-NULL 2-'dat' +#5 lat_reorder/Sort() 1-No 2-Yes,decreasing = F 3-Yes,decreasing = T +#6 lon_reorder/CircularSort() 1-No 2-Yes,(0, 360) 3-Yes,(-180, 180) +#7 transform 1-NO 2-YES +#8 transform_crop 1-T 2-F 3-region 4-x + +############################################## +# 3-2 + +## Origin longitude in file: [-179.71875:180] +path_exp <- '/esarchive/recon/ecmwf/era5/original_files/reorder/daily_mean/$var$/$var$_$sdate$.nc' +variable <- 'tas' +sdate <- '199212' + +############################################## +test_that("1-1-2-2-1-1-1-x", { +lons.min <- 10 +lons.max <- 20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + +# lon + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10.12500, 19.96875), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 36 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) +}) + +############################################## +test_that("1-2-2-2-1-1-1-x", { +lons.min <- 20 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10.12500, 19.96875), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + FALSE + ) +}) + +############################################## +test_that("1-3-2-2-1-1-1-x", { +lons.min <- -10 +lons.max <- -20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-19.96875, -10.12500), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + FALSE + ) +}) + +############################################## +test_that("1-4-2-2-1-1-1-x", { +lons.min <- -20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-19.96875, -10.12500), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) + +############################################## +test_that("1-5-2-2-1-1-1-x", { +lons.min <- -10 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-9.84375,9.84375), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + +}) + +############################################## +test_that("1-6-2-2-1-1-1-x", { +lons.min <- 10 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c( -9.84375, 9.84375), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + FALSE + ) +}) + +############################################## +test_that("1-8-2-2-1-1-1-x", { +lons.min <- 170 +lons.max <- 190 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(170.1562, 180), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) +############################################## +############################################## +############################################## +test_that("1-1-2-2-2-2-1-x", { +lons.min <- 10 +lons.max <- 20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(0, 360), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10.12500, 19.96875), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 36 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) +}) +############################################## +test_that("1-1-2-2-2-3-1-x", { +lons.min <- 10 +lons.max <- 20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(-180, 180), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10.12500, 19.96875), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 36 + ) +}) +############################################## +test_that("1-2-2-2-2-2-1-x", { +lons.min <- 20 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(0, 360), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + length((attr(res, 'Variables')$dat1$longitude)), + 1244 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[36:37], + c(9.84375, 20.25000), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) +############################################## +test_that("1-2-2-2-2-3-1-x", { +lons.min <- 20 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(-180, 180), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + length((attr(res, 'Variables')$dat1$longitude)), + 1244 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[676:677], + c(9.84375, 20.25000), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) + +############################################## +test_that("1-3-2-2-2-2-1-x", { +lons.min <- -10 +lons.max <- -20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(0, 360), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + length((attr(res, 'Variables')$dat1$longitude)), + 1244 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[1209:1210], + c(339.7500, 350.1562), + tolerance = 0.0001 + ) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 359.7222), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-3-2-2-2-3-1-x", { +lons.min <- -10 +lons.max <- -20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(-180, 180), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + length((attr(res, 'Variables')$dat1$longitude)), + 1244 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[569:570], + c(-20.25000, -9.84375), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-4-2-2-2-2-1-x", { +lons.min <- -20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(0, 360), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(340.0312, 349.8750), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) +############################################## +test_that("1-4-2-2-2-3-1-x", { +lons.min <- -20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(-180, 180), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-19.96875, -10.12500), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) +############################################## +test_that("1-5-2-2-2-2-1-x", { +lons.min <- -10 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(0, 360), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 359.7188), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 71 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[36:37], + c(9.84375, 350.15625), + tolerance = 0.0001 + ) +}) + +############################################## +test_that("1-5-2-2-2-3-1-x", { +lons.min <- -10 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(-180, 180), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-9.84375, 9.84375), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) +############################################## +test_that("1-6-2-2-2-2-1-x", { +lons.min <- 20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(0, 360), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(20.2500, 349.8750), + tolerance = 0.001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 1173 + ) +}) + +############################################## +test_that("1-6-2-2-2-3-1-x", { +lons.min <- 20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(-180, 180), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-180, 179.7188), + tolerance = 0.001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 1173 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[605:606], + c(-10.12500, 20.25000), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-7-2-2-2-2-1-x", { +lons.min <- 330 +lons.max <- 350 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(0, 360), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(330.1875, 349.8750), + tolerance = 0.0001 + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 71 + ) + +}) +############################################## +test_that("1-7-2-2-2-3-1-x", { +lons.min <- 330 +lons.max <- 350 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(-180, 180), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-29.8125, -10.1250), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 71 + ) + +}) + +############################################## +test_that("1-8-2-2-2-2-1-x", { +lons.min <- 350 +lons.max <- 370 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(0, 360), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + length((attr(res, 'Variables')$dat1$longitude)), + 71, + tolerance = 0.0001 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[36:37], + c(9.84375, 350.15625), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-8-2-2-2-3-1-x", { +lons.min <- 350 +lons.max <- 370 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = variable, + sdate = sdate, + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(-180, 180), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + length((attr(res, 'Variables')$dat1$longitude)), + 71, + tolerance = 0.0001 + ) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-9.84375, 9.84375), + tolerance = 0.0001 + ) +}) diff --git a/tests/testthat/test-Start-reorder-lon_0to360.R b/tests/testthat/test-Start-reorder-lon_0to360.R new file mode 100644 index 0000000000000000000000000000000000000000..67d0e908612336b09ddff32add7f6a4a0d381230 --- /dev/null +++ b/tests/testthat/test-Start-reorder-lon_0to360.R @@ -0,0 +1,622 @@ +context("Start() lon Reorder non-transform 0to360 test") +#1 selector type 1-values(list) 2-values(vector) 3-indices 4-'all' 5-mix +#2 selector range 1-[10, 20] 2-[20, 10] 3-[-10, -20] 4-[-20, -10] 5-[-10, 10] 6-[10, -10] 7-[300, 350] 8-[350, 370] +#3 resolution 1-1 2-<1 3->1 +#4 returns_var 1-NULL 2-'dat' +#5 lat_reorder/Sort() 1-No 2-Yes,decreasing = F 3-Yes,decreasing = T +#6 lon_reorder/CircularSort() 1-No 2-Yes,(0, 360) 3-Yes,(-180, 180) +#7 transform 1-NO 2-YES +#8 transform_crop 1-T 2-F 3-region 4-x + +############################################## +# 3-2 +path_exp <- '/esarchive/exp/ecmwf/system5_m1/daily_mean/$var$_f6h/$var$_$sdate$.nc' + +## Origin longitude in file: [0:359.722222222222] + +############################################## +test_that("1-1-2-2-1-1-1-x", { +lons.min <- 10 +lons.max <- 20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + +# lon + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 37 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) +}) + +############################################## +test_that("1-2-2-2-1-1-1-x", { +lons.min <- 20 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + FALSE + ) +}) +############################################## +test_that("1-5-2-2-1-1-1-x", { +lons.min <- -10 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + +}) + +############################################## +test_that("1-6-2-2-1-1-1-x", { +lons.min <- 10 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + FALSE + ) +}) + +############################################## +test_that("1-7-2-2-1-1-1-x", { +lons.min <- 330 +lons.max <- 350 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(330, 350), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) +############################################## +test_that("1-8-2-2-1-1-1-x", { +lons.min <- 350 +lons.max <- 370 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(3:4), + latitude = values(c(lats.min:lats.max)), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(350, 359.7222222), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) +############################################## +############################################## +############################################## +test_that("1-1-2-2-2-2-1-x", { +lons.min <- 10 +lons.max <- 20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(0, 360), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 37 + ) + expect_equal( + class(attr(res, 'Variables')$dat1$longitude), + 'array' + ) +}) +############################################## +test_that("1-1-2-2-2-3-1-x", { +lons.min <- 10 +lons.max <- 20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(-180, 180), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) + expect_equal( + length(attr(res, 'Variables')$dat1$longitude), + 37 + ) +}) +############################################## +test_that("1-2-2-2-2-2-1-x", { +lons.min <- 20 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(0, 360), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + length((attr(res, 'Variables')$dat1$longitude)), + c(1261) + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[37:38], + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) +############################################## +test_that("1-2-2-2-2-3-1-x", { +lons.min <- 20 +lons.max <- 10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(-180, 180), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + length((attr(res, 'Variables')$dat1$longitude)), + c(1261) + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[685:686], + c(10, 20), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) + +############################################## +test_that("1-3-2-2-2-2-1-x", { +lons.min <- -10 +lons.max <- -20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(0, 360), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + length((attr(res, 'Variables')$dat1$longitude)), + c(1261) + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[1225:1226], + c(340, 350), + tolerance = 0.0001 + ) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(0, 359.7222), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-3-2-2-2-3-1-x", { +lons.min <- -10 +lons.max <- -20 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(-180, 180), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + length((attr(res, 'Variables')$dat1$longitude)), + c(1261) + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[577:578], + c(-20, -10), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-4-2-2-2-2-1-x", { +lons.min <- -20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(0, 360), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(340, 350), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) +############################################## +test_that("1-4-2-2-2-3-1-x", { +lons.min <- -20 +lons.max <- -10 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(-180, 180), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-20, -10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) + +############################################## +test_that("1-5-2-2-2-2-1-x", { +lons.min <- 330 +lons.max <- 350 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(0, 360), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(330, 350), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-5-2-2-2-3-1-x", { +lons.min <- 330 +lons.max <- 350 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(-180, 180), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-30, -10), + tolerance = 0.0001 + ) + expect_equal( + (attr(res, 'Variables')$dat1$longitude)[1] < (attr(res, 'Variables')$dat1$longitude)[2], + TRUE + ) +}) + +############################################## +test_that("1-6-2-2-2-2-1-x", { +lons.min <- 350 +lons.max <- 370 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(0, 360), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + length((attr(res, 'Variables')$dat1$longitude)), + c(73), + tolerance = 0.0001 + ) + expect_equal( + as.vector((attr(res, 'Variables')$dat1$longitude))[37:38], + c(10, 350), + tolerance = 0.0001 + ) +}) +############################################## +test_that("1-6-2-2-2-3-1-x", { +lons.min <- 350 +lons.max <- 370 +lats.min <- 10 +lats.max <- 20 +res <- Start(dat = list(list(path=path_exp)), + var = 'psl', + member = 'all', + sdate = '19821201', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(), + longitude_reorder = CircularSort(-180, 180), + longitude = values(list(lons.min, lons.max)), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = F) + expect_equal( + length((attr(res, 'Variables')$dat1$longitude)), + c(73), + tolerance = 0.0001 + ) + expect_equal( + range((attr(res, 'Variables')$dat1$longitude)), + c(-10, 10), + tolerance = 0.0001 + ) +}) diff --git a/tests/testthat/test-Start-reorder-retrieve.R b/tests/testthat/test-Start-reorder-retrieve.R new file mode 100644 index 0000000000000000000000000000000000000000..47412f59279905449384e00b96836fad422e7950 --- /dev/null +++ b/tests/testthat/test-Start-reorder-retrieve.R @@ -0,0 +1,157 @@ +context("Start() lon Reorder non-transform retrieve test") + + +############################################## +test_that("original range 0to360", { + +## Origin longitude in file: [0:359.722222222222] +path_exp <- '/esarchive/exp/ecmwf/system5_m1/daily_mean/$var$_f6h/$var$_$sdate$.nc' + +lons.min <- -2 +lons.max <- 2 +lats.min <- 10 +lats.max <- 12 + + +res <- Start(dat = path_exp, + var = 'psl', + member = indices(1), + sdate = '19821201', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = T) + + +res1 <- Start(dat = path_exp, + var = 'psl', + member = indices(1), + sdate = '19821201', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(decreasing = TRUE), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = T) + + +res2 <- Start(dat = path_exp, + var = 'psl', + member = indices(1), + sdate = '19821201', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(decreasing = TRUE), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude'), + member=c('ensemble','realization')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = T) + + expect_equal( + res1[1,1,1,1,1,1:7,], + res[1,1,1,1,1,7:1,] + ) + expect_equal( + res1[1,1,1,1,1,1,8:15], + res2[1,1,1,1,1,1,1:8] + ) + expect_equal( + res1[1,1,1,1,1,1,1:7], + res2[1,1,1,1,1,1,9:15] + ) + +}) + + +############################################## +test_that("original range -180to180", { + +## Origin longitude in file: [0:359.722222222222] +path_exp <- '/esarchive/recon/ecmwf/era5/original_files/reorder/daily_mean/$var$/$var$_$sdate$.nc' +variable <- 'tas' +sdate <- '199212' + +lons.min <- -2 +lons.max <- 2 +lats.min <- 10 +lats.max <- 12 + + +res <- Start(dat = path_exp, + var = variable, + sdate = '199212', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = T) + +res1 <- Start(dat = path_exp, + var = variable, + sdate = '199212', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(decreasing = TRUE), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(-180, 180), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = T) + + +res2 <- Start(dat = path_exp, + var = variable, + sdate = '199212', + time = indices(4), + latitude = values(list(lats.min, lats.max)), + latitude_reorder = Sort(decreasing = TRUE), + longitude = values(list(lons.min, lons.max)), + longitude_reorder = CircularSort(0, 360), + synonims = list(latitude=c('lat','latitude'), + longitude=c('lon','longitude')), + return_vars = list(latitude = 'dat', + longitude = 'dat', + time = NULL), + retrieve = T) + + expect_equal( + res1[1,1,1,1,1:7,], + res[1,1,1,1,7:1,] + ) + expect_equal( + res1[1,1,1,1,1,8:15], + res2[1,1,1,1,1,1:8] + ) + expect_equal( + res1[1,1,1,1,1,1:7], + res2[1,1,1,1,1,9:15] + ) + +}) +