Skip to content

Commit

Permalink
Merge pull request #52 from eodaGmbH/export_modify
Browse files Browse the repository at this point in the history
Export modify
  • Loading branch information
Friessn authored Sep 23, 2024
2 parents 342c687 + 81a5bdf commit 92e5a7a
Show file tree
Hide file tree
Showing 22 changed files with 132 additions and 90 deletions.
2 changes: 2 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
export(add_row)
export(delete_selected_rows)
export(for_each_col)
export(modify_col_def)
export(redo)
export(renderTabulator)
export(set_calculation)
Expand Down Expand Up @@ -37,3 +38,4 @@ export(trigger_get_data)
export(trigger_get_sheet_data)
export(undo)
import(htmlwidgets)
importFrom(utils,modifyList)
32 changes: 22 additions & 10 deletions R/columns.R
Original file line number Diff line number Diff line change
Expand Up @@ -116,7 +116,7 @@ set_column_editor_ <- function(widget, columns, type = c("input", "number")) {
#' @export
set_editor <- function(
widget,
column,
columns,
editor = c(
"input", "textarea", "number", "range",
"tickCross", "star", "progress", "date", "time", "datetime", "list"
Expand All @@ -130,7 +130,7 @@ set_editor <- function(
col_update$editorParams <- keys_to_camel_case(compact(editor_params))
}

modify_col_def(widget, column, col_update)
modify_col_def(widget, columns, col_update)
}

#' Set header filter
Expand All @@ -145,7 +145,7 @@ set_editor <- function(
# TODO: Rename to params that they match params used by Tabulator JS
set_header_filter <- function(
widget,
column,
columns,
# TODO: Rename to 'filter_type' or just 'filter' or 'header_filter'?
type = c("input", "number", "list", "tickCross"),
# TODO: Rename to 'filter_func'?
Expand All @@ -155,7 +155,7 @@ set_header_filter <- function(
placeholder = NULL) {
# Body
if (is.null(type)) {
type <- ifelse(is.numeric(widget$x$data[, column]), "number", "input")
type <- ifelse(is.numeric(widget$x$data[, columns]), "number", "input")
} else {
type <- match.arg(type)
}
Expand All @@ -170,15 +170,15 @@ set_header_filter <- function(
headerFilterFunc = func,
headerFilterParams = header_filter_params
)
modify_col_def(widget, column, col_update)
modify_col_def(widget, columns, col_update)
}

#' Set tooltip
#' @inherit set_formatter_html params return
#' @example examples/misc/tooltip.R
#' @export
set_tooltip <- function(widget, column) {
modify_col_def(widget, column, list(tooltip = TRUE))
set_tooltip <- function(widget, columns) {
modify_col_def(widget, columns, list(tooltip = TRUE))
}


Expand Down Expand Up @@ -217,7 +217,6 @@ set_column_defaults <- function(

#' Set calculation
#' @inherit set_formatter_html params return
#' @param column (character): The column the \code{func} is applied to.
#' @param func (character): The calculation function to be applied
#' to the values of the \code{column}.
#' @param precision (integer) The number of decimals to display.
Expand All @@ -229,19 +228,32 @@ set_column_defaults <- function(
#' @export
set_calculation <- function(
widget,
column,
columns,
func = c("avg", "max", "min", "sum", "count", "unique"), # Rename to 'calc'?
precision = 2,
pos = c("top", "bottom")) {
# Body
pos <- match.arg(pos)
col_update <- list(match.arg(func), list(precision = precision))
names(col_update) <- c(paste0(pos, "Calc"), paste0(pos, "CalcParams"))
modify_col_def(widget, column, col_update)
modify_col_def(widget, columns, col_update)
}

# Generics

#' Modify column definition
#' @inherit set_formatter_html params return
#' @param col_update A named list containing the updates to apply to each column in `columns`.
#' The updates are merged into the existing column definitions.
#' @importFrom utils modifyList
#' @export
#' @examples
#'
#' df <- data.frame(values = c(1,2,3), names = c("a","b","c"))
#' tabulator(df) |>
#' modify_col_def(c("values","names"),
#' col_update = list(hozAlign = "center"))

modify_col_def <- function(widget, columns, col_update) {
for (column in columns) {
for (index in 1:length(widget$x$options$columns)) {
Expand Down
64 changes: 32 additions & 32 deletions R/formatters.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,14 +2,14 @@

#' Set HTML formatter
#' @param widget A [tabulator()] HTML widget.
#' @param column The name of the column the formatter is applied to.
#' @param columns The names of the columns the formatter is applied to.
#' @param hoz_align (character): The horizontal alignment of the column.
#' @returns The updated [tabulator()] HTML widget
#' @example examples/formatters/formatter_html.R
#' @export
set_formatter_html <- function(widget, column, hoz_align = c("left", "center", "right")) {
set_formatter_html <- function(widget, columns, hoz_align = c("left", "center", "right")) {
col_update <- list(formatter = "html", hozAlign = match.arg(hoz_align))
modify_col_def(widget, column, col_update)
modify_col_def(widget, columns, col_update)
}

#' Set plain text formatter
Expand All @@ -18,18 +18,18 @@ set_formatter_html <- function(widget, column, hoz_align = c("left", "center", "
#' tabulator(iris) |>
#' set_formatter_plaintext("Species", hoz_align = "right")
#' @export
set_formatter_plaintext <- function(widget, column, hoz_align = "left") {
set_formatter_plaintext <- function(widget, columns, hoz_align = "left") {
col_update <- list(formatter = "plaintext", hozAlign = hoz_align)
modify_col_def(widget, column, col_update)
modify_col_def(widget, columns, col_update)
}

#' Set text area formatter
#' @inherit set_formatter_html params return
#' @example examples/formatters/formatter_textarea.R
#' @export
set_formatter_textarea <- function(widget, column, hoz_align = "left") {
set_formatter_textarea <- function(widget, columns, hoz_align = "left") {
col_update <- list(formatter = "textarea", hozAlign = hoz_align)
modify_col_def(widget, column, col_update)
modify_col_def(widget, columns, col_update)
}

#' Set money formatter
Expand All @@ -48,7 +48,7 @@ set_formatter_textarea <- function(widget, column, hoz_align = "left") {
#' @export
set_formatter_money <- function(
widget,
column,
columns,
decimal = c(",", "."),
thousand = c(".", ","),
symbol = "$", # "\U20AC"
Expand All @@ -69,7 +69,7 @@ set_formatter_money <- function(
),
hozAlign = hoz_align
)
modify_col_def(widget, column, col_update)
modify_col_def(widget, columns, col_update)
}

#' Set image formatter
Expand All @@ -84,7 +84,7 @@ set_formatter_money <- function(
#' @export
set_formatter_image <- function(
widget,
column,
columns,
height = "50px",
width = "50px",
url_prefix = NULL,
Expand All @@ -101,7 +101,7 @@ set_formatter_image <- function(
)),
hozAlign = hoz_align
)
modify_col_def(widget, column, col_update)
modify_col_def(widget, columns, col_update)
}

#' Set link formatter
Expand All @@ -116,7 +116,7 @@ set_formatter_image <- function(
#' @export
set_formatter_link <- function(
widget,
column,
columns,
label_field = NULL,
url_prefix = NULL,
url = NULL,
Expand All @@ -133,7 +133,7 @@ set_formatter_link <- function(
)),
hozAlign = hoz_align
)
modify_col_def(widget, column, col_update)
modify_col_def(widget, columns, col_update)
}

#' Set star rating formatter
Expand All @@ -142,17 +142,17 @@ set_formatter_link <- function(
#' If set to \code{NA}, the maximum value of the column is used.
#' @example examples/formatters/formatter_star.R
#' @export
set_formatter_star <- function(widget, column, number_of_stars = NA, hoz_align = "center") {
set_formatter_star <- function(widget, columns, number_of_stars = NA, hoz_align = "center") {
if (is.na(number_of_stars)) {
number_of_stars <- max(widget$x$data[column])
number_of_stars <- max(widget$x$data[columns])
}

col_update <- list(
formatter = "star",
formatterParams = list(stars = number_of_stars),
hozAlign = hoz_align
)
modify_col_def(widget, column, col_update)
modify_col_def(widget, columns, col_update)
}

#' Set progress formatter
Expand All @@ -172,7 +172,7 @@ set_formatter_star <- function(widget, column, number_of_stars = NA, hoz_align =
#' @export
set_formatter_progress <- function(
widget,
column,
columns,
min = NA,
max = NA,
color = c("yellow", "orange", "red"),
Expand All @@ -182,11 +182,11 @@ set_formatter_progress <- function(
hoz_align = "left") {
# Body
if (is.na(min)) {
min <- min(widget$x$data[column])
min <- min(widget$x$data[columns])
}

if (is.na(max)) {
max <- max(widget$x$data[column])
max <- max(widget$x$data[columns])
}

col_update <- list(
Expand All @@ -201,16 +201,16 @@ set_formatter_progress <- function(
),
hozAlign = hoz_align
)
modify_col_def(widget, column, col_update)
modify_col_def(widget, columns, col_update)
}

#' Set tick cross formatter
#' @inherit set_formatter_html params return
#' @example examples/formatters/formatter_tick_cross.R
#' @export
set_formatter_tick_cross <- function(widget, column, hoz_align = "center") {
set_formatter_tick_cross <- function(widget, columns, hoz_align = "center") {
col_update <- list(formatter = "tickCross", hozAlign = hoz_align)
modify_col_def(widget, column, col_update)
modify_col_def(widget, columns, col_update)
}

#' Set toggle switch formatter
Expand All @@ -226,7 +226,7 @@ set_formatter_tick_cross <- function(widget, column, hoz_align = "center") {
#' @export
set_formatter_toggle_switch <- function(
widget,
column,
columns,
size = 20,
on_value = "on",
off_value = "off",
Expand All @@ -247,7 +247,7 @@ set_formatter_toggle_switch <- function(
clickable = clickable
)
)
modify_col_def(widget, column, col_update)
modify_col_def(widget, columns, col_update)
}

#' Set datetime formatter
Expand All @@ -265,7 +265,7 @@ set_formatter_toggle_switch <- function(
#' @export
set_formatter_datetime <- function(
widget,
column,
columns,
input_format = "yyyy-MM-dd hh:ss:mm",
output_format = "yy/MM/dd",
invalid_placeholder = "(invalid datetime)",
Expand All @@ -282,16 +282,16 @@ set_formatter_datetime <- function(
),
hozAlign = hoz_align
)
modify_col_def(widget, column, col_update)
modify_col_def(widget, columns, col_update)
}

#' Set color formatter
#' @inherit set_formatter_html params return
#' @example examples/formatters/formatter_color.R
#' @export
set_formatter_color <- function(widget, column) {
set_formatter_color <- function(widget, columns) {
col_update <- list(formatter = "color")
modify_col_def(widget, column, col_update)
modify_col_def(widget, columns, col_update)
}

#' Set traffic light formatter
Expand All @@ -300,15 +300,15 @@ set_formatter_color <- function(widget, column) {
#' @export
set_formatter_traffic_light <- function(
widget,
column,
columns,
min = NA,
max = NA,
color = c("green", "orange", "red"),
hoz_align = "center") {
# Body
if (is.na(min)) min <- min(widget$x$data[column])
if (is.na(min)) min <- min(widget$x$data[columns])

if (is.na(max)) max <- max(widget$x$data[column])
if (is.na(max)) max <- max(widget$x$data[columns])

col_update <- list(
formatter = "traffic",
Expand All @@ -319,5 +319,5 @@ set_formatter_traffic_light <- function(
),
hozAlign = hoz_align
)
modify_col_def(widget, column, col_update)
modify_col_def(widget, columns, col_update)
}
29 changes: 29 additions & 0 deletions man/modify_col_def.Rd

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

4 changes: 2 additions & 2 deletions man/set_calculation.Rd

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

Loading

0 comments on commit 92e5a7a

Please sign in to comment.