@@ -108,6 +108,23 @@ launch_remote <- function(
108108 dots <- if (missing(..1 )) envir [[" dots" ]] else parse_dots(... )
109109 if (is.null(tls )) tls <- envir [[" tls" ]]
110110
111+ if (length(remote ) == 2L ) {
112+ requireNamespace(" rstudioapi" , quietly = TRUE ) || stop(._ [[" rstudio_api" ]])
113+ rstudioapi :: launcherAvailable()
114+ cluster <- remote [[" name" ]]
115+ container <- rstudioapi :: launcherContainer(remote [[" image" ]])
116+ lapply(
117+ seq_len(n ),
118+ function (x ) rstudioapi :: launcherSubmitJob(
119+ sprintf(" mirai_daemon_%d" , x ),
120+ cluster = cluster ,
121+ command = launch_remote(),
122+ container = container
123+ )
124+ )
125+ return (invisible ())
126+ }
127+
111128 command <- remote [[" command" ]]
112129 rscript <- remote [[" rscript" ]]
113130 quote <- remote [[" quote" ]]
@@ -431,6 +448,34 @@ cluster_config <- function(
431448 list (command = " /bin/sh" , args = args , rscript = rscript , quote = NULL )
432449}
433450
451+ # ' Workbench Remote Launch Configuration
452+ # '
453+ # ' Generates a remote configuration for launching daemons using the default
454+ # ' launcher configured in Posit Workbench.
455+ # '
456+ # ' @inherit remote_config return
457+ # '
458+ # ' @seealso [ssh_config()], [cluster_config()], and [remote_config()] for other
459+ # ' remote launch configurations.
460+ # '
461+ # ' @examples
462+ # ' tryCatch(workbench_config(), error = identity)
463+ # '
464+ # ' \dontrun{
465+ # '
466+ # ' # Launch 2 daemons using the Workbench default launcher:
467+ # ' daemons(n = 2, url = host_url(), remote = workbench_config())
468+ # ' }
469+ # '
470+ # ' @export
471+ # '
472+ workbench_config <- function () {
473+ requireNamespace(" rstudioapi" , quietly = TRUE ) || stop(._ [[" rstudio_api" ]])
474+ rstudioapi :: launcherAvailable()
475+ cluster <- rstudioapi :: launcherGetInfo()[[" clusters" ]][[1L ]]
476+ list (name = cluster [[" name" ]], image = cluster [[" defaultImage" ]])
477+ }
478+
434479# ' URL Constructors
435480# '
436481# ' `host_url()` constructs a valid host URL (at which daemons may connect) based
0 commit comments