Compare commits

..

3 commits

Author SHA1 Message Date
328ca287ff
feat: euler limited to dichotomous data not to crash the server
Some checks failed
pkgdown.yaml / pkgdown (push) Has been cancelled
2025-09-25 12:17:44 +02:00
783b454af4
chore: new translations 2025-09-25 12:17:17 +02:00
be87e97f4d
chore: more translatable strings and cleaning 2025-09-25 10:07:19 +02:00
25 changed files with 818 additions and 933 deletions

View file

@ -91,6 +91,7 @@ export(missings_validate)
export(modal_create_column)
export(modal_cut_variable)
export(modal_update_factor)
export(modal_visual_summary)
export(modify_qmd)
export(overview_vars)
export(pipe_string)
@ -141,6 +142,7 @@ export(validation_ui)
export(vectorSelectInput)
export(vertical_stacked_bars)
export(visual_summary)
export(visual_summary_server)
export(visual_summary_ui)
export(wide2long)
export(winbox_create_column)

View file

@ -1,7 +1,9 @@
# FreesearchR 25.9.2 - DEV
# FreesearchR 25.9.2
*NEW* Improvements to translations with more strings having been translated.
The Euler visualisation option has been limited to only plot dichotomous variables. This is also what makes the most sense.
# FreesearchR 25.9.1
*NEW* Language has been revised to make the app more accessible and easier to understand.

View file

@ -1,151 +0,0 @@
data_import_ui <- function(id) {
ns <- shiny::NS(id)
shiny::fluidRow(
shiny::column(width = 2),
shiny::column(
width = 8,
shiny::h4("Choose your data source"),
shiny::br(),
shinyWidgets::radioGroupButtons(
inputId = "source",
selected = "env",
choices = c(
"File upload" = "file",
"REDCap server export" = "redcap",
"Local or sample data" = "env"
),
width = "100%"
),
shiny::helpText("Upload a file from your device, get data directly from REDCap or select a sample data set for testing from the app."),
shiny::br(),
shiny::br(),
shiny::conditionalPanel(
condition = "input.source=='file'",
import_file_ui(
id = ns("file_import"),
layout_params = "dropdown",
title = "Choose a datafile to upload",
file_extensions = c(".csv", ".tsv", ".txt", ".xls", ".xlsx", ".rds", ".sas7bdat", ".ods", ".dta")
)
),
shiny::conditionalPanel(
condition = "input.source=='redcap'",
m_redcap_readUI(id = ns("redcap_import"))
),
shiny::conditionalPanel(
condition = "input.source=='env'",
datamods::import_globalenv_ui(id = ns("env"), title = NULL)
),
shiny::conditionalPanel(
condition = "input.source=='redcap'",
DT::DTOutput(outputId = ns("redcap_prev"))
)
)
)
}
data_import_server <- function(id) {
module <- function(input, output, session) {
ns <- session$ns
rv <- shiny::reactiveValues(
data_temp = NULL,
code = list()
)
data_file <- import_file_server(
id = ns("file_import"),
show_data_in = "popup",
trigger_return = "change",
return_class = "data.frame"
)
shiny::observeEvent(data_file$data(), {
shiny::req(data_file$data())
rv$data_temp <- data_file$data()
rv$code <- append_list(data = data_file$code(), list = rv$code, index = "import")
})
data_redcap <- m_redcap_readServer(
id = "redcap_import"
)
shiny::observeEvent(data_redcap(), {
# rv$data_original <- purrr::pluck(data_redcap(), "data")()
rv$data_temp <- data_redcap()
})
from_env <- datamods::import_globalenv_server(
id = "env",
trigger_return = "change",
btn_show_data = FALSE,
reset = reactive(input$hidden)
)
shiny::observeEvent(from_env$data(), {
shiny::req(from_env$data())
rv$data_temp <- from_env$data()
# rv$code <- append_list(data = from_env$code(),list = rv$code,index = "import")
})
return(list(
# status = reactive(temporary_rv$status),
# name = reactive(temporary_rv$name),
# code = reactive(temporary_rv$code),
data = shiny::reactive(rv$data_temp)
))
}
shiny::moduleServer(
id = id,
module = module
)
}
#' Test app for the data-import module
#'
#' @rdname data-import
#'
#' @examples
#' \dontrun{
#' data_import_demo_app()
#' }
data_import_demo_app <- function() {
ui <- shiny::fluidPage(
data_import_ui("data_import"),
toastui::datagridOutput2(outputId = "table"),
DT::DTOutput("data_summary")
)
server <- function(input, output, session) {
imported <- shiny::reactive(data_import_server(id = "data_import"))
# output$data_summary <- DT::renderDataTable(
# {
# shiny::req(data_val$data)
# data_val$data
# },
# options = list(
# scrollX = TRUE,
# pageLength = 5
# )
# )
output$table <- toastui::renderDatagrid2({
req(imported$data)
toastui::datagrid(
data = head(imported$data, 5),
theme = "striped",
colwidths = "guess",
minBodyHeight = 250
)
})
}
shiny::shinyApp(ui, server)
}

View file

@ -554,11 +554,11 @@ supported_plots <- function() {
fun = "plot_euler",
descr = i18n$t("Euler diagram"),
note = i18n$t("Generate area-proportional Euler diagrams to display set relationships"),
primary.type = c("dichotomous", "categorical"),
secondary.type = c("dichotomous", "categorical"),
primary.type = c("dichotomous"),
secondary.type = c("dichotomous"),
secondary.multi = TRUE,
secondary.max = 4,
tertiary.type = c("dichotomous", "categorical"),
tertiary.type = c("dichotomous"),
secondary.extra = NULL
)
)

View file

