Skip to content

Commit

Permalink
Refine auto-loading behaviour (#1915)
Browse files Browse the repository at this point in the history
* Re-order these checks

* Put some DOTS on it

* Be precise about the recommended action

* Don't message about cancellation

* Refine action around renv::restore() during autoloading

* Make `renv::restore()` (maybe) a runnable hyperlink if cli is available

* Introduce `cancel(verbose =)`

* Back out of the cli experiment
  • Loading branch information
jennybc authored Jul 2, 2024
1 parent 1f99d7d commit 65ac9cb
Show file tree
Hide file tree
Showing 3 changed files with 32 additions and 25 deletions.
34 changes: 21 additions & 13 deletions R/load.R
Original file line number Diff line number Diff line change
Expand Up @@ -70,7 +70,8 @@ load <- function(project = NULL, quiet = FALSE, profile = NULL, ...) {

action <- renv_load_action(project)
if (action[[1L]] == "cancel") {
cancel()
autoloading <- getOption("renv.autoloader.running", default = FALSE)
cancel(verbose = !autoloading)
} else if (action[[1L]] == "init") {
return(init(project))
} else if (action[[1L]] == "alt") {
Expand Down Expand Up @@ -146,22 +147,28 @@ renv_load_action <- function(project) {
if (!interactive())
return("load")

autoloading <- getOption("renv.autoloader.running", default = FALSE)
# if we're auto-loading, it's too early to interact with the user, which is
# often advisable, i.e. if we detect that the user needs to run renv::restore()
# https://github.com/rstudio/renv/issues/1650
#
# if the frontend is known to support a session init hook, defer loading until
# R is fully initialized, at which time it will be possible to interact with
# the user (currently this just applies to RStudio)
#
# otherwise, proceed with the knowledge that, if the user needs to run
# renv::restore(), a message to that effect will be emitted
if (autoloading && renv_rstudio_available()) {
setHook("rstudio.sessionInit", function(...) { renv::load(project) })
return("cancel")
}

# if this project already contains an 'renv' folder, assume it's
# already been initialized and we can directly load it
renv <- renv_paths_renv(project = project, profile = FALSE)
if (dir.exists(renv))
return("load")

# if we're running within RStudio at this point, and we're running
# within the auto-loader, we need to defer execution here so that
# the console is able to properly receive user input and update
# https://github.com/rstudio/renv/issues/1650
autoloading <- getOption("renv.autoloader.running", default = FALSE)
if (autoloading && renv_rstudio_available()) {
setHook("rstudio.sessionInit", function() { renv::load(project) })
return("cancel")
}

# check and see if we're being called within a sub-directory
path <- renv_file_find(dirname(project), function(parent) {
if (file.exists(file.path(parent, "renv")))
Expand Down Expand Up @@ -876,12 +883,13 @@ renv_load_report_synchronized <- function(project = NULL, lockfile = NULL) {
if (length(intersect(lockpkgs, libpkgs)) == 0 && length(lockpkgs) > 0L) {

caution("- None of the packages recorded in the lockfile are currently installed.")
if (renv_rstudio_autoloading()) {
autoloading <- getOption("renv.autoloader.running", default = FALSE)
if (autoloading) {
caution("- Use `renv::restore()` to restore the project library.")
return(FALSE)
}

response <- ask("Would you like to restore the project library?", default = FALSE)
response <- ask("Would you like to run `renv::restore()` to restore the project library?", default = FALSE)
if (!response)
return(FALSE)

Expand Down
4 changes: 0 additions & 4 deletions R/rstudio.R
Original file line number Diff line number Diff line change
Expand Up @@ -10,10 +10,6 @@ renv_rstudio_available <- function() {

}

renv_rstudio_autoloading <- function() {
renv_rstudio_available() && getOption("renv.autoloader.running", default = FALSE)
}

renv_rstudio_initialize <- function(project) {

tools <- catch(as.environment("tools:rstudio"))
Expand Down
19 changes: 11 additions & 8 deletions R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -126,13 +126,15 @@ ask <- function(question, default = FALSE) {
if (!interactive())
return(default)

# can't prompt for input when running autoloader in RStudio
# can't prompt for input when autoloading; code run from `.Rprofile` should
# not attempt to interact with the user
# from `?Startup`:
# "It is not intended that there be interaction with the user during startup
# code. Attempting to do so can crash the R process."
# https://github.com/rstudio/renv/issues/1879
if (renv_rstudio_available()) {
autoloading <- getOption("renv.autoloader.running", default = FALSE)
if (autoloading)
return(default)
}
autoloading <- getOption("renv.autoloader.running", default = FALSE)
if (autoloading)
return(default)

# be verbose in this scope, as we're asking the user for input
renv_scope_options(renv.verbose = TRUE)
Expand Down Expand Up @@ -519,13 +521,14 @@ take <- function(data, index = NULL) {
if (is.null(index)) data else .subset2(data, index)
}

cancel <- function() {
cancel <- function(verbose = TRUE) {

renv_snapshot_auto_suppress_next()
if (testing())
stop("Operation canceled", call. = FALSE)

message("- Operation canceled.")
if (verbose)
message("- Operation canceled.")
invokeRestart("abort")

}
Expand Down

0 comments on commit 65ac9cb

Please sign in to comment.