From 4824e2757d42627bcbaee807d245df9d9643fdc1 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Andr=C3=A9=20Ver=C3=ADssimo?= <211358+averissimo@users.noreply.github.com> Date: Thu, 28 Nov 2024 13:43:50 +0000 Subject: [PATCH] Updates "Decorators" to use name-based execution and new wrappers (#812) MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit #### Modules ##### 1 object - [x] tm_a_pca - [x] tm_g_bivariate - [x] tm_g_response - [x] tm_g_scatterplot - [x] tm_g_scatterplotmatrix - [x] tm_a_regression - [x] tm_t_crosstable - [x] tm_data_table - [x] tm_g_association ##### 2 objects ##### 3 objects - [x] tm_g_distribution - [x] tm_outliers ##### 4 objects - [x] tm_missing_data ##### Not applicable - [x] ~~tm_file_viewer~~ - [x] ~~tm_front_page~~ - [x] ~~tm_variable_browser~~ #### Changes description - Allow named-based decorators - Use `ui_decorate_teal_data` and `srv_decorate_teal_data` wrapper to simplify code - [x] New function to normalize `decorators` argument in module See [this comment](https://github.com/insightsengineering/teal.modules.general/pull/812#discussion_r1858787047) #### App with all modules (WIP)
Working example ```r pkgload::load_all("../teal") pkgload::load_all(".") # ###################################################### # # _____ _ # | __ \ | | # | | | | ___ ___ ___ _ __ __ _| |_ ___ _ __ ___ # | | | |/ _ \/ __/ _ \| '__/ _` | __/ _ \| '__/ __| # | |__| | __/ (_| (_) | | | (_| | || (_) | | \__ \ # |_____/ \___|\___\___/|_| \__,_|\__\___/|_| |___/ # # # # Decorators # ##################################################### plot_grob_decorator <- function(default_footnote = "I am a good decorator", .var_to_replace = "plot") { teal_transform_module( label = "Caption (grob)", ui = function(id) shiny::textInput(shiny::NS(id, "footnote"), "Footnote", value = default_footnote), server = function(id, data) { moduleServer(id, function(input, output, session) { logger::log_info("🟠 plot_grob with default: {default_footnote}!", namespace = "teal.modules.general") reactive({ req(data(), input$footnote) logger::log_info("changing the footnote {default_footnote}", namespace = "teal.modules.general") teal.code::eval_code(data(), substitute( { footnote_grob <- grid::textGrob(footnote, x = 0, hjust = 0, gp = grid::gpar(fontsize = 10, fontface = "italic", col = "gray50")) # Arrange the plot and footnote .var_to_replace <- gridExtra::arrangeGrob( .var_to_replace, footnote_grob, ncol = 1, heights = grid::unit.c(grid::unit(1, "npc") - grid::unit(1, "lines"), grid::unit(1, "lines")) ) }, env = list( footnote = input$footnote, .var_to_replace = as.name(.var_to_replace) ))) }) }) } ) } caption_decorator <- function(default_caption = "I am a good decorator", .var_to_replace = "plot") { teal_transform_module( label = "Caption", ui = function(id) shiny::textInput(shiny::NS(id, "footnote"), "Footnote", value = default_caption), server = make_teal_transform_server( substitute({ .var_to_replace <- .var_to_replace + ggplot2::labs(caption = footnote) }, env = list(.var_to_replace = as.name(.var_to_replace))) ) ) } table_decorator <- function(.color1 = "#f9f9f9", .color2 = "#f0f0f0", .var_to_replace = "table") { teal_transform_module( label = "Table color", ui = function(id) { selectInput( NS(id, "style"), "Table Style", choices = c("Default", "Color1", "Color2"), selected = "Default" ) }, server = function(id, data) { moduleServer(id, function(input, output, session) { logger::log_info("🔵 Table row color called to action!", namespace = "teal.modules.general") reactive({ req(data(), input$style) logger::log_info("changing the Table row color '{input$style}'", namespace = "teal.modules.general") teal.code::eval_code(data(), substitute({ .var_to_replace <- switch( style, "Color1" = DT::formatStyle( .var_to_replace, columns = attr(.var_to_replace$x, "colnames")[-1], target = "row", backgroundColor = .color1 ), "Color2" = DT::formatStyle( .var_to_replace, columns = attr(.var_to_replace$x, "colnames")[-1], target = "row", backgroundColor = .color2 ), .var_to_replace ) }, env = list( style = input$style, .var_to_replace = as.name(.var_to_replace), .color1 = .color1, .color2 = .color2 ))) }) }) } ) } head_decorator <- function(default_value = 6, .var_to_replace = "object") { teal_transform_module( label = "Head", ui = function(id) shiny::numericInput(shiny::NS(id, "n"), "Footnote", value = default_value), server = make_teal_transform_server( substitute({ .var_to_replace <- utils::head(.var_to_replace, n = n) }, env = list(.var_to_replace = as.name(.var_to_replace))) ) ) } treelis_subtitle_decorator <- function(default_caption = "I am a good decorator", .var_to_replace = "plot") { teal_transform_module( label = "Caption", ui = function(id) shiny::textInput(shiny::NS(id, "footnote"), "Footnote", value = default_caption), server = make_teal_transform_server( substitute({ .var_to_replace <- update(.var_to_replace, sub = footnote) }, env = list(.var_to_replace = as.name(.var_to_replace))) ) ) } insert_rrow_decorator <- function(default_caption = "I am a good new row", .var_to_replace = "table") { teal_transform_module( label = "New row", ui = function(id) shiny::textInput(shiny::NS(id, "new_row"), "New row", value = default_caption), server = make_teal_transform_server( substitute({ .var_to_replace <- rtables::insert_rrow(.var_to_replace, rtables::rrow(new_row)) }, env = list(.var_to_replace = as.name(.var_to_replace))) ) ) } do_nothing_decorator <- teal_transform_module(server = function(id, data) moduleServer(id, function(input, output, session) data)) # ########################################## # # _ _ _ _ # | | | | | | | | # | |_ ___ __ _| | __| | __ _| |_ __ _ # | __/ _ \/ _` | | / _` |/ _` | __/ _` | # | || __/ (_| | || (_| | (_| | || (_| | # \__\___|\__,_|_| \__,_|\__,_|\__\__,_| # ______ # |______| # # teal_data # ######################################### data <- teal_data(join_keys = default_cdisc_join_keys[c("ADSL", "ADRS")]) data <- within(data, { require(nestcolor) ADSL <- rADSL ADRS <- rADRS }) # For tm_outliers fact_vars_adsl <- names(Filter(isTRUE, sapply(data[["ADSL"]], is.factor))) vars <- choices_selected(variable_choices(data[["ADSL"]], fact_vars_adsl)) init( data = data, modules = modules( ###################################### # # _ _ _ # | | | (_) # ___ _ _| |_| |_ ___ _ __ ___ # / _ \| | | | __| | |/ _ \ '__/ __| # | (_) | |_| | |_| | | __/ | \__ \ # \___/ \__,_|\__|_|_|\___|_| |___/ # # # # outliers # ##################################### tm_outliers( outlier_var = list( data_extract_spec( dataname = "ADSL", select = select_spec( label = "Select variable:", choices = variable_choices(data[["ADSL"]], c("AGE", "BMRKR1")), selected = "AGE", multiple = FALSE, fixed = FALSE ) ) ), categorical_var = list( data_extract_spec( dataname = "ADSL", filter = filter_spec( vars = vars, choices = value_choices(data[["ADSL"]], vars$selected), selected = value_choices(data[["ADSL"]], vars$selected), multiple = TRUE ) ) ), decorators = list( box_plot = caption_decorator("I am a good decorator", "box_plot"), density_plot = caption_decorator("I am a good decorator", "density_plot"), cumulative_plot = caption_decorator("I am a good decorator", "cumulative_plot"), table = table_decorator("#FFA500", "#800080") ) ), # ####################################################### # # _ _ _ # (_) | | (_) # __ _ ___ ___ ___ ___ _ __ _| |_ _ ___ _ __ # / _` / __/ __|/ _ \ / __| |/ _` | __| |/ _ \| '_ \ # | (_| \__ \__ \ (_) | (__| | (_| | |_| | (_) | | | | # \__,_|___/___/\___/ \___|_|\__,_|\__|_|\___/|_| |_| # # # # association # ###################################################### tm_g_association( ref = data_extract_spec( dataname = "ADSL", select = select_spec( choices = variable_choices( data[["ADSL"]], c("SEX", "RACE", "COUNTRY", "ARM", "STRATA1", "STRATA2", "ITTFL", "BMRKR2") ), selected = "RACE" ) ), vars = data_extract_spec( dataname = "ADSL", select = select_spec( choices = variable_choices( data[["ADSL"]], c("SEX", "RACE", "COUNTRY", "ARM", "STRATA1", "STRATA2", "ITTFL", "BMRKR2") ), selected = "BMRKR2", multiple = TRUE ) ), decorators = list(plot_grob_decorator("I am a good grob (association)")) ), # ################################################ # # _ _ _ _ _ # | | | | | | | | | | # __| | __ _| |_ __ _ | |_ __ _| |__ | | ___ # / _` |/ _` | __/ _` || __/ _` | '_ \| |/ _ \ # | (_| | (_| | || (_| || || (_| | |_) | | __/ # \__,_|\__,_|\__\__,_| \__\__,_|_.__/|_|\___| # ______ # |______| # # data_table # ############################################### tm_data_table( variables_selected = list( iris = c("Sepal.Length", "Sepal.Width", "Petal.Length", "Petal.Width", "Species") ), dt_args = list(caption = "IRIS Table Caption"), decorators = list(table_decorator()) ), # ######################################################## # # _ _ _ # | | | | | | # ___ _ __ ___ ___ ___ ______| |_ __ _| |__ | | ___ # / __| '__/ _ \/ __/ __|______| __/ _` | '_ \| |/ _ \ # | (__| | | (_) \__ \__ \ | || (_| | |_) | | __/ # \___|_| \___/|___/___/ \__\__,_|_.__/|_|\___| # # # # cross-table # ####################################################### tm_t_crosstable( label = "Cross Table", x = data_extract_spec( dataname = "ADSL", select = select_spec( choices = variable_choices(data[["ADSL"]], subset = function(data) { idx <- !vapply(data, inherits, logical(1), c("Date", "POSIXct", "POSIXlt")) return(names(data)[idx]) }), selected = "COUNTRY", multiple = TRUE, ordered = TRUE ) ), y = data_extract_spec( dataname = "ADSL", select = select_spec( choices = variable_choices(data[["ADSL"]], subset = function(data) { idx <- vapply(data, is.factor, logical(1)) return(names(data)[idx]) }), selected = "SEX" ) ), decorators = list(insert_rrow_decorator("I am a good new row")) ), # ####################################################################################### # # _ _ _ _ _ _ # | | | | | | | | | | (_) # ___ ___ __ _| |_| |_ ___ _ __ _ __ | | ___ | |_ _ __ ___ __ _| |_ _ __ ___ __ # / __|/ __/ _` | __| __/ _ \ '__| '_ \| |/ _ \| __| | '_ ` _ \ / _` | __| '__| \ \/ / # \__ \ (_| (_| | |_| || __/ | | |_) | | (_) | |_ | | | | | | (_| | |_| | | |> < # |___/\___\__,_|\__|\__\___|_| | .__/|_|\___/ \__| |_| |_| |_|\__,_|\__|_| |_/_/\_\ # | | # |_| # # scatterplot matrix # ###################################################################################### tm_g_scatterplotmatrix( label = "Scatterplot matrix", variables = list( data_extract_spec( dataname = "ADSL", select = select_spec( choices = variable_choices(data[["ADSL"]]), selected = c("AGE", "RACE", "SEX"), multiple = TRUE, ordered = TRUE ) ), data_extract_spec( dataname = "ADRS", filter = filter_spec( label = "Select endpoints:", vars = c("PARAMCD", "AVISIT"), choices = value_choices(data[["ADRS"]], c("PARAMCD", "AVISIT"), c("PARAM", "AVISIT")), selected = "INVET - END OF INDUCTION", multiple = TRUE ), select = select_spec( choices = variable_choices(data[["ADRS"]]), selected = c("AGE", "AVAL", "ADY"), multiple = TRUE, ordered = TRUE ) ) ), decorators = list(treelis_subtitle_decorator("I am a Scatterplot matrix", "plot")) ), # ############################################# # # # # _ __ ___ ___ _ __ ___ _ __ ___ ___ # | '__/ _ \/ __| '_ \ / _ \| '_ \/ __|/ _ \ # | | | __/\__ \ |_) | (_) | | | \__ \ __/ # |_| \___||___/ .__/ \___/|_| |_|___/\___| # | | # |_| # # response # ############################################ tm_g_response( label = "Response", response = data_extract_spec( dataname = "ADSL", select = select_spec(choices = variable_choices(data[["ADSL"]], c("BMRKR2", "COUNTRY"))) ), x = data_extract_spec( dataname = "ADSL", select = select_spec(choices = variable_choices(data[["ADSL"]], c("SEX", "RACE")), selected = "RACE") ), decorators = list(caption_decorator("I am a Response", "plot")) ), # ############################################ # # _ _ _ _ # | | (_) (_) | | # | |__ ___ ____ _ _ __ _ __ _| |_ ___ # | '_ \| \ \ / / _` | '__| |/ _` | __/ _ \ # | |_) | |\ V / (_| | | | | (_| | || __/ # |_.__/|_| \_/ \__,_|_| |_|\__,_|\__\___| # # # # bivariate # ########################################### tm_g_bivariate( x = data_extract_spec( dataname = "ADSL", select = select_spec(choices = variable_choices(data[["ADSL"]]), selected = "AGE") ), y = data_extract_spec( dataname = "ADSL", select = select_spec(choices = variable_choices(data[["ADSL"]]), selected = "SEX") ), row_facet = data_extract_spec( dataname = "ADSL", select = select_spec(choices = variable_choices(data[["ADSL"]]), selected = "ARM") ), col_facet = data_extract_spec( dataname = "ADSL", select = select_spec(choices = variable_choices(data[["ADSL"]]), selected = "COUNTRY") ), decorators = list(caption_decorator("I am a Bivariate", "plot")) ), # #################### # # # # _ __ ___ __ _ # | '_ \ / __/ _` | # | |_) | (_| (_| | # | .__/ \___\__,_| # | | # |_| # # pca # ################### tm_a_pca( "PCA", dat = data_extract_spec( dataname = "ADSL", select = select_spec( choices = variable_choices(data = data[["ADSL"]], c("BMRKR1", "AGE", "EOSDY")), selected = c("BMRKR1", "AGE") ) ), decorators = list(caption_decorator("I am a PCA", "plot")) ), ##################################################### # # _ _ _ _ # | | | | | | | | # ___ ___ __ _| |_| |_ ___ _ __ _ __ | | ___ | |_ # / __|/ __/ _` | __| __/ _ \ '__| '_ \| |/ _ \| __| # \__ \ (_| (_| | |_| || __/ | | |_) | | (_) | |_ # |___/\___\__,_|\__|\__\___|_| | .__/|_|\___/ \__| # | | # |_| # # scatterplot # #################################################### tm_g_scatterplot( label = "Scatterplot", x = data_extract_spec( dataname = "ADSL", select = select_spec(choices = variable_choices(data[["ADSL"]], c("AGE", "BMRKR1", "BMRKR2"))) ), y = data_extract_spec( dataname = "ADSL", select = select_spec( choices = variable_choices(data[["ADSL"]], c("AGE", "BMRKR1", "BMRKR2")), selected = "BMRKR1" ) ), color_by = data_extract_spec( dataname = "ADSL", select = select_spec( choices = variable_choices(data[["ADSL"]], c("AGE", "BMRKR1", "BMRKR2", "RACE", "REGION1")), selected = NULL ) ), size_by = data_extract_spec( dataname = "ADSL", select = select_spec(choices = variable_choices(data[["ADSL"]], c("AGE", "BMRKR1"))) ), row_facet = data_extract_spec( dataname = "ADSL", select = select_spec( choices = variable_choices(data[["ADSL"]], c("BMRKR2", "RACE", "REGION1")), selected = NULL ) ), col_facet = data_extract_spec( dataname = "ADSL", select = select_spec( choices = variable_choices(data[["ADSL"]], c("BMRKR2", "RACE", "REGION1")), selected = NULL ) ), decorators = list(caption_decorator("I am a scatterplot", "plot")) ), # ############################################################## # # _ _ _ _ # (_) (_) | | | | # _ __ ___ _ ___ ___ _ _ __ __ _ __| | __ _| |_ __ _ # | '_ ` _ \| / __/ __| | '_ \ / _` | / _` |/ _` | __/ _` | # | | | | | | \__ \__ \ | | | | (_| | | (_| | (_| | || (_| | # |_| |_| |_|_|___/___/_|_| |_|\__, | \__,_|\__,_|\__\__,_| # __/ |_____ # |___/______| # # missing_data # ############################################################# tm_missing_data( label = "Missing data", decorators = list( summary_plot = plot_grob_decorator("A", "summary_plot"), combination_plot = plot_grob_decorator("B", "combination_plot"), summary_table = table_decorator("table", .color1 = "#f0000055"), by_subject_plot = caption_decorator("by_subject_plot") ) ), example_module(decorators = list(head_decorator(6))) ) ) |> shiny::runApp() ```
--------- Signed-off-by: André Veríssimo <211358+averissimo@users.noreply.github.com> Co-authored-by: Marcin <133694481+m7pr@users.noreply.github.com> --- R/roxygen2_templates.R | 30 +++ R/tm_a_pca.R | 130 ++++++++--- R/tm_a_regression.R | 11 +- R/tm_data_table.R | 15 +- R/tm_g_association.R | 41 ++-- R/tm_g_bivariate.R | 84 +++---- R/tm_g_distribution.R | 158 ++++++++----- R/tm_g_response.R | 18 +- R/tm_g_scatterplot.R | 21 +- R/tm_g_scatterplotmatrix.R | 20 +- R/tm_missing_data.R | 56 +++-- R/tm_outliers.R | 210 +++++++++++------- R/tm_t_crosstable.R | 19 +- R/utils.R | 35 ++- man-roxygen/ggplot2_args_multi.R | 7 - man/normalize_decorators.Rd | 18 ++ ...set_decorators.Rd => select_decorators.Rd} | 10 +- man/shared_params.Rd | 3 - man/srv_decorate_teal_data.Rd | 5 +- man/tm_a_pca.Rd | 41 +++- man/tm_a_regression.Rd | 21 +- man/tm_data_table.Rd | 11 +- man/tm_file_viewer.Rd | 4 +- man/tm_front_page.Rd | 4 +- man/tm_g_association.Rd | 22 +- man/tm_g_bivariate.Rd | 11 +- man/tm_g_distribution.Rd | 43 +++- man/tm_g_response.Rd | 11 +- man/tm_g_scatterplot.Rd | 11 +- man/tm_g_scatterplotmatrix.Rd | 11 +- man/tm_missing_data.Rd | 40 +++- man/tm_outliers.Rd | 41 +++- man/tm_t_crosstable.Rd | 11 +- man/tm_variable_browser.Rd | 8 +- 34 files changed, 757 insertions(+), 424 deletions(-) create mode 100644 R/roxygen2_templates.R delete mode 100644 man-roxygen/ggplot2_args_multi.R create mode 100644 man/normalize_decorators.Rd rename man/{subset_decorators.Rd => select_decorators.Rd} (86%) diff --git a/R/roxygen2_templates.R b/R/roxygen2_templates.R new file mode 100644 index 000000000..d55c2aef4 --- /dev/null +++ b/R/roxygen2_templates.R @@ -0,0 +1,30 @@ +# nocov start +roxygen_decorators_param <- function(module_name) { + paste( + sep = " ", + lifecycle::badge("experimental"), + " (`list` of `teal_transform_module`, named `list` of `teal_transform_module` or", + "`NULL`) optional, if not `NULL`, decorator for tables or plots included in the module.", + "When a named list of `teal_transform_module`, the decorators are applied to the", + "respective output objects.\n\n", + "Otherwise, the decorators are applied to all objects, which is equivalent as using the name `default`.\n\n", + sprintf("See section \"Decorating `%s`\"", module_name), + "below for more details." + ) +} + +roxygen_ggplot2_args_param <- function(...) { + paste( + sep = " ", + "(`ggplot2_args`) optional, object created by [`teal.widgets::ggplot2_args()`]", + "with settings for all the plots or named list of `ggplot2_args` objects for plot-specific settings.", + "The argument is merged with options variable `teal.ggplot2_args` and default module setup.\n\n", + sprintf( + "List names should match the following: `c(\"default\", %s)`.\n\n", + paste("\"", unlist(rlang::list2(...)), "\"", collapse = ", ", sep = "") + ), + "For more details see the vignette: `vignette(\"custom-ggplot2-arguments\", package = \"teal.widgets\")`." + ) +} + +# nocov end diff --git a/R/tm_a_pca.R b/R/tm_a_pca.R index 9cccffe02..c6a7fb55e 100644 --- a/R/tm_a_pca.R +++ b/R/tm_a_pca.R @@ -13,20 +13,40 @@ #' It controls the font size for plot titles, axis labels, and legends. #' - If vector of `length == 1` then the font sizes will have a fixed size. #' - while vector of `value`, `min`, and `max` allows dynamic adjustment. -#' @templateVar ggnames "Elbow plot", "Circle plot", "Biplot", "Eigenvector plot" -#' @template ggplot2_args_multi +#' @param ggplot2_args `r roxygen_ggplot2_args_param("Elbow plot", "Circle plot", "Biplot", "Eigenvector plot")` +#' @param decorators `r roxygen_decorators_param("tm_a_pca")` #' #' @inherit shared_params return #' #' @section Decorating `tm_a_pca`: #' #' This module generates the following objects, which can be modified in place using decorators: -#' - `plot` (`ggplot2`) +#' - `elbow_plot` (`ggplot2`) +#' - `circle_plot` (`ggplot2`) +#' - `biplot` (`ggplot2`) +#' - `eigenvector_plot` (`ggplot2`) +#' +#' Decorators can be applied to all outputs or only to specific objects using a +#' named list of `teal_transform_module` objects. +#' The `"default"` name is reserved for decorators that are applied to all outputs. +#' See code snippet below: +#' +#' ``` +#' tm_a_pca( +#' ..., # arguments for module +#' decorators = list( +#' default = list(teal_transform_module(...)), # applied to all outputs +#' elbow_plot = list(teal_transform_module(...)), # applied only to `elbow_plot` output +#' circle_plot = list(teal_transform_module(...)) # applied only to `circle_plot` output +#' biplot = list(teal_transform_module(...)) # applied only to `biplot` output +#' eigenvector_plot = list(teal_transform_module(...)) # applied only to `eigenvector_plot` output +#' ) +#' ) +#' ``` #' #' For additional details and examples of decorators, refer to the vignette #' `vignette("decorate-modules-output", package = "teal")` or the [`teal_transform_module()`] documentation. #' -#' #' @examplesShinylive #' library(teal.modules.general) #' interactive <- function() TRUE @@ -165,7 +185,9 @@ tm_a_pca <- function(label = "Principal Component Analysis", checkmate::assert_multi_class(pre_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE) checkmate::assert_multi_class(post_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE) - checkmate::assert_list(decorators, "teal_transform_module", null.ok = TRUE) + available_decorators <- c("elbow_plot", "circle_plot", "biplot", "eigenvector_plot") + decorators <- normalize_decorators(decorators) + assert_decorators(decorators, null.ok = TRUE, available_decorators) # End of assertions # Make UI args @@ -240,7 +262,34 @@ ui_a_pca <- function(id, ...) { choices = args$plot_choices, selected = args$plot_choices[1] ), - ui_transform_teal_data(ns("decorate"), transformators = args$decorators) + conditionalPanel( + condition = sprintf("input['%s'] == 'Elbow plot'", ns("plot_type")), + ui_decorate_teal_data( + ns("d_elbow_plot"), + decorators = select_decorators(args$decorators, "elbow_plot") + ) + ), + conditionalPanel( + condition = sprintf("input['%s'] == 'Circle plot'", ns("plot_type")), + ui_decorate_teal_data( + ns("d_circle_plot"), + decorators = select_decorators(args$decorators, "circle_plot") + ) + ), + conditionalPanel( + condition = sprintf("input['%s'] == 'Biplot'", ns("plot_type")), + ui_decorate_teal_data( + ns("d_biplot"), + decorators = select_decorators(args$decorators, "biplot") + ) + ), + conditionalPanel( + condition = sprintf("input['%s'] == 'Eigenvector plot'", ns("plot_type")), + ui_decorate_teal_data( + ns("d_eigenvector_plot"), + decorators = select_decorators(args$decorators, "eigenvector_plot") + ) + ) ), teal.widgets::panel_item( title = "Pre-processing", @@ -565,7 +614,7 @@ srv_a_pca <- function(id, data, reporter, filter_panel_api, dat, plot_height, pl ) cols <- c(getOption("ggplot2.discrete.colour"), c("lightblue", "darkred", "black"))[1:3] - plot <- ggplot(mapping = aes_string(x = "component", y = "value")) + + elbow_plot <- ggplot(mapping = aes_string(x = "component", y = "value")) + geom_bar( aes(fill = "Single variance"), data = dplyr::filter(elb_dat, metric == "Proportion of Variance"), @@ -642,7 +691,7 @@ srv_a_pca <- function(id, data, reporter, filter_panel_api, dat, plot_height, pl y = sin(seq(0, 2 * pi, length.out = 100)) ) - plot <- ggplot(pca_rot) + + circle_plot <- ggplot(pca_rot) + geom_point(aes_string(x = x_axis, y = y_axis)) + geom_label( aes_string(x = x_axis, y = y_axis, label = "label"), @@ -874,7 +923,7 @@ srv_a_pca <- function(id, data, reporter, filter_panel_api, dat, plot_height, pl qenv, substitute( expr = { - plot <- plot_call + biplot <- plot_call }, env = list( plot_call = Reduce(function(x, y) call("+", x, y), pca_plot_biplot_expr) @@ -883,8 +932,8 @@ srv_a_pca <- function(id, data, reporter, filter_panel_api, dat, plot_height, pl ) } - # plot pc_var ---- - plot_pc_var <- function(base_q) { + # plot eigenvector_plot ---- + plot_eigenvector <- function(base_q) { pc <- input$pc ggtheme <- input$ggtheme @@ -950,7 +999,7 @@ srv_a_pca <- function(id, data, reporter, filter_panel_api, dat, plot_height, pl expr = { pca_rot <- pca$rotation[, pc, drop = FALSE] %>% dplyr::as_tibble(rownames = "Variable") - plot <- plot_call + eigenvector_plot <- plot_call }, env = list( pc = pc, @@ -960,27 +1009,54 @@ srv_a_pca <- function(id, data, reporter, filter_panel_api, dat, plot_height, pl ) } - # plot final ---- - output_q <- reactive({ - req(computation()) - teal::validate_inputs(iv_r()) - teal::validate_inputs(iv_extra, header = "Plot settings are required") + # qenvs --- + output_q <- lapply( + list( + elbow_plot = plot_elbow, + circle_plot = plot_circle, + biplot = plot_biplot, + eigenvector_plot = plot_eigenvector + ), + function(fun) { + reactive({ + req(computation()) + teal::validate_inputs(iv_r()) + teal::validate_inputs(iv_extra, header = "Plot settings are required") + fun(computation()) + }) + } + ) + + decorated_q <- mapply( + function(obj_name, q) { + srv_decorate_teal_data( + id = sprintf("d_%s", obj_name), + data = q, + decorators = select_decorators(decorators, obj_name), + expr = reactive({ + substitute(print(.plot), env = list(.plot = as.name(obj_name))) + }), + expr_is_reactive = TRUE + ) + }, + names(output_q), + output_q + ) - switch(input$plot_type, - "Elbow plot" = plot_elbow(computation()), - "Circle plot" = plot_circle(computation()), - "Biplot" = plot_biplot(computation()), - "Eigenvector plot" = plot_pc_var(computation()), + # plot final ---- + decorated_output_q <- reactive({ + switch(req(input$plot_type), + "Elbow plot" = decorated_q$elbow_plot(), + "Circle plot" = decorated_q$circle_plot(), + "Biplot" = decorated_q$biplot(), + "Eigenvector plot" = decorated_q$eigenvector_plot(), stop("Unknown plot") ) }) - decorated_output_q_no_print <- srv_transform_teal_data("decorate", data = output_q, transformators = decorators) - decorated_output_q <- reactive(within(decorated_output_q_no_print(), expr = print(plot))) - plot_r <- reactive({ - req(output_q()) - decorated_output_q()[["plot"]] + plot_name <- gsub(" ", "_", tolower(req(input$plot_type))) + req(decorated_output_q())[[plot_name]] }) pws <- teal.widgets::plot_with_settings_srv( diff --git a/R/tm_a_regression.R b/R/tm_a_regression.R index b0e4d49ec..4c5368243 100644 --- a/R/tm_a_regression.R +++ b/R/tm_a_regression.R @@ -37,8 +37,10 @@ #' It takes the form of `c(value, min, max)` and it is passed to the `value_min_max` #' argument in `teal.widgets::optionalSliderInputValMinMax`. #' -#' @templateVar ggnames `r regression_names` -#' @template ggplot2_args_multi +# nolint start: line_length. +#' @param ggplot2_args `r roxygen_ggplot2_args_param("Response vs Regressor", "Residuals vs Fitted", "Scale-Location", "Cook's distance", "Residuals vs Leverage", "Cook's dist vs Leverage")` +# nolint end: line_length. +#' @param decorators `r roxygen_decorators_param("tm_a_regression")` #' #' @inherit shared_params return #' @@ -1034,8 +1036,3 @@ srv_a_regression <- function(id, ### }) } - -regression_names <- paste0( - '"Response vs Regressor", "Residuals vs Fitted", ', - '"Scale-Location", "Cook\'s distance", "Residuals vs Leverage"", "Cook\'s dist vs Leverage"' -) diff --git a/R/tm_data_table.R b/R/tm_data_table.R index 657d5bf6d..0adbcccdc 100644 --- a/R/tm_data_table.R +++ b/R/tm_data_table.R @@ -131,7 +131,8 @@ tm_data_table <- function(label = "Data Table", checkmate::assert_multi_class(pre_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE) checkmate::assert_multi_class(post_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE) - checkmate::assert_list(decorators, "teal_transform_module", null.ok = TRUE) + decorators <- normalize_decorators(decorators) + assert_decorators(decorators, null.ok = TRUE, "table") # End of assertions ans <- module( @@ -296,7 +297,7 @@ ui_data_table <- function(id, tagList( teal.widgets::get_dt_rows(ns("data_table"), ns("dt_rows")), fluidRow( - ui_transform_teal_data(ns("decorate"), transformators = decorators), + ui_decorate_teal_data(ns("decorator"), decorators = select_decorators(decorators, "table")), teal.widgets::optionalSelectInput( ns("variables"), "Select variables:", @@ -365,13 +366,15 @@ srv_data_table <- function(id, ) }) - decorated_data_table_data <- - srv_transform_teal_data("decorate", data = data_table_data, transformators = decorators) + decorated_data_table_data <- srv_decorate_teal_data( + id = "decorator", + data = data_table_data, + decorators = select_decorators(decorators, "table") + ) output$data_table <- DT::renderDataTable(server = server_rendering, { - req(data_table_data()) teal::validate_inputs(iv) - decorated_data_table_data()[["table"]] + req(decorated_data_table_data())[["table"]] }) }) } diff --git a/R/tm_g_association.R b/R/tm_g_association.R index faa79ce1c..9110cc182 100644 --- a/R/tm_g_association.R +++ b/R/tm_g_association.R @@ -20,16 +20,15 @@ #' @param distribution_theme,association_theme (`character`) optional, `ggplot2` themes to be used by default. #' Default to `"gray"`. #' -#' @templateVar ggnames "Bivariate1", "Bivariate2" -#' @template ggplot2_args_multi +#' @param ggplot2_args `r roxygen_ggplot2_args_param("Bivariate1", "Bivariate2")` +#' @param decorators `r roxygen_decorators_param("tm_")` #' #' @inherit shared_params return #' #' @section Decorating `tm_g_association`: #' #' This module generates the following objects, which can be modified in place using decorators: -#' - `plot_top` (`ggplot2`) -#' - `plot_bottom` (`ggplot2`) +#' - `plot` (`grob` created with [ggplot2::ggplotGrob()]) #' #' For additional details and examples of decorators, refer to the vignette #' `vignette("decorate-modules-output", package = "teal")` or the [`teal_transform_module()`] documentation. @@ -176,7 +175,10 @@ tm_g_association <- function(label = "Association", plot_choices <- c("Bivariate1", "Bivariate2") checkmate::assert_list(ggplot2_args, types = "ggplot2_args") checkmate::assert_subset(names(ggplot2_args), c("default", plot_choices)) - checkmate::assert_list(decorators, "teal_transform_module", null.ok = TRUE) + + decorators <- normalize_decorators(decorators) + assert_decorators(decorators, null.ok = TRUE, "plot") + # End of assertions # Make UI args @@ -247,7 +249,7 @@ ui_tm_g_association <- function(id, ...) { "Log transformed", value = FALSE ), - ui_transform_teal_data(ns("decorate"), transformators = args$decorators), + ui_decorate_teal_data(ns("decorator"), decorators = select_decorators(args$decorators, "plot")), teal.widgets::panel_group( teal.widgets::panel_item( title = "Plot settings", @@ -405,8 +407,6 @@ srv_tm_g_association <- function(id, # association ref_class_cov <- ifelse(association, ref_class, "NULL") - print_call <- quote(print(p)) - var_calls <- lapply(vars_names, function(var_i) { var_class <- class(ANL[[var_i]])[1] if (is.numeric(ANL[[var_i]]) && log_transformation) { @@ -488,6 +488,7 @@ srv_tm_g_association <- function(id, expr = { plot_top <- plot_calls[[1]] plot_bottom <- plot_calls[[1]] + plot <- tern::stack_grobs(grobs = lapply(list(plot_top, plot_bottom), ggplotGrob)) }, env = list( plot_calls = do.call( @@ -500,23 +501,19 @@ srv_tm_g_association <- function(id, ) }) - decorated_output_q <- srv_transform_teal_data("decorate", data = output_q, transformators = decorators) - decorated_output_grob_q <- reactive({ - within( - decorated_output_q(), - { - plot <- tern::stack_grobs(grobs = lapply(list(plot_top, plot_bottom), ggplotGrob)) - grid::grid.newpage() - grid::grid.draw(plot) - } - ) - }) - + decorated_output_grob_q <- srv_decorate_teal_data( + id = "decorator", + data = output_q, + decorators = select_decorators(decorators, "plot"), + expr = { + grid::grid.newpage() + grid::grid.draw(plot) + } + ) plot_r <- reactive({ req(iv_r()$is_valid()) - req(output_q()) - decorated_output_grob_q()[["plot"]] + req(decorated_output_grob_q())[["plot"]] }) pws <- teal.widgets::plot_with_settings_srv( diff --git a/R/tm_g_bivariate.R b/R/tm_g_bivariate.R index 390640dd6..447a574d8 100644 --- a/R/tm_g_bivariate.R +++ b/R/tm_g_bivariate.R @@ -276,7 +276,8 @@ tm_g_bivariate <- function(label = "Bivariate Plots", checkmate::assert_multi_class(pre_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE) checkmate::assert_multi_class(post_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE) - checkmate::assert_list(decorators, "teal_transform_module", null.ok = TRUE) + decorators <- normalize_decorators(decorators) + assert_decorators(decorators, null.ok = TRUE, "plot") # End of assertions # Make UI args @@ -350,7 +351,7 @@ ui_g_bivariate <- function(id, ...) { justified = TRUE ) ), - ui_transform_teal_data(ns("decorate"), transformators = args$decorators), + ui_decorate_teal_data(ns("decorator"), decorators = select_decorators(args$decorators, "plot")), if (!is.null(args$row_facet) || !is.null(args$col_facet)) { tags$div( class = "data-extract-box", @@ -665,47 +666,46 @@ srv_g_bivariate <- function(id, teal.code::eval_code(merged$anl_q_r(), substitute(expr = plot <- cl, env = list(cl = cl))) }) - decorated_output_q <- srv_transform_teal_data("decorate", data = output_q, transformators = decorators) - - decorated_output_q_facets <- reactive({ - ANL <- merged$anl_q_r()[["ANL"]] - row_facet_name <- as.vector(merged$anl_input_r()$columns_source$row_facet) - col_facet_name <- as.vector(merged$anl_input_r()$columns_source$col_facet) - - # Add labels to facets - nulled_row_facet_name <- varname_w_label(row_facet_name, ANL) - nulled_col_facet_name <- varname_w_label(col_facet_name, ANL) - facetting <- (isTRUE(input$facetting) && (!is.null(row_facet_name) || !is.null(col_facet_name))) - without_facet <- (is.null(nulled_row_facet_name) && is.null(nulled_col_facet_name)) || !facetting - - print_call <- if (without_facet) { - quote(print(plot)) - } else { - substitute( - expr = { - # Add facetting labels - # optional: grid.newpage() # nolint: commented_code. - # Prefixed with teal.modules.general as its usage will appear in "Show R code" - plot <- teal.modules.general::add_facet_labels( - plot, - xfacet_label = nulled_col_facet_name, - yfacet_label = nulled_row_facet_name - ) - grid::grid.newpage() - grid::grid.draw(plot) - }, - env = list(nulled_col_facet_name = nulled_col_facet_name, nulled_row_facet_name = nulled_row_facet_name) - ) - } - decorated_output_q() %>% - teal.code::eval_code(print_call) - }) - + decorated_output_q_facets <- srv_decorate_teal_data( + "decorator", + data = output_q, + decorators = select_decorators(decorators, "plot"), + expr = reactive({ + ANL <- merged$anl_q_r()[["ANL"]] + row_facet_name <- as.vector(merged$anl_input_r()$columns_source$row_facet) + col_facet_name <- as.vector(merged$anl_input_r()$columns_source$col_facet) + + # Add labels to facets + nulled_row_facet_name <- varname_w_label(row_facet_name, ANL) + nulled_col_facet_name <- varname_w_label(col_facet_name, ANL) + facetting <- (isTRUE(input$facetting) && (!is.null(row_facet_name) || !is.null(col_facet_name))) + without_facet <- (is.null(nulled_row_facet_name) && is.null(nulled_col_facet_name)) || !facetting + + print_call <- if (without_facet) { + quote(print(plot)) + } else { + substitute( + expr = { + # Add facetting labels + # optional: grid.newpage() # nolint: commented_code. + # Prefixed with teal.modules.general as its usage will appear in "Show R code" + plot <- teal.modules.general::add_facet_labels( + plot, + xfacet_label = nulled_col_facet_name, + yfacet_label = nulled_row_facet_name + ) + grid::grid.newpage() + grid::grid.draw(plot) + }, + env = list(nulled_col_facet_name = nulled_col_facet_name, nulled_row_facet_name = nulled_row_facet_name) + ) + } + print_call + }), + expr_is_reactive = TRUE + ) - plot_r <- reactive({ - req(output_q()) - decorated_output_q_facets()[["plot"]] - }) + plot_r <- reactive(req(decorated_output_q_facets())[["plot"]]) pws <- teal.widgets::plot_with_settings_srv( id = "myplot", diff --git a/R/tm_g_distribution.R b/R/tm_g_distribution.R index 8dc670d03..099c2dcfd 100644 --- a/R/tm_g_distribution.R +++ b/R/tm_g_distribution.R @@ -22,17 +22,36 @@ #' and `max`. #' Defaults to `c(30L, 1L, 100L)`. #' -#' @templateVar ggnames "Histogram", "QQplot" -#' @template ggplot2_args_multi +#' @param ggplot2_args `r roxygen_ggplot2_args_param("Histogram", "QQplot")` +#' @param decorators `r roxygen_decorators_param("tm_g_distribution")` #' #' @inherit shared_params return #' #' @section Decorating `tm_outliers`: #' -#' This module generates the following objects, which can be modified in place using decorators: -#' - `plot` (`ggplot2`) -#' - `test_table` (`data.frame`) +#' This module generates the following objects, which can be modified in place using decorators:: +#' - `histogram_plot` (`ggplot2`) +#' - `qq_plot` (`data.frame`) #' - `summary_table` (`data.frame`) +#' - `test_table` (`data.frame`) +#' +#' Decorators can be applied to all outputs or only to specific objects using a +#' named list of `teal_transform_module` objects. +#' The `"default"` name is reserved for decorators that are applied to all outputs. +#' See code snippet below: +#' +#' ``` +#' tm_g_distribution( +#' ..., # arguments for module +#' decorators = list( +#' default = list(teal_transform_module(...)), # applied to all outputs +#' histogram_plot = list(teal_transform_module(...)), # applied only to `histogram_plot` output +#' qq_plot = list(teal_transform_module(...)) # applied only to `qq_plot` output +#' summary_table = list(teal_transform_module(...)) # applied only to `summary_table` output +#' test_table = list(teal_transform_module(...)) # applied only to `test_table` output +#' ) +#' ) +#' ``` #' #' For additional details and examples of decorators, refer to the vignette #' `vignette("decorate-modules-output", package = "teal")` or the [`teal_transform_module()`] documentation. @@ -184,7 +203,10 @@ tm_g_distribution <- function(label = "Distribution Module", checkmate::assert_multi_class(pre_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE) checkmate::assert_multi_class(post_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE) - checkmate::assert_list(decorators, "teal_transform_module", null.ok = TRUE) + available_decorators <- c("histogram_plot", "qq_plot", "test_table", "summary_table") + decorators <- normalize_decorators(decorators) + assert_decorators(decorators, null.ok = TRUE, names = available_decorators) + # End of assertions # Make UI args @@ -280,7 +302,10 @@ ui_distribution <- function(id, ...) { inline = TRUE ), checkboxInput(ns("add_dens"), label = "Overlay Density", value = TRUE), - ui_transform_teal_data(ns("d_dist"), transformators = args$decorators), + ui_decorate_teal_data( + ns("d_density"), + decorators = select_decorators(args$decorators, "histogram_plot") + ), collapsed = FALSE ) ), @@ -289,10 +314,21 @@ ui_distribution <- function(id, ...) { teal.widgets::panel_item( "QQ Plot", checkboxInput(ns("qq_line"), label = "Add diagonal line(s)", TRUE), - ui_transform_teal_data(ns("d_qq"), transformators = args$decorators), + ui_decorate_teal_data( + ns("d_qq"), + decorators = select_decorators(args$decorators, "qq_plot") + ), collapsed = FALSE ) ), + ui_decorate_teal_data( + ns("d_summary"), + decorators = select_decorators(args$decorators, "summary_table") + ), + ui_decorate_teal_data( + ns("d_test"), + decorators = select_decorators(args$decorators, "test_table") + ), conditionalPanel( condition = paste0("input['", ns("main_type"), "'] == 'Density'"), teal.widgets::panel_item( @@ -677,12 +713,12 @@ srv_distribution <- function(id, ) } - if (length(s_var) == 0 && length(g_var) == 0) { - qenv <- teal.code::eval_code( + qenv <- if (length(s_var) == 0 && length(g_var) == 0) { + teal.code::eval_code( qenv, substitute( expr = { - summary_table <- ANL %>% + summary_table_data <- ANL %>% dplyr::summarise( min = round(min(dist_var_name, na.rm = TRUE), roundn), median = round(stats::median(dist_var_name, na.rm = TRUE), roundn), @@ -699,12 +735,12 @@ srv_distribution <- function(id, ) ) } else { - qenv <- teal.code::eval_code( + teal.code::eval_code( qenv, substitute( expr = { strata_vars <- strata_vars_raw - summary_table <- ANL %>% + summary_table_data <- ANL %>% dplyr::group_by_at(dplyr::vars(dplyr::any_of(strata_vars))) %>% dplyr::summarise( min = round(min(dist_var_name, na.rm = TRUE), roundn), @@ -714,7 +750,6 @@ srv_distribution <- function(id, sd = round(stats::sd(dist_var_name, na.rm = TRUE), roundn), count = dplyr::n() ) - summary_table # used to display table when running show-r-code code }, env = list( dist_var_name = dist_var_name, @@ -724,6 +759,20 @@ srv_distribution <- function(id, ) ) } + if (iv_r()$is_valid()) { + within(qenv, { + summary_table <- DT::datatable( + summary_table_data, + options = list( + autoWidth = TRUE, + columnDefs = list(list(width = "200px", targets = "_all")) + ), + rownames = FALSE + ) + }) + } else { + within(qenv, summary_table <- NULL) + } }) # distplot qenv ---- @@ -913,7 +962,7 @@ srv_distribution <- function(id, teal.code::eval_code( qenv, substitute( - expr = plot <- plot_call, + expr = histogram_plot <- plot_call, env = list(plot_call = Reduce(function(x, y) call("+", x, y), c(plot_call, parsed_ggplot2_args))) ) ) @@ -1042,7 +1091,7 @@ srv_distribution <- function(id, teal.code::eval_code( qenv, substitute( - expr = plot <- plot_call, + expr = qq_plot <- plot_call, env = list(plot_call = Reduce(function(x, y) call("+", x, y), c(plot_call, parsed_ggplot2_args))) ) ) @@ -1191,7 +1240,7 @@ srv_distribution <- function(id, qenv, substitute( expr = { - test_table <- ANL %>% + test_table_data <- ANL %>% dplyr::select(dist_var) %>% with(., broom::glance(do.call(test, args))) %>% dplyr::mutate_if(is.numeric, round, 3) @@ -1204,7 +1253,7 @@ srv_distribution <- function(id, qenv, substitute( expr = { - test_table <- ANL %>% + test_table_data <- ANL %>% dplyr::select(dist_var, s_var, g_var) %>% dplyr::group_by_at(dplyr::vars(dplyr::any_of(groups))) %>% dplyr::do(tests = broom::glance(do.call(test, args))) %>% @@ -1215,9 +1264,6 @@ srv_distribution <- function(id, ) ) } - qenv %>% - # used to display table when running show-r-code code - teal.code::eval_code(quote(test_table)) } ) @@ -1227,32 +1273,39 @@ srv_distribution <- function(id, # wrapped in if since could lead into validate error - we do want to continue test_q_out <- try(test_q(), silent = TRUE) if (!inherits(test_q_out, c("try-error", "error"))) { - c(common_q(), test_q_out) + c( + common_q(), + within(test_q_out, { + test_table <- DT::datatable( + test_table_data, + options = list(scrollX = TRUE), + rownames = FALSE + ) + }) + ) } else { - common_q() + within(common_q(), test_table <- NULL) } }) output_dist_q <- reactive(c(output_common_q(), req(dist_q()))) output_qq_q <- reactive(c(output_common_q(), req(qq_q()))) - decorated_output_dist_q_no_print <- srv_transform_teal_data( - "d_dist", + decorated_output_dist_q <- srv_decorate_teal_data( + "d_density", data = output_dist_q, - transformators = decorators + decorators = select_decorators(decorators, "histogram_plot"), + expr = print(histogram_plot) ) - decorated_output_dist_q <- reactive(within(req(decorated_output_dist_q_no_print()), expr = print(plot))) - - decorated_output_qq_q_no_print <- srv_transform_teal_data( + decorated_output_qq_q <- srv_decorate_teal_data( "d_qq", data = output_qq_q, - transformators = decorators + decorators = select_decorators(decorators, "qq_plot"), + expr = print(qq_plot) ) - decorated_output_qq_q <- reactive(within(req(decorated_output_qq_q_no_print()), expr = print(plot))) - - decorated_output_q <- reactive({ + decorated_output_q_base <- reactive({ tab <- req(input$tabs) # tab is NULL upon app launch, hence will crash without this statement if (tab == "Histogram") { decorated_output_dist_q() @@ -1261,30 +1314,31 @@ srv_distribution <- function(id, } }) - dist_r <- reactive({ - req(output_dist_q()) # Ensure original errors are displayed - decorated_output_dist_q()[["plot"]] - }) - - qq_r <- reactive({ - req(output_qq_q()) # Ensure original errors are displayed - decorated_output_qq_q()[["plot"]] - }) + decorated_output_q_summary <- srv_decorate_teal_data( + "d_summary", + data = decorated_output_q_base, + decorators = select_decorators(decorators, "summary_table"), + expr = summary_table + ) - output$summary_table <- DT::renderDataTable( - expr = if (iv_r()$is_valid()) decorated_output_dist_q()[["summary_table"]] else NULL, - options = list( - autoWidth = TRUE, - columnDefs = list(list(width = "200px", targets = "_all")) - ), - rownames = FALSE + decorated_output_q <- srv_decorate_teal_data( + "d_test", + data = decorated_output_q_summary, + decorators = select_decorators(decorators, "test_table"), + expr = test_table ) + dist_r <- reactive(req(decorated_output_dist_q())[["histogram_plot"]]) + + qq_r <- reactive(req(decorated_output_qq_q())[["qq_plot"]]) + + output$summary_table <- DT::renderDataTable(expr = decorated_output_q()[["summary_table"]]) + tests_r <- reactive({ req(iv_r()$is_valid()) teal::validate_inputs(iv_r_dist()) req(test_q()) # Ensure original errors are displayed - decorated_output_dist_q()[["test_table"]] + decorated_output_q()[["test_table"]] }) pws1 <- teal.widgets::plot_with_settings_srv( @@ -1304,9 +1358,7 @@ srv_distribution <- function(id, ) output$t_stats <- DT::renderDataTable( - expr = tests_r(), - options = list(scrollX = TRUE), - rownames = FALSE + expr = tests_r() ) teal.widgets::verbatim_popup_srv( diff --git a/R/tm_g_response.R b/R/tm_g_response.R index 18f8d6d6d..c765de9ea 100644 --- a/R/tm_g_response.R +++ b/R/tm_g_response.R @@ -201,7 +201,8 @@ tm_g_response <- function(label = "Response Plot", checkmate::assert_multi_class(pre_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE) checkmate::assert_multi_class(post_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE) - checkmate::assert_list(decorators, "teal_transform_module", null.ok = TRUE) + decorators <- normalize_decorators(decorators) + assert_decorators(decorators, null.ok = TRUE, "plot") # End of assertions # Make UI args @@ -285,7 +286,7 @@ ui_g_response <- function(id, ...) { selected = ifelse(args$freq, "frequency", "density"), justified = TRUE ), - ui_transform_teal_data(ns("decorator"), transformators = args$decorators), + ui_decorate_teal_data(ns("decorator"), decorators = select_decorators(args$decorators, "plot")), teal.widgets::panel_group( teal.widgets::panel_item( title = "Plot settings", @@ -552,13 +553,14 @@ srv_g_response <- function(id, teal.code::eval_code(qenv, plot_call) }) - decorated_output_q <- srv_transform_teal_data(id = "decorator", data = output_q, transformators = decorators) + decorated_output_plot_q <- srv_decorate_teal_data( + id = "decorator", + data = output_q, + decorators = select_decorators(decorators, "plot"), + expr = print(plot) + ) - decorated_output_plot_q <- reactive(within(decorated_output_q(), print(plot))) - plot_r <- reactive({ - req(output_q()) # Ensure original errors are displayed - decorated_output_plot_q()[["plot"]] - }) + plot_r <- reactive(req(decorated_output_plot_q())[["plot"]]) # Insert the plot into a plot_with_settings module from teal.widgets pws <- teal.widgets::plot_with_settings_srv( diff --git a/R/tm_g_scatterplot.R b/R/tm_g_scatterplot.R index 3e3f69de4..f87adb13d 100644 --- a/R/tm_g_scatterplot.R +++ b/R/tm_g_scatterplot.R @@ -307,7 +307,10 @@ tm_g_scatterplot <- function(label = "Scatterplot", checkmate::assert_scalar(table_dec) checkmate::assert_class(ggplot2_args, "ggplot2_args") - checkmate::assert_list(decorators, "teal_transform_module", null.ok = TRUE) + + decorators <- normalize_decorators(decorators) + assert_decorators(decorators, null.ok = TRUE, "plot") + # End of assertions # Make UI args @@ -430,7 +433,7 @@ ui_g_scatterplot <- function(id, ...) { is_single_dataset = is_single_dataset_value ) }, - ui_transform_teal_data(ns("decorator"), transformators = args$decorators), + ui_decorate_teal_data(ns("decorator"), decorators = select_decorators(args$decorators, "plot")), teal.widgets::panel_group( teal.widgets::panel_item( title = "Plot settings", @@ -1005,12 +1008,14 @@ srv_g_scatterplot <- function(id, teal.code::eval_code(plot_q, plot_call) }) - decorated_output_q <- srv_transform_teal_data(id = "decorator", data = output_q, transformators = decorators) - decorated_output_plot_q <- reactive(within(decorated_output_q(), print(plot))) - plot_r <- reactive({ - req(output_q()) # Ensure original errors are displayed - decorated_output_plot_q()[["plot"]] - }) + decorated_output_plot_q <- srv_decorate_teal_data( + id = "decorator", + data = output_q, + decorators = select_decorators(decorators, "plot"), + expr = print(plot) + ) + + plot_r <- reactive(req(decorated_output_plot_q())[["plot"]]) # Insert the plot into a plot_with_settings module from teal.widgets pws <- teal.widgets::plot_with_settings_srv( diff --git a/R/tm_g_scatterplotmatrix.R b/R/tm_g_scatterplotmatrix.R index 0c2a563e1..64942a0f2 100644 --- a/R/tm_g_scatterplotmatrix.R +++ b/R/tm_g_scatterplotmatrix.R @@ -202,7 +202,9 @@ tm_g_scatterplotmatrix <- function(label = "Scatterplot Matrix", checkmate::assert_multi_class(pre_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE) checkmate::assert_multi_class(post_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE) - checkmate::assert_list(decorators, "teal_transform_module", null.ok = TRUE) + + decorators <- normalize_decorators(decorators) + assert_decorators(decorators, null.ok = TRUE, "plot") # End of assertions # Make UI args @@ -249,7 +251,7 @@ ui_g_scatterplotmatrix <- function(id, ...) { is_single_dataset = is_single_dataset_value ), tags$hr(), - ui_transform_teal_data(ns("decorator"), transformators = args$decorators), + ui_decorate_teal_data(ns("decorator"), decorators = select_decorators(args$decorators, "plot")), teal.widgets::panel_group( teal.widgets::panel_item( title = "Plot settings", @@ -444,12 +446,14 @@ srv_g_scatterplotmatrix <- function(id, qenv }) - decorated_output_q_no_print <- srv_transform_teal_data(id = "decorator", data = output_q, transformators = decorators) - decorated_output_q <- reactive(within(decorated_output_q_no_print(), print(plot))) - plot_r <- reactive({ - req(output_q()) # Ensure original errors are displayed - decorated_output_q()[["plot"]] - }) + decorated_output_q <- srv_decorate_teal_data( + id = "decorator", + data = output_q, + decorators = select_decorators(decorators, "plot"), + expr = print(plot) + ) + + plot_r <- reactive(req(decorated_output_q())[["plot"]]) # Insert the plot into a plot_with_settings module pws <- teal.widgets::plot_with_settings_srv( diff --git a/R/tm_missing_data.R b/R/tm_missing_data.R index 027ba182b..34f41d61c 100644 --- a/R/tm_missing_data.R +++ b/R/tm_missing_data.R @@ -10,21 +10,41 @@ #' @param parent_dataname (`character(1)`) Specifies the parent dataset name. Default is `ADSL` for `CDISC` data. #' If provided and exists, enables additional analysis "by subject". For non-`CDISC` data, this parameter can be #' ignored. +# nolint start: line_length. #' @param ggtheme (`character`) optional, specifies the default `ggplot2` theme for plots. Defaults to `classic`. +# nolint end: line_length. #' -#' @templateVar ggnames "Summary Obs", "Summary Patients", "Combinations Main", "Combinations Hist", "By Subject" -#' @template ggplot2_args_multi +#' @param ggplot2_args `r roxygen_ggplot2_args_param("Summary Obs", "Summary Patients", "Combinations Main", "Combinations Hist", "By Subject")` +#' @param decorators `r roxygen_decorators_param("tm_missing_data")` #' #' @inherit shared_params return #' #' @section Decorating `tm_missing_data`: #' #' This module generates the following objects, which can be modified in place using decorators: -#' - `summary_plot` (`ggplot2 plot grob`) -#' - `combination_plot` (`ggplot2 plot grob`) +#' - `summary_plot` (`grob` created with [ggplot2::ggplotGrob()]) +#' - `combination_plot` (`grob` created with [ggplot2::ggplotGrob()]) #' - `by_subject_plot` (`ggplot2`) #' - `table` ([DT::datatable()]) #' +#' Decorators can be applied to all outputs or only to specific objects using a +#' named list of `teal_transform_module` objects. +#' The `"default"` name is reserved for decorators that are applied to all outputs. +#' See code snippet below: +#' +#' ``` +#' tm_missing_data( +#' ..., # arguments for module +#' decorators = list( +#' default = list(teal_transform_module(...)), # applied to all outputs +#' summary_plot = list(teal_transform_module(...)), # applied only to `summary_plot` output +#' combination_plot = list(teal_transform_module(...)) # applied only to `combination_plot` output +#' by_subject_plot = list(teal_transform_module(...)) # applied only to `by_subject_plot` output +#' table = list(teal_transform_module(...)) # applied only to `table` output +#' ) +#' ) +#' ``` +#' #' For additional details and examples of decorators, refer to the vignette #' `vignette("decorate-modules-output", package = "teal")` or the [`teal_transform_module()`] documentation. #' @@ -134,15 +154,9 @@ tm_missing_data <- function(label = "Missing data", checkmate::assert_multi_class(pre_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE) checkmate::assert_multi_class(post_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE) - available_decorators <- c("summary_plot", "summary_plot", "combination_plot", "by_subject_plot", "summary_table") - if (checkmate::test_list(decorators, "teal_transform_module", null.ok = TRUE)) { - decorators <- if (checkmate::test_names(names(decorators), subset.of = c("default", available_decorators))) { - lapply(decorators, list) - } else { - list(default = decorators) - } - } - assert_decorators(decorators, null.ok = TRUE, names = c("default", available_decorators)) + available_decorators <- c("summary_plot", "combination_plot", "by_subject_plot", "summary_table") + decorators <- normalize_decorators(decorators) + assert_decorators(decorators, null.ok = TRUE, names = available_decorators) # End of assertions ans <- module( @@ -410,16 +424,16 @@ encoding_missing_data <- function(id, summary_per_patient = FALSE, ggtheme, data value = FALSE ) }, - ui_decorate_teal_data(ns("dec_summary_plot"), decorators = subset_decorators("summary_plot", decorators)) + ui_decorate_teal_data(ns("dec_summary_plot"), decorators = select_decorators(decorators, "summary_plot")) ), conditionalPanel( is_tab_active_js(ns("summary_type"), "Combinations"), uiOutput(ns("cutoff")), - ui_decorate_teal_data(ns("dec_combination_plot"), decorators = subset_decorators("combination_plot", decorators)) + ui_decorate_teal_data(ns("dec_combination_plot"), decorators = select_decorators(decorators, "combination_plot")) ), conditionalPanel( is_tab_active_js(ns("summary_type"), "Grouped by Subject"), - ui_decorate_teal_data(ns("dec_by_subject_plot"), decorators = subset_decorators("by_subject_plot", decorators)) + ui_decorate_teal_data(ns("dec_by_subject_plot"), decorators = select_decorators(decorators, "by_subject_plot")) ), conditionalPanel( is_tab_active_js(ns("summary_type"), "By Variable Levels"), @@ -432,7 +446,7 @@ encoding_missing_data <- function(id, summary_per_patient = FALSE, ggtheme, data selected = "counts", inline = TRUE ), - ui_decorate_teal_data(ns("dec_summary_table"), decorators = subset_decorators("summary_table", decorators)) + ui_decorate_teal_data(ns("dec_summary_table"), decorators = select_decorators(decorators, "summary_table")) ), teal.widgets::panel_item( title = "Plot settings", @@ -1250,7 +1264,7 @@ srv_missing_data <- function(id, decorated_summary_plot_q <- srv_decorate_teal_data( id = "dec_summary_plot", data = summary_plot_q, - decorators = subset_decorators("summary_plot", decorators), + decorators = select_decorators(decorators, "summary_plot"), expr = { grid::grid.newpage() grid::grid.draw(summary_plot) @@ -1260,7 +1274,7 @@ srv_missing_data <- function(id, decorated_combination_plot_q <- srv_decorate_teal_data( id = "dec_combination_plot", data = combination_plot_q, - decorators = subset_decorators("combination_plot", decorators), + decorators = select_decorators(decorators, "combination_plot"), expr = { grid::grid.newpage() grid::grid.draw(combination_plot) @@ -1270,14 +1284,14 @@ srv_missing_data <- function(id, decorated_summary_table_q <- srv_decorate_teal_data( id = "dec_summary_table", data = summary_table_q, - decorators = subset_decorators("summary_table", decorators), + decorators = select_decorators(decorators, "summary_table"), expr = table ) decorated_by_subject_plot_q <- srv_decorate_teal_data( id = "dec_by_subject_plot", data = by_subject_plot_q, - decorators = subset_decorators("by_subject_plot", decorators), + decorators = select_decorators(decorators, "by_subject_plot"), expr = print(by_subject_plot) ) diff --git a/R/tm_outliers.R b/R/tm_outliers.R index be3cc51f0..55ba7ad23 100644 --- a/R/tm_outliers.R +++ b/R/tm_outliers.R @@ -11,9 +11,8 @@ #' Specifies variable(s) to be analyzed for outliers. #' @param categorical_var (`data_extract_spec` or `list` of multiple `data_extract_spec`) optional, #' specifies the categorical variable(s) to split the selected outlier variables on. -#' -#' @templateVar ggnames "Boxplot","Density Plot","Cumulative Distribution Plot" -#' @template ggplot2_args_multi +#' @param decorators `r roxygen_decorators_param("tm_outliers")` +#' @param ggplot2_args `r roxygen_ggplot2_args_param("Boxplot", "Density Plot", "Cumulative Distribution Plot")` #' #' @inherit shared_params return #' @@ -22,7 +21,26 @@ #' This module generates the following objects, which can be modified in place using decorators: #' - `box_plot` (`ggplot2`) #' - `density_plot` (`ggplot2`) -#' - `cum_dist_plot` (`ggplot2`) +#' - `cumulative_plot` (`ggplot2`) +#' - `table` ([DT::datatable()]) +#' +#' Decorators can be applied to all outputs or only to specific objects using a +#' named list of `teal_transform_module` objects. +#' The `"default"` name is reserved for decorators that are applied to all outputs. +#' See code snippet below: +#' +#' ``` +#' tm_outliers( +#' ..., # arguments for module +#' decorators = list( +#' default = list(teal_transform_module(...)), # applied to all outputs +#' box_plot = list(teal_transform_module(...)), # applied only to `box_plot` output +#' density_plot = list(teal_transform_module(...)) # applied only to `density_plot` output +#' cumulative_plot = list(teal_transform_module(...)) # applied only to `cumulative_plot` output +#' table = list(teal_transform_module(...)) # applied only to `table` output +#' ) +#' ) +#' ``` #' #' For additional details and examples of decorators, refer to the vignette #' `vignette("decorate-modules-output", package = "teal")` or the [`teal_transform_module()`] documentation. @@ -178,8 +196,9 @@ tm_outliers <- function(label = "Outliers Module", checkmate::assert_multi_class(pre_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE) checkmate::assert_multi_class(post_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE) - checkmate::assert_list(decorators, "teal_transform_module", null.ok = TRUE) - + available_decorators <- c("box_plot", "density_plot", "cumulative_plot", "table") + decorators <- normalize_decorators(decorators) + assert_decorators(decorators, null.ok = TRUE, names = available_decorators) # End of assertions # Make UI args @@ -322,7 +341,28 @@ ui_outliers <- function(id, ...) { uiOutput(ns("ui_outlier_help")) ) ), - ui_transform_teal_data(ns("decorate"), transformators = args$decorators), + conditionalPanel( + condition = paste0("input['", ns("tabs"), "'] == 'Boxplot'"), + ui_decorate_teal_data( + ns("d_box_plot"), + decorators = select_decorators(args$decorators, "box_plot") + ) + ), + conditionalPanel( + condition = paste0("input['", ns("tabs"), "'] == 'Density Plot'"), + ui_decorate_teal_data( + ns("d_density_plot"), + decorators = select_decorators(args$decorators, "density_plot") + ) + ), + conditionalPanel( + condition = paste0("input['", ns("tabs"), "'] == 'Cumulative Distribution Plot'"), + ui_decorate_teal_data( + ns("d_cumulative_plot"), + decorators = select_decorators(args$decorators, "cumulative_plot") + ) + ), + ui_decorate_teal_data(ns("d_table"), decorators = select_decorators(args$decorators, "table")), teal.widgets::panel_item( title = "Plot settings", selectInput( @@ -585,7 +625,7 @@ srv_outliers <- function(id, data, reporter, filter_panel_api, outlier_var, ) ) - if (length(categorical_var) > 0) { + qenv <- if (length(categorical_var) > 0) { qenv <- teal.code::eval_code( qenv, substitute( @@ -641,7 +681,7 @@ srv_outliers <- function(id, data, reporter, filter_panel_api, outlier_var, ) } - qenv <- teal.code::eval_code( + teal.code::eval_code( qenv, substitute( expr = { @@ -669,7 +709,6 @@ srv_outliers <- function(id, data, reporter, filter_panel_api, outlier_var, tidyr::pivot_longer(-categorical_var_name) %>% tidyr::pivot_wider(names_from = categorical_var, values_from = value) %>% tibble::column_to_rownames("name") - summary_table }, env = list( categorical_var = categorical_var, @@ -677,8 +716,22 @@ srv_outliers <- function(id, data, reporter, filter_panel_api, outlier_var, ) ) ) + } else { + within(qenv, summary_table <- data.frame()) } + # Datatable is generated in qenv to allow for output decoration + qenv <- within(qenv, { + table <- DT::datatable( + summary_table, + options = list( + dom = "t", + autoWidth = TRUE, + columnDefs = list(list(width = "200px", targets = "_all")) + ) + ) + }) + if (length(categorical_var) > 0 && nrow(qenv[["ANL_OUTLIER"]]) > 0) { shinyjs::show("order_by_outlier") } else { @@ -688,26 +741,8 @@ srv_outliers <- function(id, data, reporter, filter_panel_api, outlier_var, qenv }) - output$summary_table <- DT::renderDataTable( - expr = { - if (iv_r()$is_valid()) { - categorical_var <- as.vector(merged$anl_input_r()$columns_source$categorical_var) - if (!is.null(categorical_var)) { - DT::datatable( - common_code_q()[["summary_table"]], - options = list( - dom = "t", - autoWidth = TRUE, - columnDefs = list(list(width = "200px", targets = "_all")) - ) - ) - } - } - } - ) - # boxplot/violinplot # nolint commented_code - boxplot_q <- reactive({ + box_plot_q <- reactive({ req(common_code_q()) ANL <- common_code_q()[["ANL"]] ANL_OUTLIER <- common_code_q()[["ANL_OUTLIER"]] @@ -947,7 +982,7 @@ srv_outliers <- function(id, data, reporter, filter_panel_api, outlier_var, teal.code::eval_code( qenv, substitute( - expr = cum_dist_plot <- plot_call + + expr = cumulative_plot <- plot_call + geom_point(data = outlier_points, aes(x = outlier_var_name, y = y, color = is_outlier_selected)) + scale_color_manual(values = c("TRUE" = "red", "FALSE" = "black")) + labs + ggthemes + themes, @@ -962,37 +997,59 @@ srv_outliers <- function(id, data, reporter, filter_panel_api, outlier_var, ) }) - final_q <- reactive({ - req(input$tabs) - tab_type <- input$tabs - result_q <- if (tab_type == "Boxplot") { - boxplot_q() - } else if (tab_type == "Density Plot") { - density_plot_q() - } else if (tab_type == "Cumulative Distribution Plot") { - cumulative_plot_q() - } - # used to display table when running show-r-code code - # added after the plots so that a change in selected columns doesn't affect - # brush selection. - teal.code::eval_code( - result_q, - substitute( - expr = { - columns_index <- union( - setdiff(names(ANL_OUTLIER), c("is_outlier_selected", "order")), - table_columns - ) - ANL_OUTLIER_EXTENDED[ANL_OUTLIER_EXTENDED$is_outlier_selected, columns_index] - }, - env = list( - table_columns = input$table_ui_columns - ) - ) + current_tab_r <- reactive({ + switch(req(input$tabs), + "Boxplot" = "box_plot", + "Density Plot" = "density_plot", + "Cumulative Distribution Plot" = "cumulative_plot" ) }) - decorated_final_q <- srv_transform_teal_data("decorate", data = final_q, transformators = decorators) + decorated_q <- mapply( + function(obj_name, q) { + srv_decorate_teal_data( + id = sprintf("d_%s", obj_name), + data = q, + decorators = select_decorators(decorators, obj_name), + expr = reactive({ + substitute( + expr = { + columns_index <- union( + setdiff(names(ANL_OUTLIER), c("is_outlier_selected", "order")), + table_columns + ) + ANL_OUTLIER_EXTENDED[ANL_OUTLIER_EXTENDED$is_outlier_selected, columns_index] + print(.plot) + }, + env = list(table_columns = input$table_ui_columns, .plot = as.name(obj_name)) + ) + }), + expr_is_reactive = TRUE + ) + }, + rlang::set_names(c("box_plot", "density_plot", "cumulative_plot")), + c(box_plot_q, density_plot_q, cumulative_plot_q) + ) + + decorated_final_q_no_table <- reactive(decorated_q[[req(current_tab_r())]]()) + + decorated_final_q <- srv_decorate_teal_data( + "d_table", + data = decorated_final_q_no_table, + decorators = select_decorators(decorators, "table"), + expr = table + ) + + output$summary_table <- DT::renderDataTable( + expr = { + if (iv_r()$is_valid()) { + categorical_var <- as.vector(merged$anl_input_r()$columns_source$categorical_var) + if (!is.null(categorical_var)) { + decorated_final_q()[["table"]] + } + } + } + ) # slider text output$ui_outlier_help <- renderUI({ @@ -1042,25 +1099,22 @@ srv_outliers <- function(id, data, reporter, filter_panel_api, outlier_var, } }) - boxplot_r <- reactive({ + box_plot_r <- reactive({ teal::validate_inputs(iv_r()) - req(boxplot_q()) - decorated_final_q()[["box_plot"]] + req(decorated_q$box_plot())[["box_plot"]] }) density_plot_r <- reactive({ teal::validate_inputs(iv_r()) - req(density_plot_q()) - decorated_final_q()[["density_plot"]] + req(decorated_q$density_plot())[["density_plot"]] }) cumulative_plot_r <- reactive({ teal::validate_inputs(iv_r()) - req(cumulative_plot_q()) - decorated_final_q()[["cum_dist_plot"]] + req(decorated_q$cumulative_plot())[["cumulative_plot"]] }) box_pws <- teal.widgets::plot_with_settings_srv( id = "box_plot", - plot_r = boxplot_r, + plot_r = box_plot_r, height = plot_height, width = plot_width, brushing = TRUE @@ -1106,16 +1160,20 @@ srv_outliers <- function(id, data, reporter, filter_panel_api, outlier_var, ANL_OUTLIER_EXTENDED <- common_code_q()[["ANL_OUTLIER_EXTENDED"]] ANL <- common_code_q()[["ANL"]] - plot_brush <- if (tab == "Boxplot") { - boxplot_r() - box_pws$brush() - } else if (tab == "Density Plot") { - density_plot_r() - density_pws$brush() - } else if (tab == "Cumulative Distribution Plot") { - cumulative_plot_r() - cum_density_pws$brush() - } + plot_brush <- switch(current_tab_r(), + box_plot = { + box_plot_r() + box_pws$brush() + }, + density_plot = { + density_plot_r() + density_pws$brush() + }, + cumulative_plot = { + cumulative_plot_r() + cum_density_pws$brush() + } + ) # removing unused column ASAP ANL_OUTLIER$order <- ANL$order <- NULL diff --git a/R/tm_t_crosstable.R b/R/tm_t_crosstable.R index 549fde366..3043181a1 100644 --- a/R/tm_t_crosstable.R +++ b/R/tm_t_crosstable.R @@ -167,7 +167,9 @@ tm_t_crosstable <- function(label = "Cross Table", checkmate::assert_multi_class(pre_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE) checkmate::assert_multi_class(post_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE) checkmate::assert_class(basic_table_args, classes = "basic_table_args") - checkmate::assert_list(decorators, "teal_transform_module", null.ok = TRUE) + + decorators <- normalize_decorators(decorators) + assert_decorators(decorators, null.ok = TRUE, "plot") # End of assertions # Make UI args @@ -234,7 +236,7 @@ ui_t_crosstable <- function(id, x, y, show_percentage, show_total, pre_output, p checkboxInput(ns("show_total"), "Show total column", value = show_total) ) ), - ui_transform_teal_data(ns("decorate"), transformators = args$decorators) + ui_decorate_teal_data(ns("decorator"), decorators = select_decorators(args$decorators, "plot")) ), forms = tagList( teal.widgets::verbatim_popup_ui(ns("rcode"), "Show R code") @@ -407,15 +409,18 @@ srv_t_crosstable <- function(id, data, reporter, filter_panel_api, label, x, y, ) }) - decorated_output_q_no_print <- srv_transform_teal_data("decorate", data = output_q, transformators = decorators) - decorated_output_q <- reactive(within(decorated_output_q_no_print(), expr = table)) + decorated_output_q <- srv_decorate_teal_data( + id = "decorator", + data = output_q, + decorators = select_decorators(decorators, "plot"), + expr = table + ) - output$title <- renderText(output_q()[["title"]]) + output$title <- renderText(req(decorated_output_q())[["title"]]) table_r <- reactive({ req(iv_r()$is_valid()) - req(output_q()) - decorated_output_q()[["table"]] + req(decorated_output_q())[["table"]] }) teal.widgets::table_with_settings_srv( diff --git a/R/utils.R b/R/utils.R index 750911a6a..556a977d5 100644 --- a/R/utils.R +++ b/R/utils.R @@ -25,9 +25,6 @@ #' with text placed before the output to put the output into context. For example a title. #' @param post_output (`shiny.tag`) optional, text or UI element to be displayed after the module's output, #' adding context or further instructions. Elements like `shiny::helpText()` are useful. -#' @param decorators `r lifecycle::badge("experimental")` (`list` of `teal_transform_module` or `NULL`) optional, -#' if not `NULL`, decorator for tables or plots included in the module. -#' #' @param alpha (`integer(1)` or `integer(3)`) optional, specifies point opacity. #' - When the length of `alpha` is one: the plot points will have a fixed opacity. #' - When the length of `alpha` is three: the plot points opacity are dynamically adjusted based on @@ -286,6 +283,8 @@ assert_single_selection <- function(x, #' @param expr (`expression` or `reactive`) to evaluate on the output of the decoration. #' When an expression it must be inline code. See [within()] #' Default is `NULL` which won't evaluate any appending code. +#' @param expr_is_reactive (`logical(1)`) whether `expr` is a reactive expression +#' that skips defusing the argument. #' @details #' `srv_decorate_teal_data` is a wrapper around `srv_transform_teal_data` that #' allows to decorate the data with additional expressions. @@ -293,12 +292,13 @@ assert_single_selection <- function(x, #' first. #' #' @keywords internal -srv_decorate_teal_data <- function(id, data, decorators, expr) { +srv_decorate_teal_data <- function(id, data, decorators, expr, expr_is_reactive = FALSE) { assert_reactive(data) checkmate::assert_list(decorators, "teal_transform_module") + checkmate::assert_flag(expr_is_reactive) missing_expr <- missing(expr) - if (!missing_expr) { + if (!missing_expr && !expr_is_reactive) { expr <- rlang::enexpr(expr) } @@ -310,6 +310,8 @@ srv_decorate_teal_data <- function(id, data, decorators, expr) { req(data(), decorated_output()) if (missing_expr) { decorated_output() + } else if (expr_is_reactive) { + eval_code(decorated_output(), expr()) } else { eval_code(decorated_output(), expr) } @@ -327,7 +329,7 @@ ui_decorate_teal_data <- function(id, decorators, ...) { #' Internal function to check if decorators is a valid object #' @noRd -check_decorators <- function(x, names = NULL, null.ok = FALSE) { +check_decorators <- function(x, names = NULL, null.ok = FALSE) { # nolint: object_name. checkmate::qassert(null.ok, "B1") check_message <- checkmate::check_list( @@ -384,8 +386,25 @@ assert_decorators <- checkmate::makeAssertionFunction(check_decorators) #' @return A flat list with all decorators to include. #' It can be an empty list if none of the scope exists in `decorators` argument. #' @keywords internal -subset_decorators <- function(scope, decorators) { - checkmate::assert_character(scope) +select_decorators <- function(decorators, scope) { + checkmate::assert_character(scope, null.ok = TRUE) scope <- intersect(union("default", scope), names(decorators)) c(list(), unlist(decorators[scope], recursive = FALSE)) } + +#' Convert flat list of `teal_transform_module` to named lists +#' +#' @param decorators (list of `teal_transformodules`) to normalize. +#' @return A named list of lists with `teal_transform_module` objects. +#' @keywords internal +normalize_decorators <- function(decorators) { + if (checkmate::test_list(decorators, "teal_transform_module", null.ok = TRUE)) { + if (checkmate::test_names(names(decorators))) { + lapply(decorators, list) + } else { + list(default = decorators) + } + } else { + decorators + } +} diff --git a/man-roxygen/ggplot2_args_multi.R b/man-roxygen/ggplot2_args_multi.R deleted file mode 100644 index dc0497942..000000000 --- a/man-roxygen/ggplot2_args_multi.R +++ /dev/null @@ -1,7 +0,0 @@ -#' @param ggplot2_args (`ggplot2_args`) optional, object created by [`teal.widgets::ggplot2_args()`] -#' with settings for all the plots or named list of `ggplot2_args` objects for plot-specific settings. -#' The argument is merged with options variable `teal.ggplot2_args` and default module setup. -#' -#' List names should match the following: `c("default", <%=ggnames%>)`. -#' -#' For more details see the vignette: `vignette("custom-ggplot2-arguments", package = "teal.widgets")`. diff --git a/man/normalize_decorators.Rd b/man/normalize_decorators.Rd new file mode 100644 index 000000000..a58207f16 --- /dev/null +++ b/man/normalize_decorators.Rd @@ -0,0 +1,18 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/utils.R +\name{normalize_decorators} +\alias{normalize_decorators} +\title{Convert flat list of \code{teal_transform_module} to named lists} +\usage{ +normalize_decorators(decorators) +} +\arguments{ +\item{decorators}{(list of \code{teal_transformodules}) to normalize.} +} +\value{ +A named list of lists with \code{teal_transform_module} objects. +} +\description{ +Convert flat list of \code{teal_transform_module} to named lists +} +\keyword{internal} diff --git a/man/subset_decorators.Rd b/man/select_decorators.Rd similarity index 86% rename from man/subset_decorators.Rd rename to man/select_decorators.Rd index 9b229dffe..2c7403dca 100644 --- a/man/subset_decorators.Rd +++ b/man/select_decorators.Rd @@ -1,15 +1,15 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/utils.R -\name{subset_decorators} -\alias{subset_decorators} +\name{select_decorators} +\alias{select_decorators} \title{Subset decorators based on the scope} \usage{ -subset_decorators(scope, decorators) +select_decorators(decorators, scope) } \arguments{ -\item{scope}{(\code{character}) a character vector of decorator names to include.} - \item{decorators}{(named \code{list}) of list decorators to subset.} + +\item{scope}{(\code{character}) a character vector of decorator names to include.} } \value{ A flat list with all decorators to include. diff --git a/man/shared_params.Rd b/man/shared_params.Rd index 1cf943565..1ea6b7094 100644 --- a/man/shared_params.Rd +++ b/man/shared_params.Rd @@ -34,9 +34,6 @@ with text placed before the output to put the output into context. For example a \item{post_output}{(\code{shiny.tag}) optional, text or UI element to be displayed after the module's output, adding context or further instructions. Elements like \code{shiny::helpText()} are useful.} -\item{decorators}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} (\code{list} of \code{teal_transform_module} or \code{NULL}) optional, -if not \code{NULL}, decorator for tables or plots included in the module.} - \item{alpha}{(\code{integer(1)} or \code{integer(3)}) optional, specifies point opacity. \itemize{ \item When the length of \code{alpha} is one: the plot points will have a fixed opacity. diff --git a/man/srv_decorate_teal_data.Rd b/man/srv_decorate_teal_data.Rd index 6d6845aca..18201124e 100644 --- a/man/srv_decorate_teal_data.Rd +++ b/man/srv_decorate_teal_data.Rd @@ -5,7 +5,7 @@ \alias{ui_decorate_teal_data} \title{Wrappers around \code{srv_transform_teal_data} that allows to decorate the data} \usage{ -srv_decorate_teal_data(id, data, decorators, expr) +srv_decorate_teal_data(id, data, decorators, expr, expr_is_reactive = FALSE) ui_decorate_teal_data(id, decorators, ...) } @@ -17,6 +17,9 @@ ui_decorate_teal_data(id, decorators, ...) \item{expr}{(\code{expression} or \code{reactive}) to evaluate on the output of the decoration. When an expression it must be inline code. See \code{\link[=within]{within()}} Default is \code{NULL} which won't evaluate any appending code.} + +\item{expr_is_reactive}{(\code{logical(1)}) whether \code{expr} is a reactive expression +that skips defusing the argument.} } \description{ Wrappers around \code{srv_transform_teal_data} that allows to decorate the data diff --git a/man/tm_a_pca.Rd b/man/tm_a_pca.Rd index 5ed58485a..54de83bdb 100644 --- a/man/tm_a_pca.Rd +++ b/man/tm_a_pca.Rd @@ -35,9 +35,7 @@ specifying columns used to compute PCA.} \item{ggtheme}{(\code{character}) optional, \code{ggplot2} theme to be used by default. Defaults to \code{"gray"}.} -\item{ggplot2_args}{(\code{ggplot2_args}) optional, object created by \code{\link[teal.widgets:ggplot2_args]{teal.widgets::ggplot2_args()}} -with settings for all the plots or named list of \code{ggplot2_args} objects for plot-specific settings. -The argument is merged with options variable \code{teal.ggplot2_args} and default module setup. +\item{ggplot2_args}{(\code{ggplot2_args}) optional, object created by \code{\link[teal.widgets:ggplot2_args]{teal.widgets::ggplot2_args()}} with settings for all the plots or named list of \code{ggplot2_args} objects for plot-specific settings. The argument is merged with options variable \code{teal.ggplot2_args} and default module setup. List names should match the following: \code{c("default", "Elbow plot", "Circle plot", "Biplot", "Eigenvector plot")}. @@ -74,8 +72,11 @@ with text placed before the output to put the output into context. For example a \item{post_output}{(\code{shiny.tag}) optional, text or UI element to be displayed after the module's output, adding context or further instructions. Elements like \code{shiny::helpText()} are useful.} -\item{decorators}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} (\code{list} of \code{teal_transform_module} or \code{NULL}) optional, -if not \code{NULL}, decorator for tables or plots included in the module.} +\item{decorators}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} (\code{list} of \code{teal_transform_module}, named \code{list} of \code{teal_transform_module} or \code{NULL}) optional, if not \code{NULL}, decorator for tables or plots included in the module. When a named list of \code{teal_transform_module}, the decorators are applied to the respective output objects. + +Otherwise, the decorators are applied to all objects, which is equivalent as using the name \code{default}. + +See section "Decorating \code{tm_a_pca}" below for more details.} } \value{ Object of class \code{teal_module} to be used in \code{teal} applications. @@ -91,9 +92,29 @@ font size, through UI inputs. This module generates the following objects, which can be modified in place using decorators: \itemize{ -\item \code{plot} (\code{ggplot2}) +\item \code{elbow_plot} (\code{ggplot2}) +\item \code{circle_plot} (\code{ggplot2}) +\item \code{biplot} (\code{ggplot2}) +\item \code{eigenvector_plot} (\code{ggplot2}) } +Decorators can be applied to all outputs or only to specific objects using a +named list of \code{teal_transform_module} objects. +The \code{"default"} name is reserved for decorators that are applied to all outputs. +See code snippet below: + +\if{html}{\out{
}}\preformatted{tm_a_pca( + ..., # arguments for module + decorators = list( + default = list(teal_transform_module(...)), # applied to all outputs + elbow_plot = list(teal_transform_module(...)), # applied only to `elbow_plot` output + circle_plot = list(teal_transform_module(...)) # applied only to `circle_plot` output + biplot = list(teal_transform_module(...)) # applied only to `biplot` output + eigenvector_plot = list(teal_transform_module(...)) # applied only to `eigenvector_plot` output + ) +) +}\if{html}{\out{
}} + For additional details and examples of decorators, refer to the vignette \code{vignette("decorate-modules-output", package = "teal")} or the \code{\link[=teal_transform_module]{teal_transform_module()}} documentation. } @@ -167,13 +188,13 @@ if (interactive()) { \describe{ \item{example-1}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAokrcQAxLqkQ11XfxQpFC6cAAesKgiSoHBBsZc1AD6sVA2MUEhRroA7rSkABYq7Km4uiBKurqMcACOgrQ17L6ipMTURIyKEFWOAMoAgow1raLxuv1DI6SiSgC+3UpoqOMq+eyVAZm6ALxbwbibfEIiY3vHwmIbPVW6pDBJUEmoBGmbt7oKYAAKAMIDX0ONw+sV2+ye4VIzA0SVEqDgBGuHxBmWg8DBX0mwzEM0B72RojgIg0YMJxNIsPhiPxyN0BAKRFoBDEYK0LFoUHoIiS9MZzNESNpyNSYNSwGAmMG2NGXwAurKytSwABZQSMfgyQGfMADUSiKDCUhazGMehQCDfIioY1gLBoOBfbpC25yIHOqpkhHkfhgpWq9WavDa3X6w2Ot3umCG2hRPR7BwuGkuiO0ky0ajkRhggByjgAMnmk06XZtut1aCZdOwVJn1JodDZbBUbqIihBWAN0OxlgASBplXuExg6LrzJRgOayoA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } \item{example-2}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAokrcQAxLoDCAEQCSAMreuvxQpFC6cAAesKgiSmERBsZc1AD6SVA2ieGRRroA7rSkABYq7Fm4uiBKurqMcACOgrSN7BBipMTURIyKEPUAgr6BADIpDSPjSgC+AwBWRCrpANZwrKKVebYF-HAmUMKk6QT8tKIE6Usr65vA0PBbWXIAuu5oqJMqJex1oXldABeAERXD-PhCESiYG6SHCMR-Qb1XSkGDpKDpVAEbL-FG6BRgAAK3iGhPByPxSVhWXSMVIzA06VEqDgBCR+KpeUeehBhOmY3JeM5ojgIg0sNF4pOLLZHM5+IIpWWBDEsK0LFoUHoIlOytoqq2woV9SyNLywGA-NGgrAr1e1XZhIAQgBZLAAaSwAEZyQSwEMAOKuPD+5wAeUCvgAmoSBiaUXIKQn6lK2eR+LCnWA3Z6fX7+cG48mUzBjrR4rz7E5XJTOUnjSiTLRqORGLCAHKOMaCuv1eOJ-4DAa0Ey6dgqNvqTQ6Gy2WrI0TlCCsIbodifAAkrWqW9FjB0-TmSjAs1eQA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } } } diff --git a/man/tm_a_regression.Rd b/man/tm_a_regression.Rd index 29399feae..9d61c4805 100644 --- a/man/tm_a_regression.Rd +++ b/man/tm_a_regression.Rd @@ -54,11 +54,9 @@ vector of \code{value}, \code{min}, and \code{max}. \item{ggtheme}{(\code{character}) optional, \code{ggplot2} theme to be used by default. Defaults to \code{"gray"}.} -\item{ggplot2_args}{(\code{ggplot2_args}) optional, object created by \code{\link[teal.widgets:ggplot2_args]{teal.widgets::ggplot2_args()}} -with settings for all the plots or named list of \code{ggplot2_args} objects for plot-specific settings. -The argument is merged with options variable \code{teal.ggplot2_args} and default module setup. +\item{ggplot2_args}{(\code{ggplot2_args}) optional, object created by \code{\link[teal.widgets:ggplot2_args]{teal.widgets::ggplot2_args()}} with settings for all the plots or named list of \code{ggplot2_args} objects for plot-specific settings. The argument is merged with options variable \code{teal.ggplot2_args} and default module setup. -List names should match the following: \verb{c("default", "Response vs Regressor", "Residuals vs Fitted", "Scale-Location", "Cook's distance", "Residuals vs Leverage"", "Cook's dist vs Leverage")}. +List names should match the following: \code{c("default", "Response vs Regressor", "Residuals vs Fitted", "Scale-Location", "Cook's distance", "Residuals vs Leverage", "Cook's dist vs Leverage")}. For more details see the vignette: \code{vignette("custom-ggplot2-arguments", package = "teal.widgets")}.} @@ -98,8 +96,11 @@ It takes the form of \code{c(value, min, max)} and it is passed to the \code{val argument in \code{teal.widgets::optionalSliderInputValMinMax}. }} -\item{decorators}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} (\code{list} of \code{teal_transform_module} or \code{NULL}) optional, -if not \code{NULL}, decorator for tables or plots included in the module.} +\item{decorators}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} (\code{list} of \code{teal_transform_module}, named \code{list} of \code{teal_transform_module} or \code{NULL}) optional, if not \code{NULL}, decorator for tables or plots included in the module. When a named list of \code{teal_transform_module}, the decorators are applied to the respective output objects. + +Otherwise, the decorators are applied to all objects, which is equivalent as using the name \code{default}. + +See section "Decorating \code{tm_a_regression}" below for more details.} } \value{ Object of class \code{teal_module} to be used in \code{teal} applications. @@ -212,13 +213,13 @@ if (interactive()) { \describe{ \item{example-1}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAokrcQAxLqkQ11XfxQpFC6cAAesKgiSoHBBsZc1AD6sVA2MUEhRroA7rSkABYq7Km4uiBKurqMcACOgrQ17L6ipMTURIyKEFUAwgDyAEzxugODSgC+3UpoqCMq+eyVAZm6ALwrwbjLfEIiouu6u8JiSz1VuqQwSVBJNRI1oqJWEGcXF9RQ9HD+GwpgWDgDzEzxI-2253ej1QJFEeg2qSS4VIzA0SVEqDgBDe7wuqWg8EO-zG4OWuN0cJEGkOlKxpHRmOxZPJuk+31+un+AGUfnTdFoWLQviJEKTISyCAUiLQCGIiWBBKhggBrOBilkXWkaOD8eWKlVqvDM8kwYSaKLw3QAMQAggAZLnOCEaqomWhhHWHBwuY0XbrkuTO3H3R6iTqHRHI1H0jFYnHk-GwS3Eobqlla0g03lo2NM8Xktk-eU8qmZgWMIX0faio353GS6Wyg4bcuVkRJBsy06pYDAFPjMAAXUHZSZhBIBHBnLAdhqQXgZH+ckDvveGc9f3HFjTGtN1HNIi9Tidq4ubo9uo2todrjrVX9uIf9+W3W6tBMunYKnI0e0cBstgVOcohFBArA2ug7CzAAJA0ZQwXCjA6F0kxKGAEyDkAA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } \item{example-2}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAokqUBiXQGEAIgEkAZS9dfihSKF04AA9YVBElUPCDYy5qAH1EqBsEsIijXQB3WlIACxV2TNxdECVdXUY4AEdBWgb2CDFSYmoiRkUIOoBBHwCAGWT64bGlAF9+gCsiFTSAazhWUQrc23z+OBMoYVI0gn5aUQI0xeW1jeBoeE3MuQBdN2h0CZVi9lqQ3N0AF5-uFcH8+EIRKIgboIcIxL8BnVdKQYGkoGkGhIGqJRFYIIjkcjqFB6HBqDCFGAsHBsWI8SQqWCkUScagSKI9MDMmloqRmBo0qJUHACISicjMg8uboqVNRky-hLdJyRBoYarRcdhaLxcq6iSyRTgVSAuStbotCxaKSRIhFSz9QQSksCGJKWAAEIAWSwAGksABGB365GajRwfgen3+oMh0Owo60OIygBig1GAWczITploUUjMIcLiVEv6yrkOYlWJxol6MJ5fIF2pFYtLRKlsBlcpGCrw7bD5vVwPDLd1A6JhvJHrNatIluttrE9v7juVztd7uBVsYNvoIhOLtobqeuWAwB70zALxeVTbYEGAHFXHhZWAswANJlvrCDLwvuRKwnQc50LE0H2feNQxgJMUyLJxs2AuoTHzMDdHTTNXDXZFyzLUtcP6fpaBMXR2BUchm20OAbFsGokVEMoIFYQZ0HYNBUAAEhaKp2I4zlGB0PpZiUMAZheIA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } } } diff --git a/man/tm_data_table.Rd b/man/tm_data_table.Rd index af43a7d14..c310c2b62 100644 --- a/man/tm_data_table.Rd +++ b/man/tm_data_table.Rd @@ -47,9 +47,6 @@ with text placed before the output to put the output into context. For example a \item{post_output}{(\code{shiny.tag}) optional, text or UI element to be displayed after the module's output, adding context or further instructions. Elements like \code{shiny::helpText()} are useful.} - -\item{decorators}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} (\code{list} of \code{teal_transform_module} or \code{NULL}) optional, -if not \code{NULL}, decorator for tables or plots included in the module.} } \value{ Object of class \code{teal_module} to be used in \code{teal} applications. @@ -126,13 +123,13 @@ if (interactive()) { \describe{ \item{example-1}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAokqUBiXVIhrqu-lCkULpwAB6wqCJKAUEGxlzUAPoxUDbRgcFGugDutKQAFirsKbi6IEq6uoxwAI6CtNXsPqKkxNREjIoQlQ20onG6vaJKAL5dSmioAyp57BX+GboAvAtBuPN8QiL9K5vCYnPdlbqkMMkZiUH0IofHx1ostFDXYomicCIacPzLunQttzuxyGvwIczAAGU4KhuBgADIUCQFBR4XQoqEwngAdVo-GRqJRAAU4EEeAiIEj8ijSkSSbCcXiqQTIag4ARaGIUV0gbo5Osjnc8YkWBIdn8+qR2AQ0JoSL8UQBJLAKiH2Z4iXQAYRlVggXPmlW5vKUXVoJl07BU5GYlh0Nls5SOokKEFYAEF0OxJgASeqlH3vRg6TqjJRgEYAXSAA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } \item{example-2}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAokqUBiXQGEAIgEkAZS9dfihSKF04AA9YVBElUPCDYy5qAH1EqBsEsIijXQB3WlIACxV2TNxdECVdXUY4AEdBWgb2CDFSYmoiRkUIOoBBHwCAGWT64bGlAF9+gCsiFTSAazhWUQrc23z+OBMoYVI0gn5aUQI0xeW1jeBoeE3MuQBdN2h0CZVi9lqQ3N0AF5-uFcH8+EIRKIgboIcIxL8BnVdKQYBlcmlwvQRIjkcitCxaFBsWI0qI4CINHB+DC6KJSOwpuNgQRfmAAnZHD4AJp+HwKPC6AWOAKOABCACk+QKqgLRZLpYK5X47M5FbKwIMAOKuJXs5wADQFcjkYKReP4xxYEmhwLpDIIaE0JBhAqZ9mJIm8TqsEGNfzq-UDSn6tBMunYKnIzEsOhsthqSNEZQgrEG6HYaFQABIWlUs9nyYwdH1ZkowDMXkA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } } } diff --git a/man/tm_file_viewer.Rd b/man/tm_file_viewer.Rd index a1617b9db..cf3b5cdd3 100644 --- a/man/tm_file_viewer.Rd +++ b/man/tm_file_viewer.Rd @@ -54,8 +54,8 @@ if (interactive()) { \describe{ \item{example-1}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAokqX8opKAeNdqAfQ8vG3dPbyNdAHdaUgALFXYgqFxdECVdXSSfTLCME2Z4dgBGRQgAX1KlNFRslRj2dJyvXQBeJuTGviERUVbdLuExBogMjNIYfxNaEX8tWjhImWHR0ZVUQVJ-VE9YvrpRUmWV0ZMian4ZPtFWA7gYPOm4BrBRWFQZqZ6FPF1tggBrKBSPrfPy8ASDcRSCBqajfOS4RrHX4QCRXG7ke6fJ7fV4wd5wSaPUQAejxBKJIgwqFR3xSf0BwLaoLg3HB3TEkmksnhiJGyN0pAAHqR0bcsY9nuSPsSyW8ZVThaQ6b91Iy9MywGCBj0uTCeWAEUjjoJGNQQWBYqRSKhRIgSSSTB5JEQtI7ZfxGIIJKT1vR9rE4PwSQAFIiMLz+uCGAAiRAIgngZEMADFwzBPIYAMqoOAEWhTAieKwQcSofgmb7GjKlFa13SlUoF3TsFTkZiWHQ2WxpfmieIQVgAQXQ7GqABJBLQUhPRDIdIxSmUlGAygBdIA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } } } diff --git a/man/tm_front_page.Rd b/man/tm_front_page.Rd index 7da5acb05..35b1c3e9d 100644 --- a/man/tm_front_page.Rd +++ b/man/tm_front_page.Rd @@ -85,8 +85,8 @@ if (interactive()) { \describe{ \item{example-1}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAokqX8opKAeNdqAfQ8vG3dPbyNdAHdaUgALFXYgqFxdECVdXUY4AEdBWiz2CDFSYmoiRkUIDIBBABEAZQAZH0y6pvTdT1JGdjbGlIUweC8kwdsIulFSdkHqwTjywd0AXl1BgDlnertdLhhBgbAk-1EiQUYCOCXVwdFWMli4TQJdUbBKgF9KgCsiFX8ANZwViiRJhcbGfhwExQYSkfwEfi0UQEfy-f5AkHAaDwUFJOQAXTcZCg9BE-gAjC0khgTMx4OwAJIQExEFa6AgzMDVA5rMAAITGKTscAAHqR2ZzZrzBoL3pUvGS4P4AEzUsK0+lwdgAAwAwkRqIIYFUKTrJVy9TKwLUhbp9YbjVUVebVpyAKwYd0pABsGB9chSDqNJt0AGZXRyuTy8Hy5XIFaTyWH1V5NbBtczWRbBq5Y4MAGJ2kXinNgADi1oAEmNKkpFeSVKh5i1JtMOoM7Em9BTrrtu5TcB2wF2lboVX2G8qVUOqnzRyJw5OB2GlHXoOgWioYjM50l2UlZxk+EIRKJ2SfhGJdxkMqQYP46SR4agoFIb7eMo8oFDGP5yKWbofp+GSDIyMCoOUXhkLoKisowMCeFYEB9mBEoEFAVQSGyjxZBgBwdCBfIAPJxDIsEsuUiGaCQqFgHqmG6Nhui4XA+FgIRt6Bpxd7dueqxTv4TbzEeIE-kiNHQAEXgSPxuhVnYACyjTRvwEnIdw8lKc05S6KI8QQKw-ayUxOEyHo+hMAAfEKPGmEQRCkBAjliGWAAadHIrsjymPkUz2Y5znkNaACasHnmRelwMQED8AFTkubZc6fvpRCRP4ww-mE7IOC4nGVBk3Fzt+v7sjJogACSxBSXL1LAqCLtU6B0BhklJRkrIuYwZVvpVqDRs1tCtch8UyEl660CYujsCo5DMJYOg2LYaRzvpKisE1-VoKgFV5Ck20VaIMg6BUSgfEoYAfASQA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } } } diff --git a/man/tm_g_association.Rd b/man/tm_g_association.Rd index 2509e026b..c4c79b452 100644 --- a/man/tm_g_association.Rd +++ b/man/tm_g_association.Rd @@ -51,16 +51,17 @@ with text placed before the output to put the output into context. For example a \item{post_output}{(\code{shiny.tag}) optional, text or UI element to be displayed after the module's output, adding context or further instructions. Elements like \code{shiny::helpText()} are useful.} -\item{ggplot2_args}{(\code{ggplot2_args}) optional, object created by \code{\link[teal.widgets:ggplot2_args]{teal.widgets::ggplot2_args()}} -with settings for all the plots or named list of \code{ggplot2_args} objects for plot-specific settings. -The argument is merged with options variable \code{teal.ggplot2_args} and default module setup. +\item{ggplot2_args}{(\code{ggplot2_args}) optional, object created by \code{\link[teal.widgets:ggplot2_args]{teal.widgets::ggplot2_args()}} with settings for all the plots or named list of \code{ggplot2_args} objects for plot-specific settings. The argument is merged with options variable \code{teal.ggplot2_args} and default module setup. List names should match the following: \code{c("default", "Bivariate1", "Bivariate2")}. For more details see the vignette: \code{vignette("custom-ggplot2-arguments", package = "teal.widgets")}.} -\item{decorators}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} (\code{list} of \code{teal_transform_module} or \code{NULL}) optional, -if not \code{NULL}, decorator for tables or plots included in the module.} +\item{decorators}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} (\code{list} of \code{teal_transform_module}, named \code{list} of \code{teal_transform_module} or \code{NULL}) optional, if not \code{NULL}, decorator for tables or plots included in the module. When a named list of \code{teal_transform_module}, the decorators are applied to the respective output objects. + +Otherwise, the decorators are applied to all objects, which is equivalent as using the name \code{default}. + +See section "Decorating \code{tm_}" below for more details.} } \value{ Object of class \code{teal_module} to be used in \code{teal} applications. @@ -79,8 +80,7 @@ For more examples, please see the vignette "Using association plot" via This module generates the following objects, which can be modified in place using decorators: \itemize{ -\item \code{plot_top} (\code{ggplot2}) -\item \code{plot_bottom} (\code{ggplot2}) +\item \code{plot} (\code{grob} created with \code{\link[ggplot2:ggplotGrob]{ggplot2::ggplotGrob()}}) } For additional details and examples of decorators, refer to the vignette @@ -176,13 +176,13 @@ if (interactive()) { \describe{ \item{example-1}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAokqUBiXVIhrqu-lCkULpwAB6wqCJKAUEGxlzUAPoxUDbRgcFGugDutKQAFirsKbi6IEq6uoxwAI6CtNXsPqKkxNREjIoQlQDCAPIATHG6-QMVpuqkHaLD0PCi7ABitNTkjOy0og4upVpokRyjpZsYJpMdpe0StATc7ACMADJyL129g8BnGtMAusPU+2ohw+XymjFEP1KUHEBHyLEmMi6AF8ukp9sMVHl2OMUroALz+DK4cZ8IQiGYE0nCMTY7qVXSkGCJCSJaGiIgEWiBKwQWn0+nVEz4wlBRJhUjMDSJUSoOAEPn8+kpOZ6AkKMCjdXEumK3SiOAiDTC-WG0jS2Xy8a6yoA+gG4XqgDKBrlpF0e0YXPoIkQWqt1thRBuYmFHq9IkSgeDCxSwGA6s1YB+kN0lrAAAUAWQtbp1XZWLKc3nqoF4NmwC9tdb6SbXXB+A6M1nSH6ddaTLRQvXhYsAIKPR2uNv8t6KuRVxUeikiqBi0ISybmuUK3XK2Cq3Mawat6u1o0EvdmmXL-26232tVgZ2m90scNiX14U+KqMEEMEsNQb1wSP5INvmMMjjBNtyTFM00zKBy1KPMCzgIswDsEtGQoFsK3HZ9+UPbtLyQuBS1Qndq10GBhE0SIN22ZwJ2rDsuwbAk+wHIdq1HEd-VHLouloIUNlUSVNB0GxbHKOlREKCBWF7dB2H2AASeooXQOT9UYHROiUJElDAJEfiAA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } \item{example-2}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAokqUBiXQGEAIgEkAZS9dfihSKF04AA9YVBElUPCDYy5qAH1EqBsEsIijXQB3WlIACxV2TNxdECVdXUY4AEdBWgb2CDFSYmoiRkUIOoBBHwCAGWT64bGlAF9+gCsiFTSAazhWUQrc23z+OBMoYVI0gn5aUQI0xeW1jeBoeE3MuQBdN2h0CZVi9lqQ3N0AF5-uFcH8+EIRKIgboIcIxL8BnVdKQYGkJGkoKJREQCLQwlYIIjkciGiYYZk0tFSMwNGlRKg4ARiSTkZkHnpgQowFNRtywUjWbpRHARBoYSKxccGUyWUK6tQoPRRTDuQFRUzSLotCx8fQRIh+X95boCCUlgQxDCdYw9SITubaJbNsaTSCoMBgNzedyXi8BW7kcy1c4ABr83TcrCDLyuPCRsBeADyjgAcg4AJoR71YACy2bAAQcgzsgwAjAWi9HSwAmAt+Ox2ABifPj3IAQrmsABpLB1sD9QNyANuyWauD8VVgaOxo2C+UmWhRCcwpuDUYBVzzkmD1nD111G3Q4GU6m06WM4Pbtm5DlTn14A-Isfi4Evi+yp8kxXK6hT9VStqupKlChqPteJJmhaVrAjadpwA60EuhBrKZJ63ojK2fojoGwaFmGBYznGVTcsmaaZgWgx5pWxalhWbaFrRgz9iRYANs2rasZ2PZ9tyu4mvuKF1O+K5cmA3G9ixX7IjARy0HEnL2E4zg4QuS6iboa4bluAlPvxui7v0-S0OS7AqOQ57aHANi2DUSKiGUECsIM6DsGgqAACQtFU7keSKjA6H0sxKGAMwvEAA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } } } diff --git a/man/tm_g_bivariate.Rd b/man/tm_g_bivariate.Rd index ad90d451b..4a738e349 100644 --- a/man/tm_g_bivariate.Rd +++ b/man/tm_g_bivariate.Rd @@ -101,9 +101,6 @@ with text placed before the output to put the output into context. For example a \item{post_output}{(\code{shiny.tag}) optional, text or UI element to be displayed after the module's output, adding context or further instructions. Elements like \code{shiny::helpText()} are useful.} - -\item{decorators}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} (\code{list} of \code{teal_transform_module} or \code{NULL}) optional, -if not \code{NULL}, decorator for tables or plots included in the module.} } \value{ Object of class \code{teal_module} to be used in \code{teal} applications. @@ -244,13 +241,13 @@ if (interactive()) { \describe{ \item{example-1}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAokqUBiXVIhrqu-lCkULpwAB6wqCJKAUEGxlzUAPoxUDbRgcFGugDutKQAFirsKbi6IEq6uoxwAI6CtNXsPqKkxNREjIoQlQDCAPIATHH+GRgmzPDs-QNdAL5dSmiowyp57BUjsQC8m1C4G3xCIqK6O6QwiRKJ9NostIFw692VuqGnu4lhpMwaiaKocAITxeLxS0Hg7wUYGmUP2zxBojgIg070RyNIfwBQI2IMq1Cg9CRkLAAGUkYDSLotHcCSJELCcbiCPkiLQCGJ3tTGPd6CJEszWezRMUMsBgFCYWAALpSuRw3EvNEUuD8YnECwM+G4ky0UIq94AMQAggAZEmuLWVLoguWM1jvFKfULfdQY-6A4G4sGwPQ7CWDTUKpUonbBt1Yz0K-GEvx+0nklFcnl0wMK3QCtkcnZJ2lwfkszPClJi-0DKEy22WxUJ8iquOCVBBADWcFTCpgwk0kV9umNZuc8rTOr1dd7pvNjKtjMrIMYRGyiRM6jglJ2jq+P3DHsnu3BPdLber6NRNcx26reIJRLjZOPOd5cHpeB3lQzQs5NIf+cFYhFQRL0IBtKsqDkGNb6nGdisACh4gsOEFjv2O7Wi8M4vG0i7LquHwbq6Z7YlW3oQnGkqgUeFInui+GRri0bXroUK3hR94ps+F7pgW77Zp+fJvr+xbioBZbAWhYHoghUJ2NUgTwGQsEvPBo59hOVYoVOzxdF0tAmLo7AqOQm7aI8ci2OUzyiIUECsEa6DsEsAAk9SlA5iKMDonRKLMShgLMUpAA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } \item{example-2}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAokqUBiXQGEAIgEkAZS9dfihSKF04AA9YVBElUPCDYy5qAH1EqBsEsIijXQB3WlIACxV2TNxdECVdXUY4AEdBWgb2CDFSYmoiRkUIOoBBHwCAGWT64bGlAF9+gCsiFTSAazhWUQrc23z+OBMoYVI0gn5aUQI0xeW1jeBoeE3MuQBdN2h0CZVi9lqQ3N0AF5-uFcH8+EIRKIgbpSDA0hI0vRtCxaGE4L8BnVdFEYZk0tFSMwNGlRKg4ARMdjsZkHnpgQowFNRoywVjqaI4CINDDOdzjmSKVTqdjqFB6FyYYyAlyKaRdFpUeKRIhWX8RboCCUlgQxDDFYw0fQRCdtbRdU9csBgIzmYyXi85GyNXU+XK4PwpUyAOKuPDqkUmWhRD0wgBig1GAVc7Ox-WpToDrDxuQJUSJ6gF5MpAbqtNg9N0tpGLP9sddsp5wLdJMFOfLovFkoZYBl-IVSuNcFVZZdmrNFv1nZNWp1Yi24WtxemYAdiYbFf5oZb0YAGmqF7oYEdaHFCxGo85nS6gyHPcCD9Hc7p43Hj3VGEQCmkDrr5cD8YTiVmhdf8-AvTtXsRRrd9dFA0ls2FDUxQlagvTbOUO0NZVuw3PtR3NPVgQNI0RwHcdMinJkS3tR17xAytyHPIsmSwABZdCT2DZddEvGMNVvOp52pboX3UOAwM-dNv0g38G3-Qtp1LCjFyQ6sqLE+s+1g5taMQnlcNQntZOxTDBxw4c4FNMdLUnG0SJnOddLkjRWMZLwAHlHAAOQcABNJiNVPVj2OvLibz+fp+loExdHYFRyG-bQMTkWwaixUQyggVhBnQdg0FQAASFoqkyrLOUYHQ+lmJQwBmF4gA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } } } diff --git a/man/tm_g_distribution.Rd b/man/tm_g_distribution.Rd index 4bac76283..646644857 100644 --- a/man/tm_g_distribution.Rd +++ b/man/tm_g_distribution.Rd @@ -38,9 +38,7 @@ Defaults to density (\code{FALSE}).} \item{ggtheme}{(\code{character}) optional, \code{ggplot2} theme to be used by default. Defaults to \code{"gray"}.} -\item{ggplot2_args}{(\code{ggplot2_args}) optional, object created by \code{\link[teal.widgets:ggplot2_args]{teal.widgets::ggplot2_args()}} -with settings for all the plots or named list of \code{ggplot2_args} objects for plot-specific settings. -The argument is merged with options variable \code{teal.ggplot2_args} and default module setup. +\item{ggplot2_args}{(\code{ggplot2_args}) optional, object created by \code{\link[teal.widgets:ggplot2_args]{teal.widgets::ggplot2_args()}} with settings for all the plots or named list of \code{ggplot2_args} objects for plot-specific settings. The argument is merged with options variable \code{teal.ggplot2_args} and default module setup. List names should match the following: \code{c("default", "Histogram", "QQplot")}. @@ -66,8 +64,11 @@ with text placed before the output to put the output into context. For example a \item{post_output}{(\code{shiny.tag}) optional, with text placed after the output to put the output into context. For example the \code{\link[shiny:helpText]{shiny::helpText()}} elements are useful.} -\item{decorators}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} (\code{list} of \code{teal_transform_module} or \code{NULL}) optional, -if not \code{NULL}, decorator for tables or plots included in the module.} +\item{decorators}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} (\code{list} of \code{teal_transform_module}, named \code{list} of \code{teal_transform_module} or \code{NULL}) optional, if not \code{NULL}, decorator for tables or plots included in the module. When a named list of \code{teal_transform_module}, the decorators are applied to the respective output objects. + +Otherwise, the decorators are applied to all objects, which is equivalent as using the name \code{default}. + +See section "Decorating \code{tm_g_distribution}" below for more details.} } \value{ Object of class \code{teal_module} to be used in \code{teal} applications. @@ -80,13 +81,31 @@ visually and statistically analyze the variable's distribution. \section{Decorating \code{tm_outliers}}{ -This module generates the following objects, which can be modified in place using decorators: +This module generates the following objects, which can be modified in place using decorators:: \itemize{ -\item \code{plot} (\code{ggplot2}) -\item \code{test_table} (\code{data.frame}) +\item \code{histogram_plot} (\code{ggplot2}) +\item \code{qq_plot} (\code{data.frame}) \item \code{summary_table} (\code{data.frame}) +\item \code{test_table} (\code{data.frame}) } +Decorators can be applied to all outputs or only to specific objects using a +named list of \code{teal_transform_module} objects. +The \code{"default"} name is reserved for decorators that are applied to all outputs. +See code snippet below: + +\if{html}{\out{
}}\preformatted{tm_g_distribution( + ..., # arguments for module + decorators = list( + default = list(teal_transform_module(...)), # applied to all outputs + histogram_plot = list(teal_transform_module(...)), # applied only to `histogram_plot` output + qq_plot = list(teal_transform_module(...)) # applied only to `qq_plot` output + summary_table = list(teal_transform_module(...)) # applied only to `summary_table` output + test_table = list(teal_transform_module(...)) # applied only to `test_table` output + ) +) +}\if{html}{\out{
}} + For additional details and examples of decorators, refer to the vignette \code{vignette("decorate-modules-output", package = "teal")} or the \code{\link[=teal_transform_module]{teal_transform_module()}} documentation. } @@ -166,13 +185,13 @@ if (interactive()) { \describe{ \item{example-1}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAoksZwAjoNrv2CsBISqDC0ogT+uLpetHCk1Ky6ALz2Ts62AGTpuu7Rvv6B6BFR3rHxSSkuGVk53nkBRCbkoqRF0aUJyQ6VupnZnrVwfmAAsgCCAMrjrSVxHRVpPdX9PoP+TEREMNMxs+VdaUoAxLpSEGrUuvxQpFC6cAAesKgiSlc3BsZc1AD6b1A2r2utyMugA7rRSAALFTsP6REBKXS6HyhD7IxihJQAX0UECUaFQaJUEL8ECRf3KcMRuj4QhEonKdGapKRSNIMG+El+oVIGPogk01mprMuPO+WhYlKB3wevPUpG+olQcAILJFrL+0Hg5X8KNEEWF6tEcBEGnKxtNCqVKvYEoxUHoIm+BEhRFoBDEQz1-jkkX8AAVYtwMAAZCgSKE+w1I3Ei2O6XG42gmXTsFTkZiWHQ2WwIsm6UTQiCsUbodgEgAk3kileNjB0jFxWKUYCxAF0gA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } \item{example-2}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAoksZwAjoNrv2CsBISqDC0ogT+uLpetHCk1Ky6ALz2Ts62AGTpuu7Rvv6B6BFR3rHxSSkuGVk53nkBRCbkoqRF0aUJyQ6VupnZnrVwfmAAsgCCAMrjrSVxHRVpPdX9PoP+TEREMNMxs+VdaUoAxLoAwgAiAJLjJ7r8UKRQunAAHrCoIkp3DwbGXNQA+l8oDZPvdHkZdAB3WikAAWKnYQMiICUul0ozO4wAMj9shjsUoAL6KCAAKyIKn+AGs4KxRIiwbYIfw4CYoMJSP8CPxQgR-uTKTS6cBoPB6UC5ABdJRKLQsUQARlxBFhFIIYn+ojgIg0cH4fggaLljFoUHoIi5qto6vFYOAwH8+Kx-klksiBCGoywwyK-hOAHlHAA5BwATV9YHGzgAGv45HJcKjdFqdeR+OUg44sc6ICSlGhULiVDCDWigeUkUm+EIRKJytXhGJS2jdKQYP8JIDQqQTfRBJprEmW7du-9jRWwf8Xj31JzRKg4B6h8PbmDRXpko7Mc68MvhynF6RygeNJqF0vDSvhyq1WJysbTea4Jbb7aHvatwSwK73Z6AOKuHguj+AAQsMWAANJYAqcYJnuK4nmm5SgeBUEwbul5XmiMAcrQ7wbroABioxYlGiaYVhJi0M8erlMRpGuBRw4klecFMcmM4PGOLATlx07MKe86Ls2V5AuuyFgE6ETwWiVHUOQjDlHJClnsJMktsadbJJpCrkVhLY4fJeEiHsqTqSxK5sVeEiMEQgioNxinJECU7PDOgnniJK5ibABGfjuemUbQ8kyEpwUqUJF76Ua8r3vKunqdhuH4aZLjmfBFlohZJIkrQJi6OwKgKbO2iDPGugopeojwhArCjOg7AFgAJN4kTNVqjA6IwJKEkoYCEpKQA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } } } diff --git a/man/tm_g_response.Rd b/man/tm_g_response.Rd index 478e393a2..3f94a82c4 100644 --- a/man/tm_g_response.Rd +++ b/man/tm_g_response.Rd @@ -81,9 +81,6 @@ with text placed before the output to put the output into context. For example a \item{post_output}{(\code{shiny.tag}) optional, text or UI element to be displayed after the module's output, adding context or further instructions. Elements like \code{shiny::helpText()} are useful.} - -\item{decorators}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} (\code{list} of \code{teal_transform_module} or \code{NULL}) optional, -if not \code{NULL}, decorator for tables or plots included in the module.} } \value{ Object of class \code{teal_module} to be used in \code{teal} applications. @@ -200,13 +197,13 @@ if (interactive()) { \describe{ \item{example-1}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAokqUBiXVIhrqu-lCkULpwAB6wqCJKAUEGxlzUAPoxUDbRgcFGugDutKQAFirsKbi6IEq6uoxwAI6CtNXsPqKkxNREjIoQlTCtLKJxur0E-RWmHbrsWroqugTsCoSs1Iuli1qiq7qLsFuLUiyLcrbl3ZVDfYyiwMBaALp3g1DiJuqkHezD-Tf3d12VAF8lACuko0KhBio8gszildABefwZXBjPhCEQDRFo4RiGHnXSkGCJCSJaqiVAkURwPH43TUKD0OB+RGLLBiCkQKm6AAK7VImzwY3xZI5XMRKUSYVIzA0iXJcHmQtpKWg8AR2zAXyuqyV+KpIg06v1CtIctQCpptPO9MZzI1AGUmSbdFoWLQGSJEDqzlbKgR8kRaAQxOrXYx3fQRIl-YHg6JihkbostQKHqVFUsVngNQdGEc5Cifb7jRo4Px1YsCMtvb7zjBhJpInpEQAxACCABl7c5C7XKiZaKEy+r213XEX8f9aQXdbpQuqJVKZab5YqJ+cVbBmxqUzXi07DYiSyvzWu+3SGUyK2BHQbSC63R64F7Bev8TGgyHEWGI1GP3GEyCJNNUuVM7nTBYwA2PYUBgfNez7Y9hxZKCBQQ2t62oRsRBHTtu3Q30ByHctWzw8daynSclSnLouloExJhUchl20aljjKMZREKCBWDbdB2HBAASepSiEqlGB0TpgSUMAATuIA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } \item{example-2}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAokqUBiXQGEAIgEkAZS9dfihSKF04AA9YVBElUPCDYy5qAH1EqBsEsIijXQB3WlIACxV2TNxdECVdXUY4AEdBWgb2CDFSYmoiRkUIOoBBHwCAGWT64bGlAF9+gCsiFTSAazhWUQrc23z+OBMoYVI0gn5aUQI0xeW1jeBoeE3MuQBdN2h0CZVi9lqQ3N0AF5-uFcH8+EIRKIgboIcIxL8BnVdKQYGkJGkGqJUCRRHBEcjkdQoPQ4NQYQowFgxDiIHjdAAFHqkUSUsFIwlY2n04GZNLRUjMDRpbFwAgEwnIzIPPTAylTUZsv6S3R4kQaGFqsXHUXi5Uq3TE0nkuVgAJk7W6LQsWgkkSIJUcg0EEpLAhiGHWxi2+giE6u2jup65YDAeUjRVgF4vKp6sAAIQAslgANJYABMbN0lK8AHlHAA5BwATUpcjk7INyK1Gjg-ApCeTaczeH1KpgR1ocVlugAYoNRgFnJWq6ZaFE6zD+4PXE7Cf0VRW27oojC+QKhTrUGKJSrpbAe+Hpq259WLRrgTWtzvl4SjWSG+b1aQrTa7XAHSfR7oXW6PcCvR9P1f0DBFMlDI9I2jWNfjNZwAA0s0pLBBi8VwwHLEcqyvSdTRQtDHW-DtqE0bspwHIcsINExx1wvsKNnKsF0lZi6mY-p+loExdHYFRyE3bR8XLao-lEMoIFYQZ0HYNBUAAEhaKpZLkvFGB0PpZiUMAZheIA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } } } diff --git a/man/tm_g_scatterplot.Rd b/man/tm_g_scatterplot.Rd index 9f03f48db..66f4bd84c 100644 --- a/man/tm_g_scatterplot.Rd +++ b/man/tm_g_scatterplot.Rd @@ -94,9 +94,6 @@ with settings for the module plot. The argument is merged with options variable \code{teal.ggplot2_args} and default module setup. For more details see the vignette: \code{vignette("custom-ggplot2-arguments", package = "teal.widgets")}} - -\item{decorators}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} (\code{list} of \code{teal_transform_module} or \code{NULL}) optional, -if not \code{NULL}, decorator for tables or plots included in the module.} } \value{ Object of class \code{teal_module} to be used in \code{teal} applications. @@ -296,13 +293,13 @@ if (interactive()) { \describe{ \item{example-1}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAoksZwAjoNrv2CsBISqDC0ogT+uLpetHCk1Ky6ALz2Ts62AGTpuu7Rvv6BzgAepMwRUd6x8UkpLhlZOd55hETURIKMqLQEANYyZdGVCckOtUoAxLpSEGrUuvxQpFC6cIWwqCJK84sGxlzUAPpbUDabC0tGugDutKQAFirsR5EgSrrZno1w7NOipMStjEUEDeAGEAPIAJh2unBEKUAF8gUo0KhoSobn5gXMztUnq9dHwhCJRNVCcIxJi3m9SDB9hJ9mEFuQOq1SJSqW9qFB6HBZsl-ABlAhMmTrIikGG3IhdMQRfEcwq4s77FYldSkBmoOAEdkct5HaDwar+WFyrF63SiXnaiXJK0iDSa7W6i26Lk8vm6QXWjS6LQsWjckSIM2uqkEKUyknJf2MQP0ET7CPSggUo7AYAmyH+AC6OciOv8xAsZX8glQi16-jkclw8td9ptcH4xuaJbw9YtMGEmnWemSADEAIIAGQFzjr5tdJlohWb1WHY9cU45QIttc7uiG2MWKuKzEdoi1hZXVINsH7XrApo7p7ejd9dp9GqPzs3HPdvNbAuffoDQbgENbzDN5kyjapY3jRMwNTURHjODMszhMA8wLPw23CPAr3LSs4GrDc7ypB9yBbfkwBwqAq2AkDu2oXsRAXUdx0nEDTFnedByY5cwzXPUCItf4iEYfZ6G3I49zVQ9jxdDlzyNMibxYhtfyfB0X2k98qU-T1vTUv84wAoClLDGCxAg-8EzgJNI1gmTXXTTNr2zFD800jlCzAAAFLkyFLMA7FYLU-LsdwFngXysKLEhMMiMsK0ovCwF4njjOUtSON0AA5RwRxHVKux7Wg+0Ypd8r1Gc51I3RF3HTTkqpfi9VEWgAC8rNEpVd1VA91LfQi5MvJDQzSm1qmIp0T1Y7Tv1-SDDOGkybLMmMLOgpa4IcoaXLQqL21i8j4qomsyo5YiMri3CFtdWj6MvGqJzctjKpK2rCPqt5Go5RgiEufYTHUWJOqgCSeomuz9TOQ1Bqc5CTstFT4bUsHHumsifz0ubLKMx7TOjfSoKs3H4MWRCYdzfNdA87yoAi-aAqCyL-NCmkKFIfC4fvZ8Muy3KOYJQris40rHoqjL7rqzdPvDFo-oB20d2B7r1WR-rIYvVtFM04ixufFWpu5L80dm1bAKugT1vMgzLOslM0wQxyb1Qyn0Op2mr3pxK6eZ8K2aSqWLTOqqebyx6bqKhiheYkX2Kq8W3sl+teKBIFaBMXR2BUZl1W0L4a10F4sVEe4IFYId0HYFEABJvEiKurUYHRAQRJQwHhHMgA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } \item{example-2}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAoksZwAjoNrv2CsBISqDC0ogT+uLpetHCk1Ky6ALz2Ts62AGTpuu7Rvv6BzgAepMwRUd6x8UkpLhlZOd55hETURIKMqLQEANYyZdGVCckOtUoAxLoAwgAiAJIAypO6-FCkULpwhbCoIkorawbGXNQA+vtQNnur60a6AO60pAAWKuznkSBKutmejXDsEDEpGIrUYigg3wAgtN5gAZQ7ZaFwpQAX3BACsiCoTr1WKI3tdbLd+HATFBhKQTgR+KECCdMdjcaJgNB4PjznIALpKJRoVAIlSPPwQ5bXarvL66PhCESiarS4RiYXfb6kGAnCQnMKrcgdVqkZUq77UKD0ODUar+eYEHUyHZEUhTJ5YghiCKSo2FcXXE6bErqSmiVBwAiGo3fc6svTJfxI2HukXh3Sic0hx3JFMiDRa4Ohj1J3Qms0WmNgeapjS6LQsWimkSIBMFlUEZ1dMTVauMWv0ERU1uu9nXYDAWMw+NgTmcyJ5sCQgDirjwun8ACEALJYADSWAAjGVVxvtwAmfxyOS4fNJzNpuD8S2zheNptSim0HbR3QAMUhsPmzgviYFiYtCFLe1Tfr+riAUa4JJuel66EMoprL6xTMNmQYhmG4aRrAH6jsieAId816VhmFaBrm2FJkW5r3uWWaOp23b1k+TYti67bJMxdZwH2nGDmsw4EeOk7Tn4D6LpEB5bru+5gOusknmAZ4Ac+yYUWBpaKdue5EdB4YwK+77gT+f5qc+wGgXeyQQX+xG6LB4bwQZIJEIwJz0Eh5yof6GFUQ5uHwPecZseGpHphpjE5lhDnGqadGlgxaZVjWvENvp6kcW2crcWlPZ8dlA7UQW5zCbOY7+GJcXNhJ85ScuCmHnJS4yce8lYJCkwNf4WDOHOswAPIAHJ6U5TYuepEVabow2OLCsIWU2RnUJoJm2WZ-41VZM12VBE0IZN4W0AAXnxXneihfroZRsUGRG1xRiFlWZQWEXVBFMV5vdKq0SWjXJZWPEFRlS0FkVXGpV2vH8TlBJCSOFWEWJugzvV8k6S1qk1dNNmNejr3LcZIimZBYNJjteN7Q540qkdRqMEQdwnGSrqRT510Bl9JUPWsT2lqFhPhRRH0UdzNV-fRIvA6xQtJhDuVQyxhX9kqZWI4LKMzpjynSWAnXdR1-VDaNp7029ml43NC3k4ZxMfntttGpTpP2T9tPfOb3wgiz6ixJdUC+Td4s-UF+FI+OTtRSl5HRZh33qZLSXS-lstR97quKzLKsCfDUDlZrU6oxJOsdV1PX68bI1jV7wuMTN1uLTVK1rSTG1k9tIG7ZtNOHfmTnguCtAmLo7AqLqAbaP8Z66J8IqiC8ECsJC6DsHyAAk3iRBvKaMDoYKokoYAopyQA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } } } diff --git a/man/tm_g_scatterplotmatrix.Rd b/man/tm_g_scatterplotmatrix.Rd index 7faa664d1..4cd3d9998 100644 --- a/man/tm_g_scatterplotmatrix.Rd +++ b/man/tm_g_scatterplotmatrix.Rd @@ -35,9 +35,6 @@ with text placed before the output to put the output into context. For example a \item{post_output}{(\code{shiny.tag}) optional, text or UI element to be displayed after the module's output, adding context or further instructions. Elements like \code{shiny::helpText()} are useful.} - -\item{decorators}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} (\code{list} of \code{teal_transform_module} or \code{NULL}) optional, -if not \code{NULL}, decorator for tables or plots included in the module.} } \value{ Object of class \code{teal_module} to be used in \code{teal} applications. @@ -204,13 +201,13 @@ if (interactive()) { \describe{ \item{example-1}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAoksZwAjoNrv2CmlCkmgRw-ri6XrRwpNSsugC89k7OihAAxLpSEGrUuvyBULpwAB6wqCJK+aSFRrpc1AD6VVA2lQUGxgDutKQAFirszeEgSrq6xOakjFGiHXkFGCbM8H4QY2O0-AnjfmAAIq54uv4AYlhhx2AAknYX-s4AyndgAAq3R-4A4ucfYAByABlngAhQ7hfwAxzPACC7zkuFG6wkRB0jAg8DI2xM6lIREYq3W6wI7AATOEyboKQBGcm03Q0+nhBkk+GIwnUKD0ODUWaJYn+ACyJBYBF6rGeWDgqEE9DoBH8qUJrLW6w5EAkgigUga2JgtFiWJxeIJhJ2DIAzOFLbprdbqUyrUzlabdByuTztvywJ8ZDAoMp5b8ABLckQBiVEP0WUJgRXrZ3rVBEaUczQkT3sAAc1oAbAB2cI5gAM4QALAX6SX6QyqRWqQyixgc+EAJwJsYsOCFPnsc0AVgrfb7FqLDL7Rb7rep5oppZH5Kb4Wz7cy-FQGfNGFLC4rJIwNa34Ub1sbFMbFcbk90jYbW5X-Dg9FIGb3zIwdsPlMXX4-25-C7-PdfzjONRG4MQ5maRZljgE0Ni2RIqUQccERVMYJjINgGk2bYwJgcpYLZIldgOZ4zmeG5nkeZ43meb5nkBEEwUuSEYThVCXVEWgAC89ESFCiLGdxynUPikhcIiV1YLtGFwvFSHYPCCNJUci0QEkiw08IUN0YSORCbYHBcOQVx0CBBDEpSRHYL1RD9ahqGeeB+FoQQYGeDlGCkZ4SDobIFW0qs9NEwzkhXAh-RCBy4AQ3QrNg4kjOccITmhAEHhSQLwmCgzEiSlcvH9TRSDiRI0TxGB2B0qkiyrDTwqIURSF5XSIAqqqq0zOqixXVBGCIEwem2crGEqnStMrEClAAX1SAArIgVAaABrOBWFEQYClsWoFqW1b1pNXaIBWtbdgwqYZmec7pjEZ5NgCxEjpOjh-DAkRRGeN7bt+e7Yw43Qnv2s6iEmG6Pt+L7wfCL1fu2fxrtYbD+AVVJUiUNB11qFQehNZptiGRE+CEd7tiJ4QxDguoYAaCQGlECKghkcoiFIP0LuKSmxjdbk4bAB4GfIRhmefNnpmKMJBN0LQWFoTkScSOgms59ZmgaEophxOnUDgfk0JdeZqmgeBeeuy68ElwlRG5HXn0SK2RA0LWdeVl1udyRJ-Aea2NClmW5bERAJb1-Xxl6RaQha6Xpn9hpRXDinmmAYB4ZBzCzYAXXTlcQ-tm2YozfxOygZ4JDXZ4HyfB7g-1mBhE0AjQpcf6Q7GPEH3cWKkublvBuKfPElS9LXGrpULd0bOVYKNXig1x3RG13WW4N-1YDE17wKhsexkG6hBaxfVBadxel9dTkeY9vnvefKPZdlOBA-NkfTSjlqU9BxHfu7kO49oCPtml6gFlY5h1-gnAoSd17vX8JncEhBU5TA-sjP6W91i5w0P3HY-hSK-HIr8SivxqK-For8eivxGK-FBM8VivxYRVxProWuu9aANzyskFBE9LZX1wlfI+LtTRu15l7B218-Z31EA-L++sf5-0SDfGO0iwHVAgWASG0D07Q12IVMgPRxS-GIE1KGlw+oDR6CjSRnEr4YK9Fo4qujYH6Oas8Yxg1SB0JPow+uIhG7JRQa3Rg7cMFd18aYWgfdYqDwyuwsecZR56ymhAVItATC6HYCoQWOJtCwRMroEYKpRD9AgKwaE6B2AYwACTeHCOUq2jBUSpGmkoMA0105AA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } \item{example-2}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAoksZwAjoNrv2CmlCkmgRw-ri6XrRwpNSsugC89k7OihAAxLoAwgAiAJIAypm6-IFQunAAHrCoIkolpGVGulzUAPr1UDZ1pQbGAO60pAAWKuwd4SBKuroAgtn5ADK9uoxzi1Oz2Vj5y6tb+UoAvqkAVkQqrQDWcKyiY6W2TfxwJlDCpK0E-LSiBK1nF2ut2A0Hgdw6cgAukolGhUMsVIM-BBph0EsVSrgNnwhCJROiccIxMjptNSDBWhJWr9AuRGDUiOTAoxaBUSaTptQoPQ4NR0f58gRaTIGaRdDBmaywhsOVoWLRuXj0XRRKR2RzUaVWpVSMwNNTUHACOqNZqGqC9Il-GsFtKUabSaJeUaxYknSJ9aJDcaZQ7OdzefywPlnRpdHKWYqxIg7X6OQQhucQvjEhGFfQRJ9E7Rk-cGsBgNb5rawJDIXIsfa47p3S64Px0T6wDMAOKuPC6fxYGaZdvhAXOAAa-grvr9MHetBqlqSLkr1emREYz3cDcSDjnY4dJlZ9fRADEZgt8q4qw7Un7R2eOR1tRVdeoPl6jSbTR0LUG5ttY3Gd9Q6eif50gaL5bqaXI8nyVrBqGYoUPwqDnGQogxngYEahGKa6E2AAKMzdgAsjkYSds2ABqBS5HYI7zguCZJmI6JytQghwFmDHgqUBZFt+paQuEuH4TMRHZCR1oUfkVE0dhfhgHhhFieRlHUWAchXguNawXu0G5AAcmRzh2LoxjOLp2S6AA8vuuh6dkjiZHYuQWbpP7VhO-5TiI6Ibqe1bqXGtZhm6sEgT614OhBgbQSGHpimmUYoa5cb0TmjGpvKUbsalnH5oWzb7P4Zb+dWgXkGuMnWm2ikzGRR7VdkACaNHoRy7maNO3nJLR1ZLiu2mzs43W-ru5WHsevlxhe55blN0xTakqS0CYujsCodKPtocA2LYkz2qIIwQKwMzoOwcIACTeOE51OowOiMKkhxKGAhyQkAA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } } } diff --git a/man/tm_missing_data.Rd b/man/tm_missing_data.Rd index c05408180..d4d7e6cf9 100644 --- a/man/tm_missing_data.Rd +++ b/man/tm_missing_data.Rd @@ -34,9 +34,7 @@ ignored.} \item{ggtheme}{(\code{character}) optional, specifies the default \code{ggplot2} theme for plots. Defaults to \code{classic}.} -\item{ggplot2_args}{(\code{ggplot2_args}) optional, object created by \code{\link[teal.widgets:ggplot2_args]{teal.widgets::ggplot2_args()}} -with settings for all the plots or named list of \code{ggplot2_args} objects for plot-specific settings. -The argument is merged with options variable \code{teal.ggplot2_args} and default module setup. +\item{ggplot2_args}{(\code{ggplot2_args}) optional, object created by \code{\link[teal.widgets:ggplot2_args]{teal.widgets::ggplot2_args()}} with settings for all the plots or named list of \code{ggplot2_args} objects for plot-specific settings. The argument is merged with options variable \code{teal.ggplot2_args} and default module setup. List names should match the following: \code{c("default", "Summary Obs", "Summary Patients", "Combinations Main", "Combinations Hist", "By Subject")}. @@ -49,8 +47,11 @@ with text placed before the output to put the output into context. For example a \item{post_output}{(\code{shiny.tag}) optional, text or UI element to be displayed after the module's output, adding context or further instructions. Elements like \code{shiny::helpText()} are useful.} -\item{decorators}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} (\code{list} of \code{teal_transform_module} or \code{NULL}) optional, -if not \code{NULL}, decorator for tables or plots included in the module.} +\item{decorators}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} (\code{list} of \code{teal_transform_module}, named \code{list} of \code{teal_transform_module} or \code{NULL}) optional, if not \code{NULL}, decorator for tables or plots included in the module. When a named list of \code{teal_transform_module}, the decorators are applied to the respective output objects. + +Otherwise, the decorators are applied to all objects, which is equivalent as using the name \code{default}. + +See section "Decorating \code{tm_missing_data}" below for more details.} } \value{ Object of class \code{teal_module} to be used in \code{teal} applications. @@ -66,12 +67,29 @@ adaptable for general data analysis purposes. This module generates the following objects, which can be modified in place using decorators: \itemize{ -\item \code{summary_plot} (\verb{ggplot2 plot grob}) -\item \code{combination_plot} (\verb{ggplot2 plot grob}) +\item \code{summary_plot} (\code{grob} created with \code{\link[ggplot2:ggplotGrob]{ggplot2::ggplotGrob()}}) +\item \code{combination_plot} (\code{grob} created with \code{\link[ggplot2:ggplotGrob]{ggplot2::ggplotGrob()}}) \item \code{by_subject_plot} (\code{ggplot2}) \item \code{table} (\code{\link[DT:datatable]{DT::datatable()}}) } +Decorators can be applied to all outputs or only to specific objects using a +named list of \code{teal_transform_module} objects. +The \code{"default"} name is reserved for decorators that are applied to all outputs. +See code snippet below: + +\if{html}{\out{
}}\preformatted{tm_missing_data( + ..., # arguments for module + decorators = list( + default = list(teal_transform_module(...)), # applied to all outputs + summary_plot = list(teal_transform_module(...)), # applied only to `summary_plot` output + combination_plot = list(teal_transform_module(...)) # applied only to `combination_plot` output + by_subject_plot = list(teal_transform_module(...)) # applied only to `by_subject_plot` output + table = list(teal_transform_module(...)) # applied only to `table` output + ) +) +}\if{html}{\out{
}} + For additional details and examples of decorators, refer to the vignette \code{vignette("decorate-modules-output", package = "teal")} or the \code{\link[=teal_transform_module]{teal_transform_module()}} documentation. } @@ -132,13 +150,13 @@ if (interactive()) { \describe{ \item{example-1}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAoksZwAjoNrv2CsBKMtPzOAB6kzP64ul60cKTUrLoAvPZOzrYAZJm67rG+-ozUUBASUTHe8YkpaS6KEADEulIQatS6cKGwqCK6-FCkUEr9gwbGXNQA+iNQNsMDUGO6AO60pAAWKuwz0SBKurme3r6toqTE1ESM9fu6UPz8k9CiS2YWmtahtnsQBwehwFE3RE7FEnkm3BIEnYX2iJkuV3YIlKGxhtgAVLlzLQTOwAIzRDAABgArIS8QB2OTUgC6SwAcgBBW7-W4AXyUtx8tBeRl03NEtxg5xYvOMwoIos5v35QVEwDpfOK6ES7AF0Xuj2e9QOEtFCqWyp6HD1jFEGoeTygoh1ulN8uA-gIrGo-hpiuM1owJnUpER9uAjsILrdNNtAaDUhYoaWXp9Gn9IrNgf8UcYofqbJu0HQSxUaz8MpmNR2QoEwjENT4QhEokLf10pBgkxgPNEKgk0wWcxl9XqON0atUzEsOhs31uok2EFYjPQ7DQqAAJN4Negl2DGDprkoORAwGyaUA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } \item{example-2}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAoksZwAjoNrv2CsBKMtPzOAB6kzP64ul60cKTUrLoAvPZOzrYAZJm67rG+-ozUUBASUTHe8YkpaS6KEADEugDCACIAkgDKzbpwobCoIrr8UKRQSiNjBsZc1AD6k1A2E6NQ07oA7rSkABYq7IvRIEq6uZ7evhBipMTURIz1pwCCrZ0AMuuML+8nui9YnU+-06SgAvvUAFZEFRzADWcFYogOq1sRmGcBMUGEpDmBH4tFEBDmUJh8MRwGg8CRizkAF0lEo0Kh1iptn4IKdFjVDr8+EIRKIanzhGJ2adTqQYHMYATRCoJAtVssObp6vVaCZdOwVORmJYdDZbMcVaI9hBWE90OwmQASbzRW2iGQ6B5gpRgUG0oA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } } } diff --git a/man/tm_outliers.Rd b/man/tm_outliers.Rd index 895dd5168..be0716e59 100644 --- a/man/tm_outliers.Rd +++ b/man/tm_outliers.Rd @@ -29,11 +29,9 @@ specifies the categorical variable(s) to split the selected outlier variables on \item{ggtheme}{(\code{character}) optional, \code{ggplot2} theme to be used by default. Defaults to \code{"gray"}.} -\item{ggplot2_args}{(\code{ggplot2_args}) optional, object created by \code{\link[teal.widgets:ggplot2_args]{teal.widgets::ggplot2_args()}} -with settings for all the plots or named list of \code{ggplot2_args} objects for plot-specific settings. -The argument is merged with options variable \code{teal.ggplot2_args} and default module setup. +\item{ggplot2_args}{(\code{ggplot2_args}) optional, object created by \code{\link[teal.widgets:ggplot2_args]{teal.widgets::ggplot2_args()}} with settings for all the plots or named list of \code{ggplot2_args} objects for plot-specific settings. The argument is merged with options variable \code{teal.ggplot2_args} and default module setup. -List names should match the following: \code{c("default", "Boxplot","Density Plot","Cumulative Distribution Plot")}. +List names should match the following: \code{c("default", "Boxplot", "Density Plot", "Cumulative Distribution Plot")}. For more details see the vignette: \code{vignette("custom-ggplot2-arguments", package = "teal.widgets")}.} @@ -50,8 +48,11 @@ with text placed before the output to put the output into context. For example a \item{post_output}{(\code{shiny.tag}) optional, text or UI element to be displayed after the module's output, adding context or further instructions. Elements like \code{shiny::helpText()} are useful.} -\item{decorators}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} (\code{list} of \code{teal_transform_module} or \code{NULL}) optional, -if not \code{NULL}, decorator for tables or plots included in the module.} +\item{decorators}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} (\code{list} of \code{teal_transform_module}, named \code{list} of \code{teal_transform_module} or \code{NULL}) optional, if not \code{NULL}, decorator for tables or plots included in the module. When a named list of \code{teal_transform_module}, the decorators are applied to the respective output objects. + +Otherwise, the decorators are applied to all objects, which is equivalent as using the name \code{default}. + +See section "Decorating \code{tm_outliers}" below for more details.} } \value{ Object of class \code{teal_module} to be used in \code{teal} applications. @@ -68,9 +69,27 @@ This module generates the following objects, which can be modified in place usin \itemize{ \item \code{box_plot} (\code{ggplot2}) \item \code{density_plot} (\code{ggplot2}) -\item \code{cum_dist_plot} (\code{ggplot2}) +\item \code{cumulative_plot} (\code{ggplot2}) +\item \code{table} (\code{\link[DT:datatable]{DT::datatable()}}) } +Decorators can be applied to all outputs or only to specific objects using a +named list of \code{teal_transform_module} objects. +The \code{"default"} name is reserved for decorators that are applied to all outputs. +See code snippet below: + +\if{html}{\out{
}}\preformatted{tm_outliers( + ..., # arguments for module + decorators = list( + default = list(teal_transform_module(...)), # applied to all outputs + box_plot = list(teal_transform_module(...)), # applied only to `box_plot` output + density_plot = list(teal_transform_module(...)) # applied only to `density_plot` output + cumulative_plot = list(teal_transform_module(...)) # applied only to `cumulative_plot` output + table = list(teal_transform_module(...)) # applied only to `table` output + ) +) +}\if{html}{\out{
}} + For additional details and examples of decorators, refer to the vignette \code{vignette("decorate-modules-output", package = "teal")} or the \code{\link[=teal_transform_module]{teal_transform_module()}} documentation. } @@ -173,13 +192,13 @@ if (interactive()) { \describe{ \item{example-1}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAokrcQAxLqkQ11XfxQpFC6cAAesKgiSoHBBsZc1AD6sVA2MUEhRroA7rSkABYq7Km4uiBKuroAwgDyAEzxNQ2VzfXAwApgqIy0MCysSQDWcKxdALrjTaJwAI5JIhDsEIxEOex19XKKEAC+OwBWRCrDo6IlmbbZRycjrOc3EKccXZtdZa8teLpdPX0Dzy623cWhYoiaBAKxwIYiSMxEGjg-HYoN6UHoIiSkOhYguwQ6n3qE3GZQI7C6AAVqFAyO8fmA7KxUHA6V07Iw4EF4LSwNsdko0Kgmip8uSIFVUroALwBTK4Vp8IQicEyxXCXGtKqkGBJIiCUh0GTnTVVXR6g20GRJVHS3R0USkMWm52y4JJcKkZgaOHMskml2ummwPQywnvf0u+FwDS2qPe0S+p0Bl3U+hwfyhsAAZXT0dIulRtHRIkQ4fFyed2NoMJVBZYRYxcCxUOruNSBLAbzAk1J5MIJAIrLAglQwRGQLk8vLFaqcfI-FtXRHY5ZeAjAZgwk0URDugAYgBBAAyWecU5nppMtDCSNth5PrmnyZ2FZfLsnEYIQTgEiIvS-yQ2jK9qOuugbumEnrqKQPrRkmFapNA8CLp2XznjOV7UOQjC2ph2GwX6T4VqitYkehF5VjWtqgtQghNpRbaZB2XY9nWjCiAAJHOSIfkRybcQuMo0XRzY4uc7adKhRLdiSbGcQJvEXlUm5YbQO62g4LhgVUb4Brppr6W+Ow7LQJi6OwKjYdB2hwDYtgVOWohFBArAHug7CChxgi0GUnkzIwOiMDsuxKGAuzjEAA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } \item{example-2}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAokrcQAxLoDCAEQCSAMreuvxQpFC6cAAesKgiSmERBsZc1AD6SVA2ieGRRroA7rSkABYq7Fm4uiBKuroAgr6BADIpuoxNrUoAvooQAFZEKukA1nCsopV5tgX8cCZQwqTpBPy0ogTpQyPjk8DQ8FNZcgC67osa6VosoulQ-KLU7Ydi7ABitNTkjOwbDi5qqI0PEOFlgMAFGAui0oadTtUNhhLqQiIw5BilDdGKJ2gRSsMCGJ0qI4CINHB+OxsbQoPQRKsCbQicc8hCoTC4QjTOoVti7g8npiIO4lCD2ioSuw6qE8roALyyiK4GV8IQiXGKtXCN4y+qkGDpIiCUh0GRTPX1XTG020GTXFgK3R0USkaUQK2epVQdIxUjMK6iVBwAjur1erKvJ0c5qwvCW8Ok8mkJ1JkMrIMhsPhr3UOlk6NgQJk9O6Gl0kSIKEqj05z34wliJ3l+lwRmN1kRdnQ2Nc6qhjkAcVceF0UIAQgBZLAAaSwAEYoRia3XPWmKfxCw1h9WEzmYMtaPE9Ir3g0WoFnCvV-UTLRopSnWeL65a3X+u+93Jr-XwnAJGizLcA6jBOi6bp7vUWS+tE-q8iSwYDm+OaRrAJ5jj23Txsh4Z3t8MhOnhPwIVmkFevyza3D+q4NsyTaKjc1CCG2tEstMXaQphcbwtU-IACTruQ-DfmRa4lhulFMSxTJseCnGcmAPFlrcAniUJIk4fuh7Hk6AKvjeH45oZnrGbohn9P0tAmLofyqAGmg6DYti1LWojlBArANOg7Agnxgi0NUvmkowOjor0ShgD0pxAA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } } } diff --git a/man/tm_t_crosstable.Rd b/man/tm_t_crosstable.Rd index f4e4953e9..3a4c0d8a2 100644 --- a/man/tm_t_crosstable.Rd +++ b/man/tm_t_crosstable.Rd @@ -50,9 +50,6 @@ with settings for the module table. The argument is merged with options variable \code{teal.basic_table_args} and default module setup. For more details see the vignette: \code{vignette("custom-basic-table-arguments", package = "teal.widgets")}} - -\item{decorators}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} (\code{list} of \code{teal_transform_module} or \code{NULL}) optional, -if not \code{NULL}, decorator for tables or plots included in the module.} } \value{ Object of class \code{teal_module} to be used in \code{teal} applications. @@ -175,13 +172,13 @@ if (interactive()) { \describe{ \item{example-1}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAoksZwAjoNrv2CsIykUPQiov64ul60cKTUrLoAvPZOzooQAMS6UhBq1Lr8UEG6cAAesKgiSgVFRrpc1AD61VA2VYVQBsYA7rSkABYq7M0RIEq6ujCkBCyinRNTM2OmRIy67Fq6KroEfoSs1OG6-lpheEcoMIf+Uiz+crajEOPjk9OMosDAWgC633NQ4hM6lIK3Yrxmnx+3zS4wAvktwe9Pv5UIxaDAWKwGgBrOCsfy-OaiTwNEQQdgQRhELpghbve5KWFpABWRBUOLxoiG7VstVZ7NxrC5-IgHI4-kRpwiErpUvOqPRmLFdzSSjQqDmKl6fie+XaiT1QVwCIEwjEBr4QlCOuedRgDVIDQIVNEoiCITgNttumowTgeSS-gAwi7ZnZgpU8EtbSUDc0GqVSMwNA1RKg4Dto97mtB4AaZW8pVnbcSRBoDaWM460xmvd7nr76P782AAMr+qu6LQsWgRuCIcLF70EPpsgjmpLdtF9p2j2jjrnNZFgSUE74RTN7A5nY5y-ywK5gG6MFXG3X18aVjRwfgGzcEfaH493M8X54wYSaCp6JIOFyvt9dBWfgZBvA0-2cAC3xMWgSjApIADEAEEABlW1cc9vRhLCoOeeIknjRNk2rdNM0w20c1gH9zlXKNyOeK9SArDsUxrMjAJ9P0A3OdsyyYqdew9Ac6I4kcxwnLsexnMT5zEbkgmXWjfg3XYH23aUwBOQ8Dx3I84FuMB7lw+tGPg84tJEwCP2oL8RANZC0MgodbRguDb0Q1D0Oc3RsNtXyfKWNI0loEw1hUchiO0T17l0R5LwGCBWCQ9B2HVAASbwInS4lGB0Rg0nhCAwFhb4gA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } \item{example-2}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAoksZwAjoNrv2CsIykUPQiov64ul60cKTUrLoAvPZOzooQAMS6AMIAIgCSAMpZuvxQQbpwAB6wqCJKpeVGulzUAPoNUDb1ZVAGxgDutKQAFirsHREgSrq6AII5BQAyfbqM80tKAL5pAFZEKq0A1nCsouM9tk38cCZQwqStBPy0ogStewfHp8DQ8GcdcgAukolGhUCsVEM-BAZh1EiUerhpro+EJQvDUcIxNCZjNSDBWg8CIwiKJREEQnAcbiZtRgnBqPD-FkSWT7ME6nhkTTKvCOq0qqRmBpWqJUHACNSabCer89El-OtFuFudLRAyJaR4eqRCKxRKpdLafTGQqwAUNRpdFoWLQOXBECqYUbcQRhvsCGJ4TbGHbKY93bRPf8esBgIqFsqwIDARFRIJ6OqtUkzBZNNYAbops6XbjaPxeU0AIQ29Bxc5BCIqYYyIaiCLUIgSIPcdgARjkEUl-hyZTg4V0-gACgB5Ap5AAaGgHw7Hk+opH8cjSuZp7lIgkYEHYcpDQTkwHzlUBK9X2yROZdOs1cH4TLAWRHjgAcg4AJpO1co+60Wry5IuBeX5EIw1zuHeSQOIBqpGiYtCVLe8IAGKzIsBSuJeNKnlhQHSvEST8oKwoPPq3aYbiHRyveSqflelrJro156uKZFfnS9AMveFq6lqPp+iIjpcuRNJuh6XpJHx9oBmJe5QGGEYbNGsaMQmSbwqmlgZhcWYwS6R4rKWtQcBMugvBgtwaCBDZNi21DtsuulGuum7bruFZQAeR4no5uLnj5MxMeQEGDuazgTrRuYwD+f7Iah6G4bmcEIcFKFoRhubYbimWnmkaS0CYujsCo5DEdoVLLjpzqiKMECsLM6DsGCAAk3gRM16qMDojBpJsShgJsgJAA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } } } diff --git a/man/tm_variable_browser.Rd b/man/tm_variable_browser.Rd index 752c4c83d..b36911ed4 100644 --- a/man/tm_variable_browser.Rd +++ b/man/tm_variable_browser.Rd @@ -104,13 +104,13 @@ if (interactive()) { \describe{ \item{example-1}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAoksZwAjoNrv2CsKKoLADWdBBw-ri6XrRwpNSsugC89k7OtgBkGbruMb7+ABakMNQA7rT8UqSikdHecQnJqS6Z2bne+WAAVqIkdOS1MQ2JKQ4tSgDEulLhsrr8UKRQunAAHrCoIkoLSwbGXNQA+jtQNtuLy0a65aQFKuwnUSBKuro+tKJ7b4wfL7owpAILE+VwBQMYNQgr1KRHgUKuMLhfxMUFotzM1C+KLRBQxfwAwgB5ABMXyJxKUAF9FBAlGhUF8VGi-FD5hcmo8-nwhCJPilucIxCzXq9ioctCxaFB6CJDkwiKVRDJhSLXtRpXBMSl-AA1SXSkS6eWKmT+P6vGkWpQ02gmXTsFTkZiWHQ2WzPVmiO4QVgAQXQ7HpABJvFFg0rGDpGDTKUowJSALpAA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } \item{example-2}{ \href{https://shinylive.io/r/app/#code=NobwRAdghgtgpmAXGKAHVA6ASmANGAYwHsIAXOMpMAGwEsAjAJykYE8AKcqajGIgEwCu1OAGcMAcwpxm1AJQAdCLTIyoBUrQBucAAQAeALS6AZoIgbaJdnN0AVLAFUAoksZwAjoNrv2CsKKoLADWdBBw-ri6XrRwpNSsugC89k7OtgBkGbruMb7+ABakMNQA7rT8UqSikdHecQnJqS6Z2bne+WAAVqIkdOS1MQ2JKQ4tSgDEugDCACIAkgDK07pwAB6wqCK6-FCkUEp0TCwcgSFhcIoQu-sGxlzUAPo3UDZKL3e65aQFKuwvURASl0ugAgrNFgAZT6McFQ4Fg2Z2OzOGHg5GuCAAXyuXSIKkewTgrFE-z2UFsRh2cBMUGEpEeBH4tFEBEeeIJRJJwGg8FJLzkAF0lEo0KhPipaKQ-BAQR8UgCEXwhCJRE1lcIxDKQSDio8tCxaFB6CJHkwiKVRDJtTqQdRjXBqE1-AA1Q3G7bmy0yfwIkFXf1KK60Ey6dgqcjMSw6Gy2IGy3SiX4QVig9DsMUAEm8USzVsYOkYVyxSjAWMFQA}{Open in Shinylive} - \if{html}{\out{}} - \if{html}{\out{}} + \if{html}{\out{}} + \if{html}{\out{}} } } }