Skip to content

Commit

Permalink
refactor: rethrow errors from native_cmd
Browse files Browse the repository at this point in the history
  • Loading branch information
luciorq committed Dec 10, 2024
1 parent 9e3b06b commit b0b3d6e
Show file tree
Hide file tree
Showing 11 changed files with 189 additions and 76 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Package: condathis
Title: Run Any CLI Tool on a 'Conda' Environment
Version: 0.0.7.9010
Version: 0.0.7.9011
Authors@R: c(
person("Lucio", "Queiroz", , "[email protected]", role = c("aut", "cre", "cph"),
comment = c(ORCID = "0000-0002-6090-1834")),
Expand Down
36 changes: 20 additions & 16 deletions R/create_env.R
Original file line number Diff line number Diff line change
Expand Up @@ -156,22 +156,26 @@ create_env <- function(

quiet_flag <- parse_quiet_flag(verbose = verbose)

px_res <- native_cmd(
conda_cmd = "create",
conda_args = c(
"-n",
env_name,
"--yes",
quiet_flag,
"--no-channel-priority",
"--override-channels",
"--channel-priority=0",
channels_arg,
platform_args
),
packages_arg,
verbose = verbose,
error = "cancel"
px_res <- rethrow_error_cmd(
expr = {
native_cmd(
conda_cmd = "create",
conda_args = c(
"-n",
env_name,
"--yes",
quiet_flag,
"--no-channel-priority",
"--override-channels",
"--channel-priority=0",
channels_arg,
platform_args
),
packages_arg,
verbose = verbose,
error = "cancel"
)
}
)
}
if (isTRUE(verbose %in% c("full", "output"))) {
Expand Down
32 changes: 18 additions & 14 deletions R/install_packages.R
Original file line number Diff line number Diff line change
Expand Up @@ -45,20 +45,24 @@ install_packages <- function(packages,
additional_channels,
channels
)
px_res <- native_cmd(
conda_cmd = "install",
conda_args = c(
"-n",
env_name,
"--yes",
quiet_flag,
"--no-channel-priority",
"--override-channels",
"--channel-priority=0",
channels_arg
),
packages,
verbose = verbose
px_res <- rethrow_error_cmd(
expr = {
native_cmd(
conda_cmd = "install",
conda_args = c(
"-n",
env_name,
"--yes",
quiet_flag,
"--no-channel-priority",
"--override-channels",
"--channel-priority=0",
channels_arg
),
packages,
verbose = verbose
)
}
)

if (isTRUE(verbose %in% c("full", "output") && length(packages) > 0L)) {
Expand Down
20 changes: 12 additions & 8 deletions R/list_envs.R
Original file line number Diff line number Diff line change
Expand Up @@ -33,14 +33,18 @@
#' @export
list_envs <- function(verbose = "silent") {
env_root_dir <- get_install_dir()
px_res <- native_cmd(
conda_cmd = "env",
conda_args = c(
"list",
"-q",
"--json"
),
verbose = verbose
px_res <- rethrow_error_cmd(
expr = {
native_cmd(
conda_cmd = "env",
conda_args = c(
"list",
"-q",
"--json"
),
verbose = verbose
)
}
)
if (isTRUE(px_res$status == 0)) {
envs_list <- jsonlite::fromJSON(px_res$stdout)
Expand Down
22 changes: 13 additions & 9 deletions R/list_packages.R
Original file line number Diff line number Diff line change
Expand Up @@ -44,15 +44,19 @@ list_packages <- function(env_name = "condathis-env", verbose = "silent") {
)
}
quiet_flag <- parse_quiet_flag(verbose = verbose)
px_res <- native_cmd(
conda_cmd = "list",
conda_args = c(
"-n",
env_name,
quiet_flag,
"--json"
),
verbose = verbose
px_res <- rethrow_error_cmd(
expr = {
native_cmd(
conda_cmd = "list",
conda_args = c(
"-n",
env_name,
quiet_flag,
"--json"
),
verbose = verbose
)
}
)
if (isTRUE(px_res$status == 0)) {
pkgs_df <- jsonlite::fromJSON(px_res$stdout)
Expand Down
24 changes: 14 additions & 10 deletions R/remove_env.R
Original file line number Diff line number Diff line change
Expand Up @@ -32,16 +32,20 @@ remove_env <- function(env_name = "condathis-env",
)
}
quiet_flag <- parse_quiet_flag(verbose = verbose)
px_res <- native_cmd(
conda_cmd = "env",
conda_args = c(
"remove",
"-n",
env_name,
"--yes",
quiet_flag
),
verbose = verbose
px_res <- rethrow_error_cmd(
expr = {
native_cmd(
conda_cmd = "env",
conda_args = c(
"remove",
"-n",
env_name,
"--yes",
quiet_flag
),
verbose = verbose
)
}
)
if (isTRUE(verbose %in% c("full", "output"))) {
cli::cli_inform(
Expand Down
41 changes: 41 additions & 0 deletions R/rethrow_error_cmd.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,41 @@
#' @keywords internal
#' @noRd
rethrow_error_cmd <- function(expr, env = parent.frame()) {
code <- base::substitute(expr = expr)
err_cnd <- rlang::catch_cnd(
expr = {
px_res <- rlang::eval_bare(expr = code, env = env)
},
classes = c("system_command_status_error", "rlib_error_3_0", "c_error")
)

if (isFALSE(is.null(err_cnd))) {
additional_lines <- NULL
if (isTRUE("stderr" %in% names(err_cnd))) {
additional_lines <- stringr::str_split(
string = stringr::str_trim(err_cnd[["stderr"]]),
pattern = stringr::regex("\\R"),
simplify = FALSE
)[[1]]
}

status_code <- NULL
if (isFALSE("status" %in% names(err_cnd))) {
status_code <- "127"
additional_lines <- c("micromamba: command not found", additional_lines)
} else {
status_code <- err_cnd[["status"]]
}

env[["status_code"]] <- status_code
cli::cli_abort(
message = c(
additional_lines
),
class = "condathis_cmd_status_error",
.envir = env
)
}

return(px_res)
}
43 changes: 43 additions & 0 deletions R/rethrow_error_run.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,43 @@
#' @keywords internal
#' @noRd
rethrow_error_run <- function(expr, env = parent.frame()) {
code <- base::substitute(expr = expr)
err_cnd <- rlang::catch_cnd(
expr = {
px_res <- rlang::eval_bare(expr = code, env = env)
},
classes = c("system_command_status_error", "rlib_error_3_0", "c_error")
)

if (isFALSE(is.null(err_cnd))) {
additional_lines <- NULL
if (isTRUE("stderr" %in% names(err_cnd))) {
additional_lines <- stringr::str_split(
string = stringr::str_trim(err_cnd[["stderr"]]),
pattern = stringr::regex("\\R"),
simplify = FALSE
)[[1]]
}

status_code <- NULL
if (isFALSE("status" %in% names(err_cnd))) {
status_code <- "127"
additional_lines <- c("{cmd}: command not found", additional_lines)
} else {
status_code <- err_cnd[["status"]]
}

env[["status_code"]] <- status_code
cli::cli_abort(
message = c(
`x` = "System command {.field {cmd}} failed",
`!` = "Status code: {status_code}",
additional_lines
),
class = "condathis_run_status_error",
.envir = env
)
}

return(px_res)
}
20 changes: 12 additions & 8 deletions R/run.R
Original file line number Diff line number Diff line change
Expand Up @@ -90,14 +90,18 @@ run <- function(cmd,
method_to_use <- method[1]

if (isTRUE(method_to_use %in% c("native", "auto"))) {
px_res <- run_internal_native(
cmd = cmd,
...,
env_name = env_name,
verbose = verbose,
error = error,
stdout = stdout,
stderr = stderr
px_res <- rethrow_error_run(
expr = {
run_internal_native(
cmd = cmd,
...,
env_name = env_name,
verbose = verbose,
error = error,
stdout = stdout,
stderr = stderr
)
}
)
}
return(invisible(px_res))
Expand Down
23 changes: 14 additions & 9 deletions R/run_bin.R
Original file line number Diff line number Diff line change
Expand Up @@ -88,15 +88,20 @@ run_bin <- function(
args_vector <- character(length = 0L)
}

px_res <- processx::run(
command = cmd_path,
args = args_vector,
spinner = spinner_flag,
echo_cmd = verbose_cmd,
echo = verbose_output,
stdout = stdout,
stderr = stderr,
error_on_status = error_var
px_res <- rethrow_error_run(
expr = {
processx::run(
command = cmd_path,
args = args_vector,
spinner = spinner_flag,
echo_cmd = verbose_cmd,
echo = verbose_output,
stdout = stdout,
stderr = stderr,
error_on_status = error_var
)
}
)

return(invisible(px_res))
}
2 changes: 1 addition & 1 deletion tests/testthat/test-create_env.R
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ testthat::test_that("conda env is created", {
error = "cancel"
)
},
class = "rlib_error"
class = "condathis_run_status_error"
)

run_res <- run(
Expand Down

0 comments on commit b0b3d6e

Please sign in to comment.