feat: the missingness module was overhauled to include two different analysis methods and a better, standalone module
Some checks are pending
pkgdown.yaml / pkgdown (push) Waiting to run

This commit is contained in:
Andreas Gammelgaard Damsbo 2025-12-11 09:34:40 +01:00
parent fab5c6cf22
commit af523edc00
No known key found for this signature in database
25 changed files with 1062 additions and 733 deletions

View file

@ -8,7 +8,7 @@ message: 'To cite package "FreesearchR" in publications use:'
type: software
license: AGPL-3.0-or-later
title: 'FreesearchR: Easy data analysis for clinicians'
version: 25.12.2
version: 25.12.3
doi: 10.5281/zenodo.14527429
identifiers:
- type: url
@ -143,7 +143,7 @@ references:
authors:
- family-names: Müller
given-names: Kirill
email: krlmlr+r@mailbox.org
email: kirill@cynkra.com
orcid: https://orcid.org/0000-0002-1416-3412
year: '2025'
doi: 10.32614/CRAN.package.here
@ -250,6 +250,10 @@ references:
given-names: Barret
email: barret@posit.co
orcid: https://orcid.org/0000-0001-9986-114X
- family-names: Aden-Buie
given-names: Garrick
email: garrick@adenbuie.com
orcid: https://orcid.org/0000-0002-7111-0077
- family-names: Xie
given-names: Yihui
email: yihui@posit.co
@ -312,6 +316,10 @@ references:
given-names: Simon
email: simon.couch@posit.co
orcid: https://orcid.org/0000-0001-5676-5107
- family-names: Hvitfeldt
given-names: Emil
email: emil.hvitfeldt@posit.co
orcid: https://orcid.org/0000-0002-0679-1945
year: '2025'
doi: 10.32614/CRAN.package.broom
- type: software
@ -397,6 +405,10 @@ references:
email: joe@posit.co
- family-names: Tan
given-names: Xianying
- family-names: Aden-Buie
given-names: Garrick
email: garrick@posit.co
orcid: https://orcid.org/0000-0002-7111-0077
year: '2025'
doi: 10.32614/CRAN.package.DT
- type: software
@ -480,6 +492,10 @@ references:
given-names: Brenton M.
email: brenton@wiernik.org
orcid: https://orcid.org/0000-0001-9560-6336
- family-names: Thériault
given-names: Rémi
email: remi.theriault@mail.mcgill.ca
orcid: https://orcid.org/0000-0003-4315-6788
- family-names: Waggoner
given-names: Philip
email: philip.waggoner@gmail.com
@ -659,7 +675,7 @@ references:
authors:
- family-names: Wickham
given-names: Hadley
email: h.wickham@gmail.com
email: hadley@posit.co
year: '2025'
doi: 10.32614/CRAN.package.reshape2
- type: software
@ -999,6 +1015,9 @@ references:
- family-names: Lenth
given-names: Russell V.
email: russell-lenth@uiowa.edu
- family-names: Piaskowski
given-names: Julia
email: julia.piask@gmail.com
year: '2025'
doi: 10.32614/CRAN.package.emmeans
- type: software
@ -1111,6 +1130,10 @@ references:
- family-names: Walthert
given-names: Lorenz
email: lorenz.walthert@icloud.com
- family-names: Patil
given-names: Indrajeet
email: patilindrajeet.science@gmail.com
orcid: https://orcid.org/0000-0003-1995-6531
year: '2025'
doi: 10.32614/CRAN.package.styler
- type: software
@ -1128,7 +1151,7 @@ references:
given-names: Winston
- family-names: Bryan
given-names: Jennifer
email: jenny@rstudio.com
email: jenny@posit.co
orcid: https://orcid.org/0000-0002-6983-2759
year: '2025'
doi: 10.32614/CRAN.package.devtools

View file

@ -1,6 +1,6 @@
Package: FreesearchR
Title: Easy data analysis for clinicians
Version: 25.12.2
Version: 25.12.3
Authors@R: c(
person("Andreas Gammelgaard", "Damsbo",email="agdamsbo@clin.au.dk", role = c("aut", "cre"),
comment = c(ORCID = "0000-0002-7559-1154")),
@ -11,7 +11,7 @@ Description: Easily evaluate and analyse clinical health data in your browser, e
License: AGPL (>= 3)
Encoding: UTF-8
Roxygen: list(markdown = TRUE)
RoxygenNote: 7.3.2
RoxygenNote: 7.3.3
Imports:
assertthat,
bslib,

View file

@ -99,6 +99,7 @@ export(merge_expression)
export(merge_long)
export(missing_fraction)
export(missings_apex_plot)
export(missings_logic_across)
export(missings_validate)
export(modal_create_column)
export(modal_cut_variable)

View file

@ -1,3 +1,7 @@
# FreesearchR 25.12.3
*NEW* Extended missingness evaluation to include two different approaches. Docs will catch up and video tutorials are coming.
# FreesearchR 25.12.2
*FIX* Fixed hanging interface when splitting strings.

View file

@ -1 +1 @@
app_version <- function()'25.12.2'
app_version <- function()'25.12.3'

View file

@ -20,8 +20,18 @@
#' @importFrom shiny selectizeInput
#' @export
#'
columnSelectInput <- function(inputId, label, data, selected = "", ...,
col_subset = NULL, placeholder = "", onInitialize, none_label="No variable selected",maxItems=NULL) {
columnSelectInput <- function(
inputId,
label,
data,
selected = "",
...,
col_subset = NULL,
placeholder = "",
onInitialize,
none_label = "No variable selected",
maxItems = NULL
) {
datar <- if (is.reactive(data)) data else reactive(data)
col_subsetr <- if (is.reactive(col_subset)) col_subset else reactive(col_subset)
@ -41,8 +51,8 @@ columnSelectInput <- function(inputId, label, data, selected = "", ...,
)
}, col = names(datar()))
if (!"none" %in% names(datar())){
labels <- c("none"=list(sprintf('\n {\n \"name\": \"none\",\n \"label\": \"%s\",\n \"dataclass\": \"\",\n \"datatype\": \"\"\n }',none_label)),labels)
if (!"none" %in% names(datar())) {
labels <- c("none" = list(sprintf('\n {\n \"name\": \"none\",\n \"label\": \"%s\",\n \"dataclass\": \"\",\n \"datatype\": \"\"\n }', none_label)), labels)
choices <- setNames(names(labels), labels)
choices <- choices[match(if (length(col_subsetr()) == 0 || isTRUE(col_subsetr() == "")) names(datar()) else col_subsetr(), choices)]
} else {
@ -86,7 +96,7 @@ columnSelectInput <- function(inputId, label, data, selected = "", ...,
'</div>';
}
}")),
if (!is.null(maxItems)) list(maxItems=maxItems)
if (!is.null(maxItems)) list(maxItems = maxItems)
)
)
}
@ -107,31 +117,31 @@ columnSelectInput <- function(inputId, label, data, selected = "", ...,
#'
#' @examples
#' if (shiny::interactive()) {
#' shinyApp(
#' ui = fluidPage(
#' shiny::uiOutput("select"),
#' tableOutput("data")
#' ),
#' server = function(input, output) {
#' output$select <- shiny::renderUI({
#' vectorSelectInput(
#' inputId = "variable", label = "Variable:",
#' data = c(
#' "Cylinders" = "cyl",
#' "Transmission" = "am",
#' "Gears" = "gear"
#' shinyApp(
#' ui = fluidPage(
#' shiny::uiOutput("select"),
#' tableOutput("data")
#' ),
#' server = function(input, output) {
#' output$select <- shiny::renderUI({
#' vectorSelectInput(
#' inputId = "variable", label = "Variable:",
#' data = c(
#' "Cylinders" = "cyl",
#' "Transmission" = "am",
#' "Gears" = "gear"
#' )
#' )
#' )
#' })
#' })
#'
#' output$data <- renderTable(
#' {
#' mtcars[, c("mpg", input$variable), drop = FALSE]
#' },
#' rownames = TRUE
#' )
#' }
#' )
#' output$data <- renderTable(
#' {
#' mtcars[, c("mpg", input$variable), drop = FALSE]
#' },
#' rownames = TRUE
#' )
#' }
#' )
#' }
vectorSelectInput <- function(inputId,
label,
@ -184,5 +194,3 @@ vectorSelectInput <- function(inputId,
)
)
}

View file

@ -709,7 +709,7 @@ create_plot <- function(data, type, pri, sec, ter = NULL, ...) {
out
}
#' Print label, and if missing print variable name
#' Print label, and if missing print variable name for plots
#'
#' @param data vector or data frame
#' @param var variable name. Optional.

View file

@ -1 +1 @@
hosted_version <- function()'v25.12.2-251203'
hosted_version <- function()'v25.12.3-251211'

