diff --git a/NEWS.md b/NEWS.md
index 23cd7b88f..a7c719283 100644
--- a/NEWS.md
+++ b/NEWS.md
@@ -14,6 +14,8 @@
## Fixes
+* Improvements to setting column widths. Previously values set by `set_col_widths()` were a little off. This has now been improved. There are still corner cases where the column width set with `openxlsx2` does not match those shown in spreadsheet software. Notable differences can be seen with floating point values (e.g., `10L` works while `10.1` is slightly off) and with column width on Mac. [350](https://github.com/JanMarvin/openxlsx2/pull/350)
+
* Improve `rowNames` when writing data to worksheet. Previously the name for the rownames column defaulted to `1`. This has been changed. Now with data it defaults to an empty cell and with a data table it defaults to `_rowNames_`. [375](https://github.com/JanMarvin/openxlsx2/pull/375)
* Fix the workbook xml relationship file to not include a reference to shared strings per default. This solves [360](https://github.com/JanMarvin/openxlsx2/issues/360) for plain data files written from `openxlsx2`. [363](https://github.com/JanMarvin/openxlsx2/pull/363)
diff --git a/R/baseXML.R b/R/baseXML.R
index 832e4dda9..b07fd3190 100644
--- a/R/baseXML.R
+++ b/R/baseXML.R
@@ -137,7 +137,7 @@ genBaseStyleSheet <- function(dxfs = NULL, tableStyles = NULL, extLst = NULL) {
list(
numFmts = NULL,
- fonts = c(''),
+ fonts = c(''),
fills = c(
'',
diff --git a/R/class-workbook-wrappers.R b/R/class-workbook-wrappers.R
index d8b54cb47..025eaaecf 100644
--- a/R/class-workbook-wrappers.R
+++ b/R/class-workbook-wrappers.R
@@ -788,7 +788,7 @@ wb_remove_worksheet <- function(wb, sheet = current_sheet()) {
#'
#' wb$add_data("S1", iris)
#' wb$add_data_table("S1", x = iris, startCol = 10) ## font colour does not affect tables
-wb_set_base_font <- function(wb, fontSize = 11, fontColour = "black", fontName = "Calibri") {
+wb_set_base_font <- function(wb, fontSize = 11, fontColour = wb_colour(theme = "1"), fontName = "Calibri") {
assert_workbook(wb)
wb$clone()$set_base_font(
fontSize = fontSize,
diff --git a/R/class-workbook.R b/R/class-workbook.R
index aac76218f..6a7b9b3c0 100644
--- a/R/class-workbook.R
+++ b/R/class-workbook.R
@@ -1863,7 +1863,7 @@ wbWorkbook <- R6::R6Class(
name <- unlist(xml_attr(baseFont, "font", "name"))
if (length(sz[[1]]) == 0) {
- sz <- list("val" = "10")
+ sz <- list("val" = "11")
} else {
sz <- as.list(sz)
}
@@ -1893,16 +1893,10 @@ wbWorkbook <- R6::R6Class(
#' @param fontColour fontColour
#' @param fontName fontName
#' @return The `wbWorkbook` object
- set_base_font = function(fontSize = 11, fontColour = "black", fontName = "Calibri") {
+ set_base_font = function(fontSize = 11, fontColour = wb_colour(theme = "1"), fontName = "Calibri") {
if (fontSize < 0) stop("Invalid fontSize")
- fontColour <- validateColour(fontColour)
-
- self$styles_mgr$styles$fonts[[1]] <- sprintf(
- '',
- fontSize,
- fontColour,
- fontName
- )
+ if (is.character(fontColour) && is.null(names(fontColour))) fontColour <- wb_colour(fontColour)
+ self$styles_mgr$styles$fonts[[1]] <- create_font(sz = as.character(fontSize), color = fontColour, name = fontName)
},
### sheet names ----
@@ -2248,43 +2242,22 @@ wbWorkbook <- R6::R6Class(
## Remove duplicates
ok <- !duplicated(cols)
- widths <- widths[ok]
+ col_width <- widths[ok]
hidden <- hidden[ok]
cols <- cols[ok]
col_df <- self$worksheets[[sheet]]$unfold_cols()
+ base_font <- wb_get_base_font(self)
if (any(widths == "auto")) {
-
df <- wb_to_df(self, sheet = sheet, cols = cols, colNames = FALSE)
# TODO format(x) might not be the way it is formatted in the xlsx file.
col_width <- vapply(df, function(x) max(nchar(format(x))), NA_real_)
+ }
- # message() should be used instead if we really needed to show this
- # print(col_width)
-
- # https://docs.microsoft.com/en-us/dotnet/api/documentformat.openxml.spreadsheet.column
-
- # TODO save this instead as internal package data for quicker loading
- fw <- system.file("extdata", "fontwidth/FontWidth.csv", package = "openxlsx2")
- font_width_tab <- read.csv(fw)
-
- # TODO base font might not be the font used in this column
- base_font <- wb_get_base_font(self)
- font <- base_font$name$val
- size <- as.integer(base_font$size$val)
-
- sel <- font_width_tab$FontFamilyName == font & font_width_tab$FontSize == size
- # maximum digit width of selected font
- mdw <- font_width_tab$Width[sel]
- # formula from openxml.spreadsheet.column documentation. The formula returns exactly the expected
- # value, but the output in excel is still off. Therefore round to create even numbers. In my tests
- # the results were close to the initial col_width sizes. Character width is still bad, numbers are
- # way larger, therefore characters cells are to wide. Not sure if we need improve this.
- widths <- trunc((col_width * mdw + 5) / mdw * 256) / 256
- widths <- round(widths)
- }
+ # https://docs.microsoft.com/en-us/dotnet/api/documentformat.openxml.spreadsheet.column
+ widths <- calc_col_width(base_font = base_font, col_width = col_width)
# create empty cols
if (NROW(col_df) == 0)
diff --git a/R/class-worksheet.R b/R/class-worksheet.R
index a770ffe8b..f78c5d885 100644
--- a/R/class-worksheet.R
+++ b/R/class-worksheet.R
@@ -199,7 +199,7 @@ wbWorksheet <- R6::R6Class(
self$sheetPr <- tabColour
self$dimension <- ''
self$sheetViews <- sprintf('', as.integer(zoom), as.integer(gridLines), as.integer(rowColHeaders), as.integer(tabSelected))
- self$sheetFormatPr <- ''
+ self$sheetFormatPr <- ''
self$cols_attr <- character()
self$autoFilter <- character()
self$mergeCells <- character()
@@ -714,7 +714,7 @@ empty_cols_attr <- function(n = 0, beg, end) {
if (n > 0) {
z$min <- n_seq
z$max <- n_seq
- z$width <- "8.43" # default width in ms365
+ z$width <- "8.43"
}
z
diff --git a/R/converters.R b/R/converters.R
index c3781b548..df00fd6d7 100644
--- a/R/converters.R
+++ b/R/converters.R
@@ -61,3 +61,40 @@ get_cell_refs <- function(cellCoords) {
l <- int2col(unlist(cellCoords[, 2]))
paste0(l, cellCoords[, 1])
}
+
+
+
+#' calculate the required column width
+#'
+#' @param base_font the base font name and fontsize
+#' @param col_width column width
+#' @keywords internal
+#' @examples
+#' base_font <- wb_get_base_font(wb)
+#' calc_col_width(base_font, col_width = 10)
+#' @noRd
+calc_col_width <- function(base_font, col_width) {
+
+ # TODO save this instead as internal package data for quicker loading
+ fw <- system.file("extdata", "fontwidth/FontWidth.csv", package = "openxlsx2")
+ font_width_tab <- read.csv(fw)
+
+ # TODO base font might not be the font used in this column
+ font <- base_font$name$val
+ size <- as.integer(base_font$size$val)
+
+ sel <- font_width_tab$FontFamilyName == font & font_width_tab$FontSize == size
+ # maximum digit width of selected font
+ mdw <- font_width_tab$Width[sel]
+
+ # formula from openxml.spreadsheet.column documentation. The formula returns exactly the expected
+ # value, but the output in excel is still off. Therefore round to create even numbers. In my tests
+ # the results were close to the initial col_width sizes. Character width is still bad, numbers are
+ # way larger, therefore characters cells are to wide. Not sure if we need improve this.
+
+ # Note: cannot reproduce the exact values with MS365 on Mac. Nevertheless, these values are closer
+ # to the expected widths
+ widths <- trunc((as.numeric(col_width) * mdw + 5) / mdw * 256) / 256
+ widths <- round(widths, 3)
+ widths
+}
diff --git a/man/wbWorkbook.Rd b/man/wbWorkbook.Rd
index 7544ecfbe..b90bb656c 100644
--- a/man/wbWorkbook.Rd
+++ b/man/wbWorkbook.Rd
@@ -836,8 +836,8 @@ A list of of the font
Get the base font
\subsection{Usage}{
\if{html}{\out{
}}\preformatted{wbWorkbook$set_base_font(
- fontSize = 11,
- fontColour = "black",
+ fontSize = 12,
+ fontColour = wb_colour(theme = "1"),
fontName = "Calibri"
)}\if{html}{\out{
}}
}
diff --git a/man/wb_modify_basefont.Rd b/man/wb_modify_basefont.Rd
index 7caae8ed5..786d6ab92 100644
--- a/man/wb_modify_basefont.Rd
+++ b/man/wb_modify_basefont.Rd
@@ -5,7 +5,12 @@
\alias{wb_set_base_font}
\title{Modify the default font}
\usage{
-wb_set_base_font(wb, fontSize = 11, fontColour = "black", fontName = "Calibri")
+wb_set_base_font(
+ wb,
+ fontSize = 11,
+ fontColour = wb_colour(theme = "1"),
+ fontName = "Calibri"
+)
}
\arguments{
\item{wb}{A workbook object}
diff --git a/tests/testthat/test-base_font.R b/tests/testthat/test-base_font.R
index c4edb9594..8dc49810d 100644
--- a/tests/testthat/test-base_font.R
+++ b/tests/testthat/test-base_font.R
@@ -5,12 +5,12 @@ test_that("get_base_font works", {
list(
size = list(val = "11"),
# should this be "#000000"?
- colour = list(rgb = "FF000000"),
+ colour = list(theme = "1"),
name = list(val = "Calibri")
)
)
- wb$set_base_font(fontSize = 9, fontName = "Arial", fontColour = "red")
+ wb$set_base_font(fontSize = 9, fontName = "Arial", fontColour = wb_colour("red"))
expect_equal(
wb$get_base_font(),
list(
diff --git a/tests/testthat/test-class-workbook.R b/tests/testthat/test-class-workbook.R
index 1e7e5dce6..906ead914 100644
--- a/tests/testthat/test-class-workbook.R
+++ b/tests/testthat/test-class-workbook.R
@@ -13,7 +13,7 @@ test_that("wb_set_col_widths", {
# set column width to 12
expect_silent(wb$set_col_widths("test", widths = 12L, cols = seq_along(mtcars)))
expect_equal(
- "",
+ "",
wb$worksheets[[1]]$cols_attr
)
@@ -23,22 +23,46 @@ test_that("wb_set_col_widths", {
# reset the column with, we do not provide an option ot remove the column entry
expect_silent(wb$set_col_widths("test", cols = seq_along(mtcars)))
expect_equal(
- "",
+ "",
wb$worksheets[[1]]$cols_attr
)
# create column width for column 25
expect_silent(wb$set_col_widths("test", cols = "Y", widths = 22))
expect_equal(
- c("",
+ c("",
"",
- ""),
+ ""),
wb$worksheets[[1]]$cols_attr
)
# a few more errors
expect_error(wb$set_col_widths("test", cols = "Y", width = 1:2))
expect_error(wb$set_col_widths("test", cols = "Y", hidden = 1:2))
+
+
+
+
+ wb <- wb_workbook()$
+ add_worksheet()$
+ set_col_widths(cols = 1:10, width = (8:17) + .5)$
+ add_data(x = rbind(8:17), colNames = FALSE)
+
+ exp <- c(
+ "",
+ "",
+ "",
+ "",
+ "",
+ "",
+ "",
+ "",
+ "",
+ ""
+ )
+ got <- wb$worksheets[[1]]$cols_attr
+ expect_equal(exp, got)
+
})
diff --git a/tests/testthat/test-wb_styles.R b/tests/testthat/test-wb_styles.R
index 646457d84..924d25abf 100644
--- a/tests/testthat/test-wb_styles.R
+++ b/tests/testthat/test-wb_styles.R
@@ -159,8 +159,9 @@ test_that("test add_font()", {
expect_silent(wb$add_font("S1", dims = "A1:K1", color = wb_colour(hex = "FFFFFF00")))
# check xf
- exp <- c("",
- ""
+ exp <- c(
+ "",
+ ""
)
got <- wb$styles_mgr$styles$cellXfs
@@ -168,8 +169,9 @@ test_that("test add_font()", {
# check font
- exp <- c("",
- ""
+ exp <- c(
+ "",
+ ""
)
got <- wb$styles_mgr$styles$fonts
@@ -434,7 +436,7 @@ test_that("style names are xml", {
exp <- list(
numFmts = NULL,
fonts = c(
- "",
+ "",
"",
"",
"",