From e3bced75a389cdba93751f6f302abeb2352bee4d Mon Sep 17 00:00:00 2001 From: Toph Allen Date: Tue, 14 Jun 2022 15:35:57 -0400 Subject: [PATCH 1/8] Update quarto file handling, add tests --- R/bundle.R | 33 +++++++++++++++---- tests/testthat/qmd-and-rmd/non-shiny-rmd.Rmd | 7 ++++ .../testthat/qmd-and-rmd/quarto-doc-none.qmd | 7 ++++ tests/testthat/test-bundle.R | 25 +++++++++++++- 4 files changed, 65 insertions(+), 7 deletions(-) create mode 100644 tests/testthat/qmd-and-rmd/non-shiny-rmd.Rmd create mode 100644 tests/testthat/qmd-and-rmd/quarto-doc-none.qmd diff --git a/R/bundle.R b/R/bundle.R index e30e57f8..80db0564 100644 --- a/R/bundle.R +++ b/R/bundle.R @@ -406,14 +406,32 @@ inferAppMode <- function(appDir, appPrimaryDoc, files, quartoInfo) { return("shiny") } - # Determine if we have Rmd and if they are (optionally) need the Shiny runtime. - rmdFiles <- grep("^[^/\\\\]+\\.[rq]md$", files, ignore.case = TRUE, perl = TRUE, value = TRUE) + # Determine if we have Rmd files, and if they use the Shiny runtime. + rmdFiles <- grep("^[^/\\\\]+\\.rmd$", files, ignore.case = TRUE, perl = TRUE, value = TRUE) shinyRmdFiles <- sapply(file.path(appDir, rmdFiles), isShinyRmd) - # An Rmd file with a Shiny runtime uses rmarkdown::run. + # Determine if we have qmd files, and if they use the Shiny runtime + qmdFiles <- grep("^[^/\\\\]+\\.qmd$", files, ignore.case = TRUE, perl = TRUE, value = TRUE) + shinyQmdFiles <- sapply(file.path(appDir, qmdFiles), isShinyRmd) + + # Trying to deploy Quarto and R Markdown files simultaneously is an error. + if (length(rmdFiles) > 0 && length(qmdFiles) > 0) { + stop("Cannot infer app mode because there are both .qmd and .Rmd files in deployment files.") + } + + # To deploy Quarto content, we need to have received or inferred Quarto metadata. + missingQuartoInfoErrorText <- paste( + "Attempting to deploy Quarto project without successfully running 'quarto inspect'.", + "Please provide the path to a quarto binary to the 'quarto'." + ) + + # Shiny or Quarto documents with "server: shiny" in their YAML front matter + # are rmd-shiny or quarto-shiny. if (any(shinyRmdFiles)) { + return("rmd-shiny") + } else if (any(shinyQmdFiles)) { if (is.null(quartoInfo)) { - return("rmd-shiny") + stop(missingQuartoInfoErrorText) } else { return("quarto-shiny") } @@ -427,10 +445,13 @@ inferAppMode <- function(appDir, appPrimaryDoc, files, quartoInfo) { return("shiny") } - # Any non-Shiny R Markdown documents are rendered content (rmd-static). + # Any non-Shiny R Markdown or Quarto documents are rendered content and get + # rmd-static or quarto-static. if (length(rmdFiles) > 0) { + return("rmd-static") + } else if (length(qmdFiles) > 0) { if (is.null(quartoInfo)) { - return("rmd-static") + stop(missingQuartoInfoErrorText) } else { return("quarto-static") } diff --git a/tests/testthat/qmd-and-rmd/non-shiny-rmd.Rmd b/tests/testthat/qmd-and-rmd/non-shiny-rmd.Rmd new file mode 100644 index 00000000..f9476ad0 --- /dev/null +++ b/tests/testthat/qmd-and-rmd/non-shiny-rmd.Rmd @@ -0,0 +1,7 @@ +--- +title: Not a Shiny R Markdown Document +output: html_document +--- + + + diff --git a/tests/testthat/qmd-and-rmd/quarto-doc-none.qmd b/tests/testthat/qmd-and-rmd/quarto-doc-none.qmd new file mode 100644 index 00000000..bb1dfc22 --- /dev/null +++ b/tests/testthat/qmd-and-rmd/quarto-doc-none.qmd @@ -0,0 +1,7 @@ +--- +title: "quarto-doc-none" +--- + +## Quarto + +Quarto enables you to weave together content and executable code into a finished document. To learn more about Quarto see . diff --git a/tests/testthat/test-bundle.R b/tests/testthat/test-bundle.R index dc2a29e1..f710d44b 100644 --- a/tests/testthat/test-bundle.R +++ b/tests/testthat/test-bundle.R @@ -563,8 +563,31 @@ test_that("writeManifest: Quarto Python-only website gets correct manifest data" expect_null(manifest$packages) }) +test_that("writeManifest: Deploying Quarto content without Quarto info in an error", { + missingQuartoInfoErrorText <- paste( + "Attempting to deploy Quarto project without successfully running 'quarto inspect'.", + "Please provide the path to a quarto binary to the 'quarto'." + ) + + appDir <- "quarto-website-r" + expect_error( + makeManifest(appDir, appPrimaryDoc = NULL, quarto = NULL), + missingQuartoInfoErrorText + ) +}) + +test_that("writeManifest: Attempting to deploy a directory with Rmd and qmd files is an error", { + quarto <- quartoPathOrSkip() + + appDir <- "qmd-and-rmd" + expect_error( + makeManifest(appDir, appPrimaryDoc = NULL, quarto = quarto), + "Cannot infer app mode because there are both .qmd and .Rmd files in deployment files." + ) +}) + test_that("writeManifest: Sets environment.image in the manifest if one is provided", { - appDir <- "quarto-proj-r-shiny" + appDir <- "shinyapp-simple" manifest <- makeManifest(appDir, appPrimaryDoc = NULL, image = "rstudio/content-base:latest") expect_equal(manifest$environment$image, "rstudio/content-base:latest") From 1f19eb8117a058ae0709659a04f0309abaaa8458 Mon Sep 17 00:00:00 2001 From: Toph Allen Date: Tue, 14 Jun 2022 15:45:39 -0400 Subject: [PATCH 2/8] Fix typo --- R/bundle.R | 2 +- tests/testthat/test-bundle.R | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/R/bundle.R b/R/bundle.R index 80db0564..2b26a88a 100644 --- a/R/bundle.R +++ b/R/bundle.R @@ -422,7 +422,7 @@ inferAppMode <- function(appDir, appPrimaryDoc, files, quartoInfo) { # To deploy Quarto content, we need to have received or inferred Quarto metadata. missingQuartoInfoErrorText <- paste( "Attempting to deploy Quarto project without successfully running 'quarto inspect'.", - "Please provide the path to a quarto binary to the 'quarto'." + "Please provide the path to a quarto binary to the 'quarto' argument." ) # Shiny or Quarto documents with "server: shiny" in their YAML front matter diff --git a/tests/testthat/test-bundle.R b/tests/testthat/test-bundle.R index f710d44b..745cf881 100644 --- a/tests/testthat/test-bundle.R +++ b/tests/testthat/test-bundle.R @@ -566,7 +566,7 @@ test_that("writeManifest: Quarto Python-only website gets correct manifest data" test_that("writeManifest: Deploying Quarto content without Quarto info in an error", { missingQuartoInfoErrorText <- paste( "Attempting to deploy Quarto project without successfully running 'quarto inspect'.", - "Please provide the path to a quarto binary to the 'quarto'." + "Please provide the path to a quarto binary to the 'quarto' argument." ) appDir <- "quarto-website-r" From ad8153ab578eca88f533caca03a1313790ac7998 Mon Sep 17 00:00:00 2001 From: Toph Allen Date: Tue, 14 Jun 2022 15:49:11 -0400 Subject: [PATCH 3/8] Adjust language --- R/bundle.R | 2 +- tests/testthat/test-bundle.R | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/R/bundle.R b/R/bundle.R index 2b26a88a..244dc25c 100644 --- a/R/bundle.R +++ b/R/bundle.R @@ -421,7 +421,7 @@ inferAppMode <- function(appDir, appPrimaryDoc, files, quartoInfo) { # To deploy Quarto content, we need to have received or inferred Quarto metadata. missingQuartoInfoErrorText <- paste( - "Attempting to deploy Quarto project without successfully running 'quarto inspect'.", + "Attempting to deploy Quarto project without Quarto metadata.", "Please provide the path to a quarto binary to the 'quarto' argument." ) diff --git a/tests/testthat/test-bundle.R b/tests/testthat/test-bundle.R index 745cf881..4af0aa0c 100644 --- a/tests/testthat/test-bundle.R +++ b/tests/testthat/test-bundle.R @@ -565,7 +565,7 @@ test_that("writeManifest: Quarto Python-only website gets correct manifest data" test_that("writeManifest: Deploying Quarto content without Quarto info in an error", { missingQuartoInfoErrorText <- paste( - "Attempting to deploy Quarto project without successfully running 'quarto inspect'.", + "Attempting to deploy Quarto project without Quarto metadata.", "Please provide the path to a quarto binary to the 'quarto' argument." ) From 62e3b4ac4f6207c6806ba670e7e2d71a64b7c0a3 Mon Sep 17 00:00:00 2001 From: Toph Allen Date: Tue, 14 Jun 2022 15:52:27 -0400 Subject: [PATCH 4/8] The IDE now apparently removes this line from project files --- rsconnect.Rproj | 1 - 1 file changed, 1 deletion(-) diff --git a/rsconnect.Rproj b/rsconnect.Rproj index 6d372f12..7e916bd0 100644 --- a/rsconnect.Rproj +++ b/rsconnect.Rproj @@ -17,7 +17,6 @@ StripTrailingWhitespace: Yes BuildType: Package PackageUseDevtools: Yes -PackageCleanBeforeInstall: Yes PackageInstallArgs: --no-multiarch --with-keep.source PackageCheckArgs: --as-cran PackageRoxygenize: rd,collate,namespace From 6b1e2aafea1d6c7642aa0322af3e9b8e5dd70668 Mon Sep 17 00:00:00 2001 From: Toph Allen Date: Tue, 14 Jun 2022 15:56:38 -0400 Subject: [PATCH 5/8] Update NEWS.md --- NEWS.md | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/NEWS.md b/NEWS.md index 7b58cf5d..2fce3a7d 100644 --- a/NEWS.md +++ b/NEWS.md @@ -2,6 +2,10 @@ ## 0.8.27 (in development) +* Quarto content will no longer silently deploy as R Markdown content when + Quarto metadata is missing or cannot be gathered. Functions will error, + requesting the path to a Quarto binary in the `quarto` argument. (#594) + ## 0.8.26 From 7080f6feb44621be26c4339f247e76dba529c897 Mon Sep 17 00:00:00 2001 From: Toph Allen Date: Wed, 15 Jun 2022 15:33:03 -0400 Subject: [PATCH 6/8] Update conditions, adjust tests --- R/bundle.R | 40 +++++++++++++++++------------------- tests/testthat/test-bundle.R | 14 ++++++------- 2 files changed, 26 insertions(+), 28 deletions(-) diff --git a/R/bundle.R b/R/bundle.R index 244dc25c..49df9b06 100644 --- a/R/bundle.R +++ b/R/bundle.R @@ -413,27 +413,27 @@ inferAppMode <- function(appDir, appPrimaryDoc, files, quartoInfo) { # Determine if we have qmd files, and if they use the Shiny runtime qmdFiles <- grep("^[^/\\\\]+\\.qmd$", files, ignore.case = TRUE, perl = TRUE, value = TRUE) shinyQmdFiles <- sapply(file.path(appDir, qmdFiles), isShinyRmd) + hasQuartoYaml <- any(grepl("^_quarto.y(a)?ml$", x = files, ignore.case = TRUE, perl = TRUE)) - # Trying to deploy Quarto and R Markdown files simultaneously is an error. - if (length(rmdFiles) > 0 && length(qmdFiles) > 0) { - stop("Cannot infer app mode because there are both .qmd and .Rmd files in deployment files.") - } + requiresQuarto <- any(length(qmdFiles > 0), hasQuartoYaml) - # To deploy Quarto content, we need to have received or inferred Quarto metadata. - missingQuartoInfoErrorText <- paste( - "Attempting to deploy Quarto project without Quarto metadata.", - "Please provide the path to a quarto binary to the 'quarto' argument." - ) + # 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 + # content. + if (requiresQuarto && is.null(quartoInfo)) { + stop(paste( + "Attempting to deploy Quarto content without Quarto metadata.", + "Please provide the path to a quarto binary to the 'quarto' argument." + )) + } # Shiny or Quarto documents with "server: shiny" in their YAML front matter # are rmd-shiny or quarto-shiny. - if (any(shinyRmdFiles)) { - return("rmd-shiny") - } else if (any(shinyQmdFiles)) { - if (is.null(quartoInfo)) { - stop(missingQuartoInfoErrorText) - } else { + if (any(shinyRmdFiles) || any(shinyQmdFiles)) { + if (!is.null(quartoInfo)) { return("quarto-shiny") + } else { + return("rmd-shiny") } } @@ -447,13 +447,11 @@ inferAppMode <- function(appDir, appPrimaryDoc, files, quartoInfo) { # Any non-Shiny R Markdown or Quarto documents are rendered content and get # rmd-static or quarto-static. - if (length(rmdFiles) > 0) { - return("rmd-static") - } else if (length(qmdFiles) > 0) { - if (is.null(quartoInfo)) { - stop(missingQuartoInfoErrorText) - } else { + if (length(rmdFiles) > 0 || length(qmdFiles) > 0) { + if (!is.null(quartoInfo)) { return("quarto-static") + } else { + return("rmd-static") } } diff --git a/tests/testthat/test-bundle.R b/tests/testthat/test-bundle.R index 4af0aa0c..8711c4d3 100644 --- a/tests/testthat/test-bundle.R +++ b/tests/testthat/test-bundle.R @@ -565,7 +565,7 @@ test_that("writeManifest: Quarto Python-only website gets correct manifest data" test_that("writeManifest: Deploying Quarto content without Quarto info in an error", { missingQuartoInfoErrorText <- paste( - "Attempting to deploy Quarto project without Quarto metadata.", + "Attempting to deploy Quarto content without Quarto metadata.", "Please provide the path to a quarto binary to the 'quarto' argument." ) @@ -576,14 +576,14 @@ test_that("writeManifest: Deploying Quarto content without Quarto info in an err ) }) -test_that("writeManifest: Attempting to deploy a directory with Rmd and qmd files is an error", { +test_that("writeManifest: Deploying R Markdown content with Quarto gives a Quarto app mode", { quarto <- quartoPathOrSkip() - appDir <- "qmd-and-rmd" - expect_error( - makeManifest(appDir, appPrimaryDoc = NULL, quarto = quarto), - "Cannot infer app mode because there are both .qmd and .Rmd files in deployment files." - ) + manifest <- makeManifest("test-rmds", "simple.Rmd", quarto = quarto) + + expect_equal(manifest$metadata$appmode, "quarto-static") + expect_equal(manifest$quarto$engines, "knitr") + expect_equal(manifest$metadata$primary_rmd, "simple.Rmd") }) test_that("writeManifest: Sets environment.image in the manifest if one is provided", { From 02024dce5d4b0f31cde0f526f124f65572f7af61 Mon Sep 17 00:00:00 2001 From: Toph Allen Date: Wed, 15 Jun 2022 15:49:11 -0400 Subject: [PATCH 7/8] Remove no-longer-needed test files --- tests/testthat/qmd-and-rmd/non-shiny-rmd.Rmd | 7 ------- tests/testthat/qmd-and-rmd/quarto-doc-none.qmd | 7 ------- 2 files changed, 14 deletions(-) delete mode 100644 tests/testthat/qmd-and-rmd/non-shiny-rmd.Rmd delete mode 100644 tests/testthat/qmd-and-rmd/quarto-doc-none.qmd diff --git a/tests/testthat/qmd-and-rmd/non-shiny-rmd.Rmd b/tests/testthat/qmd-and-rmd/non-shiny-rmd.Rmd deleted file mode 100644 index f9476ad0..00000000 --- a/tests/testthat/qmd-and-rmd/non-shiny-rmd.Rmd +++ /dev/null @@ -1,7 +0,0 @@ ---- -title: Not a Shiny R Markdown Document -output: html_document ---- - - - diff --git a/tests/testthat/qmd-and-rmd/quarto-doc-none.qmd b/tests/testthat/qmd-and-rmd/quarto-doc-none.qmd deleted file mode 100644 index bb1dfc22..00000000 --- a/tests/testthat/qmd-and-rmd/quarto-doc-none.qmd +++ /dev/null @@ -1,7 +0,0 @@ ---- -title: "quarto-doc-none" ---- - -## Quarto - -Quarto enables you to weave together content and executable code into a finished document. To learn more about Quarto see . From 478476cc49b628000f9334c1188f5bcbe165a12a Mon Sep 17 00:00:00 2001 From: Toph Allen Date: Thu, 16 Jun 2022 17:29:31 -0400 Subject: [PATCH 8/8] Update Quarto conditions --- R/bundle.R | 9 +- .../static-with-quarto-yaml/_quarto.yml | 2 + .../static-with-quarto-yaml/slideshow.html | 681 ++++++++++++++++++ tests/testthat/test-bundle.R | 23 +- 4 files changed, 712 insertions(+), 3 deletions(-) create mode 100644 tests/testthat/static-with-quarto-yaml/_quarto.yml create mode 100644 tests/testthat/static-with-quarto-yaml/slideshow.html diff --git a/R/bundle.R b/R/bundle.R index 49df9b06..66f9033c 100644 --- a/R/bundle.R +++ b/R/bundle.R @@ -413,9 +413,14 @@ inferAppMode <- function(appDir, appPrimaryDoc, files, quartoInfo) { # Determine if we have qmd files, and if they use the Shiny runtime qmdFiles <- grep("^[^/\\\\]+\\.qmd$", files, ignore.case = TRUE, perl = TRUE, value = TRUE) shinyQmdFiles <- sapply(file.path(appDir, qmdFiles), isShinyRmd) - hasQuartoYaml <- any(grepl("^_quarto.y(a)?ml$", x = files, ignore.case = TRUE, perl = TRUE)) - requiresQuarto <- any(length(qmdFiles > 0), hasQuartoYaml) + # 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 + hasQuartoYaml <- any(grepl("^_quarto.y(a)?ml$", x = files, ignore.case = TRUE, perl = TRUE)) + hasQuartoSupportedFiles <- any(length(qmdFiles) > 0, length(rmdFiles > 0)) + requiresQuarto <- (hasQuartoSupportedFiles && 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 diff --git a/tests/testthat/static-with-quarto-yaml/_quarto.yml b/tests/testthat/static-with-quarto-yaml/_quarto.yml new file mode 100644 index 00000000..3749eac1 --- /dev/null +++ b/tests/testthat/static-with-quarto-yaml/_quarto.yml @@ -0,0 +1,2 @@ +project: + title: "slideshow" diff --git a/tests/testthat/static-with-quarto-yaml/slideshow.html b/tests/testthat/static-with-quarto-yaml/slideshow.html new file mode 100644 index 00000000..36a9f361 --- /dev/null +++ b/tests/testthat/static-with-quarto-yaml/slideshow.html @@ -0,0 +1,681 @@ + + + + + + + + + + + + slideshow + + + + + + + + + + + + + + + +
+
+ +
+

