Skip to content

Commit

Permalink
Fixing issue where copying data views or figures failed to copy the u…
Browse files Browse the repository at this point in the history
…nderlying lists used to create preload files.
  • Loading branch information
john-harrold committed Dec 1, 2024
1 parent 6ece5c8 commit 18a9248
Show file tree
Hide file tree
Showing 6 changed files with 108 additions and 78 deletions.
46 changes: 34 additions & 12 deletions R/ASM_Server.R
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,9 @@ ASM_Server <- function(id,
mod_ids) {
moduleServer(id, function(input, output, session) {

# Used to trigger messages from download button
toMessage = reactiveValues()

#------------------------------------
# Create ui outputs here:
output$ui_asm_save_name_text = renderUI({
Expand Down Expand Up @@ -155,16 +158,45 @@ ASM_Server <- function(id,
# mod_ids = mod_ids),
# c("ws_res"))

tcres = FM_tc(cmd = "ws_res = ASM_save_state(state=state, session=session, file_path=file, pll=NULL)",
if((any(c("ShinySession", "session_proxy") %in% class(session)))){
if(system.file(package = "shinybusy") !=""){
shinybusy::show_modal_spinner(text=state[["MC"]][["labels"]][["busy"]][["saving_state"]])
}
}

tmp_cmd = "ws_res = ASM_save_state(state=state, session=session, file_path=file, pll=NULL)"
tcres = FM_tc(cmd = tmp_cmd,
tc_env =
list(state = state,
session = session,
file = file),
capture = c("ws_res"))

if((any(c("ShinySession", "session_proxy") %in% class(session)))){
if(system.file(package = "shinybusy") !=""){
shinybusy::remove_modal_spinner()
}
}


if(!tcres$isgood){
FM_le(state, "Failed to write state")
FM_le(state, tmp_cmd)
FM_le(state, tcres$msgs)

state = FM_set_notification(
state = state,
notify_text = state[["MC"]][["errors"]][["save_failed"]],
notify_id = "ASM save failed",
type = "failure")

state = FM_set_ui_msg(state, tcres$msgs)
FM_set_mod_state(session, id, state)

toMessage[["message"]] = TRUE
notify_res =
FM_notify(state = state,
session = session)
}
}
)
Expand Down Expand Up @@ -294,6 +326,7 @@ ASM_Server <- function(id,
output$ui_asm_msg = renderText({
input[["button_state_save"]]
input[["input_load_state"]]
toMessage$message
state = ASM_fetch_state(id = id,
input = input,
session = session,
Expand Down Expand Up @@ -1197,12 +1230,6 @@ ASM_save_state = function(state, session, file_path, pll = NULL){
isgood = TRUE
msgs = c()

if((any(c("ShinySession", "session_proxy") %in% class(session)))){
if(system.file(package = "shinybusy") !=""){
shinybusy::show_modal_spinner(text=state[["MC"]][["labels"]][["busy"]][["saving_state"]])
}
}

# If pll is null then we generate it here:
if(is.null(pll)){
mkp_res = FM_mk_app_preload(session)
Expand Down Expand Up @@ -1296,11 +1323,6 @@ ASM_save_state = function(state, session, file_path, pll = NULL){
}
}

if((any(c("ShinySession", "session_proxy") %in% class(session)))){
if(system.file(package = "shinybusy") !=""){
shinybusy::remove_modal_spinner()
}
}

# Zipping everything up into an archive
zip::zip(zipfile=file_path,
Expand Down
11 changes: 7 additions & 4 deletions R/DW_Server.R
Original file line number Diff line number Diff line change
Expand Up @@ -1772,6 +1772,7 @@ DW_fetch_state = function(id, input, session,
# From the original view we copy both the WDS and elements_table fields
new_view[["WDS"]] = original_view[["WDS"]]
new_view[["elements_table"]] = original_view[["elements_table"]]
new_view[["elements_list"]] = original_view[["elements_list"]]
state = DW_set_current_view(state, new_view)

# Setting hold for views select
Expand Down Expand Up @@ -3401,18 +3402,21 @@ DW_mk_preload = function(state){
tmp_source_ele[["elements_list"]][[tmp_key]][["pll"]])
FM_le(state, paste0(" -> ",tmp_key, ": ", tmp_source_ele[["elements_list"]][[tmp_key]][["pll"]][["action"]]) )
} else {
err_msg = c(err_msg, paste0("missing preload list (pll) for key: ", tmp_key))
tmp_err_msg = paste0(" -> missing preload list (pll) for key: ", tmp_key)
FM_le(state, tmp_err_msg, entry_type="danger")
err_msg = c(err_msg, tmp_err_msg)
isgood = FALSE
}
} else {
err_msg = c(err_msg, paste0("missing key: ", tmp_key))
tmp_err_msg = paste0(" -> missing key: ", tmp_key)
FM_le(state, tmp_err_msg, entry_type="danger")
err_msg = c(err_msg, tmp_err_msg)
isgood = FALSE
}
comp_idx = comp_idx + 1
}
}


# Appending element
ylist[["elements"]][[ele_idx]] = list(element = tmp_element)
ele_idx = ele_idx + 1
Expand All @@ -3425,7 +3429,6 @@ DW_mk_preload = function(state){
yaml_list[[ state[["id"]] ]] = ylist

if(!isgood && !is.null(err_msg)){
formods::FM_le(state,err_msg,entry_type="danger")
msgs = c(msgs, err_msg)
}

Expand Down
76 changes: 40 additions & 36 deletions R/FG_Server.R
Original file line number Diff line number Diff line change
Expand Up @@ -1360,7 +1360,7 @@ FG_Server <- function(id,
#' \item{msgs: Any messages generated when building the
#' figure.}
#' \item{notes: Figure notes (user editable)}
#' \item{num_pages: Number of pages in the figure.}
#' \item{num_pages: Number of pages in the figure.}
#' \item{page: The currently selected figure page.}
#' }
#' }
Expand Down Expand Up @@ -1734,6 +1734,7 @@ FG_fetch_state = function(id,
# new_fig[["DW_checksum" ]] = old_fig[["DW_checksum" ]]
# new_fig[["DSV_checksum" ]] = old_fig[["DSV_checksum" ]]
new_fig[["elements_table"]] = old_fig[["elements_table"]]
new_fig[["elements_list" ]] = old_fig[["elements_list" ]]
new_fig[["code" ]] = old_fig[["code" ]]
new_fig[["fobj" ]] = old_fig[["fobj" ]]
new_fig[["code_previous" ]] = old_fig[["code_previous" ]]
Expand Down Expand Up @@ -1853,7 +1854,7 @@ FG_init_state = function(FM_yaml_file, MOD_yaml_file, id, id_UD, id_DW, session)
text_component_xlab = "xlab",
text_component_ylab = "ylab",
text_component_ggtitle = "title")),
scales = list(
scales = list(
mapping = list(
select_component_xscale = "xscale",
select_component_yscale = "yscale",
Expand Down Expand Up @@ -2186,12 +2187,12 @@ fers_builder = function(state){

# Number of rows
if(!(ui[["select_component_facet_nrow"]] %in% state[["MC"]][["formatting"]][["components"]][["facet_dims"]][["nrow"]][["choices"]])){
ui[["select_component_facet_nrow"]] = state[["MC"]][["formatting"]][["components"]][["facet_dims"]][["nrow"]][["default"]]
ui[["select_component_facet_nrow"]] = state[["MC"]][["formatting"]][["components"]][["facet_dims"]][["nrow"]][["default"]]
}

# Number of columns
if(!(ui[["select_component_facet_ncol"]] %in% state[["MC"]][["formatting"]][["components"]][["facet_dims"]][["ncol"]][["choices"]])){
ui[["select_component_facet_ncol"]] = state[["MC"]][["formatting"]][["components"]][["facet_dims"]][["ncol"]][["default"]]
ui[["select_component_facet_ncol"]] = state[["MC"]][["formatting"]][["components"]][["facet_dims"]][["ncol"]][["default"]]
}

# The faceting command will depend on the number of columns selected
Expand Down Expand Up @@ -2227,8 +2228,8 @@ fers_builder = function(state){

# Defining the preload options for faceting
for(uiname in names(state[["FG"]][["manual_elements"]][[element]][["mapping"]])){
pll[["options"]][[
state[["FG"]][["manual_elements"]][[element]][["mapping"]][[ uiname ]]
pll[["options"]][[
state[["FG"]][["manual_elements"]][[element]][["mapping"]][[ uiname ]]
]] = ui[[uiname]]
}

Expand Down Expand Up @@ -2291,8 +2292,8 @@ fers_builder = function(state){

# Defining the preload options for faceting
for(uiname in names(state[["FG"]][["manual_elements"]][[element]][["mapping"]])){
pll[["options"]][[
state[["FG"]][["manual_elements"]][[element]][["mapping"]][[ uiname ]]
pll[["options"]][[
state[["FG"]][["manual_elements"]][[element]][["mapping"]][[ uiname ]]
]] = ui[[uiname]]
}

Expand Down Expand Up @@ -2330,8 +2331,8 @@ fers_builder = function(state){

# Defining the preload options for faceting
for(uiname in names(state[["FG"]][["manual_elements"]][[element]][["mapping"]])){
pll[["options"]][[
state[["FG"]][["manual_elements"]][[element]][["mapping"]][[ uiname ]]
pll[["options"]][[
state[["FG"]][["manual_elements"]][[element]][["mapping"]][[ uiname ]]
]] = ui[[uiname]]
}

Expand Down Expand Up @@ -2535,7 +2536,7 @@ FG_build = function(state,

# Adding to the list
current_fig[["elements_list"]][[fge_key]][["pll"]] = pll

# Incrementing the counter
current_fig[["fge_cntr"]] = current_fig[["fge_cntr"]] + 1

Expand Down Expand Up @@ -2952,7 +2953,7 @@ res}
#'@title Populate Session Data for Module Testing
#'@description Populates the supplied session variable for testing.
#'@param session Shiny session variable (in app) or a list (outside of app)
#'@return The FG portion of the `all_sess_res` returned from \code{\link{FM_app_preload}}
#'@return The FG portion of the `all_sess_res` returned from \code{\link{FM_app_preload}}
#'@examples
#' sess_res = FG_test_mksession()
#'@seealso \code{\link{FM_app_preload}}
Expand All @@ -2973,10 +2974,10 @@ res}
#'@description Populates the supplied session variable with information from
#'list of sources.
#'@param session Shiny session variable (in app) or a list (outside of app)
#'@param src_list List of preload data (all read together with module IDs at the top level)
#'@param src_list List of preload data (all read together with module IDs at the top level)
#'@param yaml_res List data from module yaml config
#'@param mod_ID Module ID of the module being loaded.
#'@param react_state Reactive shiny object (in app) or a list (outside of app) used to trigger reactions.
#'@param mod_ID Module ID of the module being loaded.
#'@param react_state Reactive shiny object (in app) or a list (outside of app) used to trigger reactions.
#'@param quickload Logical \code{TRUE} to load reduced analysis \code{FALSE} to load the full analysis
#'@return list with the following elements
#' \itemize{
Expand Down Expand Up @@ -3039,9 +3040,9 @@ FG_preload = function(session, src_list, yaml_res, mod_ID=NULL, react_state = l
while(state[["FG"]][["fig_cntr"]] < max(enumeric)){
state = FG_new_fig(state)
}
# culling any unneeded views
# culling any unneeded views
for(fig_id in names(state[["FG"]][["figs"]])){
# This is a view that doesn't exist in elements so
# This is a view that doesn't exist in elements so
# we need to cull it
if(!(fig_id %in% names(element_map))){
# Setting the view to be deleted as the current view
Expand All @@ -3056,7 +3057,7 @@ FG_preload = function(session, src_list, yaml_res, mod_ID=NULL, react_state = l
# This contains all plot types:
plot_elements = state[["MC"]][["elements"]]

# these are the elements defined by aesthetics
# these are the elements defined by aesthetics
aes_elements = state[["FG"]][["aes_elements"]]

# ui elements that are automatically generated
Expand All @@ -3075,7 +3076,7 @@ FG_preload = function(session, src_list, yaml_res, mod_ID=NULL, react_state = l
# Making the current element element id active
state[["FG"]][["current_fig"]] = element_id

# Getting the numeric position in the list corresponding
# Getting the numeric position in the list corresponding
# to the current element id
ele_idx = element_map[[element_id]]

Expand All @@ -3098,12 +3099,12 @@ FG_preload = function(session, src_list, yaml_res, mod_ID=NULL, react_state = l
# Attaching data source
if(!is.null(elements[[ele_idx]][["element"]][["data_source"]][["id"]]) &
!is.null(elements[[ele_idx]][["element"]][["data_source"]][["idx"]])){
tmp_DSV = DSV[["catalog"]][c(DSV[["catalog"]][["id"]] == elements[[ele_idx]][["element"]][["data_source"]][["id"]] &
tmp_DSV = DSV[["catalog"]][c(DSV[["catalog"]][["id"]] == elements[[ele_idx]][["element"]][["data_source"]][["id"]] &
DSV[["catalog"]][["idx"]] == elements[[ele_idx]][["element"]][["data_source"]][["idx"]]), ]
if(nrow(tmp_DSV) == 1){
FM_le(state, paste0("setting data source: ", tmp_DSV[["object"]][1]) )
current_ele = FG_fetch_current_fig(state)
current_ele[["fig_dsview"]] = tmp_DSV[["object"]][1]
current_ele[["fig_dsview"]] = tmp_DSV[["object"]][1]
state = FG_set_current_fig(state, current_ele)
} else {
FM_le(state, paste0("error locating data source, expecting 1 source found ", nrow(tmp_DSV)), entry_type="danger")
Expand Down Expand Up @@ -3192,7 +3193,7 @@ FG_preload = function(session, src_list, yaml_res, mod_ID=NULL, react_state = l
}

if(add_component){
# Adding aesthetics
# Adding aesthetics
if(!is.null(tmp_component[["aes"]])){
for(cname in names( tmp_component[["aes"]])){
cname_ui = paste0("select_component_", cname)
Expand Down Expand Up @@ -3243,7 +3244,7 @@ FG_preload = function(session, src_list, yaml_res, mod_ID=NULL, react_state = l
} else {
add_component = FALSE
isgood = FALSE
tmp_msg = paste0("unknown plot component type: ", tmp_component[["type"]] )
tmp_msg = paste0("unknown plot component type: ", tmp_component[["type"]] )
msgs = c(msgs, tmp_msg)
FM_le(state,tmp_msg,entry_type="danger")
}
Expand Down Expand Up @@ -3297,13 +3298,13 @@ FG_preload = function(session, src_list, yaml_res, mod_ID=NULL, react_state = l
session = FM_set_mod_state(session, mod_ID, state)
}

res = list(isgood = isgood,
res = list(isgood = isgood,
msgs = msgs,
session = session,
input = input,
react_state = react_state,
state = state)

res}

#'@export
Expand All @@ -3322,13 +3323,13 @@ res}
#' res = FG_mk_preload(state)
FG_mk_preload = function(state){
isgood = TRUE
msgs = c()
msgs = c()
err_msg = c()

ylist = list(
fm_yaml = file.path("config", basename(state[["FM_yaml_file"]])),
mod_yaml = file.path("config", basename(state[["MOD_yaml_file"]])),
elements = list()
elements = list()
)


Expand All @@ -3339,9 +3340,9 @@ FG_mk_preload = function(state){
# Walking through each element:
for(element_id in names(state[["FG"]][["figs"]])){
tmp_source_ele = state[["FG"]][["figs"]][[element_id]]

# Finding the data source:
dsv_row =
dsv_row =
DSV[["catalog"]][
DSV[["catalog"]][["object"]] == tmp_source_ele[["fig_dsview"]], ]
ds_id = dsv_row[["id"]]
Expand All @@ -3356,9 +3357,9 @@ FG_mk_preload = function(state){
id = ds_id,
idx = ds_idx),
components = list())

FM_le(state, paste0("saving element (", tmp_source_ele[["idx"]], ") ", tmp_source_ele[["key"]]))

# Adding components:
if(is.data.frame(tmp_source_ele[["elements_table"]])){
comp_idx = 1
Expand All @@ -3369,17 +3370,21 @@ FG_mk_preload = function(state){
tmp_source_ele[["elements_list"]][[tmp_key]][["pll"]])
FM_le(state, paste0(" -> ",tmp_key, ": ", tmp_source_ele[["elements_list"]][[tmp_key]][["pll"]][["type"]]) )
} else {
err_msg = c(err_msg, paste0("missing preload list (pll) for key: ", tmp_key))
tmp_err_msg =paste0("missing preload list (pll) for key: ", tmp_key)
err_msg = c(err_msg, tmp_err_msg)
FM_le(state, tmp_err_msg, entry_type="danger")
isgood = FALSE
}
} else {
err_msg = c(err_msg, paste0("missing key: ", tmp_key))
tmp_err_msg = paste0(" -> missing key: ",tmp_key)
err_msg = c(err_msg, tmp_err_msg)
FM_le(state, tmp_err_msg, entry_type="danger")
isgood = FALSE
}
comp_idx = comp_idx + 1
}
}

# Appending element
ylist[["elements"]][[ele_idx]] = list(element = tmp_element)
ele_idx = ele_idx + 1
Expand All @@ -3392,10 +3397,9 @@ FG_mk_preload = function(state){
yaml_list[[ state[["id"]] ]] = ylist

if(!isgood && !is.null(err_msg)){
formods::FM_le(state,err_msg,entry_type="danger")
msgs = c(msgs, err_msg)
}

res = list(
isgood = isgood,
msgs = msgs,
Expand Down
Loading

0 comments on commit 18a9248

Please sign in to comment.