Skip to content

Commit

Permalink
add cities endpoint; fix pbservations
Browse files Browse the repository at this point in the history
  • Loading branch information
dwu0042 committed May 29, 2024
1 parent 53819de commit bf7f52e
Show file tree
Hide file tree
Showing 2 changed files with 103 additions and 52 deletions.
34 changes: 33 additions & 1 deletion R/client.R
Original file line number Diff line number Diff line change
Expand Up @@ -61,10 +61,42 @@ get_measurements_for_location <- function(
collate_paginated_output(
endpoint = "measurements",
query_params = query_params,
max_pbservations = max_observations,
pagination_size = max_observations,
response_parser = get_measures
)

}


get_cities <- function(
country = NULL,
max_observations = 1000,
...
) {

assertthat::assert_that(inherits(country, "character") | is.null(country))

country <- restify_vector(country)

additional_args <- list(...)
parsed_args <- lapply(seq_along(additional_args), function(i) {
restify_vector(input = additional_args[[i]], name = names(additional_args)[i])
})
names(parsed_args) <- names(additional_args)

query_params <- list(
country = country,
limit = as.character(max_observations)
)

query_params <- modifyList(query_params, parsed_args)

collate_paginated_output(
endpoint = "cities",
query_params = query_params,
pagination_size = = max_observations,
response_parser = get_cities
)


}
121 changes: 70 additions & 51 deletions R/data_processing.R
Original file line number Diff line number Diff line change
@@ -1,54 +1,3 @@
#' Get Air Quality Measures
#'
#' This function extracts air quality measures from a parsed API response.
#'
#' @param req_cont A list containing the parsed API response. The location data
#' should be stored in the second element of this list.
#'
#' @return A tibble containing air quality measures with columns for location ID,
#' location name, parameter name, measured value, date and time of measurement
#' (in UTC), unit of measurement, latitude, longitude, country, and city.
#'
#' @importFrom tibble tibble
#' @importFrom purrr map_dfr
#' @importFrom lubridate ymd_hms
#'
#' @examples
#' # Sample usage:
#' library(tibble)
#' library(purrr)
#' library(lubridate)
#'
#' # Sample parsed API response
#' req_cont <- content(response, "parsed")
#'
#' # Get air quality measures
#' measures <- get_measures(req_cont)
#'

get_measures <- function(req_cont) {

# To obtain the response
locations_list <- req_cont[[2]]

# Extract data from locations_list and combine into air_df
air_df <- locations_list |>
map_dfr(~ tibble(
location_id = .x$locationId,
location = .x$location,
parameter = .x$parameter,
value = .x$value,
date_utc = ymd_hms(.x$date$utc),
unit = .x$unit,
lat = .x$coordinates$latitude,
long = .x$coordinates$longitude,
country = .x$country,
city = .x$city
))

return(air_df)

}

#' Collate paginated output for a given query
#'
Expand Down Expand Up @@ -109,4 +58,74 @@ collate_paginated_output <- function(
}

do.call(rbind, output_list)
}


#' Get Air Quality Measures
#'
#' This function extracts air quality measures from a parsed API response.
#'
#' @param req_cont A list containing the parsed API response. The location data
#' should be stored in the second element of this list.
#'
#' @return A tibble containing air quality measures with columns for location ID,
#' location name, parameter name, measured value, date and time of measurement
#' (in UTC), unit of measurement, latitude, longitude, country, and city.
#'
#' @importFrom tibble tibble
#' @importFrom purrr map_dfr
#' @importFrom lubridate ymd_hms
#'
#' @examples
#' # Sample usage:
#' library(tibble)
#' library(purrr)
#' library(lubridate)
#'
#' # Sample parsed API response
#' req_cont <- content(response, "parsed")
#'
#' # Get air quality measures
#' measures <- get_measures(req_cont)
#'

get_measures <- function(req_cont) {

# To obtain the response
measurements_list <- req_cont[[2]]

# Extract data from locations_list and combine into air_df
air_df <- measurements_list |>
map_dfr(~ tibble(
location_id = .x$locationId,
location = .x$location,
parameter = .x$parameter,
value = .x$value,
date_utc = ymd_hms(.x$date$utc),
unit = .x$unit,
lat = .x$coordinates$latitude,
long = .x$coordinates$longitude,
country = .x$country,
city = .x$city
))

return(air_df)

}


get_cities <- function(req_cont) {

# Extract out the results part of the response
cities_info <- req_cont[[2]]

# Map this to a tibble
cities_df <- cities_info |>
map_dfr(~ tibble(
city = .x$city,
country = .x$country,
locations = .x$locations
))

return(cities_df)
}

0 comments on commit bf7f52e

Please sign in to comment.