Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
1 change: 1 addition & 0 deletions .Rbuildignore
Original file line number Diff line number Diff line change
Expand Up @@ -4,3 +4,4 @@
^azkit\.code-workspace$
^CODEOWNERS$
^\.github$
^\.lintr$
3 changes: 1 addition & 2 deletions R/get_auth_token.R
Original file line number Diff line number Diff line change
Expand Up @@ -131,8 +131,7 @@ get_auth_token <- function(
)
invisible(NULL)
} else {
# check_that(token, AzureAuth::is_azure_token, "Invalid token returned")
token
check_that(token, AzureAuth::is_azure_token, "Invalid token returned")
}
}

Expand Down
55 changes: 32 additions & 23 deletions R/get_container.R
Original file line number Diff line number Diff line change
@@ -1,56 +1,65 @@
#' Get Azure storage container
#'
#' The environment variable "AZ_STORAGE_EP" must be set. This provides the URL
#' The environment variable "AZ_STORAGE_EP" should be set. This provides the URL
#' for the default Azure storage endpoint.
#' Use [list_container_names] to get a list of available container names.
#'
#' @param container_name Name of the container as a string. `NULL` by default,
#' which means the function will look instead for a container name stored in
#' the environment variable "AZ_CONTAINER"
#' @param ... arguments to be passed through to [get_auth_token]
#' @param token An Azure authentication token. If left as `NULL`, a token
#' returned by [get_auth_token] will be used
#' @param endpoint_url An Azure endpoint URL. If left as `NULL`, the default,
#' the value of the environment variable "AZ_STORAGE_EP" will be used
#' @param ... arguments to be passed through to [get_auth_token], if a token is
#' not already supplied
#' @returns An Azure blob container (list object of class "blob_container")
#' @export
get_container <- function(container_name = NULL, ...) {
msg <- glue::glue(
get_container <- function(
container_name = NULL,
token = NULL,
endpoint_url = NULL,
...
) {
msg <- paste0(
"{.var container_name} is empty. ",
"Did you forget to set an environment variable?"
)
cont_nm <- check_nzchar(container_name, msg) %||% check_envvar("AZ_CONTAINER")
token <- get_auth_token(...)
endpoint <- get_default_endpoint(token)
container_names <- list_container_names(token)
not_found_msg <- ct_error_msg("Container {.val {cont_nm}} not found")
cont_nm |>
check_that(\(x) x %in% container_names, not_found_msg) |>
AzureStor::blob_container(endpoint = endpoint)
container_name <- (container_name %||% check_envvar("AZ_CONTAINER")) |>
check_nzchar(msg)
token <- token %||% get_auth_token(...)

get_azure_endpoint(token, endpoint_url) |>
AzureStor::blob_container(container_name)
}


#' Return a list of container names that are found at the default endpoint
#' Return a list of container names that are found at the endpoint
#'
#' @inheritParams get_container
#' @inheritParams get_default_endpoint
#' @returns A character vector of all container names found
#' @export
list_container_names <- function(token = NULL, ...) {
list_container_names <- function(token = NULL, endpoint_url = NULL, ...) {
token <- token %||% get_auth_token(...)
endpoint <- get_default_endpoint(token)
lcn <- "list_container_names" # nolint
container_list <- AzureStor::list_blob_containers(endpoint) |>
rlang::try_fetch(error = \(e) cli::cli_abort("Error in {.fn {lcn}}: {e}"))
endpoint <- get_azure_endpoint(token, endpoint_url)
container_list <- AzureStor::list_blob_containers(endpoint)
stopifnot("no containers found" = length(container_list) >= 1L)
names(container_list)
}


#' Return an Azure "blob_endpoint"
#'
#' @param token An Azure authentication token
#' This function will return the endpoint specified in the environment variable
#' "AZ_STORAGE_EP" by default
#'
#' @inheritParams get_container
#' @returns An Azure blob endpoint (object of class "blob_endpoint")
#' @keywords internal
get_default_endpoint <- function(token) {
check_envvar("AZ_STORAGE_EP") |>
AzureStor::blob_endpoint(token = token)
get_azure_endpoint <- function(token = NULL, endpoint_url = NULL, ...) {
token <- token %||% get_auth_token(...)
endpoint_url <- endpoint_url %||% check_envvar("AZ_STORAGE_EP")
AzureStor::blob_endpoint(endpoint_url, token = token)
}


Expand Down
2 changes: 1 addition & 1 deletion R/read_azure_files.R
Original file line number Diff line number Diff line change
Expand Up @@ -129,7 +129,7 @@ check_blob_exists <- function(container, file, ext, info, path) {
# though this usage pattern should be quite rare!
dpath <- file.path(path, dir_name)
fname <- basename(file)
if (nzchar(ext) & !gregg(fname, "\\.{ext}$")) {
if (nzchar(ext) && !gregg(fname, "\\.{ext}$")) {
fname <- glue::glue("{fname}.{ext}")
}
# remove duplicate slashes and any initial slashes
Expand Down
2 changes: 1 addition & 1 deletion man/check_scalar_type.Rd

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

2 changes: 1 addition & 1 deletion man/check_vec.Rd

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

26 changes: 26 additions & 0 deletions man/get_azure_endpoint.Rd

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

13 changes: 10 additions & 3 deletions man/get_container.Rd

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

18 changes: 0 additions & 18 deletions man/get_default_endpoint.Rd

This file was deleted.

15 changes: 10 additions & 5 deletions man/list_container_names.Rd

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

2 changes: 1 addition & 1 deletion man/read_azure_csv.Rd

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

2 changes: 1 addition & 1 deletion man/read_azure_file.Rd

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

2 changes: 1 addition & 1 deletion man/read_azure_json.Rd

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

2 changes: 1 addition & 1 deletion man/read_azure_jsongz.Rd

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

2 changes: 1 addition & 1 deletion man/read_azure_parquet.Rd

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

2 changes: 1 addition & 1 deletion man/read_azure_rds.Rd

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