Skip to content

Commit

Permalink
Don't fail if index writing fails
Browse files Browse the repository at this point in the history
  • Loading branch information
richfitz committed Nov 22, 2023
1 parent 5760b0f commit dc1d6cf
Show file tree
Hide file tree
Showing 3 changed files with 26 additions and 3 deletions.
2 changes: 1 addition & 1 deletion R/outpack_index.R
Original file line number Diff line number Diff line change
Expand Up @@ -74,7 +74,7 @@ index_update <- function(root_path, prev, skip_cache, progress) {

if (!identical(data, prev)) {
fs::dir_create(dirname(path_index))
saverds_atomic(data, path_index)
saverds_atomic(data, path_index, allow_fail = TRUE)
}

data
Expand Down
12 changes: 10 additions & 2 deletions R/util.R
Original file line number Diff line number Diff line change
Expand Up @@ -617,10 +617,18 @@ file_canonical_case <- function(path, workdir) {
}


saverds_atomic <- function(data, path) {
saverds_atomic <- function(data, path, allow_fail = FALSE) {
tmp <- tempfile(pattern = sub("\\.rds", "", basename(path)),
tmpdir = dirname(path),
fileext = ".rds")
saveRDS(data, tmp)
fs::file_move(tmp, path)
if (allow_fail) {
tryCatch(
fs::file_move(tmp, path),
error = function(e) unlink(tmp))
} else {
tryCatch(
fs::file_move(tmp, path),
finally = unlink(tmp))
}
}
15 changes: 15 additions & 0 deletions tests/testthat/test-util.R
Original file line number Diff line number Diff line change
Expand Up @@ -306,3 +306,18 @@ test_that("can convert files to canonical case", {
expect_equal(file_canonical_case("A/win~1/C", tmp), NA_character_)
expect_equal(file_canonical_case(c("a/b/c", "a/b/d"), tmp), c("a/b/c", NA))
})


test_that("can gracefully cope with rds save failure", {
mock_move <- mockery::mock(stop("some error"), cycle = TRUE)
mockery::stub(saverds_atomic, "fs::file_move", mock_move)
tmp <- withr::local_tempdir()
path <- file.path(tmp, "file.rds")
expect_silent(
saverds_atomic(NULL, path, allow_fail = TRUE))
expect_equal(dir(tmp), character())
expect_error(
saverds_atomic(NULL, path, allow_fail = FALSE),
"some error")
expect_equal(dir(tmp), character())
})

0 comments on commit dc1d6cf

Please sign in to comment.