diff --git a/NEWS.md b/NEWS.md index 1445015a..e28c8bc2 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,10 @@ # rsconnect (development version) +* `deployApp()`'s `quarto` argument now takes values `TRUE`, `FALSE` or + `NA`. The previous value (a path to a quarto binary) is now deprecated, + and instead we automatically figure out the packge from `QUARTO_PATH` and + `PATH` env vars (#658). + * `deployApp()` gains a new `envVars` argument which takes a vector of the names of environment variables that should be securely copied to the server. The names (not values) of these environment variables are also saved in the diff --git a/R/appMetadata-quarto.R b/R/appMetadata-quarto.R new file mode 100644 index 00000000..2b5290f0 --- /dev/null +++ b/R/appMetadata-quarto.R @@ -0,0 +1,69 @@ +inferQuartoInfo <- function(metadata, appDir, appPrimaryDoc) { + if (hasQuartoMetadata(metadata)) { + return(list( + version = metadata[["quarto_version"]], + engines = metadata[["quarto_engines"]] + )) + } + + # If we don't yet have Quarto details, run quarto inspect ourselves + inspect <- quartoInspect( + appDir = appDir, + appPrimaryDoc = appPrimaryDoc + ) + if (is.null(inspect)) { + return(NULL) + } + + list( + version = inspect[["quarto"]][["version"]], + engines = I(inspect[["engines"]]) + ) +} + +hasQuartoMetadata <- function(x) { + !is.null(x$quarto_version) +} + +# Run "quarto inspect" on the target and returns its output as a parsed object. +quartoInspect <- function(appDir = NULL, appPrimaryDoc = NULL) { + # If "quarto inspect appDir" fails, we will try "quarto inspect + # appPrimaryDoc", so that we can support single files as well as projects. + quarto <- quarto_path() + if (is.null(quarto)) { + cli::cli_abort(c( + "`quarto` not found.", + i = "Check that it is installed and available on your {.envvar PATH}." + )) + } + + paths <- c(appDir, file.path(appDir, appPrimaryDoc)) + + for (path in paths) { + args <- c("inspect", path.expand(path)) + inspect <- tryCatch( + { + json <- suppressWarnings(system2(quarto, args, stdout = TRUE, stderr = TRUE)) + parsed <- jsonlite::fromJSON(json) + return(parsed) + }, + error = function(e) NULL + ) + } + return(NULL) +} + +# inlined from quarto::quarto_path() +quarto_path <- function() { + path_env <- Sys.getenv("QUARTO_PATH", unset = NA) + if (is.na(path_env)) { + path <- unname(Sys.which("quarto")) + if (nzchar(path)) { + path + } else { + NULL + } + } else { + path_env + } +} diff --git a/R/appMetadata.R b/R/appMetadata.R index 71edfaf7..37d104aa 100644 --- a/R/appMetadata.R +++ b/R/appMetadata.R @@ -1,7 +1,7 @@ appMetadata <- function(appDir, appFiles = NULL, appPrimaryDoc = NULL, - quarto = NULL, + quarto = NA, contentCategory = NULL, isCloudServer = FALSE, metadata = list()) { @@ -9,10 +9,23 @@ appMetadata <- function(appDir, appFiles <- listDeploymentFiles(appDir, appFiles) checkAppLayout(appDir, appPrimaryDoc) - # User has supplied quarto path or quarto package/IDE has supplied metadata + if (is_string(quarto)) { + lifecycle::deprecate_warn( + when = "0.9.0", + what = "deployApp(quarto = 'can no longer be a path')", + with = I("quarto = `TRUE` instead") + ) + quarto <- TRUE + } else { + check_bool(quarto, allow_na = TRUE) + } + + # If quarto package/IDE has supplied metadata, always use quarto # https://github.com/quarto-dev/quarto-r/blob/08caf0f42504e7/R/publish.R#L117-L121 # https://github.com/rstudio/rstudio/blob/3d45a20307f650/src/cpp/session/modules/SessionRSConnect.cpp#L81-L123 - hasQuarto <- !is.null(quarto) || hasQuartoMetadata(metadata) + if (hasQuartoMetadata(metadata)) { + quarto <- TRUE + } # Generally we want to infer appPrimaryDoc from appMode, but there's one # special case @@ -24,7 +37,7 @@ appMetadata <- function(appDir, rootFiles <- appFiles[dirname(appFiles) == "."] appMode <- inferAppMode( file.path(appDir, appFiles), - hasQuarto = hasQuarto, + usesQuarto = quarto, isCloudServer = isCloudServer ) } @@ -44,12 +57,16 @@ appMetadata <- function(appDir, appDir = appDir, files = appFiles ) - quartoInfo <- inferQuartoInfo( - appDir = appDir, - appPrimaryDoc = appPrimaryDoc, - quarto = quarto, - metadata = metadata - ) + + if (appIsQuartoDocument(appMode)) { + quartoInfo <- inferQuartoInfo( + metadata = metadata, + appDir = appDir, + appPrimaryDoc = appPrimaryDoc + ) + } else { + quartoInfo <- NULL + } list( appMode = appMode, @@ -99,10 +116,9 @@ checkAppLayout <- function(appDir, appPrimaryDoc = NULL) { )) } - # infer the mode of the application from files in the root dir inferAppMode <- function(absoluteAppFiles, - hasQuarto = FALSE, + usesQuarto = NA, isCloudServer = FALSE) { matchingNames <- function(paths, pattern) { @@ -125,22 +141,13 @@ inferAppMode <- function(absoluteAppFiles, rmdFiles <- matchingNames(absoluteAppFiles, "\\.rmd$") qmdFiles <- matchingNames(absoluteAppFiles, "\\.qmd$") - # We make Quarto requirement conditional on the presence of files that Quarto - # can render and _quarto.yml, because keying off the presence of qmds - # *or* _quarto.yml was causing deployment failures in static content. - # https://github.com/rstudio/rstudio/issues/11444 - quartoYml <- matchingNames(absoluteAppFiles, "^_quarto.y(a)?ml$") - hasQuartoYaml <- length(quartoYml) > 0 - hasQuartoCompatibleFiles <- length(qmdFiles) > 0 || length(rmdFiles > 0) - requiresQuarto <- (hasQuartoCompatibleFiles && hasQuartoYaml) || length(qmdFiles) > 0 - - # We gate the deployment of content that appears to be Quarto behind the - # presence of Quarto metadata. Rmd files can still be deployed as Quarto - if (requiresQuarto && !hasQuarto) { - cli::cli_abort(c( - "Can't deploy Quarto content when {.arg quarto} is {.code NULL}.", - i = "Please supply a path to a quarto binary in {.arg quarto}." - )) + if (is.na(usesQuarto)) { + # Can't use _quarto.yml alone because it causes deployment failures for + # static content: https://github.com/rstudio/rstudio/issues/11444 + quartoYml <- matchingNames(absoluteAppFiles, "^_quarto.y(a)?ml$") + + usesQuarto <- length(qmdFiles) > 0 || + (length(quartoYml) > 0 && length(rmdFiles > 0)) } # Documents with "server: shiny" in their YAML front matter need shiny too @@ -150,7 +157,7 @@ inferAppMode <- function(absoluteAppFiles, if (hasShinyQmd) { return("quarto-shiny") } else if (hasShinyRmd) { - if (hasQuarto) { + if (usesQuarto) { return("quarto-shiny") } else { return("rmd-shiny") @@ -168,7 +175,7 @@ inferAppMode <- function(absoluteAppFiles, # Any non-Shiny R Markdown or Quarto documents are rendered content and get # rmd-static or quarto-static. if (length(rmdFiles) > 0 || length(qmdFiles) > 0) { - if (hasQuarto) { + if (usesQuarto) { return("quarto-static") } else { # For Shinyapps and posit.cloud, treat "rmd-static" app mode as "rmd-shiny" so that @@ -275,6 +282,14 @@ appIsDocument <- function(appMode) { ) } +appIsQuartoDocument <- function(appMode) { + appMode %in% c( + "quarto-static", + "quarto-shiny" + ) +} + + appHasParameters <- function(appDir, appPrimaryDoc, appMode, contentCategory = NULL) { # Only Rmd deployments are marked as having parameters. Shiny applications # may distribute an Rmd alongside app.R, but that does not cause the @@ -321,55 +336,3 @@ documentHasPythonChunk <- function(filename) { matches <- grep("`{python", lines, fixed = TRUE) return(length(matches) > 0) } - -inferQuartoInfo <- function(appDir, appPrimaryDoc, quarto, metadata) { - if (hasQuartoMetadata(metadata)) { - return(list( - version = metadata[["quarto_version"]], - engines = metadata[["quarto_engines"]] - )) - } - - if (is.null(quarto)) { - return(NULL) - } - - # If we don't yet have Quarto details, run quarto inspect ourselves - inspect <- quartoInspect( - quarto = quarto, - appDir = appDir, - appPrimaryDoc = appPrimaryDoc - ) - if (is.null(inspect)) { - return(NULL) - } - - list( - version = inspect[["quarto"]][["version"]], - engines = I(inspect[["engines"]]) - ) -} - -hasQuartoMetadata <- function(x) { - !is.null(x$quarto_version) -} - -# Run "quarto inspect" on the target and returns its output as a parsed object. -quartoInspect <- function(quarto, appDir = NULL, appPrimaryDoc = NULL) { - # If "quarto inspect appDir" fails, we will try "quarto inspect - # appPrimaryDoc", so that we can support single files as well as projects. - paths <- c(appDir, file.path(appDir, appPrimaryDoc)) - - for (path in paths) { - args <- c("inspect", path.expand(path)) - inspect <- tryCatch( - { - json <- suppressWarnings(system2(quarto, args, stdout = TRUE, stderr = TRUE)) - parsed <- jsonlite::fromJSON(json) - return(parsed) - }, - error = function(e) NULL - ) - } - return(NULL) -} diff --git a/R/deployApp.R b/R/deployApp.R index 24d109e0..c91cb0b2 100644 --- a/R/deployApp.R +++ b/R/deployApp.R @@ -122,9 +122,13 @@ #' @param forceGeneratePythonEnvironment Optional. If an existing #' `requirements.txt` file is found, it will be overwritten when this argument #' is `TRUE`. -#' @param quarto Optional. Full path to a Quarto binary for use deploying Quarto -#' content. The provided Quarto binary will be used to run `quarto inspect` -#' to gather information about the content. +#' @param quarto Should the deployed content be built by quarto? +#' (`TRUE`, `FALSE`, or `NA`). The default, `NA`, will use quarto if +#' there are `.qmd` files in the bundle, or if there is a +#' `_quarto.yml` and `.Rmd` files. +#' +#' (This option is ignored and quarto will always be used if the +#' `metadata` contains `quarto_version` and `quarto_engines` fields.) #' @param appVisibility One of `NULL`, `"private"`, or `"public"`; the #' visibility of the deployment. When `NULL`, no change to visibility is #' made. Currently has an effect only on deployments to shinyapps.io. @@ -155,7 +159,7 @@ #' #' # deploy a Quarto website, using the quarto package to #' # find the Quarto binary -#' deployApp("~/projects/quarto/site1", quarto = quarto::quarto_path()) +#' deployApp("~/projects/quarto/site1") #' } #' @seealso [applications()], [terminateApp()], and [restartApp()] #' @family Deployment functions @@ -183,7 +187,7 @@ deployApp <- function(appDir = getwd(), forceUpdate = NULL, python = NULL, forceGeneratePythonEnvironment = FALSE, - quarto = NULL, + quarto = NA, appVisibility = NULL, image = NULL ) { diff --git a/R/writeManifest.R b/R/writeManifest.R index 14e2643a..d63cfa76 100644 --- a/R/writeManifest.R +++ b/R/writeManifest.R @@ -22,7 +22,7 @@ writeManifest <- function(appDir = getwd(), contentCategory = NULL, python = NULL, forceGeneratePythonEnvironment = FALSE, - quarto = NULL, + quarto = NA, image = NULL, verbose = FALSE) { appFiles <- listDeploymentFiles( diff --git a/man/deployApp.Rd b/man/deployApp.Rd index 15be5aa2..396d9f68 100644 --- a/man/deployApp.Rd +++ b/man/deployApp.Rd @@ -27,7 +27,7 @@ deployApp( forceUpdate = NULL, python = NULL, forceGeneratePythonEnvironment = FALSE, - quarto = NULL, + quarto = NA, appVisibility = NULL, image = NULL ) @@ -153,9 +153,13 @@ installed in the environment.} \code{requirements.txt} file is found, it will be overwritten when this argument is \code{TRUE}.} -\item{quarto}{Optional. Full path to a Quarto binary for use deploying Quarto -content. The provided Quarto binary will be used to run \verb{quarto inspect} -to gather information about the content.} +\item{quarto}{Should the deployed content be built by quarto? +(\code{TRUE}, \code{FALSE}, or \code{NA}). The default, \code{NA}, will use quarto if +there are \code{.qmd} files in the bundle, or if there is a +\verb{_quarto.yml} and \code{.Rmd} files. + +(This option is ignored and quarto will always be used if the +\code{metadata} contains \code{quarto_version} and \code{quarto_engines} fields.)} \item{appVisibility}{One of \code{NULL}, \code{"private"}, or \code{"public"}; the visibility of the deployment. When \code{NULL}, no change to visibility is @@ -216,7 +220,7 @@ deployApp(launch.browser = FALSE) # deploy a Quarto website, using the quarto package to # find the Quarto binary -deployApp("~/projects/quarto/site1", quarto = quarto::quarto_path()) +deployApp("~/projects/quarto/site1") } } \seealso{ diff --git a/man/writeManifest.Rd b/man/writeManifest.Rd index be68baab..aabf4f73 100644 --- a/man/writeManifest.Rd +++ b/man/writeManifest.Rd @@ -12,7 +12,7 @@ writeManifest( contentCategory = NULL, python = NULL, forceGeneratePythonEnvironment = FALSE, - quarto = NULL, + quarto = NA, image = NULL, verbose = FALSE ) @@ -47,9 +47,13 @@ installed in the environment.} \code{requirements.txt} file is found, it will be overwritten when this argument is \code{TRUE}.} -\item{quarto}{Optional. Full path to a Quarto binary for use deploying Quarto -content. The provided Quarto binary will be used to run \verb{quarto inspect} -to gather information about the content.} +\item{quarto}{Should the deployed content be built by quarto? +(\code{TRUE}, \code{FALSE}, or \code{NA}). The default, \code{NA}, will use quarto if +there are \code{.qmd} files in the bundle, or if there is a +\verb{_quarto.yml} and \code{.Rmd} files. + +(This option is ignored and quarto will always be used if the +\code{metadata} contains \code{quarto_version} and \code{quarto_engines} fields.)} \item{image}{Optional. The name of the image to use when building and executing this content. If none is provided, Posit Connect will diff --git a/tests/testthat/_snaps/appMetadata-quarto.md b/tests/testthat/_snaps/appMetadata-quarto.md new file mode 100644 index 00000000..62994c8a --- /dev/null +++ b/tests/testthat/_snaps/appMetadata-quarto.md @@ -0,0 +1,9 @@ +# quartoInspect requires quarto + + Code + quartoInspect() + Condition + Error in `quartoInspect()`: + ! `quarto` not found. + i Check that it is installed and available on your `PATH`. + diff --git a/tests/testthat/_snaps/appMetadata.md b/tests/testthat/_snaps/appMetadata.md index 4a81eafd..6be24562 100644 --- a/tests/testthat/_snaps/appMetadata.md +++ b/tests/testthat/_snaps/appMetadata.md @@ -7,6 +7,23 @@ ! No content to deploy. x `appDir` is empty. +# quarto path is deprecated + + Code + . <- appMetadata(dir, quarto = "abc") + Condition + Warning: + The `quarto` argument of `deployApp()` can no longer be a path as of rsconnect 0.9.0. + i Please use quarto = `TRUE` instead instead. + +# validates quarto argument + + Code + appMetadata(dir, quarto = 1) + Condition + Error in `appMetadata()`: + ! `quarto` must be `TRUE`, `FALSE`, or `NA`, not the number 1. + # checkLayout() errors if primary doc & app.R Code @@ -28,21 +45,6 @@ 3. A website containing `.html` and/or `.pdf` files. 4. A plumber API with `plumber.R` or `entrypoint.R`. -# quarto docs require quarto - - Code - inferAppMode(single_qmd) - Condition - Error in `inferAppMode()`: - ! Can't deploy Quarto content when `quarto` is `NULL`. - i Please supply a path to a quarto binary in `quarto`. - Code - inferAppMode(rmd_and_quarto_yml) - Condition - Error in `inferAppMode()`: - ! Can't deploy Quarto content when `quarto` is `NULL`. - i Please supply a path to a quarto binary in `quarto`. - # errors if no files with needed extension Code diff --git a/tests/testthat/_snaps/writeManifest.md b/tests/testthat/_snaps/writeManifest.md index 3dd015d1..4d312482 100644 --- a/tests/testthat/_snaps/writeManifest.md +++ b/tests/testthat/_snaps/writeManifest.md @@ -1,18 +1,9 @@ -# Deploying a Quarto project without Quarto info in an error +# Deploying a Quarto project without Quarto is an error Code - makeManifest(appDir, quarto = NULL) + makeManifest(appDir) Condition - Error in `inferAppMode()`: - ! Can't deploy Quarto content when `quarto` is `NULL`. - i Please supply a path to a quarto binary in `quarto`. - -# Deploying a Quarto doc without Quarto info in an error - - Code - makeManifest(appDir, appPrimaryDoc = appPrimaryDoc) - Condition - Error in `inferAppMode()`: - ! Can't deploy Quarto content when `quarto` is `NULL`. - i Please supply a path to a quarto binary in `quarto`. + Error in `quartoInspect()`: + ! `quarto` not found. + i Check that it is installed and available on your `PATH`. diff --git a/tests/testthat/helper-paths.R b/tests/testthat/helper-paths.R index 159d48f3..d0f15c47 100644 --- a/tests/testthat/helper-paths.R +++ b/tests/testthat/helper-paths.R @@ -16,28 +16,9 @@ pythonPathOrSkip <- function() { # quarto ------------------------------------------------------------------ -quartoPathOrSkip <- function() { - skip_on_cran() +skip_if_no_quarto <- function() { quarto <- quarto_path() skip_if(is.null(quarto), "quarto cli is not installed") - return(quarto) -} -quarto_path <- function() { - path_env <- Sys.getenv("QUARTO_PATH", unset = NA) - if (!is.na(path_env)) { - return(path_env) - } else { - locations <- c( - "quarto", # Use PATH - "/usr/local/bin/quarto", # Location used by some installers - "/opt/quarto/bin/quarto", # Location used by some installers - "/Applications/RStudio.app/Contents/MacOS/quarto/bin/quarto" # macOS IDE - ) - for (location in locations) { - path <- unname(Sys.which(location)) - if (nzchar(path)) return(path) - } - return(NULL) - } + invisible() } diff --git a/tests/testthat/test-appMetadata-quarto.R b/tests/testthat/test-appMetadata-quarto.R new file mode 100644 index 00000000..18fd922d --- /dev/null +++ b/tests/testthat/test-appMetadata-quarto.R @@ -0,0 +1,102 @@ + +# quarto ------------------------------------------------------------------ + +fakeQuartoMetadata <- function(version, engines) { + # See quarto-r/R/publish.R lines 396 and 113. + metadata <- list() + metadata$quarto_version <- version + metadata$quarto_engines <- I(engines) + return(metadata) +} + +test_that("inferQuartoInfo correctly detects info when quarto is provided alone", { + skip_if_no_quarto() + + quartoInfo <- inferQuartoInfo( + metadata = list(), + appDir = test_path("quarto-doc-none"), + appPrimaryDoc = "quarto-doc-none.qmd" + ) + expect_named(quartoInfo, c("version", "engines")) + expect_equal(quartoInfo$engines, I(c("markdown"))) + + quartoInfo <- inferQuartoInfo( + appDir = test_path("quarto-website-r"), + appPrimaryDoc = NULL, + metadata = list() + ) + expect_named(quartoInfo, c("version", "engines")) + expect_equal(quartoInfo$engines, I(c("knitr"))) +}) + +test_that("inferQuartoInfo extracts info from metadata", { + metadata <- fakeQuartoMetadata(version = "99.9.9", engines = c("internal-combustion")) + + quartoInfo <- inferQuartoInfo( + appDir = test_path("quarto-website-r"), + appPrimaryDoc = NULL, + metadata = metadata + ) + expect_equal(quartoInfo, list( + version = "99.9.9", + engines = I("internal-combustion") + )) +}) + +test_that("inferQuartoInfo prefers using metadata over quarto inspect", { + skip_if_no_quarto() + + metadata <- fakeQuartoMetadata(version = "99.9.9", engines = c("internal-combustion")) + + quartoInfo <- inferQuartoInfo( + appDir = test_path("quarto-website-r"), + appPrimaryDoc = NULL, + metadata = metadata + ) + expect_equal(quartoInfo$engines, I(c("internal-combustion"))) +}) + +test_that("inferQuartoInfo returns NULL for non-quarto content", { + skip_if_no_quarto() + + quartoInfo <- inferQuartoInfo( + appDir = test_path("shinyapp-simple"), + appPrimaryDoc = NULL, + metadata = list() + ) + expect_null(quartoInfo) +}) + +test_that("quartoInspect requires quarto", { + local_mocked_bindings(quarto_path = function() NULL) + expect_snapshot(error = TRUE, { + quartoInspect() + }) +}) + +test_that("quartoInspect identifies on Quarto projects", { + skip_if_no_quarto() + + inspect <- quartoInspect(test_path("quarto-website-r")) + expect_true(all(c("quarto", "engines") %in% names(inspect))) + + inspect <- quartoInspect(test_path("quarto-proj-r-shiny")) + expect_true(all(c("quarto", "engines") %in% names(inspect))) +}) + +test_that("quartoInspect identifies Quarto documents", { + skip_if_no_quarto() + + inspect <- quartoInspect( + appDir = test_path("quarto-doc-none"), + appPrimaryDoc = "quarto-doc-none.qmd" + ) + expect_true(all(c("quarto", "engines") %in% names(inspect))) +}) + +test_that("quartoInspect returns NULL on non-quarto Quarto content", { + skip_if_no_quarto() + + inspect <- quartoInspect(test_path("shinyapp-simple")) + expect_null(inspect) +}) diff --git a/tests/testthat/test-appMetadata.R b/tests/testthat/test-appMetadata.R index 2a7f0d0d..f8b9a5a8 100644 --- a/tests/testthat/test-appMetadata.R +++ b/tests/testthat/test-appMetadata.R @@ -11,10 +11,21 @@ test_that("quarto affects mode inference", { metadata <- appMetadata(dir) expect_equal(metadata$appMode, "rmd-static") - metadata <- appMetadata(dir, quarto = "quarto") + metadata <- appMetadata(dir, metadata = list(quarto_version = 1)) expect_equal(metadata$appMode, "quarto-static") }) +test_that("quarto path is deprecated", { + dir <- local_temp_app(list("foo.Rmd" = "")) + expect_snapshot(. <- appMetadata(dir, quarto = "abc")) +}) + +test_that("validates quarto argument", { + dir <- local_temp_app(list("foo.Rmd" = "")) + expect_snapshot(appMetadata(dir, quarto = 1), error = TRUE) +}) + + test_that("handles special case of appPrimaryDoc as R file", { dir <- local_temp_app(list("foo.R" = "")) metadata <- appMetadata(dir, appPrimaryDoc = "foo.R") @@ -72,24 +83,11 @@ test_that("can infer mode for static quarto and rmd docs", { paths <- list.files(dir, full.names = TRUE) expect_equal(inferAppMode(paths), "rmd-static") - expect_equal(inferAppMode(paths, hasQuarto = TRUE), "quarto-static") + expect_equal(inferAppMode(paths, usesQuarto = TRUE), "quarto-static") # Static R Markdown treated as rmd-shiny for shinyapps and rstudio.cloud targets expect_equal(inferAppMode(paths, isCloudServer = TRUE), "rmd-shiny") }) -test_that("quarto docs require quarto", { - dir <- local_temp_app(list("foo.qmd" = "")) - single_qmd <- list.files(dir, full.names = TRUE) - - dir <- local_temp_app(list("foo.Rmd" = "", "_quarto.yaml" = "")) - rmd_and_quarto_yml <- list.files(dir, full.names = TRUE) - - expect_snapshot(error = TRUE, { - inferAppMode(single_qmd) - inferAppMode(rmd_and_quarto_yml) - }) -}) - test_that("can infer mode for shiny rmd docs", { yaml_runtime <- function(runtime) { c("---", paste0("runtime: ", runtime), "---") @@ -125,12 +123,12 @@ test_that("can infer mode for shiny qmd docs", { dir <- local_temp_app(list("index.Qmd" = yaml_runtime("shiny"))) paths <- list.files(dir, full.names = TRUE) - expect_equal(inferAppMode(paths, hasQuarto = TRUE), "quarto-shiny") + expect_equal(inferAppMode(paths), "quarto-shiny") # Can force Rmd to use quarto dir <- local_temp_app(list("index.Rmd" = yaml_runtime("shiny"))) paths <- list.files(dir, full.names = TRUE) - expect_equal(inferAppMode(paths, hasQuarto = TRUE), "quarto-shiny") + expect_equal(inferAppMode(paths, usesQuarto = TRUE), "quarto-shiny") # Prefers quarto if both present dir <- local_temp_app(list( @@ -138,7 +136,7 @@ test_that("can infer mode for shiny qmd docs", { "index.Rmd" = yaml_runtime("shiny") )) paths <- list.files(dir, full.names = TRUE) - expect_equal(inferAppMode(paths, hasQuarto = TRUE), "quarto-shiny") + expect_equal(inferAppMode(paths), "quarto-shiny") }) test_that("Shiny R Markdown files are detected correctly", { @@ -215,7 +213,6 @@ test_that("otherwise look at yaml metadata", { expect_false(appHasParameters(dir, "index.Rmd", "rmd-shiny")) }) - # detectPythonInDocuments ------------------------------------------------- test_that("dir without Rmds doesn't have have python", { @@ -236,110 +233,3 @@ test_that("Rmd or qmd with python chunk has python", { dir <- local_temp_app(list("foo.qmd" = c("```{python}", "1+1", "````"))) expect_true(detectPythonInDocuments(dir)) }) - -# quarto ------------------------------------------------------------------ - -fakeQuartoMetadata <- function(version, engines) { - # See quarto-r/R/publish.R lines 396 and 113. - metadata <- list() - metadata$quarto_version <- version - metadata$quarto_engines <- I(engines) - return(metadata) -} - - -test_that("inferQuartoInfo returns null when no quarto is provided", { - expect_null(inferQuartoInfo(quarto = NULL, metadata = list())) -}) - - -test_that("inferQuartoInfo correctly detects info when quarto is provided alone", { - quarto <- quartoPathOrSkip() - - quartoInfo <- inferQuartoInfo( - appDir = test_path("quarto-doc-none"), - appPrimaryDoc = "quarto-doc-none.qmd", - quarto = quarto, - metadata = list() - ) - expect_named(quartoInfo, c("version", "engines")) - expect_equal(quartoInfo$engines, I(c("markdown"))) - - quartoInfo <- inferQuartoInfo( - appDir = test_path("quarto-website-r"), - appPrimaryDoc = NULL, - quarto = quarto, - metadata = list() - ) - expect_named(quartoInfo, c("version", "engines")) - expect_equal(quartoInfo$engines, I(c("knitr"))) -}) - -test_that("inferQuartoInfo extracts info from metadata", { - metadata <- fakeQuartoMetadata(version = "99.9.9", engines = c("internal-combustion")) - - quartoInfo <- inferQuartoInfo( - appDir = test_path("quarto-website-r"), - appPrimaryDoc = NULL, - quarto = NULL, - metadata = metadata - ) - expect_equal(quartoInfo, list( - version = "99.9.9", - engines = I("internal-combustion") - )) -}) - -test_that("inferQuartoInfo prefers using metadata over quarto inspect", { - quarto <- quartoPathOrSkip() - - metadata <- fakeQuartoMetadata(version = "99.9.9", engines = c("internal-combustion")) - - quartoInfo <- inferQuartoInfo( - appDir = test_path("quarto-website-r"), - appPrimaryDoc = NULL, - quarto = quarto, - metadata = metadata - ) - expect_equal(quartoInfo$engines, I(c("internal-combustion"))) -}) - -test_that("inferQuartoInfo returns NULL for non-quarto content", { - quarto <- quartoPathOrSkip() - - quartoInfo <- inferQuartoInfo( - appDir = test_path("shinyapp-simple"), - appPrimaryDoc = NULL, - quarto = quarto, - metadata = list() - ) - expect_null(quartoInfo) -}) - -test_that("quartoInspect identifies on Quarto projects", { - quarto <- quartoPathOrSkip() - - inspect <- quartoInspect(quarto, test_path("quarto-website-r")) - expect_true(all(c("quarto", "engines") %in% names(inspect))) - - inspect <- quartoInspect(quarto, test_path("quarto-proj-r-shiny")) - expect_true(all(c("quarto", "engines") %in% names(inspect))) -}) - -test_that("quartoInspect identifies Quarto documents", { - quarto <- quartoPathOrSkip() - - inspect <- quartoInspect( - quarto, - appDir = test_path("quarto-doc-none"), - appPrimaryDoc = "quarto-doc-none.qmd" - ) - expect_true(all(c("quarto", "engines") %in% names(inspect))) -}) - -test_that("quartoInspect returns NULL on non-quarto Quarto content", { - quarto <- quartoPathOrSkip() - - inspect <- quartoInspect(quarto, test_path("shinyapp-simple")) - expect_null(inspect) -}) diff --git a/tests/testthat/test-writeManifest.R b/tests/testthat/test-writeManifest.R index 8ba12671..d231af84 100644 --- a/tests/testthat/test-writeManifest.R +++ b/tests/testthat/test-writeManifest.R @@ -67,10 +67,10 @@ test_that("Rmd without a python block doesn't include reticulate or python in th # Quarto Tests test_that("Quarto website includes quarto in the manifest", { - quarto <- quartoPathOrSkip() + skip_if_no_quarto() appDir <- test_path("quarto-website-r") - manifest <- makeManifest(appDir, quarto = quarto) + manifest <- makeManifest(appDir, quarto = TRUE) expect_equal(manifest$metadata$appmode, "quarto-static") expect_equal(manifest$quarto$engines, "knitr") @@ -78,11 +78,11 @@ test_that("Quarto website includes quarto in the manifest", { }) test_that("Quarto document includes quarto in the manifest", { - quarto <- quartoPathOrSkip() + skip_if_no_quarto() appDir <- test_path("quarto-doc-none") appPrimaryDoc <- "quarto-doc-none.qmd" - manifest <- makeManifest(appDir, appPrimaryDoc, quarto = quarto) + manifest <- makeManifest(appDir, appPrimaryDoc, quarto = TRUE) expect_equal(manifest$metadata$appmode, "quarto-static") expect_equal(manifest$quarto$engines, "markdown") @@ -90,11 +90,11 @@ test_that("Quarto document includes quarto in the manifest", { }) test_that("Specifying quarto arg includes quarto in the manifest, even with no appPrimaryDoc specified (.qmd)", { - quarto <- quartoPathOrSkip() + skip_if_no_quarto() appDir <- test_path("quarto-doc-none") appPrimaryDoc <- NULL - manifest <- makeManifest(appDir, appPrimaryDoc, quarto = quarto) + manifest <- makeManifest(appDir, appPrimaryDoc, quarto = TRUE) expect_equal(manifest$metadata$appmode, "quarto-static") expect_equal(manifest$quarto$engines, "markdown") @@ -102,11 +102,11 @@ test_that("Specifying quarto arg includes quarto in the manifest, even with no a }) test_that("Specifying quarto arg includes quarto in the manifest, even with no appPrimaryDoc specified (.Rmd)", { - quarto <- quartoPathOrSkip() + skip_if_no_quarto() appDir <- test_path("shiny-rmds") appPrimaryDoc <- NULL - manifest <- makeManifest(appDir, appPrimaryDoc, quarto = quarto) + manifest <- makeManifest(appDir, appPrimaryDoc, quarto = TRUE) expect_equal(manifest$metadata$appmode, "quarto-shiny") expect_equal(manifest$quarto$engines, "knitr") @@ -114,20 +114,20 @@ test_that("Specifying quarto arg includes quarto in the manifest, even with no a }) test_that("specifying quarto arg with non-quarto app does not include quarto in the manifest", { - quarto <- quartoPathOrSkip() + skip_if_no_quarto() appDir <- test_path("shinyapp-singleR") appPrimaryDoc <- "single.R" - manifest <- makeManifest(appDir, appPrimaryDoc, quarto = quarto) + manifest <- makeManifest(appDir, appPrimaryDoc, quarto = TRUE) expect_null(manifest$quarto) }) test_that("Quarto shiny project includes quarto in the manifest", { - quarto <- quartoPathOrSkip() + skip_if_no_quarto() appDir <- test_path("quarto-proj-r-shiny") - manifest <- makeManifest(appDir, quarto = quarto) + manifest <- makeManifest(appDir, quarto = TRUE) expect_equal(manifest$metadata$appmode, "quarto-shiny") expect_equal(manifest$quarto$engines, "knitr") @@ -136,11 +136,11 @@ test_that("Quarto shiny project includes quarto in the manifest", { test_that("Quarto R + Python website includes quarto and python in the manifest", { skip_if_not_installed("reticulate") - quarto <- quartoPathOrSkip() + skip_if_no_quarto() python <- pythonPathOrSkip() appDir <- test_path("quarto-website-r-py") - manifest <- makeManifest(appDir, python = python, quarto = quarto) + manifest <- makeManifest(appDir, python = python, quarto = TRUE) expect_equal(manifest$metadata$appmode, "quarto-static") expect_equal(manifest$quarto$engines, "knitr") @@ -152,11 +152,12 @@ test_that("Quarto R + Python website includes quarto and python in the manifest" test_that("Quarto Python-only website gets correct manifest data", { skip_if_not_installed("reticulate") - quarto <- quartoPathOrSkip() + skip_if_no_quarto() + python <- pythonPathOrSkip() appDir <- test_path("quarto-website-py") - manifest <- makeManifest(appDir, python = python, quarto = quarto) + manifest <- makeManifest(appDir, python = python, quarto = TRUE) expect_equal(manifest$metadata$appmode, "quarto-static") expect_equal(manifest$quarto$engines, "jupyter") @@ -167,24 +168,17 @@ test_that("Quarto Python-only website gets correct manifest data", { expect_null(manifest$packages) }) -test_that("Deploying a Quarto project without Quarto info in an error", { - appDir <- test_path("quarto-website-r") - expect_snapshot(makeManifest(appDir, quarto = NULL), error = TRUE) -}) +test_that("Deploying a Quarto project without Quarto is an error", { + local_mocked_bindings(quarto_path = function() NULL) -test_that("Deploying a Quarto doc without Quarto info in an error", { - appDir <- test_path("quarto-doc-none") - appPrimaryDoc <- "quarto-doc-none.qmd" - expect_snapshot( - makeManifest(appDir, appPrimaryDoc = appPrimaryDoc), - error = TRUE - ) + appDir <- test_path("quarto-website-r") + expect_snapshot(makeManifest(appDir), error = TRUE) }) test_that("Deploying R Markdown content with Quarto gives a Quarto app mode", { - quarto <- quartoPathOrSkip() + skip_if_no_quarto() - manifest <- makeManifest(test_path("test-rmds"), "simple.Rmd", quarto = quarto) + manifest <- makeManifest(test_path("test-rmds"), "simple.Rmd", quarto = TRUE) expect_equal(manifest$metadata$appmode, "quarto-static") expect_equal(manifest$quarto$engines, "knitr")