mirror of
https://github.com/agdamsbo/FreesearchR.git
synced 2025-09-12 01:49:39 +02:00
new ui
This commit is contained in:
parent
c7b879f458
commit
ec5603d368
4 changed files with 807 additions and 745 deletions
164
R/data_plots.R
164
R/data_plots.R
|
@ -11,97 +11,96 @@
|
||||||
data_visuals_ui <- function(id, tab_title = "Plots", ...) {
|
data_visuals_ui <- function(id, tab_title = "Plots", ...) {
|
||||||
ns <- shiny::NS(id)
|
ns <- shiny::NS(id)
|
||||||
|
|
||||||
# bslib::navset_bar(
|
|
||||||
list(
|
list(
|
||||||
|
bslib::layout_sidebar(
|
||||||
# Sidebar with a slider input
|
sidebar = bslib::sidebar(
|
||||||
sidebar = bslib::sidebar(
|
bslib::accordion(
|
||||||
bslib::accordion(
|
multiple = FALSE,
|
||||||
multiple = FALSE,
|
bslib::accordion_panel(
|
||||||
bslib::accordion_panel(
|
title = "Creating plot",
|
||||||
title = "Creating plot",
|
icon = bsicons::bs_icon("graph-up"),
|
||||||
icon = bsicons::bs_icon("graph-up"),
|
shiny::uiOutput(outputId = ns("primary")),
|
||||||
shiny::uiOutput(outputId = ns("primary")),
|
shiny::helpText('Only non-text variables are available for plotting. Go the "Data" to reclass data to plot.'),
|
||||||
shiny::helpText('Only non-text variables are available for plotting. Go the "Data" to reclass data to plot.'),
|
shiny::tags$br(),
|
||||||
shiny::tags$br(),
|
shiny::uiOutput(outputId = ns("type")),
|
||||||
shiny::uiOutput(outputId = ns("type")),
|
shiny::uiOutput(outputId = ns("secondary")),
|
||||||
shiny::uiOutput(outputId = ns("secondary")),
|
shiny::uiOutput(outputId = ns("tertiary")),
|
||||||
shiny::uiOutput(outputId = ns("tertiary")),
|
shiny::br(),
|
||||||
shiny::br(),
|
shiny::actionButton(
|
||||||
shiny::actionButton(
|
inputId = ns("act_plot"),
|
||||||
inputId = ns("act_plot"),
|
label = "Plot",
|
||||||
label = "Plot",
|
width = "100%",
|
||||||
width = "100%",
|
icon = shiny::icon("palette"),
|
||||||
icon = shiny::icon("palette"),
|
disabled = FALSE
|
||||||
disabled = FALSE
|
),
|
||||||
|
shiny::helpText('Adjust settings, then press "Plot".')
|
||||||
),
|
),
|
||||||
shiny::helpText('Adjust settings, then press "Plot".')
|
bslib::accordion_panel(
|
||||||
),
|
title = "Download",
|
||||||
# bslib::accordion_panel(
|
icon = bsicons::bs_icon("download"),
|
||||||
# title = "Advanced",
|
shinyWidgets::noUiSliderInput(
|
||||||
# icon = bsicons::bs_icon("gear")
|
inputId = ns("height_slide"),
|
||||||
# ),
|
label = "Plot height (mm)",
|
||||||
bslib::accordion_panel(
|
min = 50,
|
||||||
title = "Download",
|
max = 300,
|
||||||
icon = bsicons::bs_icon("download"),
|
value = 100,
|
||||||
shinyWidgets::noUiSliderInput(
|
step = 1,
|
||||||
inputId = ns("height_slide"),
|
format = shinyWidgets::wNumbFormat(decimals = 0),
|
||||||
label = "Plot height (mm)",
|
color = datamods:::get_primary_color(),
|
||||||
min = 50,
|
inline = TRUE
|
||||||
max = 300,
|
),
|
||||||
value = 100,
|
# shiny::numericInput(
|
||||||
step = 1,
|
# inputId = ns("height_numeric"),
|
||||||
format = shinyWidgets::wNumbFormat(decimals = 0),
|
# label = "Plot height (mm)",
|
||||||
color = datamods:::get_primary_color(),
|
# min = 50,
|
||||||
inline = TRUE
|
# max = 300,
|
||||||
),
|
# value = 100
|
||||||
# shiny::numericInput(
|
# ),
|
||||||
# inputId = ns("height_numeric"),
|
shinyWidgets::noUiSliderInput(
|
||||||
# label = "Plot height (mm)",
|
inputId = ns("width"),
|
||||||
# min = 50,
|
label = "Plot width (mm)",
|
||||||
# max = 300,
|
min = 50,
|
||||||
# value = 100
|
max = 300,
|
||||||
# ),
|
value = 100,
|
||||||
shinyWidgets::noUiSliderInput(
|
step = 1,
|
||||||
inputId = ns("width"),
|
format = shinyWidgets::wNumbFormat(decimals = 0),
|
||||||
label = "Plot width (mm)",
|
color = datamods:::get_primary_color()
|
||||||
min = 50,
|
),
|
||||||
max = 300,
|
shiny::selectInput(
|
||||||
value = 100,
|
inputId = ns("plot_type"),
|
||||||
step = 1,
|
label = "File format",
|
||||||
format = shinyWidgets::wNumbFormat(decimals = 0),
|
choices = list(
|
||||||
color = datamods:::get_primary_color()
|
"png",
|
||||||
),
|
"tiff",
|
||||||
shiny::selectInput(
|
"eps",
|
||||||
inputId = ns("plot_type"),
|
"pdf",
|
||||||
label = "File format",
|
"jpeg",
|
||||||
choices = list(
|
"svg"
|
||||||
"png",
|
)
|
||||||
"tiff",
|
),
|
||||||
"eps",
|
shiny::br(),
|
||||||
"pdf",
|
# Button
|
||||||
"jpeg",
|
shiny::downloadButton(
|
||||||
"svg"
|
outputId = ns("download_plot"),
|
||||||
|
label = "Download plot",
|
||||||
|
icon = shiny::icon("download")
|
||||||
)
|
)
|
||||||
),
|
|
||||||
shiny::br(),
|
|
||||||
# Button
|
|
||||||
shiny::downloadButton(
|
|
||||||
outputId = ns("download_plot"),
|
|
||||||
label = "Download plot",
|
|
||||||
icon = shiny::icon("download")
|
|
||||||
)
|
)
|
||||||
)
|
),
|
||||||
)
|
shiny::p("We have collected a few notes on visualising data and details on the options included in FreesearchR:", shiny::tags$a(
|
||||||
),
|
href = "https://agdamsbo.github.io/FreesearchR/articles/visuals.html",
|
||||||
bslib::nav_panel(
|
"View notes in new tab",
|
||||||
title = tab_title,
|
target = "_blank",
|
||||||
|
rel = "noopener noreferrer"
|
||||||
|
))
|
||||||
|
),
|
||||||
shiny::plotOutput(ns("plot"), height = "70vh"),
|
shiny::plotOutput(ns("plot"), height = "70vh"),
|
||||||
shiny::tags$br(),
|
shiny::tags$br(),
|
||||||
shiny::tags$br(),
|
shiny::tags$br(),
|
||||||
shiny::htmlOutput(outputId = ns("code_plot"))
|
shiny::htmlOutput(outputId = ns("code_plot"))
|
||||||
)
|
)
|
||||||
)
|
)
|
||||||
|
# )
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
|
@ -725,6 +724,7 @@ get_label <- function(data, var = NULL) {
|
||||||
#' paste(sample(letters[1:10], 100, TRUE), collapse = "") |> line_break(force = TRUE)
|
#' paste(sample(letters[1:10], 100, TRUE), collapse = "") |> line_break(force = TRUE)
|
||||||
line_break <- function(data, lineLength = 20, force = FALSE) {
|
line_break <- function(data, lineLength = 20, force = FALSE) {
|
||||||
if (isTRUE(force)) {
|
if (isTRUE(force)) {
|
||||||
|
## This eats some letters when splitting a sentence... ??
|
||||||
gsub(paste0("(.{1,", lineLength, "})(\\s|[[:alnum:]])"), "\\1\n", data)
|
gsub(paste0("(.{1,", lineLength, "})(\\s|[[:alnum:]])"), "\\1\n", data)
|
||||||
} else {
|
} else {
|
||||||
paste(strwrap(data, lineLength), collapse = "\n")
|
paste(strwrap(data, lineLength), collapse = "\n")
|
||||||
|
@ -746,7 +746,7 @@ line_break <- function(data, lineLength = 20, force = FALSE) {
|
||||||
wrap_plot_list <- function(data,
|
wrap_plot_list <- function(data,
|
||||||
tag_levels = NULL,
|
tag_levels = NULL,
|
||||||
title = NULL,
|
title = NULL,
|
||||||
axis.font.family=NULL,
|
axis.font.family = NULL,
|
||||||
...) {
|
...) {
|
||||||
if (ggplot2::is_ggplot(data[[1]])) {
|
if (ggplot2::is_ggplot(data[[1]])) {
|
||||||
if (length(data) > 1) {
|
if (length(data) > 1) {
|
||||||
|
|
|
@ -44,14 +44,7 @@ data_missings_server <- function(id,
|
||||||
|
|
||||||
tryCatch(
|
tryCatch(
|
||||||
{
|
{
|
||||||
if (!is.null(by_var) && by_var != "" && by_var %in% names(df_tbl)) {
|
out <- compare_missings(df_tbl,by_var)
|
||||||
df_tbl[[by_var]] <- ifelse(is.na(df_tbl[[by_var]]), "Missing", "Non-missing")
|
|
||||||
|
|
||||||
out <- gtsummary::tbl_summary(df_tbl, by = by_var) |>
|
|
||||||
gtsummary::add_p()
|
|
||||||
} else {
|
|
||||||
out <- gtsummary::tbl_summary(df_tbl)
|
|
||||||
}
|
|
||||||
},
|
},
|
||||||
error = function(err) {
|
error = function(err) {
|
||||||
showNotification(paste0("Error: ", err), type = "err")
|
showNotification(paste0("Error: ", err), type = "err")
|
||||||
|
@ -129,10 +122,22 @@ missing_demo_app <- function() {
|
||||||
|
|
||||||
missing_demo_app()
|
missing_demo_app()
|
||||||
|
|
||||||
|
#' Pairwise comparison of missings across covariables
|
||||||
|
#'
|
||||||
|
#' @param data data frame
|
||||||
|
#' @param by_var variable to stratify by missingness
|
||||||
|
#'
|
||||||
|
#' @returns gtsummary list object
|
||||||
|
#' @export
|
||||||
|
#'
|
||||||
|
compare_missings <- function(data,by_var){
|
||||||
|
if (!is.null(by_var) && by_var != "" && by_var %in% names(data)) {
|
||||||
|
data[[by_var]] <- ifelse(is.na(data[[by_var]]), "Missing", "Non-missing")
|
||||||
|
|
||||||
|
out <- gtsummary::tbl_summary(data, by = by_var) |>
|
||||||
|
gtsummary::add_p()
|
||||||
|
} else {
|
||||||
|
out <- gtsummary::tbl_summary(data)
|
||||||
|
}
|
||||||
|
out
|
||||||
|
}
|
||||||
|
|
|
@ -44,155 +44,173 @@ regression_ui <- function(id, ...) {
|
||||||
ns <- shiny::NS(id)
|
ns <- shiny::NS(id)
|
||||||
|
|
||||||
shiny::tagList(
|
shiny::tagList(
|
||||||
title = "",
|
# title = "",
|
||||||
sidebar = bslib::sidebar(
|
bslib::nav_panel(
|
||||||
shiny::uiOutput(outputId = ns("data_info"), inline = TRUE),
|
title = "Regression table",
|
||||||
bslib::accordion(
|
bslib::layout_sidebar(
|
||||||
open = "acc_reg",
|
sidebar = bslib::sidebar(
|
||||||
multiple = FALSE,
|
shiny::uiOutput(outputId = ns("data_info"), inline = TRUE),
|
||||||
bslib::accordion_panel(
|
bslib::accordion(
|
||||||
value = "acc_reg",
|
open = "acc_reg",
|
||||||
title = "Regression",
|
multiple = FALSE,
|
||||||
icon = bsicons::bs_icon("calculator"),
|
bslib::accordion_panel(
|
||||||
shiny::uiOutput(outputId = ns("outcome_var")),
|
value = "acc_reg",
|
||||||
# shiny::selectInput(
|
title = "Regression",
|
||||||
# inputId = "design",
|
icon = bsicons::bs_icon("calculator"),
|
||||||
# label = "Study design",
|
shiny::uiOutput(outputId = ns("outcome_var")),
|
||||||
# selected = "no",
|
# shiny::selectInput(
|
||||||
# inline = TRUE,
|
# inputId = "design",
|
||||||
# choices = list(
|
# label = "Study design",
|
||||||
# "Cross-sectional" = "cross-sectional"
|
# selected = "no",
|
||||||
# )
|
# inline = TRUE,
|
||||||
# ),
|
# choices = list(
|
||||||
shiny::uiOutput(outputId = ns("regression_type")),
|
# "Cross-sectional" = "cross-sectional"
|
||||||
shiny::radioButtons(
|
# )
|
||||||
inputId = ns("all"),
|
# ),
|
||||||
label = "Specify covariables",
|
shiny::uiOutput(outputId = ns("regression_type")),
|
||||||
inline = TRUE, selected = 2,
|
shiny::radioButtons(
|
||||||
choiceNames = c(
|
inputId = ns("all"),
|
||||||
"Yes",
|
label = "Specify covariables",
|
||||||
"No"
|
inline = TRUE, selected = 2,
|
||||||
),
|
choiceNames = c(
|
||||||
choiceValues = c(1, 2)
|
"Yes",
|
||||||
),
|
"No"
|
||||||
shiny::conditionalPanel(
|
),
|
||||||
condition = "input.all==1",
|
choiceValues = c(1, 2)
|
||||||
shiny::uiOutput(outputId = ns("regression_vars")),
|
),
|
||||||
shiny::helpText("If none are selected, all are included."),
|
shiny::conditionalPanel(
|
||||||
shiny::tags$br(),
|
condition = "input.all==1",
|
||||||
ns = ns
|
shiny::uiOutput(outputId = ns("regression_vars")),
|
||||||
),
|
shiny::helpText("If none are selected, all are included."),
|
||||||
bslib::input_task_button(
|
shiny::tags$br(),
|
||||||
id = ns("load"),
|
ns = ns
|
||||||
label = "Analyse",
|
),
|
||||||
icon = bsicons::bs_icon("pencil"),
|
bslib::input_task_button(
|
||||||
label_busy = "Working...",
|
id = ns("load"),
|
||||||
icon_busy = fontawesome::fa_i("arrows-rotate",
|
label = "Analyse",
|
||||||
class = "fa-spin",
|
icon = bsicons::bs_icon("pencil"),
|
||||||
"aria-hidden" = "true"
|
label_busy = "Working...",
|
||||||
),
|
icon_busy = fontawesome::fa_i("arrows-rotate",
|
||||||
type = "secondary",
|
class = "fa-spin",
|
||||||
auto_reset = TRUE
|
"aria-hidden" = "true"
|
||||||
),
|
),
|
||||||
shiny::helpText("Press 'Analyse' to create the regression model and after changing parameters."),
|
type = "secondary",
|
||||||
shiny::tags$br(),
|
auto_reset = TRUE
|
||||||
shiny::radioButtons(
|
),
|
||||||
inputId = ns("add_regression_p"),
|
shiny::helpText("Press 'Analyse' to create the regression model and after changing parameters."),
|
||||||
label = "Show p-value",
|
|
||||||
inline = TRUE,
|
|
||||||
selected = "yes",
|
|
||||||
choices = list(
|
|
||||||
"Yes" = "yes",
|
|
||||||
"No" = "no"
|
|
||||||
)
|
|
||||||
),
|
|
||||||
# shiny::tags$br(),
|
|
||||||
# shiny::radioButtons(
|
|
||||||
# inputId = ns("tbl_theme"),
|
|
||||||
# label = "Show p-value",
|
|
||||||
# inline = TRUE,
|
|
||||||
# selected = "jama",
|
|
||||||
# choices = list(
|
|
||||||
# "JAMA" = "jama",
|
|
||||||
# "Lancet" = "lancet",
|
|
||||||
# "NEJM" = "nejm"
|
|
||||||
# )
|
|
||||||
# ),
|
|
||||||
shiny::tags$br()
|
|
||||||
),
|
|
||||||
do.call(
|
|
||||||
bslib::accordion_panel,
|
|
||||||
c(
|
|
||||||
list(
|
|
||||||
value = "acc_plot",
|
|
||||||
title = "Coefficient plot",
|
|
||||||
icon = bsicons::bs_icon("bar-chart-steps"),
|
|
||||||
shiny::tags$br(),
|
shiny::tags$br(),
|
||||||
shiny::uiOutput(outputId = ns("plot_model"))
|
shiny::radioButtons(
|
||||||
),
|
inputId = ns("add_regression_p"),
|
||||||
# plot_download_ui(ns("reg_plot_download"))
|
label = "Show p-value",
|
||||||
shiny::tagList(
|
inline = TRUE,
|
||||||
shinyWidgets::noUiSliderInput(
|
selected = "yes",
|
||||||
inputId = ns("plot_height"),
|
|
||||||
label = "Plot height (mm)",
|
|
||||||
min = 50,
|
|
||||||
max = 300,
|
|
||||||
value = 100,
|
|
||||||
step = 1,
|
|
||||||
format = shinyWidgets::wNumbFormat(decimals = 0),
|
|
||||||
color = datamods:::get_primary_color()
|
|
||||||
),
|
|
||||||
shinyWidgets::noUiSliderInput(
|
|
||||||
inputId = ns("plot_width"),
|
|
||||||
label = "Plot width (mm)",
|
|
||||||
min = 50,
|
|
||||||
max = 300,
|
|
||||||
value = 100,
|
|
||||||
step = 1,
|
|
||||||
format = shinyWidgets::wNumbFormat(decimals = 0),
|
|
||||||
color = datamods:::get_primary_color()
|
|
||||||
),
|
|
||||||
shiny::selectInput(
|
|
||||||
inputId = ns("plot_type"),
|
|
||||||
label = "File format",
|
|
||||||
choices = list(
|
choices = list(
|
||||||
"png",
|
"Yes" = "yes",
|
||||||
"tiff",
|
"No" = "no"
|
||||||
"eps",
|
|
||||||
"pdf",
|
|
||||||
"jpeg",
|
|
||||||
"svg"
|
|
||||||
)
|
)
|
||||||
),
|
),
|
||||||
shiny::br(),
|
# shiny::tags$br(),
|
||||||
# Button
|
# shiny::radioButtons(
|
||||||
shiny::downloadButton(
|
# inputId = ns("tbl_theme"),
|
||||||
outputId = ns("download_plot"),
|
# label = "Show p-value",
|
||||||
label = "Download plot",
|
# inline = TRUE,
|
||||||
icon = shiny::icon("download")
|
# selected = "jama",
|
||||||
|
# choices = list(
|
||||||
|
# "JAMA" = "jama",
|
||||||
|
# "Lancet" = "lancet",
|
||||||
|
# "NEJM" = "nejm"
|
||||||
|
# )
|
||||||
|
# ),
|
||||||
|
shiny::tags$br()
|
||||||
|
)
|
||||||
|
)
|
||||||
|
),
|
||||||
|
gt::gt_output(outputId = ns("table2"))
|
||||||
|
)
|
||||||
|
),
|
||||||
|
bslib::nav_panel(
|
||||||
|
title = "Coefficient plot",
|
||||||
|
bslib::layout_sidebar(
|
||||||
|
sidebar = bslib::sidebar(
|
||||||
|
bslib::accordion(
|
||||||
|
open = "acc_reg",
|
||||||
|
multiple = FALSE,
|
||||||
|
do.call(
|
||||||
|
bslib::accordion_panel,
|
||||||
|
c(
|
||||||
|
list(
|
||||||
|
value = "acc_plot",
|
||||||
|
title = "Coefficient plot",
|
||||||
|
icon = bsicons::bs_icon("bar-chart-steps"),
|
||||||
|
shiny::tags$br(),
|
||||||
|
shiny::uiOutput(outputId = ns("plot_model"))
|
||||||
|
),
|
||||||
|
# plot_download_ui(ns("reg_plot_download"))
|
||||||
|
shiny::tagList(
|
||||||
|
shinyWidgets::noUiSliderInput(
|
||||||
|
inputId = ns("plot_height"),
|
||||||
|
label = "Plot height (mm)",
|
||||||
|
min = 50,
|
||||||
|
max = 300,
|
||||||
|
value = 100,
|
||||||
|
step = 1,
|
||||||
|
format = shinyWidgets::wNumbFormat(decimals = 0),
|
||||||
|
color = datamods:::get_primary_color()
|
||||||
|
),
|
||||||
|
shinyWidgets::noUiSliderInput(
|
||||||
|
inputId = ns("plot_width"),
|
||||||
|
label = "Plot width (mm)",
|
||||||
|
min = 50,
|
||||||
|
max = 300,
|
||||||
|
value = 100,
|
||||||
|
step = 1,
|
||||||
|
format = shinyWidgets::wNumbFormat(decimals = 0),
|
||||||
|
color = datamods:::get_primary_color()
|
||||||
|
),
|
||||||
|
shiny::selectInput(
|
||||||
|
inputId = ns("plot_type"),
|
||||||
|
label = "File format",
|
||||||
|
choices = list(
|
||||||
|
"png",
|
||||||
|
"tiff",
|
||||||
|
"eps",
|
||||||
|
"pdf",
|
||||||
|
"jpeg",
|
||||||
|
"svg"
|
||||||
|
)
|
||||||
|
),
|
||||||
|
shiny::br(),
|
||||||
|
# Button
|
||||||
|
shiny::downloadButton(
|
||||||
|
outputId = ns("download_plot"),
|
||||||
|
label = "Download plot",
|
||||||
|
icon = shiny::icon("download")
|
||||||
|
)
|
||||||
|
)
|
||||||
)
|
)
|
||||||
)
|
)
|
||||||
)
|
)
|
||||||
),
|
),
|
||||||
bslib::accordion_panel(
|
shiny::plotOutput(outputId = ns("regression_plot"), height = "80vh")
|
||||||
value = "acc_checks",
|
|
||||||
title = "Checks",
|
|
||||||
icon = bsicons::bs_icon("clipboard-check"),
|
|
||||||
shiny::uiOutput(outputId = ns("plot_checks"))
|
|
||||||
)
|
|
||||||
)
|
)
|
||||||
),
|
),
|
||||||
bslib::nav_panel(
|
|
||||||
title = "Regression table",
|
|
||||||
gt::gt_output(outputId = ns("table2"))
|
|
||||||
),
|
|
||||||
bslib::nav_panel(
|
|
||||||
title = "Coefficient plot",
|
|
||||||
shiny::plotOutput(outputId = ns("regression_plot"), height = "80vh")
|
|
||||||
),
|
|
||||||
bslib::nav_panel(
|
bslib::nav_panel(
|
||||||
title = "Model checks",
|
title = "Model checks",
|
||||||
shiny::plotOutput(outputId = ns("check"), height = "90vh")
|
bslib::layout_sidebar(
|
||||||
|
sidebar = bslib::sidebar(
|
||||||
|
bslib::accordion(
|
||||||
|
open = "acc_reg",
|
||||||
|
multiple = FALSE,
|
||||||
|
bslib::accordion_panel(
|
||||||
|
value = "acc_checks",
|
||||||
|
title = "Checks",
|
||||||
|
icon = bsicons::bs_icon("clipboard-check"),
|
||||||
|
shiny::uiOutput(outputId = ns("plot_checks"))
|
||||||
|
)
|
||||||
|
)
|
||||||
|
),
|
||||||
|
shiny::plotOutput(outputId = ns("check"), height = "90vh")
|
||||||
|
)
|
||||||
)
|
)
|
||||||
)
|
)
|
||||||
}
|
}
|
||||||
|
|
File diff suppressed because it is too large
Load diff
Loading…
Add table
Reference in a new issue