Skip to content

Commit

Permalink
make purple_air_request return only the request, not perform it
Browse files Browse the repository at this point in the history
  • Loading branch information
cole-brokamp committed Jul 6, 2024
1 parent cac4a8c commit fc32751
Show file tree
Hide file tree
Showing 4 changed files with 17 additions and 16 deletions.
6 changes: 4 additions & 2 deletions R/check_api_key.R
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
#' check purple air api key
#'
#'
#' Use the PurpleAir API to validate your Purple Air API Key.
#' Find more details on this function at https://api.purpleair.com/#api-keys-check-api-key
#' @param purple_air_api_key A character that is your PurpleAir API `READ` key
Expand All @@ -15,7 +15,9 @@ check_api_key <- function(purple_air_api_key = Sys.getenv("PURPLE_AIR_API_KEY"))
purple_air_api_key = purple_air_api_key,
resource = "keys",
success_code = as.integer(201)
)
) |>
httr2::req_perform() |>
httr2::resp_body_json()
# TODO add check that is must be a `READ` type key?
cli::cli_alert_success("Using valid '{resp$api_key_type}' key with version {resp$api_version} of the PurpleAir API on {as.POSIXct(resp$time_stamp)}")
return(invisible(purple_air_api_key))
Expand Down
10 changes: 6 additions & 4 deletions R/get_sensor_data.R
Original file line number Diff line number Diff line change
Expand Up @@ -21,8 +21,10 @@ get_sensor_data <- function(sensor_index, fields, purple_air_api_key = Sys.geten
sensor_index = as.integer(sensor_index),
fields = fields,
read_key = read_key
)
resp$sensor$sensor_index <- NULL
if ("last_seen" %in% names(resp$sensor)) resp$sensor$last_seen <- as.POSIXct.numeric(resp$sensor$last_seen)
return(resp$sensor)
) |>
httr2::req_perform()
out <- httr2::resp_body_json(resp)$sensor
out$sensor_index <- NULL
if ("last_seen" %in% names(out)) out$last_seen <- as.POSIXct.numeric(out$last_seen)
return(out)
}
4 changes: 3 additions & 1 deletion R/get_sensors_data.R
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,9 @@ get_sensors_data <- function(x, fields, location_type = c("both", "inside", "out
success_code = as.integer(200),
fields = fields,
read_keys = read_keys
)
) |>
httr2::req_perform() |>
httr2::resp_body_json()
out <-
purrr::map(resp$data, stats::setNames, resp$fields) |>
purrr::modify(as.data.frame) |>
Expand Down
13 changes: 4 additions & 9 deletions R/purple_air_request.R
Original file line number Diff line number Diff line change
@@ -1,30 +1,25 @@
purple_air_request <- function(purple_air_api_key = Sys.getenv("PURPLE_AIR_API_KEY"), resource = c("keys", "sensors", "sensor_history"), sensor_index = NULL, success_code, ...) {
purple_air_request <- function(purple_air_api_key = Sys.getenv("PURPLE_AIR_API_KEY"), resource = c("keys", "organization", "sensors", "sensor_history"), sensor_index = NULL, success_code, ...) {
if (!rlang::is_integer(success_code)) cli::cli_abort("success_code must be an integer")
resource <- rlang::arg_match(resource)
req <-
httr2::request("https://api.purpleair.com/v1") |>
httr2::req_user_agent("PurpleAir (https://github.com/cole-brokamp/PurpleAir)") |>
httr2::req_user_agent("PurpleAir package for R (https://github.com/cole-brokamp/PurpleAir)") |>
httr2::req_headers("X-API-Key" = purple_air_api_key, .redact = "X-API-Key") |>
httr2::req_error(
is_error = \(resp) httr2::resp_status(resp) != success_code,
body = \(resp) glue::glue_data(httr2::resp_body_json(resp), "{error}: {description} (API version: {api_version})")
) |>
httr2::req_url_query(!!!list(...), .multi = "comma")

if (resource == "keys") req <- httr2::req_url_path_append(req, "keys")
if (resource == "organization") req <- httr2::req_url_path_append(req, "organization")
if (resource == "sensors") {
req <- httr2::req_url_path_append(req, "sensors")
if (!is.null(sensor_index)) {
req <- httr2::req_url_path_append(req, sensor_index)
}
}
if (resource == "sensor_history") req <- httr2::req_url_path_append(req, "sensors", sensor_index, "history")

resp <-
req |>
httr2::req_perform() |>
httr2::resp_body_json()
return(resp)
return(req)
}

# https://api.purpleair.com/#api-sensors-get-sensor-data

0 comments on commit fc32751

Please sign in to comment.