diff --git a/R/tm_g_pp_adverse_events.R b/R/tm_g_pp_adverse_events.R index 95f1356da..38e69e67f 100644 --- a/R/tm_g_pp_adverse_events.R +++ b/R/tm_g_pp_adverse_events.R @@ -47,7 +47,7 @@ template_adverse_events <- function(dataname = "ANL", list(), substitute( expr = { - table <- dataname %>% + table_data <- dataname %>% dplyr::select( aeterm, tox_grade, causality, outcome, action, time, decod ) %>% @@ -63,9 +63,7 @@ template_adverse_events <- function(dataname = "ANL", key_cols = NULL, default_formatting = list(all = fmt_config(align = "left")) ) - main_title(table) <- paste("Patient ID:", patient_id) - - table + main_title(table_output) <- paste("Patient ID:", patient_id) }, env = list( dataname = as.name(dataname), @@ -110,7 +108,7 @@ template_adverse_events <- function(dataname = "ANL", chart_list <- add_expr( list(), substitute( - expr = plot <- dataname %>% + expr = plot_output <- dataname %>% dplyr::select(aeterm, time, tox_grade, causality) %>% dplyr::mutate(ATOXGR = as.character(tox_grade)) %>% dplyr::arrange(dplyr::desc(ATOXGR)) %>% @@ -156,11 +154,6 @@ template_adverse_events <- function(dataname = "ANL", ) ) - chart_list <- add_expr( - expr_ls = chart_list, - new_expr = quote(plot) - ) - y$table <- bracket_expr(table_list) y$chart <- bracket_expr(chart_list) @@ -187,9 +180,35 @@ template_adverse_events <- function(dataname = "ANL", #' available choices and preselected option for the `ASTDY` variable from `dataname`. #' @param decod ([teal.transform::choices_selected()])\cr object with all #' available choices and preselected option for the `AEDECOD` variable from `dataname`. +#' @param decorators `r roxygen_decorators_param("tm_g_pp_adverse_events")` #' #' @inherit module_arguments return #' +#' @section Decorating `tm_g_pp_adverse_events`: +#' +#' This module generates the following objects, which can be modified in place using decorators:: +#' - `plot` (`ggplot2`) +#' - `table` (`listing_df` - output of `rlistings::as_listing`) +#' +#' 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_pp_adverse_events( +#' ..., # arguments for module +#' decorators = list( +#' default = list(teal_transform_module(...)), # applied to all outputs +#' plot = list(teal_transform_module(...)), # applied only to `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. +#' #' @examplesShinylive #' library(teal.modules.clinical) #' interactive <- function() TRUE @@ -268,7 +287,8 @@ tm_g_pp_adverse_events <- function(label, plot_width = NULL, pre_output = NULL, post_output = NULL, - ggplot2_args = teal.widgets::ggplot2_args()) { + ggplot2_args = teal.widgets::ggplot2_args(), + decorators = NULL) { message("Initializing tm_g_pp_adverse_events") checkmate::assert_string(label) checkmate::assert_string(dataname) @@ -293,6 +313,8 @@ tm_g_pp_adverse_events <- function(label, checkmate::assert_class(pre_output, classes = "shiny.tag", null.ok = TRUE) checkmate::assert_class(post_output, classes = "shiny.tag", null.ok = TRUE) checkmate::assert_class(ggplot2_args, "ggplot2_args") + decorators <- normalize_decorators(decorators) + assert_decorators(decorators, names = c("plot", "table"), null.ok = TRUE) args <- as.list(environment()) data_extract_list <- list( @@ -319,7 +341,8 @@ tm_g_pp_adverse_events <- function(label, patient_col = patient_col, plot_height = plot_height, plot_width = plot_width, - ggplot2_args = ggplot2_args + ggplot2_args = ggplot2_args, + decorators = decorators ) ), datanames = c(dataname, parentname) @@ -408,6 +431,8 @@ ui_g_adverse_events <- function(id, ...) { is_single_dataset = is_single_dataset_value ) ), + ui_decorate_teal_data(ns("d_table"), decorators = select_decorators(ui_args$decorators, "table")), + ui_decorate_teal_data(ns("d_plot"), decorators = select_decorators(ui_args$decorators, "plot")), teal.widgets::panel_item( title = "Plot settings", collapsed = TRUE, @@ -445,7 +470,8 @@ srv_g_adverse_events <- function(id, plot_height, plot_width, label, - ggplot2_args) { + ggplot2_args, + decorators) { with_reporter <- !missing(reporter) && inherits(reporter, "Reporter") with_filter <- !missing(filter_panel_api) && inherits(filter_panel_api, "FilterPanelAPI") checkmate::assert_class(data, "reactive") @@ -564,14 +590,29 @@ srv_g_adverse_events <- function(id, paste("
Patient ID:", all_q()[["pt_id"]], "
") }) - output$table <- DT::renderDataTable( - expr = teal.code::dev_suppress(all_q()[["table"]]), - options = list(pageLength = input$table_rows) + # Allow for the table and plot qenv to be joined + table_q <- reactive(within(all_q(), table <- table_output)) + plot_q <- reactive(within(all_q(), plot <- plot_output)) + + decorated_all_q_table <- srv_decorate_teal_data( + "d_table", + data = table_q, + decorators = select_decorators(decorators, "table"), + expr = table + ) + + decorated_all_q_plot <- srv_decorate_teal_data( + "d_plot", + data = plot_q, + decorators = select_decorators(decorators, "plot"), + expr = print(plot) ) + table_r <- reactive(teal.code::dev_suppress(decorated_all_q_table()[["table"]])) + plot_r <- reactive({ req(iv_r()$is_valid()) - all_q()[["plot"]] + decorated_all_q_plot()[["plot"]] }) pws <- teal.widgets::plot_with_settings_srv( @@ -581,9 +622,18 @@ srv_g_adverse_events <- function(id, width = plot_width ) + output$table <- DT::renderDataTable( + expr = table_r(), + options = list(pageLength = input$table_rows) + ) + + decorated_all_q <- reactive( + c(decorated_all_q_table(), decorated_all_q_plot()) + ) + teal.widgets::verbatim_popup_srv( id = "rcode", - verbatim_content = reactive(teal.code::get_code(all_q())), + verbatim_content = reactive(teal.code::get_code(req(decorated_all_q()))), title = label ) @@ -597,14 +647,14 @@ srv_g_adverse_events <- function(id, filter_panel_api = filter_panel_api ) card$append_text("Table", "header3") - card$append_table(teal.code::dev_suppress(all_q()[["table"]])) + card$append_table(teal.code::dev_suppress(table_r())) card$append_text("Plot", "header3") card$append_plot(plot_r(), dim = pws$dim()) if (!comment == "") { card$append_text("Comment", "header3") card$append_text(comment) } - card$append_src(teal.code::get_code(all_q())) + card$append_src(teal.code::get_code(req(decorated_all_q()))) card } teal.reporter::simple_reporter_srv("simple_reporter", reporter = reporter, card_fun = card_fun) diff --git a/R/tm_t_logistic.R b/R/tm_t_logistic.R index b0101dd1b..40563a000 100644 --- a/R/tm_t_logistic.R +++ b/R/tm_t_logistic.R @@ -186,14 +186,13 @@ template_logistic <- function(dataname, y$table <- substitute( expr = { - result <- expr_basic_table_args %>% + table <- expr_basic_table_args %>% summarize_logistic( conf_level = conf_level, drop_and_remove_str = "_NA_" ) %>% rtables::append_topleft(topleft) %>% rtables::build_table(df = mod) - result }, env = list( expr_basic_table_args = parsed_basic_table_args, @@ -222,6 +221,14 @@ template_logistic <- function(dataname, #' #' @inherit module_arguments return seealso #' +#' @section Decorating Module: +#' +#' This module generates the following objects, which can be modified in place using decorators: +#' - `table` (`ElementaryTable` - output of `rtables::build_table`) +#' +#' 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.clinical) #' interactive <- function() TRUE @@ -297,7 +304,8 @@ tm_t_logistic <- function(label, conf_level = teal.transform::choices_selected(c(0.95, 0.9, 0.8), 0.95, keep_order = TRUE), pre_output = NULL, post_output = NULL, - basic_table_args = teal.widgets::basic_table_args()) { + basic_table_args = teal.widgets::basic_table_args(), + decorators = NULL) { message("Initializing tm_t_logistic") checkmate::assert_string(label) checkmate::assert_string(dataname) @@ -311,6 +319,8 @@ tm_t_logistic <- function(label, checkmate::assert_class(pre_output, classes = "shiny.tag", null.ok = TRUE) checkmate::assert_class(post_output, classes = "shiny.tag", null.ok = TRUE) checkmate::assert_class(basic_table_args, "basic_table_args") + decorators <- normalize_decorators(decorators) + assert_decorators(decorators, null.ok = TRUE, "table") args <- as.list(environment()) @@ -333,7 +343,8 @@ tm_t_logistic <- function(label, label = label, dataname = dataname, parentname = parentname, - basic_table_args = basic_table_args + basic_table_args = basic_table_args, + decorators = decorators ) ), datanames = teal.transform::get_extract_datanames(data_extract_list) @@ -424,7 +435,8 @@ ui_t_logistic <- function(id, ...) { a$conf_level$selected, multiple = FALSE, fixed = a$conf_level$fixed - ) + ), + ui_decorate_teal_data(ns("decorator"), decorators = select_decorators(a$decorators, "table")) ), forms = tagList( teal.widgets::verbatim_popup_ui(ns("rcode"), button_label = "Show R code") @@ -447,7 +459,8 @@ srv_t_logistic <- function(id, avalc_var, cov_var, label, - basic_table_args) { + basic_table_args, + decorators) { with_reporter <- !missing(reporter) && inherits(reporter, "Reporter") with_filter <- !missing(filter_panel_api) && inherits(filter_panel_api, "FilterPanelAPI") checkmate::assert_class(data, "reactive") @@ -659,6 +672,7 @@ srv_t_logistic <- function(id, ) }) + # Generate r code for the analysis. all_q <- reactive({ validate_checks() @@ -696,16 +710,26 @@ srv_t_logistic <- function(id, teal.code::eval_code(merged$anl_q(), as.expression(calls)) }) - table_r <- reactive(all_q()[["result"]]) + # Decoration of table output. + decorated_table_q <- srv_decorate_teal_data( + id = "decorator", + data = all_q, + decorators = select_decorators(decorators, "table"), + expr = table + ) + + table_r <- reactive(decorated_table_q()[["table"]]) teal.widgets::table_with_settings_srv( id = "table", table_r = table_r ) + # Render R code. + source_code_r <- reactive(teal.code::get_code(req(decorated_table_q()))) teal.widgets::verbatim_popup_srv( id = "rcode", - verbatim_content = reactive(teal.code::get_code(all_q())), + verbatim_content = source_code_r, title = label ) @@ -724,7 +748,7 @@ srv_t_logistic <- function(id, card$append_text("Comment", "header3") card$append_text(comment) } - card$append_src(teal.code::get_code(all_q())) + card$append_src(source_code_r()) card } teal.reporter::simple_reporter_srv("simple_reporter", reporter = reporter, card_fun = card_fun) diff --git a/R/tm_t_pp_medical_history.R b/R/tm_t_pp_medical_history.R index b73235d39..881e77725 100644 --- a/R/tm_t_pp_medical_history.R +++ b/R/tm_t_pp_medical_history.R @@ -40,7 +40,7 @@ template_medical_history <- function(dataname = "ANL", dplyr::distinct() %>% `colnames<-`(labels) - result <- rtables::basic_table() %>% + table <- rtables::basic_table() %>% rtables::split_cols_by_multivar(colnames(result_raw)[2:3]) %>% rtables::split_rows_by( colnames(result_raw)[1], @@ -54,9 +54,7 @@ template_medical_history <- function(dataname = "ANL", rtables::analyze_colvars(function(x) x[seq_along(x)]) %>% rtables::build_table(result_raw) - main_title(result) <- paste("Patient ID:", patient_id) - - result + main_title(table) <- paste("Patient ID:", patient_id) }, env = list( dataname = as.name(dataname), mhbodsys = as.name(mhbodsys), @@ -88,6 +86,13 @@ template_medical_history <- function(dataname = "ANL", #' available choices and preselected option for the `MHDISTAT` variable from `dataname`. #' #' @inherit module_arguments return +#' @section Decorating Module: +#' +#' This module generates the following objects, which can be modified in place using decorators: +#' - `table` (`TableTree` - output of `rtables::build_table`) +#' +#' 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.clinical) @@ -141,7 +146,8 @@ tm_t_pp_medical_history <- function(label, mhbodsys = NULL, mhdistat = NULL, pre_output = NULL, - post_output = NULL) { + post_output = NULL, + decorators = NULL) { message("Initializing tm_t_pp_medical_history") checkmate::assert_string(label) checkmate::assert_string(dataname) @@ -152,6 +158,8 @@ tm_t_pp_medical_history <- function(label, checkmate::assert_class(mhdistat, "choices_selected", null.ok = TRUE) checkmate::assert_class(pre_output, classes = "shiny.tag", null.ok = TRUE) checkmate::assert_class(post_output, classes = "shiny.tag", null.ok = TRUE) + decorators <- normalize_decorators(decorators) + assert_decorators(decorators, null.ok = TRUE, "table") args <- as.list(environment()) data_extract_list <- list( @@ -171,7 +179,8 @@ tm_t_pp_medical_history <- function(label, dataname = dataname, parentname = parentname, label = label, - patient_col = patient_col + patient_col = patient_col, + decorators = decorators ) ), datanames = c(dataname, parentname) @@ -221,7 +230,8 @@ ui_t_medical_history <- function(id, ...) { label = "Select MHDISTAT variable:", data_extract_spec = ui_args$mhdistat, is_single_dataset = is_single_dataset_value - ) + ), + ui_decorate_teal_data(ns("decorator"), decorators = select_decorators(ui_args$decorators, "table")) ), forms = tagList( teal.widgets::verbatim_popup_ui(ns("rcode"), button_label = "Show R code") @@ -242,7 +252,8 @@ srv_t_medical_history <- function(id, mhterm, mhbodsys, mhdistat, - label) { + label, + decorators) { with_reporter <- !missing(reporter) && inherits(reporter, "Reporter") with_filter <- !missing(filter_panel_api) && inherits(filter_panel_api, "FilterPanelAPI") checkmate::assert_class(data, "reactive") @@ -303,6 +314,7 @@ srv_t_medical_history <- function(id, teal.code::eval_code(as.expression(anl_inputs()$expr)) }) + # Generate r code for the analysis. all_q <- reactive({ teal::validate_inputs(iv_r()) @@ -335,16 +347,27 @@ srv_t_medical_history <- function(id, teal.code::eval_code(as.expression(unlist(my_calls))) }) - table_r <- reactive(all_q()[["result"]]) + # Decoration of table output. + decorated_table_q <- srv_decorate_teal_data( + id = "decorator", + data = all_q, + decorators = select_decorators(decorators, "table"), + expr = table + ) + + # Outputs to render. + table_r <- reactive(decorated_table_q()[["table"]]) teal.widgets::table_with_settings_srv( id = "table", table_r = table_r ) + # Render R code. + source_code_r <- reactive(teal.code::get_code(req(decorated_table_q()))) teal.widgets::verbatim_popup_srv( id = "rcode", - verbatim_content = reactive(teal.code::get_code(all_q())), + verbatim_content = source_code_r, title = label ) @@ -363,7 +386,7 @@ srv_t_medical_history <- function(id, card$append_text("Comment", "header3") card$append_text(comment) } - card$append_src(teal.code::get_code(all_q())) + card$append_src(source_code_r()) card } teal.reporter::simple_reporter_srv("simple_reporter", reporter = reporter, card_fun = card_fun) diff --git a/R/tm_t_shift_by_grade.R b/R/tm_t_shift_by_grade.R index f45ec5372..97256f3f6 100644 --- a/R/tm_t_shift_by_grade.R +++ b/R/tm_t_shift_by_grade.R @@ -449,9 +449,8 @@ template_shift_by_grade <- function(parentname, y$table <- substitute( expr = { - result <- rtables::build_table(lyt = lyt, df = anl, alt_counts_df = parent) %>% + table <- rtables::build_table(lyt = lyt, df = anl, alt_counts_df = parent) %>% rtables::prune_table() - result }, env = list(parent = as.name(parentname)) ) @@ -472,6 +471,14 @@ template_shift_by_grade <- function(parentname, #' #' @inherit module_arguments return seealso #' +#' @section Decorating Module: +#' +#' This module generates the following objects, which can be modified in place using decorators: +#' - `table` (`TableTree` - output of `rtables::build_table`) +#' +#' 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.clinical) #' interactive <- function() TRUE @@ -572,7 +579,8 @@ tm_t_shift_by_grade <- function(label, post_output = NULL, na_level = default_na_str(), code_missing_baseline = FALSE, - basic_table_args = teal.widgets::basic_table_args()) { + basic_table_args = teal.widgets::basic_table_args(), + decorators = NULL) { message("Initializing tm_t_shift_by_grade") checkmate::assert_string(label) checkmate::assert_string(dataname) @@ -593,6 +601,8 @@ tm_t_shift_by_grade <- function(label, checkmate::assert_class(pre_output, classes = "shiny.tag", null.ok = TRUE) checkmate::assert_class(post_output, classes = "shiny.tag", null.ok = TRUE) checkmate::assert_class(basic_table_args, "basic_table_args") + decorators <- normalize_decorators(decorators) + assert_decorators(decorators, null.ok = TRUE, "table") args <- as.list(environment()) @@ -619,7 +629,8 @@ tm_t_shift_by_grade <- function(label, label = label, total_label = total_label, na_level = na_level, - basic_table_args = basic_table_args + basic_table_args = basic_table_args, + decorators = decorators ) ), datanames = teal.transform::get_extract_datanames(data_extract_list) @@ -704,6 +715,7 @@ ui_t_shift_by_grade <- function(id, ...) { ) ) ), + ui_decorate_teal_data(ns("decorator"), decorators = select_decorators(a$decorators, "table")), teal.widgets::panel_group( teal.widgets::panel_item( "Additional Variables Info", @@ -751,7 +763,8 @@ srv_t_shift_by_grade <- function(id, drop_arm_levels, na_level, label, - basic_table_args) { + basic_table_args, + decorators) { with_reporter <- !missing(reporter) && inherits(reporter, "Reporter") with_filter <- !missing(filter_panel_api) && inherits(filter_panel_api, "FilterPanelAPI") checkmate::assert_class(data, "reactive") @@ -840,6 +853,7 @@ srv_t_shift_by_grade <- function(id, ) }) + # Generate r code for the analysis. all_q <- reactive({ validate_checks() @@ -865,8 +879,16 @@ srv_t_shift_by_grade <- function(id, teal.code::eval_code(merged$anl_q(), as.expression(unlist(my_calls))) }) + # Decoration of table output. + decorated_table_q <- srv_decorate_teal_data( + id = "decorator", + data = all_q, + decorators = select_decorators(decorators, "table"), + expr = table + ) + # Outputs to render. - table_r <- reactive(all_q()[["result"]]) + table_r <- reactive(decorated_table_q()[["table"]]) teal.widgets::table_with_settings_srv( id = "table", @@ -874,9 +896,10 @@ srv_t_shift_by_grade <- function(id, ) # Render R code. + source_code_r <- reactive(teal.code::get_code(req(decorated_table_q()))) teal.widgets::verbatim_popup_srv( id = "rcode", - verbatim_content = reactive(teal.code::get_code(all_q())), + verbatim_content = source_code_r, title = label ) @@ -895,7 +918,7 @@ srv_t_shift_by_grade <- function(id, card$append_text("Comment", "header3") card$append_text(comment) } - card$append_src(teal.code::get_code(all_q())) + card$append_src(source_code_r()) card } teal.reporter::simple_reporter_srv("simple_reporter", reporter = reporter, card_fun = card_fun) diff --git a/R/tm_t_smq.R b/R/tm_t_smq.R index e1081cdec..b79251aca 100644 --- a/R/tm_t_smq.R +++ b/R/tm_t_smq.R @@ -290,8 +290,7 @@ template_smq <- function(dataname, all_zero <- function(tr) { !inherits(tr, "ContentRow") && rtables::all_zero_or_na(tr) } - pruned_and_sorted_result <- sorted_result %>% rtables::trim_rows(criteria = all_zero) - pruned_and_sorted_result + table <- sorted_result %>% rtables::trim_rows(criteria = all_zero) } ) @@ -316,6 +315,14 @@ template_smq <- function(dataname, #' #' @inherit module_arguments return seealso #' +#' @section Decorating Module: +#' +#' This module generates the following objects, which can be modified in place using decorators: +#' - `table` (`TableTree` - output of `rtables::build_table`) +#' +#' 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.clinical) #' interactive <- function() TRUE @@ -391,7 +398,8 @@ tm_t_smq <- function(label, scopes, pre_output = NULL, post_output = NULL, - basic_table_args = teal.widgets::basic_table_args()) { + basic_table_args = teal.widgets::basic_table_args(), + decorators = NULL) { message("Initializing tm_t_smq") checkmate::assert_string(label) checkmate::assert_string(dataname) @@ -408,6 +416,8 @@ tm_t_smq <- function(label, checkmate::assert_class(pre_output, classes = "shiny.tag", null.ok = TRUE) checkmate::assert_class(post_output, classes = "shiny.tag", null.ok = TRUE) checkmate::assert_class(basic_table_args, "basic_table_args") + decorators <- normalize_decorators(decorators) + assert_decorators(decorators, null.ok = TRUE, "table") args <- as.list(environment()) @@ -432,7 +442,8 @@ tm_t_smq <- function(label, na_level = na_level, label = label, total_label = total_label, - basic_table_args = basic_table_args + basic_table_args = basic_table_args, + decorators = decorators ) ), datanames = teal.transform::get_extract_datanames(data_extract_list) @@ -444,7 +455,6 @@ ui_t_smq <- function(id, ...) { ns <- NS(id) a <- list(...) # module args - is_single_dataset_value <- teal.transform::is_single_dataset( a$arm_var, a$id_var, @@ -482,6 +492,7 @@ ui_t_smq <- function(id, ...) { data_extract_spec = a$baskets, is_single_dataset = is_single_dataset_value ), + ui_decorate_teal_data(ns("decorator"), decorators = select_decorators(a$decorators, "table")), teal.widgets::panel_group( teal.widgets::panel_item( "Additional Variables Info", @@ -540,7 +551,8 @@ srv_t_smq <- function(id, na_level, label, total_label, - basic_table_args) { + basic_table_args, + decorators) { with_reporter <- !missing(reporter) && inherits(reporter, "Reporter") with_filter <- !missing(filter_panel_api) && inherits(filter_panel_api, "FilterPanelAPI") checkmate::assert_class(data, "reactive") @@ -621,6 +633,7 @@ srv_t_smq <- function(id, ) }) + # Generate r code for the analysis. all_q <- reactive({ validate_checks() @@ -642,8 +655,16 @@ srv_t_smq <- function(id, teal.code::eval_code(merged$anl_q(), as.expression(unlist(my_calls))) }) + # Decoration of table output. + decorated_table_q <- srv_decorate_teal_data( + id = "decorator", + data = all_q, + decorators = select_decorators(decorators, "table"), + expr = table + ) + # Outputs to render. - table_r <- reactive(all_q()[["pruned_and_sorted_result"]]) + table_r <- reactive(decorated_table_q()[["table"]]) teal.widgets::table_with_settings_srv( id = "table", @@ -651,9 +672,10 @@ srv_t_smq <- function(id, ) # Render R code. + source_code_r <- reactive(teal.code::get_code(req(decorated_table_q()))) teal.widgets::verbatim_popup_srv( id = "rcode", - verbatim_content = reactive(teal.code::get_code(all_q())), + verbatim_content = source_code_r, title = label ) @@ -672,7 +694,7 @@ srv_t_smq <- function(id, card$append_text("Comment", "header3") card$append_text(comment) } - card$append_src(teal.code::get_code(all_q())) + card$append_src(source_code_r()) card } teal.reporter::simple_reporter_srv("simple_reporter", reporter = reporter, card_fun = card_fun) diff --git a/R/tm_t_summary.R b/R/tm_t_summary.R index 239558ada..c1f7b9f7d 100644 --- a/R/tm_t_summary.R +++ b/R/tm_t_summary.R @@ -199,8 +199,7 @@ template_summary <- function(dataname, y$table <- substitute( expr = { - result <- rtables::build_table(lyt = lyt, df = anl, alt_counts_df = parent) - result + table <- rtables::build_table(lyt = lyt, df = anl, alt_counts_df = parent) }, env = list(parent = as.name(parentname)) ) @@ -223,6 +222,14 @@ template_summary <- function(dataname, #' #' @inherit module_arguments return seealso #' +#' @section Decorating Module: +#' +#' This module generates the following objects, which can be modified in place using decorators: +#' - `table` (`TableTree` - output of `rtables::build_table`) +#' +#' 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.clinical) #' interactive <- function() TRUE @@ -281,7 +288,8 @@ tm_t_summary <- function(label, drop_arm_levels = TRUE, pre_output = NULL, post_output = NULL, - basic_table_args = teal.widgets::basic_table_args()) { + basic_table_args = teal.widgets::basic_table_args(), + decorators = NULL) { message("Initializing tm_t_summary") checkmate::assert_string(label) checkmate::assert_string(dataname) @@ -297,6 +305,8 @@ tm_t_summary <- function(label, checkmate::assert_flag(add_total) checkmate::assert_flag(show_arm_var_labels) checkmate::assert_string(total_label) + decorators <- normalize_decorators(decorators) + assert_decorators(decorators, null.ok = TRUE, "table") useNA <- match.arg(useNA) # nolint: object_name. denominator <- match.arg(denominator) @@ -323,7 +333,8 @@ tm_t_summary <- function(label, show_arm_var_labels = show_arm_var_labels, total_label = total_label, na_level = na_level, - basic_table_args = basic_table_args + basic_table_args = basic_table_args, + decorators = decorators ) ), datanames = c(dataname, parentname) @@ -404,7 +415,8 @@ ui_summary <- function(id, ...) { ) } ) - ) + ), + ui_decorate_teal_data(ns("decorator"), decorators = select_decorators(a$decorators, "table")) ), forms = tagList( teal.widgets::verbatim_popup_ui(ns("rcode"), button_label = "Show R code") @@ -429,7 +441,8 @@ srv_summary <- function(id, na_level, drop_arm_levels, label, - basic_table_args) { + basic_table_args, + decorators) { with_reporter <- !missing(reporter) && inherits(reporter, "Reporter") with_filter <- !missing(filter_panel_api) && inherits(filter_panel_api, "FilterPanelAPI") checkmate::assert_class(data, "reactive") @@ -496,7 +509,7 @@ srv_summary <- function(id, } }) - # validate inputs + # Validate inputs. validate_checks <- reactive({ teal::validate_inputs(iv_r()) adsl_filtered <- merged$anl_q()[[parentname]] @@ -539,7 +552,7 @@ srv_summary <- function(id, ) }) - # generate r code for the analysis + # Generate r code for the analysis. all_q <- reactive({ validate_checks() @@ -572,14 +585,24 @@ srv_summary <- function(id, teal.code::eval_code(merged$anl_q(), as.expression(unlist(my_calls))) }) + # Decoration of table output. + decorated_table_q <- srv_decorate_teal_data( + id = "decorator", + data = all_q, + decorators = select_decorators(decorators, "table"), + expr = table + ) + # Outputs to render. - table_r <- reactive(all_q()[["result"]]) + table_r <- reactive(decorated_table_q()[["table"]]) + teal.widgets::table_with_settings_srv(id = "table", table_r = table_r) # Render R code. + source_code_r <- reactive(teal.code::get_code(req(decorated_table_q()))) teal.widgets::verbatim_popup_srv( id = "rcode", - verbatim_content = reactive(teal.code::get_code(all_q())), + verbatim_content = source_code_r, title = label ) @@ -598,7 +621,7 @@ srv_summary <- function(id, card$append_text("Comment", "header3") card$append_text(comment) } - card$append_src(teal.code::get_code(all_q())) + card$append_src(source_code_r()) card } teal.reporter::simple_reporter_srv("simple_reporter", reporter = reporter, card_fun = card_fun) diff --git a/R/tm_t_summary_by.R b/R/tm_t_summary_by.R index e9163901b..49d1df798 100644 --- a/R/tm_t_summary_by.R +++ b/R/tm_t_summary_by.R @@ -285,20 +285,18 @@ template_summary_by <- function(parentname, rvs <- unlist(unname(row_values(tr))) isTRUE(all(rvs == 0)) } - result <- rtables::build_table( + table <- rtables::build_table( lyt = lyt, df = anl, alt_counts_df = parent ) %>% rtables::trim_rows(criteria = all_zero) - result }, env = list(parent = as.name(parentname)) ) } else { y$table <- substitute( expr = { - result <- rtables::build_table(lyt = lyt, df = anl, alt_counts_df = parent) - result + table <- rtables::build_table(lyt = lyt, df = anl, alt_counts_df = parent) }, env = list(parent = as.name(parentname)) ) @@ -321,6 +319,14 @@ template_summary_by <- function(parentname, #' #' @inherit module_arguments return seealso #' +#' @section Decorating Module: +#' +#' This module generates the following objects, which can be modified in place using decorators: +#' - `table` (`TableTree` - output of `rtables::build_table`) +#' +#' 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.clinical) #' interactive <- function() TRUE @@ -396,7 +402,8 @@ tm_t_summary_by <- function(label, drop_zero_levels = TRUE, pre_output = NULL, post_output = NULL, - basic_table_args = teal.widgets::basic_table_args()) { + basic_table_args = teal.widgets::basic_table_args(), + decorators = NULL) { message("Initializing tm_t_summary_by") checkmate::assert_string(label) checkmate::assert_string(dataname) @@ -424,6 +431,9 @@ tm_t_summary_by <- function(label, numeric_stats_choices <- c("n", "mean_sd", "mean_ci", "geom_mean", "median", "median_ci", "quantiles", "range") numeric_stats <- match.arg(numeric_stats, numeric_stats_choices, several.ok = TRUE) + decorators <- normalize_decorators(decorators) + assert_decorators(decorators, null.ok = TRUE, "table") + args <- c(as.list(environment())) data_extract_list <- list( @@ -451,7 +461,8 @@ tm_t_summary_by <- function(label, label = label, total_label = total_label, na_level = na_level, - basic_table_args = basic_table_args + basic_table_args = basic_table_args, + decorators = decorators ) ), datanames = teal.transform::get_extract_datanames(data_extract_list) @@ -558,6 +569,7 @@ ui_summary_by <- function(id, ...) { } ) ), + ui_decorate_teal_data(ns("decorator"), decorators = select_decorators(a$decorators, "table")), teal.widgets::panel_group( teal.widgets::panel_item( "Additional Variables Info", @@ -596,7 +608,8 @@ srv_summary_by <- function(id, drop_arm_levels, drop_zero_levels, label, - basic_table_args) { + basic_table_args, + decorators) { with_reporter <- !missing(reporter) && inherits(reporter, "Reporter") with_filter <- !missing(filter_panel_api) && inherits(filter_panel_api, "FilterPanelAPI") checkmate::assert_class(data, "reactive") @@ -685,7 +698,7 @@ srv_summary_by <- function(id, } }) - # The R-code corresponding to the analysis. + # Generate r code for the analysis. all_q <- reactive({ validate_checks() summarize_vars <- as.vector(merged$anl_input_r()$columns_source$summarize_vars) @@ -715,8 +728,16 @@ srv_summary_by <- function(id, teal.code::eval_code(merged$anl_q(), as.expression(unlist(my_calls))) }) + # Decoration of table output. + decorated_table_q <- srv_decorate_teal_data( + id = "decorator", + data = all_q, + decorators = select_decorators(decorators, "table"), + expr = table + ) + # Outputs to render. - table_r <- reactive(all_q()[["result"]]) + table_r <- reactive(decorated_table_q()[["table"]]) teal.widgets::table_with_settings_srv( id = "table", @@ -724,9 +745,10 @@ srv_summary_by <- function(id, ) # Render R code. + source_code_r <- reactive(teal.code::get_code(req(decorated_table_q()))) teal.widgets::verbatim_popup_srv( id = "rcode", - verbatim_content = reactive(teal.code::get_code(all_q())), + verbatim_content = source_code_r, title = label ) @@ -745,7 +767,7 @@ srv_summary_by <- function(id, card$append_text("Comment", "header3") card$append_text(comment) } - card$append_src(teal.code::get_code(all_q())) + card$append_src(source_code_r()) card } teal.reporter::simple_reporter_srv("simple_reporter", reporter = reporter, card_fun = card_fun) diff --git a/man/tm_g_pp_adverse_events.Rd b/man/tm_g_pp_adverse_events.Rd index a5e56dd54..90625071f 100644 --- a/man/tm_g_pp_adverse_events.Rd +++ b/man/tm_g_pp_adverse_events.Rd @@ -21,7 +21,8 @@ tm_g_pp_adverse_events( plot_width = NULL, pre_output = NULL, post_output = NULL, - ggplot2_args = teal.widgets::ggplot2_args() + ggplot2_args = teal.widgets::ggplot2_args(), + decorators = NULL ) } \arguments{ @@ -72,6 +73,8 @@ For example the \code{\link[shiny:helpText]{shiny::helpText()}} elements are use for the module plot. The argument is merged with option \code{teal.ggplot2_args} and with default module arguments (hard coded in the module body). For more details, see the vignette: \code{vignette("custom-ggplot2-arguments", package = "teal.widgets")}.} + +\item{decorators}{\verb{r roxygen_decorators_param("tm_g_pp_adverse_events")}} } \value{ a \code{teal_module} object. @@ -79,6 +82,34 @@ a \code{teal_module} object. \description{ This module produces an adverse events table and \code{\link[ggplot2:ggplot]{ggplot2::ggplot()}} type plot using ADaM datasets. } +\section{Decorating \code{tm_g_pp_adverse_events}}{ + + +This module generates the following objects, which can be modified in place using decorators:: +\itemize{ +\item \code{plot} (\code{ggplot2}) +\item \code{table} (\code{listing_df} - output of \code{rlistings::as_listing}) +} + +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_pp_adverse_events( + ..., # arguments for module + decorators = list( + default = list(teal_transform_module(...)), # applied to all outputs + plot = list(teal_transform_module(...)), # applied only to `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. +} + \examples{ library(nestcolor) library(dplyr) diff --git a/man/tm_g_pp_patient_timeline.Rd b/man/tm_g_pp_patient_timeline.Rd index 45175ce25..41d9d4026 100644 --- a/man/tm_g_pp_patient_timeline.Rd +++ b/man/tm_g_pp_patient_timeline.Rd @@ -89,14 +89,7 @@ for the module plot. The argument is merged with option \code{teal.ggplot2_args} (hard coded in the module body). 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}, 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 Module" below for more details.} +\item{decorators}{\verb{r roxygen_decorators_param("tm_g_pp_adverse_events")}} } \value{ a \code{teal_module} object. diff --git a/man/tm_t_logistic.Rd b/man/tm_t_logistic.Rd index 41a8e2bad..a40e45660 100644 --- a/man/tm_t_logistic.Rd +++ b/man/tm_t_logistic.Rd @@ -19,7 +19,8 @@ tm_t_logistic( TRUE), pre_output = NULL, post_output = NULL, - basic_table_args = teal.widgets::basic_table_args() + basic_table_args = teal.widgets::basic_table_args(), + decorators = NULL ) } \arguments{ @@ -63,6 +64,15 @@ For example the \code{\link[shiny:helpText]{shiny::helpText()}} elements are use with settings for the module table. The argument is merged with option \code{teal.basic_table_args} and with default module arguments (hard coded in the module body). 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}, 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 Module" below for more details.} } \value{ a \code{teal_module} object. @@ -71,6 +81,18 @@ a \code{teal_module} object. This module produces a multi-variable logistic regression table consistent with the TLG Catalog template \code{LGRT02} available \href{https://insightsengineering.github.io/tlg-catalog/stable/tables/efficacy/lgrt02.html}{here}. } +\section{Decorating Module}{ + + +This module generates the following objects, which can be modified in place using decorators: +\itemize{ +\item \code{table} (\code{ElementaryTable} - output of \code{rtables::build_table}) +} + +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. +} + \examples{ library(dplyr) diff --git a/man/tm_t_pp_medical_history.Rd b/man/tm_t_pp_medical_history.Rd index 0de76f252..6e6dc2ce9 100644 --- a/man/tm_t_pp_medical_history.Rd +++ b/man/tm_t_pp_medical_history.Rd @@ -13,7 +13,8 @@ tm_t_pp_medical_history( mhbodsys = NULL, mhdistat = NULL, pre_output = NULL, - post_output = NULL + post_output = NULL, + decorators = NULL ) } \arguments{ @@ -39,6 +40,15 @@ For example a title.} \item{post_output}{(\code{shiny.tag}) optional,\cr 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}, 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 Module" below for more details.} } \value{ a \code{teal_module} object. @@ -46,6 +56,18 @@ a \code{teal_module} object. \description{ This module produces a patient profile medical history report using ADaM datasets. } +\section{Decorating Module}{ + + +This module generates the following objects, which can be modified in place using decorators: +\itemize{ +\item \code{table} (\code{TableTree} - output of \code{rtables::build_table}) +} + +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. +} + \examples{ data <- teal_data() data <- within(data, { diff --git a/man/tm_t_shift_by_grade.Rd b/man/tm_t_shift_by_grade.Rd index 0af0b42f4..059adb022 100644 --- a/man/tm_t_shift_by_grade.Rd +++ b/man/tm_t_shift_by_grade.Rd @@ -34,7 +34,8 @@ tm_t_shift_by_grade( post_output = NULL, na_level = default_na_str(), code_missing_baseline = FALSE, - basic_table_args = teal.widgets::basic_table_args() + basic_table_args = teal.widgets::basic_table_args(), + decorators = NULL ) } \arguments{ @@ -97,6 +98,15 @@ default \code{na_level} to apply in all modules, run \code{set_default_na_str("n with settings for the module table. The argument is merged with option \code{teal.basic_table_args} and with default module arguments (hard coded in the module body). 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}, 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 Module" below for more details.} } \value{ a \code{teal_module} object. @@ -104,6 +114,18 @@ a \code{teal_module} object. \description{ This module produces a summary table of worst grades per subject by visit and parameter. } +\section{Decorating Module}{ + + +This module generates the following objects, which can be modified in place using decorators: +\itemize{ +\item \code{table} (\code{TableTree} - output of \code{rtables::build_table}) +} + +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. +} + \examples{ data <- teal_data() data <- within(data, { diff --git a/man/tm_t_smq.Rd b/man/tm_t_smq.Rd index cd211d8ed..5169323c1 100644 --- a/man/tm_t_smq.Rd +++ b/man/tm_t_smq.Rd @@ -23,7 +23,8 @@ tm_t_smq( scopes, pre_output = NULL, post_output = NULL, - basic_table_args = teal.widgets::basic_table_args() + basic_table_args = teal.widgets::basic_table_args(), + decorators = NULL ) } \arguments{ @@ -82,6 +83,15 @@ For example the \code{\link[shiny:helpText]{shiny::helpText()}} elements are use with settings for the module table. The argument is merged with option \code{teal.basic_table_args} and with default module arguments (hard coded in the module body). 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}, 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 Module" below for more details.} } \value{ a \code{teal_module} object. @@ -89,6 +99,18 @@ a \code{teal_module} object. \description{ This module produces an adverse events table by Standardized MedDRA Query. } +\section{Decorating Module}{ + + +This module generates the following objects, which can be modified in place using decorators: +\itemize{ +\item \code{table} (\code{TableTree} - output of \code{rtables::build_table}) +} + +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. +} + \examples{ data <- teal_data() data <- within(data, { diff --git a/man/tm_t_summary.Rd b/man/tm_t_summary.Rd index e0a427b8c..912584a41 100644 --- a/man/tm_t_summary.Rd +++ b/man/tm_t_summary.Rd @@ -22,7 +22,8 @@ tm_t_summary( drop_arm_levels = TRUE, pre_output = NULL, post_output = NULL, - basic_table_args = teal.widgets::basic_table_args() + basic_table_args = teal.widgets::basic_table_args(), + decorators = NULL ) } \arguments{ @@ -78,6 +79,15 @@ For example the \code{\link[shiny:helpText]{shiny::helpText()}} elements are use with settings for the module table. The argument is merged with option \code{teal.basic_table_args} and with default module arguments (hard coded in the module body). 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}, 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 Module" below for more details.} } \value{ a \code{teal_module} object. @@ -85,6 +95,18 @@ a \code{teal_module} object. \description{ This module produces a table to summarize variables. } +\section{Decorating Module}{ + + +This module generates the following objects, which can be modified in place using decorators: +\itemize{ +\item \code{table} (\code{TableTree} - output of \code{rtables::build_table}) +} + +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. +} + \examples{ # Preparation of the test case - use `EOSDY` and `DCSREAS` variables to demonstrate missing data. data <- teal_data() diff --git a/man/tm_t_summary_by.Rd b/man/tm_t_summary_by.Rd index 91173fea1..44bf42ceb 100644 --- a/man/tm_t_summary_by.Rd +++ b/man/tm_t_summary_by.Rd @@ -28,7 +28,8 @@ tm_t_summary_by( drop_zero_levels = TRUE, pre_output = NULL, post_output = NULL, - basic_table_args = teal.widgets::basic_table_args() + basic_table_args = teal.widgets::basic_table_args(), + decorators = NULL ) } \arguments{ @@ -98,6 +99,15 @@ For example the \code{\link[shiny:helpText]{shiny::helpText()}} elements are use with settings for the module table. The argument is merged with option \code{teal.basic_table_args} and with default module arguments (hard coded in the module body). 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}, 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 Module" below for more details.} } \value{ a \code{teal_module} object. @@ -105,6 +115,18 @@ a \code{teal_module} object. \description{ This module produces a table to summarize variables by row groups. } +\section{Decorating Module}{ + + +This module generates the following objects, which can be modified in place using decorators: +\itemize{ +\item \code{table} (\code{TableTree} - output of \code{rtables::build_table}) +} + +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. +} + \examples{ data <- teal_data() data <- within(data, {