Skip to content

Commit

Permalink
make launchers work with next dispatcher
Browse files Browse the repository at this point in the history
  • Loading branch information
shikokuchuo committed Nov 28, 2024
1 parent f00f195 commit c7a4915
Show file tree
Hide file tree
Showing 3 changed files with 11 additions and 5 deletions.
2 changes: 1 addition & 1 deletion R/daemons.R
Original file line number Diff line number Diff line change
Expand Up @@ -307,7 +307,6 @@ daemons <- function(n, url = NULL, remote = NULL, dispatcher = c("process", "nex
res <- launch_sync_dispatcher(sock, sockc, wa5(urld, dots, n, urlc, url), output, tls, pass)
is.object(res) && stop(._[["sync_dispatcher"]])
store_dispatcher(sockc, res, cv, envir)
`[[<-`(envir, "msgid", 100L)
},
{
n <- if (missing(n)) length(url) else if (is.numeric(n) && n >= 1L) as.integer(n) else stop(._[["n_one"]])
Expand All @@ -322,6 +321,7 @@ daemons <- function(n, url = NULL, remote = NULL, dispatcher = c("process", "nex
res <- launch_sync_dispatcher(sock, sockc, wa52(urld, dots, n, urlc, url), output, tls, pass)
is.object(res) && stop(._[["sync_dispatcher"]])
store_dispatcher(sockc, res, cv, envir)
`[[<-`(envir, "msgid", 100L)
},
{
n <- if (missing(n)) length(url) else if (is.numeric(n) && n >= 1L) as.integer(n) else stop(._[["n_one"]])
Expand Down
8 changes: 5 additions & 3 deletions R/launchers.R
Original file line number Diff line number Diff line change
Expand Up @@ -83,13 +83,14 @@ launch_local <- function(url, ..., tls = NULL, .compute = "default") {

envir <- ..[[.compute]]
is.null(envir) && stop(._[["daemons_unset"]])
write_args <- if (length(envir[["msgid"]])) wa32 else wa3
dots <- parse_dots(...)
output <- attr(dots, "output")
if (is.null(tls)) tls <- envir[["tls"]]
url <- process_url(url, envir)
is.character(url) || stop(._[["url_spec"]])
for (u in url)
launch_daemon(wa3(u, dots, next_stream(envir), tls), output)
launch_daemon(write_args(u, dots, next_stream(envir), tls), output)

}

Expand Down Expand Up @@ -119,6 +120,7 @@ launch_remote <- function(url, remote = remote_config(), ..., tls = NULL, .compu
url <- rep(..[[.compute]][["urls"]], max(length(url), 1L))
}
envir <- ..[[.compute]]
write_args <- if (length(envir[["msgid"]])) wa32 else wa3
is.null(envir) && stop(._[["daemons_unset"]])
dots <- parse_dots(...)
if (is.null(tls)) tls <- envir[["tls"]]
Expand All @@ -144,7 +146,7 @@ launch_remote <- function(url, remote = remote_config(), ..., tls = NULL, .compu
arglen <- length(args)
cmds <- character(arglen)
for (i in seq_along(args))
cmds[i] <- sprintf("%s -e %s", rscript, wa3(url[min(i, ulen)], dots, next_stream(envir), tls))
cmds[i] <- sprintf("%s -e %s", rscript, write_args(url[min(i, ulen)], dots, next_stream(envir), tls))

for (i in seq_along(args))
system2(command, args = `[<-`(args[[i]], find_dot(args[[i]]), if (quote) shQuote(cmds[i]) else cmds[i]), wait = FALSE)
Expand All @@ -160,7 +162,7 @@ launch_remote <- function(url, remote = remote_config(), ..., tls = NULL, .compu

cmds <- character(ulen)
for (i in seq_along(url))
cmds[i] <- sprintf("%s -e %s", rscript, wa3(url[i], dots, next_stream(envir), tls))
cmds[i] <- sprintf("%s -e %s", rscript, write_args(url[i], dots, next_stream(envir), tls))

if (length(command))
for (cmd in cmds)
Expand Down
6 changes: 5 additions & 1 deletion tests/tests.R
Original file line number Diff line number Diff line change
Expand Up @@ -318,13 +318,17 @@ connection && Sys.getenv("NOT_CRAN") == "true" && {
test_equal(daemons(1, dispatcher = "next", cleanup = FALSE), 1L)
m1 <- mirai({ Sys.sleep(1); res <<- "m1 done" })
m2 <- mirai({ Sys.sleep(1); res <<- "m2 done" })
Sys.sleep(0.01)
Sys.sleep(0.1)
test_true(stop_mirai(m2))
test_equal(m2$data, 20L)
test_true(stop_mirai(m1))
test_class("miraiError", mirai(res)[])
test_equal(status()$connections, 1L)
test_equal(length(nextget("urls")), 1L)
test_null(launch_local(1))
test_class("miraiLaunchCmd", launch_remote(1))
Sys.sleep(1L)
test_equal(status()$daemons, 2L)
test_zero(daemons(0))
}
Sys.sleep(1L)

0 comments on commit c7a4915

Please sign in to comment.