Skip to content

Commit

Permalink
Keep files until object is gc-d, closes #23
Browse files Browse the repository at this point in the history
print() shows the directory, if still around.
  • Loading branch information
gaborcsardi committed Jul 19, 2017
1 parent 656ad73 commit 8808e7f
Show file tree
Hide file tree
Showing 3 changed files with 20 additions and 3 deletions.
4 changes: 2 additions & 2 deletions R/package.R
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,6 @@ rcmdcheck <- function(path = ".", quiet = FALSE, args = character(),
}

targz <- build_package(path, tmp <- tempfile())
on.exit(unlink(tmp, recursive = TRUE), add = TRUE)

out <- with_dir(
dirname(targz),
Expand All @@ -63,7 +62,8 @@ rcmdcheck <- function(path = ".", quiet = FALSE, args = character(),
version = unname(dsc$get("Version")),
rversion = R.Version()$version.string, # should be the same
platform = R.Version()$platform, # should be the same
description = read_char(tmpdesc)
description = read_char(tmpdesc),
tempfiles = tmp
)

res
Expand Down
13 changes: 12 additions & 1 deletion R/parse.R
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@

parse_check_output <- function(output, package = NULL, version = NULL,
rversion = NULL, platform = NULL,
description = NULL) {
description = NULL, tempfiles = NULL) {

entries <- strsplit(paste0("\n", output$stdout), "\n* ", fixed = TRUE)[[1]][-1]

Expand All @@ -27,6 +27,17 @@ parse_check_output <- function(output, package = NULL, version = NULL,
res$errors = c(res$errors, "R CMD check timed out")
}

if (!is.null(tempfiles)) {
res$cleaner <- new.env(parent = emptyenv())
res$cleaner$cleanme <- tempfiles
finalizer <- function(e) {
try(unlink(e$cleanme, recursive = TRUE), silent = TRUE)
}
## To avoid keeping this execution environment
environment(finalizer) <- baseenv()
reg.finalizer(res$cleaner, finalizer, onexit = TRUE)
}

res
}

Expand Down
6 changes: 6 additions & 0 deletions R/print.R
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,12 @@ print.rcmdcheck <- function(x, header = TRUE, ...) {
lapply(x$notes, print_entry)
}

if (!is.null(x$cleaner) && file.exists(chkdir <- x$cleaner$cleanme)) {
cat(" Check directory: ", sQuote(chkdir), "\n", sep = "")
} else {
cat(" Check directory already cleared.\n")
}

summary(x, ...)
}

Expand Down

0 comments on commit 8808e7f

Please # to comment.