diff --git a/R/Start.R b/R/Start.R index f86a98b622651ac501478649346319fd70bd3864..964d52f2426f1f0c331f9883df8b53144b1dbf16 100644 --- a/R/Start.R +++ b/R/Start.R @@ -1221,7 +1221,7 @@ Start <- function(..., # dim = indices/selectors, dims_to_check <- debug debug <- TRUE } - + ############################## READING FILE DIMS ############################ # Check that no unrecognized variables are present in the path patterns # and also that no file dimensions are requested to THREDDs catalogs. @@ -1947,6 +1947,10 @@ Start <- function(..., # dim = indices/selectors, transformed_common_vars_unorder_indices <- NULL transform_crop_domain <- NULL + # store warning messages from transform + warnings1 <- NULL + warnings2 <- NULL + for (i in 1:length(dat)) { if (dataset_has_files[i]) { indices <- indices_of_first_files_with_data[[i]] @@ -2101,11 +2105,16 @@ Start <- function(..., # dim = indices/selectors, } # Transform the variables - transformed_data <- do.call(transform, c(list(data_array = NULL, - variables = vars_to_transform, - file_selectors = selectors_of_first_files_with_data[[i]], - crop_domain = transform_crop_domain), - transform_params)) + tmp <- .withWarnings( + do.call(transform, c(list(data_array = NULL, + variables = vars_to_transform, + file_selectors = selectors_of_first_files_with_data[[i]], + crop_domain = transform_crop_domain), + transform_params)) + ) + transformed_data <- tmp$value + warnings1 <- c(warnings1, tmp$warnings) + # Discard the common transformed variables if already transformed before if (!is.null(transformed_common_vars)) { common_ones <- which(names(picked_common_vars) %in% names(transformed_data$variables)) @@ -2974,12 +2983,16 @@ Start <- function(..., # dim = indices/selectors, inner_dim, sub_array_of_fri) } } - - 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]], - crop_domain = transform_crop_domain), - transform_params))$variables[[var_with_selectors_name]] + tmp <- .withWarnings( + do.call(transform, c(list(data_array = NULL, + variables = subset_vars_to_transform, + file_selectors = selectors_of_first_files_with_data[[i]], + crop_domain = transform_crop_domain), + transform_params))$variables[[var_with_selectors_name]] + ) + transformed_subset_var <- tmp$value + warnings2 <- c(warnings2, tmp$warnings) + # Sorting the transformed variable and working out the indices again after transform. if (!is.null(dim_reorder_params[[inner_dim]])) { transformed_subset_var_reorder <- dim_reorder_params[[inner_dim]](transformed_subset_var) @@ -3737,7 +3750,10 @@ Start <- function(..., # dim = indices/selectors, final_dims_fake, dims_of_merge_dim, all_split_dims) } } - + + # store warning messages from transform + warnings3 <- NULL + # The following several lines will only run if retrieve = TRUE if (retrieve) { @@ -3816,10 +3832,12 @@ Start <- function(..., # dim = indices/selectors, # the appropriate work pieces. work_pieces <- retrieve_progress_message(work_pieces, num_procs, silent) + # NOTE: In .LoadDataFile(), metadata is saved in metadata_folder/1 or /2 etc. Before here, # the path name is created in work_pieces but the path hasn't been built yet. if (num_procs == 1) { - found_files <- lapply(work_pieces, .LoadDataFile, + tmp <- .withWarnings( + lapply(work_pieces, .LoadDataFile, shared_matrix_pointer = shared_matrix_pointer, file_data_reader = file_data_reader, synonims = synonims, @@ -3827,9 +3845,15 @@ Start <- function(..., # dim = indices/selectors, transform_params = transform_params, transform_crop_domain = transform_crop_domain, silent = silent, debug = debug) + ) + found_files <- tmp$value + warnings3 <- c(warnings3, tmp$warnings) + } else { cluster <- parallel::makeCluster(num_procs, outfile = "") # Send the heavy work to the workers + ##NOTE: .withWarnings() can't catch warnings like it does above (num_procs == 1). The warnings + ## show below when "bigmemory::as.matrix(data_array)" is called. Don't know how to fix it for now. work_errors <- try({ found_files <- parallel::clusterApplyLB(cluster, work_pieces, .LoadDataFile, shared_matrix_pointer = shared_matrix_pointer, @@ -4077,6 +4101,16 @@ Start <- function(..., # dim = indices/selectors, } } + # Print the warnings from transform + if (!is.null(c(warnings1, warnings2, warnings3))) { + transform_warnings_list <- lapply(c(warnings1, warnings2, warnings3), function(x) { + return(x$message) + }) + transform_warnings_list <- unique(transform_warnings_list) + for (i in 1:length(transform_warnings_list)) { + .warning(transform_warnings_list[[i]]) + } + } # Change final_dims_fake back because retrieve = FALSE will use it for attributes later if (exists("final_dims_fake_output")) { diff --git a/R/Utils.R b/R/Utils.R index 9bf23e995b4f2c75e262ebc675547b9960feb132..3d4d864a31c93f80529c2730dc3436e0149a3251 100644 --- a/R/Utils.R +++ b/R/Utils.R @@ -859,3 +859,13 @@ } return(unlist(new_list)) } + +.withWarnings <- function(expr) { + myWarnings <- NULL + wHandler <- function(w) { + myWarnings <<- c(myWarnings, list(w)) + invokeRestart("muffleWarning") + } + val <- withCallingHandlers(expr, warning = wHandler) + list(value = val, warnings = myWarnings) +} diff --git a/inst/doc/usecase/ex1_1_tranform.R b/inst/doc/usecase/ex1_1_tranform.R index a544f84c96005aea28ae6f99f3e61fc5b2fc9c88..e735280c0c9b08e5d0d96c674d58e7973177fb39 100644 --- a/inst/doc/usecase/ex1_1_tranform.R +++ b/inst/doc/usecase/ex1_1_tranform.R @@ -39,8 +39,7 @@ obs <- Start(dat = obs_path, transform = CDORemapper, transform_extra_cells = 2, transform_params = list(grid = 'r360x181', - method = 'conservative', - crop = c(lons.min, lons.max, lats.min, lats.max)), + method = 'conservative'), transform_vars = c('latitude', 'longitude'), return_vars = list(time = NULL, latitude = 'dat', diff --git a/inst/doc/usecase/ex1_5_latlon_reorder.R b/inst/doc/usecase/ex1_5_latlon_reorder.R index c54314f5f7a2da70c2d7f1672eb7cc1c3578ae6d..75469bf059f46e91c1c48830ada0c55bb9b2a061 100644 --- a/inst/doc/usecase/ex1_5_latlon_reorder.R +++ b/inst/doc/usecase/ex1_5_latlon_reorder.R @@ -98,9 +98,7 @@ res <- Start(dat = path_exp, longitude_reorder = CircularSort(-180, 180), transform = CDORemapper, transform_params = list(grid ='r360x181', - method = 'con', - crop = c(lons.min, lons.max, - lats.min, lats.max)), + method = 'con'), transform_vars = c('longitude', 'latitude'), synonims = list(latitude=c('lat', 'latitude'), longitude=c('lon', 'longitude')), @@ -151,9 +149,7 @@ res <- Start(dat = path_exp, longitude_reorder = CircularSort(0, 360), transform = CDORemapper, transform_params = list(grid ='r360x181', - method = 'con', - crop = c(lons.min, lons.max, - lats.min, lats.max)), + method = 'con'), transform_vars = c('longitude', 'latitude'), synonims = list(latitude=c('lat', 'latitude'), longitude=c('lon', 'longitude')), diff --git a/inst/doc/usecase/ex2_12_transform_and_chunk.R b/inst/doc/usecase/ex2_12_transform_and_chunk.R index 8b2eb831878c0844b5262a3c501c7f8ccdbb5882..d89448c96aba28bbec50b5a8fb5079d2a17cabf0 100644 --- a/inst/doc/usecase/ex2_12_transform_and_chunk.R +++ b/inst/doc/usecase/ex2_12_transform_and_chunk.R @@ -43,8 +43,7 @@ exp <- Start(dat = '/esarchive/exp/ecmwf/system5_m1/monthly_mean/$var$_f6h/$var$ longitude_reorder = CircularSort(0, 360), transform = CDORemapper, transform_params = list(grid = 'r100x50', - method = 'con', - crop = c(lons.min, lons.max, lats.min, lats.max)), + method = 'con'), transform_vars = c('latitude', 'longitude'), transform_extra_cells = 8, synonims = list(latitude = c('latitude', 'lat'), @@ -93,8 +92,7 @@ exp <- Start(dat = '/esarchive/exp/ecmwf/system5_m1/monthly_mean/$var$_f6h/$var$ longitude_reorder = CircularSort(0, 360), transform = CDORemapper, transform_params = list(grid = 'r100x50', - method = 'con', - crop = FALSE), + method = 'con'), transform_vars = c('latitude', 'longitude'), transform_extra_cells = 8, synonims = list(latitude = c('latitude', 'lat'), @@ -136,8 +134,7 @@ exp <- Start(dat = '/esarchive/exp/ecmwf/system5_m1/monthly_mean/$var$_f6h/$var$ longitude_reorder = CircularSort(0, 360), transform = CDORemapper, transform_params = list(grid = 'r100x50', - method = 'con', - crop = FALSE), + method = 'con'), transform_vars = c('latitude', 'longitude'), transform_extra_cells = 8, synonims = list(latitude = c('latitude', 'lat'),