View file

@ -1,18 +1,46 @@
#' Data correlations evaluation module
#'
#' @param id Module id
#' @param ... additional UI elements to show before the table overview
#'
#' @name data-missings
#' @returns Shiny ui module
#' @export
data_missings_ui <- function(id) {
data_missings_ui <- function(id, ...) {
ns <- shiny::NS(id)
shiny::tagList(
gt::gt_output(outputId = ns("missings_table"))
list(
bslib::layout_sidebar(
sidebar = bslib::sidebar(
bslib::accordion(
id = ns("acc_mis"),
open = "acc_chars",
multiple = FALSE,
bslib::accordion_panel(
value = "acc_pan_mis",
title = "Settings",
icon = bsicons::bs_icon("x-circle"),
shiny::uiOutput(ns("missings_method")),
shiny::uiOutput(ns("missings_var")),
shiny::helpText(i18n$t("Evaluate missingness by either comparing missing values across variables (optionally grouped by af categorical or dichotomous variable) or compare variables grouped by the missing status (missing or not) of an outcome variable. If there is a significant difference i the missingness, this may cause a bias in you data and should be considered carefully interpreting the data and analyses as data may not be missing at random.")),
shiny::br(),
shiny::actionButton(
inputId = ns("act_miss"),
label = i18n$t("Evaluate"),
width = "100%",
icon = shiny::icon("calculator"),
disabled = FALSE
)
)
)
),
...,
gt::gt_output(outputId = ns("missings_table"))
)
)
}
## This should really just be rebuild to only contain a function
#'
#' @param data data
@ -23,108 +51,192 @@ data_missings_ui <- function(id) {
#' @export
data_missings_server <- function(id,
data,
variable,
max_level=20,
max_level = 20,
...) {
shiny::moduleServer(
id = id,
module = function(input, output, session) {
# ns <- session$ns
ns <- session$ns
datar <- if (is.reactive(data)) data else reactive(data)
variabler <- if (is.reactive(variable)) variable else reactive(variable)
rv <- shiny::reactiveValues(
data = NULL,
table = NULL
)
rv$data <- shiny::reactive({
df_tbl <- datar()
by_var <- variabler()
## Notes
##
## Code export is still missing
## Direct table export would be nice
tryCatch(
{
out <- compare_missings(df_tbl,by_var,max_level = max_level)
},
error = function(err) {
showNotification(paste0("Error: ", err), type = "err")
}
)
shiny::observe(
output$missings_method <- shiny::renderUI({
shiny::req(data())
vectorSelectInput(
inputId = ns("missings_method"),
label = i18n$t("Select missings analysis to apply"),
choices = setNames(
c(
"predictors",
"outcome"
),
c(
i18n$t("Variables"),
i18n$t("By outcome")
)
)
)
})
)
out
})
output$missings_table <- gt::render_gt({
shiny::req(datar)
shiny::req(variabler)
if (is.null(variabler()) || variabler() == "" || !variabler() %in% names(datar())) {
tbl <- rv$data()
if (anyNA(datar())){
title <- i18n$t("No variable chosen for analysis")
shiny::observe({
output$missings_var <- shiny::renderUI({
shiny::req(datar())
shiny::req(input$missings_method)
# browser()
if (input$missings_method == "predictors") {
df <- data_type_filter(data(), type = c("categorical", "dichotomous"))
} else {
title <- i18n$t("No missing observations")
df <- datar()[apply(datar(), 2, anyNA)]
}
} else {
tbl <- rv$data()|>
gtsummary::bold_p()
title <- glue::glue(i18n$t("Missing vs non-missing observations in the variable **'{variabler()}'**"))
}
out <- tbl |>
gtsummary::as_gt() |>
gt::tab_header(title = gt::md(title))
rv$table <- out
out
columnSelectInput(
inputId = ns("missings_var"),
label = i18n$t("Select variable to stratify analysis"),
data = df,
col_subset = c("none", names(df)),
none_label = i18n$t("No variable")
)
})
})
return(reactive(rv$table))
shiny::observeEvent(
list(input$act_miss),
{
shiny::req(datar())
shiny::req(input$missings_var)
# browser()
df_tbl <- datar()
by_var <- input$missings_var
parameters <- list(
by_var = by_var,
max_level = max_level,
type = input$missings_method
)
tryCatch(
{
shiny::withProgress(message = i18n$t("Calculating. Hold tight for a moment.."), {
out <- do.call(
compare_missings,
modifyList(parameters, list(data = df_tbl))
)
})
},
error = function(err) {
showNotification(paste0("Error: ", err), type = "err")
}
)
if (is.null(input$missings_var) || input$missings_var == "" || !input$missings_var %in% names(datar()) || input$missings_var == "none") {
# if (is.null(variabler()) || variabler() == "" || !variabler() %in% names(data()) || variabler() == "none") {
# tbl <- rv$data()
if (anyNA(datar())) {
title <- i18n$t("No variable chosen for analysis")
} else {
title <- i18n$t("No missing observations")
}
} else {
## Due to reactivity, the table updates too quickly. this mitigates that issue..
if (input$missings_var == "predictors") {
title <- glue::glue(i18n$t("Missings across variables by the variable **'{input$missings_var}'**"))
} else {
title <- glue::glue(i18n$t("Missing vs non-missing observations in the variable **'{input$missings_var}'**"))
}
}
attr(out, "tbl_title") <- title
rv$data <- shiny::reactive(out)
}
)
shiny::observeEvent(
list(
# input$act_miss
rv$data
),
{
output$missings_table <- gt::render_gt({
shiny::req(rv$data)
# shiny::req(input$missings_var)
# browser()
if ("p.value" %in% names(rv$data()[["table_body"]])) {
tbl <- rv$data() |>
gtsummary::bold_p()
} else {
tbl <- rv$data()
}
out <- tbl |>
gtsummary::as_gt() |>
gt::tab_header(title = gt::md(attr(tbl, "tbl_title")))
attr(out, "strat_var") <- input$missings_var
rv$table <- out
out
})
}
)
return(shiny::reactive(rv$table))
}
)
}
missing_demo_app <- function() {
ui <- shiny::fluidPage(
shiny::actionButton(
inputId = "modal_missings",
label = "Browse data",
width = "100%",
disabled = FALSE
),
shiny::selectInput(
inputId = "missings_var",
label = "Select variable to stratify analysis", choices = c("cyl", "vs")
),
data_missings_ui("data")
ui <- do.call(
bslib::page,
c(
list(
title = i18n$t("Missings"),
icon = bsicons::bs_icon("x-circle")
),
data_missings_ui(id = "data")
)
)
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_missings_server(id = "data", data = data_demo, variable = shiny::reactive(input$missings_var))
data_missings_server(id = "data", data = data_demo)
visual_summary_server(id = "visual", data = data_demo)
# visual_summary_server(id = "visual", data = data_demo)
observeEvent(input$modal_missings, {
tryCatch(
{
modal_visual_summary(id = "visual")
},
error = function(err) {
showNotification(paste0("We encountered the following error browsing your data: ", err), type = "err")
}
)
})
# observeEvent(input$modal_missings, {
# tryCatch(
# {
# modal_visual_summary(id = "visual")
# },
# error = function(err) {
# showNotification(paste0("We encountered the following error browsing your data: ", err), type = "err")
# }
# )
# })
}
shiny::shinyApp(ui, server)
}
missing_demo_app()
# missing_demo_app()
#' Pairwise comparison of missings across covariables
#'
@ -134,24 +246,76 @@ missing_demo_app()
#' @returns gtsummary list object
#' @export
#'
compare_missings <- function(data,by_var,max_level=20){
compare_missings <- function(
data,
by_var,
max_level = 20,
type = c("predictors", "outcome")
) {
type <- match.arg(type)
if (!is.null(by_var) && by_var != "" && by_var %in% names(data)) {
data <- data |>
lapply(\(.x){
# browser()
if (is.factor(.x)){
cut_var(.x,breaks=20,type="top")
if (is.factor(.x)) {
cut_var(.x, breaks = 20, type = "top")
} else {
.x
}
}) |> dplyr::bind_cols()
}) |>
dplyr::bind_cols()
data[[by_var]] <- ifelse(is.na(data[[by_var]]), "Missing", "Non-missing")
if (type == "predictors") {
data <- missings_logic_across(data, exclude = by_var)
} else {
data[[by_var]] <- ifelse(is.na(data[[by_var]]), "Missing", "Non-missing")
}
out <- gtsummary::tbl_summary(data, by = by_var) |>
gtsummary::add_p()
} else {
if (type == "predictors") {
data <- missings_logic_across(data)
}
out <- gtsummary::tbl_summary(data)
}
out
}
#' Converting all variables to logicals by missing status
#'
#' @param data data
#' @param exclude character vector of variable names to be excluded
#'
#' @returns data frame
#' @export
#'
#' @examples
#' mtcars |> missings_logic_across("cyl")
#' ## gtsummary::trial |>
#' ## missings_logic_across() |>
#' ## gtsummary::tbl_summary()
missings_logic_across <- function(data, exclude = NULL) {
# This function includes a approach way to preserve variable labels
names(data) |>
lapply(\(.x){
# browser()
# Saving original labels
lab <- REDCapCAST::get_attr(data[[.x]], attr = "label")
if (!.x %in% exclude) {
out <- is.na(data[[.x]])
} else {
out <- data[[.x]]
}
if (!is.na(lab)) {
# Restoring original labels, if not NA
REDCapCAST::set_attr(data = out, label = lab, attr = "label", overwrite = TRUE)
} else {
out
}
}) |>
dplyr::bind_cols(.name_repair = "unique_quiet") |>
setNames(names(data))
}

Binary file not shown.

View file

@ -452,26 +452,15 @@ ui_elements <- function(selection) {
data_correlations_ui(id = "correlations", height = 600)
)
),
bslib::nav_panel(
title = i18n$t("Missings"),
icon = bsicons::bs_icon("x-circle"),
bslib::layout_sidebar(
sidebar = bslib::sidebar(
bslib::accordion(
id = "acc_mis",
open = "acc_chars",
multiple = FALSE,
bslib::accordion_panel(
value = "acc_pan_mis",
title = "Settings",
icon = bsicons::bs_icon("x-circle"),
shiny::uiOutput("missings_var"),
shiny::helpText(i18n$t("To consider if data is missing by random, choose the outcome/dependent variable (only variables with any missings are available). If there is a significant difference across other variables depending on missing observations, it may not be missing at random."))
)
)
do.call(
bslib::nav_panel,
c(
list(
title = i18n$t("Missings"),
icon = bsicons::bs_icon("x-circle")
),
validation_ui("validation_mcar"),
data_missings_ui(id = "missingness")
data_missings_ui(id = "missingness",
validation_ui("validation_mcar"))
)
)
),

View file

@ -688,7 +688,7 @@ convert_to <- function(data,
#' Get variable(s) to convert
#'
#' @param vars Output of [summary_vars()]
#' @param vars variables, output from summary_vars() function
#' @param classes_input List of inputs containing new classes
#'
#' @return a `data.table`.

View file

@ -109,6 +109,9 @@ validation_server <- function(id,
purrr::list_flatten()
} else if (length(to_validate) > 0) {
out <- make_validation_alerts(to_validate)
} else {
## Defaulting to an emptu output vector
out <- character()
}
valid_ui$x <- tagList(out)
}
@ -332,7 +335,7 @@ validation_lib <- function(name = NULL) {
"mcar" = function(x, y) {
### Placeholder for missingness validation
list(
string = i18n$t("There is a significant correlation between {n_nonmcar} variables and missing observations in the outcome variable {outcome}."),
string = i18n$t("There is a significant difference in data missingness in {n_nonmcar} {ifelse(n_nnonmcar==1,'variable','variables')} grouped by the selected outcome/grouping variable {outcome}."),
summary.fun = mcar_validate,
summary.fun.args = list(
data = x,

View file

@ -11,11 +11,11 @@
|collate |en_US.UTF-8 |
|ctype |en_US.UTF-8 |
|tz |Europe/Copenhagen |
|date |2025-12-03 |
|date |2025-12-11 |
|rstudio |2025.09.2+418 Cucumberleaf Sunflower (desktop) |
|pandoc |3.6.4 @ /opt/homebrew/bin/ (via rmarkdown) |
|quarto |1.7.30 @ /usr/local/bin/quarto |
|FreesearchR |25.12.2.251203 |
|FreesearchR |25.12.3.251211 |
--------------------------------------------------------------------------------
@ -28,189 +28,188 @@
|assertthat |0.2.1 |2019-03-21 |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) |
|bayestestR |0.17.0 |2025-08-29 |CRAN (R 4.4.1) |
|bit |4.6.0 |2025-03-06 |CRAN (R 4.4.1) |
|bit64 |4.6.0-1 |2025-01-16 |CRAN (R 4.4.1) |
|bitops |1.0-9 |2024-10-03 |CRAN (R 4.4.1) |
|boot |1.3-31 |2024-08-28 |RSPM (R 4.4.0) |
|boot |1.3-32 |2025-08-29 |CRAN (R 4.4.1) |
|brio |1.1.5 |2024-04-24 |CRAN (R 4.4.1) |
|broom |1.0.9 |2025-07-28 |CRAN (R 4.4.1) |
|broom.helpers |1.21.0 |2025-04-24 |CRAN (R 4.4.1) |
|broom |1.0.11 |2025-12-04 |CRAN (R 4.4.3) |
|broom.helpers |1.22.0 |2025-09-17 |CRAN (R 4.4.1) |
|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) |
|calendar |0.2.0 |2024-08-20 |CRAN (R 4.4.1) |
|cards |0.6.1 |2025-07-03 |CRAN (R 4.4.1) |
|cardx |0.2.5 |2025-07-03 |CRAN (R 4.4.1) |
|cards |0.7.1 |2025-12-02 |CRAN (R 4.4.3) |
|cardx |0.3.1 |2025-12-04 |CRAN (R 4.4.3) |
|caTools |1.18.3 |2024-09-04 |CRAN (R 4.4.1) |
|cellranger |1.1.0 |2016-07-27 |CRAN (R 4.4.0) |
|cffr |1.2.0 |2025-01-25 |CRAN (R 4.4.1) |
|checkmate |2.3.2 |2024-07-29 |RSPM (R 4.4.0) |
|checkmate |2.3.3 |2025-08-18 |CRAN (R 4.4.1) |
|class |7.3-23 |2025-01-01 |CRAN (R 4.4.1) |
|classInt |0.4-11 |2025-01-08 |CRAN (R 4.4.1) |
|cli |3.6.5 |2025-04-23 |CRAN (R 4.4.1) |
|cluster |2.1.8.1 |2025-03-12 |CRAN (R 4.4.1) |
|codetools |0.2-20 |2024-03-31 |CRAN (R 4.4.1) |
|colorspace |2.1-1 |2024-07-26 |CRAN (R 4.4.1) |
|colorspace |2.1-2 |2025-09-22 |CRAN (R 4.4.1) |
|commonmark |2.0.0 |2025-07-07 |CRAN (R 4.4.1) |
|crayon |1.5.3 |2024-06-20 |CRAN (R 4.4.1) |
|curl |6.4.0 |2025-06-22 |RSPM (R 4.4.0) |
|data.table |1.17.8 |2025-07-10 |CRAN (R 4.4.1) |
|datamods |1.5.3 |2024-10-02 |CRAN (R 4.4.1) |
|datawizard |1.2.0 |2025-07-17 |CRAN (R 4.4.1) |
|datawizard |1.3.0 |2025-10-11 |CRAN (R 4.4.1) |
|DEoptimR |1.1-4 |2025-07-27 |CRAN (R 4.4.1) |
|desc |1.4.3 |2023-12-10 |CRAN (R 4.4.1) |
|devtools |2.4.5 |2022-10-11 |CRAN (R 4.4.0) |
|devtools |2.4.6 |2025-10-03 |CRAN (R 4.4.1) |
|DHARMa |0.4.7 |2024-10-18 |CRAN (R 4.4.1) |
|digest |0.6.37 |2024-08-19 |CRAN (R 4.4.1) |
|digest |0.6.39 |2025-11-19 |CRAN (R 4.4.3) |
|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) |
|DT |0.34.0 |2025-09-02 |CRAN (R 4.4.1) |
|e1071 |1.7-16 |2024-09-16 |CRAN (R 4.4.1) |
|easystats |0.7.5 |2025-07-11 |CRAN (R 4.4.1) |
|ellipsis |0.3.2 |2021-04-29 |CRAN (R 4.4.1) |
|emmeans |1.11.2 |2025-07-11 |CRAN (R 4.4.1) |
|emmeans |2.0.0 |2025-10-29 |CRAN (R 4.4.1) |
|esquisse |2.1.0 |2025-02-21 |CRAN (R 4.4.1) |
|estimability |1.5.1 |2024-05-12 |CRAN (R 4.4.1) |
|eulerr |7.0.2 |2024-03-28 |CRAN (R 4.4.0) |
|evaluate |1.0.4 |2025-06-18 |RSPM (R 4.4.0) |
|eulerr |7.0.4 |2025-09-24 |CRAN (R 4.4.1) |
|evaluate |1.0.5 |2025-08-27 |CRAN (R 4.4.1) |
|farver |2.1.2 |2024-05-13 |CRAN (R 4.4.1) |
|fastmap |1.2.0 |2024-05-15 |CRAN (R 4.4.1) |
|flextable |0.9.9 |2025-05-31 |CRAN (R 4.4.1) |
|flextable |0.9.10 |2025-08-24 |CRAN (R 4.4.1) |
|fontawesome |0.5.3 |2024-11-16 |CRAN (R 4.4.1) |
|fontBitstreamVera |0.1.1 |2017-02-01 |CRAN (R 4.4.1) |
|fontLiberation |0.1.0 |2016-10-15 |CRAN (R 4.4.1) |
|fontquiver |0.2.1 |2017-02-01 |CRAN (R 4.4.0) |
|forcats |1.0.0 |2023-01-29 |RSPM (R 4.4.0) |
|forcats |1.0.1 |2025-09-25 |CRAN (R 4.4.1) |
|foreach |1.5.2 |2022-02-02 |CRAN (R 4.4.0) |
|foreign |0.8-90 |2025-03-31 |CRAN (R 4.4.1) |
|Formula |1.2-5 |2023-02-24 |CRAN (R 4.4.1) |
|FreesearchR |25.12.2 |NA |NA |
|FreesearchR |25.12.3 |NA |NA |
|fs |1.6.6 |2025-04-12 |CRAN (R 4.4.1) |
|gdtools |0.4.2 |2025-03-27 |CRAN (R 4.4.1) |
|gdtools |0.4.4 |2025-10-06 |CRAN (R 4.4.1) |
|generics |0.1.4 |2025-05-09 |CRAN (R 4.4.1) |
|ggalluvial |0.12.5 |2023-02-22 |CRAN (R 4.4.0) |
|ggcorrplot |0.1.4.1 |2023-09-05 |CRAN (R 4.4.0) |
|ggforce |0.5.0 |2025-06-18 |CRAN (R 4.4.1) |
|ggplot2 |3.5.2 |2025-04-09 |CRAN (R 4.4.1) |
|ggridges |0.5.6 |2024-01-23 |CRAN (R 4.4.0) |
|ggstats |0.10.0 |2025-07-02 |CRAN (R 4.4.1) |
|ggplot2 |4.0.1 |2025-11-14 |CRAN (R 4.4.1) |
|ggridges |0.5.7 |2025-08-27 |CRAN (R 4.4.1) |
|ggstats |0.11.0 |2025-09-15 |CRAN (R 4.4.1) |
|glue |1.8.0 |2024-09-30 |CRAN (R 4.4.1) |
|gridExtra |2.3 |2017-09-09 |CRAN (R 4.4.1) |
|gt |1.0.0 |2025-04-05 |CRAN (R 4.4.1) |
|gt |1.1.0 |2025-09-23 |CRAN (R 4.4.1) |
|gtable |0.3.6 |2024-10-25 |CRAN (R 4.4.1) |
|gtsummary |2.3.0 |2025-07-03 |CRAN (R 4.4.1) |
|gtsummary |2.5.0 |2025-12-05 |CRAN (R 4.4.3) |
|haven |2.5.5 |2025-05-30 |CRAN (R 4.4.1) |
|here |1.0.1 |2020-12-13 |CRAN (R 4.4.1) |
|Hmisc |5.2-3 |2025-03-16 |CRAN (R 4.4.1) |
|hms |1.1.3 |2023-03-21 |CRAN (R 4.4.0) |
|here |1.0.2 |2025-09-15 |CRAN (R 4.4.1) |
|Hmisc |5.2-4 |2025-10-05 |CRAN (R 4.4.1) |
|hms |1.1.4 |2025-10-17 |CRAN (R 4.4.1) |
|htmlTable |2.4.3 |2024-07-21 |CRAN (R 4.4.0) |
|htmltools |0.5.8.1 |2024-04-04 |CRAN (R 4.4.1) |
|htmltools |0.5.9 |2025-12-04 |CRAN (R 4.4.3) |
|htmlwidgets |1.6.4 |2023-12-06 |CRAN (R 4.4.0) |
|httpuv |1.6.16 |2025-04-16 |CRAN (R 4.4.1) |
|IDEAFilter |0.2.1 |2025-07-29 |CRAN (R 4.4.1) |
|insight |1.4.0 |2025-08-18 |CRAN (R 4.4.1) |
|insight |1.4.4 |2025-12-06 |CRAN (R 4.4.3) |
|iterators |1.0.14 |2022-02-05 |CRAN (R 4.4.1) |
|jquerylib |0.1.4 |2021-04-26 |CRAN (R 4.4.0) |
|jsonlite |2.0.0 |2025-03-27 |CRAN (R 4.4.1) |
|jsonvalidate |1.5.0 |2025-02-07 |CRAN (R 4.4.1) |
|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 |RSPM (R 4.4.0) |
|later |1.4.4 |2025-08-27 |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) |
|lme4 |1.1-37 |2025-03-26 |CRAN (R 4.4.1) |
|litedown |0.8 |2025-11-02 |CRAN (R 4.4.1) |
|lme4 |1.1-38 |2025-12-02 |CRAN (R 4.4.3) |
|lubridate |1.9.4 |2024-12-08 |CRAN (R 4.4.1) |
|magrittr |2.0.3 |2022-03-30 |RSPM (R 4.4.0) |
|magrittr |2.0.4 |2025-09-12 |CRAN (R 4.4.1) |
|markdown |2.0 |2025-03-23 |CRAN (R 4.4.1) |
|MASS |7.3-65 |2025-02-28 |CRAN (R 4.4.1) |
|Matrix |1.7-3 |2025-03-11 |RSPM (R 4.4.0) |
|Matrix |1.7-4 |2025-08-28 |CRAN (R 4.4.1) |
|memoise |2.0.1 |2021-11-26 |CRAN (R 4.4.0) |
|mime |0.13 |2025-03-17 |CRAN (R 4.4.1) |
|miniUI |0.1.2 |2025-04-17 |CRAN (R 4.4.1) |
|minqa |1.2.8 |2024-08-17 |CRAN (R 4.4.1) |
|mvtnorm |1.3-3 |2025-01-10 |CRAN (R 4.4.1) |
|NHANES |2.1.0 |2015-07-02 |CRAN (R 4.4.0) |
|nlme |3.1-168 |2025-03-31 |CRAN (R 4.4.1) |
|nloptr |2.2.1 |2025-03-17 |CRAN (R 4.4.1) |
|nnet |7.3-20 |2025-01-01 |CRAN (R 4.4.1) |
|officer |0.6.10 |2025-05-30 |CRAN (R 4.4.1) |
|officer |0.7.2 |2025-12-04 |CRAN (R 4.4.3) |
|opdisDownsampling |1.0.1 |2024-04-15 |CRAN (R 4.4.0) |
|openssl |2.3.3 |2025-05-26 |CRAN (R 4.4.1) |
|openxlsx2 |1.18 |2025-07-29 |CRAN (R 4.4.1) |
|parameters |0.27.0 |2025-07-09 |CRAN (R 4.4.1) |
|patchwork |1.3.1 |2025-06-21 |RSPM (R 4.4.0) |
|openssl |2.3.4 |2025-09-30 |CRAN (R 4.4.1) |
|openxlsx2 |1.22 |2025-12-07 |CRAN (R 4.4.3) |
|otel |0.2.0 |2025-08-29 |CRAN (R 4.4.1) |
|parameters |0.28.3 |2025-11-25 |CRAN (R 4.4.3) |
|patchwork |1.3.2 |2025-08-25 |CRAN (R 4.4.1) |
|pbmcapply |1.5.1 |2022-04-28 |CRAN (R 4.4.1) |
|performance |0.15.0 |2025-07-10 |CRAN (R 4.4.1) |
|performance |0.15.3 |2025-12-01 |CRAN (R 4.4.3) |
|phosphoricons |0.2.1 |2024-04-08 |CRAN (R 4.4.0) |
|pillar |1.11.0 |2025-07-04 |RSPM (R 4.4.0) |
|pillar |1.11.1 |2025-09-17 |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) |
|pkgload |1.4.0 |2024-06-28 |RSPM (R 4.4.0) |
|pkgload |1.4.1 |2025-09-23 |CRAN (R 4.4.1) |
|plyr |1.8.9 |2023-10-02 |CRAN (R 4.4.1) |
|polyclip |1.10-7 |2024-07-23 |CRAN (R 4.4.1) |
|pracma |2.4.4 |2023-11-10 |CRAN (R 4.4.1) |
|pracma |2.4.6 |2025-10-22 |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) |
|promises |1.3.3 |2025-05-29 |CRAN (R 4.4.1) |
|promises |1.5.0 |2025-11-01 |CRAN (R 4.4.1) |
|proxy |0.4-27 |2022-06-09 |CRAN (R 4.4.1) |
|ps |1.9.1 |2025-04-12 |CRAN (R 4.4.1) |
|purrr |1.1.0 |2025-07-10 |CRAN (R 4.4.1) |
|purrr |1.2.0 |2025-11-04 |CRAN (R 4.4.1) |
|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) |
|qqplotr |0.0.7 |2025-09-05 |CRAN (R 4.4.1) |
|quarto |1.5.1 |2025-09-04 |CRAN (R 4.4.1) |
|R.cache |0.17.0 |2025-05-02 |CRAN (R 4.4.1) |
|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 |RSPM (R 4.4.0) |
|ragg |1.5.0 |2025-09-02 |CRAN (R 4.4.1) |
|rankinPlot |1.1.0 |2023-01-30 |CRAN (R 4.4.0) |
|rappdirs |0.3.3 |2021-01-31 |CRAN (R 4.4.1) |
|rbibutils |2.3 |2024-10-04 |CRAN (R 4.4.1) |
|rbibutils |2.4 |2025-11-07 |CRAN (R 4.4.1) |
|RColorBrewer |1.1-3 |2022-04-03 |CRAN (R 4.4.1) |
|Rcpp |1.1.0 |2025-07-02 |CRAN (R 4.4.1) |
|RcppArmadillo |14.6.0-1 |2025-07-02 |CRAN (R 4.4.1) |
|RcppArmadillo |15.2.2-1 |2025-11-22 |CRAN (R 4.4.3) |
|Rdpack |2.6.4 |2025-04-09 |CRAN (R 4.4.1) |
|reactable |0.4.4 |2023-03-12 |CRAN (R 4.4.0) |
|reactable |0.4.5 |2025-12-01 |CRAN (R 4.4.3) |
|readODS |2.3.2 |2025-01-13 |CRAN (R 4.4.1) |
|readr |2.1.5 |2024-01-10 |CRAN (R 4.4.0) |
|readr |2.1.6 |2025-11-14 |CRAN (R 4.4.3) |
|readxl |1.4.5 |2025-03-07 |CRAN (R 4.4.1) |
|REDCapCAST |25.3.2 |2025-03-10 |CRAN (R 4.4.1) |
|REDCapR |1.5.0 |2025-07-28 |CRAN (R 4.4.1) |
|reformulas |0.4.1 |2025-04-30 |CRAN (R 4.4.1) |
|REDCapR |1.6.0 |2025-10-08 |CRAN (R 4.4.1) |
|reformulas |0.4.2 |2025-10-28 |CRAN (R 4.4.1) |
|remotes |2.5.0 |2024-03-17 |CRAN (R 4.4.1) |
|rempsyc |0.1.9 |2025-02-01 |CRAN (R 4.4.1) |
|rempsyc |0.2.0 |2025-09-15 |CRAN (R 4.4.1) |
|renv |1.1.5 |2025-07-24 |CRAN (R 4.4.1) |
|reshape2 |1.4.4 |2020-04-09 |CRAN (R 4.4.0) |
|rio |1.2.3 |2024-09-25 |CRAN (R 4.4.1) |
|reshape2 |1.4.5 |2025-11-12 |CRAN (R 4.4.1) |
|rio |1.2.4 |2025-09-26 |CRAN (R 4.4.1) |
|rlang |1.1.6 |2025-04-11 |CRAN (R 4.4.1) |
|rmarkdown |2.29 |2024-11-04 |CRAN (R 4.4.1) |
|robustbase |0.99-4-1 |2024-09-27 |CRAN (R 4.4.1) |
|roxygen2 |7.3.2 |2024-06-28 |RSPM (R 4.4.0) |
|rmarkdown |2.30 |2025-09-28 |CRAN (R 4.4.1) |
|robustbase |0.99-6 |2025-09-04 |CRAN (R 4.4.1) |
|roxygen2 |7.3.3 |2025-09-03 |CRAN (R 4.4.1) |
|rpart |4.1.24 |2025-01-07 |CRAN (R 4.4.1) |
|rprojroot |2.1.0 |2025-07-12 |RSPM (R 4.4.0) |
|rsconnect |1.5.0 |2025-06-26 |CRAN (R 4.4.1) |
|rprojroot |2.1.1 |2025-08-26 |CRAN (R 4.4.1) |
|rsconnect |1.7.0 |2025-12-06 |CRAN (R 4.4.3) |
|rstudioapi |0.17.1 |2024-10-22 |CRAN (R 4.4.1) |
|S7 |0.2.1 |2025-11-14 |CRAN (R 4.4.3) |
|sass |0.4.10 |2025-04-11 |CRAN (R 4.4.1) |
|scales |1.4.0 |2025-04-24 |CRAN (R 4.4.1) |
|see |0.11.0 |2025-03-11 |CRAN (R 4.4.1) |
|see |0.12.0 |2025-09-14 |CRAN (R 4.4.1) |
|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 |1.12.1 |2025-12-09 |CRAN (R 4.4.1) |
|shiny.i18n |0.3.0 |2023-01-16 |CRAN (R 4.4.0) |
|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) |
|shinyWidgets |0.9.0 |2025-02-21 |CRAN (R 4.4.1) |
|sourcetools |0.1.7-1 |2023-02-01 |CRAN (R 4.4.1) |
|stringi |1.8.7 |2025-03-27 |CRAN (R 4.4.1) |
|stringr |1.5.1 |2023-11-14 |RSPM (R 4.4.0) |
|stringr |1.6.0 |2025-11-04 |CRAN (R 4.4.1) |
|stRoke |25.9.2 |2025-09-30 |CRAN (R 4.4.1) |
|styler |1.10.3 |2024-04-07 |CRAN (R 4.4.0) |
|systemfonts |1.2.3 |2025-04-30 |CRAN (R 4.4.1) |
|testthat |3.2.3 |2025-01-13 |CRAN (R 4.4.1) |
|textshaping |1.0.1 |2025-05-01 |RSPM (R 4.4.0) |
|thematic |0.1.7 |2025-06-19 |CRAN (R 4.4.1) |
|styler |1.11.0 |2025-10-13 |CRAN (R 4.4.1) |
|systemfonts |1.3.1 |2025-10-01 |CRAN (R 4.4.1) |
|testthat |3.3.1 |2025-11-25 |CRAN (R 4.4.3) |
|textshaping |1.0.4 |2025-10-10 |CRAN (R 4.4.1) |
|thematic |0.1.8 |2025-09-29 |CRAN (R 4.4.1) |
|tibble |3.3.0 |2025-06-08 |CRAN (R 4.4.1) |
|tidyr |1.3.1 |2024-01-24 |CRAN (R 4.4.1) |
|tidyselect |1.2.1 |2024-03-11 |CRAN (R 4.4.0) |
@ -219,17 +218,15 @@
|tweenr |2.0.3 |2024-02-26 |CRAN (R 4.4.0) |
|twosamples |2.0.1 |2023-06-23 |CRAN (R 4.4.1) |
|tzdb |0.5.0 |2025-03-15 |CRAN (R 4.4.1) |
|urlchecker |1.0.1 |2021-11-30 |CRAN (R 4.4.1) |
|usethis |3.1.0 |2024-11-26 |RSPM (R 4.4.0) |
|usethis |3.2.1 |2025-09-06 |CRAN (R 4.4.1) |
|utf8 |1.2.6 |2025-06-08 |CRAN (R 4.4.1) |
|uuid |1.2-1 |2024-07-29 |CRAN (R 4.4.1) |
|V8 |6.0.6 |2025-08-18 |CRAN (R 4.4.1) |
|vctrs |0.6.5 |2023-12-01 |CRAN (R 4.4.0) |
|vroom |1.6.5 |2023-12-05 |CRAN (R 4.4.0) |
|vroom |1.6.7 |2025-11-28 |CRAN (R 4.4.3) |
|withr |3.0.2 |2024-10-28 |CRAN (R 4.4.1) |
|writexl |1.5.4 |2025-04-15 |CRAN (R 4.4.1) |
|xfun |0.52 |2025-04-02 |RSPM (R 4.4.0) |
|xml2 |1.3.8 |2025-03-14 |RSPM (R 4.4.0) |
|xfun |0.54 |2025-10-30 |CRAN (R 4.4.1) |
|xml2 |1.5.1 |2025-12-01 |CRAN (R 4.4.3) |
|xtable |1.8-4 |2019-04-21 |CRAN (R 4.4.1) |
|yaml |2.3.10 |2024-07-26 |CRAN (R 4.4.1) |
|yaml |2.3.11 |2025-11-28 |CRAN (R 4.4.3) |
|zip |2.3.3 |2025-05-13 |CRAN (R 4.4.1) |

View file

@ -152,8 +152,6 @@
"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}.","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"
@ -250,7 +248,6 @@
"Generating the report. Hold on for a moment..","Opretter rapporten. Vent et øjeblik.."
"We encountered the following error showing missingness:","Under analysen af manglende observationer opstod følgende fejl:"
"We encountered the following error browsing your data:","I forsøget på at vise en dataoversigt opstod følgende fejl:"
"To consider if data is missing by random, choose the outcome/dependent variable (only variables with any missings are available). If there is a significant difference across other variables depending on missing observations, it may not be missing at random.","Vælg svarvariablen, for at få hjælp til at vurdere om manglende observationer manglende tilfældigt eller ej (kun variabler med manglende data kan vælges). Hvis der er statistisk signifikant forskel mellem nogle af de øvrige variabler i forhold til manglende data i den valgte variable kan det være et udtryk for at data ikke mangler tilfældigt."
"Choose a name for the column to be created or modified, then enter an expression before clicking on the button below to create the variable, or cancel to exit without saving anything.","Vælg et navn til den nye variabel, skriv din formel og tryk så på knappen for at gemme variablen, eller annuler for at lukke uden at gemme."
"Please fill in web address and API token, then press 'Connect'.","Udfyld serveradresse og API-nøgle, og tryk så 'Fobind'."
"Other","Other"
@ -299,3 +296,11 @@
"Words","Words"
"Shorten to first letters","Shorten to first letters"
"Shorten to first words","Shorten to first words"
"Select missings analysis to apply","Select missings analysis to apply"
"Variables","Variables"
"By outcome","By outcome"
"Missings across variables by the variable **'{input$missings_var}'**","Missings across variables by the variable **'{input$missings_var}'**"
"Missing vs non-missing observations in the variable **'{input$missings_var}'**","Missing vs non-missing observations in the variable **'{input$missings_var}'**"
"Evaluate missingness by either comparing missing values across variables (optionally grouped by af categorical or dichotomous variable) or compare variables grouped by the missing status (missing or not) of an outcome variable. If there is a significant difference i the missingness, this may cause a bias in you data and should be considered carefully interpreting the data and analyses as data may not be missing at random.","Evaluate missingness by either comparing missing values across variables (optionally grouped by af categorical or dichotomous variable) or compare variables grouped by the missing status (missing or not) of an outcome variable. If there is a significant difference i the missingness, this may cause a bias in you data and should be considered carefully interpreting the data and analyses as data may not be missing at random."
"Calculating. Hold tight for a moment..","Calculating. Hold tight for a moment.."
"There is a significant difference in data missingness in {n_nonmcar} {ifelse(n_nnonmcar==1,'variable','variables')} grouped by the selected outcome/grouping variable {outcome}.","There is a significant difference in data missingness in {n_nonmcar} {ifelse(n_nnonmcar==1,'variable','variables')} grouped by the selected outcome/grouping variable {outcome}."

1 en da
152 We encountered the following error creating your report: Følgende fejl opstod, da rapporten blev dannet:
153 No variable chosen for analysis Ingen variabel er valgt til analysen
154 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}. Der er en betydelig korrelation blandt {n_nonmcar} variabler sammenlignet efter manglende observationer i {outcome}.
155 There is a total of {p_miss} % missing observations. Der er i alt {p_miss} % manglende observationer.
156 Median: Median:
157 Restore original data Gendan originale data
248 Generating the report. Hold on for a moment.. Opretter rapporten. Vent et øjeblik..
249 We encountered the following error showing missingness: Under analysen af manglende observationer opstod følgende fejl:
250 We encountered the following error browsing your data: I forsøget på at vise en dataoversigt opstod følgende fejl:
To consider if data is missing by random, choose the outcome/dependent variable (only variables with any missings are available). If there is a significant difference across other variables depending on missing observations, it may not be missing at random. Vælg svarvariablen, for at få hjælp til at vurdere om manglende observationer manglende tilfældigt eller ej (kun variabler med manglende data kan vælges). Hvis der er statistisk signifikant forskel mellem nogle af de øvrige variabler i forhold til manglende data i den valgte variable kan det være et udtryk for at data ikke mangler tilfældigt.
251 Choose a name for the column to be created or modified, then enter an expression before clicking on the button below to create the variable, or cancel to exit without saving anything. Vælg et navn til den nye variabel, skriv din formel og tryk så på knappen for at gemme variablen, eller annuler for at lukke uden at gemme.
252 Please fill in web address and API token, then press 'Connect'. Udfyld serveradresse og API-nøgle, og tryk så 'Fobind'.
253 Other Other
296 Words Words
297 Shorten to first letters Shorten to first letters
298 Shorten to first words Shorten to first words
299 Select missings analysis to apply Select missings analysis to apply
300 Variables Variables
301 By outcome By outcome
302 Missings across variables by the variable **'{input$missings_var}'** Missings across variables by the variable **'{input$missings_var}'**
303 Missing vs non-missing observations in the variable **'{input$missings_var}'** Missing vs non-missing observations in the variable **'{input$missings_var}'**
304 Evaluate missingness by either comparing missing values across variables (optionally grouped by af categorical or dichotomous variable) or compare variables grouped by the missing status (missing or not) of an outcome variable. If there is a significant difference i the missingness, this may cause a bias in you data and should be considered carefully interpreting the data and analyses as data may not be missing at random. Evaluate missingness by either comparing missing values across variables (optionally grouped by af categorical or dichotomous variable) or compare variables grouped by the missing status (missing or not) of an outcome variable. If there is a significant difference i the missingness, this may cause a bias in you data and should be considered carefully interpreting the data and analyses as data may not be missing at random.
305 Calculating. Hold tight for a moment.. Calculating. Hold tight for a moment..
306 There is a significant difference in data missingness in {n_nonmcar} {ifelse(n_nnonmcar==1,'variable','variables')} grouped by the selected outcome/grouping variable {outcome}. There is a significant difference in data missingness in {n_nonmcar} {ifelse(n_nnonmcar==1,'variable','variables')} grouped by the selected outcome/grouping variable {outcome}.

View file

@ -105,7 +105,6 @@
"First five rows are shown below:","First five rows are shown below:"
"No variable chosen for analysis","No variable chosen for analysis"
"No missing observations","No missing observations"
"Missing vs non-missing observations in the variable **'{variabler()}'**","Missing vs non-missing observations in the variable **'{variabler()}'**"
"Grouped by {get_label(data,ter)}","Grouped by {get_label(data,ter)}"
"Import data from REDCap","Import data from REDCap"
"REDCap server","REDCap server"
@ -207,7 +206,6 @@
"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 (only variables with any missings are available). If there is a significant difference across other variables depending on missing observations, it may not be missing at random.","To consider if data is missing by random, choose the outcome/dependent variable (only variables with any missings are available). If there is a significant difference across other variables depending on missing observations, it may not be missing at random."
"Visuals","Visuals"
"Analysis validation","Analysis validation"
"Report","Report"
@ -230,7 +228,6 @@
"You removed {p_out} % of observations.","You removed {p_out} % of observations."
"You removed {p_out} % of variables.","You removed {p_out} % of variables."
"There is a total of {p_miss} % missing observations.","There is a total of {p_miss} % missing observations."
"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}."
"Data includes {n_pairs} pairs of highly correlated variables.","Data includes {n_pairs} pairs of highly correlated variables."
"Class","Class"
"Observations","Observations"
@ -299,3 +296,11 @@
"Words","Words"
"Shorten to first letters","Shorten to first letters"
"Shorten to first words","Shorten to first words"
"Select missings analysis to apply","Select missings analysis to apply"
"Variables","Variables"
"By outcome","By outcome"
"Missings across variables by the variable **'{input$missings_var}'**","Missings across variables by the variable **'{input$missings_var}'**"
"Missing vs non-missing observations in the variable **'{input$missings_var}'**","Missing vs non-missing observations in the variable **'{input$missings_var}'**"
"Evaluate missingness by either comparing missing values across variables (optionally grouped by af categorical or dichotomous variable) or compare variables grouped by the missing status (missing or not) of an outcome variable. If there is a significant difference i the missingness, this may cause a bias in you data and should be considered carefully interpreting the data and analyses as data may not be missing at random.","Evaluate missingness by either comparing missing values across variables (optionally grouped by af categorical or dichotomous variable) or compare variables grouped by the missing status (missing or not) of an outcome variable. If there is a significant difference i the missingness, this may cause a bias in you data and should be considered carefully interpreting the data and analyses as data may not be missing at random."
"Calculating. Hold tight for a moment..","Calculating. Hold tight for a moment.."
"There is a significant difference in data missingness in {n_nonmcar} {ifelse(n_nnonmcar==1,'variable','variables')} grouped by the selected outcome/grouping variable {outcome}.","There is a significant difference in data missingness in {n_nonmcar} {ifelse(n_nnonmcar==1,'variable','variables')} grouped by the selected outcome/grouping variable {outcome}."

1 en de
105 First five rows are shown below: First five rows are shown below:
106 No variable chosen for analysis No variable chosen for analysis
107 No missing observations No missing observations
Missing vs non-missing observations in the variable **'{variabler()}'** Missing vs non-missing observations in the variable **'{variabler()}'**
108 Grouped by {get_label(data,ter)} Grouped by {get_label(data,ter)}
109 Import data from REDCap Import data from REDCap
110 REDCap server REDCap server
206 Correlation cut-off Correlation cut-off
207 Set the cut-off for considered 'highly correlated'. Set the cut-off for considered 'highly correlated'.
208 Missings Missings
To consider if data is missing by random, choose the outcome/dependent variable (only variables with any missings are available). If there is a significant difference across other variables depending on missing observations, it may not be missing at random. To consider if data is missing by random, choose the outcome/dependent variable (only variables with any missings are available). If there is a significant difference across other variables depending on missing observations, it may not be missing at random.
209 Visuals Visuals
210 Analysis validation Analysis validation
211 Report Report
228 You removed {p_out} % of observations. You removed {p_out} % of observations.
229 You removed {p_out} % of variables. You removed {p_out} % of variables.
230 There is a total of {p_miss} % missing observations. There is a total of {p_miss} % missing observations.
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}.
231 Data includes {n_pairs} pairs of highly correlated variables. Data includes {n_pairs} pairs of highly correlated variables.
232 Class Class
233 Observations Observations
296 Words Words
297 Shorten to first letters Shorten to first letters
298 Shorten to first words Shorten to first words
299 Select missings analysis to apply Select missings analysis to apply
300 Variables Variables
301 By outcome By outcome
302 Missings across variables by the variable **'{input$missings_var}'** Missings across variables by the variable **'{input$missings_var}'**
303 Missing vs non-missing observations in the variable **'{input$missings_var}'** Missing vs non-missing observations in the variable **'{input$missings_var}'**
304 Evaluate missingness by either comparing missing values across variables (optionally grouped by af categorical or dichotomous variable) or compare variables grouped by the missing status (missing or not) of an outcome variable. If there is a significant difference i the missingness, this may cause a bias in you data and should be considered carefully interpreting the data and analyses as data may not be missing at random. Evaluate missingness by either comparing missing values across variables (optionally grouped by af categorical or dichotomous variable) or compare variables grouped by the missing status (missing or not) of an outcome variable. If there is a significant difference i the missingness, this may cause a bias in you data and should be considered carefully interpreting the data and analyses as data may not be missing at random.
305 Calculating. Hold tight for a moment.. Calculating. Hold tight for a moment..
306 There is a significant difference in data missingness in {n_nonmcar} {ifelse(n_nnonmcar==1,'variable','variables')} grouped by the selected outcome/grouping variable {outcome}. There is a significant difference in data missingness in {n_nonmcar} {ifelse(n_nnonmcar==1,'variable','variables')} grouped by the selected outcome/grouping variable {outcome}.

View file

@ -105,7 +105,6 @@
"First five rows are shown below:","First five rows are shown below:"
"No variable chosen for analysis","No variable chosen for analysis"
"No missing observations","No missing observations"
"Missing vs non-missing observations in the variable **'{variabler()}'**","Missing vs non-missing observations in the variable **'{variabler()}'**"
"Grouped by {get_label(data,ter)}","Grouped by {get_label(data,ter)}"
"Import data from REDCap","Import data from REDCap"
"REDCap server","REDCap server"
@ -207,7 +206,6 @@
"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 (only variables with any missings are available). If there is a significant difference across other variables depending on missing observations, it may not be missing at random.","To consider if data is missing by random, choose the outcome/dependent variable (only variables with any missings are available). If there is a significant difference across other variables depending on missing observations, it may not be missing at random."
"Visuals","Visuals"
"Analysis validation","Analysis validation"
"Report","Report"
@ -230,7 +228,6 @@
"You removed {p_out} % of observations.","You removed {p_out} % of observations."
"You removed {p_out} % of variables.","You removed {p_out} % of variables."
"There is a total of {p_miss} % missing observations.","There is a total of {p_miss} % missing observations."
"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}."
"Data includes {n_pairs} pairs of highly correlated variables.","Data includes {n_pairs} pairs of highly correlated variables."
"Class","Class"
"Observations","Observations"
@ -299,3 +296,11 @@
"Words","Words"
"Shorten to first letters","Shorten to first letters"
"Shorten to first words","Shorten to first words"
"Select missings analysis to apply","Select missings analysis to apply"
"Variables","Variables"
"By outcome","By outcome"
"Missings across variables by the variable **'{input$missings_var}'**","Missings across variables by the variable **'{input$missings_var}'**"
"Missing vs non-missing observations in the variable **'{input$missings_var}'**","Missing vs non-missing observations in the variable **'{input$missings_var}'**"
"Evaluate missingness by either comparing missing values across variables (optionally grouped by af categorical or dichotomous variable) or compare variables grouped by the missing status (missing or not) of an outcome variable. If there is a significant difference i the missingness, this may cause a bias in you data and should be considered carefully interpreting the data and analyses as data may not be missing at random.","Evaluate missingness by either comparing missing values across variables (optionally grouped by af categorical or dichotomous variable) or compare variables grouped by the missing status (missing or not) of an outcome variable. If there is a significant difference i the missingness, this may cause a bias in you data and should be considered carefully interpreting the data and analyses as data may not be missing at random."
"Calculating. Hold tight for a moment..","Calculating. Hold tight for a moment.."
"There is a significant difference in data missingness in {n_nonmcar} {ifelse(n_nnonmcar==1,'variable','variables')} grouped by the selected outcome/grouping variable {outcome}.","There is a significant difference in data missingness in {n_nonmcar} {ifelse(n_nnonmcar==1,'variable','variables')} grouped by the selected outcome/grouping variable {outcome}."

1 en sv
105 First five rows are shown below: First five rows are shown below:
106 No variable chosen for analysis No variable chosen for analysis
107 No missing observations No missing observations
Missing vs non-missing observations in the variable **'{variabler()}'** Missing vs non-missing observations in the variable **'{variabler()}'**
108 Grouped by {get_label(data,ter)} Grouped by {get_label(data,ter)}
109 Import data from REDCap Import data from REDCap
110 REDCap server REDCap server
206 Correlation cut-off Correlation cut-off
207 Set the cut-off for considered 'highly correlated'. Set the cut-off for considered 'highly correlated'.
208 Missings Missings
To consider if data is missing by random, choose the outcome/dependent variable (only variables with any missings are available). If there is a significant difference across other variables depending on missing observations, it may not be missing at random. To consider if data is missing by random, choose the outcome/dependent variable (only variables with any missings are available). If there is a significant difference across other variables depending on missing observations, it may not be missing at random.
209 Visuals Visuals
210 Analysis validation Analysis validation
211 Report Report
228 You removed {p_out} % of observations. You removed {p_out} % of observations.
229 You removed {p_out} % of variables. You removed {p_out} % of variables.
230 There is a total of {p_miss} % missing observations. There is a total of {p_miss} % missing observations.
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}.
231 Data includes {n_pairs} pairs of highly correlated variables. Data includes {n_pairs} pairs of highly correlated variables.
232 Class Class
233 Observations Observations
296 Words Words
297 Shorten to first letters Shorten to first letters
298 Shorten to first words Shorten to first words
299 Select missings analysis to apply Select missings analysis to apply
300 Variables Variables
301 By outcome By outcome
302 Missings across variables by the variable **'{input$missings_var}'** Missings across variables by the variable **'{input$missings_var}'**
303 Missing vs non-missing observations in the variable **'{input$missings_var}'** Missing vs non-missing observations in the variable **'{input$missings_var}'**
304 Evaluate missingness by either comparing missing values across variables (optionally grouped by af categorical or dichotomous variable) or compare variables grouped by the missing status (missing or not) of an outcome variable. If there is a significant difference i the missingness, this may cause a bias in you data and should be considered carefully interpreting the data and analyses as data may not be missing at random. Evaluate missingness by either comparing missing values across variables (optionally grouped by af categorical or dichotomous variable) or compare variables grouped by the missing status (missing or not) of an outcome variable. If there is a significant difference i the missingness, this may cause a bias in you data and should be considered carefully interpreting the data and analyses as data may not be missing at random.
305 Calculating. Hold tight for a moment.. Calculating. Hold tight for a moment..
306 There is a significant difference in data missingness in {n_nonmcar} {ifelse(n_nnonmcar==1,'variable','variables')} grouped by the selected outcome/grouping variable {outcome}. There is a significant difference in data missingness in {n_nonmcar} {ifelse(n_nnonmcar==1,'variable','variables')} grouped by the selected outcome/grouping variable {outcome}.

