Skip to content

Commit

Permalink
Merge pull request #76 from uace-azmet/add-az_lw15min-fxn
Browse files Browse the repository at this point in the history
Add az lw15min fxn
  • Loading branch information
jeremylweiss committed Jun 26, 2024
2 parents 5cafd42 + be97b24 commit d78c3ea
Show file tree
Hide file tree
Showing 13 changed files with 277 additions and 41 deletions.
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -6,5 +6,6 @@ export(az_add_units)
export(az_daily)
export(az_heat)
export(az_hourly)
export(az_lw15min)
importFrom(magrittr,"%>%")
importFrom(rlang,.data)
18 changes: 9 additions & 9 deletions R/az_15min.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,10 +7,10 @@
#' `station_id = c(8, 37)`) or as character vector with the prefix "az" and
#' two digits (e.g. `station_id = c("az08", "az37")`). If left blank, data for
#' all stations will be returned.
#' @param start_date_time A length 1 vector of class POSIXct or character in
#' @param start_date_time A length-1 vector of class POSIXct or character in
#' YYYY-MM-DD HH:MM:SS format, in AZ time. If only a date (YYYY-MM-DD) is
#' supplied, data will be requested starting at 00:00:01 of that day.
#' @param end_date_time A length 1 vector of class POSIXct or character in
#' @param end_date_time A length-1 vector of class POSIXct or character in
#' YYYY-MM-DD HH:MM:SS format, in AZ time. If only a date (YYYY-MM-DD) is
#' supplied, data will be requested through the *end* of that day (23:59:59).
#' Defaults to the current date and time if left blank and `start_date_time`
Expand All @@ -26,7 +26,7 @@
#' the AZMet API.
#' @return a tibble. For units and other metadata, see
#' <https://azmet.arizona.edu/about>
#' @seealso [az_daily()], [az_lw15min()], [az_lwdaily()], [az_heat()], [az_hourly()]
#' @seealso [az_daily()], [az_heat()], [az_hourly()], [az_lw15min()]
#' @source <https://azmet.arizona.edu/>
#' @importFrom rlang .data
#' @export
Expand Down Expand Up @@ -125,11 +125,11 @@ az_15min <- function(station_id = NULL, start_date_time = NULL, end_date_time =
#}

# Warn if the missing data is just at the end
#if (lubridate::ymd_hms(max(out$date_datetime), tz = "America/Phoenix") < params$end) {
# warning(
# "You requested data through ", params$end, " but only data through ", max(out$date_datetime), " were available."
# )
#}
if (lubridate::ymd_hms(max(out$datetime), tz = tz) < params$end) {
warning(
"You requested data through ", params$end, " but only data through ", max(out$datetime), " were available."
)
}


# Wrangle output -------------------------------------------------------------
Expand All @@ -145,7 +145,7 @@ az_15min <- function(station_id = NULL, start_date_time = NULL, end_date_time =
dplyr::mutate(
datetime = lubridate::force_tz(
lubridate::ymd_hms(.data$datetime),
tzone = "America/Phoenix"
tzone = tz
)
) %>%
# Convert NAs
Expand Down
10 changes: 5 additions & 5 deletions R/az_daily.R
Original file line number Diff line number Diff line change
@@ -1,30 +1,30 @@
#' Retrieve Daily Weather Data from AZMET
#'
#' Retrieves daily data from the Arizona Meteorological Network API. For a list
#' of weather stations and their locations see see [station_info].
#' of weather stations and their locations see [station_info].
#'
#' @param station_id station ID can be supplied as numeric vector (e.g.
#' `station_id = c(8, 37)`) or as character vector with the prefix "az" and 2
#' digits (e.g. `station_id = c("az08", "az37")`) If left blank data for all
#' stations will be returned
#' @param start_date A length 1 vector of class Date, POSIXct, or character in
#' @param start_date A length-1 vector of class Date, POSIXct, or character in
#' YYYY-MM-DD format. Will be rounded **down** to the nearest day if more
#' precision is supplied.
#' @param end_date A length 1 vector of class Date, POSIXct, or character in
#' @param end_date A length-1 vector of class Date, POSIXct, or character in
#' YYYY-MM-DD format. Will be rounded **down** to the nearest day if more
#' precision is supplied. Defaults to the current date if left blank.
#' @details If neither `start_date` nor `end_date` are supplied, the most recent
#' day of data will be returned. If only `start_date` is supplied, then the
#' end date defaults to the current date. Supplying only `end_date` will
#' result in an error.
#' @note If `station_id` is supplied as a vector, multiple successive calls to
#' the API will be made. You may find better performance getting data for all
#' the API will be made. You may find better performance getting data for all
#' the stations by leaving `station_id` blank and subsetting the resulting
#' dataframe. Requests for data from all stations for more than 6-12 months
#' may take considerable time.
#' @return a tibble. For units and other metadata, see
#' <https://ag.arizona.edu/azmet/raw2003.htm>
#' @seealso [az_hourly()], [az_heat()]
#' @seealso [az_15min()], [az_heat()], [az_hourly()], [az_lw15min()]
#' @source <https://ag.arizona.edu/azmet/>
#'
#' @importFrom rlang .data
Expand Down
8 changes: 4 additions & 4 deletions R/az_heat.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,16 +3,16 @@
#' Retrieves accumulated heat units and reference evapotranspiration units from
#' the Arizona Meteorological Network API. By default, returned values are
#' cumulative since January 1 of the current year. For a list of weather
#' stations and their locations see see [station_info].
#' stations and their locations see [station_info].
#'
#' @param station_id station ID can be supplied as numeric vector (e.g.
#' `station_id = c(8, 37)`) or as character vector with the prefix "az" and 2
#' digits (e.g. `station_id = c("az08", "az37")`) If left blank data for all
#' stations will be returned
#' @param start_date A length 1 vector of class Date, POSIXct, or character in
#' @param start_date A length-1 vector of class Date, POSIXct, or character in
#' YYYY-MM-DD format. Will be rounded **down** to the nearest day if more
#' precision is supplied.
#' @param end_date A length 1 vector of class Date, POSIXct, or character in
#' @param end_date A length-1 vector of class Date, POSIXct, or character in
#' YYYY-MM-DD format. Will be rounded **down** to the nearest day if more
#' precision is supplied. Defaults to the current date if left blank. If only
#' an `end_date` is supplied, then data will be cumulative from the start of
Expand All @@ -26,7 +26,7 @@
#' dataframe.
#' @return a tibble. For units and other metadata, see
#' <https://ag.arizona.edu/azmet/raw2003.htm>
#' @seealso [az_daily()], [az_hourly()]
#' @seealso [az_15min()], [az_daily()], [az_hourly()], [az_lw15min()]
#' @source <https://ag.arizona.edu/azmet/>
#' @importFrom rlang .data
#' @export
Expand Down
8 changes: 4 additions & 4 deletions R/az_hourly.R
Original file line number Diff line number Diff line change
@@ -1,17 +1,17 @@
#' Retrieve Hourly Weather Data
#'
#' Retrieves hourly weather data from the Arizona Meteorological Network API.
#' For a list of weather stations and their locations see see [station_info].
#' For a list of weather stations and their locations see [station_info].
#'
#' @param station_id station ID can be supplied as numeric vector (e.g.
#' `station_id = c(8, 37)`) or as character vector with the prefix "az" and 2
#' digits (e.g. `station_id = c("az08", "az37")`) If left blank data for all
#' stations will be returned
#' @param start_date_time A length 1 vector of class POSIXct or character in
#' @param start_date_time A length-1 vector of class POSIXct or character in
#' YYYY-MM-DD HH format, in AZ time. Will be rounded **down** to the nearest
#' hour if more precision is supplied. If only a date (YYYY-MM-DD) is
#' supplied, data will be requested starting at 01:00:00 of that day
#' @param end_date_time A length 1 vector of class POSIXct or character in
#' @param end_date_time A length-1 vector of class POSIXct or character in
#' YYYY-MM-DD HH format, in AZ time. Will be rounded **down** to the nearest
#' hour if more precision is supplied. If only a date (YYYY-MM-DD) is
#' supplied, data will be requested through the *end* of that day (23:59:59).
Expand All @@ -28,7 +28,7 @@
#' take considerable time.
#' @return a tibble. For units and other metadata, see
#' <https://ag.arizona.edu/azmet/raw2003.htm>
#' @seealso [az_daily()], [az_heat()]
#' @seealso [az_15min()], [az_daily()], [az_heat()], [az_lw15min()]
#' @source <https://ag.arizona.edu/azmet/>
#' @importFrom rlang .data
#' @export
Expand Down
169 changes: 169 additions & 0 deletions R/az_lw15min.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,169 @@
#' Retrieve 15-minute Leaf Wetness Data from AZMet
#'
#' Retrieves 15-minute leaf-wetness data from the AZMet (Arizona Meteorological
#' Network) API. Currently, these data only are available from stations in the
#' Yuma area. For a list of stations and their locations see [station_info].
#'
#' @param station_id Station ID can be supplied as numeric vector (e.g.
#' `station_id = c(8, 37)`) or as character vector with the prefix "az" and
#' two digits (e.g. `station_id = c("az08", "az37")`). If left blank, data for
#' all stations will be returned.
#' @param start_date_time A length-1 vector of class POSIXct or character in
#' YYYY-MM-DD HH:MM:SS format, in AZ time. If only a date (YYYY-MM-DD) is
#' supplied, data will be requested starting at 00:00:01 of that day.
#' @param end_date_time A length-1 vector of class POSIXct or character in
#' YYYY-MM-DD HH:MM:SS format, in AZ time. If only a date (YYYY-MM-DD) is
#' supplied, data will be requested through the *end* of that day (23:59:59).
#' Defaults to the current date and time if left blank and `start_date_time`
#' is specified.
#' @details If neither `start_date_time` nor `end_date_time` are supplied, the
#' most recent date-time of data will be returned. If only `start_date_time`
#' is supplied, then `end_date_time` defaults to the current time. Supplying
#' only `end_date_time` will result in an error.
#' @note If `station_id` is supplied as a vector, multiple successive calls to
#' the API will be made. You may find better performance getting data for all
#' the stations by leaving `station_id` blank and subsetting the resulting
#' dataframe. Only the most recent 48 hours of 15-minute data are stored in
#' the AZMet API.
#' @return a tibble. For units and other metadata, see
#' <https://azmet.arizona.edu/about>
#' @seealso [az_15min()], [az_daily()], [az_heat()], [az_hourly()]
#' @source <https://azmet.arizona.edu/>
#' @importFrom rlang .data
#' @export
#'
#' @examples
#' \dontrun{
#' # Most recent 15-minute leaf-wetness data for all stations:
#' az_lw15min()
#'
#' # Specify stations:
#' az_lw15min(station_id = c(1, 2))
#' az_lw15min(station_id = c("az01", "az02"))
#'
#' # Specify dates:
#' az_lw15min(start_date_time = "2022-09-25 01:00:00")
#' az_lw15min(start_date_time = "2022-09-25 01:00:00", end_date_time = "2022-09-25 07:00:00")
#' }


az_lw15min <- function(station_id = NULL, start_date_time = NULL, end_date_time = NULL) {

# TODO: check for valid station IDs

check_internet()

if (!is.null(end_date_time) & is.null(start_date_time)) {
stop("If you supply `end_date_time`, you must also supply `start_date_time`.")
}

params <-
parse_params(
station_id = station_id,
start = start_date_time,
end = end_date_time,
hour = FALSE,
real_time = TRUE
)

tz <- "America/Phoenix"


# Query API ------------------------------------------------------------------

if (is.null(start_date_time) & is.null(end_date_time)) {
message("Querying most recent date-time of leaf wetness 15-minute data ...")
} else {
message(
"Querying data from ", format(params$start, "%Y-%m-%d %H:%M:%S")," through ", format(params$end, "%Y-%m-%d %H:%M:%S", " ...")
)
}

if (length(station_id) <= 1) {
out <-
retrieve_data(
params$station_id,
params$start_f,
params$time_interval,
endpoint = "lw15min"
)
} else if (length(station_id) > 1) {
out <-
purrr::map_df(
params$station_id,
function(x) {
retrieve_data(
x,
params$start_f,
params$time_interval,
endpoint = "lw15min"
)
}
)
}

# If the most recent date-time is queried, make sure only one date-time is
# returned per station
if (is.null(start_date_time) & is.null(end_date_time)) {
out <-
out %>%
dplyr::filter(.data$datetime == max(.data$datetime), .by = "meta_station_id")
}

if (nrow(out) == 0) {
warning("No data retrieved from API.")
# Return 0x0 tibble
return(tibble::tibble())
}

# Check if any data are missing. Note, this always "passes" when both start and
# end are NULL (because period("*") is NA)
#n_obs <- out %>%
# dplyr::summarise(n = dplyr::n(), .by = dplyr::all_of("meta_station_id")) %>%
# dplyr::filter(.data$n < as.numeric(lubridate::period(params$time_interval), "hour"))
#if (nrow(n_obs) != 0) {
# warning("Some requested data were unavailable.")
#}

# Warn if the missing data are just at the end
if (lubridate::ymd_hms(max(out$datetime), tz = tz) < params$end) {
warning(
"You requested data through ", params$end, " but only data through ", max(out$datetime), " were available."
)
}


# Wrangle output -------------------------------------------------------------

out <- out %>%
# Move metadata to beginning
dplyr::select(dplyr::starts_with("meta_"), dplyr::everything()) %>%
dplyr::mutate(dplyr::across(
c(-"meta_station_id", -"meta_station_name", -"date_hour", -"datetime"),
as.numeric
)) %>%
dplyr::filter(.data$meta_station_id != "az99") %>%
dplyr::mutate(
datetime = lubridate::force_tz(
lubridate::ymd_hms(.data$datetime),
tzone = tz
)
) %>%
# Convert NAs
dplyr::mutate(
dplyr::across(
tidyselect::where(is.numeric),
function(x)
dplyr::if_else(x %in% c(-999, -9999, -99999, -7999, 999, 999.9, 9999), NA_real_, x)
)
)

if (length(unique(out$datetime)) == 1) {
message("Returning data from ", format(unique(out$datetime), "%Y-%m-%d %H:%M:%S"))
} else {
message(
"Returning data from ", format(min(out$datetime), "%Y-%m-%d %H:%M:%S"), " through ", format(max(out$datetime), "%Y-%m-%d %H:%M:%S"))
}

return(out)
}
4 changes: 2 additions & 2 deletions R/parse_params.R
Original file line number Diff line number Diff line change
Expand Up @@ -133,7 +133,7 @@ parse_params <- function(station_id, start, end, hour = FALSE, real_time = FALSE
} else if (isTRUE(real_time)) { # 15min data
parse_fun <- function(x, end = FALSE) {
lubridate::parse_date_time(x, orders = c("YmdHMS", "YmdHM", "YmdH", "Ymd"), tz = tz) %>%
lubridate::floor_date(unit = "min")
lubridate::floor_date(unit = "secs")
}
} else { # Daily data
parse_fun <- function(x, end = FALSE) {
Expand Down Expand Up @@ -220,7 +220,7 @@ parse_params <- function(station_id, start, end, hour = FALSE, real_time = FALSE
if (is.null(start)) {
time_interval <- "*"
} else {
end_rounded <- lubridate::round_date(end_parsed, "hour")
end_rounded <- lubridate::round_date(end_parsed, unit = "hour")
start_rounded <- lubridate::round_date(start_parsed, unit = "hour")
d <- lubridate::as.period(end_rounded - start_rounded)
time_interval <- lubridate::format_ISO8601(d)
Expand Down
2 changes: 1 addition & 1 deletion R/retrieve_data.R
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ retrieve_data <-
station_id,
start_f,
time_interval,
endpoint = c("daily", "hourly", "hueto", "15min"),
endpoint = c("15min", "daily", "hourly", "hueto", "lw15min"),
print_call = getOption("azmet.print_api_call")
) {

Expand Down
6 changes: 3 additions & 3 deletions man/az_15min.Rd

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

Loading

0 comments on commit d78c3ea

Please sign in to comment.