@ -206,6 +206,9 @@ describe_col_num <- function(x, with_summary = TRUE) {
tags$div(
i18n$t("Mean:"), round(mean(x, na.rm = TRUE), 2)
),
tags$div(
i18n$t("Median:"), round(median(x, na.rm = TRUE), 2)
),
tags$div(
i18n$t("Max:"), round(max(x, na.rm = TRUE), 2)
),

View file

@ -1 +1 @@
hosted_version <- function()'v25.9.2-250924'
hosted_version <- function()'v25.9.2-250925'

View file

@ -12,20 +12,20 @@ m_redcap_readUI <- function(id, title = TRUE, url = NULL) {
if (isTRUE(title)) {
title <- shiny::tags$h4(
"Import data from REDCap",
i18n$t("Import data from REDCap"),
class = "redcap-module-title"
)
}
server_ui <- shiny::tagList(
shiny::tags$h4("REDCap server"),
shiny::tags$h4(i18n$t("REDCap server")),
shiny::textInput(
inputId = ns("uri"),
label = "Web address",
label = i18n$t("Web address"),
value = if_not_missing(url, "https://redcap.your.institution/"),
width = "100%"
),
shiny::helpText("Format should be either 'https://redcap.your.institution/' or 'https://your.institution/redcap/'"),
shiny::helpText(i18n$t("Format should be either 'https://redcap.your.institution/' or 'https://your.institution/redcap/'")),
# shiny::textInput(
# inputId = ns("api"),
# label = "API token",
@ -34,16 +34,16 @@ m_redcap_readUI <- function(id, title = TRUE, url = NULL) {
# ),
shiny::passwordInput(
inputId = ns("api"),
label = "API token",
label = i18n$t("API token"),
value = "",
width = "100%"
),
shiny::helpText("The token is a string of 32 numbers and letters."),
shiny::helpText(i18n$t("The token is a string of 32 numbers and letters.")),
shiny::br(),
shiny::br(),
shiny::actionButton(
inputId = ns("data_connect"),
label = "Connect",
label = i18n$t("Connect"),
icon = shiny::icon("link", lib = "glyphicon"),
width = "100%",
disabled = TRUE
@ -68,13 +68,13 @@ m_redcap_readUI <- function(id, title = TRUE, url = NULL) {
shiny::uiOutput(outputId = ns("arms")),
shiny::textInput(
inputId = ns("filter"),
label = "Optional filter logic (e.g., [gender] = 'female')"
)
label = i18n$t("Optional filter logic (e.g., [gender] = 'female')"
))
)
params_ui <-
shiny::tagList(
shiny::tags$h4("Data import parameters"),
shiny::tags$h4(i18n$t("Data import parameters")),
shiny::tags$div(
style = htmltools::css(
display = "grid",
@ -100,14 +100,14 @@ m_redcap_readUI <- function(id, title = TRUE, url = NULL) {
)
)
),
shiny::helpText("Select fields/variables to import and click the funnel to apply optional filters"),
shiny::helpText(i18n$t("Select fields/variables to import and click the funnel to apply optional filters")),
shiny::tags$br(),
shiny::tags$br(),
shiny::uiOutput(outputId = ns("data_type")),
shiny::uiOutput(outputId = ns("fill")),
shiny::actionButton(
inputId = ns("data_import"),
label = "Import",
label = i18n$t("Import"),
icon = shiny::icon("download", lib = "glyphicon"),
width = "100%",
disabled = TRUE
@ -226,11 +226,11 @@ m_redcap_readServer <- function(id) {
selector = ns("connect"),
status = "success",
include_data_alert(
see_data_text = "Click to see data dictionary",
see_data_text = i18n$t("Click to see data dictionary"),
dataIdName = "see_dd",
extra = tags$p(
tags$b(phosphoricons::ph("check", weight = "bold"), "Connected to server!"),
glue::glue("The {data_rv$info$project_title} project is loaded.")
tags$b(phosphoricons::ph("check", weight = "bold"), i18n$t("Connected to server!")),
glue::glue(i18n$t("The {data_rv$info$project_title} project is loaded."))
),
btn_show_data = TRUE
)
@ -257,10 +257,10 @@ m_redcap_readServer <- function(id) {
shiny::observeEvent(input$see_dd, {
show_data(
purrr::pluck(data_rv$dd_list, "data"),
title = "Data dictionary",
title = i18n$t("Data dictionary"),
type = "modal",
show_classes = FALSE,
tags$b("Preview:")
tags$b(i18n$t("Preview:"))
)
})
@ -268,10 +268,10 @@ m_redcap_readServer <- function(id) {
show_data(
# purrr::pluck(data_rv$dd_list, "data"),
data_rv$data,
title = "Imported data set",
title = i18n$t("Imported data set"),
type = "modal",
show_classes = FALSE,
tags$b("Preview:")
tags$b(i18n$t("Preview:"))
)
})
@ -289,7 +289,7 @@ m_redcap_readServer <- function(id) {
shiny::req(data_rv$dd_list)
shinyWidgets::virtualSelectInput(
inputId = ns("fields"),
label = "Select fields/variables to import:",
label = i18n$t("Select fields/variables to import:"),
choices = purrr::pluck(data_rv$dd_list, "data") |>
dplyr::select(field_name, form_name) |>
(\(.x){
@ -308,7 +308,7 @@ m_redcap_readServer <- function(id) {
if (isTRUE(data_rv$info$has_repeating_instruments_or_events)) {
vectorSelectInput(
inputId = ns("data_type"),
label = "Specify the data format",
label = i18n$t("Specify the data format"),
choices = c(
"Wide data (One row for each subject)" = "wide",
"Long data for project with repeating instruments (default REDCap)" = "long"
@ -335,7 +335,7 @@ m_redcap_readServer <- function(id) {
if (input$data_type == "long" && isTRUE(any(input$fields %in% data_rv$rep_fields))) {
vectorSelectInput(
inputId = ns("fill"),
label = "Fill missing values?",
label = i18n$t("Fill missing values?"),
choices = c(
"Yes, fill missing, non-repeated values" = "yes",
"No, leave the data as is" = "no"
@ -417,7 +417,7 @@ m_redcap_readServer <- function(id) {
data_rv$data_message <- imported$raw_text
} else {
data_rv$data_status <- "success"
data_rv$data_message <- "Requested data was retrieved!"
data_rv$data_message <- i18n$t("Requested data was retrieved!")
## The data management below should be separated to allow for changing
## "wide"/"long" without re-importing data
@ -452,12 +452,12 @@ m_redcap_readServer <- function(id) {
if (!any(in_data_check[-1])) {
data_rv$data_status <- "warning"
data_rv$data_message <- "Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access."
data_rv$data_message <- i18n$t("Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.")
}
if (!all(in_data_check)) {
data_rv$data_status <- "warning"
data_rv$data_message <- "Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access."
data_rv$data_message <- i18n$t("Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.")
}
data_rv$code <- code
@ -484,7 +484,7 @@ m_redcap_readServer <- function(id) {
# data_rv$data_message
# ),
include_data_alert(
see_data_text = "Click to see the imported data",
see_data_text = i18n$t("Click to see the imported data"),
dataIdName = "see_data",
extra = tags$p(
tags$b(phosphoricons::ph("check", weight = "bold"), data_rv$data_message)

View file

@ -46,7 +46,7 @@ regression_ui <- function(id, ...) {
shiny::tagList(
# title = "",
bslib::nav_panel(
title = "Regression table",
title = i18n$t("Regression table"),
bslib::layout_sidebar(
sidebar = bslib::sidebar(
shiny::uiOutput(outputId = ns("data_info"), inline = TRUE),
@ -56,7 +56,7 @@ regression_ui <- function(id, ...) {
multiple = FALSE,
bslib::accordion_panel(
value = "acc_pan_reg",
title = "Regression",
title = i18n$t("Regression"),
icon = bsicons::bs_icon("calculator"),
shiny::uiOutput(outputId = ns("outcome_var")),
# shiny::selectInput(
@ -71,7 +71,7 @@ regression_ui <- function(id, ...) {
shiny::uiOutput(outputId = ns("regression_type")),
shiny::radioButtons(
inputId = ns("all"),
label = "Specify covariables",
label = i18n$t("Specify covariables"),
inline = TRUE, selected = 2,
choiceNames = c(
"Yes",
@ -82,15 +82,15 @@ regression_ui <- function(id, ...) {
shiny::conditionalPanel(
condition = "input.all==1",
shiny::uiOutput(outputId = ns("regression_vars")),
shiny::helpText("If none are selected, all are included."),
shiny::helpText(i18n$t("If none are selected, all are included.")),
shiny::tags$br(),
ns = ns
),
bslib::input_task_button(
id = ns("load"),
label = "Analyse",
label = i18n$t("Analyse"),
icon = bsicons::bs_icon("pencil"),
label_busy = "Working...",
label_busy = i18n$t("Working..."),
icon_busy = fontawesome::fa_i("arrows-rotate",
class = "fa-spin",
"aria-hidden" = "true"
@ -98,17 +98,18 @@ regression_ui <- function(id, ...) {
type = "secondary",
auto_reset = TRUE
),
shiny::helpText("Press 'Analyse' to create the regression model and after changing parameters."),
shiny::helpText(i18n$t("Press 'Analyse' to create the regression model and after changing parameters.")),
shiny::tags$br(),
shiny::radioButtons(
inputId = ns("add_regression_p"),
label = "Show p-value",
label = i18n$t("Show p-value"),
inline = TRUE,
selected = "yes",
choices = list(
"Yes" = "yes",
"No" = "no"
)
choiceNames = c(
"Yes",
"No"
),
choiceValues = c("yes", "no")
),
# shiny::tags$br(),
# shiny::radioButtons(
@ -151,7 +152,7 @@ regression_ui <- function(id, ...) {
shiny::tagList(
shinyWidgets::noUiSliderInput(
inputId = ns("plot_height"),
label = "Plot height (mm)",
label = i18n$t("Plot height (mm)"),
min = 50,
max = 300,
value = 100,
@ -161,7 +162,7 @@ regression_ui <- function(id, ...) {
),
shinyWidgets::noUiSliderInput(
inputId = ns("plot_width"),
label = "Plot width (mm)",
label = i18n$t("Plot width (mm)"),
min = 50,
max = 300,
value = 100,
@ -171,7 +172,7 @@ regression_ui <- function(id, ...) {
),
shiny::selectInput(
inputId = ns("plot_type"),
label = "File format",
label = i18n$t("File format"),
choices = list(
"png",
"tiff",
@ -185,7 +186,7 @@ regression_ui <- function(id, ...) {
# Button
shiny::downloadButton(
outputId = ns("download_plot"),
label = "Download plot",
label = i18n$t("Download plot"),
icon = shiny::icon("download")
)
)
@ -197,7 +198,7 @@ regression_ui <- function(id, ...) {
)
),
bslib::nav_panel(
title = "Model checks",
title = i18n$t("Model checks"),
bslib::layout_sidebar(
sidebar = bslib::sidebar(
bslib::accordion(

Binary file not shown.

View file

@ -321,11 +321,11 @@ ui_elements <- function(selection) {
shiny::tags$br(),
shiny::actionButton(
inputId = "data_reset",
label = "Restore original data",
label = i18n$t("Restore original data"),
width = "100%"
),
shiny::tags$br(),
shiny::helpText("Reset to original imported dataset. Careful! There is no un-doing."),
shiny::helpText(i18n$t("Reset to original imported dataset. Careful! There is no un-doing.")),
shiny::tags$br()
)
# )
@ -344,7 +344,7 @@ ui_elements <- function(selection) {
# bslib::navset_bar(
# title = "",
bslib::nav_panel(
title = "Characteristics",
title = i18n$t("Characteristics"),
icon = bsicons::bs_icon("table"),
bslib::layout_sidebar(
sidebar = bslib::sidebar(
@ -359,12 +359,12 @@ ui_elements <- function(selection) {
title = "Settings",
icon = bsicons::bs_icon("table"),
shiny::uiOutput("strat_var"),
shiny::helpText("Only factor/categorical variables are available for stratification. Go back to the 'Prepare' tab to reclass a variable if it's not on the list."),
shiny::helpText(i18n$t("Only factor/categorical variables are available for stratification. Go back to the 'Prepare' tab to reclass a variable if it's not on the list.")),
shiny::conditionalPanel(
condition = "input.strat_var!='none'",
shiny::radioButtons(
inputId = "add_p",
label = "Compare strata?",
label = i18n$t("Compare strata?"),
selected = "no",
inline = TRUE,
choices = list(
@ -378,7 +378,7 @@ ui_elements <- function(selection) {
shiny::br(),
shiny::actionButton(
inputId = "act_eval",
label = "Evaluate",
label = i18n$t("Evaluate"),
width = "100%",
icon = shiny::icon("calculator"),
disabled = TRUE
@ -390,7 +390,7 @@ ui_elements <- function(selection) {
)
),
bslib::nav_panel(
title = "Correlations",
title = i18n$t("Correlations"),
icon = bsicons::bs_icon("bounding-box"),
bslib::layout_sidebar(
sidebar = bslib::sidebar(
@ -404,11 +404,11 @@ ui_elements <- function(selection) {
title = "Settings",
icon = bsicons::bs_icon("bounding-box"),
shiny::uiOutput("outcome_var_cor"),
shiny::helpText("To avoid evaluating the correlation of the outcome variable, this can be excluded from the plot or select 'none'."),
shiny::helpText(i18n$t("To avoid evaluating the correlation of the outcome variable, this can be excluded from the plot or select 'none'.")),
shiny::br(),
shinyWidgets::noUiSliderInput(
inputId = "cor_cutoff",
label = "Correlation cut-off",
label = i18n$t("Correlation cut-off"),
min = 0,
max = 1,
step = .01,
@ -416,7 +416,7 @@ ui_elements <- function(selection) {
format = shinyWidgets::wNumbFormat(decimals = 2),
color = datamods:::get_primary_color()
),
shiny::helpText("Set the cut-off for considered 'highly correlated'.")
shiny::helpText(i18n$t("Set the cut-off for considered 'highly correlated'."))
)
)
),
@ -424,7 +424,7 @@ ui_elements <- function(selection) {
)
),
bslib::nav_panel(
title = "Missings",
title = i18n$t("Missings"),
icon = bsicons::bs_icon("x-circle"),
bslib::layout_sidebar(
sidebar = bslib::sidebar(
@ -437,7 +437,7 @@ ui_elements <- function(selection) {
title = "Settings",
icon = bsicons::bs_icon("x-circle"),
shiny::uiOutput("missings_var"),
shiny::helpText("To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not.")
shiny::helpText(i18n$t("To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not."))
)
)
),
@ -525,7 +525,8 @@ ui_elements <- function(selection) {
outputId = "report",
label = "Download report",
icon = shiny::icon("download")
)
),
shiny::br()
# shiny::helpText("If choosing to output to MS Word, please note, that when opening the document, two errors will pop-up. Choose to repair and choose not to update references. The issue is being worked on. You can always choose LibreOffice instead."),
),
shiny::column(

View file

@ -1,10 +1,12 @@
#' Data correlations evaluation module
#'
#' @param id Module id
#' @param id id
#'
#' @name data-missings
#' @name visual-summary
#' @returns Shiny ui module
#' @export
#'
#' @example examples/visual_summary_demo.R
visual_summary_ui <- function(id) {
ns <- shiny::NS(id)
@ -13,8 +15,17 @@ visual_summary_ui <- function(id) {
)
}
#' Visual summary server
#'
#' @param data_r reactive data
#' @param ... passed on to the visual_summary() function
#'
#' @name visual-summary
#' @returns shiny server
#' @export
#'
visual_summary_server <- function(id,
data_r=shiny::reactive(NULL),
data_r = shiny::reactive(NULL),
...) {
shiny::moduleServer(
id = id,
@ -43,45 +54,26 @@ visual_summary_server <- function(id,
# missings_apex_plot(datar(), ...)
# })
output$visual_plot <- shiny::renderPlot(expr = {
visual_summary(data = rv$data,...)
visual_summary(data = rv$data, na.label = i18n$t("Missings"), legend.title = i18n$t("Class"), ylab = i18n$t("Observations"), ...)
})
}
)
}
visual_summary_demo_app <- function() {
ui <- shiny::fluidPage(
shiny::actionButton(
inputId = "modal_missings",
label = "Visual summary",
width = "100%",
disabled = FALSE
)
)
server <- function(input, output, session) {
data_demo <- mtcars
data_demo[sample(1:32, 10), "cyl"] <- NA
data_demo[sample(1:32, 8), "vs"] <- NA
visual_summary_server(id = "data", data = shiny::reactive(data_demo))
observeEvent(input$modal_missings, {
tryCatch(
{
modal_visual_summary(id = "data")
},
error = function(err) {
showNotification(paste0("We encountered the following error browsing your data: ", err), type = "err")
}
)
})
}
shiny::shinyApp(ui, server)
}
visual_summary_demo_app()
#' Visual summary modal
#'
#' @param title title
#' @param easyClose easyClose
#' @param size modal size
#' @param footer modal footer
#' @param ... ignored
#'
#' @name visual-summary
#'
#' @returns shiny modal
#' @export
#'
modal_visual_summary <- function(id,
title = "Visual overview of data classes and missing observations",
easyClose = TRUE,
@ -100,9 +92,10 @@ modal_visual_summary <- function(id,
## Slow with many observations...
#' Plot missings and class with apexcharter
#' Plot missings and class with apexcharter. Not in use with FreesearchR.
#'
#' @param data data frame
#' @name visual-summary
#'
#' @returns An [apexchart()] `htmlwidget` object.
#' @export
@ -157,6 +150,10 @@ missings_apex_plot <- function(data, animation = FALSE, ...) {
#'
#' @param data data
#' @param ... optional arguments passed to data_summary_gather()
#' @param legend.title Legend title
#' @param ylab Y axis label
#'
#' @name visual-summary
#'
#' @returns ggplot2 object
#' @export
@ -167,11 +164,15 @@ missings_apex_plot <- function(data, animation = FALSE, ...) {
#' data_demo[sample(1:32, 8), "vs"] <- NA
#' visual_summary(data_demo)
#' visual_summary(data_demo, palette.fun = scales::hue_pal())
#' visual_summary(dplyr::storms)
#' visual_summary(dplyr::storms, summary.fun = data_type)
visual_summary <- function(data, legend.title = "Data class", ...) {
#' visual_summary(dplyr::storms, summary.fun = data_type, na.label = "Missings", legend.title = "Class")
visual_summary <- function(data, legend.title = NULL, ylab = "Observations", ...) {
l <- data_summary_gather(data, ...)
if (is.null(legend.title)) {
legend.title <- l$summary.fun
}
df <- l$data
df$valueType <- factor(df$valueType, levels = names(l$colors))
@ -185,13 +186,13 @@ visual_summary <- function(data, legend.title = "Data class", ...) {
vjust = 1, hjust = 1
)) +
ggplot2::scale_fill_manual(values = l$colors) +
ggplot2::labs(x = "", y = "Observations") +
ggplot2::labs(x = "", y = ylab) +
ggplot2::scale_y_reverse() +
ggplot2::theme(axis.text.x = ggplot2::element_text(hjust = 0.5)) +
ggplot2::guides(colour = "none") +
ggplot2::guides(fill = ggplot2::guide_legend(title = legend.title)) +
# change the limits etc.
ggplot2::guides(fill = ggplot2::guide_legend(title = "Type")) +
# ggplot2::guides(fill = ggplot2::guide_legend(title = guide.lab)) +
# add info about the axes
ggplot2::scale_x_discrete(position = "top") +
ggplot2::theme(axis.text.x = ggplot2::element_text(hjust = 0)) +
@ -206,16 +207,18 @@ visual_summary <- function(data, legend.title = "Data class", ...) {
#' Data summary for printing visual summary
#'
#' @param data data.frame
#' @param fun summary function. Default is "class"
#' @param palette.fun optionally use specific palette functions. First argument
#' has to be the length.
#' @param summary.fun fun for summarising
#' @param na.label label for NA
#' @param ... overflow
#'
#' @returns data.frame
#' @export
#'
#' @examples
#' mtcars |> data_summary_gather()
data_summary_gather <- function(data, summary.fun = class, palette.fun = viridisLite::viridis) {
data_summary_gather <- function(data, summary.fun = class, palette.fun = viridisLite::viridis, na.label = "NA", ...) {
df_plot <- setNames(data, unique_short(names(data))) |>
purrr::map_df(\(x){
ifelse(is.na(x),
@ -237,12 +240,12 @@ data_summary_gather <- function(data, summary.fun = class, palette.fun = viridis
forcats::as_factor() |>
as.numeric()
df_plot$valueType[is.na(df_plot$valueType)] <- "NA"
df_plot$valueType[is.na(df_plot$valueType)] <- na.label
df_plot$valueType_num[is.na(df_plot$valueType_num)] <- max(df_plot$valueType_num, na.rm = TRUE) + 1
labels <- setNames(unique(df_plot$valueType_num), unique(df_plot$valueType)) |> sort()
if (any(df_plot$valueType == "NA")) {
if (any(df_plot$valueType == na.label)) {
colors <- setNames(c(palette.fun(length(labels) - 1), "#999999"), names(labels))
} else {
colors <- setNames(palette.fun(length(labels)), names(labels))
@ -260,7 +263,7 @@ data_summary_gather <- function(data, summary.fun = class, palette.fun = viridis
}) |>
setNames(NULL)
list(data = df_plot, colors = colors, labels = label_list)
list(data = df_plot, colors = colors, labels = label_list, summary.fun = deparse(substitute(summary.fun)))
}

View file

@ -11,11 +11,11 @@
|collate |en_US.UTF-8 |
|ctype |en_US.UTF-8 |
|tz |Europe/Copenhagen |
|date |2025-09-24 |
|date |2025-09-25 |
|rstudio |2025.05.0+496 Mariposa Orchid (desktop) |
|pandoc |3.6.4 @ /opt/homebrew/bin/ (via rmarkdown) |
|quarto |1.7.30 @ /usr/local/bin/quarto |
|FreesearchR |25.9.2.250924 |
|FreesearchR |25.9.2.250925 |
--------------------------------------------------------------------------------
@ -26,6 +26,8 @@
|apexcharter |0.4.4 |2024-09-06 |CRAN (R 4.4.1) |
|askpass |1.2.1 |2024-10-04 |CRAN (R 4.4.1) |
|assertthat |0.2.1 |2019-03-21 |CRAN (R 4.4.1) |
|attachment |0.4.5 |2025-03-14 |CRAN (R 4.4.1) |
|attempt |0.3.1 |2020-05-03 |CRAN (R 4.4.1) |
|backports |1.5.0 |2024-05-23 |CRAN (R 4.4.1) |
|base64enc |0.1-3 |2015-07-28 |CRAN (R 4.4.1) |
|bayestestR |0.16.1 |2025-07-01 |CRAN (R 4.4.1) |
@ -39,7 +41,6 @@
|bsicons |0.1.2 |2023-11-04 |CRAN (R 4.4.0) |
|bslib |0.9.0 |2025-01-30 |CRAN (R 4.4.1) |
|cachem |1.1.0 |2024-05-16 |CRAN (R 4.4.1) |
|callr |3.7.6 |2024-03-25 |CRAN (R 4.4.0) |
|cards |0.6.1 |2025-07-03 |CRAN (R 4.4.1) |
|cardx |0.2.5 |2025-07-03 |CRAN (R 4.4.1) |
|caTools |1.18.3 |2024-09-04 |CRAN (R 4.4.1) |
@ -61,6 +62,7 @@
|devtools |2.4.5 |2022-10-11 |CRAN (R 4.4.0) |
|DHARMa |0.4.7 |2024-10-18 |CRAN (R 4.4.1) |
|digest |0.6.37 |2024-08-19 |CRAN (R 4.4.1) |
|dockerfiler |0.2.5 |2025-05-07 |CRAN (R 4.4.1) |
|doParallel |1.0.17 |2022-02-07 |CRAN (R 4.4.0) |
|dplyr |1.1.4 |2023-11-17 |CRAN (R 4.4.0) |
|DT |0.33 |2024-04-04 |CRAN (R 4.4.0) |
@ -114,6 +116,7 @@
|KernSmooth |2.23-26 |2025-01-01 |CRAN (R 4.4.1) |
|keyring |1.4.1 |2025-06-15 |CRAN (R 4.4.1) |
|knitr |1.50 |2025-03-16 |CRAN (R 4.4.1) |
|labeling |0.4.3 |2023-08-29 |CRAN (R 4.4.1) |
|later |1.4.2 |2025-04-08 |CRAN (R 4.4.1) |
|lattice |0.22-7 |2025-04-02 |CRAN (R 4.4.1) |
|lifecycle |1.0.4 |2023-11-07 |CRAN (R 4.4.1) |
@ -144,10 +147,10 @@
|pillar |1.11.0 |2025-07-04 |CRAN (R 4.4.1) |
|pkgbuild |1.4.8 |2025-05-26 |CRAN (R 4.4.1) |
|pkgconfig |2.0.3 |2019-09-22 |CRAN (R 4.4.1) |
|pkgdown |2.1.3 |2025-05-25 |CRAN (R 4.4.1) |
|pkgload |1.4.0 |2024-06-28 |CRAN (R 4.4.0) |
|plyr |1.8.9 |2023-10-02 |CRAN (R 4.4.1) |
|polyclip |1.10-7 |2024-07-23 |CRAN (R 4.4.1) |
|polylabelr |0.3.0 |2024-11-19 |CRAN (R 4.4.1) |
|pracma |2.4.4 |2023-11-10 |CRAN (R 4.4.1) |
|processx |3.8.6 |2025-02-21 |CRAN (R 4.4.1) |
|profvis |0.4.0 |2024-09-20 |CRAN (R 4.4.1) |
@ -158,9 +161,6 @@
|qqconf |1.3.2 |2023-04-14 |CRAN (R 4.4.0) |
|qqplotr |0.0.6 |2023-01-25 |CRAN (R 4.4.0) |
|quarto |1.5.0 |2025-07-28 |RSPM (R 4.4.0) |
|R.methodsS3 |1.8.2 |2022-06-13 |CRAN (R 4.4.1) |
|R.oo |1.27.1 |2025-05-02 |CRAN (R 4.4.1) |
|R.utils |2.13.0 |2025-02-24 |CRAN (R 4.4.1) |
|R6 |2.6.1 |2025-02-15 |CRAN (R 4.4.1) |
|ragg |1.4.0 |2025-04-10 |CRAN (R 4.4.1) |
|rankinPlot |1.1.0 |2023-01-30 |CRAN (R 4.4.0) |
@ -195,6 +195,7 @@
|sessioninfo |1.2.3 |2025-02-05 |CRAN (R 4.4.1) |
|shiny |1.11.1 |2025-07-03 |CRAN (R 4.4.1) |
|shiny.i18n |0.3.0 |2023-01-16 |CRAN (R 4.4.0) |
|shiny2docker |0.0.3 |2025-06-28 |CRAN (R 4.4.1) |
|shinybusy |0.3.3 |2024-03-09 |CRAN (R 4.4.0) |
|shinyjs |2.1.0 |2021-12-23 |CRAN (R 4.4.0) |
|shinyTime |1.0.3 |2022-08-19 |CRAN (R 4.4.0) |
@ -224,4 +225,5 @@
|xml2 |1.3.8 |2025-03-14 |CRAN (R 4.4.1) |
|xtable |1.8-4 |2019-04-21 |CRAN (R 4.4.1) |
|yaml |2.3.10 |2024-07-26 |CRAN (R 4.4.1) |
|yesno |0.1.3 |2024-07-26 |CRAN (R 4.4.1) |
|zip |2.3.3 |2025-05-13 |CRAN (R 4.4.1) |

View file

@ -1,7 +1,7 @@
########
#### Current file: /var/folders/9l/xbc19wxx0g79jdd2sf_0v291mhwh7f/T//RtmpCENEZ9/file6e54cbc3538.R
#### Current file: /var/folders/9l/xbc19wxx0g79jdd2sf_0v291mhwh7f/T//Rtmpo2rU34/file15cb36d55cf55.R
########
i18n_path <- here::here("translations")
@ -2205,11 +2205,11 @@ supported_plots <- function() {
fun = "plot_euler",
descr = i18n$t("Euler diagram"),
note = i18n$t("Generate area-proportional Euler diagrams to display set relationships"),
primary.type = c("dichotomous", "categorical"),
secondary.type = c("dichotomous", "categorical"),
primary.type = c("dichotomous"),
secondary.type = c("dichotomous"),
secondary.multi = TRUE,
secondary.max = 4,
tertiary.type = c("dichotomous", "categorical"),
tertiary.type = c("dichotomous"),
secondary.extra = NULL
)
)
@ -2523,163 +2523,6 @@ clean_common_axis <- function(p, axis) {
}
########
#### Current file: /Users/au301842/FreesearchR/R//data-import.R
########
data_import_ui <- function(id) {
ns <- shiny::NS(id)
shiny::fluidRow(
shiny::column(width = 2),
shiny::column(
width = 8,
shiny::h4("Choose your data source"),
shiny::br(),
shinyWidgets::radioGroupButtons(
inputId = "source",
selected = "env",
choices = c(
"File upload" = "file",
"REDCap server export" = "redcap",
"Local or sample data" = "env"
),
width = "100%"
),
shiny::helpText("Upload a file from your device, get data directly from REDCap or select a sample data set for testing from the app."),
shiny::br(),
shiny::br(),
shiny::conditionalPanel(
condition = "input.source=='file'",
import_file_ui(
id = ns("file_import"),
layout_params = "dropdown",
title = "Choose a datafile to upload",
file_extensions = c(".csv", ".tsv", ".txt", ".xls", ".xlsx", ".rds", ".sas7bdat", ".ods", ".dta")
)
),
shiny::conditionalPanel(
condition = "input.source=='redcap'",
m_redcap_readUI(id = ns("redcap_import"))
),
shiny::conditionalPanel(
condition = "input.source=='env'",
datamods::import_globalenv_ui(id = ns("env"), title = NULL)
),
shiny::conditionalPanel(
condition = "input.source=='redcap'",
DT::DTOutput(outputId = ns("redcap_prev"))
)
)
)
}
data_import_server <- function(id) {
module <- function(input, output, session) {
ns <- session$ns
rv <- shiny::reactiveValues(
data_temp = NULL,
code = list()
)
data_file <- import_file_server(
id = ns("file_import"),
show_data_in = "popup",
trigger_return = "change",
return_class = "data.frame"
)
shiny::observeEvent(data_file$data(), {
shiny::req(data_file$data())
rv$data_temp <- data_file$data()
rv$code <- append_list(data = data_file$code(), list = rv$code, index = "import")
})
data_redcap <- m_redcap_readServer(
id = "redcap_import"
)
shiny::observeEvent(data_redcap(), {
# rv$data_original <- purrr::pluck(data_redcap(), "data")()
rv$data_temp <- data_redcap()
})
from_env <- datamods::import_globalenv_server(
id = "env",
trigger_return = "change",
btn_show_data = FALSE,
reset = reactive(input$hidden)
)
shiny::observeEvent(from_env$data(), {
shiny::req(from_env$data())
rv$data_temp <- from_env$data()
# rv$code <- append_list(data = from_env$code(),list = rv$code,index = "import")
})
return(list(
# status = reactive(temporary_rv$status),
# name = reactive(temporary_rv$name),
# code = reactive(temporary_rv$code),
data = shiny::reactive(rv$data_temp)
))
}
shiny::moduleServer(
id = id,
module = module
)
}
#' Test app for the data-import module
#'
#' @rdname data-import
#'
#' @examples
#' \dontrun{
#' data_import_demo_app()
#' }
data_import_demo_app <- function() {
ui <- shiny::fluidPage(
data_import_ui("data_import"),
toastui::datagridOutput2(outputId = "table"),
DT::DTOutput("data_summary")
)
server <- function(input, output, session) {
imported <- shiny::reactive(data_import_server(id = "data_import"))
# output$data_summary <- DT::renderDataTable(
# {
# shiny::req(data_val$data)
# data_val$data
# },
# options = list(
# scrollX = TRUE,
# pageLength = 5
# )
# )
output$table <- toastui::renderDatagrid2({
req(imported$data)
toastui::datagrid(
data = head(imported$data, 5),
theme = "striped",
colwidths = "guess",
minBodyHeight = 250
)
})
}
shiny::shinyApp(ui, server)
}
########
#### Current file: /Users/au301842/FreesearchR/R//data-summary.R
########
@ -3290,6 +3133,9 @@ describe_col_num <- function(x, with_summary = TRUE) {
tags$div(
i18n$t("Mean:"), round(mean(x, na.rm = TRUE), 2)
),
tags$div(
i18n$t("Median:"), round(median(x, na.rm = TRUE), 2)
),
tags$div(
i18n$t("Max:"), round(max(x, na.rm = TRUE), 2)
),
@ -4107,7 +3953,7 @@ simple_snake <- function(data){
#### Current file: /Users/au301842/FreesearchR/R//hosted_version.R
########
hosted_version <- function()'v25.9.2-250924'
hosted_version <- function()'v25.9.2-250925'
########
@ -5703,20 +5549,20 @@ m_redcap_readUI <- function(id, title = TRUE, url = NULL) {
if (isTRUE(title)) {
title <- shiny::tags$h4(
"Import data from REDCap",
i18n$t("Import data from REDCap"),
class = "redcap-module-title"
)
}
server_ui <- shiny::tagList(
shiny::tags$h4("REDCap server"),
shiny::tags$h4(i18n$t("REDCap server")),
shiny::textInput(
inputId = ns("uri"),
label = "Web address",
label = i18n$t("Web address"),
value = if_not_missing(url, "https://redcap.your.institution/"),
width = "100%"
),
shiny::helpText("Format should be either 'https://redcap.your.institution/' or 'https://your.institution/redcap/'"),
shiny::helpText(i18n$t("Format should be either 'https://redcap.your.institution/' or 'https://your.institution/redcap/'")),
# shiny::textInput(
# inputId = ns("api"),
# label = "API token",
@ -5725,16 +5571,16 @@ m_redcap_readUI <- function(id, title = TRUE, url = NULL) {
# ),
shiny::passwordInput(
inputId = ns("api"),
label = "API token",
label = i18n$t("API token"),
value = "",
width = "100%"
),
shiny::helpText("The token is a string of 32 numbers and letters."),
shiny::helpText(i18n$t("The token is a string of 32 numbers and letters.")),
shiny::br(),
shiny::br(),
shiny::actionButton(
inputId = ns("data_connect"),
label = "Connect",
label = i18n$t("Connect"),
icon = shiny::icon("link", lib = "glyphicon"),
width = "100%",
disabled = TRUE
@ -5759,13 +5605,13 @@ m_redcap_readUI <- function(id, title = TRUE, url = NULL) {
shiny::uiOutput(outputId = ns("arms")),
shiny::textInput(
inputId = ns("filter"),
label = "Optional filter logic (e.g., [gender] = 'female')"
)
label = i18n$t("Optional filter logic (e.g., [gender] = 'female')"
))
)
params_ui <-
shiny::tagList(
shiny::tags$h4("Data import parameters"),
shiny::tags$h4(i18n$t("Data import parameters")),
shiny::tags$div(
style = htmltools::css(
display = "grid",
@ -5791,14 +5637,14 @@ m_redcap_readUI <- function(id, title = TRUE, url = NULL) {
)
)
),
shiny::helpText("Select fields/variables to import and click the funnel to apply optional filters"),
shiny::helpText(i18n$t("Select fields/variables to import and click the funnel to apply optional filters")),
shiny::tags$br(),
shiny::tags$br(),
shiny::uiOutput(outputId = ns("data_type")),
shiny::uiOutput(outputId = ns("fill")),
shiny::actionButton(
inputId = ns("data_import"),
label = "Import",
label = i18n$t("Import"),
icon = shiny::icon("download", lib = "glyphicon"),
width = "100%",
disabled = TRUE
@ -5917,11 +5763,11 @@ m_redcap_readServer <- function(id) {
selector = ns("connect"),
status = "success",
include_data_alert(
see_data_text = "Click to see data dictionary",
see_data_text = i18n$t("Click to see data dictionary"),
dataIdName = "see_dd",
extra = tags$p(
tags$b(phosphoricons::ph("check", weight = "bold"), "Connected to server!"),
glue::glue("The {data_rv$info$project_title} project is loaded.")
tags$b(phosphoricons::ph("check", weight = "bold"), i18n$t("Connected to server!")),
glue::glue(i18n$t("The {data_rv$info$project_title} project is loaded."))
),
btn_show_data = TRUE
)
@ -5948,10 +5794,10 @@ m_redcap_readServer <- function(id) {
shiny::observeEvent(input$see_dd, {
show_data(
purrr::pluck(data_rv$dd_list, "data"),
title = "Data dictionary",
title = i18n$t("Data dictionary"),
type = "modal",
show_classes = FALSE,
tags$b("Preview:")
tags$b(i18n$t("Preview:"))
)
})
@ -5959,10 +5805,10 @@ m_redcap_readServer <- function(id) {
show_data(
# purrr::pluck(data_rv$dd_list, "data"),
data_rv$data,
title = "Imported data set",
title = i18n$t("Imported data set"),
type = "modal",
show_classes = FALSE,
tags$b("Preview:")
tags$b(i18n$t("Preview:"))
)
})
@ -5980,7 +5826,7 @@ m_redcap_readServer <- function(id) {
shiny::req(data_rv$dd_list)
shinyWidgets::virtualSelectInput(
inputId = ns("fields"),
label = "Select fields/variables to import:",
label = i18n$t("Select fields/variables to import:"),
choices = purrr::pluck(data_rv$dd_list, "data") |>
dplyr::select(field_name, form_name) |>
(\(.x){
@ -5999,7 +5845,7 @@ m_redcap_readServer <- function(id) {
if (isTRUE(data_rv$info$has_repeating_instruments_or_events)) {
vectorSelectInput(
inputId = ns("data_type"),
label = "Specify the data format",
label = i18n$t("Specify the data format"),
choices = c(
"Wide data (One row for each subject)" = "wide",
"Long data for project with repeating instruments (default REDCap)" = "long"
@ -6026,7 +5872,7 @@ m_redcap_readServer <- function(id) {
if (input$data_type == "long" && isTRUE(any(input$fields %in% data_rv$rep_fields))) {
vectorSelectInput(
inputId = ns("fill"),
label = "Fill missing values?",
label = i18n$t("Fill missing values?"),
choices = c(
"Yes, fill missing, non-repeated values" = "yes",
"No, leave the data as is" = "no"
@ -6108,7 +5954,7 @@ m_redcap_readServer <- function(id) {
data_rv$data_message <- imported$raw_text
} else {
data_rv$data_status <- "success"
data_rv$data_message <- "Requested data was retrieved!"
data_rv$data_message <- i18n$t("Requested data was retrieved!")
## The data management below should be separated to allow for changing
## "wide"/"long" without re-importing data
@ -6143,12 +5989,12 @@ m_redcap_readServer <- function(id) {
if (!any(in_data_check[-1])) {
data_rv$data_status <- "warning"
data_rv$data_message <- "Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access."
data_rv$data_message <- i18n$t("Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.")
}
if (!all(in_data_check)) {
data_rv$data_status <- "warning"
data_rv$data_message <- "Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access."
data_rv$data_message <- i18n$t("Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.")
}
data_rv$code <- code
@ -6175,7 +6021,7 @@ m_redcap_readServer <- function(id) {
# data_rv$data_message
# ),
include_data_alert(
see_data_text = "Click to see the imported data",
see_data_text = i18n$t("Click to see the imported data"),
dataIdName = "see_data",
extra = tags$p(
tags$b(phosphoricons::ph("check", weight = "bold"), data_rv$data_message)
@ -7515,7 +7361,7 @@ regression_ui <- function(id, ...) {
shiny::tagList(
# title = "",
bslib::nav_panel(
title = "Regression table",
title = i18n$t("Regression table"),
bslib::layout_sidebar(
sidebar = bslib::sidebar(
shiny::uiOutput(outputId = ns("data_info"), inline = TRUE),
@ -7525,7 +7371,7 @@ regression_ui <- function(id, ...) {
multiple = FALSE,
bslib::accordion_panel(
value = "acc_pan_reg",
title = "Regression",
title = i18n$t("Regression"),
icon = bsicons::bs_icon("calculator"),
shiny::uiOutput(outputId = ns("outcome_var")),
# shiny::selectInput(
@ -7540,7 +7386,7 @@ regression_ui <- function(id, ...) {
shiny::uiOutput(outputId = ns("regression_type")),
shiny::radioButtons(
inputId = ns("all"),
label = "Specify covariables",
label = i18n$t("Specify covariables"),
inline = TRUE, selected = 2,
choiceNames = c(
"Yes",
@ -7551,15 +7397,15 @@ regression_ui <- function(id, ...) {
shiny::conditionalPanel(
condition = "input.all==1",
shiny::uiOutput(outputId = ns("regression_vars")),
shiny::helpText("If none are selected, all are included."),
shiny::helpText(i18n$t("If none are selected, all are included.")),
shiny::tags$br(),
ns = ns
),
bslib::input_task_button(
id = ns("load"),
label = "Analyse",
label = i18n$t("Analyse"),
icon = bsicons::bs_icon("pencil"),
label_busy = "Working...",
label_busy = i18n$t("Working..."),
icon_busy = fontawesome::fa_i("arrows-rotate",
class = "fa-spin",
"aria-hidden" = "true"
@ -7567,17 +7413,18 @@ regression_ui <- function(id, ...) {
type = "secondary",
auto_reset = TRUE
),
shiny::helpText("Press 'Analyse' to create the regression model and after changing parameters."),
shiny::helpText(i18n$t("Press 'Analyse' to create the regression model and after changing parameters.")),
shiny::tags$br(),
shiny::radioButtons(
inputId = ns("add_regression_p"),
label = "Show p-value",
label = i18n$t("Show p-value"),
inline = TRUE,
selected = "yes",
choices = list(
"Yes" = "yes",
"No" = "no"
)
choiceNames = c(
"Yes",
"No"
),
choiceValues = c("yes", "no")
),
# shiny::tags$br(),
# shiny::radioButtons(
@ -7620,7 +7467,7 @@ regression_ui <- function(id, ...) {
shiny::tagList(
shinyWidgets::noUiSliderInput(
inputId = ns("plot_height"),
label = "Plot height (mm)",
label = i18n$t("Plot height (mm)"),
min = 50,
max = 300,
value = 100,
@ -7630,7 +7477,7 @@ regression_ui <- function(id, ...) {
),
shinyWidgets::noUiSliderInput(
inputId = ns("plot_width"),
label = "Plot width (mm)",
label = i18n$t("Plot width (mm)"),
min = 50,
max = 300,
value = 100,
@ -7640,7 +7487,7 @@ regression_ui <- function(id, ...) {
),
shiny::selectInput(
inputId = ns("plot_type"),
label = "File format",
label = i18n$t("File format"),
choices = list(
"png",
"tiff",
@ -7654,7 +7501,7 @@ regression_ui <- function(id, ...) {
# Button
shiny::downloadButton(
outputId = ns("download_plot"),
label = "Download plot",
label = i18n$t("Download plot"),
icon = shiny::icon("download")
)
)
@ -7666,7 +7513,7 @@ regression_ui <- function(id, ...) {
)
),
bslib::nav_panel(
title = "Model checks",
title = i18n$t("Model checks"),
bslib::layout_sidebar(
sidebar = bslib::sidebar(
bslib::accordion(
@ -8739,11 +8586,11 @@ ui_elements <- function(selection) {
shiny::tags$br(),
shiny::actionButton(
inputId = "data_reset",
label = "Restore original data",
label = i18n$t("Restore original data"),
width = "100%"
),
shiny::tags$br(),
shiny::helpText("Reset to original imported dataset. Careful! There is no un-doing."),
shiny::helpText(i18n$t("Reset to original imported dataset. Careful! There is no un-doing.")),
shiny::tags$br()
)
# )
@ -8762,7 +8609,7 @@ ui_elements <- function(selection) {
# bslib::navset_bar(
# title = "",
bslib::nav_panel(
title = "Characteristics",
title = i18n$t("Characteristics"),
icon = bsicons::bs_icon("table"),
bslib::layout_sidebar(
sidebar = bslib::sidebar(
@ -8777,12 +8624,12 @@ ui_elements <- function(selection) {
title = "Settings",
icon = bsicons::bs_icon("table"),
shiny::uiOutput("strat_var"),
shiny::helpText("Only factor/categorical variables are available for stratification. Go back to the 'Prepare' tab to reclass a variable if it's not on the list."),
shiny::helpText(i18n$t("Only factor/categorical variables are available for stratification. Go back to the 'Prepare' tab to reclass a variable if it's not on the list.")),
shiny::conditionalPanel(
condition = "input.strat_var!='none'",
shiny::radioButtons(
inputId = "add_p",
label = "Compare strata?",
label = i18n$t("Compare strata?"),
selected = "no",
inline = TRUE,
choices = list(
@ -8796,7 +8643,7 @@ ui_elements <- function(selection) {
shiny::br(),
shiny::actionButton(
inputId = "act_eval",
label = "Evaluate",
label = i18n$t("Evaluate"),
width = "100%",
icon = shiny::icon("calculator"),
disabled = TRUE
@ -8808,7 +8655,7 @@ ui_elements <- function(selection) {
)
),
bslib::nav_panel(
title = "Correlations",
title = i18n$t("Correlations"),
icon = bsicons::bs_icon("bounding-box"),
bslib::layout_sidebar(
sidebar = bslib::sidebar(
@ -8822,11 +8669,11 @@ ui_elements <- function(selection) {
title = "Settings",
icon = bsicons::bs_icon("bounding-box"),
shiny::uiOutput("outcome_var_cor"),
shiny::helpText("To avoid evaluating the correlation of the outcome variable, this can be excluded from the plot or select 'none'."),
shiny::helpText(i18n$t("To avoid evaluating the correlation of the outcome variable, this can be excluded from the plot or select 'none'.")),
shiny::br(),
shinyWidgets::noUiSliderInput(
inputId = "cor_cutoff",
label = "Correlation cut-off",
label = i18n$t("Correlation cut-off"),
min = 0,
max = 1,
step = .01,
@ -8834,7 +8681,7 @@ ui_elements <- function(selection) {
format = shinyWidgets::wNumbFormat(decimals = 2),
color = datamods:::get_primary_color()
),
shiny::helpText("Set the cut-off for considered 'highly correlated'.")
shiny::helpText(i18n$t("Set the cut-off for considered 'highly correlated'."))
)
)
),
@ -8842,7 +8689,7 @@ ui_elements <- function(selection) {
)
),
bslib::nav_panel(
title = "Missings",
title = i18n$t("Missings"),
icon = bsicons::bs_icon("x-circle"),
bslib::layout_sidebar(
sidebar = bslib::sidebar(
@ -8855,7 +8702,7 @@ ui_elements <- function(selection) {
title = "Settings",
icon = bsicons::bs_icon("x-circle"),
shiny::uiOutput("missings_var"),
shiny::helpText("To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not.")
shiny::helpText(i18n$t("To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not."))
)
)
),
@ -8943,7 +8790,8 @@ ui_elements <- function(selection) {
outputId = "report",
label = "Download report",
icon = shiny::icon("download")
)
),
shiny::br()
# shiny::helpText("If choosing to output to MS Word, please note, that when opening the document, two errors will pop-up. Choose to repair and choose not to update references. The issue is being worked on. You can always choose LibreOffice instead."),
),
shiny::column(
@ -10633,11 +10481,13 @@ make_validation_alerts <- function(data) {
#' Data correlations evaluation module
#'
#' @param id Module id
#' @param id id
#'
#' @name data-missings
#' @name visual-summary
#' @returns Shiny ui module
#' @export
#'
#' @example examples/visual_summary_demo.R
visual_summary_ui <- function(id) {
ns <- shiny::NS(id)
@ -10646,8 +10496,17 @@ visual_summary_ui <- function(id) {
)
}
#' Visual summary server
#'
#' @param data_r reactive data
#' @param ... passed on to the visual_summary() function
#'
#' @name visual-summary
#' @returns shiny server
#' @export
#'
visual_summary_server <- function(id,
data_r=shiny::reactive(NULL),
data_r = shiny::reactive(NULL),
...) {
shiny::moduleServer(
id = id,
@ -10676,45 +10535,26 @@ visual_summary_server <- function(id,
# missings_apex_plot(datar(), ...)
# })
output$visual_plot <- shiny::renderPlot(expr = {
visual_summary(data = rv$data,...)
visual_summary(data = rv$data, na.label = i18n$t("Missings"), legend.title = i18n$t("Class"), ylab = i18n$t("Observations"), ...)
})
}
)
}
visual_summary_demo_app <- function() {
ui <- shiny::fluidPage(
shiny::actionButton(
inputId = "modal_missings",
label = "Visual summary",
width = "100%",
disabled = FALSE
)
)
server <- function(input, output, session) {
data_demo <- mtcars
data_demo[sample(1:32, 10), "cyl"] <- NA
data_demo[sample(1:32, 8), "vs"] <- NA
visual_summary_server(id = "data", data = shiny::reactive(data_demo))
observeEvent(input$modal_missings, {
tryCatch(
{
modal_visual_summary(id = "data")
},
error = function(err) {
showNotification(paste0("We encountered the following error browsing your data: ", err), type = "err")
}
)
})
}
shiny::shinyApp(ui, server)
}
visual_summary_demo_app()
#' Visual summary modal
#'
#' @param title title
#' @param easyClose easyClose
#' @param size modal size
#' @param footer modal footer
#' @param ... ignored
#'
#' @name visual-summary
#'
#' @returns shiny modal
#' @export
#'
modal_visual_summary <- function(id,
title = "Visual overview of data classes and missing observations",
easyClose = TRUE,
@ -10733,9 +10573,10 @@ modal_visual_summary <- function(id,
## Slow with many observations...
#' Plot missings and class with apexcharter
#' Plot missings and class with apexcharter. Not in use with FreesearchR.
#'
#' @param data data frame
#' @name visual-summary
#'
#' @returns An [apexchart()] `htmlwidget` object.
#' @export
@ -10790,6 +10631,10 @@ missings_apex_plot <- function(data, animation = FALSE, ...) {
#'
#' @param data data
#' @param ... optional arguments passed to data_summary_gather()
#' @param legend.title Legend title
#' @param ylab Y axis label
#'
#' @name visual-summary
#'
#' @returns ggplot2 object
#' @export
@ -10800,11 +10645,15 @@ missings_apex_plot <- function(data, animation = FALSE, ...) {
#' data_demo[sample(1:32, 8), "vs"] <- NA
#' visual_summary(data_demo)
#' visual_summary(data_demo, palette.fun = scales::hue_pal())
#' visual_summary(dplyr::storms)
#' visual_summary(dplyr::storms, summary.fun = data_type)
visual_summary <- function(data, legend.title = "Data class", ...) {
#' visual_summary(dplyr::storms, summary.fun = data_type, na.label = "Missings", legend.title = "Class")
visual_summary <- function(data, legend.title = NULL, ylab = "Observations", ...) {
l <- data_summary_gather(data, ...)
if (is.null(legend.title)) {
legend.title <- l$summary.fun
}
df <- l$data
df$valueType <- factor(df$valueType, levels = names(l$colors))
@ -10818,13 +10667,13 @@ visual_summary <- function(data, legend.title = "Data class", ...) {
vjust = 1, hjust = 1
)) +
ggplot2::scale_fill_manual(values = l$colors) +
ggplot2::labs(x = "", y = "Observations") +
ggplot2::labs(x = "", y = ylab) +
ggplot2::scale_y_reverse() +
ggplot2::theme(axis.text.x = ggplot2::element_text(hjust = 0.5)) +
ggplot2::guides(colour = "none") +
ggplot2::guides(fill = ggplot2::guide_legend(title = legend.title)) +
# change the limits etc.
ggplot2::guides(fill = ggplot2::guide_legend(title = "Type")) +
# ggplot2::guides(fill = ggplot2::guide_legend(title = guide.lab)) +
# add info about the axes
ggplot2::scale_x_discrete(position = "top") +
ggplot2::theme(axis.text.x = ggplot2::element_text(hjust = 0)) +
@ -10839,16 +10688,18 @@ visual_summary <- function(data, legend.title = "Data class", ...) {
#' Data summary for printing visual summary
#'
#' @param data data.frame
#' @param fun summary function. Default is "class"
#' @param palette.fun optionally use specific palette functions. First argument
#' has to be the length.
#' @param summary.fun fun for summarising
#' @param na.label label for NA
#' @param ... overflow
#'
#' @returns data.frame
#' @export
#'
#' @examples
#' mtcars |> data_summary_gather()
data_summary_gather <- function(data, summary.fun = class, palette.fun = viridisLite::viridis) {
data_summary_gather <- function(data, summary.fun = class, palette.fun = viridisLite::viridis, na.label = "NA", ...) {
df_plot <- setNames(data, unique_short(names(data))) |>
purrr::map_df(\(x){
ifelse(is.na(x),
@ -10870,12 +10721,12 @@ data_summary_gather <- function(data, summary.fun = class, palette.fun = viridis
forcats::as_factor() |>
as.numeric()
df_plot$valueType[is.na(df_plot$valueType)] <- "NA"
df_plot$valueType[is.na(df_plot$valueType)] <- na.label
df_plot$valueType_num[is.na(df_plot$valueType_num)] <- max(df_plot$valueType_num, na.rm = TRUE) + 1
labels <- setNames(unique(df_plot$valueType_num), unique(df_plot$valueType)) |> sort()
if (any(df_plot$valueType == "NA")) {
if (any(df_plot$valueType == na.label)) {
colors <- setNames(c(palette.fun(length(labels) - 1), "#999999"), names(labels))
} else {
colors <- setNames(palette.fun(length(labels)), names(labels))
@ -10893,7 +10744,7 @@ data_summary_gather <- function(data, summary.fun = class, palette.fun = viridis
}) |>
setNames(NULL)
list(data = df_plot, colors = colors, labels = label_list)
list(data = df_plot, colors = colors, labels = label_list, summary.fun = deparse(substitute(summary.fun)))
}
@ -11442,7 +11293,7 @@ server <- function(input, output, session) {
modal_visual_summary(
id = "initial_summary",
footer = NULL,
size = "xl"
size = "xl",title = i18n$t("Data classes and missing observations")
)
},
error = function(err) {
@ -11575,8 +11426,10 @@ server <- function(input, output, session) {
shinyWidgets::ask_confirmation(
cancelOnDismiss = TRUE,
inputId = "reset_confirm",
title = "Please confirm data reset?",
type = "warning"
title = i18n$t("Please confirm data reset!"),
type = "warning",
text = i18n$t("Sure you want to reset data? This cannot be undone."),
btn_labels = c(i18n$t("Cancel"), i18n$t("Confirm"))
)
})
@ -11590,14 +11443,14 @@ server <- function(input, output, session) {
output$data_info <- shiny::renderUI({
shiny::req(data_filter())
data_description(data_filter(), "The filtered data")
data_description(data_filter(), data_text = i18n$t("The filtered data"))
})
######### Create factor
shiny::observeEvent(
input$modal_cut,
modal_cut_variable("modal_cut", title = "Create new factor")
modal_cut_variable("modal_cut", title = i18n$t("Create new factor"))
)
data_modal_cut <- cut_variable_server(
@ -11614,7 +11467,7 @@ server <- function(input, output, session) {
shiny::observeEvent(
input$modal_update,
datamods::modal_update_factor(id = "modal_update", title = "Reorder factor levels")
datamods::modal_update_factor(id = "modal_update", title = i18n$t("Reorder factor levels"))
)
data_modal_update <- datamods::update_factor_server(
@ -11634,8 +11487,8 @@ server <- function(input, output, session) {
input$modal_column,
modal_create_column(
id = "modal_column",
footer = shiny::markdown("This window is aimed at advanced users and require some *R*-experience!"),
title = "Create new variables"
footer = shiny::markdown(i18n$t("This window is aimed at advanced users and require some *R*-experience!")),
title = i18n$t("Create new variables")
)
)
data_modal_r <- create_column_server(
@ -11673,7 +11526,7 @@ server <- function(input, output, session) {
# c("dichotomous", "ordinal", "categorical", "datatime", "continuous")
shinyWidgets::virtualSelectInput(
inputId = "column_filter",
label = "Select data types to include",
label = i18n$t("Select data types to include"),
selected = unique(data_type(rv$data)),
choices = unique(data_type(rv$data)),
updateOn = "change",
@ -11878,7 +11731,7 @@ server <- function(input, output, session) {
observeEvent(input$modal_browse, {
tryCatch(
{
show_data(REDCapCAST::fct_drop(rv$data_filtered), title = "Uploaded data overview", type = "modal")
show_data(REDCapCAST::fct_drop(rv$data_filtered), title = i18n$t("Uploaded data overview"), type = "modal")
},
error = function(err) {
showNotification(paste0("We encountered the following error browsing your data: ", err), type = "err")
@ -11900,7 +11753,7 @@ server <- function(input, output, session) {
{
modal_visual_summary(
id = "visual_overview",
footer = "Here is an overview of how your data is interpreted, and where data is missing. Use this information to consider if data is missing at random or if some observations are missing systematically wich may be caused by an observation bias.",
footer = i18n$t("Here is an overview of how your data is interpreted, and where data is missing. Use this information to consider if data is missing at random or if some observations are missing systematically wich may be caused by an observation bias."),
size = "xl"
)
},
@ -11952,12 +11805,12 @@ server <- function(input, output, session) {
output$code_import <- shiny::renderUI({
shiny::req(rv$code$import)
prismCodeBlock(paste0("#Data import\n", rv$code$import))
prismCodeBlock(paste0(i18n$t("#Data import\n"), rv$code$import))
})
output$code_format <- shiny::renderUI({
shiny::req(rv$code$format)
prismCodeBlock(paste0("#Data import formatting\n", rv$code$format))
prismCodeBlock(paste0(i18n$t("#Data import formatting\n"), rv$code$format))
})
output$code_data <- shiny::renderUI({

View file

@ -129,34 +129,93 @@
"Drawing the plot. Hold tight for a moment..","Tegner grafikken. Spænd selen.."
"#Plotting\n","#Tegner\n"
"Stacked horizontal bars","Stablede horisontale søjler"
"A classical way of visualising the distribution of an ordinal scale like the modified Ranking Scale and known as Grotta bars","A classical way of visualising the distribution of an ordinal scale like the modified Ranking Scale and known as Grotta bars"
"Violin plot","Violin plot"
"A modern alternative to the classic boxplot to visualise data distribution","A modern alternative to the classic boxplot to visualise data distribution"
"Sankey plot","Sankey plot"
"A way of visualising change between groups","A way of visualising change between groups"
"Scatter plot","Scatter plot"
"A classic way of showing the association between to variables","A classic way of showing the association between to variables"
"Box plot","Box plot"
"A classic way to plot data distribution by groups","A classic way to plot data distribution by groups"
"A classical way of visualising the distribution of an ordinal scale like the modified Ranking Scale and known as Grotta bars","En klassisk visualisering af fordelingen af observationer på en ordinal kategorisk skala. Typisk brugt til modified Rankin Scale og kendes også som 'Grotta bars'"
"Violin plot","Violin-diagram"
"A modern alternative to the classic boxplot to visualise data distribution","Moderne alternativ til den klassiske box-plot og velegnet til at visualisere fordelingen af observationer"
"Sankey plot","Sankey-diagram"
"A way of visualising change between groups","Visualiserer ændring mellem grupper for samme type observationer"
"Scatter plot","Punkt-diagram"
"A classic way of showing the association between to variables","Visualiserer forholdet mellem to variabler"
"Box plot","Kasse-diagram"
"A classic way to plot data distribution by groups","Klassik måde at visualisere fordeling"
"Euler diagram","Eulerdiagram"
"Generate area-proportional Euler diagrams to display set relationships","Generate area-proportional Euler diagrams to display set relationships"
"Generate area-proportional Euler diagrams to display set relationships","Generer proportionelt Euler-diagram for at vise forhold mellem forskellige kategoriske observationer"
"Documentation","Dokumentation"
"Data is only stored for analyses and deleted when the app is closed.","Data is only stored for analyses and deleted when the app is closed."
"Consider [running ***FreesearchR*** locally](https://agdamsbo.github.io/FreesearchR/#run-locally-on-your-own-machine) if working with sensitive data.","Consider [running ***FreesearchR*** locally](https://agdamsbo.github.io/FreesearchR/#run-locally-on-your-own-machine) if working with sensitive data."
"Data is only stored for analyses and deleted when the app is closed.","Data opbevares alene til brug i analyser og slettes så snart appen lukkes."
"Consider [running ***FreesearchR*** locally](https://agdamsbo.github.io/FreesearchR/#run-locally-on-your-own-machine) if working with sensitive data.","Overvej at [køre ***FreesearchR*** lokalt](https://agdamsbo.github.io/FreesearchR/#run-locally-on-your-own-machine) hvis du arbejder med personfølsomme data."
"Feedback","Feedback"
"License: AGPLv3","Licens: AGPLv3"
"Source","Kilde"
"Data includes {n_pairs} pairs of highly correlated variables.","Der er {n_pairs} variabel-par, der er stærkt internt korrelerede."
"Create plot","Dan grafik"
"Coefficients plot","Koefficientgraf"
"Checks","Checks"
"Below you find a summary table for quick insigths, and on the right you can visualise data classes, browse observations and apply different data filters.","Below you find a summary table for quick insigths, and on the right you can visualise data classes, browse observations and apply different data filters."
"Checks","Test af model"
"Below you find a summary table for quick insigths, and on the right you can visualise data classes, browse observations and apply different data filters.","Nedenfor er en opsummerende tabel, der giver hurtigt overblik. Til højre kan du få et visuelt overblik, gennemgå observationer og oprette datafiltre."
"Browse observations","Gennemse observationer"
"Settings","Indstillinger"
"The following error occured on determining correlations:","The following error occured on determining correlations:"
"We encountered the following error creating your report:","We encountered the following error creating your report:"
"The following error occured on determining correlations:","Følgende fejl opstod i forbindelse med korrelationsanalysen:"
"We encountered the following error creating your report:","Følgende fejl opstod, da rapporten blev dannet:"
"No variable chosen for analysis","Ingen variabel er valgt til analysen"
"No missing observations","Ingen manglende observationer"
"Missing vs non-missing observations in the variable **'{variabler()}'**","Manglende vs ikke-manglende observationer i variablen **'{variabler()}'**"
"There is a significant correlation between {n_nonmcar} variables and missing observations in the outcome variable {outcome}.","There is a significant correlation between {n_nonmcar} variables and missing observations in the outcome variable {outcome}."
"There is a significant correlation between {n_nonmcar} variables and missing observations in the outcome variable {outcome}.","Der er en betydelig korrelation blandt {n_nonmcar} variabler sammenlignet efter manglende observationer i {outcome}."
"There is a total of {p_miss} % missing observations.","Der er i alt {p_miss} % manglende observationer."
"Median:","Median:"
"Restore original data","Gendan originale data"
"Reset to original imported dataset. Careful! There is no un-doing.","Gendan det oprindeligt importerede datasæt. Forsigtig! Alle dine ændringer vil forsvinde."
"Characteristics","Karakteristika"
"Only factor/categorical variables are available for stratification. Go back to the 'Prepare' tab to reclass a variable if it's not on the list.","Alene kategoriske variabler kan danne grundlag for stratificering. Mangler du en variabel, så gå til ""Forbered"" og omklassificer til kategorisk."
"Compare strata?","Sammenlign strata?"
"Correlations","Korrelationer"
"To avoid evaluating the correlation of the outcome variable, this can be excluded from the plot or select 'none'.","For at udelukke svarvariablen fra korrelationsanalysen, så kan du vælge din svarvariabel eller vælge 'non', hvis du ikke vil angive en."
"Correlation cut-off","Korrelationsgrænse"
"Set the cut-off for considered 'highly correlated'.","Angiv grænsen for. hvad, der tolkes som 'betydelig korrelation'."
"Missings","Manglende observationer"
"To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not.","To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not."
"Class","Klasse"
"Observations","Observationer"
"Data classes and missing observations","Dataklasser og manglende observationer"
"Sure you want to reset data? This cannot be undone.","Er du sikker på at du vil gendanne data? Det kan ikke fortrydes."
"Cancel","Afbryd"
"Confirm","Bekræft"
"The filtered data","Filtreret data"
"Create new factor","Ny kategorisk variabel"
"This window is aimed at advanced users and require some *R*-experience!","This window is aimed at advanced users and require some *R*-experience!"
"Create new variables","Opret ny variabel"
"Select data types to include","Vælg datatyper, der skal inkluderes"
"Uploaded data overview","Overblik over uploaded data"
"Here is an overview of how your data is interpreted, and where data is missing. Use this information to consider if data is missing at random or if some observations are missing systematically wich may be caused by an observation bias.","Here is an overview of how your data is interpreted, and where data is missing. Use this information to consider if data is missing at random or if some observations are missing systematically wich may be caused by an observation bias."
"#Data import\n","#Data import\n"
"#Data import formatting\n","#Formatering ved data-import\n"
"Specify covariables","Angiv kovariabler"
"If none are selected, all are included.","Hvis ingen er valgt inkluderes alle."
"Analyse","Analysér"
"Working...","Arbejder..."
"Press 'Analyse' to create the regression model and after changing parameters.","Tryk 'Analysér' for at danne regressionsmodel og for at opdatere hvis parametre ændres."
"Show p-value","Vis p-værdi"
"Model checks","Model-test"
"Please confirm data reset!","Bekræft gendannelse af data!"
"Import data from REDCap","Importér data fra REDCap"
"REDCap server","REDCap-server"
"Web address","Web address"
"Format should be either 'https://redcap.your.institution/' or 'https://your.institution/redcap/'","Adressen skal være som 'https://redcap.your.institution/' eller 'https://your.institution/redcap/'"
"API token","API token"
"The token is a string of 32 numbers and letters.","En API-nøgle består af ialt 32 tal og bogstaver."
"Connect","Forbind"
"Data import parameters","Data import parameters"
"Select fields/variables to import and click the funnel to apply optional filters","Select fields/variables to import and click the funnel to apply optional filters"
"Import","Import"
"Click to see data dictionary","Click to see data dictionary"
"Connected to server!","Connected to server!"
"The {data_rv$info$project_title} project is loaded.","The {data_rv$info$project_title} project is loaded."
"Data dictionary","Data dictionary"
"Preview:","Preview:"
"Imported data set","Imported data set"
"Select fields/variables to import:","Select fields/variables to import:"
"Specify the data format","Specify the data format"
"Fill missing values?","Fill missing values?"
"Requested data was retrieved!","Requested data was retrieved!"
"Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.","Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access."
"Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.","Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access."
"Click to see the imported data","Click to see the imported data"
"Regression table","Regression table"

1 en da
129 Drawing the plot. Hold tight for a moment.. Tegner grafikken. Spænd selen..
130 #Plotting\n #Tegner\n
131 Stacked horizontal bars Stablede horisontale søjler
132 A classical way of visualising the distribution of an ordinal scale like the modified Ranking Scale and known as Grotta bars A classical way of visualising the distribution of an ordinal scale like the modified Ranking Scale and known as Grotta bars En klassisk visualisering af fordelingen af observationer på en ordinal kategorisk skala. Typisk brugt til modified Rankin Scale og kendes også som 'Grotta bars'
133 Violin plot Violin plot Violin-diagram
134 A modern alternative to the classic boxplot to visualise data distribution A modern alternative to the classic boxplot to visualise data distribution Moderne alternativ til den klassiske box-plot og velegnet til at visualisere fordelingen af observationer
135 Sankey plot Sankey plot Sankey-diagram
136 A way of visualising change between groups A way of visualising change between groups Visualiserer ændring mellem grupper for samme type observationer
137 Scatter plot Scatter plot Punkt-diagram
138 A classic way of showing the association between to variables A classic way of showing the association between to variables Visualiserer forholdet mellem to variabler
139 Box plot Box plot Kasse-diagram
140 A classic way to plot data distribution by groups A classic way to plot data distribution by groups Klassik måde at visualisere fordeling
141 Euler diagram Eulerdiagram
142 Generate area-proportional Euler diagrams to display set relationships Generate area-proportional Euler diagrams to display set relationships Generer proportionelt Euler-diagram for at vise forhold mellem forskellige kategoriske observationer
143 Documentation Dokumentation
144 Data is only stored for analyses and deleted when the app is closed. Data is only stored for analyses and deleted when the app is closed. Data opbevares alene til brug i analyser og slettes så snart appen lukkes.
145 Consider [running ***FreesearchR*** locally](https://agdamsbo.github.io/FreesearchR/#run-locally-on-your-own-machine) if working with sensitive data. Consider [running ***FreesearchR*** locally](https://agdamsbo.github.io/FreesearchR/#run-locally-on-your-own-machine) if working with sensitive data. Overvej at [køre ***FreesearchR*** lokalt](https://agdamsbo.github.io/FreesearchR/#run-locally-on-your-own-machine) hvis du arbejder med personfølsomme data.
146 Feedback Feedback
147 License: AGPLv3 Licens: AGPLv3
148 Source Kilde
149 Data includes {n_pairs} pairs of highly correlated variables. Der er {n_pairs} variabel-par, der er stærkt internt korrelerede.
150 Create plot Dan grafik
151 Coefficients plot Koefficientgraf
152 Checks Checks Test af model
153 Below you find a summary table for quick insigths, and on the right you can visualise data classes, browse observations and apply different data filters. Below you find a summary table for quick insigths, and on the right you can visualise data classes, browse observations and apply different data filters. Nedenfor er en opsummerende tabel, der giver hurtigt overblik. Til højre kan du få et visuelt overblik, gennemgå observationer og oprette datafiltre.
154 Browse observations Gennemse observationer
155 Settings Indstillinger
156 The following error occured on determining correlations: The following error occured on determining correlations: Følgende fejl opstod i forbindelse med korrelationsanalysen:
157 We encountered the following error creating your report: We encountered the following error creating your report: Følgende fejl opstod, da rapporten blev dannet:
158 No variable chosen for analysis Ingen variabel er valgt til analysen
159 No missing observations Ingen manglende observationer
160 Missing vs non-missing observations in the variable **'{variabler()}'** Manglende vs ikke-manglende observationer i variablen **'{variabler()}'**
161 There is a significant correlation between {n_nonmcar} variables and missing observations in the outcome variable {outcome}. There is a significant correlation between {n_nonmcar} variables and missing observations in the outcome variable {outcome}. Der er en betydelig korrelation blandt {n_nonmcar} variabler sammenlignet efter manglende observationer i {outcome}.
162 There is a total of {p_miss} % missing observations. Der er i alt {p_miss} % manglende observationer.
163 Median: Median:
164 Restore original data Gendan originale data
165 Reset to original imported dataset. Careful! There is no un-doing. Gendan det oprindeligt importerede datasæt. Forsigtig! Alle dine ændringer vil forsvinde.
166 Characteristics Karakteristika
167 Only factor/categorical variables are available for stratification. Go back to the 'Prepare' tab to reclass a variable if it's not on the list. Alene kategoriske variabler kan danne grundlag for stratificering. Mangler du en variabel, så gå til "Forbered" og omklassificer til kategorisk.
168 Compare strata? Sammenlign strata?
169 Correlations Korrelationer
170 To avoid evaluating the correlation of the outcome variable, this can be excluded from the plot or select 'none'. For at udelukke svarvariablen fra korrelationsanalysen, så kan du vælge din svarvariabel eller vælge 'non', hvis du ikke vil angive en.
171 Correlation cut-off Korrelationsgrænse
172 Set the cut-off for considered 'highly correlated'. Angiv grænsen for. hvad, der tolkes som 'betydelig korrelation'.
173 Missings Manglende observationer
174 To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not. To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not.
175 Class Klasse
176 Observations Observationer
177 Data classes and missing observations Dataklasser og manglende observationer
178 Sure you want to reset data? This cannot be undone. Er du sikker på at du vil gendanne data? Det kan ikke fortrydes.
179 Cancel Afbryd
180 Confirm Bekræft
181 The filtered data Filtreret data
182 Create new factor Ny kategorisk variabel
183 This window is aimed at advanced users and require some *R*-experience! This window is aimed at advanced users and require some *R*-experience!
184 Create new variables Opret ny variabel
185 Select data types to include Vælg datatyper, der skal inkluderes
186 Uploaded data overview Overblik over uploaded data
187 Here is an overview of how your data is interpreted, and where data is missing. Use this information to consider if data is missing at random or if some observations are missing systematically wich may be caused by an observation bias. Here is an overview of how your data is interpreted, and where data is missing. Use this information to consider if data is missing at random or if some observations are missing systematically wich may be caused by an observation bias.
188 #Data import\n #Data import\n
189 #Data import formatting\n #Formatering ved data-import\n
190 Specify covariables Angiv kovariabler
191 If none are selected, all are included. Hvis ingen er valgt inkluderes alle.
192 Analyse Analysér
193 Working... Arbejder...
194 Press 'Analyse' to create the regression model and after changing parameters. Tryk 'Analysér' for at danne regressionsmodel og for at opdatere hvis parametre ændres.
195 Show p-value Vis p-værdi
196 Model checks Model-test
197 Please confirm data reset! Bekræft gendannelse af data!
198 Import data from REDCap Importér data fra REDCap
199 REDCap server REDCap-server
200 Web address Web address
201 Format should be either 'https://redcap.your.institution/' or 'https://your.institution/redcap/' Adressen skal være som 'https://redcap.your.institution/' eller 'https://your.institution/redcap/'
202 API token API token
203 The token is a string of 32 numbers and letters. En API-nøgle består af ialt 32 tal og bogstaver.
204 Connect Forbind
205 Data import parameters Data import parameters
206 Select fields/variables to import and click the funnel to apply optional filters Select fields/variables to import and click the funnel to apply optional filters
207 Import Import
208 Click to see data dictionary Click to see data dictionary
209 Connected to server! Connected to server!
210 The {data_rv$info$project_title} project is loaded. The {data_rv$info$project_title} project is loaded.
211 Data dictionary Data dictionary
212 Preview: Preview:
213 Imported data set Imported data set
214 Select fields/variables to import: Select fields/variables to import:
215 Specify the data format Specify the data format
216 Fill missing values? Fill missing values?
217 Requested data was retrieved! Requested data was retrieved!
218 Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access. Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.
219 Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access. Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.
220 Click to see the imported data Click to see the imported data
221 Regression table Regression table

View file

@ -160,3 +160,62 @@
"Missing vs non-missing observations in the variable **'{variabler()}'**","Missing vs non-missing observations in the variable **'{variabler()}'**"
"There is a significant correlation between {n_nonmcar} variables and missing observations in the outcome variable {outcome}.","There is a significant correlation between {n_nonmcar} variables and missing observations in the outcome variable {outcome}."
"There is a total of {p_miss} % missing observations.","There is a total of {p_miss} % missing observations."
"Median:","Median:"
"Restore original data","Restore original data"
"Reset to original imported dataset. Careful! There is no un-doing.","Reset to original imported dataset. Careful! There is no un-doing."
"Characteristics","Characteristics"
"Only factor/categorical variables are available for stratification. Go back to the 'Prepare' tab to reclass a variable if it's not on the list.","Only factor/categorical variables are available for stratification. Go back to the 'Prepare' tab to reclass a variable if it's not on the list."
"Compare strata?","Compare strata?"
"Correlations","Correlations"
"To avoid evaluating the correlation of the outcome variable, this can be excluded from the plot or select 'none'.","To avoid evaluating the correlation of the outcome variable, this can be excluded from the plot or select 'none'."
"Correlation cut-off","Correlation cut-off"
"Set the cut-off for considered 'highly correlated'.","Set the cut-off for considered 'highly correlated'."
"Missings","Missings"
"To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not.","To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not."
"Class","Class"
"Observations","Observations"
"Data classes and missing observations","Data classes and missing observations"
"Sure you want to reset data? This cannot be undone.","Sure you want to reset data? This cannot be undone."
"Cancel","Cancel"
"Confirm","Confirm"
"The filtered data","The filtered data"
"Create new factor","Create new factor"
"This window is aimed at advanced users and require some *R*-experience!","This window is aimed at advanced users and require some *R*-experience!"
"Create new variables","Create new variables"
"Select data types to include","Select data types to include"
"Uploaded data overview","Uploaded data overview"
"Here is an overview of how your data is interpreted, and where data is missing. Use this information to consider if data is missing at random or if some observations are missing systematically wich may be caused by an observation bias.","Here is an overview of how your data is interpreted, and where data is missing. Use this information to consider if data is missing at random or if some observations are missing systematically wich may be caused by an observation bias."
"#Data import\n","#Data import\n"
"#Data import formatting\n","#Data import formatting\n"
"Specify covariables","Specify covariables"
"If none are selected, all are included.","If none are selected, all are included."
"Analyse","Analyse"
"Working...","Working..."
"Press 'Analyse' to create the regression model and after changing parameters.","Press 'Analyse' to create the regression model and after changing parameters."
"Show p-value","Show p-value"
"Model checks","Model checks"
"Please confirm data reset!","Please confirm data reset!"
"Import data from REDCap","Import data from REDCap"
"REDCap server","REDCap server"
"Web address","Web address"
"Format should be either 'https://redcap.your.institution/' or 'https://your.institution/redcap/'","Format should be either 'https://redcap.your.institution/' or 'https://your.institution/redcap/'"
"API token","API token"
"The token is a string of 32 numbers and letters.","The token is a string of 32 numbers and letters."
"Connect","Connect"
"Data import parameters","Data import parameters"
"Select fields/variables to import and click the funnel to apply optional filters","Select fields/variables to import and click the funnel to apply optional filters"
"Import","Import"
"Click to see data dictionary","Click to see data dictionary"
"Connected to server!","Connected to server!"
"The {data_rv$info$project_title} project is loaded.","The {data_rv$info$project_title} project is loaded."
"Data dictionary","Data dictionary"
"Preview:","Preview:"
"Imported data set","Imported data set"
"Select fields/variables to import:","Select fields/variables to import:"
"Specify the data format","Specify the data format"
"Fill missing values?","Fill missing values?"
"Requested data was retrieved!","Requested data was retrieved!"
"Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.","Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access."
"Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.","Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access."
"Click to see the imported data","Click to see the imported data"
"Regression table","Regression table"

1 en sw
160 Missing vs non-missing observations in the variable **'{variabler()}'** Missing vs non-missing observations in the variable **'{variabler()}'**
161 There is a significant correlation between {n_nonmcar} variables and missing observations in the outcome variable {outcome}. There is a significant correlation between {n_nonmcar} variables and missing observations in the outcome variable {outcome}.
162 There is a total of {p_miss} % missing observations. There is a total of {p_miss} % missing observations.
163 Median: Median:
164 Restore original data Restore original data
165 Reset to original imported dataset. Careful! There is no un-doing. Reset to original imported dataset. Careful! There is no un-doing.
166 Characteristics Characteristics
167 Only factor/categorical variables are available for stratification. Go back to the 'Prepare' tab to reclass a variable if it's not on the list. Only factor/categorical variables are available for stratification. Go back to the 'Prepare' tab to reclass a variable if it's not on the list.
168 Compare strata? Compare strata?
169 Correlations Correlations
170 To avoid evaluating the correlation of the outcome variable, this can be excluded from the plot or select 'none'. To avoid evaluating the correlation of the outcome variable, this can be excluded from the plot or select 'none'.
171 Correlation cut-off Correlation cut-off
172 Set the cut-off for considered 'highly correlated'. Set the cut-off for considered 'highly correlated'.
173 Missings Missings
174 To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not. To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not.
175 Class Class
176 Observations Observations
177 Data classes and missing observations Data classes and missing observations
178 Sure you want to reset data? This cannot be undone. Sure you want to reset data? This cannot be undone.
179 Cancel Cancel
180 Confirm Confirm
181 The filtered data The filtered data
182 Create new factor Create new factor
183 This window is aimed at advanced users and require some *R*-experience! This window is aimed at advanced users and require some *R*-experience!
184 Create new variables Create new variables
185 Select data types to include Select data types to include
186 Uploaded data overview Uploaded data overview
187 Here is an overview of how your data is interpreted, and where data is missing. Use this information to consider if data is missing at random or if some observations are missing systematically wich may be caused by an observation bias. Here is an overview of how your data is interpreted, and where data is missing. Use this information to consider if data is missing at random or if some observations are missing systematically wich may be caused by an observation bias.
188 #Data import\n #Data import\n
189 #Data import formatting\n #Data import formatting\n
190 Specify covariables Specify covariables
191 If none are selected, all are included. If none are selected, all are included.
192 Analyse Analyse
193 Working... Working...
194 Press 'Analyse' to create the regression model and after changing parameters. Press 'Analyse' to create the regression model and after changing parameters.
195 Show p-value Show p-value
196 Model checks Model checks
197 Please confirm data reset! Please confirm data reset!
198 Import data from REDCap Import data from REDCap
199 REDCap server REDCap server
200 Web address Web address
201 Format should be either 'https://redcap.your.institution/' or 'https://your.institution/redcap/' Format should be either 'https://redcap.your.institution/' or 'https://your.institution/redcap/'
202 API token API token
203 The token is a string of 32 numbers and letters. The token is a string of 32 numbers and letters.
204 Connect Connect
205 Data import parameters Data import parameters
206 Select fields/variables to import and click the funnel to apply optional filters Select fields/variables to import and click the funnel to apply optional filters
207 Import Import
208 Click to see data dictionary Click to see data dictionary
209 Connected to server! Connected to server!
210 The {data_rv$info$project_title} project is loaded. The {data_rv$info$project_title} project is loaded.
211 Data dictionary Data dictionary
212 Preview: Preview:
213 Imported data set Imported data set
214 Select fields/variables to import: Select fields/variables to import:
215 Specify the data format Specify the data format
216 Fill missing values? Fill missing values?
217 Requested data was retrieved! Requested data was retrieved!
218 Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access. Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.
219 Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access. Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.
220 Click to see the imported data Click to see the imported data
221 Regression table Regression table

View file

@ -0,0 +1,32 @@
visual_summary_demo_app <- function() {
ui <- shiny::fluidPage(
shiny::actionButton(
inputId = "modal_missings",
label = "Visual summary",
width = "100%",
disabled = FALSE
)
)
server <- function(input, output, session) {
data_demo <- mtcars
data_demo[sample(1:32, 10), "cyl"] <- NA
data_demo[sample(1:32, 8), "vs"] <- NA
data_demo$gear <- factor(data_demo$gear)
visual_summary_server(id = "data", data = shiny::reactive(data_demo),summary.fun=class)
observeEvent(input$modal_missings, {
tryCatch(
{
modal_visual_summary(id = "data")
},
error = function(err) {
showNotification(paste0("We encountered the following error browsing your data: ", err), type = "err")
}
)
})
}
shiny::shinyApp(ui, server)
}
visual_summary_demo_app()

View file

@ -1,7 +1,7 @@
########
#### Current file: /var/folders/9l/xbc19wxx0g79jdd2sf_0v291mhwh7f/T//RtmpCENEZ9/file6e5430b6d378.R
#### Current file: /var/folders/9l/xbc19wxx0g79jdd2sf_0v291mhwh7f/T//Rtmpo2rU34/file15cb31846160a.R
########
i18n_path <- system.file("translations", package = "FreesearchR")
@ -2205,11 +2205,11 @@ supported_plots <- function() {
fun = "plot_euler",
descr = i18n$t("Euler diagram"),
note = i18n$t("Generate area-proportional Euler diagrams to display set relationships"),
primary.type = c("dichotomous", "categorical"),
secondary.type = c("dichotomous", "categorical"),
primary.type = c("dichotomous"),
secondary.type = c("dichotomous"),
secondary.multi = TRUE,
secondary.max = 4,
tertiary.type = c("dichotomous", "categorical"),
tertiary.type = c("dichotomous"),
secondary.extra = NULL
)
)
@ -2523,163 +2523,6 @@ clean_common_axis <- function(p, axis) {
}
########
#### Current file: /Users/au301842/FreesearchR/R//data-import.R
########
data_import_ui <- function(id) {
ns <- shiny::NS(id)
shiny::fluidRow(
shiny::column(width = 2),
shiny::column(
width = 8,
shiny::h4("Choose your data source"),
shiny::br(),
shinyWidgets::radioGroupButtons(
inputId = "source",
selected = "env",
choices = c(
"File upload" = "file",
"REDCap server export" = "redcap",
"Local or sample data" = "env"
),
width = "100%"
),
shiny::helpText("Upload a file from your device, get data directly from REDCap or select a sample data set for testing from the app."),
shiny::br(),
shiny::br(),
shiny::conditionalPanel(
condition = "input.source=='file'",
import_file_ui(
id = ns("file_import"),
layout_params = "dropdown",
title = "Choose a datafile to upload",
file_extensions = c(".csv", ".tsv", ".txt", ".xls", ".xlsx", ".rds", ".sas7bdat", ".ods", ".dta")
)
),
shiny::conditionalPanel(
condition = "input.source=='redcap'",
m_redcap_readUI(id = ns("redcap_import"))
),
shiny::conditionalPanel(
condition = "input.source=='env'",
datamods::import_globalenv_ui(id = ns("env"), title = NULL)
),
shiny::conditionalPanel(
condition = "input.source=='redcap'",
DT::DTOutput(outputId = ns("redcap_prev"))
)
)
)
}
data_import_server <- function(id) {
module <- function(input, output, session) {
ns <- session$ns
rv <- shiny::reactiveValues(
data_temp = NULL,
code = list()
)
data_file <- import_file_server(
id = ns("file_import"),
show_data_in = "popup",
trigger_return = "change",
return_class = "data.frame"
)
shiny::observeEvent(data_file$data(), {
shiny::req(data_file$data())
rv$data_temp <- data_file$data()
rv$code <- append_list(data = data_file$code(), list = rv$code, index = "import")
})
data_redcap <- m_redcap_readServer(
id = "redcap_import"
)
shiny::observeEvent(data_redcap(), {
# rv$data_original <- purrr::pluck(data_redcap(), "data")()
rv$data_temp <- data_redcap()
})
from_env <- datamods::import_globalenv_server(
id = "env",
trigger_return = "change",
btn_show_data = FALSE,
reset = reactive(input$hidden)
)
shiny::observeEvent(from_env$data(), {
shiny::req(from_env$data())
rv$data_temp <- from_env$data()
# rv$code <- append_list(data = from_env$code(),list = rv$code,index = "import")
})
return(list(
# status = reactive(temporary_rv$status),
# name = reactive(temporary_rv$name),
# code = reactive(temporary_rv$code),
data = shiny::reactive(rv$data_temp)
))
}
shiny::moduleServer(
id = id,
module = module
)
}
#' Test app for the data-import module
#'
#' @rdname data-import
#'
#' @examples
#' \dontrun{
#' data_import_demo_app()
#' }
data_import_demo_app <- function() {
ui <- shiny::fluidPage(
data_import_ui("data_import"),
toastui::datagridOutput2(outputId = "table"),
DT::DTOutput("data_summary")
)
server <- function(input, output, session) {
imported <- shiny::reactive(data_import_server(id = "data_import"))
# output$data_summary <- DT::renderDataTable(
# {
# shiny::req(data_val$data)
# data_val$data
# },
# options = list(
# scrollX = TRUE,
# pageLength = 5
# )
# )
output$table <- toastui::renderDatagrid2({
req(imported$data)
toastui::datagrid(
data = head(imported$data, 5),
theme = "striped",
colwidths = "guess",
minBodyHeight = 250
)
})
}
shiny::shinyApp(ui, server)
}
########
#### Current file: /Users/au301842/FreesearchR/R//data-summary.R
########
@ -3290,6 +3133,9 @@ describe_col_num <- function(x, with_summary = TRUE) {
tags$div(
i18n$t("Mean:"), round(mean(x, na.rm = TRUE), 2)
),
tags$div(
i18n$t("Median:"), round(median(x, na.rm = TRUE), 2)
),
tags$div(
i18n$t("Max:"), round(max(x, na.rm = TRUE), 2)
),
@ -4107,7 +3953,7 @@ simple_snake <- function(data){
#### Current file: /Users/au301842/FreesearchR/R//hosted_version.R
########
hosted_version <- function()'v25.9.2-250924'
hosted_version <- function()'v25.9.2-250925'
########
@ -5703,20 +5549,20 @@ m_redcap_readUI <- function(id, title = TRUE, url = NULL) {
if (isTRUE(title)) {
title <- shiny::tags$h4(
"Import data from REDCap",
i18n$t("Import data from REDCap"),
class = "redcap-module-title"
)
}
server_ui <- shiny::tagList(
shiny::tags$h4("REDCap server"),
shiny::tags$h4(i18n$t("REDCap server")),
shiny::textInput(
inputId = ns("uri"),
label = "Web address",
label = i18n$t("Web address"),
value = if_not_missing(url, "https://redcap.your.institution/"),
width = "100%"
),
shiny::helpText("Format should be either 'https://redcap.your.institution/' or 'https://your.institution/redcap/'"),
shiny::helpText(i18n$t("Format should be either 'https://redcap.your.institution/' or 'https://your.institution/redcap/'")),
# shiny::textInput(
# inputId = ns("api"),
# label = "API token",
@ -5725,16 +5571,16 @@ m_redcap_readUI <- function(id, title = TRUE, url = NULL) {
# ),
shiny::passwordInput(
inputId = ns("api"),
label = "API token",
label = i18n$t("API token"),
value = "",
width = "100%"
),
shiny::helpText("The token is a string of 32 numbers and letters."),
shiny::helpText(i18n$t("The token is a string of 32 numbers and letters.")),
shiny::br(),
shiny::br(),
shiny::actionButton(
inputId = ns("data_connect"),
label = "Connect",
label = i18n$t("Connect"),
icon = shiny::icon("link", lib = "glyphicon"),
width = "100%",
disabled = TRUE
@ -5759,13 +5605,13 @@ m_redcap_readUI <- function(id, title = TRUE, url = NULL) {
shiny::uiOutput(outputId = ns("arms")),
shiny::textInput(
inputId = ns("filter"),
label = "Optional filter logic (e.g., [gender] = 'female')"
)
label = i18n$t("Optional filter logic (e.g., [gender] = 'female')"
))
)
params_ui <-
shiny::tagList(
shiny::tags$h4("Data import parameters"),
shiny::tags$h4(i18n$t("Data import parameters")),
shiny::tags$div(
style = htmltools::css(
display = "grid",
@ -5791,14 +5637,14 @@ m_redcap_readUI <- function(id, title = TRUE, url = NULL) {
)
)
),
shiny::helpText("Select fields/variables to import and click the funnel to apply optional filters"),
shiny::helpText(i18n$t("Select fields/variables to import and click the funnel to apply optional filters")),
shiny::tags$br(),
shiny::tags$br(),
shiny::uiOutput(outputId = ns("data_type")),
shiny::uiOutput(outputId = ns("fill")),
shiny::actionButton(
inputId = ns("data_import"),
label = "Import",
label = i18n$t("Import"),
icon = shiny::icon("download", lib = "glyphicon"),
width = "100%",
disabled = TRUE
@ -5917,11 +5763,11 @@ m_redcap_readServer <- function(id) {
selector = ns("connect"),
status = "success",
include_data_alert(
see_data_text = "Click to see data dictionary",
see_data_text = i18n$t("Click to see data dictionary"),
dataIdName = "see_dd",
extra = tags$p(
tags$b(phosphoricons::ph("check", weight = "bold"), "Connected to server!"),
glue::glue("The {data_rv$info$project_title} project is loaded.")
tags$b(phosphoricons::ph("check", weight = "bold"), i18n$t("Connected to server!")),
glue::glue(i18n$t("The {data_rv$info$project_title} project is loaded."))
),
btn_show_data = TRUE
)
@ -5948,10 +5794,10 @@ m_redcap_readServer <- function(id) {
shiny::observeEvent(input$see_dd, {
show_data(
purrr::pluck(data_rv$dd_list, "data"),
title = "Data dictionary",
title = i18n$t("Data dictionary"),
type = "modal",
show_classes = FALSE,
tags$b("Preview:")
tags$b(i18n$t("Preview:"))
)
})
@ -5959,10 +5805,10 @@ m_redcap_readServer <- function(id) {
show_data(
# purrr::pluck(data_rv$dd_list, "data"),
data_rv$data,
title = "Imported data set",
title = i18n$t("Imported data set"),
type = "modal",
show_classes = FALSE,
tags$b("Preview:")
tags$b(i18n$t("Preview:"))
)
})
@ -5980,7 +5826,7 @@ m_redcap_readServer <- function(id) {
shiny::req(data_rv$dd_list)
shinyWidgets::virtualSelectInput(
inputId = ns("fields"),
label = "Select fields/variables to import:",
label = i18n$t("Select fields/variables to import:"),
choices = purrr::pluck(data_rv$dd_list, "data") |>
dplyr::select(field_name, form_name) |>
(\(.x){
@ -5999,7 +5845,7 @@ m_redcap_readServer <- function(id) {
if (isTRUE(data_rv$info$has_repeating_instruments_or_events)) {
vectorSelectInput(
inputId = ns("data_type"),
label = "Specify the data format",
label = i18n$t("Specify the data format"),
choices = c(
"Wide data (One row for each subject)" = "wide",
"Long data for project with repeating instruments (default REDCap)" = "long"
@ -6026,7 +5872,7 @@ m_redcap_readServer <- function(id) {
if (input$data_type == "long" && isTRUE(any(input$fields %in% data_rv$rep_fields))) {
vectorSelectInput(
inputId = ns("fill"),
label = "Fill missing values?",
label = i18n$t("Fill missing values?"),
choices = c(
"Yes, fill missing, non-repeated values" = "yes",
"No, leave the data as is" = "no"
@ -6108,7 +5954,7 @@ m_redcap_readServer <- function(id) {
data_rv$data_message <- imported$raw_text
} else {
data_rv$data_status <- "success"
data_rv$data_message <- "Requested data was retrieved!"
data_rv$data_message <- i18n$t("Requested data was retrieved!")
## The data management below should be separated to allow for changing
## "wide"/"long" without re-importing data
@ -6143,12 +5989,12 @@ m_redcap_readServer <- function(id) {
if (!any(in_data_check[-1])) {
data_rv$data_status <- "warning"
data_rv$data_message <- "Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access."
data_rv$data_message <- i18n$t("Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.")
}
if (!all(in_data_check)) {
data_rv$data_status <- "warning"
data_rv$data_message <- "Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access."
data_rv$data_message <- i18n$t("Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.")
}
data_rv$code <- code
@ -6175,7 +6021,7 @@ m_redcap_readServer <- function(id) {
# data_rv$data_message
# ),
include_data_alert(
see_data_text = "Click to see the imported data",
see_data_text = i18n$t("Click to see the imported data"),
dataIdName = "see_data",
extra = tags$p(
tags$b(phosphoricons::ph("check", weight = "bold"), data_rv$data_message)
@ -7515,7 +7361,7 @@ regression_ui <- function(id, ...) {
shiny::tagList(
# title = "",
bslib::nav_panel(
title = "Regression table",
title = i18n$t("Regression table"),
bslib::layout_sidebar(
sidebar = bslib::sidebar(
shiny::uiOutput(outputId = ns("data_info"), inline = TRUE),
@ -7525,7 +7371,7 @@ regression_ui <- function(id, ...) {
multiple = FALSE,
bslib::accordion_panel(
value = "acc_pan_reg",
title = "Regression",
title = i18n$t("Regression"),
icon = bsicons::bs_icon("calculator"),
shiny::uiOutput(outputId = ns("outcome_var")),
# shiny::selectInput(
@ -7540,7 +7386,7 @@ regression_ui <- function(id, ...) {
shiny::uiOutput(outputId = ns("regression_type")),
shiny::radioButtons(
inputId = ns("all"),
label = "Specify covariables",
label = i18n$t("Specify covariables"),
inline = TRUE, selected = 2,
choiceNames = c(
"Yes",
@ -7551,15 +7397,15 @@ regression_ui <- function(id, ...) {
shiny::conditionalPanel(
condition = "input.all==1",
shiny::uiOutput(outputId = ns("regression_vars")),
shiny::helpText("If none are selected, all are included."),
shiny::helpText(i18n$t("If none are selected, all are included.")),
shiny::tags$br(),
ns = ns
),
bslib::input_task_button(
id = ns("load"),
label = "Analyse",
label = i18n$t("Analyse"),
icon = bsicons::bs_icon("pencil"),
label_busy = "Working...",
label_busy = i18n$t("Working..."),
icon_busy = fontawesome::fa_i("arrows-rotate",
class = "fa-spin",
"aria-hidden" = "true"
@ -7567,17 +7413,18 @@ regression_ui <- function(id, ...) {
type = "secondary",
auto_reset = TRUE
),
shiny::helpText("Press 'Analyse' to create the regression model and after changing parameters."),
shiny::helpText(i18n$t("Press 'Analyse' to create the regression model and after changing parameters.")),
shiny::tags$br(),
shiny::radioButtons(
inputId = ns("add_regression_p"),
label = "Show p-value",
label = i18n$t("Show p-value"),
inline = TRUE,
selected = "yes",
choices = list(
"Yes" = "yes",
"No" = "no"
)
choiceNames = c(
"Yes",
"No"
),
choiceValues = c("yes", "no")
),
# shiny::tags$br(),
# shiny::radioButtons(
@ -7620,7 +7467,7 @@ regression_ui <- function(id, ...) {
shiny::tagList(
shinyWidgets::noUiSliderInput(
inputId = ns("plot_height"),
label = "Plot height (mm)",
label = i18n$t("Plot height (mm)"),
min = 50,
max = 300,
value = 100,
@ -7630,7 +7477,7 @@ regression_ui <- function(id, ...) {
),
shinyWidgets::noUiSliderInput(
inputId = ns("plot_width"),
label = "Plot width (mm)",
label = i18n$t("Plot width (mm)"),
min = 50,
max = 300,
value = 100,
@ -7640,7 +7487,7 @@ regression_ui <- function(id, ...) {
),
shiny::selectInput(
inputId = ns("plot_type"),
label = "File format",
label = i18n$t("File format"),
choices = list(
"png",
"tiff",
@ -7654,7 +7501,7 @@ regression_ui <- function(id, ...) {
# Button
shiny::downloadButton(
outputId = ns("download_plot"),
label = "Download plot",
label = i18n$t("Download plot"),
icon = shiny::icon("download")
)
)
@ -7666,7 +7513,7 @@ regression_ui <- function(id, ...) {
)
),
bslib::nav_panel(
title = "Model checks",
title = i18n$t("Model checks"),
bslib::layout_sidebar(
sidebar = bslib::sidebar(
bslib::accordion(
@ -8739,11 +8586,11 @@ ui_elements <- function(selection) {
shiny::tags$br(),
shiny::actionButton(
inputId = "data_reset",
label = "Restore original data",
label = i18n$t("Restore original data"),
width = "100%"
),
shiny::tags$br(),
shiny::helpText("Reset to original imported dataset. Careful! There is no un-doing."),
shiny::helpText(i18n$t("Reset to original imported dataset. Careful! There is no un-doing.")),
shiny::tags$br()
)
# )
@ -8762,7 +8609,7 @@ ui_elements <- function(selection) {
# bslib::navset_bar(
# title = "",
bslib::nav_panel(
title = "Characteristics",
title = i18n$t("Characteristics"),
icon = bsicons::bs_icon("table"),
bslib::layout_sidebar(
sidebar = bslib::sidebar(
@ -8777,12 +8624,12 @@ ui_elements <- function(selection) {
title = "Settings",
icon = bsicons::bs_icon("table"),
shiny::uiOutput("strat_var"),
shiny::helpText("Only factor/categorical variables are available for stratification. Go back to the 'Prepare' tab to reclass a variable if it's not on the list."),
shiny::helpText(i18n$t("Only factor/categorical variables are available for stratification. Go back to the 'Prepare' tab to reclass a variable if it's not on the list.")),
shiny::conditionalPanel(
condition = "input.strat_var!='none'",
shiny::radioButtons(
inputId = "add_p",
label = "Compare strata?",
label = i18n$t("Compare strata?"),
selected = "no",
inline = TRUE,
choices = list(
@ -8796,7 +8643,7 @@ ui_elements <- function(selection) {
shiny::br(),
shiny::actionButton(
inputId = "act_eval",
label = "Evaluate",
label = i18n$t("Evaluate"),
width = "100%",
icon = shiny::icon("calculator"),
disabled = TRUE
@ -8808,7 +8655,7 @@ ui_elements <- function(selection) {
)
),
bslib::nav_panel(
title = "Correlations",
title = i18n$t("Correlations"),
icon = bsicons::bs_icon("bounding-box"),
bslib::layout_sidebar(
sidebar = bslib::sidebar(
@ -8822,11 +8669,11 @@ ui_elements <- function(selection) {
title = "Settings",
icon = bsicons::bs_icon("bounding-box"),
shiny::uiOutput("outcome_var_cor"),
shiny::helpText("To avoid evaluating the correlation of the outcome variable, this can be excluded from the plot or select 'none'."),
shiny::helpText(i18n$t("To avoid evaluating the correlation of the outcome variable, this can be excluded from the plot or select 'none'.")),
shiny::br(),
shinyWidgets::noUiSliderInput(
inputId = "cor_cutoff",
label = "Correlation cut-off",
label = i18n$t("Correlation cut-off"),
min = 0,
max = 1,
step = .01,
@ -8834,7 +8681,7 @@ ui_elements <- function(selection) {
format = shinyWidgets::wNumbFormat(decimals = 2),
color = datamods:::get_primary_color()
),
shiny::helpText("Set the cut-off for considered 'highly correlated'.")
shiny::helpText(i18n$t("Set the cut-off for considered 'highly correlated'."))
)
)
),
@ -8842,7 +8689,7 @@ ui_elements <- function(selection) {
)
),
bslib::nav_panel(
title = "Missings",
title = i18n$t("Missings"),
icon = bsicons::bs_icon("x-circle"),
bslib::layout_sidebar(
sidebar = bslib::sidebar(
@ -8855,7 +8702,7 @@ ui_elements <- function(selection) {
title = "Settings",
icon = bsicons::bs_icon("x-circle"),
shiny::uiOutput("missings_var"),
shiny::helpText("To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not.")
shiny::helpText(i18n$t("To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not."))
)
)
),
@ -8943,7 +8790,8 @@ ui_elements <- function(selection) {
outputId = "report",
label = "Download report",
icon = shiny::icon("download")
)
),
shiny::br()
# shiny::helpText("If choosing to output to MS Word, please note, that when opening the document, two errors will pop-up. Choose to repair and choose not to update references. The issue is being worked on. You can always choose LibreOffice instead."),
),
shiny::column(
@ -10633,11 +10481,13 @@ make_validation_alerts <- function(data) {
#' Data correlations evaluation module
#'
#' @param id Module id
#' @param id id
#'
#' @name data-missings
#' @name visual-summary
#' @returns Shiny ui module
#' @export
#'
#' @example examples/visual_summary_demo.R
visual_summary_ui <- function(id) {
ns <- shiny::NS(id)
@ -10646,8 +10496,17 @@ visual_summary_ui <- function(id) {
)
}
#' Visual summary server
#'
#' @param data_r reactive data
#' @param ... passed on to the visual_summary() function
#'
#' @name visual-summary
#' @returns shiny server
#' @export
#'
visual_summary_server <- function(id,
data_r=shiny::reactive(NULL),
data_r = shiny::reactive(NULL),
...) {
shiny::moduleServer(
id = id,
@ -10676,45 +10535,26 @@ visual_summary_server <- function(id,
# missings_apex_plot(datar(), ...)
# })
output$visual_plot <- shiny::renderPlot(expr = {
visual_summary(data = rv$data,...)
visual_summary(data = rv$data, na.label = i18n$t("Missings"), legend.title = i18n$t("Class"), ylab = i18n$t("Observations"), ...)
})
}
)
}
visual_summary_demo_app <- function() {
ui <- shiny::fluidPage(
shiny::actionButton(
inputId = "modal_missings",
label = "Visual summary",
width = "100%",
disabled = FALSE
)
)
server <- function(input, output, session) {
data_demo <- mtcars
data_demo[sample(1:32, 10), "cyl"] <- NA
data_demo[sample(1:32, 8), "vs"] <- NA
visual_summary_server(id = "data", data = shiny::reactive(data_demo))
observeEvent(input$modal_missings, {
tryCatch(
{
modal_visual_summary(id = "data")
},
error = function(err) {
showNotification(paste0("We encountered the following error browsing your data: ", err), type = "err")
}
)
})
}
shiny::shinyApp(ui, server)
}
visual_summary_demo_app()
#' Visual summary modal
#'
#' @param title title
#' @param easyClose easyClose
#' @param size modal size
#' @param footer modal footer
#' @param ... ignored
#'
#' @name visual-summary
#'
#' @returns shiny modal
#' @export
#'
modal_visual_summary <- function(id,
title = "Visual overview of data classes and missing observations",
easyClose = TRUE,
@ -10733,9 +10573,10 @@ modal_visual_summary <- function(id,
## Slow with many observations...
#' Plot missings and class with apexcharter
#' Plot missings and class with apexcharter. Not in use with FreesearchR.
#'
#' @param data data frame
#' @name visual-summary
#'
#' @returns An [apexchart()] `htmlwidget` object.
#' @export
@ -10790,6 +10631,10 @@ missings_apex_plot <- function(data, animation = FALSE, ...) {
#'
#' @param data data
#' @param ... optional arguments passed to data_summary_gather()
#' @param legend.title Legend title
#' @param ylab Y axis label
#'
#' @name visual-summary
#'
#' @returns ggplot2 object
#' @export
@ -10800,11 +10645,15 @@ missings_apex_plot <- function(data, animation = FALSE, ...) {
#' data_demo[sample(1:32, 8), "vs"] <- NA
#' visual_summary(data_demo)
#' visual_summary(data_demo, palette.fun = scales::hue_pal())
#' visual_summary(dplyr::storms)
#' visual_summary(dplyr::storms, summary.fun = data_type)
visual_summary <- function(data, legend.title = "Data class", ...) {
#' visual_summary(dplyr::storms, summary.fun = data_type, na.label = "Missings", legend.title = "Class")
visual_summary <- function(data, legend.title = NULL, ylab = "Observations", ...) {
l <- data_summary_gather(data, ...)
if (is.null(legend.title)) {
legend.title <- l$summary.fun
}
df <- l$data
df$valueType <- factor(df$valueType, levels = names(l$colors))
@ -10818,13 +10667,13 @@ visual_summary <- function(data, legend.title = "Data class", ...) {
vjust = 1, hjust = 1
)) +
ggplot2::scale_fill_manual(values = l$colors) +
ggplot2::labs(x = "", y = "Observations") +
ggplot2::labs(x = "", y = ylab) +
ggplot2::scale_y_reverse() +
ggplot2::theme(axis.text.x = ggplot2::element_text(hjust = 0.5)) +
ggplot2::guides(colour = "none") +
ggplot2::guides(fill = ggplot2::guide_legend(title = legend.title)) +
# change the limits etc.
ggplot2::guides(fill = ggplot2::guide_legend(title = "Type")) +
# ggplot2::guides(fill = ggplot2::guide_legend(title = guide.lab)) +
# add info about the axes
ggplot2::scale_x_discrete(position = "top") +
ggplot2::theme(axis.text.x = ggplot2::element_text(hjust = 0)) +
@ -10839,16 +10688,18 @@ visual_summary <- function(data, legend.title = "Data class", ...) {
#' Data summary for printing visual summary
#'
#' @param data data.frame
#' @param fun summary function. Default is "class"
#' @param palette.fun optionally use specific palette functions. First argument
#' has to be the length.
#' @param summary.fun fun for summarising
#' @param na.label label for NA
#' @param ... overflow
#'
#' @returns data.frame
#' @export
#'
#' @examples
#' mtcars |> data_summary_gather()
data_summary_gather <- function(data, summary.fun = class, palette.fun = viridisLite::viridis) {
data_summary_gather <- function(data, summary.fun = class, palette.fun = viridisLite::viridis, na.label = "NA", ...) {
df_plot <- setNames(data, unique_short(names(data))) |>
purrr::map_df(\(x){
ifelse(is.na(x),
@ -10870,12 +10721,12 @@ data_summary_gather <- function(data, summary.fun = class, palette.fun = viridis
forcats::as_factor() |>
as.numeric()
df_plot$valueType[is.na(df_plot$valueType)] <- "NA"
df_plot$valueType[is.na(df_plot$valueType)] <- na.label
df_plot$valueType_num[is.na(df_plot$valueType_num)] <- max(df_plot$valueType_num, na.rm = TRUE) + 1
labels <- setNames(unique(df_plot$valueType_num), unique(df_plot$valueType)) |> sort()
if (any(df_plot$valueType == "NA")) {
if (any(df_plot$valueType == na.label)) {
colors <- setNames(c(palette.fun(length(labels) - 1), "#999999"), names(labels))
} else {
colors <- setNames(palette.fun(length(labels)), names(labels))
@ -10893,7 +10744,7 @@ data_summary_gather <- function(data, summary.fun = class, palette.fun = viridis
}) |>
setNames(NULL)
list(data = df_plot, colors = colors, labels = label_list)
list(data = df_plot, colors = colors, labels = label_list, summary.fun = deparse(substitute(summary.fun)))
}
@ -11442,7 +11293,7 @@ server <- function(input, output, session) {
modal_visual_summary(
id = "initial_summary",
footer = NULL,
size = "xl"
size = "xl",title = i18n$t("Data classes and missing observations")
)
},
error = function(err) {
@ -11575,8 +11426,10 @@ server <- function(input, output, session) {
shinyWidgets::ask_confirmation(
cancelOnDismiss = TRUE,
inputId = "reset_confirm",
title = "Please confirm data reset?",
type = "warning"
title = i18n$t("Please confirm data reset!"),
type = "warning",
text = i18n$t("Sure you want to reset data? This cannot be undone."),
btn_labels = c(i18n$t("Cancel"), i18n$t("Confirm"))
)
})
@ -11590,14 +11443,14 @@ server <- function(input, output, session) {
output$data_info <- shiny::renderUI({
shiny::req(data_filter())
data_description(data_filter(), "The filtered data")
data_description(data_filter(), data_text = i18n$t("The filtered data"))
})
######### Create factor
shiny::observeEvent(
input$modal_cut,
modal_cut_variable("modal_cut", title = "Create new factor")
modal_cut_variable("modal_cut", title = i18n$t("Create new factor"))
)
data_modal_cut <- cut_variable_server(
@ -11614,7 +11467,7 @@ server <- function(input, output, session) {
shiny::observeEvent(
input$modal_update,
datamods::modal_update_factor(id = "modal_update", title = "Reorder factor levels")
datamods::modal_update_factor(id = "modal_update", title = i18n$t("Reorder factor levels"))
)
data_modal_update <- datamods::update_factor_server(
@ -11634,8 +11487,8 @@ server <- function(input, output, session) {
input$modal_column,
modal_create_column(
id = "modal_column",
footer = shiny::markdown("This window is aimed at advanced users and require some *R*-experience!"),
title = "Create new variables"
footer = shiny::markdown(i18n$t("This window is aimed at advanced users and require some *R*-experience!")),
title = i18n$t("Create new variables")
)
)
data_modal_r <- create_column_server(
@ -11673,7 +11526,7 @@ server <- function(input, output, session) {
# c("dichotomous", "ordinal", "categorical", "datatime", "continuous")
shinyWidgets::virtualSelectInput(
inputId = "column_filter",
label = "Select data types to include",
label = i18n$t("Select data types to include"),
selected = unique(data_type(rv$data)),
choices = unique(data_type(rv$data)),
updateOn = "change",
@ -11878,7 +11731,7 @@ server <- function(input, output, session) {
observeEvent(input$modal_browse, {
tryCatch(
{
show_data(REDCapCAST::fct_drop(rv$data_filtered), title = "Uploaded data overview", type = "modal")
show_data(REDCapCAST::fct_drop(rv$data_filtered), title = i18n$t("Uploaded data overview"), type = "modal")
},
error = function(err) {
showNotification(paste0("We encountered the following error browsing your data: ", err), type = "err")
@ -11900,7 +11753,7 @@ server <- function(input, output, session) {
{
modal_visual_summary(
id = "visual_overview",
footer = "Here is an overview of how your data is interpreted, and where data is missing. Use this information to consider if data is missing at random or if some observations are missing systematically wich may be caused by an observation bias.",
footer = i18n$t("Here is an overview of how your data is interpreted, and where data is missing. Use this information to consider if data is missing at random or if some observations are missing systematically wich may be caused by an observation bias."),
size = "xl"
)
},
@ -11952,12 +11805,12 @@ server <- function(input, output, session) {
output$code_import <- shiny::renderUI({
shiny::req(rv$code$import)
prismCodeBlock(paste0("#Data import\n", rv$code$import))
prismCodeBlock(paste0(i18n$t("#Data import\n"), rv$code$import))
})
output$code_format <- shiny::renderUI({
shiny::req(rv$code$format)
prismCodeBlock(paste0("#Data import formatting\n", rv$code$format))
prismCodeBlock(paste0(i18n$t("#Data import formatting\n"), rv$code$format))
})
output$code_data <- shiny::renderUI({

View file

@ -129,34 +129,93 @@
"Drawing the plot. Hold tight for a moment..","Tegner grafikken. Spænd selen.."
"#Plotting\n","#Tegner\n"
"Stacked horizontal bars","Stablede horisontale søjler"
"A classical way of visualising the distribution of an ordinal scale like the modified Ranking Scale and known as Grotta bars","A classical way of visualising the distribution of an ordinal scale like the modified Ranking Scale and known as Grotta bars"
"Violin plot","Violin plot"
"A modern alternative to the classic boxplot to visualise data distribution","A modern alternative to the classic boxplot to visualise data distribution"
"Sankey plot","Sankey plot"
"A way of visualising change between groups","A way of visualising change between groups"
"Scatter plot","Scatter plot"
"A classic way of showing the association between to variables","A classic way of showing the association between to variables"
"Box plot","Box plot"
"A classic way to plot data distribution by groups","A classic way to plot data distribution by groups"
"A classical way of visualising the distribution of an ordinal scale like the modified Ranking Scale and known as Grotta bars","En klassisk visualisering af fordelingen af observationer på en ordinal kategorisk skala. Typisk brugt til modified Rankin Scale og kendes også som 'Grotta bars'"
"Violin plot","Violin-diagram"
"A modern alternative to the classic boxplot to visualise data distribution","Moderne alternativ til den klassiske box-plot og velegnet til at visualisere fordelingen af observationer"
"Sankey plot","Sankey-diagram"
"A way of visualising change between groups","Visualiserer ændring mellem grupper for samme type observationer"
"Scatter plot","Punkt-diagram"
"A classic way of showing the association between to variables","Visualiserer forholdet mellem to variabler"
"Box plot","Kasse-diagram"
"A classic way to plot data distribution by groups","Klassik måde at visualisere fordeling"
"Euler diagram","Eulerdiagram"
"Generate area-proportional Euler diagrams to display set relationships","Generate area-proportional Euler diagrams to display set relationships"
"Generate area-proportional Euler diagrams to display set relationships","Generer proportionelt Euler-diagram for at vise forhold mellem forskellige kategoriske observationer"
"Documentation","Dokumentation"
"Data is only stored for analyses and deleted when the app is closed.","Data is only stored for analyses and deleted when the app is closed."
"Consider [running ***FreesearchR*** locally](https://agdamsbo.github.io/FreesearchR/#run-locally-on-your-own-machine) if working with sensitive data.","Consider [running ***FreesearchR*** locally](https://agdamsbo.github.io/FreesearchR/#run-locally-on-your-own-machine) if working with sensitive data."
"Data is only stored for analyses and deleted when the app is closed.","Data opbevares alene til brug i analyser og slettes så snart appen lukkes."
"Consider [running ***FreesearchR*** locally](https://agdamsbo.github.io/FreesearchR/#run-locally-on-your-own-machine) if working with sensitive data.","Overvej at [køre ***FreesearchR*** lokalt](https://agdamsbo.github.io/FreesearchR/#run-locally-on-your-own-machine) hvis du arbejder med personfølsomme data."
"Feedback","Feedback"
"License: AGPLv3","Licens: AGPLv3"
"Source","Kilde"
"Data includes {n_pairs} pairs of highly correlated variables.","Der er {n_pairs} variabel-par, der er stærkt internt korrelerede."
"Create plot","Dan grafik"
"Coefficients plot","Koefficientgraf"
"Checks","Checks"
"Below you find a summary table for quick insigths, and on the right you can visualise data classes, browse observations and apply different data filters.","Below you find a summary table for quick insigths, and on the right you can visualise data classes, browse observations and apply different data filters."
"Checks","Test af model"
"Below you find a summary table for quick insigths, and on the right you can visualise data classes, browse observations and apply different data filters.","Nedenfor er en opsummerende tabel, der giver hurtigt overblik. Til højre kan du få et visuelt overblik, gennemgå observationer og oprette datafiltre."
"Browse observations","Gennemse observationer"
"Settings","Indstillinger"
"The following error occured on determining correlations:","The following error occured on determining correlations:"
"We encountered the following error creating your report:","We encountered the following error creating your report:"
"The following error occured on determining correlations:","Følgende fejl opstod i forbindelse med korrelationsanalysen:"
"We encountered the following error creating your report:","Følgende fejl opstod, da rapporten blev dannet:"
"No variable chosen for analysis","Ingen variabel er valgt til analysen"
"No missing observations","Ingen manglende observationer"
"Missing vs non-missing observations in the variable **'{variabler()}'**","Manglende vs ikke-manglende observationer i variablen **'{variabler()}'**"
"There is a significant correlation between {n_nonmcar} variables and missing observations in the outcome variable {outcome}.","There is a significant correlation between {n_nonmcar} variables and missing observations in the outcome variable {outcome}."
"There is a significant correlation between {n_nonmcar} variables and missing observations in the outcome variable {outcome}.","Der er en betydelig korrelation blandt {n_nonmcar} variabler sammenlignet efter manglende observationer i {outcome}."
"There is a total of {p_miss} % missing observations.","Der er i alt {p_miss} % manglende observationer."
"Median:","Median:"
"Restore original data","Gendan originale data"
"Reset to original imported dataset. Careful! There is no un-doing.","Gendan det oprindeligt importerede datasæt. Forsigtig! Alle dine ændringer vil forsvinde."
"Characteristics","Karakteristika"
"Only factor/categorical variables are available for stratification. Go back to the 'Prepare' tab to reclass a variable if it's not on the list.","Alene kategoriske variabler kan danne grundlag for stratificering. Mangler du en variabel, så gå til ""Forbered"" og omklassificer til kategorisk."
"Compare strata?","Sammenlign strata?"
"Correlations","Korrelationer"
"To avoid evaluating the correlation of the outcome variable, this can be excluded from the plot or select 'none'.","For at udelukke svarvariablen fra korrelationsanalysen, så kan du vælge din svarvariabel eller vælge 'non', hvis du ikke vil angive en."
"Correlation cut-off","Korrelationsgrænse"
"Set the cut-off for considered 'highly correlated'.","Angiv grænsen for. hvad, der tolkes som 'betydelig korrelation'."
"Missings","Manglende observationer"
"To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not.","To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not."
"Class","Klasse"
"Observations","Observationer"
"Data classes and missing observations","Dataklasser og manglende observationer"
"Sure you want to reset data? This cannot be undone.","Er du sikker på at du vil gendanne data? Det kan ikke fortrydes."
"Cancel","Afbryd"
"Confirm","Bekræft"
"The filtered data","Filtreret data"
"Create new factor","Ny kategorisk variabel"
"This window is aimed at advanced users and require some *R*-experience!","This window is aimed at advanced users and require some *R*-experience!"
"Create new variables","Opret ny variabel"
"Select data types to include","Vælg datatyper, der skal inkluderes"
"Uploaded data overview","Overblik over uploaded data"
"Here is an overview of how your data is interpreted, and where data is missing. Use this information to consider if data is missing at random or if some observations are missing systematically wich may be caused by an observation bias.","Here is an overview of how your data is interpreted, and where data is missing. Use this information to consider if data is missing at random or if some observations are missing systematically wich may be caused by an observation bias."
"#Data import\n","#Data import\n"
"#Data import formatting\n","#Formatering ved data-import\n"
"Specify covariables","Angiv kovariabler"
"If none are selected, all are included.","Hvis ingen er valgt inkluderes alle."
"Analyse","Analysér"
"Working...","Arbejder..."
"Press 'Analyse' to create the regression model and after changing parameters.","Tryk 'Analysér' for at danne regressionsmodel og for at opdatere hvis parametre ændres."
"Show p-value","Vis p-værdi"
"Model checks","Model-test"
"Please confirm data reset!","Bekræft gendannelse af data!"
"Import data from REDCap","Importér data fra REDCap"
"REDCap server","REDCap-server"
"Web address","Web address"
"Format should be either 'https://redcap.your.institution/' or 'https://your.institution/redcap/'","Adressen skal være som 'https://redcap.your.institution/' eller 'https://your.institution/redcap/'"
"API token","API token"
"The token is a string of 32 numbers and letters.","En API-nøgle består af ialt 32 tal og bogstaver."
"Connect","Forbind"
"Data import parameters","Data import parameters"
"Select fields/variables to import and click the funnel to apply optional filters","Select fields/variables to import and click the funnel to apply optional filters"
"Import","Import"
"Click to see data dictionary","Click to see data dictionary"
"Connected to server!","Connected to server!"
"The {data_rv$info$project_title} project is loaded.","The {data_rv$info$project_title} project is loaded."
"Data dictionary","Data dictionary"
"Preview:","Preview:"
"Imported data set","Imported data set"
"Select fields/variables to import:","Select fields/variables to import:"
"Specify the data format","Specify the data format"
"Fill missing values?","Fill missing values?"
"Requested data was retrieved!","Requested data was retrieved!"
"Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.","Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access."
"Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.","Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access."
"Click to see the imported data","Click to see the imported data"
"Regression table","Regression table"

1 en da
129 Drawing the plot. Hold tight for a moment.. Tegner grafikken. Spænd selen..
130 #Plotting\n #Tegner\n
131 Stacked horizontal bars Stablede horisontale søjler
132 A classical way of visualising the distribution of an ordinal scale like the modified Ranking Scale and known as Grotta bars A classical way of visualising the distribution of an ordinal scale like the modified Ranking Scale and known as Grotta bars En klassisk visualisering af fordelingen af observationer på en ordinal kategorisk skala. Typisk brugt til modified Rankin Scale og kendes også som 'Grotta bars'
133 Violin plot Violin plot Violin-diagram
134 A modern alternative to the classic boxplot to visualise data distribution A modern alternative to the classic boxplot to visualise data distribution Moderne alternativ til den klassiske box-plot og velegnet til at visualisere fordelingen af observationer
135 Sankey plot Sankey plot Sankey-diagram
136 A way of visualising change between groups A way of visualising change between groups Visualiserer ændring mellem grupper for samme type observationer
137 Scatter plot Scatter plot Punkt-diagram
138 A classic way of showing the association between to variables A classic way of showing the association between to variables Visualiserer forholdet mellem to variabler
139 Box plot Box plot Kasse-diagram
140 A classic way to plot data distribution by groups A classic way to plot data distribution by groups Klassik måde at visualisere fordeling
141 Euler diagram Eulerdiagram
142 Generate area-proportional Euler diagrams to display set relationships Generate area-proportional Euler diagrams to display set relationships Generer proportionelt Euler-diagram for at vise forhold mellem forskellige kategoriske observationer
143 Documentation Dokumentation
144 Data is only stored for analyses and deleted when the app is closed. Data is only stored for analyses and deleted when the app is closed. Data opbevares alene til brug i analyser og slettes så snart appen lukkes.
145 Consider [running ***FreesearchR*** locally](https://agdamsbo.github.io/FreesearchR/#run-locally-on-your-own-machine) if working with sensitive data. Consider [running ***FreesearchR*** locally](https://agdamsbo.github.io/FreesearchR/#run-locally-on-your-own-machine) if working with sensitive data. Overvej at [køre ***FreesearchR*** lokalt](https://agdamsbo.github.io/FreesearchR/#run-locally-on-your-own-machine) hvis du arbejder med personfølsomme data.
146 Feedback Feedback
147 License: AGPLv3 Licens: AGPLv3
148 Source Kilde
149 Data includes {n_pairs} pairs of highly correlated variables. Der er {n_pairs} variabel-par, der er stærkt internt korrelerede.
150 Create plot Dan grafik
151 Coefficients plot Koefficientgraf
152 Checks Checks Test af model
153 Below you find a summary table for quick insigths, and on the right you can visualise data classes, browse observations and apply different data filters. Below you find a summary table for quick insigths, and on the right you can visualise data classes, browse observations and apply different data filters. Nedenfor er en opsummerende tabel, der giver hurtigt overblik. Til højre kan du få et visuelt overblik, gennemgå observationer og oprette datafiltre.
154 Browse observations Gennemse observationer
155 Settings Indstillinger
156 The following error occured on determining correlations: The following error occured on determining correlations: Følgende fejl opstod i forbindelse med korrelationsanalysen:
157 We encountered the following error creating your report: We encountered the following error creating your report: Følgende fejl opstod, da rapporten blev dannet:
158 No variable chosen for analysis Ingen variabel er valgt til analysen
159 No missing observations Ingen manglende observationer
160 Missing vs non-missing observations in the variable **'{variabler()}'** Manglende vs ikke-manglende observationer i variablen **'{variabler()}'**
161 There is a significant correlation between {n_nonmcar} variables and missing observations in the outcome variable {outcome}. There is a significant correlation between {n_nonmcar} variables and missing observations in the outcome variable {outcome}. Der er en betydelig korrelation blandt {n_nonmcar} variabler sammenlignet efter manglende observationer i {outcome}.
162 There is a total of {p_miss} % missing observations. Der er i alt {p_miss} % manglende observationer.
163 Median: Median:
164 Restore original data Gendan originale data
165 Reset to original imported dataset. Careful! There is no un-doing. Gendan det oprindeligt importerede datasæt. Forsigtig! Alle dine ændringer vil forsvinde.
166 Characteristics Karakteristika
167 Only factor/categorical variables are available for stratification. Go back to the 'Prepare' tab to reclass a variable if it's not on the list. Alene kategoriske variabler kan danne grundlag for stratificering. Mangler du en variabel, så gå til "Forbered" og omklassificer til kategorisk.
168 Compare strata? Sammenlign strata?
169 Correlations Korrelationer
170 To avoid evaluating the correlation of the outcome variable, this can be excluded from the plot or select 'none'. For at udelukke svarvariablen fra korrelationsanalysen, så kan du vælge din svarvariabel eller vælge 'non', hvis du ikke vil angive en.
171 Correlation cut-off Korrelationsgrænse
172 Set the cut-off for considered 'highly correlated'. Angiv grænsen for. hvad, der tolkes som 'betydelig korrelation'.
173 Missings Manglende observationer
174 To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not. To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not.
175 Class Klasse
176 Observations Observationer
177 Data classes and missing observations Dataklasser og manglende observationer
178 Sure you want to reset data? This cannot be undone. Er du sikker på at du vil gendanne data? Det kan ikke fortrydes.
179 Cancel Afbryd
180 Confirm Bekræft
181 The filtered data Filtreret data
182 Create new factor Ny kategorisk variabel
183 This window is aimed at advanced users and require some *R*-experience! This window is aimed at advanced users and require some *R*-experience!
184 Create new variables Opret ny variabel
185 Select data types to include Vælg datatyper, der skal inkluderes
186 Uploaded data overview Overblik over uploaded data
187 Here is an overview of how your data is interpreted, and where data is missing. Use this information to consider if data is missing at random or if some observations are missing systematically wich may be caused by an observation bias. Here is an overview of how your data is interpreted, and where data is missing. Use this information to consider if data is missing at random or if some observations are missing systematically wich may be caused by an observation bias.
188 #Data import\n #Data import\n
189 #Data import formatting\n #Formatering ved data-import\n
190 Specify covariables Angiv kovariabler
191 If none are selected, all are included. Hvis ingen er valgt inkluderes alle.
192 Analyse Analysér
193 Working... Arbejder...
194 Press 'Analyse' to create the regression model and after changing parameters. Tryk 'Analysér' for at danne regressionsmodel og for at opdatere hvis parametre ændres.
195 Show p-value Vis p-værdi
196 Model checks Model-test
197 Please confirm data reset! Bekræft gendannelse af data!
198 Import data from REDCap Importér data fra REDCap
199 REDCap server REDCap-server
200 Web address Web address
201 Format should be either 'https://redcap.your.institution/' or 'https://your.institution/redcap/' Adressen skal være som 'https://redcap.your.institution/' eller 'https://your.institution/redcap/'
202 API token API token
203 The token is a string of 32 numbers and letters. En API-nøgle består af ialt 32 tal og bogstaver.
204 Connect Forbind
205 Data import parameters Data import parameters
206 Select fields/variables to import and click the funnel to apply optional filters Select fields/variables to import and click the funnel to apply optional filters
207 Import Import
208 Click to see data dictionary Click to see data dictionary
209 Connected to server! Connected to server!
210 The {data_rv$info$project_title} project is loaded. The {data_rv$info$project_title} project is loaded.
211 Data dictionary Data dictionary
212 Preview: Preview:
213 Imported data set Imported data set
214 Select fields/variables to import: Select fields/variables to import:
215 Specify the data format Specify the data format
216 Fill missing values? Fill missing values?
217 Requested data was retrieved! Requested data was retrieved!
218 Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access. Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.
219 Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access. Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.
220 Click to see the imported data Click to see the imported data
221 Regression table Regression table

View file

@ -160,3 +160,62 @@
"Missing vs non-missing observations in the variable **'{variabler()}'**","Missing vs non-missing observations in the variable **'{variabler()}'**"
"There is a significant correlation between {n_nonmcar} variables and missing observations in the outcome variable {outcome}.","There is a significant correlation between {n_nonmcar} variables and missing observations in the outcome variable {outcome}."
"There is a total of {p_miss} % missing observations.","There is a total of {p_miss} % missing observations."
"Median:","Median:"
"Restore original data","Restore original data"
"Reset to original imported dataset. Careful! There is no un-doing.","Reset to original imported dataset. Careful! There is no un-doing."
"Characteristics","Characteristics"
"Only factor/categorical variables are available for stratification. Go back to the 'Prepare' tab to reclass a variable if it's not on the list.","Only factor/categorical variables are available for stratification. Go back to the 'Prepare' tab to reclass a variable if it's not on the list."
"Compare strata?","Compare strata?"
"Correlations","Correlations"
"To avoid evaluating the correlation of the outcome variable, this can be excluded from the plot or select 'none'.","To avoid evaluating the correlation of the outcome variable, this can be excluded from the plot or select 'none'."
"Correlation cut-off","Correlation cut-off"
"Set the cut-off for considered 'highly correlated'.","Set the cut-off for considered 'highly correlated'."
"Missings","Missings"
"To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not.","To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not."
"Class","Class"
"Observations","Observations"
"Data classes and missing observations","Data classes and missing observations"
"Sure you want to reset data? This cannot be undone.","Sure you want to reset data? This cannot be undone."
"Cancel","Cancel"
"Confirm","Confirm"
"The filtered data","The filtered data"
"Create new factor","Create new factor"
"This window is aimed at advanced users and require some *R*-experience!","This window is aimed at advanced users and require some *R*-experience!"
"Create new variables","Create new variables"
"Select data types to include","Select data types to include"
"Uploaded data overview","Uploaded data overview"
"Here is an overview of how your data is interpreted, and where data is missing. Use this information to consider if data is missing at random or if some observations are missing systematically wich may be caused by an observation bias.","Here is an overview of how your data is interpreted, and where data is missing. Use this information to consider if data is missing at random or if some observations are missing systematically wich may be caused by an observation bias."
"#Data import\n","#Data import\n"
"#Data import formatting\n","#Data import formatting\n"
"Specify covariables","Specify covariables"
"If none are selected, all are included.","If none are selected, all are included."
"Analyse","Analyse"
"Working...","Working..."
"Press 'Analyse' to create the regression model and after changing parameters.","Press 'Analyse' to create the regression model and after changing parameters."
"Show p-value","Show p-value"
"Model checks","Model checks"
"Please confirm data reset!","Please confirm data reset!"
"Import data from REDCap","Import data from REDCap"
"REDCap server","REDCap server"
"Web address","Web address"
"Format should be either 'https://redcap.your.institution/' or 'https://your.institution/redcap/'","Format should be either 'https://redcap.your.institution/' or 'https://your.institution/redcap/'"
"API token","API token"
"The token is a string of 32 numbers and letters.","The token is a string of 32 numbers and letters."
"Connect","Connect"
"Data import parameters","Data import parameters"
"Select fields/variables to import and click the funnel to apply optional filters","Select fields/variables to import and click the funnel to apply optional filters"
"Import","Import"
"Click to see data dictionary","Click to see data dictionary"
"Connected to server!","Connected to server!"
"The {data_rv$info$project_title} project is loaded.","The {data_rv$info$project_title} project is loaded."
"Data dictionary","Data dictionary"
"Preview:","Preview:"
"Imported data set","Imported data set"
"Select fields/variables to import:","Select fields/variables to import:"
"Specify the data format","Specify the data format"
"Fill missing values?","Fill missing values?"
"Requested data was retrieved!","Requested data was retrieved!"
"Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.","Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access."
"Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.","Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access."
"Click to see the imported data","Click to see the imported data"
"Regression table","Regression table"

1 en sw
160 Missing vs non-missing observations in the variable **'{variabler()}'** Missing vs non-missing observations in the variable **'{variabler()}'**
161 There is a significant correlation between {n_nonmcar} variables and missing observations in the outcome variable {outcome}. There is a significant correlation between {n_nonmcar} variables and missing observations in the outcome variable {outcome}.
162 There is a total of {p_miss} % missing observations. There is a total of {p_miss} % missing observations.
163 Median: Median:
164 Restore original data Restore original data
165 Reset to original imported dataset. Careful! There is no un-doing. Reset to original imported dataset. Careful! There is no un-doing.
166 Characteristics Characteristics
167 Only factor/categorical variables are available for stratification. Go back to the 'Prepare' tab to reclass a variable if it's not on the list. Only factor/categorical variables are available for stratification. Go back to the 'Prepare' tab to reclass a variable if it's not on the list.
168 Compare strata? Compare strata?
169 Correlations Correlations
170 To avoid evaluating the correlation of the outcome variable, this can be excluded from the plot or select 'none'. To avoid evaluating the correlation of the outcome variable, this can be excluded from the plot or select 'none'.
171 Correlation cut-off Correlation cut-off
172 Set the cut-off for considered 'highly correlated'. Set the cut-off for considered 'highly correlated'.
173 Missings Missings
174 To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not. To consider if data is missing by random, choose the outcome/dependent variable, if it has any missings to evaluate if there is a significant difference across other variables depending on missing data or not.
175 Class Class
176 Observations Observations
177 Data classes and missing observations Data classes and missing observations
178 Sure you want to reset data? This cannot be undone. Sure you want to reset data? This cannot be undone.
179 Cancel Cancel
180 Confirm Confirm
181 The filtered data The filtered data
182 Create new factor Create new factor
183 This window is aimed at advanced users and require some *R*-experience! This window is aimed at advanced users and require some *R*-experience!
184 Create new variables Create new variables
185 Select data types to include Select data types to include
186 Uploaded data overview Uploaded data overview
187 Here is an overview of how your data is interpreted, and where data is missing. Use this information to consider if data is missing at random or if some observations are missing systematically wich may be caused by an observation bias. Here is an overview of how your data is interpreted, and where data is missing. Use this information to consider if data is missing at random or if some observations are missing systematically wich may be caused by an observation bias.
188 #Data import\n #Data import\n
189 #Data import formatting\n #Data import formatting\n
190 Specify covariables Specify covariables
191 If none are selected, all are included. If none are selected, all are included.
192 Analyse Analyse
193 Working... Working...
194 Press 'Analyse' to create the regression model and after changing parameters. Press 'Analyse' to create the regression model and after changing parameters.
195 Show p-value Show p-value
196 Model checks Model checks
197 Please confirm data reset! Please confirm data reset!
198 Import data from REDCap Import data from REDCap
199 REDCap server REDCap server
200 Web address Web address
201 Format should be either 'https://redcap.your.institution/' or 'https://your.institution/redcap/' Format should be either 'https://redcap.your.institution/' or 'https://your.institution/redcap/'
202 API token API token
203 The token is a string of 32 numbers and letters. The token is a string of 32 numbers and letters.
204 Connect Connect
205 Data import parameters Data import parameters
206 Select fields/variables to import and click the funnel to apply optional filters Select fields/variables to import and click the funnel to apply optional filters
207 Import Import
208 Click to see data dictionary Click to see data dictionary
209 Connected to server! Connected to server!
210 The {data_rv$info$project_title} project is loaded. The {data_rv$info$project_title} project is loaded.
211 Data dictionary Data dictionary
212 Preview: Preview:
213 Imported data set Imported data set
214 Select fields/variables to import: Select fields/variables to import:
215 Specify the data format Specify the data format
216 Fill missing values? Fill missing values?
217 Requested data was retrieved! Requested data was retrieved!
218 Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access. Data retrieved, but it looks like only the ID was retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.
219 Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access. Data retrieved, but it looks like not all requested fields were retrieved from the server. Please check with your REDCap administrator that you have required permissions for data access.
220 Click to see the imported data Click to see the imported data
221 Regression table Regression table

View file

@ -1,16 +0,0 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/data-import.R
\name{data_import_demo_app}
\alias{data_import_demo_app}
\title{Test app for the data-import module}
\usage{
data_import_demo_app()
}
\description{
Test app for the data-import module
}
\examples{
\dontrun{
data_import_demo_app()
}
}

View file

@ -1,17 +1,14 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/missings-module.R, R/visual_summary.R
% Please edit documentation in R/missings-module.R
\name{data-missings}
\alias{data-missings}
\alias{data_missings_ui}
\alias{data_missings_server}
\alias{visual_summary_ui}
\title{Data correlations evaluation module}
\usage{
data_missings_ui(id)
data_missings_server(id, data, variable, ...)
visual_summary_ui(id)
}
\arguments{
\item{id}{Module id}
@ -24,11 +21,7 @@ visual_summary_ui(id)
Shiny ui module
shiny server module
Shiny ui module
}
\description{
Data correlations evaluation module
Data correlations evaluation module
}

View file

@ -7,16 +7,22 @@
data_summary_gather(
data,
summary.fun = class,
palette.fun = viridisLite::viridis
palette.fun = viridisLite::viridis,
na.label = "NA",
...
)
}
\arguments{
\item{data}{data.frame}
\item{summary.fun}{fun for summarising}
\item{palette.fun}{optionally use specific palette functions. First argument
has to be the length.}
\item{fun}{summary function. Default is "class"}
\item{na.label}{label for NA}
\item{...}{overflow}
}
\value{
data.frame

View file

@ -1,26 +0,0 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/visual_summary.R
\name{missings_apex_plot}
\alias{missings_apex_plot}
\title{Plot missings and class with apexcharter}
\usage{
missings_apex_plot(data, animation = FALSE, ...)
}
\arguments{
\item{data}{data frame}
}
\value{
An \code{\link[=apexchart]{apexchart()}} \code{htmlwidget} object.
}
\description{
Plot missings and class with apexcharter
}
\examples{
data_demo <- mtcars
data_demo[2:4, "cyl"] <- NA
rbind(data_demo, data_demo, data_demo, data_demo) |> missings_apex_plot()
data_demo |> missings_apex_plot()
mtcars |> missings_apex_plot(animation = TRUE)
# dplyr::storms |> missings_apex_plot()
visdat::vis_dat(dplyr::storms)
}

119
man/visual-summary.Rd Normal file
View file

@ -0,0 +1,119 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/visual_summary.R
\name{visual-summary}
\alias{visual-summary}
\alias{visual_summary_ui}
\alias{visual_summary_server}
\alias{modal_visual_summary}
\alias{missings_apex_plot}
\alias{visual_summary}
\title{Data correlations evaluation module}
\usage{
visual_summary_ui(id)
visual_summary_server(id, data_r = shiny::reactive(NULL), ...)
modal_visual_summary(
id,
title = "Visual overview of data classes and missing observations",
easyClose = TRUE,
size = "xl",
footer = NULL,
...
)
missings_apex_plot(data, animation = FALSE, ...)
visual_summary(data, legend.title = NULL, ylab = "Observations", ...)
}
\arguments{
\item{id}{id}
\item{data_r}{reactive data}
\item{...}{optional arguments passed to data_summary_gather()}
\item{title}{title}
\item{easyClose}{easyClose}
\item{size}{modal size}
\item{footer}{modal footer}
\item{data}{data}
\item{legend.title}{Legend title}
\item{ylab}{Y axis label}
}
\value{
Shiny ui module
shiny server
shiny modal
An \code{\link[=apexchart]{apexchart()}} \code{htmlwidget} object.
ggplot2 object
}
\description{
Data correlations evaluation module
Visual summary server
Visual summary modal
Plot missings and class with apexcharter. Not in use with FreesearchR.
Ggplot2 data summary visualisation based on visdat::vis_dat.
}
\examples{
visual_summary_demo_app <- function() {
ui <- shiny::fluidPage(
shiny::actionButton(
inputId = "modal_missings",
label = "Visual summary",
width = "100\%",
disabled = FALSE
)
)
server <- function(input, output, session) {
data_demo <- mtcars
data_demo[sample(1:32, 10), "cyl"] <- NA
data_demo[sample(1:32, 8), "vs"] <- NA
data_demo$gear <- factor(data_demo$gear)
visual_summary_server(id = "data", data = shiny::reactive(data_demo),summary.fun=class)
observeEvent(input$modal_missings, {
tryCatch(
{
modal_visual_summary(id = "data")
},
error = function(err) {
showNotification(paste0("We encountered the following error browsing your data: ", err), type = "err")
}
)
})
}
shiny::shinyApp(ui, server)
}
visual_summary_demo_app()
data_demo <- mtcars
data_demo[2:4, "cyl"] <- NA
rbind(data_demo, data_demo, data_demo, data_demo) |> missings_apex_plot()
data_demo |> missings_apex_plot()
mtcars |> missings_apex_plot(animation = TRUE)
# dplyr::storms |> missings_apex_plot()
visdat::vis_dat(dplyr::storms)
data_demo <- mtcars
data_demo[sample(1:32, 10), "cyl"] <- NA
data_demo[sample(1:32, 8), "vs"] <- NA
visual_summary(data_demo)
visual_summary(data_demo, palette.fun = scales::hue_pal())
visual_summary(dplyr::storms, summary.fun = data_type)
visual_summary(dplyr::storms, summary.fun = data_type, na.label = "Missings", legend.title = "Class")
}

View file

@ -1,28 +0,0 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/visual_summary.R
\name{visual_summary}
\alias{visual_summary}
\title{Ggplot2 data summary visualisation based on visdat::vis_dat.}
\usage{
visual_summary(data, legend.title = "Data class", ...)
}
\arguments{
\item{data}{data}
\item{...}{optional arguments passed to data_summary_gather()}
}
\value{
ggplot2 object
}
\description{
Ggplot2 data summary visualisation based on visdat::vis_dat.
}
\examples{
data_demo <- mtcars
data_demo[sample(1:32, 10), "cyl"] <- NA
data_demo[sample(1:32, 8), "vs"] <- NA
visual_summary(data_demo)
visual_summary(data_demo, palette.fun = scales::hue_pal())
visual_summary(dplyr::storms)
visual_summary(dplyr::storms, summary.fun = data_type)
}