Skip to content

Commit

Permalink
add password argument
Browse files Browse the repository at this point in the history
  • Loading branch information
JanMarvin committed Jul 18, 2023
1 parent 45cb57f commit 4703cca
Show file tree
Hide file tree
Showing 7 changed files with 59 additions and 7 deletions.
8 changes: 6 additions & 2 deletions R/class-workbook-wrappers.R
Original file line number Diff line number Diff line change
Expand Up @@ -59,6 +59,10 @@ wb_workbook <- function(
#' @param wb A `wbWorkbook` object to write to file
#' @param path A path to save the workbook to
#' @param overwrite If `FALSE`, will not overwrite when `path` exists
#' @param password an optional password to encrypt the input file. The input is
#' encrypted once the output file is written. The password is expected to be
#' plain text. If security is of importance, do not use this argument. If the
#' password is lost, opening the file will be impossible.
#'
#' @export
#' @family workbook wrappers
Expand All @@ -74,9 +78,9 @@ wb_workbook <- function(
#' \donttest{
#' wb_save(wb, path = temp_xlsx(), overwrite = TRUE)
#' }
wb_save <- function(wb, path = NULL, overwrite = TRUE) {
wb_save <- function(wb, path = NULL, overwrite = TRUE, password = NULL) {
assert_workbook(wb)
wb$clone()$save(path = path, overwrite = overwrite)
wb$clone()$save(path = path, overwrite = overwrite, password = password)
}

# add data ----------------------------------------------------------------
Expand Down
9 changes: 8 additions & 1 deletion R/class-workbook.R
Original file line number Diff line number Diff line change
Expand Up @@ -1490,6 +1490,7 @@ wbWorkbook <- R6::R6Class(
#' @param sheet sheet
#' @param data_only data_only
#' @param calc_chain calc_chain
#' @param password password
#' @param ... additional arguments
#' @return The `wbWorkbook` object invisibly
load = function(
Expand All @@ -1498,6 +1499,7 @@ wbWorkbook <- R6::R6Class(
sheet,
data_only = FALSE,
calc_chain = FALSE,
password = NULL,
...
) {
if (missing(file)) file <- substitute()
Expand All @@ -1521,8 +1523,9 @@ wbWorkbook <- R6::R6Class(
#' Save the workbook
#' @param path The path to save the workbook to
#' @param overwrite If `FALSE`, will not overwrite when `path` exists
#' @param password password
#' @return The `wbWorkbook` object invisibly
save = function(path = self$path, overwrite = TRUE) {
save = function(path = self$path, overwrite = TRUE, password = NULL) {
assert_class(path, "character")
assert_class(overwrite, "logical")

Expand Down Expand Up @@ -2206,6 +2209,10 @@ wbWorkbook <- R6::R6Class(
stop("Failed to save workbook")
}

if (!is.null(password)) {
msoc("enc", inFile = path, outFile = path, pass = password)
}

# (re)assign file path (if successful)
self$path <- path
invisible(self)
Expand Down
17 changes: 15 additions & 2 deletions R/wb_load.R
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,12 @@
#' chain will be created upon the next time the worksheet is loaded in
#' spreadsheet software. Keeping it, might only speed loading time in said
#' software.
#' @param password an optional password to decrypt the input file. The input is
#' decrypted into a temporary folder on the hard drive. Afterwards it is loaded
#' into a wbWorkbook object and can be interacted with. Unless it is saved with
#' [wb_save()] argument `password` it remains decrypted. And the password is
#' expected to be plain text. If security is of importance, do not use this
#' argument.
#' @param ... additional arguments
#' @description wb_load returns a workbook object conserving styles and
#' formatting of the original .xlsx file.
Expand All @@ -33,15 +39,22 @@
#' wb$add_worksheet("A new worksheet")
wb_load <- function(
file,
xlsx_file = NULL,
xlsx_file = NULL,
sheet,
data_only = FALSE,
data_only = FALSE,
calc_chain = FALSE,
password = NULL,
...
) {

standardize_case_names(...)

if (!is.null(password)) {
temp <- temp_xlsx()
msoc("dec", inFile = file, outFile = temp, pass = password)
file <- temp
}

file <- xlsx_file %||% file
file <- getFile(file)

Expand Down
7 changes: 6 additions & 1 deletion man/wbWorkbook.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

8 changes: 8 additions & 0 deletions man/wb_load.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

7 changes: 6 additions & 1 deletion man/wb_save.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

10 changes: 10 additions & 0 deletions tests/testthat/test-cryptography.R
Original file line number Diff line number Diff line change
Expand Up @@ -31,4 +31,14 @@ test_that("test that encryption works", {
0
)

tmp <- temp_xlsx()
wbin <- wb_workbook()$add_worksheet()$
add_data(x = head(iris))$save(tmp, password = "openxlsx2")

wbout <- wb_load(tmp, password = "openxlsx2")
exp <- wb_to_df(wbin)
got <- wb_to_df(wbout)

expect_equal(exp, got)

})

0 comments on commit 4703cca

Please sign in to comment.