mirror of
https://github.com/agdamsbo/FreesearchR.git
synced 2025-09-12 01:49:39 +02:00
internalised the create_column function from datamods for ui modifications - all variable icons are the same throughout now - added custom css
This commit is contained in:
parent
e3017458dd
commit
6a43ba7b5b
12 changed files with 1322 additions and 23 deletions
443
R/create-column-mod.R
Normal file
443
R/create-column-mod.R
Normal file
|
@ -0,0 +1,443 @@
|
|||
#' @title Create new column
|
||||
#'
|
||||
#' @description
|
||||
#' This module allow to enter an expression to create a new column in a `data.frame`.
|
||||
#'
|
||||
#'
|
||||
#' @param id Module's ID.
|
||||
#'
|
||||
#' @return A [shiny::reactive()] function returning the data.
|
||||
#'
|
||||
#' @note User can only use a subset of function: `r paste(list_allowed_operations(), collapse=", ")`.
|
||||
#' You can add more operations using the `allowed_operations` argument, for example if you want to allow to use package lubridate, you can do:
|
||||
#' ```r
|
||||
#' c(list_allowed_operations(), getNamespaceExports("lubridate"))
|
||||
#' ```
|
||||
#'
|
||||
#' @export
|
||||
#'
|
||||
#' @importFrom htmltools tagList tags css
|
||||
#' @importFrom shiny NS textInput textAreaInput uiOutput actionButton
|
||||
#' @importFrom phosphoricons ph
|
||||
#' @importFrom shinyWidgets virtualSelectInput
|
||||
#'
|
||||
#' @name create-column
|
||||
#'
|
||||
#' @example example/create_column_module_demo.R
|
||||
create_column_ui <- function(id) {
|
||||
ns <- NS(id)
|
||||
tagList(
|
||||
# datamods:::html_dependency_datamods(),
|
||||
# html_dependency_FreesearchR(),
|
||||
tags$head(
|
||||
tags$link(rel = "stylesheet", type = "text/css", href = "FreesearchR/inst/assets/css/FreesearchR.css")
|
||||
),
|
||||
# tags$head(
|
||||
# # Note the wrapping of the string in HTML()
|
||||
# tags$style(HTML("
|
||||
# /* modified from esquisse for data types */
|
||||
# .btn-column-categorical {
|
||||
# background-color: #EF562D;
|
||||
# color: #FFFFFF;
|
||||
# }
|
||||
# .btn-column-continuous {
|
||||
# background-color: #0C4C8A;
|
||||
# color: #FFFFFF;
|
||||
# }
|
||||
# .btn-column-dichotomous {
|
||||
# background-color: #97D5E0;
|
||||
# color: #FFFFFF;
|
||||
# }
|
||||
# .btn-column-datetime {
|
||||
# background-color: #97D5E0;
|
||||
# color: #FFFFFF;
|
||||
# }
|
||||
# .btn-column-id {
|
||||
# background-color: #848484;
|
||||
# color: #FFFFFF;
|
||||
# }
|
||||
# .btn-column-text {
|
||||
# background-color: #2E2E2E;
|
||||
# color: #FFFFFF;
|
||||
# }"))
|
||||
# ),
|
||||
fluidRow(
|
||||
column(
|
||||
width = 6,
|
||||
textInput(
|
||||
inputId = ns("new_column"),
|
||||
label = i18n("New column name:"),
|
||||
value = "new_column1",
|
||||
width = "100%"
|
||||
)
|
||||
),
|
||||
column(
|
||||
width = 6,
|
||||
shinyWidgets::virtualSelectInput(
|
||||
inputId = ns("group_by"),
|
||||
label = i18n("Group calculation by:"),
|
||||
choices = NULL,
|
||||
multiple = TRUE,
|
||||
disableSelectAll = TRUE,
|
||||
hasOptionDescription = TRUE,
|
||||
width = "100%"
|
||||
)
|
||||
)
|
||||
),
|
||||
textAreaInput(
|
||||
inputId = ns("expression"),
|
||||
label = i18n("Enter an expression to define new column:"),
|
||||
value = "",
|
||||
width = "100%",
|
||||
rows = 6
|
||||
),
|
||||
tags$i(
|
||||
class = "d-block",
|
||||
phosphoricons::ph("info"),
|
||||
datamods::i18n("Click on a column name to add it to the expression:")
|
||||
),
|
||||
uiOutput(outputId = ns("columns")),
|
||||
uiOutput(outputId = ns("feedback")),
|
||||
tags$div(
|
||||
style = css(
|
||||
display = "grid",
|
||||
gridTemplateColumns = "3fr 1fr",
|
||||
columnGap = "10px",
|
||||
margin = "10px 0"
|
||||
),
|
||||
actionButton(
|
||||
inputId = ns("compute"),
|
||||
label = tagList(
|
||||
phosphoricons::ph("gear"), i18n("Create column")
|
||||
),
|
||||
class = "btn-outline-primary",
|
||||
width = "100%"
|
||||
),
|
||||
actionButton(
|
||||
inputId = ns("remove"),
|
||||
label = tagList(
|
||||
phosphoricons::ph("trash")
|
||||
),
|
||||
class = "btn-outline-danger",
|
||||
width = "100%"
|
||||
)
|
||||
)
|
||||
)
|
||||
}
|
||||
|
||||
#' @param data_r A [shiny::reactive()] function returning a `data.frame`.
|
||||
#' @param allowed_operations A `list` of allowed operations, see below for details.
|
||||
#'
|
||||
#' @export
|
||||
#'
|
||||
#' @rdname create-column
|
||||
#'
|
||||
#' @importFrom shiny moduleServer reactiveValues observeEvent renderUI req
|
||||
#' updateTextAreaInput reactive bindEvent observe
|
||||
#' @importFrom shinyWidgets alert updateVirtualSelect
|
||||
create_column_server <- function(id,
|
||||
data_r = reactive(NULL),
|
||||
allowed_operations = list_allowed_operations()) {
|
||||
moduleServer(
|
||||
id,
|
||||
function(input, output, session) {
|
||||
ns <- session$ns
|
||||
|
||||
info_alert <- shinyWidgets::alert(
|
||||
status = "info",
|
||||
phosphoricons::ph("question"),
|
||||
datamods::i18n("Choose a name for the column to be created or modified,"),
|
||||
datamods::i18n("then enter an expression before clicking on the button above to validate or on "),
|
||||
phosphoricons::ph("trash"), datamods::i18n("to delete it.")
|
||||
)
|
||||
|
||||
rv <- reactiveValues(
|
||||
data = NULL,
|
||||
feedback = info_alert
|
||||
)
|
||||
|
||||
observeEvent(input$hidden, rv$feedback <- info_alert)
|
||||
|
||||
bindEvent(observe({
|
||||
data <- data_r()
|
||||
shinyWidgets::updateVirtualSelect(
|
||||
inputId = "group_by",
|
||||
choices = make_choices_with_infos(data)
|
||||
)
|
||||
}), data_r(), input$hidden)
|
||||
|
||||
observeEvent(data_r(), rv$data <- data_r())
|
||||
|
||||
output$feedback <- renderUI(rv$feedback)
|
||||
|
||||
output$columns <- renderUI({
|
||||
data <- req(rv$data)
|
||||
mapply(
|
||||
label = names(data),
|
||||
data = data,
|
||||
FUN = btn_column,
|
||||
MoreArgs = list(inputId = ns("add_column")),
|
||||
SIMPLIFY = FALSE
|
||||
)
|
||||
})
|
||||
|
||||
observeEvent(input$add_column, {
|
||||
updateTextAreaInput(
|
||||
session = session,
|
||||
inputId = "expression",
|
||||
value = paste0(input$expression, input$add_column)
|
||||
)
|
||||
})
|
||||
|
||||
observeEvent(input$new_column, {
|
||||
if (input$new_column == "") {
|
||||
rv$feedback <- shinyWidgets::alert(
|
||||
status = "warning",
|
||||
ph("warning"), datamods::i18n("New column name cannot be empty")
|
||||
)
|
||||
}
|
||||
})
|
||||
|
||||
observeEvent(input$remove, {
|
||||
rv$data[[input$new_column]] <- NULL
|
||||
})
|
||||
observeEvent(input$compute, {
|
||||
rv$feedback <- try_compute_column(
|
||||
expression = input$expression,
|
||||
name = input$new_column,
|
||||
rv = rv,
|
||||
allowed_operations = allowed_operations,
|
||||
by = input$group_by
|
||||
)
|
||||
})
|
||||
|
||||
return(reactive(rv$data))
|
||||
}
|
||||
)
|
||||
}
|
||||
|
||||
#' @export
|
||||
#'
|
||||
#' @rdname create-column
|
||||
# @importFrom methods getGroupMembers
|
||||
list_allowed_operations <- function() {
|
||||
c(
|
||||
"(", "c",
|
||||
# getGroupMembers("Arith"),
|
||||
c("+", "-", "*", "^", "%%", "%/%", "/"),
|
||||
# getGroupMembers("Compare"),
|
||||
c("==", ">", "<", "!=", "<=", ">="),
|
||||
# getGroupMembers("Logic"),
|
||||
c("&", "|"),
|
||||
# getGroupMembers("Math"),
|
||||
c(
|
||||
"abs", "sign", "sqrt", "ceiling", "floor", "trunc", "cummax",
|
||||
"cummin", "cumprod", "cumsum", "exp", "expm1", "log", "log10",
|
||||
"log2", "log1p", "cos", "cosh", "sin", "sinh", "tan", "tanh",
|
||||
"acos", "acosh", "asin", "asinh", "atan", "atanh", "cospi", "sinpi",
|
||||
"tanpi", "gamma", "lgamma", "digamma", "trigamma"
|
||||
),
|
||||
# getGroupMembers("Math2"),
|
||||
c("round", "signif"),
|
||||
# getGroupMembers("Summary"),
|
||||
c("max", "min", "range", "prod", "sum", "any", "all"),
|
||||
"pmin", "pmax", "mean",
|
||||
"paste", "paste0", "substr", "nchar", "trimws",
|
||||
"gsub", "sub", "grepl", "ifelse", "length",
|
||||
"as.numeric", "as.character", "as.integer", "as.Date", "as.POSIXct",
|
||||
"as.factor", "factor"
|
||||
)
|
||||
}
|
||||
|
||||
|
||||
#' @inheritParams shiny::modalDialog
|
||||
#' @export
|
||||
#'
|
||||
#' @importFrom shiny showModal modalDialog textInput
|
||||
#' @importFrom htmltools tagList
|
||||
#'
|
||||
#' @rdname create-column
|
||||
modal_create_column <- function(id,
|
||||
title = i18n("Create a new column"),
|
||||
easyClose = TRUE,
|
||||
size = "l",
|
||||
footer = NULL) {
|
||||
ns <- NS(id)
|
||||
showModal(modalDialog(
|
||||
title = tagList(title, datamods:::button_close_modal()),
|
||||
create_column_ui(id),
|
||||
tags$div(
|
||||
style = "display: none;",
|
||||
textInput(inputId = ns("hidden"), label = NULL, value = datamods:::genId())
|
||||
),
|
||||
easyClose = easyClose,
|
||||
size = size,
|
||||
footer = footer
|
||||
))
|
||||
}
|
||||
|
||||
#' @inheritParams shinyWidgets::WinBox
|
||||
#' @export
|
||||
#'
|
||||
#' @importFrom shinyWidgets WinBox wbOptions wbControls
|
||||
#' @importFrom htmltools tagList
|
||||
#' @rdname create-column
|
||||
winbox_create_column <- function(id,
|
||||
title = i18n("Create a new column"),
|
||||
options = shinyWidgets::wbOptions(),
|
||||
controls = shinyWidgets::wbControls()) {
|
||||
ns <- NS(id)
|
||||
WinBox(
|
||||
title = title,
|
||||
ui = tagList(
|
||||
create_column_ui(id),
|
||||
tags$div(
|
||||
style = "display: none;",
|
||||
textInput(inputId = ns("hidden"), label = NULL, value = datamods:::genId())
|
||||
)
|
||||
),
|
||||
options = modifyList(
|
||||
shinyWidgets::wbOptions(height = "550px", modal = TRUE),
|
||||
options
|
||||
),
|
||||
controls = controls,
|
||||
auto_height = FALSE
|
||||
)
|
||||
}
|
||||
|
||||
|
||||
try_compute_column <- function(expression,
|
||||
name,
|
||||
rv,
|
||||
allowed_operations,
|
||||
by = NULL) {
|
||||
parsed <- try(parse(text = expression, keep.source = FALSE), silent = TRUE)
|
||||
if (inherits(parsed, "try-error")) {
|
||||
return(datamods:::alert_error(attr(parsed, "condition")$message))
|
||||
}
|
||||
funs <- unlist(c(extract_calls(parsed), lapply(parsed, extract_calls)), recursive = TRUE)
|
||||
if (!are_allowed_operations(funs, allowed_operations)) {
|
||||
return(datamods:::alert_error(datamods::i18n("Some operations are not allowed")))
|
||||
}
|
||||
if (!isTruthy(by)) {
|
||||
result <- try(
|
||||
rlang::eval_tidy(rlang::parse_expr(expression), data = rv$data),
|
||||
silent = TRUE
|
||||
)
|
||||
} else {
|
||||
result <- try(
|
||||
{
|
||||
dt <- as.data.table(rv$data)
|
||||
new_col <- NULL
|
||||
dt[, new_col := rlang::eval_tidy(rlang::parse_expr(expression), data = .SD), by = by]
|
||||
dt$new_col
|
||||
},
|
||||
silent = TRUE
|
||||
)
|
||||
}
|
||||
if (inherits(result, "try-error")) {
|
||||
return(alert_error(attr(result, "condition")$message))
|
||||
}
|
||||
adding_col <- try(rv$data[[name]] <- result, silent = TRUE)
|
||||
if (inherits(adding_col, "try-error")) {
|
||||
return(alert_error(attr(adding_col, "condition")$message))
|
||||
}
|
||||
code <- if (!isTruthy(by)) {
|
||||
rlang::call2("mutate", !!!rlang::set_names(list(rlang::parse_expr(expression)), name))
|
||||
} else {
|
||||
rlang::call2(
|
||||
"mutate",
|
||||
!!!rlang::set_names(list(rlang::parse_expr(expression)), name),
|
||||
!!!list(.by = rlang::expr(c(!!!rlang::syms(by))))
|
||||
)
|
||||
}
|
||||
attr(rv$data, "code") <- Reduce(
|
||||
f = function(x, y) rlang::expr(!!x %>% !!y),
|
||||
x = c(attr(rv$data, "code"), code)
|
||||
)
|
||||
shinyWidgets::alert(
|
||||
status = "success",
|
||||
ph("check"), datamods::i18n("Column added!")
|
||||
)
|
||||
}
|
||||
|
||||
are_allowed_operations <- function(x, allowed_operations) {
|
||||
all(
|
||||
x %in% allowed_operations
|
||||
)
|
||||
}
|
||||
|
||||
|
||||
extract_calls <- function(exp) {
|
||||
if (is.call(exp)) {
|
||||
return(list(
|
||||
as.character(exp[[1L]]),
|
||||
lapply(exp[-1L], extract_calls)
|
||||
))
|
||||
}
|
||||
}
|
||||
|
||||
alert_error <- function(text) {
|
||||
alert(
|
||||
status = "danger",
|
||||
ph("bug"), text
|
||||
)
|
||||
}
|
||||
|
||||
|
||||
btn_column <- function(label, data, inputId) {
|
||||
icon <- get_var_icon(data, "class")
|
||||
type <- data_type(data)
|
||||
tags$button(
|
||||
type = "button",
|
||||
class = paste0("btn btn-column-", type),
|
||||
style = css(
|
||||
"--bs-btn-padding-y" = ".25rem",
|
||||
"--bs-btn-padding-x" = ".5rem",
|
||||
"--bs-btn-font-size" = ".75rem",
|
||||
"margin-bottom" = "5px"
|
||||
),
|
||||
if (!is.null(icon)) icon,
|
||||
label,
|
||||
onclick = sprintf(
|
||||
"Shiny.setInputValue('%s', '%s', {priority: 'event'})",
|
||||
inputId, label
|
||||
)
|
||||
)
|
||||
}
|
||||
|
||||
make_choices_with_infos <- function(data) {
|
||||
lapply(
|
||||
X = seq_along(data),
|
||||
FUN = function(i) {
|
||||
nm <- names(data)[i]
|
||||
values <- data[[nm]]
|
||||
icon <- get_var_icon(values, "class")
|
||||
# icon <- if (inherits(values, "character")) {
|
||||
# phosphoricons::ph("text-aa")
|
||||
# } else if (inherits(values, "factor")) {
|
||||
# phosphoricons::ph("list-bullets")
|
||||
# } else if (inherits(values, c("numeric", "integer"))) {
|
||||
# phosphoricons::ph("hash")
|
||||
# } else if (inherits(values, c("Date"))) {
|
||||
# phosphoricons::ph("calendar")
|
||||
# } else if (inherits(values, c("POSIXt"))) {
|
||||
# phosphoricons::ph("clock")
|
||||
# } else {
|
||||
# NULL
|
||||
# }
|
||||
description <- if (is.atomic(values)) {
|
||||
paste(i18n("Unique values:"), data.table::uniqueN(values))
|
||||
} else {
|
||||
""
|
||||
}
|
||||
list(
|
||||
label = htmltools::doRenderTags(tagList(
|
||||
icon, nm
|
||||
)),
|
||||
value = nm,
|
||||
description = description
|
||||
)
|
||||
}
|
||||
)
|
||||
}
|
|
@ -318,9 +318,9 @@ class_icons <- function(x) {
|
|||
shiny::icon("arrow-down-a-z")
|
||||
} else if (identical(x, "logical")) {
|
||||
shiny::icon("toggle-off")
|
||||
} else if (any(c("Date", "POSIXct", "POSIXt") %in% x)) {
|
||||
} else if (any(c("Date", "POSIXt") %in% x)) {
|
||||
shiny::icon("calendar-days")
|
||||
} else if ("hms" %in% x) {
|
||||
} else if (any("POSIXct", "hms") %in% x) {
|
||||
shiny::icon("clock")
|
||||
} else {
|
||||
shiny::icon("table")
|
||||
|
@ -360,3 +360,33 @@ type_icons <- function(x) {
|
|||
}
|
||||
}
|
||||
}
|
||||
|
||||
#' Easily get variable icon based on data type or class
|
||||
#'
|
||||
#' @param data variable or data frame
|
||||
#' @param class.type "type" or "class". Default is "class"
|
||||
#'
|
||||
#' @returns svg icon
|
||||
#' @export
|
||||
#'
|
||||
#' @examples
|
||||
#' mtcars[1] |> get_var_icon("class")
|
||||
#' default_parsing(mtcars) |> get_var_icon()
|
||||
get_var_icon <- function(data,class.type=c("class","type")){
|
||||
if (is.data.frame(data)){
|
||||
lapply(data,get_var_icon)
|
||||
} else {
|
||||
|
||||
class.type <- match.arg(class.type)
|
||||
|
||||
switch(class.type,
|
||||
type = {
|
||||
type_icons(data_type(data))
|
||||
},
|
||||
class = {
|
||||
class(data)[1] |> class_icons()
|
||||
}
|
||||
)
|
||||
}
|
||||
|
||||
}
|
||||
|
|
348
R/datagrid-infos-mod.R
Normal file
348
R/datagrid-infos-mod.R
Normal file
|
@ -0,0 +1,348 @@
|
|||
|
||||
#' Display a table in a window
|
||||
#'
|
||||
#' @param data a data object (either a `matrix` or a `data.frame`).
|
||||
#' @param title Title to be displayed in window.
|
||||
#' @param show_classes Show variables classes under variables names in table header.
|
||||
#' @param type Display table in a pop-up with [shinyWidgets::show_alert()],
|
||||
#' in modal window with [shiny::showModal()] or in a WinBox window with [shinyWidgets::WinBox()].
|
||||
#' @param options Arguments passed to [toastui::datagrid()].
|
||||
#' @param width Width of the window, only used if `type = "popup"` or `type = "winbox"`.
|
||||
#' @param ... Additional options, such as `wbOptions = wbOptions()` or `wbControls = wbControls()`.
|
||||
#'
|
||||
#' @note
|
||||
#' If you use `type = "winbox"`, you'll need to use `shinyWidgets::html_dependency_winbox()` somewhere in your UI.
|
||||
#'
|
||||
#' @return No value.
|
||||
#' @export
|
||||
#'
|
||||
#' @importFrom htmltools tags tagList css
|
||||
#' @importFrom shiny showModal modalDialog
|
||||
#' @importFrom utils modifyList packageVersion
|
||||
#'
|
||||
#' @example examples/show_data.R
|
||||
show_data <- function(data,
|
||||
title = NULL,
|
||||
options = NULL,
|
||||
show_classes = TRUE,
|
||||
type = c("popup", "modal", "winbox"),
|
||||
width = "65%",
|
||||
...) { # nocov start
|
||||
type <- match.arg(type)
|
||||
data <- as.data.frame(data)
|
||||
args <- list(...)
|
||||
gridTheme <- getOption("datagrid.theme")
|
||||
if (length(gridTheme) < 1) {
|
||||
datamods:::apply_grid_theme()
|
||||
}
|
||||
on.exit(toastui::reset_grid_theme())
|
||||
|
||||
if (is.null(options))
|
||||
options <- list()
|
||||
|
||||
options$height <- 550
|
||||
options$minBodyHeight <- 400
|
||||
options$data <- data
|
||||
options$theme <- "default"
|
||||
options$colwidths <- "guess"
|
||||
options$guess_colwidths_opts <- list(min_width = 90, max_width = 400, mul = 1, add = 10)
|
||||
if (isTRUE(show_classes))
|
||||
options$summary <- construct_col_summary(data)
|
||||
datatable <- rlang::exec(toastui::datagrid, !!!options)
|
||||
datatable <- toastui::grid_columns(datatable, className = "font-monospace")
|
||||
if (identical(type, "winbox")) {
|
||||
stopifnot(
|
||||
"You need shinyWidgets >= 0.8.4" = packageVersion("shinyWidgets") >= "0.8.4"
|
||||
)
|
||||
wb_options <- if (is.null(args$wbOptions)) {
|
||||
shinyWidgets::wbOptions(
|
||||
height = "600px",
|
||||
width = width,
|
||||
modal = TRUE
|
||||
)
|
||||
} else {
|
||||
modifyList(
|
||||
shinyWidgets::wbOptions(
|
||||
height = "600px",
|
||||
width = width,
|
||||
modal = TRUE
|
||||
),
|
||||
args$wbOptions
|
||||
)
|
||||
}
|
||||
wb_controls <- if (is.null(args$wbControls)) {
|
||||
shinyWidgets::wbControls()
|
||||
} else {
|
||||
args$wbControls
|
||||
}
|
||||
shinyWidgets::WinBox(
|
||||
title = title,
|
||||
ui = datatable,
|
||||
options = wb_options,
|
||||
controls = wb_controls,
|
||||
padding = "0 5px"
|
||||
)
|
||||
} else if (identical(type, "popup")) {
|
||||
shinyWidgets::show_alert(
|
||||
title = NULL,
|
||||
text = tags$div(
|
||||
if (!is.null(title)) {
|
||||
tagList(
|
||||
tags$h3(title),
|
||||
tags$hr()
|
||||
)
|
||||
},
|
||||
style = "color: #000 !important;",
|
||||
datatable
|
||||
),
|
||||
closeOnClickOutside = TRUE,
|
||||
showCloseButton = TRUE,
|
||||
btn_labels = NA,
|
||||
html = TRUE,
|
||||
width = width
|
||||
)
|
||||
} else {
|
||||
showModal(modalDialog(
|
||||
title = tagList(
|
||||
datamods:::button_close_modal(),
|
||||
title
|
||||
),
|
||||
tags$div(
|
||||
style = css(minHeight = validateCssUnit(options$height)),
|
||||
toastui::renderDatagrid2(datatable)
|
||||
),
|
||||
size = "xl",
|
||||
footer = NULL,
|
||||
easyClose = TRUE
|
||||
))
|
||||
}
|
||||
} # nocov end
|
||||
|
||||
|
||||
|
||||
#' @importFrom htmltools tagList tags css
|
||||
describe_col_char <- function(x, with_summary = TRUE) {
|
||||
tags$div(
|
||||
style = css(padding = "3px 0", fontSize = "x-small"),
|
||||
tags$div(
|
||||
style = css(fontStyle = "italic"),
|
||||
get_var_icon(x),
|
||||
# phosphoricons::ph("text-aa"),
|
||||
"character"
|
||||
),
|
||||
if (with_summary) {
|
||||
tagList(
|
||||
tags$hr(style = css(margin = "3px 0")),
|
||||
tags$div(
|
||||
i18n("Unique:"), length(unique(x))
|
||||
),
|
||||
tags$div(
|
||||
i18n("Missing:"), sum(is.na(x))
|
||||
),
|
||||
tags$div(
|
||||
style = css(whiteSpace = "normal", wordBreak = "break-all"),
|
||||
i18n("Most Common:"), gsub(
|
||||
pattern = "'",
|
||||
replacement = "\u07F4",
|
||||
x = names(sort(table(x), decreasing = TRUE))[1]
|
||||
)
|
||||
),
|
||||
tags$div(
|
||||
"\u00A0"
|
||||
)
|
||||
)
|
||||
}
|
||||
)
|
||||
}
|
||||
|
||||
fmt_p <- function(val, tot) {
|
||||
paste0(round(val / tot * 100, 1), "%")
|
||||
}
|
||||
|
||||
describe_col_factor <- function(x, with_summary = TRUE) {
|
||||
count <- sort(table(x, useNA = "always"), decreasing = TRUE)
|
||||
total <- sum(count)
|
||||
one <- count[!is.na(names(count))][1]
|
||||
two <- count[!is.na(names(count))][2]
|
||||
missing <- count[is.na(names(count))]
|
||||
tags$div(
|
||||
style = css(padding = "3px 0", fontSize = "x-small"),
|
||||
tags$div(
|
||||
style = css(fontStyle = "italic"),
|
||||
get_var_icon(x),
|
||||
# phosphoricons::ph("list-bullets"),
|
||||
"factor"
|
||||
),
|
||||
if (with_summary) {
|
||||
tagList(
|
||||
tags$hr(style = css(margin = "3px 0")),
|
||||
tags$div(
|
||||
names(one), ":", fmt_p(one, total)
|
||||
),
|
||||
tags$div(
|
||||
names(two), ":", fmt_p(two, total)
|
||||
),
|
||||
tags$div(
|
||||
"Missing", ":", fmt_p(missing, total)
|
||||
),
|
||||
tags$div(
|
||||
"\u00A0"
|
||||
)
|
||||
)
|
||||
}
|
||||
)
|
||||
}
|
||||
|
||||
describe_col_num <- function(x, with_summary = TRUE) {
|
||||
tags$div(
|
||||
style = css(padding = "3px 0", fontSize = "x-small"),
|
||||
tags$div(
|
||||
style = css(fontStyle = "italic"),
|
||||
get_var_icon(x),
|
||||
# phosphoricons::ph("hash"),
|
||||
"numeric"
|
||||
),
|
||||
if (with_summary) {
|
||||
tagList(
|
||||
tags$hr(style = css(margin = "3px 0")),
|
||||
tags$div(
|
||||
i18n("Min:"), round(min(x, na.rm = TRUE), 2)
|
||||
),
|
||||
tags$div(
|
||||
i18n("Mean:"), round(mean(x, na.rm = TRUE), 2)
|
||||
),
|
||||
tags$div(
|
||||
i18n("Max:"), round(max(x, na.rm = TRUE), 2)
|
||||
),
|
||||
tags$div(
|
||||
i18n("Missing:"), sum(is.na(x))
|
||||
)
|
||||
)
|
||||
}
|
||||
)
|
||||
}
|
||||
|
||||
|
||||
describe_col_date <- function(x, with_summary = TRUE) {
|
||||
tags$div(
|
||||
style = css(padding = "3px 0", fontSize = "x-small"),
|
||||
tags$div(
|
||||
style = css(fontStyle = "italic"),
|
||||
get_var_icon(x),
|
||||
# phosphoricons::ph("calendar"),
|
||||
"date"
|
||||
),
|
||||
if (with_summary) {
|
||||
tagList(
|
||||
tags$hr(style = css(margin = "3px 0")),
|
||||
tags$div(
|
||||
i18n("Min:"), min(x, na.rm = TRUE)
|
||||
),
|
||||
tags$div(
|
||||
i18n("Max:"), max(x, na.rm = TRUE)
|
||||
),
|
||||
tags$div(
|
||||
i18n("Missing:"), sum(is.na(x))
|
||||
),
|
||||
tags$div(
|
||||
"\u00A0"
|
||||
)
|
||||
)
|
||||
}
|
||||
)
|
||||
}
|
||||
|
||||
describe_col_datetime <- function(x, with_summary = TRUE) {
|
||||
tags$div(
|
||||
style = css(padding = "3px 0", fontSize = "x-small"),
|
||||
tags$div(
|
||||
style = css(fontStyle = "italic"),
|
||||
get_var_icon(x),
|
||||
# phosphoricons::ph("clock"),
|
||||
"datetime"
|
||||
),
|
||||
if (with_summary) {
|
||||
tagList(
|
||||
tags$hr(style = css(margin = "3px 0")),
|
||||
tags$div(
|
||||
i18n("Min:"), min(x, na.rm = TRUE)
|
||||
),
|
||||
tags$div(
|
||||
i18n("Max:"), max(x, na.rm = TRUE)
|
||||
),
|
||||
tags$div(
|
||||
i18n("Missing:"), sum(is.na(x))
|
||||
),
|
||||
tags$div(
|
||||
"\u00A0"
|
||||
)
|
||||
)
|
||||
}
|
||||
)
|
||||
}
|
||||
|
||||
|
||||
describe_col_other <- function(x, with_summary = TRUE) {
|
||||
tags$div(
|
||||
style = css(padding = "3px 0", fontSize = "x-small"),
|
||||
tags$div(
|
||||
style = css(fontStyle = "italic"),
|
||||
get_var_icon(x),
|
||||
# phosphoricons::ph("clock"),
|
||||
paste(class(x), collapse = ", ")
|
||||
),
|
||||
if (with_summary) {
|
||||
tagList(
|
||||
tags$hr(style = css(margin = "3px 0")),
|
||||
tags$div(
|
||||
i18n("Unique:"), length(unique(x))
|
||||
),
|
||||
tags$div(
|
||||
i18n("Missing:"), sum(is.na(x))
|
||||
),
|
||||
tags$div(
|
||||
"\u00A0"
|
||||
),
|
||||
tags$div(
|
||||
"\u00A0"
|
||||
)
|
||||
)
|
||||
}
|
||||
)
|
||||
}
|
||||
|
||||
construct_col_summary <- function(data) {
|
||||
list(
|
||||
position = "top",
|
||||
height = 90,
|
||||
columnContent = lapply(
|
||||
X = setNames(names(data), names(data)),
|
||||
FUN = function(col) {
|
||||
values <- data[[col]]
|
||||
content <- if (inherits(values, "character")) {
|
||||
describe_col_char(values)
|
||||
} else if (inherits(values, "factor")) {
|
||||
describe_col_factor(values)
|
||||
} else if (inherits(values, c("numeric", "integer"))) {
|
||||
describe_col_num(values)
|
||||
} else if (inherits(values, c("Date"))) {
|
||||
describe_col_date(values)
|
||||
} else if (inherits(values, c("POSIXt"))) {
|
||||
describe_col_datetime(values)
|
||||
} else {
|
||||
describe_col_other(values)
|
||||
}
|
||||
list(
|
||||
template = toastui::JS(
|
||||
"function(value) {",
|
||||
sprintf(
|
||||
"return '%s';",
|
||||
gsub(replacement = "", pattern = "\n", x = htmltools::doRenderTags(content))
|
||||
),
|
||||
"}"
|
||||
)
|
||||
)
|
||||
}
|
||||
)
|
||||
)
|
||||
}
|
9
R/html_dependency_freesearchr.R
Normal file
9
R/html_dependency_freesearchr.R
Normal file
|
@ -0,0 +1,9 @@
|
|||
html_dependency_FreesearchR <- function() {
|
||||
htmltools::htmlDependency(
|
||||
name = "FreesearchR",
|
||||
version = packageVersion("FreesearchR"),
|
||||
src = list(href = "FreesearchR", file = "assets"),
|
||||
package = "FreesearchR",
|
||||
stylesheet = "css/FreesearchR.css"
|
||||
)
|
||||
}
|
18
R/theme.R
18
R/theme.R
|
@ -10,7 +10,7 @@ custom_theme <- function(...,
|
|||
secondary = "#FF6F61",
|
||||
bootswatch = "united",
|
||||
base_font = bslib::font_google("Montserrat"),
|
||||
heading_font = bslib::font_google("Public Sans",wght = "700"),
|
||||
heading_font = bslib::font_google("Public Sans", wght = "700"),
|
||||
code_font = bslib::font_google("Open Sans")
|
||||
# success = "#1E4A8F",
|
||||
# info = ,
|
||||
|
@ -22,7 +22,7 @@ custom_theme <- function(...,
|
|||
# heading_font = bslib::font_google("Jost", wght = "800"),
|
||||
# heading_font = bslib::font_google("Noto Serif"),
|
||||
# heading_font = bslib::font_google("Alice"),
|
||||
){
|
||||
) {
|
||||
bslib::bs_theme(
|
||||
...,
|
||||
"navbar-bg" = primary,
|
||||
|
@ -36,6 +36,16 @@ custom_theme <- function(...,
|
|||
)
|
||||
}
|
||||
|
||||
compliment_colors <- function() {
|
||||
c(
|
||||
"#00C896",
|
||||
"#FFB100",
|
||||
"#8A4FFF",
|
||||
"#11A0EC"
|
||||
)
|
||||
}
|
||||
|
||||
|
||||
|
||||
#' GGplot default theme for plotting in Shiny
|
||||
#'
|
||||
|
@ -44,7 +54,7 @@ custom_theme <- function(...,
|
|||
#' @returns ggplot object
|
||||
#' @export
|
||||
#'
|
||||
gg_theme_shiny <- function(){
|
||||
gg_theme_shiny <- function() {
|
||||
ggplot2::theme(
|
||||
axis.title = ggplot2::element_text(size = 18),
|
||||
axis.text = ggplot2::element_text(size = 14),
|
||||
|
@ -64,7 +74,7 @@ gg_theme_shiny <- function(){
|
|||
#' @returns ggplot object
|
||||
#' @export
|
||||
#'
|
||||
gg_theme_export <- function(){
|
||||
gg_theme_export <- function() {
|
||||
ggplot2::theme(
|
||||
axis.title = ggplot2::element_text(size = 18),
|
||||
axis.text.x = ggplot2::element_text(size = 14),
|
||||
|
|
69
examples/create_column_module_demo.R
Normal file
69
examples/create_column_module_demo.R
Normal file
|
@ -0,0 +1,69 @@
|
|||
|
||||
library(shiny)
|
||||
library(reactable)
|
||||
|
||||
ui <- fluidPage(
|
||||
theme = bslib::bs_theme(version = 5L, preset = "bootstrap"),
|
||||
shinyWidgets::html_dependency_winbox(),
|
||||
tags$h2("Create new column"),
|
||||
fluidRow(
|
||||
column(
|
||||
width = 4,
|
||||
create_column_ui("inline"),
|
||||
actionButton("modal", "Or click here to open a modal to create a column"),
|
||||
tags$br(), tags$br(),
|
||||
actionButton("winbox", "Or click here to open a WinBox to create a column")
|
||||
),
|
||||
column(
|
||||
width = 8,
|
||||
reactableOutput(outputId = "table"),
|
||||
verbatimTextOutput("code")
|
||||
)
|
||||
)
|
||||
)
|
||||
|
||||
server <- function(input, output, session) {
|
||||
|
||||
rv <- reactiveValues(data = MASS::Cars93[, c(1, 3, 4, 5, 6, 10)])
|
||||
|
||||
# inline mode
|
||||
data_inline_r <- create_column_server(
|
||||
id = "inline",
|
||||
data_r = reactive(rv$data)
|
||||
)
|
||||
observeEvent(data_inline_r(), rv$data <- data_inline_r())
|
||||
|
||||
# modal window mode
|
||||
observeEvent(input$modal, modal_create_column("modal"))
|
||||
data_modal_r <- create_column_server(
|
||||
id = "modal",
|
||||
data_r = reactive(rv$data)
|
||||
)
|
||||
observeEvent(data_modal_r(), rv$data <- data_modal_r())
|
||||
|
||||
# WinBox window mode
|
||||
observeEvent(input$winbox, winbox_create_column("winbox"))
|
||||
data_winbox_r <- create_column_server(
|
||||
id = "winbox",
|
||||
data_r = reactive(rv$data)
|
||||
)
|
||||
observeEvent(data_winbox_r(), rv$data <- data_winbox_r())
|
||||
|
||||
# Show result
|
||||
output$table <- renderReactable({
|
||||
data <- req(rv$data)
|
||||
reactable(
|
||||
data = data,
|
||||
bordered = TRUE,
|
||||
compact = TRUE,
|
||||
striped = TRUE
|
||||
)
|
||||
})
|
||||
|
||||
output$code <- renderPrint({
|
||||
attr(rv$data, "code")
|
||||
})
|
||||
}
|
||||
|
||||
if (interactive())
|
||||
shinyApp(ui, server)
|
124
inst/apps/FreesearchR/www/style.css
Normal file
124
inst/apps/FreesearchR/www/style.css
Normal file
|
@ -0,0 +1,124 @@
|
|||
|
||||
/*!
|
||||
* Copyright (c) 2025 FreesearchR
|
||||
*
|
||||
* FreesearchR, CSS styles
|
||||
* https://github.com/agdamsbo/FreesearchR
|
||||
*
|
||||
* @version 0.0.1
|
||||
*/
|
||||
|
||||
.container-fluid > .nav > li >
|
||||
a[data-value='FreesearchR'] {font-size: 28px}
|
||||
|
||||
/* from datamods */
|
||||
.show-block {
|
||||
display: block !important;
|
||||
}
|
||||
.show-inline {
|
||||
display: inline !important;
|
||||
}
|
||||
.hidden {
|
||||
display: none !important;
|
||||
}
|
||||
.invisible {
|
||||
visibility: hidden;
|
||||
}
|
||||
|
||||
.container-rule {
|
||||
position: relative;
|
||||
text-align: center;
|
||||
height: 25px;
|
||||
margin-bottom: 5px;
|
||||
}
|
||||
|
||||
.horizontal-rule {
|
||||
position: absolute;
|
||||
top: 11px;
|
||||
right: 0;
|
||||
left: 0;
|
||||
background-color: #d0cfcf;
|
||||
height: 1px;
|
||||
z-index: 100;
|
||||
margin: 0;
|
||||
border: none;
|
||||
}
|
||||
|
||||
.label-rule {
|
||||
background: #FFF;
|
||||
opacity: 1;
|
||||
z-index: 101;
|
||||
background-color: #FFF;
|
||||
position: relative;
|
||||
padding: 0 10px 0 10px;
|
||||
}
|
||||
|
||||
.datamods-table-container {
|
||||
overflow: auto;
|
||||
word-break: keep-all;
|
||||
white-space: nowrap;
|
||||
}
|
||||
|
||||
.datamods-table-container > .table {
|
||||
margin-bottom: 0 !important;
|
||||
}
|
||||
|
||||
.datamods-file-import {
|
||||
display: grid;
|
||||
grid-template-columns: auto 50px;
|
||||
grid-column-gap: 10px;
|
||||
}
|
||||
|
||||
.datamods-dt-nowrap {
|
||||
word-break: keep-all;
|
||||
white-space: nowrap;
|
||||
}
|
||||
|
||||
|
||||
|
||||
/* validation */
|
||||
.datamods-validation-results {
|
||||
display: grid;
|
||||
grid-template-columns: repeat(3, 1fr);
|
||||
grid-template-rows: 1fr;
|
||||
height: 50px;
|
||||
line-height: 50px;
|
||||
font-size: large;
|
||||
}
|
||||
|
||||
.datamods-validation-summary {
|
||||
font-weight: bold;
|
||||
text-align: center;
|
||||
}
|
||||
|
||||
.datamods-validation-item {
|
||||
font-size: larger;
|
||||
}
|
||||
|
||||
|
||||
|
||||
/* modified from esquisse for data types */
|
||||
.btn-column-categorical {
|
||||
background-color: #00C896;
|
||||
color: #FFFFFF;
|
||||
}
|
||||
.btn-column-continuous {
|
||||
background-color: #FFB100;
|
||||
color: #FFFFFF;
|
||||
}
|
||||
.btn-column-dichotomous {
|
||||
background-color: #8A4FFF;
|
||||
color: #FFFFFF;
|
||||
}
|
||||
.btn-column-datetime {
|
||||
background-color: #11A0EC;
|
||||
color: #FFFFFF;
|
||||
}
|
||||
.btn-column-id {
|
||||
background-color: #848484;
|
||||
color: #FFFFFF;
|
||||
}
|
||||
.btn-column-text {
|
||||
background-color: #2E2E2E;
|
||||
color: #FFFFFF;
|
||||
}
|
124
inst/assets/css/FreesearchR.css
Normal file
124
inst/assets/css/FreesearchR.css
Normal file
|
@ -0,0 +1,124 @@
|
|||
|
||||
/*!
|
||||
* Copyright (c) 2025 FreesearchR
|
||||
*
|
||||
* FreesearchR, CSS styles
|
||||
* https://github.com/agdamsbo/FreesearchR
|
||||
*
|
||||
* @version 0.0.1
|
||||
*/
|
||||
|
||||
.container-fluid > .nav > li >
|
||||
a[data-value='FreesearchR'] {font-size: 28px}
|
||||
|
||||
/* from datamods */
|
||||
.show-block {
|
||||
display: block !important;
|
||||
}
|
||||
.show-inline {
|
||||
display: inline !important;
|
||||
}
|
||||
.hidden {
|
||||
display: none !important;
|
||||
}
|
||||
.invisible {
|
||||
visibility: hidden;
|
||||
}
|
||||
|
||||
.container-rule {
|
||||
position: relative;
|
||||
text-align: center;
|
||||
height: 25px;
|
||||
margin-bottom: 5px;
|
||||
}
|
||||
|
||||
.horizontal-rule {
|
||||
position: absolute;
|
||||
top: 11px;
|
||||
right: 0;
|
||||
left: 0;
|
||||
background-color: #d0cfcf;
|
||||
height: 1px;
|
||||
z-index: 100;
|
||||
margin: 0;
|
||||
border: none;
|
||||
}
|
||||
|
||||
.label-rule {
|
||||
background: #FFF;
|
||||
opacity: 1;
|
||||
z-index: 101;
|
||||
background-color: #FFF;
|
||||
position: relative;
|
||||
padding: 0 10px 0 10px;
|
||||
}
|
||||
|
||||
.datamods-table-container {
|
||||
overflow: auto;
|
||||
word-break: keep-all;
|
||||
white-space: nowrap;
|
||||
}
|
||||
|
||||
.datamods-table-container > .table {
|
||||
margin-bottom: 0 !important;
|
||||
}
|
||||
|
||||
.datamods-file-import {
|
||||
display: grid;
|
||||
grid-template-columns: auto 50px;
|
||||
grid-column-gap: 10px;
|
||||
}
|
||||
|
||||
.datamods-dt-nowrap {
|
||||
word-break: keep-all;
|
||||
white-space: nowrap;
|
||||
}
|
||||
|
||||
|
||||
|
||||
/* validation */
|
||||
.datamods-validation-results {
|
||||
display: grid;
|
||||
grid-template-columns: repeat(3, 1fr);
|
||||
grid-template-rows: 1fr;
|
||||
height: 50px;
|
||||
line-height: 50px;
|
||||
font-size: large;
|
||||
}
|
||||
|
||||
.datamods-validation-summary {
|
||||
font-weight: bold;
|
||||
text-align: center;
|
||||
}
|
||||
|
||||
.datamods-validation-item {
|
||||
font-size: larger;
|
||||
}
|
||||
|
||||
|
||||
|
||||
/* modified from esquisse for data types */
|
||||
.btn-column-categorical {
|
||||
background-color: #00C896;
|
||||
color: #FFFFFF;
|
||||
}
|
||||
.btn-column-continuous {
|
||||
background-color: #FFB100;
|
||||
color: #FFFFFF;
|
||||
}
|
||||
.btn-column-dichotomous {
|
||||
background-color: #8A4FFF;
|
||||
color: #FFFFFF;
|
||||
}
|
||||
.btn-column-datetime {
|
||||
background-color: #11A0EC;
|
||||
color: #FFFFFF;
|
||||
}
|
||||
.btn-column-id {
|
||||
background-color: #848484;
|
||||
color: #FFFFFF;
|
||||
}
|
||||
.btn-column-text {
|
||||
background-color: #2E2E2E;
|
||||
color: #FFFFFF;
|
||||
}
|
76
man/create-column.Rd
Normal file
76
man/create-column.Rd
Normal file
|
@ -0,0 +1,76 @@
|
|||
% Generated by roxygen2: do not edit by hand
|
||||
% Please edit documentation in R/create-column-mod.R
|
||||
\name{create-column}
|
||||
\alias{create-column}
|
||||
\alias{create_column_ui}
|
||||
\alias{create_column_server}
|
||||
\alias{list_allowed_operations}
|
||||
\alias{modal_create_column}
|
||||
\alias{winbox_create_column}
|
||||
\title{Create new column}
|
||||
\usage{
|
||||
create_column_ui(id)
|
||||
|
||||
create_column_server(
|
||||
id,
|
||||
data_r = reactive(NULL),
|
||||
allowed_operations = list_allowed_operations()
|
||||
)
|
||||
|
||||
list_allowed_operations()
|
||||
|
||||
modal_create_column(
|
||||
id,
|
||||
title = i18n("Create a new column"),
|
||||
easyClose = TRUE,
|
||||
size = "l",
|
||||
footer = NULL
|
||||
)
|
||||
|
||||
winbox_create_column(
|
||||
id,
|
||||
title = i18n("Create a new column"),
|
||||
options = shinyWidgets::wbOptions(),
|
||||
controls = shinyWidgets::wbControls()
|
||||
)
|
||||
}
|
||||
\arguments{
|
||||
\item{id}{Module's ID.}
|
||||
|
||||
\item{data_r}{A \code{\link[shiny:reactive]{shiny::reactive()}} function returning a \code{data.frame}.}
|
||||
|
||||
\item{allowed_operations}{A \code{list} of allowed operations, see below for details.}
|
||||
|
||||
\item{title}{An optional title for the dialog.}
|
||||
|
||||
\item{easyClose}{If \code{TRUE}, the modal dialog can be dismissed by
|
||||
clicking outside the dialog box, or be pressing the Escape key. If
|
||||
\code{FALSE} (the default), the modal dialog can't be dismissed in those
|
||||
ways; instead it must be dismissed by clicking on a \code{modalButton()}, or
|
||||
from a call to \code{\link[shiny:removeModal]{removeModal()}} on the server.}
|
||||
|
||||
\item{size}{One of \code{"s"} for small, \code{"m"} (the default) for medium,
|
||||
\code{"l"} for large, or \code{"xl"} for extra large. Note that \code{"xl"} only
|
||||
works with Bootstrap 4 and above (to opt-in to Bootstrap 4+,
|
||||
pass \code{\link[bslib:bs_theme]{bslib::bs_theme()}} to the \code{theme} argument of a page container
|
||||
like \code{\link[shiny:fluidPage]{fluidPage()}}).}
|
||||
|
||||
\item{footer}{UI for footer. Use \code{NULL} for no footer.}
|
||||
|
||||
\item{options}{List of options, see \code{\link[shinyWidgets:wbOptions]{wbOptions()}}.}
|
||||
|
||||
\item{controls}{List of controls, see \code{\link[shinyWidgets:wbControls]{wbControls()}}.}
|
||||
}
|
||||
\value{
|
||||
A \code{\link[shiny:reactive]{shiny::reactive()}} function returning the data.
|
||||
}
|
||||
\description{
|
||||
This module allow to enter an expression to create a new column in a \code{data.frame}.
|
||||
}
|
||||
\note{
|
||||
User can only use a subset of function: (, c, +, -, *, ^, \%\%, \%/\%, /, ==, >, <, !=, <=, >=, &, |, abs, sign, sqrt, ceiling, floor, trunc, cummax, cummin, cumprod, cumsum, exp, expm1, log, log10, log2, log1p, cos, cosh, sin, sinh, tan, tanh, acos, acosh, asin, asinh, atan, atanh, cospi, sinpi, tanpi, gamma, lgamma, digamma, trigamma, round, signif, max, min, range, prod, sum, any, all, pmin, pmax, mean, paste, paste0, substr, nchar, trimws, gsub, sub, grepl, ifelse, length, as.numeric, as.character, as.integer, as.Date, as.POSIXct, as.factor, factor.
|
||||
You can add more operations using the \code{allowed_operations} argument, for example if you want to allow to use package lubridate, you can do:
|
||||
|
||||
\if{html}{\out{<div class="sourceCode r">}}\preformatted{c(list_allowed_operations(), getNamespaceExports("lubridate"))
|
||||
}\if{html}{\out{</div>}}
|
||||
}
|
|
@ -33,7 +33,7 @@ cut_var(x, ...)
|
|||
...
|
||||
)
|
||||
|
||||
\method{cut_var}{Date}(x, breaks, start.on.monday = TRUE, ...)
|
||||
\method{cut_var}{Date}(x, breaks = NULL, start.on.monday = TRUE, ...)
|
||||
}
|
||||
\arguments{
|
||||
\item{x}{an object inheriting from class "POSIXct"}
|
||||
|
@ -58,6 +58,8 @@ readr::parse_datetime(c("1992-02-01 01:00:20", "1992-02-06 03:00:20", "1992-05-0
|
|||
readr::parse_datetime(c("1992-02-01 01:00:20", "1992-02-06 03:00:20", "1992-05-01 01:20:20", "1992-09-01 08:20:20", "1999-02-01 21:20:20", "1992-12-01 03:02:20")) |> cut_var(breaks = "weekday")
|
||||
readr::parse_datetime(c("1992-02-01 01:00:20", "1992-02-06 03:00:20", "1992-05-01 01:20:20", "1992-09-01 08:20:20", "1999-02-01 21:20:20", "1992-12-01 03:02:20")) |> cut_var(breaks = "month_only")
|
||||
readr::parse_datetime(c("1992-02-01 01:00:20", "1992-02-06 03:00:20", "1992-05-01 01:20:20", "1992-09-01 08:20:20", "1999-02-01 21:20:20", "1992-12-01 03:02:20")) |> cut_var(breaks=NULL,format = "\%A-\%H")
|
||||
readr::parse_datetime(c("1992-02-01 01:00:20", "1992-02-06 03:00:20", "1992-05-01 01:20:20", "1992-09-01 08:20:20", "1999-02-01 21:20:20", "1992-12-01 03:02:20")) |> cut_var(breaks=NULL,format = "\%W")
|
||||
as.Date(c("1992-02-01 01:00:20", "1992-02-06 03:00:20", "1992-05-01 01:20:20", "1992-09-01 08:20:20", "1999-02-01 21:20:20", "1992-12-01 03:02:20")) |> cut_var(2)
|
||||
as.Date(c("1992-02-01 01:00:20", "1992-02-06 03:00:20", "1992-05-01 01:20:20", "1992-09-01 08:20:20", "1999-02-01 21:20:20", "1992-12-01 03:02:20")) |> cut_var(breaks = "weekday")
|
||||
as.Date(c("1992-02-01 01:00:20", "1992-02-06 03:00:20", "1992-05-01 01:20:20", "1992-09-01 08:20:20", "1999-02-01 21:20:20", "1992-12-01 03:02:20")) |> cut_var(format = "\%W")
|
||||
}
|
||||
|
|
23
man/get_var_icon.Rd
Normal file
23
man/get_var_icon.Rd
Normal file
|
@ -0,0 +1,23 @@
|
|||
% Generated by roxygen2: do not edit by hand
|
||||
% Please edit documentation in R/data-summary.R
|
||||
\name{get_var_icon}
|
||||
\alias{get_var_icon}
|
||||
\title{Easily get variable icon based on data type or class}
|
||||
\usage{
|
||||
get_var_icon(data, class.type = c("class", "type"))
|
||||
}
|
||||
\arguments{
|
||||
\item{data}{variable or data frame}
|
||||
|
||||
\item{class.type}{"type" or "class". Default is "class"}
|
||||
}
|
||||
\value{
|
||||
svg icon
|
||||
}
|
||||
\description{
|
||||
Easily get variable icon based on data type or class
|
||||
}
|
||||
\examples{
|
||||
mtcars[1] |> get_var_icon("class")
|
||||
default_parsing(mtcars) |> get_var_icon()
|
||||
}
|
41
man/show_data.Rd
Normal file
41
man/show_data.Rd
Normal file
|
@ -0,0 +1,41 @@
|
|||
% Generated by roxygen2: do not edit by hand
|
||||
% Please edit documentation in R/datagrid-infos-mod.R
|
||||
\name{show_data}
|
||||
\alias{show_data}
|
||||
\title{Display a table in a window}
|
||||
\usage{
|
||||
show_data(
|
||||
data,
|
||||
title = NULL,
|
||||
options = NULL,
|
||||
show_classes = TRUE,
|
||||
type = c("popup", "modal", "winbox"),
|
||||
width = "65\%",
|
||||
...
|
||||
)
|
||||
}
|
||||
\arguments{
|
||||
\item{data}{a data object (either a \code{matrix} or a \code{data.frame}).}
|
||||
|
||||
\item{title}{Title to be displayed in window.}
|
||||
|
||||
\item{options}{Arguments passed to \code{\link[toastui:datagrid]{toastui::datagrid()}}.}
|
||||
|
||||
\item{show_classes}{Show variables classes under variables names in table header.}
|
||||
|
||||
\item{type}{Display table in a pop-up with \code{\link[shinyWidgets:sweetalert]{shinyWidgets::show_alert()}},
|
||||
in modal window with \code{\link[shiny:showModal]{shiny::showModal()}} or in a WinBox window with \code{\link[shinyWidgets:WinBox]{shinyWidgets::WinBox()}}.}
|
||||
|
||||
\item{width}{Width of the window, only used if \code{type = "popup"} or \code{type = "winbox"}.}
|
||||
|
||||
\item{...}{Additional options, such as \code{wbOptions = wbOptions()} or \code{wbControls = wbControls()}.}
|
||||
}
|
||||
\value{
|
||||
No value.
|
||||
}
|
||||
\description{
|
||||
Display a table in a window
|
||||
}
|
||||
\note{
|
||||
If you use \code{type = "winbox"}, you'll need to use \code{shinyWidgets::html_dependency_winbox()} somewhere in your UI.
|
||||
}
|
Loading…
Add table
Reference in a new issue