Skip to content

Commit

Permalink
Merge pull request #103 from IDEMSInternational/LC_changes
Browse files Browse the repository at this point in the history
Adding functionality for definitions when summaries are called from bucket
  • Loading branch information
lilyclements authored Mar 27, 2024
2 parents c9ba388 + 27854a2 commit c8c3e25
Show file tree
Hide file tree
Showing 5 changed files with 37 additions and 9 deletions.
12 changes: 9 additions & 3 deletions R/annual_rainfall_summaries.R
Original file line number Diff line number Diff line change
Expand Up @@ -20,12 +20,18 @@ annual_rainfall_summaries <- function(country, station_id, summaries = c("annual
list_return <- NULL

# do the summaries exist already?
summary_data <- epicsadata::get_summaries_data(country, station_id, summary = "annual_rainfall_summaries")

get_summaries <- get_summaries_data(country, station_id, summary = "annual_rainfall_summaries")
summary_data <- get_summaries[[1]]
# what if the definitions is different? Have an override option.
# if the summary data exists, and if you do not want to override it then:
if (nrow(summary_data) > 0 & override == FALSE) {
list_return[[1]] <- "definition from summary"
files <- epicsadata::get_objects_in_bucket(country, station_id, get_summaries)
if (nrow(files) == 0) {
list_return[[1]] <- (definitions(country, station_id, summaries = summaries))
} else {
list_return[[1]] <- (definitions(country, station_id, summaries = summaries, file_name))
}

} else {
# Get data definitions and summary definitions
definitions <- definitions(country = country, station_id = station_id, summaries = summaries)
Expand Down
5 changes: 3 additions & 2 deletions R/definitions.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,14 +3,15 @@
#' @param country `character(1)` The country code of the data.
#' @param station_id `character(1)` The station code in the data.
#' @param summaries `character` Vector of summaries to display
#' @param file Default `NULL` meaning that the most recent definitions file will be found and imported. Otherwise specify as a string the file to import. In format: "STATIONNAME.TIMESTAMP" e.g. "1.20240311152831"
#'
#' @return TODO
#' @export
#'
#' @examples # e.g. definitions("zm", "16", "annual_rain")
#' # error: definitions("zm", "1", c("annual_rain", "hi", "end_season"))
definitions <- function(country, station_id, summaries){
definition_data <- epicsadata::get_definitions_data(country = country, station_id = station_id)
definitions <- function(country, station_id, summaries, file = NULL){
definition_data <- epicsadata::get_definitions_data(country = country, station_id = station_id, file = file)
definition_data <- purrr::map(.x = summaries, .f = ~ definition_data[[.x]])
names(definition_data) <- summaries
# are any NULL 1 = NULL
Expand Down
18 changes: 15 additions & 3 deletions R/export_r_instat_to_bucket.R
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,9 @@
#' @param summaries A character vector specifying the types of summaries to include.
#' @param file_path The path to the directory where the JSON file will be saved locally.
#' @param file_name The name of the JSON file (without the ".json" extension).
#' @param country `character(1)` The country code of the data.
#' @param station_id `character` The id's of the stations to analyse. Either a
#' single value or a vector.
#' @param include_summary_data Logical indicating whether to include summary data in the export.
#'
#' @return NULL (invisibly)
Expand All @@ -31,9 +34,12 @@ export_r_instat_to_bucket <- function(data, data_by_year, data_by_year_month = N
rain = NULL, tmin = NULL, tmax = NULL, year = NULL, month = NULL,
summaries = c("annual_rainfall", "annual_temperature", "monthly_temperature", "extremes", "crop_success", "start_season"),
file_path, file_name,
station_id, country,
include_summary_data = FALSE){

definitions_data <- collate_definitions_data(data = data,
timestamp <- format(Sys.time(), format = "%Y%m%d%H%M%S")

definitions_data <- epicsadata::collate_definitions_data(data = data,
data_by_year = data_by_year,
data_by_year_month = data_by_year_month,
crop_data = crop_data,
Expand All @@ -50,10 +56,16 @@ export_r_instat_to_bucket <- function(data, data_by_year, data_by_year_month = N
auto_unbox = TRUE, pretty = TRUE)

# Read from computer to bucket
epicsadata::add_definitions_to_bucket(country = country, station_id = station_id, new_definitions = file_name)

add_definitions_to_bucket(country = country, station_id = station_id,
new_definitions = paste0(file_path, file_name),
timestamp = timestamp)

if (include_summary_data){
# function to read summary data from R-Instat into summaries in buckets
if ("annual_rainfall" %in% summaries){
add_summaries_to_bucket(country = country, station_id = station_id, data = data_book$get_data_frame(data_by_year),
summary = "annual_rainfall_summaries", timestamp = timestamp)
}
}
return("Uploaded to Bucket")
}
4 changes: 3 additions & 1 deletion man/definitions.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

7 changes: 7 additions & 0 deletions man/export_r_instat_to_bucket.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

0 comments on commit c8c3e25

Please sign in to comment.