View file

@ -152,8 +152,6 @@
"We encountered the following error creating your report:","We encountered the following error creating your report:"
"No variable chosen for analysis","No variable chosen for analysis"
"No missing observations","No missing observations"
"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"
@ -250,7 +248,6 @@
"Generating the report. Hold on for a moment..","Generating the report. Hold on for a moment.."
"We encountered the following error showing missingness:","We encountered the following error showing missingness:"
"We encountered the following error browsing your data:","We encountered the following error browsing your data:"
"To consider if data is missing by random, choose the outcome/dependent variable (only variables with any missings are available). If there is a significant difference across other variables depending on missing observations, it may not be missing at random.","To consider if data is missing by random, choose the outcome/dependent variable (only variables with any missings are available). If there is a significant difference across other variables depending on missing observations, it may not be missing at random."
"Choose a name for the column to be created or modified, then enter an expression before clicking on the button below to create the variable, or cancel to exit without saving anything.","Choose a name for the column to be created or modified, then enter an expression before clicking on the button below to create the variable, or cancel to exit without saving anything."
"Other","Other"
"Hour of the day","Hour of the day"
@ -299,3 +296,11 @@
"Words","Words"
"Shorten to first letters","Shorten to first letters"
"Shorten to first words","Shorten to first words"
"Select missings analysis to apply","Select missings analysis to apply"
"Variables","Variables"
"By outcome","By outcome"
"Missings across variables by the variable **'{input$missings_var}'**","Missings across variables by the variable **'{input$missings_var}'**"
"Missing vs non-missing observations in the variable **'{input$missings_var}'**","Missing vs non-missing observations in the variable **'{input$missings_var}'**"
"Evaluate missingness by either comparing missing values across variables (optionally grouped by af categorical or dichotomous variable) or compare variables grouped by the missing status (missing or not) of an outcome variable. If there is a significant difference i the missingness, this may cause a bias in you data and should be considered carefully interpreting the data and analyses as data may not be missing at random.","Evaluate missingness by either comparing missing values across variables (optionally grouped by af categorical or dichotomous variable) or compare variables grouped by the missing status (missing or not) of an outcome variable. If there is a significant difference i the missingness, this may cause a bias in you data and should be considered carefully interpreting the data and analyses as data may not be missing at random."
"Calculating. Hold tight for a moment..","Calculating. Hold tight for a moment.."
"There is a significant difference in data missingness in {n_nonmcar} {ifelse(n_nnonmcar==1,'variable','variables')} grouped by the selected outcome/grouping variable {outcome}.","There is a significant difference in data missingness in {n_nonmcar} {ifelse(n_nnonmcar==1,'variable','variables')} grouped by the selected outcome/grouping variable {outcome}."

