Skip to content

Commit 24d91dd

Browse files
vedhavm7prgithub-actions[bot]
authored
Remove "default" decoration and use the same way of decoration in all modules (#846)
Closes #845 Changes: 1. Removes the ability to have a "default" decoration applied to all output objects. 2. Makes sure that all our modules follow the same decoration format: `decorators = list(output_name = teal_transform_module(...))` 3. Improve the error message so the user knows that they have to provide the names from the available list of names. <details> <summary>Decorator examples that should be working</summary> ```r 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") { print(.var_to_replace) 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( # #################### # # # # _ __ ___ __ _ # | '_ \ / __/ _` | # | |_) | (_| (_| | # | .__/ \___\__,_| # | | # |_| # # 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( elbow_plot = caption_decorator("I am a elbow_plot", "elbow_plot"), circle_plot = caption_decorator("I am a circle_plot", "circle_plot"), biplot = caption_decorator("I am a biplot", "biplot"), eigenvector_plot = caption_decorator("I am a eigenvector_plot", "eigenvector_plot") ) ), ############################################################################### # # _ __ ___ __ _ _ __ ___ ___ ___(_) ___ _ __ # | '__/ _ \/ _` | '__/ _ \/ __/ __| |/ _ \| '_ \ # | | | __/ (_| | | | __/\__ \__ \ | (_) | | | | # |_| \___|\__, |_| \___||___/___/_|\___/|_| |_| # __|_| # # regression # ############################################################################### tm_a_regression( label = "Regression", response = data_extract_spec( dataname = "ADSL", select = select_spec( label = "Select variable:", choices = "BMRKR1", selected = "BMRKR1", multiple = FALSE, fixed = TRUE ) ), regressor = data_extract_spec( dataname = "ADSL", select = select_spec( label = "Select variables:", choices = variable_choices(data[["ADSL"]], c("AGE", "SEX", "RACE")), selected = "AGE", multiple = TRUE, fixed = FALSE ) ), decorators = list( plot = caption_decorator("I am a Regression", "plot") ) ), # ####################################################### # # _ _ _ # (_) | | (_) # __ _ ___ ___ ___ ___ _ __ _| |_ _ ___ _ __ # / _` / __/ __|/ _ \ / __| |/ _` | __| |/ _ \| '_ \ # | (_| \__ \__ \ (_) | (__| | (_| | |_| | (_) | | | | # \__,_|___/___/\___/ \___|_|\__,_|\__|_|\___/|_| |_| # # # # 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 = plot_grob_decorator("I am a good grob (association)") ) ), # ############################################ # # _ _ _ _ # | | (_) (_) | | # | |__ ___ ____ _ _ __ _ __ _| |_ ___ # | '_ \| \ \ / / _` | '__| |/ _` | __/ _ \ # | |_) | |\ 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( plot = caption_decorator("I am a Bivariate", "plot") ) ), ############################################################################### # # _ _ _ _ _ _ _ # __| (_)___| |_ _ __(_) |__ _ _| |_(_) ___ _ __ # / _` | / __| __| '__| | '_ \| | | | __| |/ _ \| '_ \ # | (_| | \__ \ |_| | | | |_) | |_| | |_| | (_) | | | | # \__,_|_|___/\__|_| |_|_.__/ \__,_|\__|_|\___/|_| |_| # # distribution ############################################################################### tm_g_distribution( dist_var = data_extract_spec( dataname = "ADSL", select = select_spec( choices = variable_choices(data[["ADSL"]], c("AGE", "BMRKR1")), selected = "BMRKR1", multiple = FALSE, fixed = FALSE ) ), strata_var = data_extract_spec( dataname = "ADSL", filter = filter_spec( vars = vars, multiple = TRUE ) ), group_var = data_extract_spec( dataname = "ADSL", filter = filter_spec( vars = vars, multiple = TRUE ) ), decorators = list( histogram_plot = caption_decorator("I am a Histogram", "histogram_plot"), qq_plot = caption_decorator("I am a QQ plot", "qq_plot"), summary_table = table_decorator("summary_table", .color1 = "#f0000055"), test_table = table_decorator("test_table", .color1 = "#f0000055") ) ), # ############################################# # # # # _ __ ___ ___ _ __ ___ _ __ ___ ___ # | '__/ _ \/ __| '_ \ / _ \| '_ \/ __|/ _ \ # | | | __/\__ \ |_) | (_) | | | \__ \ __/ # |_| \___||___/ .__/ \___/|_| |_|___/\___| # | | # |_| # # 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( plot = caption_decorator("I am a Response", "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( plot = caption_decorator("I am a scatterplot", "plot") ) ), # ####################################################################################### # # _ _ _ _ _ _ # | | | | | | | | | | (_) # ___ ___ __ _| |_| |_ ___ _ __ _ __ | | ___ | |_ _ __ ___ __ _| |_ _ __ ___ __ # / __|/ __/ _` | __| __/ _ \ '__| '_ \| |/ _ \| __| | '_ ` _ \ / _` | __| '__| \ \/ / # \__ \ (_| (_| | |_| || __/ | | |_) | | (_) | |_ | | | | | | (_| | |_| | | |> < # |___/\___\__,_|\__|\__\___|_| | .__/|_|\___/ \__| |_| |_| |_|\__,_|\__|_| |_/_/\_\ # | | # |_| # # 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( plot = treelis_subtitle_decorator("I am a Scatterplot matrix", "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("I am a by_subject_plot", "by_subject_plot") ) ), ###################################### # # _ _ _ # | | | (_) # ___ _ _| |_| |_ ___ _ __ ___ # / _ \| | | | __| | |/ _ \ '__/ __| # | (_) | |_| | |_| | | __/ | \__ \ # \___/ \__,_|\__|_|_|\___|_| |___/ # # # # 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") ) ), # ######################################################## # # _ _ _ # | | | | | | # ___ _ __ ___ ___ ___ ______| |_ __ _| |__ | | ___ # / __| '__/ _ \/ __/ __|______| __/ _` | '_ \| |/ _ \ # | (__| | | (_) \__ \__ \ | || (_| | |_) | | __/ # \___|_| \___/|___/___/ \__\__,_|_.__/|_|\___| # # # # 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( table = insert_rrow_decorator("I am a good new row") ) ) ) ) |> shiny::runApp() ``` </details> --------- Co-authored-by: m7pr <[email protected]> Co-authored-by: github-actions <41898282+github-actions[bot]@users.noreply.github.com>
1 parent 8c092aa commit 24d91dd

28 files changed

+260
-162
lines changed

R/tm_a_pca.R

Lines changed: 6 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -25,20 +25,18 @@
2525
#' - `biplot` (`ggplot2`)
2626
#' - `eigenvector_plot` (`ggplot2`)
2727
#'
28-
#' Decorators can be applied to all outputs or only to specific objects using a
29-
#' named list of `teal_transform_module` objects.
30-
#' The `"default"` name is reserved for decorators that are applied to all outputs.
28+
#' A Decorator is applied to the specific output using a named list of `teal_transform_module` objects.
29+
#' The name of this list corresponds to the name of the output to which the decorator is applied.
3130
#' See code snippet below:
3231
#'
3332
#' ```
3433
#' tm_a_pca(
3534
#' ..., # arguments for module
3635
#' decorators = list(
37-
#' default = list(teal_transform_module(...)), # applied to all outputs
38-
#' elbow_plot = list(teal_transform_module(...)), # applied only to `elbow_plot` output
39-
#' circle_plot = list(teal_transform_module(...)) # applied only to `circle_plot` output
40-
#' biplot = list(teal_transform_module(...)) # applied only to `biplot` output
41-
#' eigenvector_plot = list(teal_transform_module(...)) # applied only to `eigenvector_plot` output
36+
#' elbow_plot = teal_transform_module(...), # applied to the `elbow_plot` output
37+
#' circle_plot = teal_transform_module(...), # applied to the `circle_plot` output
38+
#' biplot = teal_transform_module(...), # applied to the `biplot` output
39+
#' eigenvector_plot = teal_transform_module(...) # applied to the `eigenvector_plot` output
4240
#' )
4341
#' )
4442
#' ```
@@ -186,9 +184,7 @@ tm_a_pca <- function(label = "Principal Component Analysis",
186184
checkmate::assert_multi_class(post_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE)
187185

188186
available_decorators <- c("elbow_plot", "circle_plot", "biplot", "eigenvector_plot")
189-
decorators <- normalize_decorators(decorators)
190187
assert_decorators(decorators, available_decorators)
191-
# End of assertions
192188

193189
# Make UI args
194190
args <- as.list(environment())

R/tm_a_regression.R

Lines changed: 13 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -48,6 +48,19 @@
4848
#' This module generates the following objects, which can be modified in place using decorators:
4949
#' - `plot` (`ggplot2`)
5050
#'
51+
#' A Decorator is applied to the specific output using a named list of `teal_transform_module` objects.
52+
#' The name of this list corresponds to the name of the output to which the decorator is applied.
53+
#' See code snippet below:
54+
#'
55+
#' ```
56+
#' tm_a_regression(
57+
#' ..., # arguments for module
58+
#' decorators = list(
59+
#' plot = teal_transform_module(...) # applied to the `plot` output
60+
#' )
61+
#' )
62+
#' ```
63+
#'
5164
#' For additional details and examples of decorators, refer to the vignette
5265
#' `vignette("decorate-modules-output", package = "teal")` or the [`teal::teal_transform_module()`] documentation.
5366
#'
@@ -225,7 +238,6 @@ tm_a_regression <- function(label = "Regression Analysis",
225238
.var.name = "label_segment_threshold"
226239
)
227240
}
228-
decorators <- normalize_decorators(decorators)
229241
assert_decorators(decorators, "plot")
230242
# End of assertions
231243

R/tm_g_association.R

Lines changed: 13 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,19 @@
2929
#' This module generates the following objects, which can be modified in place using decorators:
3030
#' - `plot` (`grob` created with [ggplot2::ggplotGrob()])
3131
#'
32+
#' A Decorator is applied to the specific output using a named list of `teal_transform_module` objects.
33+
#' The name of this list corresponds to the name of the output to which the decorator is applied.
34+
#' See code snippet below:
35+
#'
36+
#' ```
37+
#' tm_g_association(
38+
#' ..., # arguments for module
39+
#' decorators = list(
40+
#' plot = teal_transform_module(...) # applied to the `plot` output
41+
#' )
42+
#' )
43+
#' ```
44+
#'
3245
#' For additional details and examples of decorators, refer to the vignette
3346
#' `vignette("decorate-modules-output", package = "teal")` or the [`teal::teal_transform_module()`] documentation.
3447
#'
@@ -176,7 +189,6 @@ tm_g_association <- function(label = "Association",
176189
checkmate::assert_list(ggplot2_args, types = "ggplot2_args")
177190
checkmate::assert_subset(names(ggplot2_args), c("default", plot_choices))
178191

179-
decorators <- normalize_decorators(decorators)
180192
assert_decorators(decorators, "plot")
181193
# End of assertions
182194

R/tm_g_bivariate.R

Lines changed: 13 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -51,6 +51,19 @@
5151
#' This module generates the following objects, which can be modified in place using decorators:
5252
#' - `plot` (`ggplot2`)
5353
#'
54+
#' A Decorator is applied to the specific output using a named list of `teal_transform_module` objects.
55+
#' The name of this list corresponds to the name of the output to which the decorator is applied.
56+
#' See code snippet below:
57+
#'
58+
#' ```
59+
#' tm_g_bivariate(
60+
#' ..., # arguments for module
61+
#' decorators = list(
62+
#' plot = teal_transform_module(...) # applied to the `plot` output
63+
#' )
64+
#' )
65+
#' ```
66+
#'
5467
#' For additional details and examples of decorators, refer to the vignette
5568
#' `vignette("decorate-modules-output", package = "teal")` or the [`teal::teal_transform_module()`] documentation.
5669
#'
@@ -277,7 +290,6 @@ tm_g_bivariate <- function(label = "Bivariate Plots",
277290
checkmate::assert_multi_class(pre_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE)
278291
checkmate::assert_multi_class(post_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE)
279292

280-
decorators <- normalize_decorators(decorators)
281293
assert_decorators(decorators, "plot")
282294
# End of assertions
283295

R/tm_g_distribution.R

Lines changed: 6 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -34,20 +34,18 @@
3434
#' - `summary_table` (`listing_df` created with [rlistings::as_listing()])
3535
#' - `test_table` (`listing_df` created with [rlistings::as_listing()])
3636
#'
37-
#' Decorators can be applied to all outputs or only to specific objects using a
38-
#' named list of `teal_transform_module` objects.
39-
#' The `"default"` name is reserved for decorators that are applied to all outputs.
37+
#' A Decorator is applied to the specific output using a named list of `teal_transform_module` objects.
38+
#' The name of this list corresponds to the name of the output to which the decorator is applied.
4039
#' See code snippet below:
4140
#'
4241
#' ```
4342
#' tm_g_distribution(
4443
#' ..., # arguments for module
4544
#' decorators = list(
46-
#' default = list(teal_transform_module(...)), # applied to all outputs
47-
#' histogram_plot = list(teal_transform_module(...)), # applied only to `histogram_plot` output
48-
#' qq_plot = list(teal_transform_module(...)) # applied only to `qq_plot` output
49-
#' summary_table = list(teal_transform_module(...)) # applied only to `summary_table` output
50-
#' test_table = list(teal_transform_module(...)) # applied only to `test_table` output
45+
#' histogram_plot = teal_transform_module(...), # applied only to `histogram_plot` output
46+
#' qq_plot = teal_transform_module(...), # applied only to `qq_plot` output
47+
#' summary_table = teal_transform_module(...), # applied only to `summary_table` output
48+
#' test_table = teal_transform_module(...) # applied only to `test_table` output
5149
#' )
5250
#' )
5351
#' ```
@@ -194,7 +192,6 @@ tm_g_distribution <- function(label = "Distribution Module",
194192
checkmate::assert_multi_class(post_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE)
195193

196194
available_decorators <- c("histogram_plot", "qq_plot", "test_table", "summary_table")
197-
decorators <- normalize_decorators(decorators)
198195
assert_decorators(decorators, names = available_decorators)
199196

200197
# End of assertions

R/tm_g_response.R

Lines changed: 13 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -44,6 +44,19 @@
4444
#' This module generates the following objects, which can be modified in place using decorators:
4545
#' - `plot` (`ggplot2`)
4646
#'
47+
#' A Decorator is applied to the specific output using a named list of `teal_transform_module` objects.
48+
#' The name of this list corresponds to the name of the output to which the decorator is applied.
49+
#' See code snippet below:
50+
#'
51+
#' ```
52+
#' tm_g_response(
53+
#' ..., # arguments for module
54+
#' decorators = list(
55+
#' plot = teal_transform_module(...) # applied to the `plot` output
56+
#' )
57+
#' )
58+
#' ```
59+
#'
4760
#' For additional details and examples of decorators, refer to the vignette
4861
#' `vignette("decorate-modules-output", package = "teal")` or the [`teal::teal_transform_module()`] documentation.
4962
#'
@@ -202,7 +215,6 @@ tm_g_response <- function(label = "Response Plot",
202215
checkmate::assert_multi_class(pre_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE)
203216
checkmate::assert_multi_class(post_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE)
204217

205-
decorators <- normalize_decorators(decorators)
206218
assert_decorators(decorators, "plot")
207219
# End of assertions
208220

R/tm_g_scatterplot.R

Lines changed: 13 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -35,6 +35,19 @@
3535
#' This module generates the following objects, which can be modified in place using decorators:
3636
#' - `plot` (`ggplot2`)
3737
#'
38+
#' A Decorator is applied to the specific output using a named list of `teal_transform_module` objects.
39+
#' The name of this list corresponds to the name of the output to which the decorator is applied.
40+
#' See code snippet below:
41+
#'
42+
#' ```
43+
#' tm_g_scatterplot(
44+
#' ..., # arguments for module
45+
#' decorators = list(
46+
#' plot = teal_transform_module(...) # applied to the `plot` output
47+
#' )
48+
#' )
49+
#' ```
50+
#'
3851
#' For additional details and examples of decorators, refer to the vignette
3952
#' `vignette("decorate-modules-output", package = "teal")` or the [`teal::teal_transform_module()`] documentation.
4053
#'
@@ -299,7 +312,6 @@ tm_g_scatterplot <- function(label = "Scatterplot",
299312
checkmate::assert_scalar(table_dec)
300313
checkmate::assert_class(ggplot2_args, "ggplot2_args")
301314

302-
decorators <- normalize_decorators(decorators)
303315
assert_decorators(decorators, "plot")
304316

305317
# End of assertions

R/tm_g_scatterplotmatrix.R

Lines changed: 13 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,19 @@
2323
#' This module generates the following objects, which can be modified in place using decorators:
2424
#' - `plot` (`trellis` - output of `lattice::splom`)
2525
#'
26+
#' A Decorator is applied to the specific output using a named list of `teal_transform_module` objects.
27+
#' The name of this list corresponds to the name of the output to which the decorator is applied.
28+
#' See code snippet below:
29+
#'
30+
#' ```
31+
#' tm_g_scatterplotmatrix(
32+
#' ..., # arguments for module
33+
#' decorators = list(
34+
#' plot = teal_transform_module(...) # applied to the `plot` output
35+
#' )
36+
#' )
37+
#' ```
38+
#'
2639
#' For additional details and examples of decorators, refer to the vignette
2740
#' `vignette("decorate-modules-output", package = "teal")` or the [`teal::teal_transform_module()`] documentation.
2841
#'
@@ -199,7 +212,6 @@ tm_g_scatterplotmatrix <- function(label = "Scatterplot Matrix",
199212
checkmate::assert_multi_class(pre_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE)
200213
checkmate::assert_multi_class(post_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE)
201214

202-
decorators <- normalize_decorators(decorators)
203215
assert_decorators(decorators, "plot")
204216
# End of assertions
205217

R/tm_missing_data.R

Lines changed: 9 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -25,20 +25,18 @@
2525
#' - `by_subject_plot` (`ggplot2`)
2626
#' - `table` (`listing_df` created with [rlistings::as_listing()])
2727
#'
28-
#' Decorators can be applied to all outputs or only to specific objects using a
29-
#' named list of `teal_transform_module` objects.
30-
#' The `"default"` name is reserved for decorators that are applied to all outputs.
28+
#' A Decorator is applied to the specific output using a named list of `teal_transform_module` objects.
29+
#' The name of this list corresponds to the name of the output to which the decorator is applied.
3130
#' See code snippet below:
3231
#'
3332
#' ```
3433
#' tm_missing_data(
3534
#' ..., # arguments for module
3635
#' decorators = list(
37-
#' default = list(teal_transform_module(...)), # applied to all outputs
38-
#' summary_plot = list(teal_transform_module(...)), # applied only to `summary_plot` output
39-
#' combination_plot = list(teal_transform_module(...)) # applied only to `combination_plot` output
40-
#' by_subject_plot = list(teal_transform_module(...)) # applied only to `by_subject_plot` output
41-
#' table = list(teal_transform_module(...)) # applied only to `table` output
36+
#' summary_plot = teal_transform_module(...), # applied only to `summary_plot` output
37+
#' combination_plot = teal_transform_module(...), # applied only to `combination_plot` output
38+
#' by_subject_plot = teal_transform_module(...), # applied only to `by_subject_plot` output
39+
#' table = teal_transform_module(...) # applied only to `table` output
4240
#' )
4341
#' )
4442
#' ```
@@ -147,8 +145,7 @@ tm_missing_data <- function(label = "Missing data",
147145
checkmate::assert_multi_class(pre_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE)
148146
checkmate::assert_multi_class(post_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE)
149147

150-
available_decorators <- c("summary_plot", "combination_plot", "by_subject_plot", "summary_table")
151-
decorators <- normalize_decorators(decorators)
148+
available_decorators <- c("summary_plot", "combination_plot", "by_subject_plot", "table")
152149
assert_decorators(decorators, names = available_decorators)
153150
# End of assertions
154151

@@ -446,7 +443,7 @@ encoding_missing_data <- function(id, summary_per_patient = FALSE, ggtheme, data
446443
selected = "counts",
447444
inline = TRUE
448445
),
449-
ui_decorate_teal_data(ns("dec_summary_table"), decorators = select_decorators(decorators, "summary_table"))
446+
ui_decorate_teal_data(ns("dec_summary_table"), decorators = select_decorators(decorators, "table"))
450447
),
451448
teal.widgets::panel_item(
452449
title = "Plot settings",
@@ -1295,7 +1292,7 @@ srv_missing_data <- function(id,
12951292
decorated_summary_table_q <- srv_decorate_teal_data(
12961293
id = "dec_summary_table",
12971294
data = summary_table_q,
1298-
decorators = select_decorators(decorators, "summary_table"),
1295+
decorators = select_decorators(decorators, "table"),
12991296
expr = table
13001297
)
13011298

R/tm_outliers.R

Lines changed: 6 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -23,20 +23,18 @@
2323
#' - `cumulative_plot` (`ggplot2`)
2424
#' - `table` (`listing_df` created with [rlistings::as_listing()])
2525
#'
26-
#' Decorators can be applied to all outputs or only to specific objects using a
27-
#' named list of `teal_transform_module` objects.
28-
#' The `"default"` name is reserved for decorators that are applied to all outputs.
26+
#' A Decorator is applied to the specific output using a named list of `teal_transform_module` objects.
27+
#' The name of this list corresponds to the name of the output to which the decorator is applied.
2928
#' See code snippet below:
3029
#'
3130
#' ```
3231
#' tm_outliers(
3332
#' ..., # arguments for module
3433
#' decorators = list(
35-
#' default = list(teal_transform_module(...)), # applied to all outputs
36-
#' box_plot = list(teal_transform_module(...)), # applied only to `box_plot` output
37-
#' density_plot = list(teal_transform_module(...)) # applied only to `density_plot` output
38-
#' cumulative_plot = list(teal_transform_module(...)) # applied only to `cumulative_plot` output
39-
#' table = list(teal_transform_module(...)) # applied only to `table` output
34+
#' box_plot = teal_transform_module(...), # applied only to `box_plot` output
35+
#' density_plot = teal_transform_module(...), # applied only to `density_plot` output
36+
#' cumulative_plot = teal_transform_module(...), # applied only to `cumulative_plot` output
37+
#' table = teal_transform_module(...) # applied only to `table` output
4038
#' )
4139
#' )
4240
#' ```
@@ -197,7 +195,6 @@ tm_outliers <- function(label = "Outliers Module",
197195
checkmate::assert_multi_class(post_output, c("shiny.tag", "shiny.tag.list", "html"), null.ok = TRUE)
198196

199197
available_decorators <- c("box_plot", "density_plot", "cumulative_plot", "table")
200-
decorators <- normalize_decorators(decorators)
201198
assert_decorators(decorators, names = available_decorators)
202199
# End of assertions
203200

0 commit comments

Comments
 (0)