This commit is contained in:
Alex Kyllo 2022-10-10 22:34:59 -07:00
Родитель 6505f453da
Коммит 84d66a9fb6
4 изменённых файлов: 45 добавлений и 44 удалений

Просмотреть файл

@ -301,7 +301,7 @@ AzureTokenCLI <- R6::R6Class("AzureTokenCLI",
{
tryCatch(
{
cmd <- build_access_token_cmd(
cmd <- build_az_token_cmd(
resource = self$resource,
tenant = self$tenant
)

Просмотреть файл

@ -240,7 +240,7 @@
#'
#' }
#' @export
get_azure_token <- function(resource, tenant, app, password=NULL, username=NULL, certificate=NULL, auth_type=NULL,
get_azure_token <- function(resource, tenant, app=NULL, password=NULL, username=NULL, certificate=NULL, auth_type=NULL,
aad_host="https://login.microsoftonline.com/", version=1,
authorize_args=list(), token_args=list(),
use_cache=NULL, on_behalf_of=NULL, auth_code=NULL, device_creds=NULL)
@ -281,7 +281,7 @@ get_azure_token <- function(resource, tenant, app, password=NULL, username=NULL,
#' @param confirm For `delete_azure_token`, whether to prompt for confirmation before deleting a token.
#' @rdname get_azure_token
#' @export
delete_azure_token <- function(resource, tenant, app, password=NULL, username=NULL, certificate=NULL, auth_type=NULL,
delete_azure_token <- function(resource, tenant, app=NULL, password=NULL, username=NULL, certificate=NULL, auth_type=NULL,
aad_host="https://login.microsoftonline.com/", version=1,
authorize_args=list(), token_args=list(), on_behalf_of=NULL,
hash=NULL, confirm=TRUE)
@ -346,7 +346,7 @@ list_azure_tokens <- function()
#' @rdname get_azure_token
#' @export
token_hash <- function(resource, tenant, app, password=NULL, username=NULL, certificate=NULL, auth_type=NULL,
token_hash <- function(resource, tenant, app = NULL, password=NULL, username=NULL, certificate=NULL, auth_type=NULL,
aad_host="https://login.microsoftonline.com/", version=1,
authorize_args=list(), token_args=list(), on_behalf_of=NULL)
{

Просмотреть файл

@ -172,10 +172,12 @@ build_az_token_cmd <- function(command = "az", resource, tenant)
handle_az_cmd_errors <- function(cond)
{
not_found <- grepl("not found", cond, fixed = TRUE)
not_loggedin <- grepl("az login", cond, fixed = TRUE) |
grepl("az account set", cond, fixed = TRUE)
if (not_found)
not_found <- grepl("not found", cond, fixed = TRUE)
error_in <- grepl("error in running", cond, fixed = TRUE)
if (not_found | error_in)
{
msg <- paste("az is not installed or not in PATH.\n",
"Please see: ",
@ -186,7 +188,9 @@ handle_az_cmd_errors <- function(cond)
}
else if (not_loggedin)
{
stop("You are not logged into the Azure CLI. Please run 'az login' and try again.")
stop("You are not logged into the Azure CLI.
Please call AzureAuth::az_login()
or run 'az login' from your shell and try again.")
}
else
{
@ -196,6 +200,25 @@ handle_az_cmd_errors <- function(cond)
}
}
capt <- function(...) {
print(list(...))
print("a" %in% list(...))
}
az_login <- function(command = "az",...)
{
args <- list(...)
cmdargs <- list(command = command, args = c("login"))
for (arg in c("username", "password", "tenant", "scope",
"service_principal", "use_device_code")) {
if (arg %in% names(args))
cmdargs$args <- c(cmdargs$args, paste0("--", arg, " ", args[arg]))
}
cat("Trying to open a web browser to log into Azure CLI...\n")
cat(cmdargs$command, paste(cmdargs$args), "\n")
do.call(system2, cmdargs)
}
execute_az_token_cmd <- function(cmd)
{
tryCatch(
@ -204,10 +227,14 @@ execute_az_token_cmd <- function(cmd)
# result is a multi-line JSON string, concatenate together
paste0(result)
},
warning = function(cond)
warning = function()
{
# if an error case, catch it, pass the error string and handle it
handle_az_cmd_errors(cond)
handle_az_cmd_errors(result)
},
error = function(cond)
{
handle_az_cmd_errors(cond$message)
}
)
}

Просмотреть файл

@ -38,7 +38,6 @@ test_that("az account command is assembled properly even if missing tenant",
)
})
test_that("az account command is assembled properly even if missing resource",
{
tenant <- "microsoft.com"
@ -100,14 +99,8 @@ test_that("the token data from az login is handled by AzureTokenCLI",
test_that("the appropriate error is thrown when the az CLI is not installed",
{
expect_error(
execute_az_token_cmd(
build_az_token_cmd(
"bnrwfq", # pass a different command name that is unlikely to exist
resource = "foo",
tenant = "bar"
)
),
regexp = "bnrwfq is not installed."
handle_az_cmd_errors("error in running command"),
regexp = "az is not installed or not in PATH."
)
})
@ -124,36 +117,17 @@ test_that("invalid scope error is handled", {
"To re-authenticate, please run:\n",
"az login --scope my_resource/.default"
)
expect_error(, regexp = "")
expect_error(handle_az_cmd_errors(msg))
})
if (Sys.which("az") == "")
skip("az not installed, skipping tests.")
# cond <- system2("az", args = c("account show"), stdout = TRUE)
# not_loggedin <- grepl("az login", cond, fixed = TRUE) |
# grepl("az account set", cond, fixed = TRUE)
# if (not_loggedin)
# skip("az not logged in, skipping tests.")
test_that("the appropriate error is thrown when the resource is invalid",
test_that("the appropriate error is thrown when the tenant is invalid",
{
fail("TODO")
errmsg <- "Failed to resolve tenant 'faketenant'"
expect_error(handle_az_cmd_errors(errmsg), regexp = "Failed to resolve tenant")
})
test_that("the appropriate error is thrown when az login fails",
test_that("the appropriate error is thrown when the user is not logged in",
{
fail("TODO")
errmsg <- "ERROR: Please run 'az login' to setup account."
expect_error(handle_az_cmd_errors(errmsg), regexp = "You are not logged in")
})
test_that("az login is called if the user is not already logged in",
{
fail("TODO")
})
test_that("token is successfully retrieved if user is logged in",
{
fail("TODO")
})