1 en sw
152 We encountered the following error creating your report: We encountered the following error creating your report:
153 No variable chosen for analysis No variable chosen for analysis
154 No missing observations No missing observations
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}.
155 There is a total of {p_miss} % missing observations. There is a total of {p_miss} % missing observations.
156 Median: Median:
157 Restore original data Restore original data
248 Generating the report. Hold on for a moment.. Generating the report. Hold on for a moment..
249 We encountered the following error showing missingness: We encountered the following error showing missingness:
250 We encountered the following error browsing your data: We encountered the following error browsing your data:
To consider if data is missing by random, choose the outcome/dependent variable (only variables with any missings are available). If there is a significant difference across other variables depending on missing observations, it may not be missing at random. To consider if data is missing by random, choose the outcome/dependent variable (only variables with any missings are available). If there is a significant difference across other variables depending on missing observations, it may not be missing at random.
251 Choose a name for the column to be created or modified, then enter an expression before clicking on the button below to create the variable, or cancel to exit without saving anything. Choose a name for the column to be created or modified, then enter an expression before clicking on the button below to create the variable, or cancel to exit without saving anything.
252 Other Other
253 Hour of the day Hour of the day
296 Words Words
297 Shorten to first letters Shorten to first letters
298 Shorten to first words Shorten to first words
299 Select missings analysis to apply Select missings analysis to apply
300 Variables Variables
301 By outcome By outcome
302 Missings across variables by the variable **'{input$missings_var}'** Missings across variables by the variable **'{input$missings_var}'**
303 Missing vs non-missing observations in the variable **'{input$missings_var}'** Missing vs non-missing observations in the variable **'{input$missings_var}'**
304 Evaluate missingness by either comparing missing values across variables (optionally grouped by af categorical or dichotomous variable) or compare variables grouped by the missing status (missing or not) of an outcome variable. If there is a significant difference i the missingness, this may cause a bias in you data and should be considered carefully interpreting the data and analyses as data may not be missing at random. Evaluate missingness by either comparing missing values across variables (optionally grouped by af categorical or dichotomous variable) or compare variables grouped by the missing status (missing or not) of an outcome variable. If there is a significant difference i the missingness, this may cause a bias in you data and should be considered carefully interpreting the data and analyses as data may not be missing at random.
305 Calculating. Hold tight for a moment.. Calculating. Hold tight for a moment..
306 There is a significant difference in data missingness in {n_nonmcar} {ifelse(n_nnonmcar==1,'variable','variables')} grouped by the selected outcome/grouping variable {outcome}. There is a significant difference in data missingness in {n_nonmcar} {ifelse(n_nnonmcar==1,'variable','variables')} grouped by the selected outcome/grouping variable {outcome}.

