Skip to content

Commit 9ec59e9

Browse files
averissimodependabot-preview[bot]m7prllrs-rochegithub-actions[bot]
authored
🗃️ Decorators feature branch (#1252)
- Partner to insightsengineering/teal#1357 - Introduces decorators to modules. More about decorators in here insightsengineering/teal#1384 - Part 1 of insightsengineering/teal#1371 (comment) ### Changes description - Adds internal wrapper around `srv_decorate_data` as utility to append code after decorator _(such as `print(plot)`)_ - Implements decorators in modules #### Checklist for final review: Double check check for every module: - Works with and without decorators - Has param and section in documentation - Code shows in "Show R code" - Reporter shows both the outputs and code #### Todo on feature branch - [x] Link the `teal_transform_module` parameter to an extended explanation as [suggested here](https://github.com/insightsengineering/teal.modules.clinical/pull/1252/files/a78c0baa0996fb30fdff551bccb7bab0ec86caa6#r1870909229) - [x] Meet with SME to validate some changes in template, topics: - modules with listing/dt - Merge all modules - [x] Part 1 of insightsengineering/teal#1371 (comment) - [x] Part 2 of insightsengineering/teal#1371 (comment) - [x] Accept changes to snapshots in regression testing #1304 #### Example apps Not all modules could be used in same App as the examples' data are not 100% compatible. Hence the 2 apps below. <details> <summary>Example app</summary> ```r # Load packages pkgload::load_all("../teal.modules.clinical", export_all = FALSE) # Decorators ------------------------------------------------------------------ insert_rrow_decorator <- function(default_caption = "I am a good new row", .var_to_replace = "table") { teal_transform_module( label = "New rtables 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))) ) ) } add_title_decorator <- function(default_check = TRUE, .var_to_replace = "plot") { teal_transform_module( label = "Title", ui = function(id) shiny::checkboxInput(NS(id, "flag"), "Add title?", TRUE), server = make_teal_transform_server( substitute({ if (flag) .var_to_replace <- .var_to_replace + ggplot2::ggtitle("Title added by decorator") }, env = list(.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))) ) ) } change_theme_decorator <- function(default_check = TRUE, .var_to_replace = "plot") { teal_transform_module( label = "Theme", ui = function(id) shiny::checkboxInput(NS(id, "flag"), "Apply dark theme?", TRUE), server = make_teal_transform_server( substitute({ if (flag) .var_to_replace <- .var_to_replace + ggplot2::theme_dark() }, env = list(.var_to_replace = as.name(.var_to_replace)) ) ) ) } add_cowplot_title_decorator <- function(default_check = TRUE, .var_to_replace = "plot") { teal_transform_module( label = "Cowplot title", ui = function(id) shiny::checkboxInput(NS(id, "flag"), "Add title?", TRUE), server = make_teal_transform_server( substitute({ if (flag) .var_to_replace <- .var_to_replace + ggplot2::ggtitle("Title added by decorator") + cowplot::theme_cowplot() }, env = list(.var_to_replace = as.name(.var_to_replace)) ) ) ) } rlisting_footer <- function(default_footer = "I am a good footer", .var_to_replace = "table_listing") { teal_transform_module( label = "New row", ui = function(id) shiny::textInput(shiny::NS(id, "footer"), "footer", value = default_footer), server = make_teal_transform_server( substitute({ rlistings::main_footer(.var_to_replace) <- footer }, env = list(.var_to_replace = as.name(.var_to_replace))) ) ) } # End of decorators ----------------------------------------------------------- library(dplyr) # arm_ref_comp <- list(ARMCD = list(ref = "ARM B", comp = c("ARM A", "ARM C"))) arm_ref_comp <- list( ACTARMCD = list(ref = "ARM B", comp = c("ARM A", "ARM C")), ARM = list(ref = "B: Placebo", comp = c("A: Drug X", "C: Combination")) ) data <- within(teal_data(), { ADSL <- tmc_ex_adsl |> mutate(ITTFL = factor("Y") |> with_label("Intent-To-Treat Population Flag")) |> mutate(DTHFL = case_when(!is.na(DTHDT) ~ "Y", TRUE ~ "") |> with_label("Subject Death Flag")) ADAE <- tmc_ex_adae |> filter(!((AETOXGR == 1) & (AESEV == "MILD") & (ARM == "A: Drug X"))) ADAE$ASTDY <- structure( as.double(ADAE$ASTDY, unit = attr(ADAE$ASTDY, "units", exact = TRUE)), label = attr(ADAE$ASTDY, "label", exact = TRUE) ) .lbls_adae <- col_labels(tmc_ex_adae) ADAE <- tmc_ex_adae %>% mutate_if(is.character, as.factor) #' be certain of having factors col_labels(ADAE) <- .lbls_adae ADTTE <- tmc_ex_adtte ADLB <- tmc_ex_adlb |> mutate(AVISIT == forcats::fct_reorder(AVISIT, AVISITN, min)) |> mutate( ONTRTFL = case_when( AVISIT %in% c("SCREENING", "BASELINE") ~ "", TRUE ~ "Y" ) |> with_label("On Treatment Record Flag") ) ADVS <- tmc_ex_advs ADRS <- tmc_ex_adrs |> mutate( AVALC = d_onco_rsp_label(AVALC) |> with_label("Character Result/Finding") ) |> filter(PARAMCD != "OVRINV" | AVISIT == "FOLLOW UP") |> filter(PARAMCD %in% c("BESRSPI", "INVET")) ADAETTE <- tmc_ex_adaette %>% filter(PARAMCD %in% c("AETTE1", "AETTE2", "AETTE3")) %>% mutate(is_event = CNSR == 0) %>% mutate(n_events = as.integer(is_event)) .add_event_flags <- function(dat) { dat <- dat %>% mutate( TMPFL_SER = AESER == "Y", TMPFL_REL = AEREL == "Y", TMPFL_GR5 = AETOXGR == "5", TMP_SMQ01 = !is.na(SMQ01NAM), TMP_SMQ02 = !is.na(SMQ02NAM), TMP_CQ01 = !is.na(CQ01NAM) ) column_labels <- list( TMPFL_SER = "Serious AE", TMPFL_REL = "Related AE", TMPFL_GR5 = "Grade 5 AE", TMP_SMQ01 = aesi_label(dat[["SMQ01NAM"]], dat[["SMQ01SC"]]), TMP_SMQ02 = aesi_label("Y.9.9.9.9/Z.9.9.9.9 AESI"), TMP_CQ01 = aesi_label(dat[["CQ01NAM"]]) ) col_labels(dat)[names(column_labels)] <- as.character(column_labels) dat } ADEX <- tmc_ex_adex set.seed(1, kind = "Mersenne-Twister") .labels <- col_labels(ADEX, fill = FALSE) ADEX <- ADEX %>% distinct(USUBJID, .keep_all = TRUE) %>% mutate( PARAMCD = "TDURD", PARAM = "Overall duration (days)", AVAL = sample(x = seq(1, 200), size = n(), replace = TRUE), AVALU = "Days" ) %>% bind_rows(ADEX) col_labels(ADEX) <- .labels ADCM <- tmc_ex_adcm ADMH <- tmc_ex_admh ADCM$CMASTDTM <- ADCM$ASTDTM ADCM$CMAENDTM <- ADCM$AENDTM ADEG <- tmc_ex_adeg # smq .names_baskets <- grep("^(SMQ|CQ).*NAM$", names(ADAE), value = TRUE) .names_scopes <- grep("^SMQ.*SC$", names(ADAE), value = TRUE) .cs_baskets <- choices_selected( choices = variable_choices(ADAE, subset = .names_baskets), selected = .names_baskets ) .cs_scopes <- choices_selected( choices = variable_choices(ADAE, subset = .names_scopes), selected = .names_scopes, fixed = TRUE ) # summary ADSL$EOSDY[1] <- NA_integer_ }) join_keys(data) <- default_cdisc_join_keys[names(data)] adcm_keys <- c("STUDYID", "USUBJID", "ASTDTM", "CMSEQ", "ATC1", "ATC2", "ATC3", "ATC4") join_keys(data)["ADCM", "ADCM"] <- adcm_keys # Use in choices selected ----------------------------------------------------- ADSL <- data[["ADSL"]] ADQS <- data[["ADQS"]] ADAE <- data[["ADAE"]] ADTTE <- data[["ADTTE"]] ADLB <- data[["ADLB"]] ADAE <- data[["ADAE"]] ADVS <- data[["ADVS"]] ADRS <- data[["ADRS"]] ADAETTE <- data[["ADAETTE"]] ADEX <- data[["ADEX"]] ADCM <- data[["ADCM"]] ADMH <- data[["ADMH"]] ADEG <- data[["ADEG"]] # Init ------------------------------------------------------------------------ init( data = data, modules = modules( # ------------------------------------------------------------------------- tm_t_summary_by( label = "Summary by Row Groups Table", dataname = "ADLB", arm_var = choices_selected( choices = variable_choices(ADSL, c("ARM", "ARMCD")), selected = "ARM" ), add_total = TRUE, by_vars = choices_selected( choices = variable_choices(ADLB, c("PARAM", "AVISIT")), selected = c("AVISIT") ), summarize_vars = choices_selected( choices = variable_choices(ADLB, c("AVAL", "CHG")), selected = c("AVAL") ), useNA = "ifany", paramcd = choices_selected( choices = value_choices(ADLB, "PARAMCD", "PARAM"), selected = "ALT" ), decorators = list(insert_rrow_decorator()) ), # ------------------------------------------------------------------------- tm_t_smq( label = "Adverse Events by SMQ Table", dataname = "ADAE", arm_var = choices_selected( choices = variable_choices(data[["ADSL"]], subset = c("ARM", "SEX")), selected = "ARM" ), add_total = FALSE, baskets = data[[".cs_baskets"]], scopes = data[[".cs_scopes"]], llt = choices_selected( choices = variable_choices(data[["ADAE"]], subset = c("AEDECOD")), selected = "AEDECOD" ), decorators = list(insert_rrow_decorator()) ), # ------------------------------------------------------------------------- tm_t_shift_by_grade( label = "Grade Laboratory Abnormality Table", dataname = "ADLB", arm_var = choices_selected( choices = variable_choices(ADSL, subset = c("ARM", "ARMCD")), selected = "ARM" ), paramcd = choices_selected( choices = value_choices(ADLB, "PARAMCD", "PARAM"), selected = "ALT" ), worst_flag_var = choices_selected( choices = variable_choices(ADLB, subset = c("WGRLOVFL", "WGRLOFL", "WGRHIVFL", "WGRHIFL")), selected = c("WGRLOVFL") ), worst_flag_indicator = choices_selected( value_choices(ADLB, "WGRLOVFL"), selected = "Y", fixed = TRUE ), anl_toxgrade_var = choices_selected( choices = variable_choices(ADLB, subset = c("ATOXGR")), selected = c("ATOXGR"), fixed = TRUE ), base_toxgrade_var = choices_selected( choices = variable_choices(ADLB, subset = c("BTOXGR")), selected = c("BTOXGR"), fixed = TRUE ), add_total = FALSE, decorators = list(insert_rrow_decorator()) ), # ------------------------------------------------------------------------- tm_t_shift_by_arm( label = "Shift by Arm Table", dataname = "ADEG", arm_var = choices_selected( variable_choices(ADSL, subset = c("ARM", "ARMCD")), selected = "ARM" ), paramcd = choices_selected( value_choices(ADEG, "PARAMCD"), selected = "HR" ), visit_var = choices_selected( value_choices(ADEG, "AVISIT"), selected = "POST-BASELINE MINIMUM" ), aval_var = choices_selected( variable_choices(ADEG, subset = "ANRIND"), selected = "ANRIND", fixed = TRUE ), baseline_var = choices_selected( variable_choices(ADEG, subset = "BNRIND"), selected = "BNRIND", fixed = TRUE ), useNA = "ifany", decorators = list(insert_rrow_decorator()) ), # ------------------------------------------------------------------------- tm_t_shift_by_arm_by_worst( label = "Shift by Arm Table (by worst)", dataname = "ADEG", arm_var = choices_selected( variable_choices(ADSL, subset = c("ARM", "ARMCD")), selected = "ARM" ), paramcd = choices_selected( value_choices(ADEG, "PARAMCD"), selected = "ECGINTP" ), worst_flag_var = choices_selected( variable_choices(ADEG, c("WORS02FL", "WORS01FL")), selected = "WORS02FL" ), worst_flag = choices_selected( value_choices(ADEG, "WORS02FL"), selected = "Y", fixed = TRUE ), aval_var = choices_selected( variable_choices(ADEG, c("AVALC", "ANRIND")), selected = "AVALC" ), baseline_var = choices_selected( variable_choices(ADEG, c("BASEC", "BNRIND")), selected = "BASEC" ), useNA = "ifany", decorators = list(insert_rrow_decorator()) ), # ------------------------------------------------------------------------- tm_t_pp_prior_medication( label = "Prior Medication", dataname = "ADCM", parentname = "ADSL", patient_col = "USUBJID", atirel = choices_selected( choices = variable_choices(ADCM, "ATIREL"), selected = "ATIREL" ), cmdecod = choices_selected( choices = variable_choices(ADCM, "CMDECOD"), selected = "CMDECOD" ), cmindc = choices_selected( choices = variable_choices(ADCM, "CMINDC"), selected = "CMINDC" ), cmstdy = choices_selected( choices = variable_choices(ADCM, "ASTDY"), selected = "ASTDY" ), decorators = list( table = rlisting_footer(.var_to_replace = "table") ) ), # ------------------------------------------------------------------------- tm_t_pp_medical_history( label = "Medical History", dataname = "ADMH", parentname = "ADSL", patient_col = "USUBJID", mhterm = choices_selected( choices = variable_choices(ADMH, c("MHTERM")), selected = "MHTERM" ), mhbodsys = choices_selected( choices = variable_choices(ADMH, "MHBODSYS"), selected = "MHBODSYS" ), mhdistat = choices_selected( choices = variable_choices(ADMH, "MHDISTAT"), selected = "MHDISTAT" ), decorators = list(insert_rrow_decorator()) ), # ------------------------------------------------------------------------- tm_t_pp_laboratory( label = "Vitals", dataname = "ADLB", patient_col = "USUBJID", paramcd = choices_selected( choices = variable_choices(ADLB, "PARAMCD"), selected = "PARAMCD" ), param = choices_selected( choices = variable_choices(ADLB, "PARAM"), selected = "PARAM" ), timepoints = choices_selected( choices = variable_choices(ADLB, "ADY"), selected = "ADY" ), anrind = choices_selected( choices = variable_choices(ADLB, "ANRIND"), selected = "ANRIND" ), aval_var = choices_selected( choices = variable_choices(ADLB, "AVAL"), selected = "AVAL" ), avalu_var = choices_selected( choices = variable_choices(ADLB, "AVALU"), selected = "AVALU" ), decorators = list(table = rlisting_footer(.var_to_replace = "table")) ), # ------------------------------------------------------------------------- tm_t_pp_basic_info( label = "Basic Info", dataname = "ADSL", patient_col = "USUBJID", vars = choices_selected(choices = variable_choices(ADSL), selected = c("ARM", "AGE", "SEX", "COUNTRY", "RACE", "EOSSTT")) , decorators = list( table = rlisting_footer(.var_to_replace = "table") ) ), # ------------------------------------------------------------------------- tm_t_mult_events( label = "Concomitant Medications by Medication Class and Preferred Name", dataname = "ADCM", arm_var = choices_selected(c("ARM", "ARMCD"), "ARM"), seq_var = choices_selected("CMSEQ", selected = "CMSEQ", fixed = TRUE), hlt = choices_selected( choices = variable_choices(ADCM, c("ATC1", "ATC2", "ATC3", "ATC4")), selected = c("ATC1", "ATC2", "ATC3", "ATC4") ), llt = choices_selected(choices = variable_choices(ADCM, c("CMDECOD")), selected = c("CMDECOD")), add_total = TRUE, event_type = "treatment", decorators = list(insert_rrow_decorator()) ), # ------------------------------------------------------------------------- tm_t_logistic( label = "Logistic Regression", dataname = "ADRS", arm_var = choices_selected( choices = variable_choices(ADRS, c("ARM", "ARMCD")), selected = "ARM" ), arm_ref_comp = arm_ref_comp, paramcd = choices_selected( choices = value_choices(ADRS, "PARAMCD", "PARAM"), selected = "BESRSPI" ), cov_var = choices_selected( choices = c("SEX", "AGE", "BMRKR1", "BMRKR2"), selected = "SEX" ), decorators = list(insert_rrow_decorator()) ), # ------------------------------------------------------------------------- tm_t_exposure( label = "Duration of Exposure Table", dataname = "ADEX", paramcd = choices_selected( choices = value_choices(data[["ADEX"]], "PARAMCD", "PARAM"), selected = "TDURD" ), col_by_var = choices_selected( choices = variable_choices(data[["ADEX"]], subset = c("SEX", "ARM")), selected = "SEX" ), row_by_var = choices_selected( choices = variable_choices(data[["ADEX"]], subset = c("RACE", "REGION1", "STRATA1", "SEX")), selected = "RACE" ), parcat = choices_selected( choices = value_choices(data[["ADEX"]], "PARCAT2"), selected = "Drug A" ), add_total = FALSE, decorators = list(insert_rrow_decorator()) ), # ------------------------------------------------------------------------- tm_t_events( label = "Adverse Event Table", dataname = "ADAE", arm_var = choices_selected(c("ARM", "ARMCD"), "ARM"), llt = choices_selected( choices = variable_choices(ADAE, c("AETERM", "AEDECOD")), selected = c("AEDECOD") ), hlt = choices_selected( choices = variable_choices(ADAE, c("AEBODSYS", "AESOC")), selected = "AEBODSYS" ), add_total = TRUE, event_type = "adverse event", decorators = list(insert_rrow_decorator()) ), # ------------------------------------------------------------------------- tm_t_events_patyear( label = "AE Rate Adjusted for Patient-Years At Risk Table", dataname = "ADAETTE", arm_var = choices_selected( choices = variable_choices(ADSL, c("ARM", "ARMCD")), selected = "ARMCD" ), add_total = TRUE, events_var = choices_selected( choices = variable_choices(ADAETTE, "n_events"), selected = "n_events", fixed = TRUE ), paramcd = choices_selected( choices = value_choices(ADAETTE, "PARAMCD", "PARAM"), selected = "AETTE1" ), decorators = list(insert_rrow_decorator()) ), # ------------------------------------------------------------------------- tm_t_events_by_grade( label = "Adverse Events by Grade Table", dataname = "ADAE", arm_var = choices_selected(c("ARM", "ARMCD"), "ARM"), llt = choices_selected( choices = variable_choices(ADAE, c("AETERM", "AEDECOD")), selected = c("AEDECOD") ), hlt = choices_selected( choices = variable_choices(ADAE, c("AEBODSYS", "AESOC")), selected = "AEBODSYS" ), grade = choices_selected( choices = variable_choices(ADAE, c("AETOXGR", "AESEV")), selected = "AETOXGR" ), decorators = list(insert_rrow_decorator()) ), # ------------------------------------------------------------------------- tm_t_coxreg( label = "Cox Reg.", dataname = "ADTTE", arm_var = choices_selected(c("ARM", "ARMCD", "ACTARMCD"), "ARM"), arm_ref_comp = arm_ref_comp, paramcd = choices_selected( value_choices(ADTTE, "PARAMCD", "PARAM"), "OS" ), strata_var = choices_selected( c("COUNTRY", "STRATA1", "STRATA2"), "STRATA1" ), cov_var = choices_selected( c("AGE", "BMRKR1", "BMRKR2", "REGION1"), "AGE" ), multivariate = TRUE, decorators = list(insert_rrow_decorator()) ), # ------------------------------------------------------------------------- tm_t_abnormality( label = "Abnormality Table", dataname = "ADLB", arm_var = choices_selected( choices = variable_choices(ADSL, subset = c("ARM", "ARMCD")), selected = "ARM" ), add_total = FALSE, by_vars = choices_selected( choices = variable_choices(ADLB, subset = c("LBCAT", "PARAM", "AVISIT")), selected = c("LBCAT", "PARAM"), keep_order = TRUE ), baseline_var = choices_selected( variable_choices(ADLB, subset = "BNRIND"), selected = "BNRIND", fixed = TRUE ), grade = choices_selected( choices = variable_choices(ADLB, subset = "ANRIND"), selected = "ANRIND", fixed = TRUE ), abnormal = list(low = "LOW", high = "HIGH"), exclude_base_abn = FALSE, decorators = list(insert_rrow_decorator("I am a good new row")) ), # ------------------------------------------------------------------------- tm_g_pp_vitals( label = "Vitals", dataname = "ADVS", parentname = "ADSL", patient_col = "USUBJID", plot_height = c(600L, 200L, 2000L), paramcd = choices_selected( choices = variable_choices(ADVS, "PARAMCD"), selected = "PARAMCD" ), xaxis = choices_selected( choices = variable_choices(ADVS, "ADY"), selected = "ADY" ), aval_var = choices_selected( choices = variable_choices(ADVS, "AVAL"), selected = "AVAL" ), decorators = list(plot = add_title_decorator("plot")) ), # ------------------------------------------------------------------------- tm_g_pp_adverse_events( label = "Adverse Events", dataname = "ADAE", parentname = "ADSL", patient_col = "USUBJID", plot_height = c(600L, 200L, 2000L), aeterm = choices_selected( choices = variable_choices(ADAE, "AETERM"), selected = "AETERM" ), tox_grade = choices_selected( choices = variable_choices(ADAE, "AETOXGR"), selected = "AETOXGR" ), causality = choices_selected( choices = variable_choices(ADAE, "AEREL"), selected = "AEREL" ), outcome = choices_selected( choices = variable_choices(ADAE, "AEOUT"), selected = "AEOUT" ), action = choices_selected( choices = variable_choices(ADAE, "AEACN"), selected = "AEACN" ), time = choices_selected( choices = variable_choices(ADAE, "ASTDY"), selected = "ASTDY" ), decod = NULL, decorators = list( plot = caption_decorator('I am a good caption', 'plot'), table = rlisting_footer(.var_to_replace = 'table') ) ), # ------------------------------------------------------------------------- tm_g_lineplot( label = "Line Plot", dataname = "ADLB", strata = choices_selected( variable_choices(ADSL, c("ARM", "ARMCD", "ACTARMCD")), "ARM" ), y = choices_selected( variable_choices(ADLB, c("AVAL", "BASE", "CHG", "PCHG")), "AVAL" ), param = choices_selected( value_choices(ADLB, "PARAMCD", "PARAM"), "ALT" ), decorators = list(add_cowplot_title_decorator("plot")) ), # ------------------------------------------------------------------------- tm_g_km( label = "Kaplan-Meier Plot", dataname = "ADTTE", arm_var = choices_selected( variable_choices(ADSL, c("ARM", "ARMCD", "ACTARMCD")), "ARM" ), paramcd = choices_selected( value_choices(ADTTE, "PARAMCD", "PARAM"), "OS" ), arm_ref_comp = arm_ref_comp, strata_var = choices_selected( variable_choices(ADSL, c("SEX", "BMRKR2")), "SEX" ), facet_var = choices_selected( variable_choices(ADSL, c("SEX", "BMRKR2")), NULL ), decorators = list(plot = add_cowplot_title_decorator(TRUE, "plot")) ), # ------------------------------------------------------------------------- tm_g_barchart_simple( label = "ADAE Analysis", x = data_extract_spec( dataname = "ADSL", select = select_spec( choices = variable_choices( ADSL, c( "ARM", "ACTARM", "SEX", "RACE", "ITTFL", "SAFFL", "STRATA2" ) ), selected = "ACTARM", multiple = FALSE ) ), fill = list( data_extract_spec( dataname = "ADSL", select = select_spec( choices = variable_choices( ADSL, c( "ARM", "ACTARM", "SEX", "RACE", "ITTFL", "SAFFL", "STRATA2" ) ), selected = "SEX", multiple = FALSE ) ), data_extract_spec( dataname = "ADAE", select = select_spec( choices = variable_choices(ADAE, c("AETOXGR", "AESEV", "AESER")), selected = NULL, multiple = FALSE ) ) ), x_facet = list( data_extract_spec( dataname = "ADAE", select = select_spec( choices = variable_choices(ADAE, c("AETOXGR", "AESEV", "AESER")), selected = "AETOXGR", multiple = FALSE ) ), data_extract_spec( dataname = "ADSL", select = select_spec( choices = variable_choices( ADSL, c( "ARM", "ACTARM", "SEX", "RACE", "ITTFL", "SAFFL", "STRATA2" ) ), selected = NULL, multiple = FALSE ) ) ), y_facet = list( data_extract_spec( dataname = "ADAE", select = select_spec( choices = variable_choices(ADAE, c("AETOXGR", "AESEV", "AESER")), selected = "AESEV", multiple = FALSE ) ), data_extract_spec( dataname = "ADSL", select = select_spec( choices = variable_choices( ADSL, c( "ARM", "ACTARM", "SEX", "RACE", "ITTFL", "SAFFL", "STRATA2" ) ), selected = NULL, multiple = FALSE ) ) ), decorators = list(plot = caption_decorator('The best', 'plot')) ) ) ) |> shiny::runApp() ``` </details> <details> <summary>Second App</summary> ```r # Load packages pkgload::load_all("../teal.modules.clinical", export_all = FALSE) # Example below 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))) ) ) } # Preparation of the test case - use `EOSDY` and `DCSREAS` variables to demonstrate missing data. data <- teal_data() data <- within(data, { ADSL <- tmc_ex_adsl |> mutate( DTHFL = case_when( !is.na(DTHDT) ~ "Y", TRUE ~ "" ) %>% with_label("Subject Death Flag") ) ADSL$EOSDY[1] <- NA_integer_ ADAE <- tmc_ex_adae .add_event_flags <- function(dat) { dat <- dat %>% mutate( TMPFL_SER = AESER == "Y", TMPFL_REL = AEREL == "Y", TMPFL_GR5 = AETOXGR == "5", TMP_SMQ01 = !is.na(SMQ01NAM), TMP_SMQ02 = !is.na(SMQ02NAM), TMP_CQ01 = !is.na(CQ01NAM) ) column_labels <- list( TMPFL_SER = "Serious AE", TMPFL_REL = "Related AE", TMPFL_GR5 = "Grade 5 AE", TMP_SMQ01 = aesi_label(dat[["SMQ01NAM"]], dat[["SMQ01SC"]]), TMP_SMQ02 = aesi_label("Y.9.9.9.9/Z.9.9.9.9 AESI"), TMP_CQ01 = aesi_label(dat[["CQ01NAM"]]) ) col_labels(dat)[names(column_labels)] <- as.character(column_labels) dat } #' Generating user-defined event flags. ADAE <- ADAE %>% .add_event_flags() .ae_anl_vars <- names(ADAE)[startsWith(names(ADAE), "TMPFL_")] .aesi_vars <- names(ADAE)[startsWith(names(ADAE), "TMP_")] ADTTE <- tmc_ex_adtte # responder ADRS <- tmc_ex_adrs %>% mutate( AVALC = d_onco_rsp_label(AVALC) %>% with_label("Character Result/Finding") ) %>% filter(PARAMCD != "OVRINV" | AVISIT == "FOLLOW UP") ADQS <- tmc_ex_adqs %>% filter(ABLFL != "Y" & ABLFL2 != "Y") %>% filter(AVISIT %in% c("WEEK 1 DAY 8", "WEEK 2 DAY 15", "WEEK 3 DAY 22")) %>% mutate( AVISIT = as.factor(AVISIT), AVISITN = rank(AVISITN) %>% as.factor() %>% as.numeric() %>% as.factor() #' making consecutive numeric factor ) }) join_keys(data) <- default_cdisc_join_keys[names(data)] ADSL <- data[["ADSL"]] ADRS <- data[["ADRS"]] app <- init( data = data, modules = modules( # ------------------------------------------------------------------------- tm_a_mmrm( label = "MMRM", dataname = "ADQS", aval_var = choices_selected(c("AVAL", "CHG"), "AVAL"), id_var = choices_selected(c("USUBJID", "SUBJID"), "USUBJID"), arm_var = choices_selected(c("ARM", "ARMCD"), "ARM"), visit_var = choices_selected(c("AVISIT", "AVISITN"), "AVISIT"), arm_ref_comp = arm_ref_comp, paramcd = choices_selected( choices = value_choices(data[["ADQS"]], "PARAMCD", "PARAM"), selected = "FKSI-FWB" ), cov_var = choices_selected(c("BASE", "AGE", "SEX", "BASE:AVISIT"), NULL) , decorators = list( lsmeans_table = insert_rrow_decorator("A", .var_to_replace = "lsmeans_table") , lsmeans_plot = add_title_decorator("B", .var_to_replace = "lsmeans_plot") , covariance_table = insert_rrow_decorator("C", .var_to_replace = "covariance_table") , fixed_effects_table = insert_rrow_decorator("D", .var_to_replace = "fixed_effects_table") , diagnostic_table = insert_rrow_decorator(.var_to_replace = "diagnostic_table") , diagnostic_plot = add_title_decorator(.var_to_replace = "diagnostic_plot") ) ), # ------------------------------------------------------------------------- tm_t_binary_outcome( label = "Responders", dataname = "ADRS", paramcd = choices_selected( choices = value_choices(ADRS, "PARAMCD", "PARAM"), selected = "BESRSPI" ), arm_var = choices_selected( choices = variable_choices(ADRS, c("ARM", "ARMCD", "ACTARMCD")), selected = "ARM" ), arm_ref_comp = arm_ref_comp, strata_var = choices_selected( choices = variable_choices(ADRS, c("SEX", "BMRKR2", "RACE")), selected = "RACE" ), default_responses = list( BESRSPI = list( rsp = c("Complete Response (CR)", "Partial Response (PR)"), levels = c( "Complete Response (CR)", "Partial Response (PR)", "Stable Disease (SD)", "Progressive Disease (PD)" ) ), INVET = list( rsp = c("Stable Disease (SD)", "Not Evaluable (NE)"), levels = c( "Complete Response (CR)", "Not Evaluable (NE)", "Partial Response (PR)", "Progressive Disease (PD)", "Stable Disease (SD)" ) ), OVRINV = list( rsp = c("Progressive Disease (PD)", "Stable Disease (SD)"), levels = c("Progressive Disease (PD)", "Stable Disease (SD)", "Not Evaluable (NE)") ) ), decorators = list(insert_rrow_decorator("I am a new row")) ), # ------------------------------------------------------------------------- tm_t_events_summary( label = "Adverse Events Summary", dataname = "ADAE", arm_var = choices_selected( choices = variable_choices("ADSL", c("ARM", "ARMCD")), selected = "ARM" ), flag_var_anl = choices_selected( choices = variable_choices("ADAE", data[[".ae_anl_vars"]]), selected = data[[".ae_anl_vars"]][1], keep_order = TRUE, fixed = FALSE ), flag_var_aesi = choices_selected( choices = variable_choices("ADAE", data[[".aesi_vars"]]), selected = data[[".aesi_vars"]][1], keep_order = TRUE, fixed = FALSE ), add_total = TRUE, decorators = list(insert_rrow_decorator()) ), # ------------------------------------------------------------------------- tm_t_summary( label = "Demographic Table", dataname = "ADSL", arm_var = choices_selected(c("ARM", "ARMCD"), "ARM"), add_total = TRUE, summarize_vars = choices_selected( c("SEX", "RACE", "BMRKR2", "EOSDY", "DCSREAS", "AGE"), c("SEX", "RACE") ), useNA = "ifany", decorators = list(insert_rrow_decorator()) ) ) ) |> shiny::runApp() ``` </details> --------- Signed-off-by: Marcin <[email protected]> Signed-off-by: Lluís Revilla <[email protected]> Signed-off-by: André Veríssimo <[email protected]> Co-authored-by: 27856297+dependabot-preview[bot]@users.noreply.github.com <27856297+dependabot-preview[bot]@users.noreply.github.com> Co-authored-by: Marcin <[email protected]> Co-authored-by: m7pr <[email protected]> Co-authored-by: Lluís Revilla <[email protected]> Co-authored-by: Lluís Revilla <[email protected]> Co-authored-by: github-actions <41898282+github-actions[bot]@users.noreply.github.com>
1 parent c2c21c7 commit 9ec59e9

File tree

107 files changed

+2612
-682
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

107 files changed

+2612
-682
lines changed

.pre-commit-config.yaml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -33,7 +33,6 @@ repos:
3333
- methods
3434
- rlistings
3535
- rmarkdown
36-
- rtables
3736
- scales
3837
- shiny
3938
- shinyjs
@@ -48,6 +47,9 @@ repos:
4847
- insightsengineering/teal.widgets
4948
- insightsengineering/tern.gee
5049
- insightsengineering/tern.mmrm
50+
- insightsengineering/rtables
51+
- insightsengineering/rtables.officer
52+
- insightsengineering/formatters
5153
- utils
5254
- vistime
5355
- id: spell-check

R/argument_convention.R

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -203,6 +203,14 @@ NULL
203203
#' value indicating worst grade.
204204
#' @param worst_flag_var ([teal.transform::choices_selected()])\cr object
205205
#' with all available choices and preselected option for variable names that can be used as worst flag variable.
206+
#' @param decorators `r lifecycle::badge("experimental")`
207+
#' " (`list` of `teal_transform_module`, named `list` of `teal_transform_module` or" `NULL`) optional,
208+
#' if not `NULL`, decorator for tables or plots included in the module.
209+
#' When a named list of `teal_transform_module`, the decorators are applied to the respective output objects.
210+
#'
211+
#' Otherwise, the decorators are applied to all objects, which is equivalent as using the name `default`.
212+
#'
213+
#' See section "Decorating Module" below for more details.
206214
#'
207215
#' @return a `teal_module` object.
208216
#'

R/tm_a_gee.R

Lines changed: 39 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -69,9 +69,9 @@ template_a_gee <- function(output_table,
6969
if (output_table == "t_gee_cov") {
7070
substitute(
7171
expr = {
72-
result_table <- tern.gee::as.rtable(model_fit, type = "cov")
73-
subtitles(result_table) <- st
74-
main_footer(result_table) <- mf
72+
table <- tern.gee::as.rtable(model_fit, type = "cov")
73+
subtitles(table) <- st
74+
main_footer(table) <- mf
7575
},
7676
env = list(
7777
st = basic_table_args$subtitles,
@@ -81,9 +81,9 @@ template_a_gee <- function(output_table,
8181
} else if (output_table == "t_gee_coef") {
8282
substitute(
8383
expr = {
84-
result_table <- tern.gee::as.rtable(data.frame(Coefficient = model_fit$coefficients))
85-
subtitles(result_table) <- st
86-
main_footer(result_table) <- mf
84+
table <- tern.gee::as.rtable(data.frame(Coefficient = model_fit$coefficients))
85+
subtitles(table) <- st
86+
main_footer(table) <- mf
8787
},
8888
env = list(
8989
conf_level = conf_level,
@@ -95,17 +95,16 @@ template_a_gee <- function(output_table,
9595
substitute(
9696
expr = {
9797
lsmeans_fit_model <- tern.gee::lsmeans(model_fit, conf_level)
98-
result_table <- rtables::basic_table(show_colcounts = TRUE) %>%
98+
table <- rtables::basic_table(show_colcounts = TRUE) %>%
9999
rtables::split_cols_by(var = input_arm_var, ref_group = model_fit$ref_level) %>%
100100
tern.gee::summarize_gee_logistic() %>%
101101
rtables::build_table(
102102
df = lsmeans_fit_model,
103103
alt_counts_df = dataname_lsmeans
104104
)
105105

106-
subtitles(result_table) <- st
107-
main_footer(result_table) <- mf
108-
result_table
106+
subtitles(table) <- st
107+
main_footer(table) <- mf
109108
},
110109
env = list(
111110
dataname_lsmeans = as.name(dataname_lsmeans),
@@ -135,6 +134,14 @@ template_a_gee <- function(output_table,
135134
#'
136135
#' @inherit module_arguments return seealso
137136
#'
137+
#' @section Decorating Module:
138+
#'
139+
#' This module generates the following objects, which can be modified in place using decorators:
140+
#' - `table` (`ElementaryTable` - output of `rtables::build_table`)
141+
#'
142+
#' For additional details and examples of decorators, refer to the vignette
143+
#' `vignette("decorate-modules-output", package = "teal")` or the [`teal_transform_module()`] documentation.
144+
#'
138145
#' @examplesShinylive
139146
#' library(teal.modules.clinical)
140147
#' interactive <- function() TRUE
@@ -200,7 +207,8 @@ tm_a_gee <- function(label,
200207
conf_level = teal.transform::choices_selected(c(0.95, 0.9, 0.8), 0.95, keep_order = TRUE),
201208
pre_output = NULL,
202209
post_output = NULL,
203-
basic_table_args = teal.widgets::basic_table_args()) {
210+
basic_table_args = teal.widgets::basic_table_args(),
211+
decorators = NULL) {
204212
message("Initializing tm_a_gee (prototype)")
205213

206214
cov_var <- teal.transform::add_no_selected_choices(cov_var, multiple = TRUE)
@@ -218,6 +226,8 @@ tm_a_gee <- function(label,
218226
checkmate::assert_class(pre_output, classes = "shiny.tag", null.ok = TRUE)
219227
checkmate::assert_class(post_output, classes = "shiny.tag", null.ok = TRUE)
220228
checkmate::assert_class(basic_table_args, "basic_table_args")
229+
decorators <- normalize_decorators(decorators)
230+
assert_decorators(decorators, "table", null.ok = TRUE)
221231

222232
args <- as.list(environment())
223233

@@ -243,7 +253,8 @@ tm_a_gee <- function(label,
243253
parentname = parentname,
244254
arm_ref_comp = arm_ref_comp,
245255
label = label,
246-
basic_table_args = basic_table_args
256+
basic_table_args = basic_table_args,
257+
decorators = decorators
247258
)
248259
),
249260
datanames = teal.transform::get_extract_datanames(data_extract_list)
@@ -358,7 +369,8 @@ ui_gee <- function(id, ...) {
358369
"Coefficients" = "t_gee_coef"
359370
),
360371
selected = "t_gee_lsmeans"
361-
)
372+
),
373+
ui_decorate_teal_data(ns("decorator"), decorators = select_decorators(a$decorators, "table"))
362374
),
363375
forms = tagList(
364376
teal.widgets::verbatim_popup_ui(ns("rcode"), button_label = "Show R code")
@@ -385,7 +397,8 @@ srv_gee <- function(id,
385397
label,
386398
plot_height,
387399
plot_width,
388-
basic_table_args) {
400+
basic_table_args,
401+
decorators) {
389402
with_reporter <- !missing(reporter) && inherits(reporter, "Reporter")
390403
with_filter <- !missing(filter_panel_api) && inherits(filter_panel_api, "FilterPanelAPI")
391404
checkmate::assert_class(data, "reactive")
@@ -546,19 +559,26 @@ srv_gee <- function(id,
546559
output_title
547560
})
548561

549-
table_r <- reactive({
550-
table_q()[["result_table"]]
551-
})
562+
decorated_table_q <- srv_decorate_teal_data(
563+
id = "decorator",
564+
data = table_q,
565+
decorators = select_decorators(decorators, "table"),
566+
expr = table
567+
)
568+
569+
# Outputs to render.
570+
table_r <- reactive(decorated_table_q()[["table"]])
552571

553572
teal.widgets::table_with_settings_srv(
554573
id = "table",
555574
table_r = table_r
556575
)
557576

558577
# Render R code
578+
source_code_r <- reactive(teal.code::get_code(req(decorated_table_q())))
559579
teal.widgets::verbatim_popup_srv(
560580
id = "rcode",
561-
verbatim_content = reactive(teal.code::get_code(table_q())),
581+
verbatim_content = source_code_r,
562582
title = label
563583
)
564584

@@ -582,7 +602,7 @@ srv_gee <- function(id,
582602
card$append_text("Comment", "header3")
583603
card$append_text(comment)
584604
}
585-
card$append_src(teal.code::get_code(table_q()))
605+
card$append_src(source_code_r())
586606
card
587607
}
588608
teal.reporter::simple_reporter_srv("simple_reporter", reporter = reporter, card_fun = card_fun)

0 commit comments

Comments
 (0)