slideshow

+
+ +
+

Quarto

+

Quarto enables you to weave together content and executable code into a finished presentation. To learn more about Quarto presentations see https://quarto.org/docs/presentations/.

+
+
+

Bullets

+

When you click the Render button a document will be generated that includes:

+
    +
  • Content authored with markdown
  • +
  • Output from executable code
  • +
+
+
+

Code

+

When you click the Render button a presentation will be generated that includes both content and the output of embedded code. You can embed code like this:

+
+
+
[1] 2
+
+
+ +
+
+
+ + + + + + + + + + + + + + + + + + + + + + + + + \ No newline at end of file diff --git a/tests/testthat/test-bundle.R b/tests/testthat/test-bundle.R index 8711c4d3..35b9d1dd 100644 --- a/tests/testthat/test-bundle.R +++ b/tests/testthat/test-bundle.R @@ -563,7 +563,7 @@ test_that("writeManifest: Quarto Python-only website gets correct manifest data" expect_null(manifest$packages) }) -test_that("writeManifest: Deploying Quarto content without Quarto info in an error", { +test_that("writeManifest: Deploying a Quarto project without Quarto info in an error", { missingQuartoInfoErrorText <- paste( "Attempting to deploy Quarto content without Quarto metadata.", "Please provide the path to a quarto binary to the 'quarto' argument." @@ -576,6 +576,20 @@ test_that("writeManifest: Deploying Quarto content without Quarto info in an err ) }) +test_that("writeManifest: Deploying a Quarto doc without Quarto info in an error", { + missingQuartoInfoErrorText <- paste( + "Attempting to deploy Quarto content without Quarto metadata.", + "Please provide the path to a quarto binary to the 'quarto' argument." + ) + + appDir <- "quarto-doc-none" + appPrimaryDoc <- "quarto-doc-none.qmd" + expect_error( + makeManifest(appDir, appPrimaryDoc = appPrimaryDoc, quarto = NULL), + missingQuartoInfoErrorText + ) +}) + test_that("writeManifest: Deploying R Markdown content with Quarto gives a Quarto app mode", { quarto <- quartoPathOrSkip() @@ -586,6 +600,13 @@ test_that("writeManifest: Deploying R Markdown content with Quarto gives a Quart expect_equal(manifest$metadata$primary_rmd, "simple.Rmd") }) +test_that("writeManifest: Deploying static content with _quarto.yaml succeeds without quartoInfo", { + + manifest <- makeManifest("static-with-quarto-yaml", NULL, quarto = NULL) + + expect_equal(manifest$metadata$appmode, "static") +}) + test_that("writeManifest: Sets environment.image in the manifest if one is provided", { appDir <- "shinyapp-simple"