View file

@ -4,7 +4,12 @@
\alias{compare_missings}
\title{Pairwise comparison of missings across covariables}
\usage{
compare_missings(data, by_var, max_level = 20)
compare_missings(
data,
by_var,
max_level = 20,
type = c("predictors", "outcome")
)
}
\arguments{
\item{data}{data frame}

View file

@ -6,13 +6,15 @@
\alias{data_missings_server}
\title{Data correlations evaluation module}
\usage{
data_missings_ui(id)
data_missings_ui(id, ...)
data_missings_server(id, data, variable, max_level = 20, ...)
data_missings_server(id, data, max_level = 20, ...)
}
\arguments{
\item{id}{Module id}
\item{...}{additional UI elements to show before the table overview}
\item{data}{data}
\item{output.format}{output format}

View file

@ -2,7 +2,7 @@
% Please edit documentation in R/data_plots.R
\name{get_label}
\alias{get_label}
\title{Print label, and if missing print variable name}
\title{Print label, and if missing print variable name for plots}
\usage{
get_label(data, var = NULL)
}
@ -15,7 +15,7 @@ get_label(data, var = NULL)
character string
}
\description{
Print label, and if missing print variable name
Print label, and if missing print variable name for plots
}
\examples{
mtcars |> get_label(var = "mpg")

View file

@ -0,0 +1,25 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/missings-module.R
\name{missings_logic_across}
\alias{missings_logic_across}
\title{Converting all variables to logicals by missing status}
\usage{
missings_logic_across(data, exclude = NULL)
}
\arguments{
\item{data}{data}
\item{exclude}{character vector of variable names to be excluded}
}
\value{
data frame
}
\description{
Converting all variables to logicals by missing status
}
\examples{
mtcars |> missings_logic_across("cyl")
## gtsummary::trial |>
## missings_logic_across() |>
## gtsummary::tbl_summary()
}

View file

@ -37,30 +37,30 @@ A selectizeInput customized for named vectors
}
\examples{
if (shiny::interactive()) {
shinyApp(
ui = fluidPage(
shiny::uiOutput("select"),
tableOutput("data")
),
server = function(input, output) {
output$select <- shiny::renderUI({
vectorSelectInput(
inputId = "variable", label = "Variable:",
data = c(
"Cylinders" = "cyl",
"Transmission" = "am",
"Gears" = "gear"
shinyApp(
ui = fluidPage(
shiny::uiOutput("select"),
tableOutput("data")
),
server = function(input, output) {
output$select <- shiny::renderUI({
vectorSelectInput(
inputId = "variable", label = "Variable:",
data = c(
"Cylinders" = "cyl",
"Transmission" = "am",
"Gears" = "gear"
)
)
)
})
})
output$data <- renderTable(
{
mtcars[, c("mpg", input$variable), drop = FALSE]
},
rownames = TRUE
)
}
)
output$data <- renderTable(
{
mtcars[, c("mpg", input$variable), drop = FALSE]
},
rownames = TRUE
)
}
)
}
}

View file

@ -54,7 +54,7 @@ shiny server
shiny modal
An \code{\link[=apexchart]{apexchart()}} \code{htmlwidget} object.
An \code{\link[apexcharter:apexchart]{apexcharter::apexchart()}} \code{htmlwidget} object.
ggplot2 object
}

1034
renv.lock

File diff suppressed because one or more lines are too long