@@ -95,13 +95,13 @@ launch_remote <- function(n = 1L, remote = remote_config(), ..., tls = NULL, .co
9595 if (is.null(tls )) tls <- envir [[" tls" ]]
9696
9797 if (length(remote ) == 2L ) {
98- requireNamespace( " rstudioapi " , quietly = TRUE ) || stop( ._ [[ " rstudio_api " ]] )
99- rstudioapi :: launcherAvailable( )
98+ submit_job <- .subset2(rstudio(), " .rs.api.launcher.submitJob " )
99+ new_container <- .subset2(rstudio(), " .rs.api.launcher.newContainer " )
100100 cluster <- remote [[" name" ]]
101- container <- rstudioapi :: launcherContainer (remote [[" image" ]])
101+ container <- new_container (remote [[" image" ]])
102102 lapply(
103103 seq_len(n ),
104- function (x ) rstudioapi :: launcherSubmitJob (
104+ function (x ) submit_job (
105105 sprintf(" mirai_daemon_%d" , x ),
106106 cluster = cluster ,
107107 command = launch_remote(),
@@ -431,9 +431,8 @@ cluster_config <- function(command = "sbatch", options = "", rscript = "Rscript"
431431# ' @export
432432# '
433433workbench_config <- function () {
434- requireNamespace(" rstudioapi" , quietly = TRUE ) || stop(._ [[" rstudio_api" ]])
435- rstudioapi :: launcherAvailable()
436- cluster <- rstudioapi :: launcherGetInfo()[[" clusters" ]][[1L ]]
434+ get_info <- .subset2(rstudio(), " .rs.api.launcher.getInfo" )
435+ cluster <- get_info()[[" clusters" ]][[1L ]]
437436 list (name = cluster [[" name" ]], image = cluster [[" defaultImage" ]])
438437}
439438
@@ -521,3 +520,12 @@ find_dot <- function(args) {
521520 any(sel ) || stop(._ [[" dot_required" ]], call. = FALSE )
522521 sel
523522}
523+
524+ rstudio <- function () {
525+ idx <- match(" tools:rstudio" , search())
526+ is.na(idx ) && stop(._ [[" rstudio_api" ]])
527+ tools <- as.environment(idx )
528+ feature_available <- .subset2(tools , " .rs.api.launcher.jobsFeatureAvailable" )
529+ is.function(feature_available ) && feature_available() || stop(._ [[" rstudio_api" ]])
530+ tools
531+ }
0 commit comments