Skip to content

Commit

Permalink
Deployment record improvements (#827)
Browse files Browse the repository at this point in the history
* Improve `envVars` handling. Fixes #820.
* Add support for `version`. Fixes #821.
* Name arguments to `createDeploymentTarget()` calls
  • Loading branch information
hadley authored May 2, 2023
1 parent e6c0b1e commit 0918f7f
Show file tree
Hide file tree
Showing 5 changed files with 78 additions and 33 deletions.
47 changes: 25 additions & 22 deletions R/deploymentTarget.R
Original file line number Diff line number Diff line change
Expand Up @@ -41,13 +41,13 @@ deploymentTarget <- function(recordPath = ".",
}

createDeploymentTarget(
appName,
appTitle,
appId,
envVars,
fullAccount$name, # first deploy must be to own account
fullAccount$name,
fullAccount$server
appName = appName,
appTitle = appTitle,
appId = appId,
envVars = envVars,
username = fullAccount$name, # first deploy must be to own account
account = fullAccount$name,
server = fullAccount$server
)
} else if (nrow(appDeployments) == 1) {
# If both appName and appId supplied, check that they're consistent.
Expand Down Expand Up @@ -77,12 +77,12 @@ deploymentTargetForApp <- function(appId,
application <- getApplication(accountDetails$name, accountDetails$server, appId)

createDeploymentTarget(
application$name,
application$title %||% appTitle,
application$id,
application$owner_username,
accountDetails$name,
accountDetails$server
appName = application$name,
appTitle = application$title %||% appTitle,
appId = application$id,
username = application$owner_username,
account = accountDetails$name,
server = accountDetails$server
)
}

Expand All @@ -92,28 +92,31 @@ createDeploymentTarget <- function(appName,
envVars,
username,
account,
server) {
server,
version = 1) {
list(
appName = appName,
appTitle = appTitle %||% "",
envVars = envVars,
appId = appId,
username = username,
account = account,
server = server
server = server,
version = version
)
}

updateDeploymentTarget <- function(previous, appTitle = NULL, envVars = NULL) {
createDeploymentTarget(
previous$name,
appTitle %||% previous$title,
previous$appId,
envVars %||% previous$envVars[[1]],
appName = previous$name,
appTitle = appTitle %||% previous$title,
appId = previous$appId,
envVars = envVars %||% previous$envVars[[1]],
# if username not previously recorded, use current account
previous$username %||% previous$account,
previous$account,
previous$server
username = previous$username %||% previous$account,
account = previous$account,
server = previous$server,
version = previous$version
)
}

Expand Down
14 changes: 10 additions & 4 deletions R/deployments.R
Original file line number Diff line number Diff line change
Expand Up @@ -70,6 +70,7 @@ deployments <- function(appPath = ".",
ok <- ok & okServer
}

deployments$envVars[is.na(deployments$envVars)] <- ""
if (is.character(deployments$envVars)) {
deployments$envVars <- strsplit(deployments$envVars, ", ")
}
Expand All @@ -79,9 +80,11 @@ deployments <- function(appPath = ".",

deploymentFields <- c(
"name", "title", "username", "account", "server", "hostUrl", "appId",
"bundleId", "url", "envVars"
"bundleId", "url", "envVars", "version"
)

deploymentRecordVersion <- 1L

saveDeployment <- function(recordDir,
target,
application,
Expand All @@ -97,6 +100,7 @@ saveDeployment <- function(recordDir,
account = target$account,
server = target$server,
envVars = target$envVars,
version = target$version,
hostUrl = hostUrl,
appId = application$id,
bundleId = bundleId,
Expand All @@ -111,7 +115,7 @@ saveDeployment <- function(recordDir,
addToDeploymentHistory(recordDir, deployment)
}

invisible(NULL)
invisible(path)
}

deploymentRecord <- function(name,
Expand All @@ -124,6 +128,7 @@ deploymentRecord <- function(name,
appId = NULL,
bundleId = NULL,
url = NULL,
version = deploymentRecordVersion,
metadata = list()) {

check_character(envVars, allow_null = TRUE)
Expand All @@ -134,11 +139,12 @@ deploymentRecord <- function(name,
username = username,
account = account,
server = server,
envVars = paste0(envVars, collapse = ", "),
envVars = if (length(envVars) > 0) paste0(envVars, collapse = ", ") else NA,
hostUrl = hostUrl %||% "",
appId = appId %||% "",
bundleId = bundleId %||% "",
url = url %||% ""
url = url %||% "",
version = version
)
c(standard, metadata)
}
Expand Down
5 changes: 3 additions & 2 deletions tests/testthat/helper.R
Original file line number Diff line number Diff line change
Expand Up @@ -83,6 +83,7 @@ addTestDeployment <- function(path,
server = "example.com",
url = paste0("https://", server, "/", username, "/", appId),
hostUrl = NULL,
version = deploymentRecordVersion,
metadata = list()) {
saveDeployment(
path,
Expand All @@ -93,12 +94,12 @@ addTestDeployment <- function(path,
envVars = envVars,
account = account,
username = username,
server = server
server = server,
version = version
),
application = list(id = appId, url = url),
hostUrl = hostUrl,
metadata = metadata,
addToHistory = FALSE
)
invisible()
}
9 changes: 8 additions & 1 deletion tests/testthat/test-deploymentTarget.R
Original file line number Diff line number Diff line change
Expand Up @@ -80,11 +80,18 @@ test_that("succeeds if there's a single existing deployment", {
addTestAccount("ron")

app_dir <- withr::local_tempdir()
addTestDeployment(app_dir, appName = "test", appId = "1", username = "ron")
addTestDeployment(
app_dir,
appName = "test",
appId = "1",
username = "ron",
version = "999"
)

target <- deploymentTarget(app_dir)
expect_equal(target$appId, "1")
expect_equal(target$username, "ron")
expect_equal(target$version, "999")

target <- deploymentTarget(app_dir, appName = "test")
expect_equal(target$appId, "1")
Expand Down
36 changes: 32 additions & 4 deletions tests/testthat/test-deployments.R
Original file line number Diff line number Diff line change
Expand Up @@ -69,6 +69,25 @@ test_that("can read/write metadata", {
expect_equal(out$meta2, "two")
})

test_that("can read/write version", {
dir <- local_temp_app()

addTestDeployment(dir, version = "999")
out <- deployments(dir, excludeOrphaned = FALSE)
expect_equal(out$version, "999")
})

test_that("can read/write missing version", {
# also tests we can read files written by previous versions of package
dir <- local_temp_app()

path <- addTestDeployment(dir, version = NA)
out <- deployments(dir, excludeOrphaned = FALSE)

expect_false("version" %in% rownames(read.dcf(path)))
expect_equal(out$version, NA)
})

test_that("can read/write env vars", {
app <- local_temp_app()
addTestDeployment(app, "test1", envVars = c("TEST1", "TEST2"))
Expand All @@ -78,12 +97,21 @@ test_that("can read/write env vars", {
expect_equal(deps$envVars, list(c("TEST1", "TEST2"), character()))
})

test_that("can read env vars when none set", {
test_that("can read/write empty env vars", {
# also tests we can read files written by previous versions of package
app <- local_temp_app()
addTestDeployment(app, "test1", envVars = NA_character_)

# With empty character vector
path <- addTestDeployment(app, "test1", envVars = character())
deps <- deployments(app, excludeOrphaned = FALSE)
expect_equal(deps$envVars, list(NA_character_))
expect_false("envVars" %in% rownames(read.dcf(path)))
expect_equal(deps$envVars, list(character()))

# Or with empty string
path <- addTestDeployment(app, "test1", envVars = "")
deps <- deployments(app, excludeOrphaned = FALSE)
expect_false("envVars" %in% rownames(read.dcf(path)))
expect_equal(deps$envVars, list(character()))
})

test_that("can read/write env vars", {
Expand All @@ -108,7 +136,7 @@ test_that("saveDeployment appends to global history", {
appName = "my-app",
appTitle = "",
appId = 10,
envVars = NULL,
envVars = "abc", # ensure there's an envVars column in output
account = "foo",
username = "foo",
server = "bar"
Expand Down

0 comments on commit 0918f7f

Please sign in to comment.