Skip to content

Commit

Permalink
Simplify conditions (#924)
Browse files Browse the repository at this point in the history
* single quotes

* simplify conditions

* further lints
  • Loading branch information
olivroy authored Jan 30, 2024
1 parent 096cfdd commit 61cdc0d
Show file tree
Hide file tree
Showing 13 changed files with 44 additions and 41 deletions.
16 changes: 8 additions & 8 deletions R/class-style_mgr.R
Original file line number Diff line number Diff line change
Expand Up @@ -447,14 +447,14 @@ style_mgr <- R6::R6Class("wbStylesMgr", {
typ <- NULL
id <- NULL

is_numfmt <- any(ifelse(xml_node_name(style[sty]) == "numFmt", TRUE, FALSE))
is_font <- any(ifelse(xml_node_name(style[sty]) == "font", TRUE, FALSE))
is_fill <- any(ifelse(xml_node_name(style[sty]) == "fill", TRUE, FALSE))
is_border <- any(ifelse(xml_node_name(style[sty]) == "border", TRUE, FALSE))
is_xf <- any(ifelse(xml_node_name(style[sty]) == "xf", TRUE, FALSE))
is_celSty <- any(ifelse(xml_node_name(style[sty]) == "cellStyle", TRUE, FALSE))
is_dxf <- any(ifelse(xml_node_name(style[sty]) == "dxf", TRUE, FALSE))
is_tabSty <- any(ifelse(xml_node_name(style[sty]) == "tableStyle", TRUE, FALSE))
is_numfmt <- any(xml_node_name(style[sty]) == "numFmt")
is_font <- any(xml_node_name(style[sty]) == "font")
is_fill <- any(xml_node_name(style[sty]) == "fill")
is_border <- any(xml_node_name(style[sty]) == "border")
is_xf <- any(xml_node_name(style[sty]) == "xf")
is_celSty <- any(xml_node_name(style[sty]) == "cellStyle")
is_dxf <- any(xml_node_name(style[sty]) == "dxf")
is_tabSty <- any(xml_node_name(style[sty]) == "tableStyle")

is_xf_fr <- isTRUE(attr(style, "cellStyleXf"))

Expand Down
2 changes: 1 addition & 1 deletion R/class-workbook-utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -162,7 +162,7 @@ wb_create_columns <- function(wb, sheet, cols) {
col_df <- col_to_df(read_xml(wb$createCols(sheet, n = max(cols))))

# found a few cols, but not all required cols. create the missing columns
if (any(!cols %in% as.numeric(col_df$min))) {
if (!all(cols %in% as.numeric(col_df$min))) {
beg <- max(as.numeric(col_df$min)) + 1
end <- max(cols)

Expand Down
32 changes: 17 additions & 15 deletions R/class-workbook.R
Original file line number Diff line number Diff line change
Expand Up @@ -1561,7 +1561,7 @@ wbWorkbook <- R6::R6Class(
sel <- which(pt$name == pivot_table)
cid <- pt$cacheId[sel]

uni_name <- paste0(stringi::stri_replace_all_fixed(slicer, ' ', '_'), cid)
uni_name <- paste0(stringi::stri_replace_all_fixed(slicer, " ", "_"), cid)

### slicer_cache
sortOrder <- NULL
Expand Down Expand Up @@ -2517,16 +2517,16 @@ wbWorkbook <- R6::R6Class(
)
} else {
write_file(
head = '',
head = "",
body = '<styleSheet xmlns:x="http://schemas.openxmlformats.org/spreadsheetml/2006/main"/>',
tail = '',
tail = "",
fl = file.path(xlDir, "styles.xml")
)
}

if (length(self$calcChain)) {
write_file(
head = '',
head = "",
body = pxml(self$calcChain),
tail = "",
fl = file.path(xlDir, "calcChain.xml")
Expand All @@ -2536,9 +2536,9 @@ wbWorkbook <- R6::R6Class(
# write metadata file. required if cm attribut is set.
if (length(self$metadata)) {
write_file(
head = '',
head = "",
body = self$metadata,
tail = '',
tail = "",
fl = file.path(xlDir, "metadata.xml")
)
}
Expand Down Expand Up @@ -2579,7 +2579,7 @@ wbWorkbook <- R6::R6Class(
CT$tmpDirPartName <- paste0(tmpDir, CT$PartName)
CT$fileExists <- file.exists(CT$tmpDirPartName)

if (any(!CT$fileExists)) {
if (!all(CT$fileExists)) {
missing_in_tmp <- CT$PartName[!CT$fileExists]
warning(
"[CT] file expected to be in output is missing: ",
Expand All @@ -2592,7 +2592,7 @@ wbWorkbook <- R6::R6Class(
WR$tmpDirPartName <- paste0(tmpDir, "/xl/", WR$Target)
WR$fileExists <- file.exists(WR$tmpDirPartName)

if (any(!WR$fileExists)) {
if (!all(WR$fileExists)) {
missing_in_tmp <- WR$Target[!WR$fileExists]
warning(
"[WR] file expected to be in output is missing: ",
Expand Down Expand Up @@ -2634,7 +2634,7 @@ wbWorkbook <- R6::R6Class(
WR$type <- basename(WR$Type)
WR <- WR[WR$type != "hyperlink", ]

if (any(!WR$fileExists)) {
if (!all(WR$fileExists)) {
missing_in_tmp <- WR$Target[!WR$fileExists]
warning(
"[", folder, "] file expected to be in output is missing: ",
Expand Down Expand Up @@ -3377,7 +3377,8 @@ wbWorkbook <- R6::R6Class(
stop("Invalid rows entered (<= 0).")
}

hidden <- all(collapsed == TRUE)
# all collapsed = TRUE
hidden <- all(collapsed)
collapsed <- rep(as.character(as.integer(collapsed)), length.out = length(cols))

# Remove duplicates
Expand Down Expand Up @@ -3599,7 +3600,8 @@ wbWorkbook <- R6::R6Class(
stop("Invalid rows entered (<= 0).")
}

hidden <- all(collapsed == TRUE)
# all collapsed = TRUE
hidden <- all(collapsed)
collapsed <- rep(as.character(as.integer(collapsed)), length.out = length(rows))

# Remove duplicates
Expand Down Expand Up @@ -7847,9 +7849,9 @@ wbWorkbook <- R6::R6Class(
## write vml output
if (self$vml[[i]] != "") {
write_file(
head = '',
head = "",
body = pxml(self$vml[[i]]),
tail = '',
tail = "",
fl = file.path(dir, sprintf("vmlDrawing%s.vml", i))
)

Expand Down Expand Up @@ -7951,9 +7953,9 @@ wbWorkbook <- R6::R6Class(
## Write drawing i (will always exist) skip those that are empty
if (!all(self$drawings[[i]] == "")) {
write_file(
head = '',
head = "",
body = pxml(self$drawings[[i]]),
tail = '',
tail = "",
fl = file.path(xldrawingsDir, stri_join("drawing", i, ".xml"))
)
if (!all(self$drawings_rels[[i]] == "")) {
Expand Down
2 changes: 1 addition & 1 deletion R/converters.R
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@ int2col <- function(x) {
col2int <- function(x) {
if (is.null(x)) return(NULL)

if (is.numeric(x) || is.integer(x) || is.factor(x))
if (is.numeric(x) || is.factor(x))
return(as.integer(x))

if (!is.character(x)) {
Expand Down
2 changes: 1 addition & 1 deletion R/helper-functions.R
Original file line number Diff line number Diff line change
Expand Up @@ -114,7 +114,7 @@ validate_color <- function(color = NULL, or_null = FALSE, envir = parent.frame()
## create a total size of 8 in ARGB format
color <- stringi::stri_pad_left(str = color, width = 8, pad = "F")

if (any(!grepl("[A-F0-9]{8}$", color))) {
if (!all(grepl("[A-F0-9]{8}$", color))) {
if (is.null(msg)) msg <- sprintf("`%s` ['%s'] is not a valid color", sx, color)
stop(simpleError(msg))
}
Expand Down
4 changes: 2 additions & 2 deletions R/pivot_table.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ distinct <- function(x) {
unis <- stringi::stri_unique(x)
lwrs <- tolower(unis)
dups <- duplicated(lwrs)
unis[dups == FALSE]
unis[!dups]
}

# append number of duplicated value.
Expand Down Expand Up @@ -71,7 +71,7 @@ cacheFields <- function(wbdata, filter, rows, cols, data, slicer) {
sharedItem <- NULL
}

if (any(is.na(dat))) {
if (anyNA(dat)) {
containsBlank <- "1"
containsSemiMixedTypes <- NULL
} else {
Expand Down
2 changes: 1 addition & 1 deletion R/pugixml.R
Original file line number Diff line number Diff line change
Expand Up @@ -123,7 +123,7 @@ xml_node <- function(xml, level1 = NULL, level2 = NULL, level3 = NULL, ...) {
if (length(lvl) == 1) z <- getXMLXPtr1(xml, level1)
if (length(lvl) == 2) z <- getXMLXPtr2(xml, level1, level2)
if (length(lvl) == 3) z <- getXMLXPtr3(xml, level1, level2, level3)
if (length(lvl) == 3) if (level2 == "*") z <- unkgetXMLXPtr3(xml, level1, level3)
if (length(lvl) == 3 && level2 == "*") z <- unkgetXMLXPtr3(xml, level1, level3)
}

z
Expand Down
4 changes: 2 additions & 2 deletions R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -252,7 +252,7 @@ check_wb_dims_args <- function(args, select = NULL) {

cond_acceptable_len_1 <- !is.null(args$from_row) || !is.null(args$from_col) || !is.null(args$x)
nams <- names(args) %||% rep("", length(args))
all_args_unnamed <- all(!nzchar(nams))
all_args_unnamed <- !any(nzchar(nams))

if (length(args) == 1 && !cond_acceptable_len_1) {
# Providing a single argument acceptable is only `x`
Expand Down Expand Up @@ -582,7 +582,7 @@ wb_dims <- function(..., select = NULL) {
}

# Just keeping this as a safeguard
has_some_unnamed_args <- any(!nzchar(nams))
has_some_unnamed_args <- !all(nzchar(nams))
if (has_some_unnamed_args) {
stop("Internal error, all arguments should be named after this point.")
}
Expand Down
6 changes: 3 additions & 3 deletions R/wb_functions.R
Original file line number Diff line number Diff line change
Expand Up @@ -122,7 +122,7 @@ guess_col_type <- function(tt) {
numfmt_is_date <- function(numFmt) {

# if numFmt is character(0)
if (length(numFmt) == 0) return(z <- NULL)
if (length(numFmt) == 0) return(NULL)

numFmt_df <- read_numfmt(read_xml(numFmt))
# we have to drop any square bracket part
Expand Down Expand Up @@ -152,7 +152,7 @@ numfmt_is_date <- function(numFmt) {
numfmt_is_posix <- function(numFmt) {

# if numFmt is character(0)
if (length(numFmt) == 0) return(z <- NULL)
if (length(numFmt) == 0) return(NULL)

numFmt_df <- read_numfmt(read_xml(numFmt))
# we have to drop any square bracket part
Expand Down Expand Up @@ -184,7 +184,7 @@ numfmt_is_posix <- function(numFmt) {
numfmt_is_hms <- function(numFmt) {

# if numFmt is character(0)
if (length(numFmt) == 0) return(z <- NULL)
if (length(numFmt) == 0) return(NULL)

numFmt_df <- read_numfmt(read_xml(numFmt))
# we have to drop any square bracket part
Expand Down
5 changes: 3 additions & 2 deletions R/write.R
Original file line number Diff line number Diff line change
Expand Up @@ -99,7 +99,7 @@ inner_update <- function(
cc[sel, replacement] <- x[replacement]

# avoid missings in cc
if (any(is.na(cc)))
if (anyNA(cc))
cc[is.na(cc)] <- ""

# push everything back to workbook
Expand Down Expand Up @@ -450,7 +450,8 @@ write_data2 <- function(
# styles. gets the reference an passes it on.
get_data_class_dims <- function(data_class) {
sel <- dc == openxlsx2_celltype[[data_class]]
sel_cols <- names(rtyp[sel == TRUE])
# sel = TRUE
sel_cols <- names(rtyp[sel])
sel_rows <- rownames(rtyp)

# ignore first row if colNames
Expand Down
2 changes: 1 addition & 1 deletion R/write_xlsx.R
Original file line number Diff line number Diff line change
Expand Up @@ -250,7 +250,7 @@ write_xlsx <- function(x, file, as_table = FALSE, ...) {
colWidths <- NULL
if ("col_widths" %in% names(params)) {
colWidths <- params$col_widths
if (any(is.na(colWidths))) colWidths[is.na(colWidths)] <- 8.43
if (anyNA(colWidths)) colWidths[is.na(colWidths)] <- 8.43
}


Expand Down
4 changes: 2 additions & 2 deletions tests/testthat/helper.R
Original file line number Diff line number Diff line change
Expand Up @@ -1020,9 +1020,9 @@ testfile_path <- function(x, replace = FALSE) {

if (!file.exists(fl)) {
return(testthat::skip("Testfile does not exist"))
} else {
return(fl)
}

fl
}


Expand Down
4 changes: 2 additions & 2 deletions tests/testthat/test-conditional_formatting.R
Original file line number Diff line number Diff line change
Expand Up @@ -695,8 +695,8 @@ test_that("containsBlanks works", {

wb <- wb_workbook()
wb$add_worksheet()
wb$add_data(x = c(NA, 1, 2, ''), colNames = FALSE, na.strings = NULL)
wb$add_data(x = c(NA, 1, 2, ''), colNames = FALSE, na.strings = NULL, startCol = 2)
wb$add_data(x = c(NA, 1, 2, ""), colNames = FALSE, na.strings = NULL)
wb$add_data(x = c(NA, 1, 2, ""), colNames = FALSE, na.strings = NULL, startCol = 2)
wb$add_conditional_formatting(cols = 1, rows = 1:4, type = "containsBlanks")
wb$add_conditional_formatting(cols = 2, rows = 1:4, type = "notContainsBlanks")

Expand Down

0 comments on commit 61cdc0d

Please sign in to comment.