From b7bef2df7e70acbf19e5e000762a7fbb4a2ea313 Mon Sep 17 00:00:00 2001 From: s1nghgurj <177268999+s1nghgurj@users.noreply.github.com> Date: Thu, 22 Aug 2024 15:44:19 +0100 Subject: [PATCH 01/17] add actionButton to reset all filters --- R/mod_listings.R | 17 ++++++++++++++--- 1 file changed, 14 insertions(+), 3 deletions(-) diff --git a/R/mod_listings.R b/R/mod_listings.R index df751dd..f25d475 100644 --- a/R/mod_listings.R +++ b/R/mod_listings.R @@ -9,7 +9,9 @@ TBL <- pack_of_constants( # nolint DRPDBUTTON_LABEL = "Click to see inputs", TABLE_ID = "listing", NO_COL_MSG = "Please select at least one column.", - EXPORT_ID = "export" + EXPORT_ID = "export", + RESET_FILT_BUTTON_ID = "reset_filt_btn", + RESET_FILT_BUTTON_LABEL = "Reset all filters." ) #' A module that displays datasets as listings @@ -48,7 +50,12 @@ listings_UI <- function(module_id) { # nolint shiny::column(2, mod_export_listings_UI(module_id = ns(TBL$EXPORT_ID)), offset = 8) ), shiny::br(), - DT::dataTableOutput(ns(TBL$TABLE_ID), height = "80vh") + shiny::actionButton(ns(TBL$RESET_FILT_BUTTON_ID), + TBL$RESET_FILT_BUTTON_LABEL, + icon = shiny::icon("filter-circle-xmark")), + shiny::br(), + DT::dataTableOutput(ns(TBL$TABLE_ID), height = "80vh"), + ) } @@ -204,7 +211,11 @@ listings_server <- function(module_id, current_rows = shiny::reactive(input[[paste0(TBL$TABLE_ID, "_rows_all")]]), intended_use_label = intended_use_label ) - + + # Proxy reference to dataTable + dt_proxy <- DT::dataTableProxy(TBL$TABLE_ID) + shiny::observeEvent(input[[TBL$RESET_FILT_BUTTON_ID]], DT::clearSearch(dt_proxy)) + output[[TBL$TABLE_ID]] <- DT::renderDataTable({ shiny::validate(shiny::need(!is.null(input[[TBL$COLUMNS_ID]]), TBL$NO_COL_MSG)) From 31460218fa3d95071b2d703d8754d8298a2ed79c Mon Sep 17 00:00:00 2001 From: s1nghgurj <177268999+s1nghgurj@users.noreply.github.com> Date: Fri, 23 Aug 2024 09:55:52 +0100 Subject: [PATCH 02/17] add buttons to select all, remove all and reset to default cols --- R/mod_listings.R | 44 ++++++++++++++++++++++++++++++++++++++------ 1 file changed, 38 insertions(+), 6 deletions(-) diff --git a/R/mod_listings.R b/R/mod_listings.R index f25d475..b5284e5 100644 --- a/R/mod_listings.R +++ b/R/mod_listings.R @@ -11,7 +11,13 @@ TBL <- pack_of_constants( # nolint NO_COL_MSG = "Please select at least one column.", EXPORT_ID = "export", RESET_FILT_BUTTON_ID = "reset_filt_btn", - RESET_FILT_BUTTON_LABEL = "Reset all filters." + RESET_FILT_BUTTON_LABEL = "Reset all filters.", + SELECT_ALL_COLS_BUTTON_ID = "select_all_cols_btn", + SELECT_ALL_COLS_BUTTON_LABEL = "Select all variables.", + REMOVE_ALL_COLS_BUTTON_ID = "remove_all_cols_btn", + REMOVE_ALL_COLS_BUTTON_LABEL = "Remove all variables.", + RESET_COLS_DEFAULT_BUTTON_ID = "reset_cols_btn", + RESET_COLS_DEFAULT_BUTTON_LABEL = "Reset to default variables." ) #' A module that displays datasets as listings @@ -41,6 +47,9 @@ listings_UI <- function(module_id) { # nolint multiple = TRUE, options = list(plugins = list("remove_button", "drag_drop")) ), + shiny::actionButton(ns(TBL$SELECT_ALL_COLS_BUTTON_ID), TBL$SELECT_ALL_COLS_BUTTON_LABEL), + shiny::actionButton(ns(TBL$REMOVE_ALL_COLS_BUTTON_ID), TBL$REMOVE_ALL_COLS_BUTTON_LABEL), + shiny::actionButton(ns(TBL$RESET_COLS_DEFAULT_BUTTON_ID), TBL$RESET_COLS_DEFAULT_BUTTON_LABEL), circle = FALSE, icon = shiny::icon("cog"), width = TBL$DRPDBUTTON_WIDTH, @@ -109,6 +118,9 @@ listings_server <- function(module_id, dataset_list() }) + # Set choices as a reactive value item + rvs <- shiny::reactiveValues(dataset_choices = NA, variable_choices = NA) + # Listing selection (start) shiny::observeEvent(v_dataset_list(), { # Fill default in case bookmark or default columns do not have all the listings in the dataset @@ -121,10 +133,10 @@ listings_server <- function(module_id, } bmk_dataset <<- NULL - choices <- generate_choices(v_dataset_list()) - shiny::exportTestValues(dataset_choices = choices) # Export values for shinytest2 tests + rvs$dataset_choices <- generate_choices(v_dataset_list()) + shiny::exportTestValues(dataset_choices = rvs$dataset_choices) # Export values for shinytest2 tests - shiny::updateSelectizeInput(inputId = TBL$DATASET_ID, choices = choices, selected = selected) + shiny::updateSelectizeInput(inputId = TBL$DATASET_ID, choices = rvs$dataset_choices, selected = selected) }) listings_data <- shiny::reactive({ @@ -153,15 +165,35 @@ listings_server <- function(module_id, ) } - choices <- generate_choices(listings_data()) + rvs$variable_choices <- generate_choices(listings_data()) shiny::updateSelectizeInput( inputId = TBL$COLUMNS_ID, - choices = choices, + choices = rvs$variable_choices, selected = r_selected_columns_in_dataset()[[input[[TBL$DATASET_ID]]]] ) } ) + + shiny::observeEvent(input[[TBL$SELECT_ALL_COLS_BUTTON_ID]], { + shiny::updateSelectizeInput(inputId = TBL$COLUMNS_ID, + choices = rvs$variable_choices, + selected = rvs$variable_choices) + }) + + shiny::observeEvent(input[[TBL$REMOVE_ALL_COLS_BUTTON_ID]], { + shiny::updateSelectizeInput(inputId = TBL$COLUMNS_ID, + choices = rvs$variable_choices, + selected = NULL) + }) + + shiny::observeEvent(input[[TBL$RESET_COLS_DEFAULT_BUTTON_ID]], { + r_selected_columns_in_dataset(fill_default_vars(default_vars, v_dataset_list())) + shiny::updateSelectizeInput(inputId = TBL$COLUMNS_ID, + choices = rvs$variable_choices, + selected = r_selected_columns_in_dataset()[[input[[TBL$DATASET_ID]]]]) + }) + shiny::observeEvent(input[[TBL$COLUMNS_ID]], { selected_columns_in_dataset <- r_selected_columns_in_dataset() From 0744214a7a3736ebffcd3652285167c7e1d9c58f Mon Sep 17 00:00:00 2001 From: s1nghgurj <177268999+s1nghgurj@users.noreply.github.com> Date: Wed, 20 Nov 2024 08:15:31 +0000 Subject: [PATCH 03/17] add shiny test and update docs --- R/mod_export_listings.R | 6 ++- R/mod_listings.R | 88 ++++++++++++++++++------------- tests/testthat/test-mod_listing.R | 51 ++++++++++++++++++ 3 files changed, 108 insertions(+), 37 deletions(-) diff --git a/R/mod_export_listings.R b/R/mod_export_listings.R index e82b95c..403aa30 100644 --- a/R/mod_export_listings.R +++ b/R/mod_export_listings.R @@ -49,7 +49,11 @@ mod_export_listings_UI <- function(module_id) { # nolint shinyFeedback::useShinyFeedback(), # needed to use shinyFeedback functionalities shinyjs::useShinyjs(), # needed to use shinyjs functionalities - shiny::actionButton(ns(EXP$EXPORTBTN_ID), label = EXP$EXPORTBTN_LABEL) + shiny::actionButton( + ns(EXP$EXPORTBTN_ID), + label = EXP$EXPORTBTN_LABEL, + icon = shiny::icon("download") + ) ) return(ui) diff --git a/R/mod_listings.R b/R/mod_listings.R index b5284e5..6c2bc80 100644 --- a/R/mod_listings.R +++ b/R/mod_listings.R @@ -11,13 +11,13 @@ TBL <- pack_of_constants( # nolint NO_COL_MSG = "Please select at least one column.", EXPORT_ID = "export", RESET_FILT_BUTTON_ID = "reset_filt_btn", - RESET_FILT_BUTTON_LABEL = "Reset all filters.", + RESET_FILT_BUTTON_LABEL = "Reset all filters", SELECT_ALL_COLS_BUTTON_ID = "select_all_cols_btn", - SELECT_ALL_COLS_BUTTON_LABEL = "Select all variables.", + SELECT_ALL_COLS_BUTTON_LABEL = "Select all variables", REMOVE_ALL_COLS_BUTTON_ID = "remove_all_cols_btn", - REMOVE_ALL_COLS_BUTTON_LABEL = "Remove all variables.", + REMOVE_ALL_COLS_BUTTON_LABEL = "Remove all variables", RESET_COLS_DEFAULT_BUTTON_ID = "reset_cols_btn", - RESET_COLS_DEFAULT_BUTTON_LABEL = "Reset to default variables." + RESET_COLS_DEFAULT_BUTTON_LABEL = "Reset to default variables" ) #' A module that displays datasets as listings @@ -37,31 +37,35 @@ listings_UI <- function(module_id) { # nolint shiny::tagList( shiny::fluidRow( - shiny::column(2, shinyWidgets::dropdownButton( - inputId = ns(TBL$DRPDBUTTON_ID), - shiny::selectizeInput(ns(TBL$DATASET_ID), label = TBL$DATASET_LABEL, choices = NULL), - shiny::selectizeInput( - ns(TBL$COLUMNS_ID), - label = TBL$COLUMNS_LABEL, - choices = NULL, - multiple = TRUE, - options = list(plugins = list("remove_button", "drag_drop")) - ), - shiny::actionButton(ns(TBL$SELECT_ALL_COLS_BUTTON_ID), TBL$SELECT_ALL_COLS_BUTTON_LABEL), - shiny::actionButton(ns(TBL$REMOVE_ALL_COLS_BUTTON_ID), TBL$REMOVE_ALL_COLS_BUTTON_LABEL), - shiny::actionButton(ns(TBL$RESET_COLS_DEFAULT_BUTTON_ID), TBL$RESET_COLS_DEFAULT_BUTTON_LABEL), - circle = FALSE, - icon = shiny::icon("cog"), - width = TBL$DRPDBUTTON_WIDTH, - label = TBL$DRPDBUTTON_LABEL, - tooltip = shinyWidgets::tooltipOptions(title = TBL$DRPDBUTTON_LABEL) - )), + shiny::column( + 2, + shinyWidgets::dropdownButton( + inputId = ns(TBL$DRPDBUTTON_ID), + shiny::selectizeInput(ns(TBL$DATASET_ID), label = TBL$DATASET_LABEL, choices = NULL), + shiny::selectizeInput( + ns(TBL$COLUMNS_ID), + label = TBL$COLUMNS_LABEL, + choices = NULL, + multiple = TRUE, + options = list(plugins = list("remove_button", "drag_drop")) + ), + shiny::actionButton(ns(TBL$SELECT_ALL_COLS_BUTTON_ID), TBL$SELECT_ALL_COLS_BUTTON_LABEL), + shiny::actionButton(ns(TBL$REMOVE_ALL_COLS_BUTTON_ID), TBL$REMOVE_ALL_COLS_BUTTON_LABEL), + shiny::actionButton(ns(TBL$RESET_COLS_DEFAULT_BUTTON_ID), TBL$RESET_COLS_DEFAULT_BUTTON_LABEL), + circle = FALSE, + icon = shiny::icon("cog"), + width = TBL$DRPDBUTTON_WIDTH, + label = TBL$DRPDBUTTON_LABEL, + tooltip = shinyWidgets::tooltipOptions(title = TBL$DRPDBUTTON_LABEL) + )), shiny::column(2, mod_export_listings_UI(module_id = ns(TBL$EXPORT_ID)), offset = 8) ), shiny::br(), - shiny::actionButton(ns(TBL$RESET_FILT_BUTTON_ID), - TBL$RESET_FILT_BUTTON_LABEL, - icon = shiny::icon("filter-circle-xmark")), + shiny::actionButton( + ns(TBL$RESET_FILT_BUTTON_ID), + TBL$RESET_FILT_BUTTON_LABEL, + icon = shiny::icon("filter-circle-xmark") + ), shiny::br(), DT::dataTableOutput(ns(TBL$TABLE_ID), height = "80vh"), @@ -176,22 +180,28 @@ listings_server <- function(module_id, ) shiny::observeEvent(input[[TBL$SELECT_ALL_COLS_BUTTON_ID]], { - shiny::updateSelectizeInput(inputId = TBL$COLUMNS_ID, - choices = rvs$variable_choices, - selected = rvs$variable_choices) + shiny::updateSelectizeInput( + inputId = TBL$COLUMNS_ID, + choices = rvs$variable_choices, + selected = rvs$variable_choices + ) }) shiny::observeEvent(input[[TBL$REMOVE_ALL_COLS_BUTTON_ID]], { - shiny::updateSelectizeInput(inputId = TBL$COLUMNS_ID, - choices = rvs$variable_choices, - selected = NULL) + shiny::updateSelectizeInput( + inputId = TBL$COLUMNS_ID, + choices = rvs$variable_choices, + selected = NULL + ) }) shiny::observeEvent(input[[TBL$RESET_COLS_DEFAULT_BUTTON_ID]], { r_selected_columns_in_dataset(fill_default_vars(default_vars, v_dataset_list())) - shiny::updateSelectizeInput(inputId = TBL$COLUMNS_ID, - choices = rvs$variable_choices, - selected = r_selected_columns_in_dataset()[[input[[TBL$DATASET_ID]]]]) + shiny::updateSelectizeInput( + inputId = TBL$COLUMNS_ID, + choices = rvs$variable_choices, + selected = r_selected_columns_in_dataset()[[input[[TBL$DATASET_ID]]]] + ) }) @@ -294,7 +304,13 @@ listings_server <- function(module_id, ordering = TRUE, columnDefs = list(list(className = "dt-center", targets = "_all")), dom = "Bfrtilp", - buttons = list(list(extend = "collection", text = "Reset Rows Order", action = htmlwidgets::JS(js))) + buttons = list( + list( + extend = "collection", + text = "Reset rows order", + action = htmlwidgets::JS(js) + ) + ) ) ) }) diff --git a/tests/testthat/test-mod_listing.R b/tests/testthat/test-mod_listing.R index 09c19c8..ec4251f 100644 --- a/tests/testthat/test-mod_listing.R +++ b/tests/testthat/test-mod_listing.R @@ -545,3 +545,54 @@ test_that("mock_table_mm() displays selected dataset after activating global fil testthat::expect_equal(actual, expected = selected) }) # integration + + +test_that("mock_table_mm() displays selected dataset after activating global filter", { + # Initialize test app + app <- shinytest2::AppDriver$new( + app_dir = app_dir, name = "test_global_filter_selected_dataset" + ) + + selected <- "adae" + # Switch dataset + app$set_inputs(`multi-dataset` = selected) + app$wait_for_idle() + + # Activate global filter + app$set_inputs(`global_filter-vars` = "RACE") + app$wait_for_idle() + + actual <- app$get_value(input = "multi-dataset") + + # Kill test app + app$stop() + + testthat::expect_equal(actual, expected = selected) +}) # integration + +test_that("Select and Deselect All Columns work correctly", { + # Initialize test app + app <- shinytest2::AppDriver$new( + app_dir = app_dir, name = "test_select_deselect_columns" + ) + + # Get initial column selection + initial_columns <- app$get_value(input = "col_sel") + + # Check "Select All Columns" button + app$click("select_all_cols_btn") + selected_columns <- app$get_value(input = "col_sel") + + # Check all columns selected + all_choices <- app$get_value(input = "col_sel-options") + expect_setequal(selected_columns, all_choices) + + # Check "Deselect All Columns" button + app$click("remove_all_cols_btn") + deselected_columns <- app$get_value(input = "col_sel") + + # Check no columns are selected + expect_equal(deselected_columns, NULL) + + app$stop() +}) From 9a5c7c76f0a956aeefcd7fc1df7caa83ceb4a967 Mon Sep 17 00:00:00 2001 From: s1nghgurj <177268999+s1nghgurj@users.noreply.github.com> Date: Wed, 20 Nov 2024 10:36:56 +0000 Subject: [PATCH 04/17] run styler --- R/mod_export_listings.R | 2 +- R/mod_listings.R | 32 +++++++++++++++---------------- tests/testthat/test-mod_listing.R | 26 ++++++++++++------------- 3 files changed, 30 insertions(+), 30 deletions(-) diff --git a/R/mod_export_listings.R b/R/mod_export_listings.R index 403aa30..06fbf2f 100644 --- a/R/mod_export_listings.R +++ b/R/mod_export_listings.R @@ -50,7 +50,7 @@ mod_export_listings_UI <- function(module_id) { # nolint shinyjs::useShinyjs(), # needed to use shinyjs functionalities shiny::actionButton( - ns(EXP$EXPORTBTN_ID), + ns(EXP$EXPORTBTN_ID), label = EXP$EXPORTBTN_LABEL, icon = shiny::icon("download") ) diff --git a/R/mod_listings.R b/R/mod_listings.R index 6c2bc80..a9fa731 100644 --- a/R/mod_listings.R +++ b/R/mod_listings.R @@ -38,7 +38,7 @@ listings_UI <- function(module_id) { # nolint shiny::tagList( shiny::fluidRow( shiny::column( - 2, + 2, shinyWidgets::dropdownButton( inputId = ns(TBL$DRPDBUTTON_ID), shiny::selectizeInput(ns(TBL$DATASET_ID), label = TBL$DATASET_LABEL, choices = NULL), @@ -57,18 +57,18 @@ listings_UI <- function(module_id) { # nolint width = TBL$DRPDBUTTON_WIDTH, label = TBL$DRPDBUTTON_LABEL, tooltip = shinyWidgets::tooltipOptions(title = TBL$DRPDBUTTON_LABEL) - )), + ) + ), shiny::column(2, mod_export_listings_UI(module_id = ns(TBL$EXPORT_ID)), offset = 8) ), shiny::br(), shiny::actionButton( - ns(TBL$RESET_FILT_BUTTON_ID), + ns(TBL$RESET_FILT_BUTTON_ID), TBL$RESET_FILT_BUTTON_LABEL, icon = shiny::icon("filter-circle-xmark") ), shiny::br(), DT::dataTableOutput(ns(TBL$TABLE_ID), height = "80vh"), - ) } @@ -124,7 +124,7 @@ listings_server <- function(module_id, # Set choices as a reactive value item rvs <- shiny::reactiveValues(dataset_choices = NA, variable_choices = NA) - + # Listing selection (start) shiny::observeEvent(v_dataset_list(), { # Fill default in case bookmark or default columns do not have all the listings in the dataset @@ -178,32 +178,32 @@ listings_server <- function(module_id, ) } ) - + shiny::observeEvent(input[[TBL$SELECT_ALL_COLS_BUTTON_ID]], { shiny::updateSelectizeInput( inputId = TBL$COLUMNS_ID, - choices = rvs$variable_choices, + choices = rvs$variable_choices, selected = rvs$variable_choices ) }) - + shiny::observeEvent(input[[TBL$REMOVE_ALL_COLS_BUTTON_ID]], { shiny::updateSelectizeInput( inputId = TBL$COLUMNS_ID, - choices = rvs$variable_choices, + choices = rvs$variable_choices, selected = NULL ) }) - + shiny::observeEvent(input[[TBL$RESET_COLS_DEFAULT_BUTTON_ID]], { r_selected_columns_in_dataset(fill_default_vars(default_vars, v_dataset_list())) shiny::updateSelectizeInput( inputId = TBL$COLUMNS_ID, - choices = rvs$variable_choices, + choices = rvs$variable_choices, selected = r_selected_columns_in_dataset()[[input[[TBL$DATASET_ID]]]] ) }) - + shiny::observeEvent(input[[TBL$COLUMNS_ID]], { selected_columns_in_dataset <- r_selected_columns_in_dataset() @@ -253,11 +253,11 @@ listings_server <- function(module_id, current_rows = shiny::reactive(input[[paste0(TBL$TABLE_ID, "_rows_all")]]), intended_use_label = intended_use_label ) - + # Proxy reference to dataTable dt_proxy <- DT::dataTableProxy(TBL$TABLE_ID) shiny::observeEvent(input[[TBL$RESET_FILT_BUTTON_ID]], DT::clearSearch(dt_proxy)) - + output[[TBL$TABLE_ID]] <- DT::renderDataTable({ shiny::validate(shiny::need(!is.null(input[[TBL$COLUMNS_ID]]), TBL$NO_COL_MSG)) @@ -306,8 +306,8 @@ listings_server <- function(module_id, dom = "Bfrtilp", buttons = list( list( - extend = "collection", - text = "Reset rows order", + extend = "collection", + text = "Reset rows order", action = htmlwidgets::JS(js) ) ) diff --git a/tests/testthat/test-mod_listing.R b/tests/testthat/test-mod_listing.R index ec4251f..2588ba9 100644 --- a/tests/testthat/test-mod_listing.R +++ b/tests/testthat/test-mod_listing.R @@ -552,21 +552,21 @@ test_that("mock_table_mm() displays selected dataset after activating global fil app <- shinytest2::AppDriver$new( app_dir = app_dir, name = "test_global_filter_selected_dataset" ) - + selected <- "adae" # Switch dataset app$set_inputs(`multi-dataset` = selected) app$wait_for_idle() - + # Activate global filter app$set_inputs(`global_filter-vars` = "RACE") app$wait_for_idle() - + actual <- app$get_value(input = "multi-dataset") - + # Kill test app app$stop() - + testthat::expect_equal(actual, expected = selected) }) # integration @@ -575,24 +575,24 @@ test_that("Select and Deselect All Columns work correctly", { app <- shinytest2::AppDriver$new( app_dir = app_dir, name = "test_select_deselect_columns" ) - + # Get initial column selection - initial_columns <- app$get_value(input = "col_sel") - + initial_columns <- app$get_value(input = "col_sel") + # Check "Select All Columns" button app$click("select_all_cols_btn") selected_columns <- app$get_value(input = "col_sel") - + # Check all columns selected all_choices <- app$get_value(input = "col_sel-options") expect_setequal(selected_columns, all_choices) - + # Check "Deselect All Columns" button - app$click("remove_all_cols_btn") + app$click("remove_all_cols_btn") deselected_columns <- app$get_value(input = "col_sel") - + # Check no columns are selected expect_equal(deselected_columns, NULL) - + app$stop() }) From 4bf4c02c9d9ee23e439a6463b81a2b77d4eb963a Mon Sep 17 00:00:00 2001 From: s1nghgurj <177268999+s1nghgurj@users.noreply.github.com> Date: Wed, 20 Nov 2024 10:55:00 +0000 Subject: [PATCH 05/17] style mod_listings --- R/mod_listings.R | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/R/mod_listings.R b/R/mod_listings.R index a9fa731..f5995d0 100644 --- a/R/mod_listings.R +++ b/R/mod_listings.R @@ -196,7 +196,9 @@ listings_server <- function(module_id, }) shiny::observeEvent(input[[TBL$RESET_COLS_DEFAULT_BUTTON_ID]], { - r_selected_columns_in_dataset(fill_default_vars(default_vars, v_dataset_list())) + r_selected_columns_in_dataset( + fill_default_vars(default_vars, v_dataset_list()) + ) shiny::updateSelectizeInput( inputId = TBL$COLUMNS_ID, choices = rvs$variable_choices, @@ -207,7 +209,9 @@ listings_server <- function(module_id, shiny::observeEvent(input[[TBL$COLUMNS_ID]], { selected_columns_in_dataset <- r_selected_columns_in_dataset() - selected_columns_in_dataset[[input[[TBL$DATASET_ID]]]] <- input[[TBL$COLUMNS_ID]] + selected_columns_in_dataset[[input[[TBL$DATASET_ID]]]] <- input[[ + TBL$COLUMNS_ID + ]] r_selected_columns_in_dataset(selected_columns_in_dataset) }) From aaf1f77149cc030c66d016f934e6a63a954c8dbc Mon Sep 17 00:00:00 2001 From: s1nghgurj <177268999+s1nghgurj@users.noreply.github.com> Date: Fri, 22 Nov 2024 12:21:08 +0000 Subject: [PATCH 06/17] add vertical scrollbar for selectizeInput --- R/mod_listings.R | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/R/mod_listings.R b/R/mod_listings.R index f5995d0..67a465e 100644 --- a/R/mod_listings.R +++ b/R/mod_listings.R @@ -42,6 +42,11 @@ listings_UI <- function(module_id) { # nolint shinyWidgets::dropdownButton( inputId = ns(TBL$DRPDBUTTON_ID), shiny::selectizeInput(ns(TBL$DATASET_ID), label = TBL$DATASET_LABEL, choices = NULL), + shiny::tags[["style"]](shiny::HTML(paste0( + "#", + ns(TBL$COLUMNS_ID), + " + div.selectize-control div.selectize-input.items {max-height:200px; overflow-y:auto;}" + ))), shiny::selectizeInput( ns(TBL$COLUMNS_ID), label = TBL$COLUMNS_LABEL, From c8f804ae83e7e8b4db030c14a13944ea2b811f7c Mon Sep 17 00:00:00 2001 From: s1nghgurj <177268999+s1nghgurj@users.noreply.github.com> Date: Sat, 23 Nov 2024 20:48:43 +0000 Subject: [PATCH 07/17] update select, unselect and reset to default cols mod_listing tests --- tests/testthat/test-mod_listing.R | 56 +++++++++++++++++++------------ 1 file changed, 34 insertions(+), 22 deletions(-) diff --git a/tests/testthat/test-mod_listing.R b/tests/testthat/test-mod_listing.R index 2588ba9..7c128d0 100644 --- a/tests/testthat/test-mod_listing.R +++ b/tests/testthat/test-mod_listing.R @@ -455,6 +455,7 @@ test_that("mock_table_mm() updates dropdown choices on dataset change in dv.mana app_dir = app_dir, name = "test_update_labels" ) + app$set_inputs(selector = "demo", wait_ = FALSE) expected <- c( "adsl [Subject Level]" = "adsl", "adae [Adverse Events]" = "adae", @@ -465,9 +466,10 @@ test_that("mock_table_mm() updates dropdown choices on dataset change in dv.mana # Verify that dataset choices are displayed properly with their labels testthat::expect_equal(actual, expected = expected) - + rm(actual, expected) + # Switch overall dataset (via module manager) - app$set_inputs(selector = "demo no labels") + app$set_inputs(selector = "demo no labels", wait_ = FALSE) expected <- c( "adsl [No label]" = "adsl", @@ -570,29 +572,39 @@ test_that("mock_table_mm() displays selected dataset after activating global fil testthat::expect_equal(actual, expected = selected) }) # integration -test_that("Select and Deselect All Columns work correctly", { - # Initialize test app +app_dir <- "./apps/listings_app" # applies for all tests within this describe() +app <- shinytest2::AppDriver$new(app_dir = app_dir, name = "test_listings_app") +app_dir <- app$get_url() + +test_that("Check select, unselect and reset all columns, works correctly", { app <- shinytest2::AppDriver$new( - app_dir = app_dir, name = "test_select_deselect_columns" + app_dir = app_dir, name = "test_select_all_columns" ) - # Get initial column selection - initial_columns <- app$get_value(input = "col_sel") - - # Check "Select All Columns" button - app$click("select_all_cols_btn") - selected_columns <- app$get_value(input = "col_sel") - - # Check all columns selected - all_choices <- app$get_value(input = "col_sel-options") - expect_setequal(selected_columns, all_choices) - - # Check "Deselect All Columns" button - app$click("remove_all_cols_btn") - deselected_columns <- app$get_value(input = "col_sel") - - # Check no columns are selected - expect_equal(deselected_columns, NULL) + # SET INITIAL DATASET + app$click("listings-dropdown_btn") + app$set_inputs(`listings-dropdown_btn_state` = TRUE, wait_ = FALSE) + app$set_inputs(`listings-dataset` = "dummy1", wait_ = FALSE) # set to simple_dummy data + + # CHECK ALL COLS SELECTED + app$click("listings-select_all_cols_btn") + actual <- app$get_value(input = "listings-col_sel") + expected <- names(simple_dummy) + + testthat::expect_equal(actual, expected) + + # CHECK ALL COLS UNSELECTED + app$click("listings-remove_all_cols_btn") + actual <- app$get_value(input = "listings-col_sel") + + testthat::expect_null(actual) + + # CHECK COLS RESET TO DEFAULT VARS + app$click("listings-reset_cols_btn") + actual <- app$get_value(input = "listings-col_sel") + expected <- names(simple_dummy)[1:3] + + testthat::expect_equal(actual, expected) app$stop() }) From 347b5bf11f0a245e0e58eaf667414e55f51cc370 Mon Sep 17 00:00:00 2001 From: s1nghgurj <177268999+s1nghgurj@users.noreply.github.com> Date: Sat, 23 Nov 2024 20:54:01 +0000 Subject: [PATCH 08/17] run styler --- tests/testthat/test-mod_listing.R | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/tests/testthat/test-mod_listing.R b/tests/testthat/test-mod_listing.R index 7c128d0..e7110ae 100644 --- a/tests/testthat/test-mod_listing.R +++ b/tests/testthat/test-mod_listing.R @@ -467,7 +467,7 @@ test_that("mock_table_mm() updates dropdown choices on dataset change in dv.mana # Verify that dataset choices are displayed properly with their labels testthat::expect_equal(actual, expected = expected) rm(actual, expected) - + # Switch overall dataset (via module manager) app$set_inputs(selector = "demo no labels", wait_ = FALSE) @@ -585,25 +585,25 @@ test_that("Check select, unselect and reset all columns, works correctly", { app$click("listings-dropdown_btn") app$set_inputs(`listings-dropdown_btn_state` = TRUE, wait_ = FALSE) app$set_inputs(`listings-dataset` = "dummy1", wait_ = FALSE) # set to simple_dummy data - + # CHECK ALL COLS SELECTED app$click("listings-select_all_cols_btn") - actual <- app$get_value(input = "listings-col_sel") + actual <- app$get_value(input = "listings-col_sel") expected <- names(simple_dummy) - + testthat::expect_equal(actual, expected) - + # CHECK ALL COLS UNSELECTED app$click("listings-remove_all_cols_btn") actual <- app$get_value(input = "listings-col_sel") - + testthat::expect_null(actual) - + # CHECK COLS RESET TO DEFAULT VARS app$click("listings-reset_cols_btn") - actual <- app$get_value(input = "listings-col_sel") + actual <- app$get_value(input = "listings-col_sel") expected <- names(simple_dummy)[1:3] - + testthat::expect_equal(actual, expected) app$stop() From abb68be0b44b14d8ce1d67331d9ad477c390dd59 Mon Sep 17 00:00:00 2001 From: s1nghgurj <177268999+s1nghgurj@users.noreply.github.com> Date: Sat, 23 Nov 2024 21:28:52 +0000 Subject: [PATCH 09/17] split tests up test-mod_listing --- tests/testthat/test-mod_listing.R | 64 ++++++++++++++++++++++++------- 1 file changed, 50 insertions(+), 14 deletions(-) diff --git a/tests/testthat/test-mod_listing.R b/tests/testthat/test-mod_listing.R index e7110ae..3a519db 100644 --- a/tests/testthat/test-mod_listing.R +++ b/tests/testthat/test-mod_listing.R @@ -448,7 +448,7 @@ test_that("mock_table_mm() displays the column names with the corresponding labe testthat::expect_equal(actual, expected) }) -test_that("mock_table_mm() updates dropdown choices on dataset change in dv.manager" %>% +test_that("mock_table_mm() updates dropdown choices with labels on dataset change in dv.manager" %>% vdoc[["add_spec"]](specs$listings_label), { # Initialize test app app <- shinytest2::AppDriver$new( @@ -464,23 +464,34 @@ test_that("mock_table_mm() updates dropdown choices on dataset change in dv.mana actual <- app$get_value(export = "multi-dataset_choices") + app$stop() + # Verify that dataset choices are displayed properly with their labels testthat::expect_equal(actual, expected = expected) - rm(actual, expected) - # Switch overall dataset (via module manager) - app$set_inputs(selector = "demo no labels", wait_ = FALSE) +}) # integration +test_that("mock_table_mm() updates dropdown choices without labels on dataset change in dv.manager" %>% + vdoc[["add_spec"]](specs$listings_label), { + # Initialize test app + app <- shinytest2::AppDriver$new( + app_dir = app_dir, name = "test_update_no_labels" + ) + + app$set_inputs(selector = "demo no labels", wait_ = FALSE) # Switch overall dataset (via module manager) + expected <- c( "adsl [No label]" = "adsl", "adae [No label]" = "adae", "small [No label]" = "small" ) - + actual <- app$get_value(export = "multi-dataset_choices") - - # Verify that dataset choices were updated due to dataset switch + + app$stop() + testthat::expect_equal(actual, expected = expected) + }) # integration test_that("mock_table_mm() displays no table when global filter returns an empty data.frame", { @@ -576,7 +587,7 @@ app_dir <- "./apps/listings_app" # applies for all tests within this describe() app <- shinytest2::AppDriver$new(app_dir = app_dir, name = "test_listings_app") app_dir <- app$get_url() -test_that("Check select, unselect and reset all columns, works correctly", { +test_that("Check select all columns works correctly", { app <- shinytest2::AppDriver$new( app_dir = app_dir, name = "test_select_all_columns" ) @@ -589,22 +600,47 @@ test_that("Check select, unselect and reset all columns, works correctly", { # CHECK ALL COLS SELECTED app$click("listings-select_all_cols_btn") actual <- app$get_value(input = "listings-col_sel") + app$stop() + expected <- names(simple_dummy) - testthat::expect_equal(actual, expected) + +}) # integration + +test_that("Check unselect all columns works correctly", { + app <- shinytest2::AppDriver$new( + app_dir = app_dir, name = "test_unselect_all_columns" + ) + + # SET INITIAL DATASET + app$click("listings-dropdown_btn") + app$set_inputs(`listings-dropdown_btn_state` = TRUE, wait_ = FALSE) + app$set_inputs(`listings-dataset` = "dummy1", wait_ = FALSE) # set to simple_dummy data # CHECK ALL COLS UNSELECTED app$click("listings-remove_all_cols_btn") actual <- app$get_value(input = "listings-col_sel") - + app$stop() testthat::expect_null(actual) +}) # integration + +test_that("Check reset all columns works correctly", { + app <- shinytest2::AppDriver$new( + app_dir = app_dir, name = "test_reset_columns" + ) + + # SET INITIAL DATASET + app$click("listings-dropdown_btn") + app$set_inputs(`listings-dropdown_btn_state` = TRUE, wait_ = FALSE) + app$set_inputs(`listings-dataset` = "dummy1", wait_ = FALSE) # set to simple_dummy data + # CHECK COLS RESET TO DEFAULT VARS app$click("listings-reset_cols_btn") actual <- app$get_value(input = "listings-col_sel") + app$stop() expected <- names(simple_dummy)[1:3] - + testthat::expect_equal(actual, expected) - - app$stop() -}) + +}) # integration From 030fa69fd8de3e1342e21b1e8b8daf6580328ebf Mon Sep 17 00:00:00 2001 From: s1nghgurj <177268999+s1nghgurj@users.noreply.github.com> Date: Sat, 23 Nov 2024 21:29:44 +0000 Subject: [PATCH 10/17] run styler --- tests/testthat/test-mod_listing.R | 29 ++++++++++++----------------- 1 file changed, 12 insertions(+), 17 deletions(-) diff --git a/tests/testthat/test-mod_listing.R b/tests/testthat/test-mod_listing.R index 3a519db..259ec21 100644 --- a/tests/testthat/test-mod_listing.R +++ b/tests/testthat/test-mod_listing.R @@ -465,33 +465,31 @@ test_that("mock_table_mm() updates dropdown choices with labels on dataset chang actual <- app$get_value(export = "multi-dataset_choices") app$stop() - + # Verify that dataset choices are displayed properly with their labels testthat::expect_equal(actual, expected = expected) - }) # integration test_that("mock_table_mm() updates dropdown choices without labels on dataset change in dv.manager" %>% - vdoc[["add_spec"]](specs$listings_label), { + vdoc[["add_spec"]](specs$listings_label), { # Initialize test app app <- shinytest2::AppDriver$new( app_dir = app_dir, name = "test_update_no_labels" ) - + app$set_inputs(selector = "demo no labels", wait_ = FALSE) # Switch overall dataset (via module manager) - + expected <- c( "adsl [No label]" = "adsl", "adae [No label]" = "adae", "small [No label]" = "small" ) - + actual <- app$get_value(export = "multi-dataset_choices") - + app$stop() - + testthat::expect_equal(actual, expected = expected) - }) # integration test_that("mock_table_mm() displays no table when global filter returns an empty data.frame", { @@ -601,17 +599,16 @@ test_that("Check select all columns works correctly", { app$click("listings-select_all_cols_btn") actual <- app$get_value(input = "listings-col_sel") app$stop() - + expected <- names(simple_dummy) testthat::expect_equal(actual, expected) - }) # integration test_that("Check unselect all columns works correctly", { app <- shinytest2::AppDriver$new( app_dir = app_dir, name = "test_unselect_all_columns" ) - + # SET INITIAL DATASET app$click("listings-dropdown_btn") app$set_inputs(`listings-dropdown_btn_state` = TRUE, wait_ = FALSE) @@ -622,25 +619,23 @@ test_that("Check unselect all columns works correctly", { actual <- app$get_value(input = "listings-col_sel") app$stop() testthat::expect_null(actual) - }) # integration test_that("Check reset all columns works correctly", { app <- shinytest2::AppDriver$new( app_dir = app_dir, name = "test_reset_columns" ) - + # SET INITIAL DATASET app$click("listings-dropdown_btn") app$set_inputs(`listings-dropdown_btn_state` = TRUE, wait_ = FALSE) app$set_inputs(`listings-dataset` = "dummy1", wait_ = FALSE) # set to simple_dummy data - + # CHECK COLS RESET TO DEFAULT VARS app$click("listings-reset_cols_btn") actual <- app$get_value(input = "listings-col_sel") app$stop() expected <- names(simple_dummy)[1:3] - + testthat::expect_equal(actual, expected) - }) # integration From 5d5d73d2a998ad7eb73c301331d08d9005d39595 Mon Sep 17 00:00:00 2001 From: s1nghgurj <177268999+s1nghgurj@users.noreply.github.com> Date: Sat, 23 Nov 2024 23:06:26 +0000 Subject: [PATCH 11/17] fix failing mock_table_mm test-mod_listing --- tests/testthat/test-mod_listing.R | 28 ++++++++++------------------ 1 file changed, 10 insertions(+), 18 deletions(-) diff --git a/tests/testthat/test-mod_listing.R b/tests/testthat/test-mod_listing.R index 259ec21..c59b8f4 100644 --- a/tests/testthat/test-mod_listing.R +++ b/tests/testthat/test-mod_listing.R @@ -461,35 +461,27 @@ test_that("mock_table_mm() updates dropdown choices with labels on dataset chang "adae [Adverse Events]" = "adae", "small [Few columns]" = "small" ) - actual <- app$get_value(export = "multi-dataset_choices") - - app$stop() - + # Verify that dataset choices are displayed properly with their labels testthat::expect_equal(actual, expected = expected) -}) # integration - -test_that("mock_table_mm() updates dropdown choices without labels on dataset change in dv.manager" %>% - vdoc[["add_spec"]](specs$listings_label), { - # Initialize test app - app <- shinytest2::AppDriver$new( - app_dir = app_dir, name = "test_update_no_labels" - ) - - app$set_inputs(selector = "demo no labels", wait_ = FALSE) # Switch overall dataset (via module manager) + + app$set_inputs(selector = "demo no labels") # Switch overall dataset (via module manager) + app$click("multi-dropdown_btn") + app$set_inputs(`multi-dropdown_btn_state` = TRUE) + app$wait_for_idle(500) + expected <- c( "adsl [No label]" = "adsl", "adae [No label]" = "adae", "small [No label]" = "small" ) - - actual <- app$get_value(export = "multi-dataset_choices") - + actual <- app$wait_for_value(export = "multi-dataset_choices", ignore = list(actual), timeout = 10e3) app$stop() - testthat::expect_equal(actual, expected = expected) + + }) # integration test_that("mock_table_mm() displays no table when global filter returns an empty data.frame", { From d5a3e674c0f4854d98264510c8b6e2246879b7b8 Mon Sep 17 00:00:00 2001 From: s1nghgurj <177268999+s1nghgurj@users.noreply.github.com> Date: Sat, 23 Nov 2024 23:07:40 +0000 Subject: [PATCH 12/17] run styler --- tests/testthat/test-mod_listing.R | 8 +++----- 1 file changed, 3 insertions(+), 5 deletions(-) diff --git a/tests/testthat/test-mod_listing.R b/tests/testthat/test-mod_listing.R index c59b8f4..75d66a0 100644 --- a/tests/testthat/test-mod_listing.R +++ b/tests/testthat/test-mod_listing.R @@ -462,16 +462,16 @@ test_that("mock_table_mm() updates dropdown choices with labels on dataset chang "small [Few columns]" = "small" ) actual <- app$get_value(export = "multi-dataset_choices") - + # Verify that dataset choices are displayed properly with their labels testthat::expect_equal(actual, expected = expected) - + app$set_inputs(selector = "demo no labels") # Switch overall dataset (via module manager) app$click("multi-dropdown_btn") app$set_inputs(`multi-dropdown_btn_state` = TRUE) app$wait_for_idle(500) - + expected <- c( "adsl [No label]" = "adsl", "adae [No label]" = "adae", @@ -480,8 +480,6 @@ test_that("mock_table_mm() updates dropdown choices with labels on dataset chang actual <- app$wait_for_value(export = "multi-dataset_choices", ignore = list(actual), timeout = 10e3) app$stop() testthat::expect_equal(actual, expected = expected) - - }) # integration test_that("mock_table_mm() displays no table when global filter returns an empty data.frame", { From bbdbbd9b0204b75c4332716c4fcce3f9e0f99008 Mon Sep 17 00:00:00 2001 From: gm-ebs-ext <177268999+gm-ebs-ext@users.noreply.github.com> Date: Sun, 24 Nov 2024 20:18:48 +0000 Subject: [PATCH 13/17] add test for reset filters --- tests/testthat/test-mod_listing.R | 50 +++++++++++++++++++++++++++---- 1 file changed, 44 insertions(+), 6 deletions(-) diff --git a/tests/testthat/test-mod_listing.R b/tests/testthat/test-mod_listing.R index 75d66a0..b2c2e1c 100644 --- a/tests/testthat/test-mod_listing.R +++ b/tests/testthat/test-mod_listing.R @@ -454,30 +454,35 @@ test_that("mock_table_mm() updates dropdown choices with labels on dataset chang app <- shinytest2::AppDriver$new( app_dir = app_dir, name = "test_update_labels" ) - + app$wait_for_idle() + app$set_inputs(selector = "demo", wait_ = FALSE) + app$wait_for_idle() + expected <- c( "adsl [Subject Level]" = "adsl", "adae [Adverse Events]" = "adae", "small [Few columns]" = "small" ) actual <- app$get_value(export = "multi-dataset_choices") - - # Verify that dataset choices are displayed properly with their labels + + actual <- app$wait_for_value( + export = "multi-dataset_choices", ignore = list(NULL), timeout = 5e3 + ) testthat::expect_equal(actual, expected = expected) - app$set_inputs(selector = "demo no labels") # Switch overall dataset (via module manager) app$click("multi-dropdown_btn") app$set_inputs(`multi-dropdown_btn_state` = TRUE) - app$wait_for_idle(500) expected <- c( "adsl [No label]" = "adsl", "adae [No label]" = "adae", "small [No label]" = "small" ) - actual <- app$wait_for_value(export = "multi-dataset_choices", ignore = list(actual), timeout = 10e3) + actual <- app$wait_for_value( + export = "multi-dataset_choices", ignore = list(actual), timeout = 10e3 + ) app$stop() testthat::expect_equal(actual, expected = expected) }) # integration @@ -514,6 +519,7 @@ test_that("mock_table_mm() displays selected columns after activating global fil # Set selected columns selected_cols <- c("STUDYID", "USUBJID") app$set_inputs(`multi-col_sel` = selected_cols) + app$wait_for_idle() # Activate global filter app$set_inputs(`global_filter-vars` = "RACE") @@ -629,3 +635,35 @@ test_that("Check reset all columns works correctly", { testthat::expect_equal(actual, expected) }) # integration + +test_that("Check reset filters works correctly", { + app <- shinytest2::AppDriver$new( + app_dir = app_dir, name = "test_reset_filters" + ) + + # SET INITIAL DATASET + app$click("listings-dropdown_btn") + app$set_inputs(`listings-dropdown_btn_state` = TRUE, wait_ = FALSE) + app$set_inputs(`listings-dataset` = "dummy1", wait_ = FALSE) # set to simple_dummy data + + expected <- app$wait_for_value(output = "listings-listing", ignore = list(NULL), timeout = 5e3) + + # SET COL FILTERS + app$set_inputs( + `listings-listing_search_columns` = c("4 ... 31", "23 ... 48", "2 ... 30"), + allow_no_input_binding_ = TRUE + ) + + app$wait_for_idle() + interim_data <- app$get_value(output = "listings-listing") + + # PRESS RESET FILT BUTTON + app$click("listings-reset_filt_btn") + app$wait_for_idle() + + actual <- app$get_value(output = "listings-listing") + app$wait_for_idle() + + testthat::expect_equal(actual, expected) + +}) # integration \ No newline at end of file From a929f67d6ba85afb7d38ca4841f0d3d6a76276e7 Mon Sep 17 00:00:00 2001 From: gm-ebs-ext <177268999+gm-ebs-ext@users.noreply.github.com> Date: Sun, 24 Nov 2024 20:29:45 +0000 Subject: [PATCH 14/17] run styler --- tests/testthat/test-mod_listing.R | 29 ++++++++++------------------- 1 file changed, 10 insertions(+), 19 deletions(-) diff --git a/tests/testthat/test-mod_listing.R b/tests/testthat/test-mod_listing.R index b2c2e1c..ccf9a1a 100644 --- a/tests/testthat/test-mod_listing.R +++ b/tests/testthat/test-mod_listing.R @@ -455,17 +455,17 @@ test_that("mock_table_mm() updates dropdown choices with labels on dataset chang app_dir = app_dir, name = "test_update_labels" ) app$wait_for_idle() - + app$set_inputs(selector = "demo", wait_ = FALSE) app$wait_for_idle() - + expected <- c( "adsl [Subject Level]" = "adsl", "adae [Adverse Events]" = "adae", "small [Few columns]" = "small" ) actual <- app$get_value(export = "multi-dataset_choices") - + actual <- app$wait_for_value( export = "multi-dataset_choices", ignore = list(NULL), timeout = 5e3 ) @@ -640,30 +640,21 @@ test_that("Check reset filters works correctly", { app <- shinytest2::AppDriver$new( app_dir = app_dir, name = "test_reset_filters" ) - + # SET INITIAL DATASET app$click("listings-dropdown_btn") app$set_inputs(`listings-dropdown_btn_state` = TRUE, wait_ = FALSE) app$set_inputs(`listings-dataset` = "dummy1", wait_ = FALSE) # set to simple_dummy data - - expected <- app$wait_for_value(output = "listings-listing", ignore = list(NULL), timeout = 5e3) - + # SET COL FILTERS app$set_inputs( - `listings-listing_search_columns` = c("4 ... 31", "23 ... 48", "2 ... 30"), + `listings-listing_search_columns` = c("4 ... 31", "23 ... 48", "2 ... 30"), allow_no_input_binding_ = TRUE ) - - app$wait_for_idle() - interim_data <- app$get_value(output = "listings-listing") - + # PRESS RESET FILT BUTTON app$click("listings-reset_filt_btn") - app$wait_for_idle() - - actual <- app$get_value(output = "listings-listing") - app$wait_for_idle() - + app$get_value(output = "listings-listing") + testthat::expect_equal(actual, expected) - -}) # integration \ No newline at end of file +}) # integration From 2819e4e01c7ccad7c6f968ab19a08485f2134ddb Mon Sep 17 00:00:00 2001 From: gm-ebs-ext <177268999+gm-ebs-ext@users.noreply.github.com> Date: Sun, 24 Nov 2024 20:40:27 +0000 Subject: [PATCH 15/17] fix test label --- tests/testthat/test-mod_listing.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/testthat/test-mod_listing.R b/tests/testthat/test-mod_listing.R index ccf9a1a..7efccf1 100644 --- a/tests/testthat/test-mod_listing.R +++ b/tests/testthat/test-mod_listing.R @@ -448,7 +448,7 @@ test_that("mock_table_mm() displays the column names with the corresponding labe testthat::expect_equal(actual, expected) }) -test_that("mock_table_mm() updates dropdown choices with labels on dataset change in dv.manager" %>% +test_that("mock_table_mm() updates dropdown choices on dataset change in dv.manager" %>% vdoc[["add_spec"]](specs$listings_label), { # Initialize test app app <- shinytest2::AppDriver$new( From c9f4c217efc60da4b3550a0ed0451f84e33eee82 Mon Sep 17 00:00:00 2001 From: gm-ebs-ext <177268999+gm-ebs-ext@users.noreply.github.com> Date: Sun, 24 Nov 2024 20:53:02 +0000 Subject: [PATCH 16/17] fix reset filters test-mod_listing.R --- tests/testthat/test-mod_listing.R | 21 ++++++++++++--------- 1 file changed, 12 insertions(+), 9 deletions(-) diff --git a/tests/testthat/test-mod_listing.R b/tests/testthat/test-mod_listing.R index 7efccf1..0354270 100644 --- a/tests/testthat/test-mod_listing.R +++ b/tests/testthat/test-mod_listing.R @@ -455,17 +455,17 @@ test_that("mock_table_mm() updates dropdown choices on dataset change in dv.mana app_dir = app_dir, name = "test_update_labels" ) app$wait_for_idle() - + app$set_inputs(selector = "demo", wait_ = FALSE) app$wait_for_idle() - + expected <- c( "adsl [Subject Level]" = "adsl", "adae [Adverse Events]" = "adae", "small [Few columns]" = "small" ) actual <- app$get_value(export = "multi-dataset_choices") - + actual <- app$wait_for_value( export = "multi-dataset_choices", ignore = list(NULL), timeout = 5e3 ) @@ -640,21 +640,24 @@ test_that("Check reset filters works correctly", { app <- shinytest2::AppDriver$new( app_dir = app_dir, name = "test_reset_filters" ) - + # SET INITIAL DATASET app$click("listings-dropdown_btn") app$set_inputs(`listings-dropdown_btn_state` = TRUE, wait_ = FALSE) app$set_inputs(`listings-dataset` = "dummy1", wait_ = FALSE) # set to simple_dummy data - + expected <- app$wait_for_value( + output = "listings-listing", ignore = list(NULL), timeout = 800 + ) + # SET COL FILTERS app$set_inputs( - `listings-listing_search_columns` = c("4 ... 31", "23 ... 48", "2 ... 30"), + `listings-listing_search_columns` = c("4 ... 31", "23 ... 48", "2 ... 30"), allow_no_input_binding_ = TRUE ) - + # PRESS RESET FILT BUTTON app$click("listings-reset_filt_btn") - app$get_value(output = "listings-listing") - + actual <- app$get_value(output = "listings-listing") + testthat::expect_equal(actual, expected) }) # integration From 8b9b0da55bc048b6c53daeed47fce01eca491122 Mon Sep 17 00:00:00 2001 From: gm-ebs-ext <177268999+gm-ebs-ext@users.noreply.github.com> Date: Sun, 24 Nov 2024 20:56:35 +0000 Subject: [PATCH 17/17] run styler --- tests/testthat/test-mod_listing.R | 16 ++++++++-------- 1 file changed, 8 insertions(+), 8 deletions(-) diff --git a/tests/testthat/test-mod_listing.R b/tests/testthat/test-mod_listing.R index 0354270..215dcc8 100644 --- a/tests/testthat/test-mod_listing.R +++ b/tests/testthat/test-mod_listing.R @@ -455,17 +455,17 @@ test_that("mock_table_mm() updates dropdown choices on dataset change in dv.mana app_dir = app_dir, name = "test_update_labels" ) app$wait_for_idle() - + app$set_inputs(selector = "demo", wait_ = FALSE) app$wait_for_idle() - + expected <- c( "adsl [Subject Level]" = "adsl", "adae [Adverse Events]" = "adae", "small [Few columns]" = "small" ) actual <- app$get_value(export = "multi-dataset_choices") - + actual <- app$wait_for_value( export = "multi-dataset_choices", ignore = list(NULL), timeout = 5e3 ) @@ -640,7 +640,7 @@ test_that("Check reset filters works correctly", { app <- shinytest2::AppDriver$new( app_dir = app_dir, name = "test_reset_filters" ) - + # SET INITIAL DATASET app$click("listings-dropdown_btn") app$set_inputs(`listings-dropdown_btn_state` = TRUE, wait_ = FALSE) @@ -648,16 +648,16 @@ test_that("Check reset filters works correctly", { expected <- app$wait_for_value( output = "listings-listing", ignore = list(NULL), timeout = 800 ) - + # SET COL FILTERS app$set_inputs( - `listings-listing_search_columns` = c("4 ... 31", "23 ... 48", "2 ... 30"), + `listings-listing_search_columns` = c("4 ... 31", "23 ... 48", "2 ... 30"), allow_no_input_binding_ = TRUE ) - + # PRESS RESET FILT BUTTON app$click("listings-reset_filt_btn") actual <- app$get_value(output = "listings-listing") - + testthat::expect_equal(actual, expected) }) # integration