latest release
Some checks failed
pkgdown.yaml / pkgdown (push) Has been cancelled

This commit is contained in:
Andreas Gammelgaard Damsbo 2025-10-08 11:13:30 +02:00
parent 13df57fbb1
commit a06177481b
No known key found for this signature in database
35 changed files with 459 additions and 435 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.10.2
version: 25.10.3
doi: 10.5281/zenodo.14527429
identifiers:
- type: url

View file

@ -1,6 +1,6 @@
Package: FreesearchR
Title: Easy data analysis for clinicians
Version: 25.10.2
Version: 25.10.3
Authors@R: c(
person("Andreas Gammelgaard", "Damsbo",email="agdamsbo@clin.au.dk", role = c("aut", "cre"),
comment = c(ORCID = "0000-0002-7559-1154")),

View file

@ -1,3 +1,7 @@
# FreesearchR 25.10.3
*NEW* Improvements to translations with more strings having been translated. Nearing completion of marking strings for translation, which means (almost) the complete interface is now translatable.
# FreesearchR 25.10.2
*NEW* Improvements to translations with more strings having been translated.

View file

@ -1 +1 @@
app_version <- function()'25.10.2'
app_version <- function()'25.10.3'

View file

@ -105,7 +105,7 @@ create_column_ui <- function(id) {
actionButton(
inputId = ns("compute"),
label = tagList(
phosphoricons::ph("gear"), i18n$t("Create column")
phosphoricons::ph("pencil"), i18n$t("Create column")
),
class = "btn-outline-primary",
width = "100%"
@ -113,7 +113,8 @@ create_column_ui <- function(id) {
actionButton(
inputId = ns("remove"),
label = tagList(
phosphoricons::ph("trash")
phosphoricons::ph("x-circle"),
i18n$t("Cancel")
),
class = "btn-outline-danger",
width = "100%"
@ -140,9 +141,7 @@ create_column_server <- function(id,
info_alert <- shinyWidgets::alert(
status = "info",
phosphoricons::ph("question"),
i18n$t("Choose a name for the column to be created or modified,"),
i18n$t("then enter an expression before clicking on the button above to validate or on "),
phosphoricons::ph("trash"), i18n$t("to delete it.")
i18n$t("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.")
)
rv <- reactiveValues(
@ -244,6 +243,7 @@ list_allowed_operations <- function() {
}
#' @inheritParams shiny::modalDialog
#' @export
#'

View file

@ -166,7 +166,7 @@ describe_col_factor <- function(x, with_summary = TRUE) {
style = htmltools::css(fontStyle = "italic"),
get_var_icon(x),
# phosphoricons::ph("list-bullets"),
"factor"
class(x)
),
if (with_summary) {
tagList(
@ -319,7 +319,7 @@ construct_col_summary <- function(data) {
values <- data[[col]]
content <- if (inherits(values, "character")) {
describe_col_char(values)
} else if (inherits(values, "factor")) {
} else if (inherits(values, c("factor","logical"))) {
describe_col_factor(values)
} else if (inherits(values, c("numeric", "integer"))) {
describe_col_num(values)

View file

@ -1 +1 @@
hosted_version <- function()'v25.10.2-251007'
hosted_version <- function()'v25.10.3-251008'

View file

@ -73,7 +73,7 @@ import_globalenv_ui <- function(id,
id = ns("import-result"),
status = "info",
tags$b(i18n$t("No data selected!")),
i18n$t("Use a datasat from your environment or from the environment of a package."),
i18n$t("Use a dataset from your environment or from the environment of a package."),
dismissible = TRUE
)
),
@ -150,7 +150,9 @@ import_globalenv_server <- function(id,
selected = character(0),
choices = choices,
choicesOpt = choicesOpt,
options = list(title = i18n$t("List of datasets..."))
options = list(
title = i18n$t("List of datasets..."),
"live-search" = TRUE)
)
})
@ -159,7 +161,7 @@ import_globalenv_server <- function(id,
id = "import-result",
status = "info",
tags$b(i18n$t("No data selected!")),
i18n$t("Use a datasat from your environment or from the environment of a package."),
i18n$t("Use a dataset from your environment or from the environment of a package."),
dismissible = TRUE
)
)

View file

@ -35,7 +35,7 @@ plot_box <- function(data, pri, sec, ter = NULL,...) {
)
})
wrap_plot_list(out,title=glue::glue("Grouped by {get_label(data,ter)}"),...)
wrap_plot_list(out,title=glue::glue(i18n$t("Grouped by {get_label(data,ter)}")),...)
}

View file

@ -119,7 +119,7 @@ plot_sankey <- function(data, pri, sec, ter = NULL, color.group = "pri", colors
#' plot_sankey_single("first", "last", color.group = "pri")
#' mtcars |>
#' default_parsing() |>
#' plot_sankey_single("cyl", "vs", color.group = "pri")
#' plot_sankey_single("cyl", "vs", color.group = "pri")
plot_sankey_single <- function(data, pri, sec, color.group = c("pri", "sec"), colors = NULL, ...) {
color.group <- match.arg(color.group)

View file

@ -26,7 +26,7 @@ plot_violin <- function(data, pri, sec, ter = NULL) {
)
})
wrap_plot_list(out, title = glue::glue("Grouped by {get_label(data,ter)}"))
wrap_plot_list(out, title = glue::glue(i18n$t("Grouped by {get_label(data,ter)}")))
})
# patchwork::wrap_plots(out,guides = "collect")
}

View file

@ -26,12 +26,6 @@ m_redcap_readUI <- function(id, title = TRUE, url = NULL) {
width = "100%"
),
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",
# value = "",
# width = "100%"
# ),
shiny::passwordInput(
inputId = ns("api"),
label = i18n$t("API token"),
@ -55,7 +49,7 @@ m_redcap_readUI <- function(id, title = TRUE, url = NULL) {
shinyWidgets::alert(
id = ns("connect-result"),
status = "info",
tags$p(phosphoricons::ph("info", weight = "bold"), "Please fill in server address (URI) and API token, then press 'Connect'.")
tags$p(phosphoricons::ph("info", weight = "bold"), i18n$t("Please fill in web address and API token, then press 'Connect'."))
),
dismissible = TRUE
),

View file

@ -69,18 +69,18 @@ regression_ui <- function(id, ...) {
# )
# ),
shiny::uiOutput(outputId = ns("regression_type")),
shiny::radioButtons(
inputId = ns("all"),
label = i18n$t("Specify covariables"),
inline = TRUE,
selected = 2,
choiceNames = c(
"Yes",
"No"
),
choiceValues = c(1, 2)
),
# shiny::uiOutput(outputId = ns("all")),
# shiny::radioButtons(
# inputId = ns("all"),
# label = i18n$t("Specify covariables"),
# inline = TRUE,
# selected = 2,
# choiceNames = c(
# "Yes",
# "No"
# ),
# choiceValues = c(1, 2)
# ),
shiny::uiOutput(outputId = ns("all_vars")),
shiny::conditionalPanel(
condition = "input.all==1",
shiny::uiOutput(outputId = ns("regression_vars")),
@ -102,17 +102,7 @@ regression_ui <- function(id, ...) {
),
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 = i18n$t("Show p-value"),
inline = TRUE,
selected = "yes",
choiceNames = c(
"Yes",
"No"
),
choiceValues = c("yes", "no")
),
shiny::uiOutput(outputId = ns("add_regression_p")),
# shiny::tags$br(),
# shiny::radioButtons(
# inputId = ns("tbl_theme"),
@ -260,20 +250,32 @@ regression_server <- function(id,
bslib::accordion_panel_update(id = "acc_checks", target = "acc_pan_checks", title = i18n$t("Checks"))
})
# shiny::observe({
# shiny::updateRadioButtons(
# session = session,
# inputId = "all",
# label = i18n$t("Specify covariables"),
# # inline = TRUE,
# # selected = 2,
# choiceNames = c(
# i18n$t("Yes"),
# i18n$t("No")
# ),
# choiceValues = c(1, 2)
# )
# })
output$all_vars <- shiny::renderUI(
shiny::radioButtons(
inputId = ns("all"),
label = i18n$t("Specify covariables"),
inline = TRUE,
selected = 2,
choiceNames = c(
i18n$t("Yes"),
i18n$t("No")
),
choiceValues = c(1, 2)
),
)
output$add_regression_p <- shiny::renderUI(
shiny::radioButtons(
inputId = ns("add_regression_p"),
label = i18n$t("Show p-value"),
inline = TRUE,
selected = "yes",
choiceNames = c(
i18n$t("Yes"),
i18n$t("No")
),
choiceValues = c("yes", "no")
))

Binary file not shown.

View file

@ -99,7 +99,7 @@ ui_elements <- function(selection) {
import_globalenv_ui(
id = "env",
title = NULL,
packages = c("NHANES", "stRoke")
packages = c("NHANES", "stRoke", "datasets")
)
),
# shiny::conditionalPanel(
@ -330,6 +330,7 @@ ui_elements <- function(selection) {
),
shiny::tags$br(),
shiny::helpText(i18n$t("Reset to original imported dataset. Careful! There is no un-doing.")),
shiny::tags$br(),
shiny::tags$br()
)
# )
@ -442,7 +443,7 @@ ui_elements <- function(selection) {
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, 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 (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."))
)
)
),

View file

@ -11,11 +11,11 @@
|collate |en_US.UTF-8 |
|ctype |en_US.UTF-8 |
|tz |Europe/Copenhagen |
|date |2025-10-07 |
|date |2025-10-08 |
|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.10.2.251007 |
|FreesearchR |25.10.3.251008 |
--------------------------------------------------------------------------------
@ -26,8 +26,6 @@
|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) |
@ -46,7 +44,6 @@
|cardx |0.2.5 |2025-07-03 |CRAN (R 4.4.1) |
|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) |
|class |7.3-23 |2025-01-01 |CRAN (R 4.4.1) |
|classInt |0.4-11 |2025-01-08 |CRAN (R 4.4.1) |
@ -56,7 +53,6 @@
|colorspace |2.1-1 |2024-07-26 |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) |
@ -65,12 +61,12 @@
|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) |
|e1071 |1.7-16 |2024-09-16 |CRAN (R 4.4.1) |
|easystats |0.7.5 |2025-07-11 |CRAN (R 4.4.1) |
|effectsize |1.0.1 |2025-05-27 |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) |
|esquisse |2.1.0 |2025-02-21 |CRAN (R 4.4.1) |
@ -88,7 +84,7 @@
|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.10.2 |NA |NA |
|FreesearchR |25.10.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) |
|generics |0.1.4 |2025-05-09 |CRAN (R 4.4.1) |
@ -116,11 +112,10 @@
|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) |
|labelled |2.14.1 |2025-05-06 |CRAN (R 4.4.1) |
|later |1.4.2 |2025-04-08 |RSPM (R 4.4.0) |
|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,7 +139,6 @@
|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) |
|pak |0.9.0 |2025-05-27 |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) |
|pbmcapply |1.5.1 |2022-04-28 |CRAN (R 4.4.1) |
@ -166,13 +160,13 @@
|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.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) |
|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) |
|RColorBrewer |1.1-3 |2022-04-03 |CRAN (R 4.4.1) |
|Rcpp |1.1.0 |2025-07-02 |CRAN (R 4.4.1) |
@ -204,7 +198,6 @@
|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) |
@ -212,6 +205,7 @@
|stringi |1.8.7 |2025-03-27 |CRAN (R 4.4.1) |
|stringr |1.5.1 |2023-11-14 |RSPM (R 4.4.0) |
|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) |
@ -226,9 +220,7 @@
|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) |
|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) |
|withr |3.0.2 |2024-10-28 |CRAN (R 4.4.1) |
@ -237,5 +229,4 @@
|xml2 |1.3.8 |2025-03-14 |RSPM (R 4.4.0) |
|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//RtmprKaNhO/file2c9540d9ead9.R
#### Current file: /var/folders/9l/xbc19wxx0g79jdd2sf_0v291mhwh7f/T//RtmpQghyAd/file101dc4d580c74.R
########
i18n_path <- here::here("translations")
@ -62,7 +62,7 @@ i18n$set_translation_language("en")
#### Current file: /Users/au301842/FreesearchR/R//app_version.R
########
app_version <- function()'25.10.2'
app_version <- function()'25.10.3'
########
@ -500,7 +500,7 @@ create_column_ui <- function(id) {
actionButton(
inputId = ns("compute"),
label = tagList(
phosphoricons::ph("gear"), i18n$t("Create column")
phosphoricons::ph("pencil"), i18n$t("Create column")
),
class = "btn-outline-primary",
width = "100%"
@ -508,7 +508,8 @@ create_column_ui <- function(id) {
actionButton(
inputId = ns("remove"),
label = tagList(
phosphoricons::ph("trash")
phosphoricons::ph("x-circle"),
i18n$t("Cancel")
),
class = "btn-outline-danger",
width = "100%"
@ -535,9 +536,7 @@ create_column_server <- function(id,
info_alert <- shinyWidgets::alert(
status = "info",
phosphoricons::ph("question"),
i18n$t("Choose a name for the column to be created or modified,"),
i18n$t("then enter an expression before clicking on the button above to validate or on "),
phosphoricons::ph("trash"), i18n$t("to delete it.")
i18n$t("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.")
)
rv <- reactiveValues(
@ -639,6 +638,7 @@ list_allowed_operations <- function() {
}
#' @inheritParams shiny::modalDialog
#' @export
#'
@ -3093,7 +3093,7 @@ describe_col_factor <- function(x, with_summary = TRUE) {
style = htmltools::css(fontStyle = "italic"),
get_var_icon(x),
# phosphoricons::ph("list-bullets"),
"factor"
class(x)
),
if (with_summary) {
tagList(
@ -3246,7 +3246,7 @@ construct_col_summary <- function(data) {
values <- data[[col]]
content <- if (inherits(values, "character")) {
describe_col_char(values)
} else if (inherits(values, "factor")) {
} else if (inherits(values, c("factor","logical"))) {
describe_col_factor(values)
} else if (inherits(values, c("numeric", "integer"))) {
describe_col_num(values)
@ -4035,7 +4035,7 @@ data_types <- function() {
#### Current file: /Users/au301842/FreesearchR/R//hosted_version.R
########
hosted_version <- function()'v25.10.2-251007'
hosted_version <- function()'v25.10.3-251008'
########
@ -4133,7 +4133,7 @@ import_globalenv_ui <- function(id,
id = ns("import-result"),
status = "info",
tags$b(i18n$t("No data selected!")),
i18n$t("Use a datasat from your environment or from the environment of a package."),
i18n$t("Use a dataset from your environment or from the environment of a package."),
dismissible = TRUE
)
),
@ -4210,7 +4210,9 @@ import_globalenv_server <- function(id,
selected = character(0),
choices = choices,
choicesOpt = choicesOpt,
options = list(title = i18n$t("List of datasets..."))
options = list(
title = i18n$t("List of datasets..."),
"live-search" = TRUE)
)
})
@ -4219,7 +4221,7 @@ import_globalenv_server <- function(id,
id = "import-result",
status = "info",
tags$b(i18n$t("No data selected!")),
i18n$t("Use a datasat from your environment or from the environment of a package."),
i18n$t("Use a dataset from your environment or from the environment of a package."),
dismissible = TRUE
)
)
@ -5311,7 +5313,7 @@ plot_box <- function(data, pri, sec, ter = NULL,...) {
)
})
wrap_plot_list(out,title=glue::glue("Grouped by {get_label(data,ter)}"),...)
wrap_plot_list(out,title=glue::glue(i18n$t("Grouped by {get_label(data,ter)}")),...)
}
@ -5794,7 +5796,7 @@ plot_sankey <- function(data, pri, sec, ter = NULL, color.group = "pri", colors
#' plot_sankey_single("first", "last", color.group = "pri")
#' mtcars |>
#' default_parsing() |>
#' plot_sankey_single("cyl", "vs", color.group = "pri")
#' plot_sankey_single("cyl", "vs", color.group = "pri")
plot_sankey_single <- function(data, pri, sec, color.group = c("pri", "sec"), colors = NULL, ...) {
color.group <- match.arg(color.group)
@ -5969,7 +5971,7 @@ plot_violin <- function(data, pri, sec, ter = NULL) {
)
})
wrap_plot_list(out, title = glue::glue("Grouped by {get_label(data,ter)}"))
wrap_plot_list(out, title = glue::glue(i18n$t("Grouped by {get_label(data,ter)}")))
})
# patchwork::wrap_plots(out,guides = "collect")
}
@ -6088,12 +6090,6 @@ m_redcap_readUI <- function(id, title = TRUE, url = NULL) {
width = "100%"
),
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",
# value = "",
# width = "100%"
# ),
shiny::passwordInput(
inputId = ns("api"),
label = i18n$t("API token"),
@ -6117,7 +6113,7 @@ m_redcap_readUI <- function(id, title = TRUE, url = NULL) {
shinyWidgets::alert(
id = ns("connect-result"),
status = "info",
tags$p(phosphoricons::ph("info", weight = "bold"), "Please fill in server address (URI) and API token, then press 'Connect'.")
tags$p(phosphoricons::ph("info", weight = "bold"), i18n$t("Please fill in web address and API token, then press 'Connect'."))
),
dismissible = TRUE
),
@ -7794,18 +7790,18 @@ regression_ui <- function(id, ...) {
# )
# ),
shiny::uiOutput(outputId = ns("regression_type")),
shiny::radioButtons(
inputId = ns("all"),
label = i18n$t("Specify covariables"),
inline = TRUE,
selected = 2,
choiceNames = c(
"Yes",
"No"
),
choiceValues = c(1, 2)
),
# shiny::uiOutput(outputId = ns("all")),
# shiny::radioButtons(
# inputId = ns("all"),
# label = i18n$t("Specify covariables"),
# inline = TRUE,
# selected = 2,
# choiceNames = c(
# "Yes",
# "No"
# ),
# choiceValues = c(1, 2)
# ),
shiny::uiOutput(outputId = ns("all_vars")),
shiny::conditionalPanel(
condition = "input.all==1",
shiny::uiOutput(outputId = ns("regression_vars")),
@ -7827,17 +7823,7 @@ regression_ui <- function(id, ...) {
),
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 = i18n$t("Show p-value"),
inline = TRUE,
selected = "yes",
choiceNames = c(
"Yes",
"No"
),
choiceValues = c("yes", "no")
),
shiny::uiOutput(outputId = ns("add_regression_p")),
# shiny::tags$br(),
# shiny::radioButtons(
# inputId = ns("tbl_theme"),
@ -7985,20 +7971,32 @@ regression_server <- function(id,
bslib::accordion_panel_update(id = "acc_checks", target = "acc_pan_checks", title = i18n$t("Checks"))
})
# shiny::observe({
# shiny::updateRadioButtons(
# session = session,
# inputId = "all",
# label = i18n$t("Specify covariables"),
# # inline = TRUE,
# # selected = 2,
# choiceNames = c(
# i18n$t("Yes"),
# i18n$t("No")
# ),
# choiceValues = c(1, 2)
# )
# })
output$all_vars <- shiny::renderUI(
shiny::radioButtons(
inputId = ns("all"),
label = i18n$t("Specify covariables"),
inline = TRUE,
selected = 2,
choiceNames = c(
i18n$t("Yes"),
i18n$t("No")
),
choiceValues = c(1, 2)
),
)
output$add_regression_p <- shiny::renderUI(
shiny::radioButtons(
inputId = ns("add_regression_p"),
label = i18n$t("Show p-value"),
inline = TRUE,
selected = "yes",
choiceNames = c(
i18n$t("Yes"),
i18n$t("No")
),
choiceValues = c("yes", "no")
))
@ -8796,7 +8794,7 @@ ui_elements <- function(selection) {
import_globalenv_ui(
id = "env",
title = NULL,
packages = c("NHANES", "stRoke")
packages = c("NHANES", "stRoke", "datasets")
)
),
# shiny::conditionalPanel(
@ -9027,6 +9025,7 @@ ui_elements <- function(selection) {
),
shiny::tags$br(),
shiny::helpText(i18n$t("Reset to original imported dataset. Careful! There is no un-doing.")),
shiny::tags$br(),
shiny::tags$br()
)
# )
@ -9139,7 +9138,7 @@ ui_elements <- function(selection) {
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, 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 (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."))
)
)
),
@ -11459,7 +11458,8 @@ ui <- bslib::page_fixed(
#### Current file: /Users/au301842/FreesearchR/app/server.R
########
data(mtcars)
data("mtcars")
data("iris")
# trial <- gtsummary::trial
# starwars <- dplyr::starwars
@ -11739,7 +11739,7 @@ server <- function(input, output, session) {
)
},
error = function(err) {
showNotification(paste0("We encountered the following error showing missingness: ", err), type = "err")
showNotification(paste(i18n$t("We encountered the following error showing missingness:"), err), type = "err")
}
)
})
@ -12176,7 +12176,7 @@ server <- function(input, output, session) {
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")
showNotification(paste(i18n$t("We encountered the following error browsing your data:"), err), type = "err")
}
)
})
@ -12200,7 +12200,7 @@ server <- function(input, output, session) {
)
},
error = function(err) {
showNotification(paste0("We encountered the following error showing missingness: ", err), type = "err")
showNotification(paste(i18n$t("We encountered the following error showing missingness:"), err), type = "err")
}
)
})
@ -12247,12 +12247,12 @@ server <- function(input, output, session) {
output$code_import <- shiny::renderUI({
shiny::req(rv$code$import)
prismCodeBlock(paste0(i18n$t("#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(i18n$t("#Data import formatting\n"), rv$code$format))
prismCodeBlock(paste0("#", i18n$t("Data import formatting"), "\n", rv$code$format))
})
output$code_data <- shiny::renderUI({
@ -12270,23 +12270,23 @@ server <- function(input, output, session) {
pipe_string() |>
expression_string(assign.str = "df <- df |>\n")
prismCodeBlock(paste0("#Data modifications\n", out))
prismCodeBlock(paste0("#", i18n$t("Data modifications"), "\n", out))
})
output$code_variables <- shiny::renderUI({
shiny::req(rv$code$variables)
out <- expression_string(rv$code$variables, assign.str = "df <- df |>\n")
prismCodeBlock(paste0("#Variables filter\n", out))
prismCodeBlock(paste0("#", i18n$t("Variables filter"), "\n", out))
})
output$code_filter <- shiny::renderUI({
shiny::req(rv$code$filter)
prismCodeBlock(paste0("#Data filter\n", rv$code$filter))
prismCodeBlock(paste0("#", i18n$t("Data filter"), "\n", rv$code$filter))
})
output$code_table1 <- shiny::renderUI({
shiny::req(rv$code$table1)
prismCodeBlock(paste0("#Data characteristics table\n", rv$code$table1))
prismCodeBlock(paste0("#", i18n$t("Data characteristics table"), "\n", rv$code$table1))
})
@ -12330,7 +12330,7 @@ server <- function(input, output, session) {
output$data_info_nochar <- shiny::renderUI({
shiny::req(rv$list$data)
data_description(rv$list$data, data_text = "The dataset without text variables")
data_description(rv$list$data, data_text = i18n$t("The dataset without text variables"))
})
## Only allow evaluation if the dataset has fewer then 50 variables
@ -12369,9 +12369,9 @@ server <- function(input, output, session) {
# # stop(glue::glue(i18n$t("The data includes {n_col} variables. Please limit to 100.")))
# print("Please limit to 100.")
# } else {
shiny::withProgress(message = "Creating the table. Hold on for a moment..", {
rv$list$table1 <- rlang::exec(create_baseline, !!!append_list(rv$list$data, parameters, "data"))
})
shiny::withProgress(message = i18n$t("Creating the table. Hold on for a moment.."), {
rv$list$table1 <- rlang::exec(create_baseline, !!!append_list(rv$list$data, parameters, "data"))
})
# }
# },
# error = function(err) {
@ -12399,7 +12399,7 @@ server <- function(input, output, session) {
inputId = "outcome_var_cor",
selected = "none",
data = rv$list$data,
label = "Select outcome variable",
label = i18n$t("Select outcome variable"),
col_subset = c(
"none",
colnames(rv$list$data)
@ -12425,7 +12425,7 @@ server <- function(input, output, session) {
output$missings_var <- shiny::renderUI({
columnSelectInput(
inputId = "missings_var",
label = "Select variable to stratify analysis",
label = i18n$t("Select variable to stratify analysis"),
data = shiny::reactive({
shiny::req(rv$data_filtered)
rv$data_filtered[apply(rv$data_filtered, 2, anyNA)]
@ -12523,7 +12523,7 @@ server <- function(input, output, session) {
rv$list$regression <- rv$regression()
rv$list$missings <- rv$missings()
shiny::withProgress(message = "Generating the report. Hold on for a moment..", {
shiny::withProgress(message = i18n$t("Generating the report. Hold on for a moment.."), {
tryCatch(
{
rv$list |>

View file

@ -44,9 +44,6 @@
"Enter an expression to define new column:","Indtast udregningen til at definere en ny variabel:"
"Click on a column name to add it to the expression:","Tryk på et variabel navn for at tilføje det til udregningen:"
"Create column","Opret variabel"
"Choose a name for the column to be created or modified,","Vælg et navn til den ændrede eller nye variabel,"
"then enter an expression before clicking on the button above to validate or on","indtast herefter udregningen før du trykker på knappen ovenfor for at validere eller på"
"to delete it.","for at slette den."
"New column name cannot be empty","Det nye variabelnavn kan ikke være tomt"
"Create a new column","Opret ny variabel"
"Some operations are not allowed","Nogle beregninger er ikke tilladte"
@ -171,7 +168,6 @@
"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"
@ -180,13 +176,11 @@
"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"
"This window is aimed at advanced users and require some *R*-experience!","Dette vindue er primært for avancerede brugere med nogen *R*-erfaring!"
"Create new variables","Opret nye variabler"
"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"
"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.","Her har du en oversigt over hvordan data er blevet formateret, og hvor der er manglende observationer. Brug informationen til at overveje om manglende data mangler tilfældigt eller og der er et mønster, som kan være et udtryk for systematisk manglende data (observationsbias)."
"Specify covariables","Angiv kovariabler"
"If none are selected, all are included.","Hvis ingen er valgt inkluderes alle."
"Analyse","Analysér"
@ -197,53 +191,67 @@
"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"
"Web address","Serveradresse"
"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"
"API token","API-nøgle"
"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"
"Select fields/variables to import and click the funnel to apply optional filters","Vælg variabler, der skal importeres og tryk på tragten for at anvende valgfrie filtre"
"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."
"Click to see data dictionary","Tryk for at se metadata (Data Dictionary)"
"Connected to server!","Forbindelse til serveren oprettet!"
"The {data_rv$info$project_title} project is loaded.","{data_rv$info$project_title}-projektet er forbundet."
"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"
"Import a dataset from an environment","Import a dataset from an environment"
"Preview:","Forsmag:"
"Imported data set","Importeret datasæt"
"Select fields/variables to import:","Vælg variabler, der skal importeres:"
"Specify the data format","Specificér dataformatet"
"Fill missing values?","Skal manglende observationer udfyldes?"
"Requested data was retrieved!","Det udvalgte data blev hentet!"
"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 er hentet, men det ser ud til kun at indeholde ID-variablen. Du skal kontakte din REDCap-administrator og sikre dig at du har adgang til faktisk at hente de udvalgte data."
"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 er hentet, men det ser ud til kun at indeholde nogle af de udvalgte variabler. Du skal kontakte din REDCap-administrator og sikre dig at du har adgang til faktisk at hente de udvalgte data."
"Click to see the imported data","Tryk for at se de importerede data"
"Regression table","Regressionstabel"
"Import a dataset from an environment","Importer et datasæt fra et kodemiljø"
"Select a dataset:","Vælg datasæt:"
"List of datasets...","List of datasets..."
"List of datasets...","Liste af datasæt..."
"No data selected!","Ingen data valgt!"
"Use a datasat from your environment or from the environment of a package.","Use a datasat from your environment or from the environment of a package."
"No dataset here...","Ingen datasæt her..."
"Use a dataset from your environment or from the environment of a package.","Use a dataset from your environment or from the environment of a package."
"Use a dataset from your environment or from the environment of a package.","Brug et datasæt fra dit lokale kodemiljø eller fra en tilgængelig pakke."
"Not a data.frame","Ikke en data.frame"
"Select source","Vælg datakilde"
"Select a data source:","Vælg datakilde:"
"Yes","Ja"
"No","Nej"
"Coefficient plot","Coefficient plot"
"Select outcome variable","Select outcome variable"
"Choose regression analysis","Choose regression analysis"
"Covariables to format as categorical","Covariables to format as categorical"
"Select variable to stratify baseline","Select variable to stratify baseline"
"Select models to plot","Select models to plot"
"Creating regression models failed with the following error:","Creating regression models failed with the following error:"
"Creating a regression table failed with the following error:","Creating a regression table failed with the following error:"
"Saving the plot. Hold on for a moment..","Saving the plot. Hold on for a moment.."
"Running model assumptions checks failed with the following error:","Running model assumptions checks failed with the following error:"
"Select checks to plot","Select checks to plot"
"Multivariable regression model checks","Multivariable regression model checks"
"Grouped by {get_label(data,ter)}","Grouped by {get_label(data,ter)}"
"Option to perform statistical comparisons between strata in baseline table.","Option to perform statistical comparisons between strata in baseline table."
"Press 'Evaluate' to create the comparison table.","Press 'Evaluate' to create the comparison table."
"The data includes {n_col} variables. Please limit to 100.","The data includes {n_col} variables. Please limit to 100."
"Coefficient plot","Koefficientplot"
"Select outcome variable","Vælg svarvariablen"
"Choose regression analysis","Vælg regressionsanalysen"
"Covariables to format as categorical","Kovariabler, der skal omklassificeres som kategoriske"
"Select variable to stratify baseline","Vælg variabel til a stratificere tabellen"
"Select models to plot","Vælg de modeller, der skal visualiseres"
"Creating regression models failed with the following error:","Oprettelsen af en regressionsmodel fejlede med den følgende besked:"
"Creating a regression table failed with the following error:","Oprettelsen af en regressionstabel fejlede med den følgende besked:"
"Saving the plot. Hold on for a moment..","Gemmer grafikken. Vent et øjeblik.."
"Running model assumptions checks failed with the following error:","Tjek af antagelser for regressionsmodellen fejlede med den følgende besked:"
"Select checks to plot","Vælg modeltests, der skal visualiseres"
"Multivariable regression model checks","Tests af multivariabel regressionsmodel"
"Grouped by {get_label(data,ter)}","Grupperet efter {get_label(data,ter)}"
"Option to perform statistical comparisons between strata in baseline table.","Mulighed for at udføre statistiske tests mellem strata i oversigtstabellen."
"Press 'Evaluate' to create the comparison table.","Tryk 'Evaluér' for at oprette en oversigtstabel."
"The data includes {n_col} variables. Please limit to 100.","Data indeholder {n_col} variabler. Begræns venligst til 100."
"Data import","Data import"
"Data import formatting","Formatering af data ved import"
"Data modifications","Ændringer af data"
"Variables filter","Variables filter"
"Data filter","Data filter"
"Data characteristics table","Oversigtstabel"
"The dataset without text variables","Datasættet uden variabler formateret som tekst"
"Creating the table. Hold on for a moment..","Opretter tabellen. Vent et øjeblik.."
"Select variable to stratify analysis","Vælg variabler til at stratificere analysen"
"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'."

1 en da
44 Enter an expression to define new column: Indtast udregningen til at definere en ny variabel:
45 Click on a column name to add it to the expression: Tryk på et variabel navn for at tilføje det til udregningen:
46 Create column Opret variabel
Choose a name for the column to be created or modified, Vælg et navn til den ændrede eller nye variabel,
then enter an expression before clicking on the button above to validate or on indtast herefter udregningen før du trykker på knappen ovenfor for at validere eller på
to delete it. for at slette den.
47 New column name cannot be empty Det nye variabelnavn kan ikke være tomt
48 Create a new column Opret ny variabel
49 Some operations are not allowed Nogle beregninger er ikke tilladte
168 Correlation cut-off Korrelationsgrænse
169 Set the cut-off for considered 'highly correlated'. Angiv grænsen for. hvad, der tolkes som 'betydelig korrelation'.
170 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.
171 Class Klasse
172 Observations Observationer
173 Data classes and missing observations Dataklasser og manglende observationer
176 Confirm Bekræft
177 The filtered data Filtreret data
178 Create new factor Ny kategorisk variabel
179 This window is aimed at advanced users and require some *R*-experience! This window is aimed at advanced users and require some *R*-experience! Dette vindue er primært for avancerede brugere med nogen *R*-erfaring!
180 Create new variables Opret ny variabel Opret nye variabler
181 Select data types to include Vælg datatyper, der skal inkluderes
182 Uploaded data overview Overblik over uploaded data
183 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. Her har du en oversigt over hvordan data er blevet formateret, og hvor der er manglende observationer. Brug informationen til at overveje om manglende data mangler tilfældigt eller og der er et mønster, som kan være et udtryk for systematisk manglende data (observationsbias).
#Data import\n #Data import\n
#Data import formatting\n #Formatering ved data-import\n
184 Specify covariables Angiv kovariabler
185 If none are selected, all are included. Hvis ingen er valgt inkluderes alle.
186 Analyse Analysér
191 Please confirm data reset! Bekræft gendannelse af data!
192 Import data from REDCap Importér data fra REDCap
193 REDCap server REDCap-server
194 Web address Web address Serveradresse
195 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/'
196 API token API token API-nøgle
197 The token is a string of 32 numbers and letters. En API-nøgle består af ialt 32 tal og bogstaver.
198 Connect Forbind
199 Data import parameters Data import parameters
200 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 Vælg variabler, der skal importeres og tryk på tragten for at anvende valgfrie filtre
201 Import Import
202 Click to see data dictionary Click to see data dictionary Tryk for at se metadata (Data Dictionary)
203 Connected to server! Connected to server! Forbindelse til serveren oprettet!
204 The {data_rv$info$project_title} project is loaded. The {data_rv$info$project_title} project is loaded. {data_rv$info$project_title}-projektet er forbundet.
205 Data dictionary Data dictionary
206 Preview: Preview: Forsmag:
207 Imported data set Imported data set Importeret datasæt
208 Select fields/variables to import: Select fields/variables to import: Vælg variabler, der skal importeres:
209 Specify the data format Specify the data format Specificér dataformatet
210 Fill missing values? Fill missing values? Skal manglende observationer udfyldes?
211 Requested data was retrieved! Requested data was retrieved! Det udvalgte data blev hentet!
212 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 er hentet, men det ser ud til kun at indeholde ID-variablen. Du skal kontakte din REDCap-administrator og sikre dig at du har adgang til faktisk at hente de udvalgte data.
213 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. Data er hentet, men det ser ud til kun at indeholde nogle af de udvalgte variabler. Du skal kontakte din REDCap-administrator og sikre dig at du har adgang til faktisk at hente de udvalgte data.
214 Click to see the imported data Click to see the imported data Tryk for at se de importerede data
215 Regression table Regression table Regressionstabel
216 Import a dataset from an environment Import a dataset from an environment Importer et datasæt fra et kodemiljø
217 Select a dataset: Vælg datasæt:
218 List of datasets... List of datasets... Liste af datasæt...
219 No data selected! Ingen data valgt!
Use a datasat from your environment or from the environment of a package. Use a datasat from your environment or from the environment of a package.
220 No dataset here... Ingen datasæt her...
221 Use a dataset from your environment or from the environment of a package. Use a dataset from your environment or from the environment of a package. Brug et datasæt fra dit lokale kodemiljø eller fra en tilgængelig pakke.
222 Not a data.frame Ikke en data.frame
223 Select source Vælg datakilde
224 Select a data source: Vælg datakilde:
225 Yes Ja
226 No Nej
227 Coefficient plot Coefficient plot Koefficientplot
228 Select outcome variable Select outcome variable Vælg svarvariablen
229 Choose regression analysis Choose regression analysis Vælg regressionsanalysen
230 Covariables to format as categorical Covariables to format as categorical Kovariabler, der skal omklassificeres som kategoriske
231 Select variable to stratify baseline Select variable to stratify baseline Vælg variabel til a stratificere tabellen
232 Select models to plot Select models to plot Vælg de modeller, der skal visualiseres
233 Creating regression models failed with the following error: Creating regression models failed with the following error: Oprettelsen af en regressionsmodel fejlede med den følgende besked:
234 Creating a regression table failed with the following error: Creating a regression table failed with the following error: Oprettelsen af en regressionstabel fejlede med den følgende besked:
235 Saving the plot. Hold on for a moment.. Saving the plot. Hold on for a moment.. Gemmer grafikken. Vent et øjeblik..
236 Running model assumptions checks failed with the following error: Running model assumptions checks failed with the following error: Tjek af antagelser for regressionsmodellen fejlede med den følgende besked:
237 Select checks to plot Select checks to plot Vælg modeltests, der skal visualiseres
238 Multivariable regression model checks Multivariable regression model checks Tests af multivariabel regressionsmodel
239 Grouped by {get_label(data,ter)} Grouped by {get_label(data,ter)} Grupperet efter {get_label(data,ter)}
240 Option to perform statistical comparisons between strata in baseline table. Option to perform statistical comparisons between strata in baseline table. Mulighed for at udføre statistiske tests mellem strata i oversigtstabellen.
241 Press 'Evaluate' to create the comparison table. Press 'Evaluate' to create the comparison table. Tryk 'Evaluér' for at oprette en oversigtstabel.
242 The data includes {n_col} variables. Please limit to 100. The data includes {n_col} variables. Please limit to 100. Data indeholder {n_col} variabler. Begræns venligst til 100.
243 Data import Data import
244 Data import formatting Formatering af data ved import
245 Data modifications Ændringer af data
246 Variables filter Variables filter
247 Data filter Data filter
248 Data characteristics table Oversigtstabel
249 The dataset without text variables Datasættet uden variabler formateret som tekst
250 Creating the table. Hold on for a moment.. Opretter tabellen. Vent et øjeblik..
251 Select variable to stratify analysis Vælg variabler til at stratificere analysen
252 Generating the report. Hold on for a moment.. Opretter rapporten. Vent et øjeblik..
253 We encountered the following error showing missingness: Under analysen af manglende observationer opstod følgende fejl:
254 We encountered the following error browsing your data: I forsøget på at vise en dataoversigt opstod følgende fejl:
255 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.
256 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.
257 Please fill in web address and API token, then press 'Connect'. Udfyld serveradresse og API-nøgle, og tryk så 'Fobind'.

View file

@ -44,9 +44,6 @@
"Enter an expression to define new column:","Enter an expression to define new column:"
"Click on a column name to add it to the expression:","Click on a column name to add it to the expression:"
"Create column","Create column"
"Choose a name for the column to be created or modified,","Choose a name for the column to be created or modified,"
"then enter an expression before clicking on the button above to validate or on","then enter an expression before clicking on the button above to validate or on"
"to delete it.","to delete it."
"New column name cannot be empty","New column name cannot be empty"
"Create a new column","Create a new column"
"Some operations are not allowed","Some operations are not allowed"
@ -171,7 +168,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, 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"
@ -185,8 +181,6 @@
"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"
@ -223,7 +217,6 @@
"Select a dataset:","Select a dataset:"
"List of datasets...","List of datasets..."
"No data selected!","No data selected!"
"Use a datasat from your environment or from the environment of a package.","Use a datasat from your environment or from the environment of a package."
"No dataset here...","No dataset here..."
"Use a dataset from your environment or from the environment of a package.","Use a dataset from your environment or from the environment of a package."
"Not a data.frame","Not a data.frame"
@ -247,3 +240,18 @@
"Option to perform statistical comparisons between strata in baseline table.","Option to perform statistical comparisons between strata in baseline table."
"Press 'Evaluate' to create the comparison table.","Press 'Evaluate' to create the comparison table."
"The data includes {n_col} variables. Please limit to 100.","The data includes {n_col} variables. Please limit to 100."
"Data import","Data import"
"Data import formatting","Data import formatting"
"Data modifications","Data modifications"
"Variables filter","Variables filter"
"Data filter","Data filter"
"Data characteristics table","Data characteristics table"
"The dataset without text variables","The dataset without text variables"
"Creating the table. Hold on for a moment..","Creating the table. Hold on for a moment.."
"Select variable to stratify analysis","Select variable to stratify analysis"
"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."
"Please fill in web address and API token, then press 'Connect'.","Please fill in web address and API token, then press 'Connect'."

1 en sw
44 Enter an expression to define new column: Enter an expression to define new column:
45 Click on a column name to add it to the expression: Click on a column name to add it to the expression:
46 Create column Create column
Choose a name for the column to be created or modified, Choose a name for the column to be created or modified,
then enter an expression before clicking on the button above to validate or on then enter an expression before clicking on the button above to validate or on
to delete it. to delete it.
47 New column name cannot be empty New column name cannot be empty
48 Create a new column Create a new column
49 Some operations are not allowed Some operations are not allowed
168 Correlation cut-off Correlation cut-off
169 Set the cut-off for considered 'highly correlated'. Set the cut-off for considered 'highly correlated'.
170 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.
171 Class Class
172 Observations Observations
173 Data classes and missing observations Data classes and missing observations
181 Select data types to include Select data types to include
182 Uploaded data overview Uploaded data overview
183 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
184 Specify covariables Specify covariables
185 If none are selected, all are included. If none are selected, all are included.
186 Analyse Analyse
217 Select a dataset: Select a dataset:
218 List of datasets... List of datasets...
219 No data selected! No data selected!
Use a datasat from your environment or from the environment of a package. Use a datasat from your environment or from the environment of a package.
220 No dataset here... No dataset here...
221 Use a dataset from your environment or from the environment of a package. Use a dataset from your environment or from the environment of a package.
222 Not a data.frame Not a data.frame
240 Option to perform statistical comparisons between strata in baseline table. Option to perform statistical comparisons between strata in baseline table.
241 Press 'Evaluate' to create the comparison table. Press 'Evaluate' to create the comparison table.
242 The data includes {n_col} variables. Please limit to 100. The data includes {n_col} variables. Please limit to 100.
243 Data import Data import
244 Data import formatting Data import formatting
245 Data modifications Data modifications
246 Variables filter Variables filter
247 Data filter Data filter
248 Data characteristics table Data characteristics table
249 The dataset without text variables The dataset without text variables
250 Creating the table. Hold on for a moment.. Creating the table. Hold on for a moment..
251 Select variable to stratify analysis Select variable to stratify analysis
252 Generating the report. Hold on for a moment.. Generating the report. Hold on for a moment..
253 We encountered the following error showing missingness: We encountered the following error showing missingness:
254 We encountered the following error browsing your data: We encountered the following error browsing your data:
255 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.
256 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.
257 Please fill in web address and API token, then press 'Connect'. Please fill in web address and API token, then press 'Connect'.

View file

@ -8,6 +8,10 @@ a free tool for basic data evaluation and analysis. If you need more
advanced tools, start with <strong><em>FreesearchR</em></strong> and
then youll probably be better off using <em>R</em> or similar
directly.</p>
<p>The <strong><em>FreesearchR</em></strong> app should be available to
as many people as possible, and the interface can be translated to any
language. If you have suggestions or want to help translate, please
reach out on <a href="mailto:info@freesearchr.org">info@freesearchr.org</a>.</p>
<p>With this tool you can:</p>
<ol style="list-style-type: decimal">
<li><p><strong>Import data</strong> from a spreadsheet/file on your

View file

@ -6,6 +6,8 @@ output: html_fragment
This is the ***FreesearchR*** data analysis tool, a free tool for basic data evaluation and analysis. If you need more advanced tools, start with ***FreesearchR*** and then you'll probably be better off using *R* or similar directly.
The ***FreesearchR*** app should be available to as many people as possible, and the interface can be translated to any language. If you have suggestions or want to help translate, please reach out on [info@freesearchr.org](mailto:info@freesearchr.org).
With this tool you can:
1. **Import data** from a spreadsheet/file on your machine, directly from a [REDCap](https://projectredcap.org/ "Read more on the data capture tool REDCap") server, try it with sample data or access data directly [if run in R locally](https://agdamsbo.github.io/FreesearchR//#run-locally-on-your-own-machine "Read about running FreesearchR on your local machine")

View file

@ -20,18 +20,18 @@ eksempel-data eller tilgå data direkte <a href="https://agdamsbo.github.io/Free
afvikler i R lokalt</a></p></li>
<li><p><strong>Forbered</strong> data til analys ved at filtrere, ændre
variabler eller opret helt nye variabler</p></li>
<li><p><strong>Evaluate data</strong> using descriptive analyses methods
and inspect cross-correlations as well as <a href="https://agdamsbo.github.io/FreesearchR/articles/missingness.html" title="Read more about missing data">missing observations</a></p></li>
<li><p><strong>Visualise data</strong> by <a href="https://agdamsbo.github.io/FreesearchR/articles/visuals.html" title="See available plot types">creating simple, clean plots</a> for
overview and quick insights</p></li>
<li><p><strong>Create simple regression models</strong> for even more
advanced data analyses</p></li>
<li><p><strong>Download</strong> results as a report, get the modified
data set and save the code for learning and to reproduce the results
later</p></li>
<li><p><strong>Evaluer data</strong> ved hjælp af beskrivende
analysemetoder og inspicer krydskorrelationer samt <a href="https://agdamsbo.github.io/FreesearchR/articles/missingness.html" title="Læs mere om manglende data">manglende observationer</a></p></li>
<li><p><strong>Visualiser data</strong> ved at <a href="https://agdamsbo.github.io/FreesearchR/articles/visuals.html" title="Se tilgængelige plottyper">oprette enkle, rene plots</a> for
overblik og hurtig indsigt</p></li>
<li><p><strong>Opret simple regressionsmodeller</strong> til endnu mere
avancerede dataanalyser</p></li>
<li><p><strong>Download</strong> resultater som en rapport, hent det
ændrede datasæt og gem koden til læring og til senere reproduktion af
resultaterne</p></li>
</ol>
<p>The full <a href="https://agdamsbo.github.io/FreesearchR/">project
documentation is here</a> where youll find detailed descriptions of the
app and link to the source code! If you want to <a href="https://redcap.au.dk/surveys/?s=JPCLPTXYDKFA8DA8">share feedback,
please follow this link to a simple survey</a>.</p>
<p>Den fulde <a href="https://agdamsbo.github.io/FreesearchR/">projektdokumentation er
her</a>, hvor du finder detaljerede beskrivelser af appen og et link til
kildekoden! Hvis du vil <a href="https://redcap.au.dk/surveys/?s=JPCLPTXYDKFA8DA8">dele feedback,
kan du følge dette link til et enkelt spørgeskema</a>.</p>
</div>

View file

@ -14,12 +14,12 @@ Herunder kan du helt kort se, hvad du kan bruge ***FreesearchR*** til:
2. **Forbered** data til analys ved at filtrere, ændre variabler eller opret helt nye variabler
3. **Evaluate data** using descriptive analyses methods and inspect cross-correlations as well as [missing observations](https://agdamsbo.github.io/FreesearchR/articles/missingness.html "Read more about missing data")
3. **Evaluer data** ved hjælp af beskrivende analysemetoder og inspicer krydskorrelationer samt [manglende observationer](https://agdamsbo.github.io/FreesearchR/articles/missingness.html "Læs mere om manglende data")
4. **Visualise data** by [creating simple, clean plots](https://agdamsbo.github.io/FreesearchR/articles/visuals.html "See available plot types") for overview and quick insights
4. **Visualiser data** ved at [oprette enkle, rene plots](https://agdamsbo.github.io/FreesearchR/articles/visuals.html "Se tilgængelige plottyper") for overblik og hurtig indsigt
5. **Create simple regression models** for even more advanced data analyses
5. **Opret simple regressionsmodeller** til endnu mere avancerede dataanalyser
6. **Download** results as a report, get the modified data set and save the code for learning and to reproduce the results later
6. **Download** resultater som en rapport, hent det ændrede datasæt og gem koden til læring og til senere reproduktion af resultaterne
The full [project documentation is here](https://agdamsbo.github.io/FreesearchR/) where you'll find detailed descriptions of the app and link to the source code! If you want to [share feedback, please follow this link to a simple survey](https://redcap.au.dk/surveys/?s=JPCLPTXYDKFA8DA8).
Den fulde [projektdokumentation er her](https://agdamsbo.github.io/FreesearchR/), hvor du finder detaljerede beskrivelser af appen og et link til kildekoden! Hvis du vil [dele feedback, kan du følge dette link til et enkelt spørgeskema](https://redcap.au.dk/surveys/?s=JPCLPTXYDKFA8DA8).

File diff suppressed because one or more lines are too long

View file

@ -2,7 +2,7 @@
output: html_fragment
---
# Karibu <img src="FreesearchR-logo.png" style="float: right;"/>
# Karibu sana! <img src="FreesearchR-logo.png" style="float: right;"/>
Hii ni ***FreesearchR*** zana ya kuchanganua data, zana isiyolipishwa ya kutathmini na kuchanganua data msingi. Iwapo unahitaji zana za kina zaidi, anza na ***FreesearchR*** na basi pengine utakuwa bora kutumia *R* au sawa moja kwa moja.
@ -10,16 +10,16 @@ Tunajitahidi kutambulisha tafsiri kamili kwa Kiswahili. Ikiwa ungependa kuchangi
Na ***FreesearchR*** unaweza:
1. **Import data** from a spreadsheet/file on your machine, directly from a [REDCap](https://projectredcap.org/ "Read more on the data capture tool REDCap") server, try it with sample data or access data directly [if run in R locally](https://agdamsbo.github.io/FreesearchR//#run-locally-on-your-own-machine "Read about running FreesearchR on your local machine")
1. **Ingiza data** kutoka kwa lahajedwali/faili kwenye mashine yako, moja kwa moja kutoka kwa seva ya [REDCap](https://projectredcap.org/ "Soma zaidi kuhusu zana ya kunasa data ya REDCap"), ijaribu kwa sampuli ya data au ufikie data moja kwa moja [ikiwa inaendeshwa katika R ndani ya nchi](https://agdamsbo.github.io/Freesearchourcal-R/-#ownon-run-your-ruwnon-" FreesearchR kwenye mashine yako ya karibu")
2. **Prepare** data for analysis by filtering data, modifying variables or create new variables
2. **Andaa** data kwa uchanganuzi kwa kuchuja data, kurekebisha vigeu au kuunda vigeu vipya
3. **Evaluate data** using descriptive analyses methods and inspect cross-correlations as well as [missing observations](https://agdamsbo.github.io/FreesearchR/articles/missingness.html "Read more about missing data")
3. **Tathmini data** kwa kutumia mbinu za uchanganuzi wa maelezo na ukague miunganisho mtambuka pamoja na [maoni yanayokosekana](https://agdamsbo.github.io/FreesearchR/articles/missingness.html "Soma zaidi kuhusu kukosa data")
4. **Visualise data** by [creating simple, clean plots](https://agdamsbo.github.io/FreesearchR/articles/visuals.html "See available plot types") for overview and quick insights
4. **Onyesha data** kwa [kuunda viwanja rahisi na safi](https://agdamsbo.github.io/FreesearchR/articles/visuals.html "Angalia aina zinazopatikana za viwanja") kwa muhtasari na maarifa ya haraka
5. **Create simple regression models** for even more advanced data analyses
5. **Unda miundo rahisi ya kurejesha kumbukumbu** kwa uchanganuzi wa hali ya juu zaidi wa data
6. **Download** results as a report, get the modified data set and save the code for learning and to reproduce the results later
6. **Pakua** matokeo kama ripoti, pata seti ya data iliyorekebishwa na uhifadhi msimbo wa kujifunza na kutoa matokeo baadaye
The full [project documentation is here](https://agdamsbo.github.io/FreesearchR/) where you'll find detailed descriptions of the app and link to the source code! If you want to [share feedback, please follow this link to a simple survey](https://redcap.au.dk/surveys/?s=JPCLPTXYDKFA8DA8).
[Hati kamili za mradi ziko hapa](https://agdamsbo.github.io/FreesearchR/) ambapo utapata maelezo ya kina ya programu na kiungo cha msimbo wa chanzo! Iwapo ungependa [kushiriki maoni, tafadhali fuata kiungo hiki cha utafiti rahisi](https://redcap.au.dk/surveys/?s=JPCLPTXYDKFA8DA8).

View file

@ -1,7 +1,7 @@
########
#### Current file: /var/folders/9l/xbc19wxx0g79jdd2sf_0v291mhwh7f/T//RtmprKaNhO/file2c953618a132.R
#### Current file: /var/folders/9l/xbc19wxx0g79jdd2sf_0v291mhwh7f/T//RtmpQghyAd/file101dc71002b73.R
########
i18n_path <- system.file("translations", package = "FreesearchR")
@ -62,7 +62,7 @@ i18n$set_translation_language("en")
#### Current file: /Users/au301842/FreesearchR/R//app_version.R
########
app_version <- function()'25.10.2'
app_version <- function()'25.10.3'
########
@ -500,7 +500,7 @@ create_column_ui <- function(id) {
actionButton(
inputId = ns("compute"),
label = tagList(
phosphoricons::ph("gear"), i18n$t("Create column")
phosphoricons::ph("pencil"), i18n$t("Create column")
),
class = "btn-outline-primary",
width = "100%"
@ -508,7 +508,8 @@ create_column_ui <- function(id) {
actionButton(
inputId = ns("remove"),
label = tagList(
phosphoricons::ph("trash")
phosphoricons::ph("x-circle"),
i18n$t("Cancel")
),
class = "btn-outline-danger",
width = "100%"
@ -535,9 +536,7 @@ create_column_server <- function(id,
info_alert <- shinyWidgets::alert(
status = "info",
phosphoricons::ph("question"),
i18n$t("Choose a name for the column to be created or modified,"),
i18n$t("then enter an expression before clicking on the button above to validate or on "),
phosphoricons::ph("trash"), i18n$t("to delete it.")
i18n$t("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.")
)
rv <- reactiveValues(
@ -639,6 +638,7 @@ list_allowed_operations <- function() {
}
#' @inheritParams shiny::modalDialog
#' @export
#'
@ -3093,7 +3093,7 @@ describe_col_factor <- function(x, with_summary = TRUE) {
style = htmltools::css(fontStyle = "italic"),
get_var_icon(x),
# phosphoricons::ph("list-bullets"),
"factor"
class(x)
),
if (with_summary) {
tagList(
@ -3246,7 +3246,7 @@ construct_col_summary <- function(data) {
values <- data[[col]]
content <- if (inherits(values, "character")) {
describe_col_char(values)
} else if (inherits(values, "factor")) {
} else if (inherits(values, c("factor","logical"))) {
describe_col_factor(values)
} else if (inherits(values, c("numeric", "integer"))) {
describe_col_num(values)
@ -4035,7 +4035,7 @@ data_types <- function() {
#### Current file: /Users/au301842/FreesearchR/R//hosted_version.R
########
hosted_version <- function()'v25.10.2-251007'
hosted_version <- function()'v25.10.3-251008'
########
@ -4133,7 +4133,7 @@ import_globalenv_ui <- function(id,
id = ns("import-result"),
status = "info",
tags$b(i18n$t("No data selected!")),
i18n$t("Use a datasat from your environment or from the environment of a package."),
i18n$t("Use a dataset from your environment or from the environment of a package."),
dismissible = TRUE
)
),
@ -4210,7 +4210,9 @@ import_globalenv_server <- function(id,
selected = character(0),
choices = choices,
choicesOpt = choicesOpt,
options = list(title = i18n$t("List of datasets..."))
options = list(
title = i18n$t("List of datasets..."),
"live-search" = TRUE)
)
})
@ -4219,7 +4221,7 @@ import_globalenv_server <- function(id,
id = "import-result",
status = "info",
tags$b(i18n$t("No data selected!")),
i18n$t("Use a datasat from your environment or from the environment of a package."),
i18n$t("Use a dataset from your environment or from the environment of a package."),
dismissible = TRUE
)
)
@ -5311,7 +5313,7 @@ plot_box <- function(data, pri, sec, ter = NULL,...) {
)
})
wrap_plot_list(out,title=glue::glue("Grouped by {get_label(data,ter)}"),...)
wrap_plot_list(out,title=glue::glue(i18n$t("Grouped by {get_label(data,ter)}")),...)
}
@ -5794,7 +5796,7 @@ plot_sankey <- function(data, pri, sec, ter = NULL, color.group = "pri", colors
#' plot_sankey_single("first", "last", color.group = "pri")
#' mtcars |>
#' default_parsing() |>
#' plot_sankey_single("cyl", "vs", color.group = "pri")
#' plot_sankey_single("cyl", "vs", color.group = "pri")
plot_sankey_single <- function(data, pri, sec, color.group = c("pri", "sec"), colors = NULL, ...) {
color.group <- match.arg(color.group)
@ -5969,7 +5971,7 @@ plot_violin <- function(data, pri, sec, ter = NULL) {
)
})
wrap_plot_list(out, title = glue::glue("Grouped by {get_label(data,ter)}"))
wrap_plot_list(out, title = glue::glue(i18n$t("Grouped by {get_label(data,ter)}")))
})
# patchwork::wrap_plots(out,guides = "collect")
}
@ -6088,12 +6090,6 @@ m_redcap_readUI <- function(id, title = TRUE, url = NULL) {
width = "100%"
),
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",
# value = "",
# width = "100%"
# ),
shiny::passwordInput(
inputId = ns("api"),
label = i18n$t("API token"),
@ -6117,7 +6113,7 @@ m_redcap_readUI <- function(id, title = TRUE, url = NULL) {
shinyWidgets::alert(
id = ns("connect-result"),
status = "info",
tags$p(phosphoricons::ph("info", weight = "bold"), "Please fill in server address (URI) and API token, then press 'Connect'.")
tags$p(phosphoricons::ph("info", weight = "bold"), i18n$t("Please fill in web address and API token, then press 'Connect'."))
),
dismissible = TRUE
),
@ -7794,18 +7790,18 @@ regression_ui <- function(id, ...) {
# )
# ),
shiny::uiOutput(outputId = ns("regression_type")),
shiny::radioButtons(
inputId = ns("all"),
label = i18n$t("Specify covariables"),
inline = TRUE,
selected = 2,
choiceNames = c(
"Yes",
"No"
),
choiceValues = c(1, 2)
),
# shiny::uiOutput(outputId = ns("all")),
# shiny::radioButtons(
# inputId = ns("all"),
# label = i18n$t("Specify covariables"),
# inline = TRUE,
# selected = 2,
# choiceNames = c(
# "Yes",
# "No"
# ),
# choiceValues = c(1, 2)
# ),
shiny::uiOutput(outputId = ns("all_vars")),
shiny::conditionalPanel(
condition = "input.all==1",
shiny::uiOutput(outputId = ns("regression_vars")),
@ -7827,17 +7823,7 @@ regression_ui <- function(id, ...) {
),
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 = i18n$t("Show p-value"),
inline = TRUE,
selected = "yes",
choiceNames = c(
"Yes",
"No"
),
choiceValues = c("yes", "no")
),
shiny::uiOutput(outputId = ns("add_regression_p")),
# shiny::tags$br(),
# shiny::radioButtons(
# inputId = ns("tbl_theme"),
@ -7985,20 +7971,32 @@ regression_server <- function(id,
bslib::accordion_panel_update(id = "acc_checks", target = "acc_pan_checks", title = i18n$t("Checks"))
})
# shiny::observe({
# shiny::updateRadioButtons(
# session = session,
# inputId = "all",
# label = i18n$t("Specify covariables"),
# # inline = TRUE,
# # selected = 2,
# choiceNames = c(
# i18n$t("Yes"),
# i18n$t("No")
# ),
# choiceValues = c(1, 2)
# )
# })
output$all_vars <- shiny::renderUI(
shiny::radioButtons(
inputId = ns("all"),
label = i18n$t("Specify covariables"),
inline = TRUE,
selected = 2,
choiceNames = c(
i18n$t("Yes"),
i18n$t("No")
),
choiceValues = c(1, 2)
),
)
output$add_regression_p <- shiny::renderUI(
shiny::radioButtons(
inputId = ns("add_regression_p"),
label = i18n$t("Show p-value"),
inline = TRUE,
selected = "yes",
choiceNames = c(
i18n$t("Yes"),
i18n$t("No")
),
choiceValues = c("yes", "no")
))
@ -8796,7 +8794,7 @@ ui_elements <- function(selection) {
import_globalenv_ui(
id = "env",
title = NULL,
packages = c("NHANES", "stRoke")
packages = c("NHANES", "stRoke", "datasets")
)
),
# shiny::conditionalPanel(
@ -9027,6 +9025,7 @@ ui_elements <- function(selection) {
),
shiny::tags$br(),
shiny::helpText(i18n$t("Reset to original imported dataset. Careful! There is no un-doing.")),
shiny::tags$br(),
shiny::tags$br()
)
# )
@ -9139,7 +9138,7 @@ ui_elements <- function(selection) {
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, 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 (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."))
)
)
),
@ -11459,7 +11458,8 @@ ui <- bslib::page_fixed(
#### Current file: /Users/au301842/FreesearchR/app/server.R
########
data(mtcars)
data("mtcars")
data("iris")
# trial <- gtsummary::trial
# starwars <- dplyr::starwars
@ -11739,7 +11739,7 @@ server <- function(input, output, session) {
)
},
error = function(err) {
showNotification(paste0("We encountered the following error showing missingness: ", err), type = "err")
showNotification(paste(i18n$t("We encountered the following error showing missingness:"), err), type = "err")
}
)
})
@ -12176,7 +12176,7 @@ server <- function(input, output, session) {
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")
showNotification(paste(i18n$t("We encountered the following error browsing your data:"), err), type = "err")
}
)
})
@ -12200,7 +12200,7 @@ server <- function(input, output, session) {
)
},
error = function(err) {
showNotification(paste0("We encountered the following error showing missingness: ", err), type = "err")
showNotification(paste(i18n$t("We encountered the following error showing missingness:"), err), type = "err")
}
)
})
@ -12247,12 +12247,12 @@ server <- function(input, output, session) {
output$code_import <- shiny::renderUI({
shiny::req(rv$code$import)
prismCodeBlock(paste0(i18n$t("#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(i18n$t("#Data import formatting\n"), rv$code$format))
prismCodeBlock(paste0("#", i18n$t("Data import formatting"), "\n", rv$code$format))
})
output$code_data <- shiny::renderUI({
@ -12270,23 +12270,23 @@ server <- function(input, output, session) {
pipe_string() |>
expression_string(assign.str = "df <- df |>\n")
prismCodeBlock(paste0("#Data modifications\n", out))
prismCodeBlock(paste0("#", i18n$t("Data modifications"), "\n", out))
})
output$code_variables <- shiny::renderUI({
shiny::req(rv$code$variables)
out <- expression_string(rv$code$variables, assign.str = "df <- df |>\n")
prismCodeBlock(paste0("#Variables filter\n", out))
prismCodeBlock(paste0("#", i18n$t("Variables filter"), "\n", out))
})
output$code_filter <- shiny::renderUI({
shiny::req(rv$code$filter)
prismCodeBlock(paste0("#Data filter\n", rv$code$filter))
prismCodeBlock(paste0("#", i18n$t("Data filter"), "\n", rv$code$filter))
})
output$code_table1 <- shiny::renderUI({
shiny::req(rv$code$table1)
prismCodeBlock(paste0("#Data characteristics table\n", rv$code$table1))
prismCodeBlock(paste0("#", i18n$t("Data characteristics table"), "\n", rv$code$table1))
})
@ -12330,7 +12330,7 @@ server <- function(input, output, session) {
output$data_info_nochar <- shiny::renderUI({
shiny::req(rv$list$data)
data_description(rv$list$data, data_text = "The dataset without text variables")
data_description(rv$list$data, data_text = i18n$t("The dataset without text variables"))
})
## Only allow evaluation if the dataset has fewer then 50 variables
@ -12369,9 +12369,9 @@ server <- function(input, output, session) {
# # stop(glue::glue(i18n$t("The data includes {n_col} variables. Please limit to 100.")))
# print("Please limit to 100.")
# } else {
shiny::withProgress(message = "Creating the table. Hold on for a moment..", {
rv$list$table1 <- rlang::exec(create_baseline, !!!append_list(rv$list$data, parameters, "data"))
})
shiny::withProgress(message = i18n$t("Creating the table. Hold on for a moment.."), {
rv$list$table1 <- rlang::exec(create_baseline, !!!append_list(rv$list$data, parameters, "data"))
})
# }
# },
# error = function(err) {
@ -12399,7 +12399,7 @@ server <- function(input, output, session) {
inputId = "outcome_var_cor",
selected = "none",
data = rv$list$data,
label = "Select outcome variable",
label = i18n$t("Select outcome variable"),
col_subset = c(
"none",
colnames(rv$list$data)
@ -12425,7 +12425,7 @@ server <- function(input, output, session) {
output$missings_var <- shiny::renderUI({
columnSelectInput(
inputId = "missings_var",
label = "Select variable to stratify analysis",
label = i18n$t("Select variable to stratify analysis"),
data = shiny::reactive({
shiny::req(rv$data_filtered)
rv$data_filtered[apply(rv$data_filtered, 2, anyNA)]
@ -12523,7 +12523,7 @@ server <- function(input, output, session) {
rv$list$regression <- rv$regression()
rv$list$missings <- rv$missings()
shiny::withProgress(message = "Generating the report. Hold on for a moment..", {
shiny::withProgress(message = i18n$t("Generating the report. Hold on for a moment.."), {
tryCatch(
{
rv$list |>

View file

@ -8,6 +8,10 @@ a free tool for basic data evaluation and analysis. If you need more
advanced tools, start with <strong><em>FreesearchR</em></strong> and
then youll probably be better off using <em>R</em> or similar
directly.</p>
<p>The <strong><em>FreesearchR</em></strong> app should be available to
as many people as possible, and the interface can be translated to any
language. If you have suggestions or want to help translate, please
reach out on <a href="mailto:info@freesearchr.org">info@freesearchr.org</a>.</p>
<p>With this tool you can:</p>
<ol style="list-style-type: decimal">
<li><p><strong>Import data</strong> from a spreadsheet/file on your

View file

@ -6,6 +6,8 @@ output: html_fragment
This is the ***FreesearchR*** data analysis tool, a free tool for basic data evaluation and analysis. If you need more advanced tools, start with ***FreesearchR*** and then you'll probably be better off using *R* or similar directly.
The ***FreesearchR*** app should be available to as many people as possible, and the interface can be translated to any language. If you have suggestions or want to help translate, please reach out on [info@freesearchr.org](mailto:info@freesearchr.org).
With this tool you can:
1. **Import data** from a spreadsheet/file on your machine, directly from a [REDCap](https://projectredcap.org/ "Read more on the data capture tool REDCap") server, try it with sample data or access data directly [if run in R locally](https://agdamsbo.github.io/FreesearchR//#run-locally-on-your-own-machine "Read about running FreesearchR on your local machine")

View file

@ -20,18 +20,18 @@ eksempel-data eller tilgå data direkte <a href="https://agdamsbo.github.io/Free
afvikler i R lokalt</a></p></li>
<li><p><strong>Forbered</strong> data til analys ved at filtrere, ændre
variabler eller opret helt nye variabler</p></li>
<li><p><strong>Evaluate data</strong> using descriptive analyses methods
and inspect cross-correlations as well as <a href="https://agdamsbo.github.io/FreesearchR/articles/missingness.html" title="Read more about missing data">missing observations</a></p></li>
<li><p><strong>Visualise data</strong> by <a href="https://agdamsbo.github.io/FreesearchR/articles/visuals.html" title="See available plot types">creating simple, clean plots</a> for
overview and quick insights</p></li>
<li><p><strong>Create simple regression models</strong> for even more
advanced data analyses</p></li>
<li><p><strong>Download</strong> results as a report, get the modified
data set and save the code for learning and to reproduce the results
later</p></li>
<li><p><strong>Evaluer data</strong> ved hjælp af beskrivende
analysemetoder og inspicer krydskorrelationer samt <a href="https://agdamsbo.github.io/FreesearchR/articles/missingness.html" title="Læs mere om manglende data">manglende observationer</a></p></li>
<li><p><strong>Visualiser data</strong> ved at <a href="https://agdamsbo.github.io/FreesearchR/articles/visuals.html" title="Se tilgængelige plottyper">oprette enkle, rene plots</a> for
overblik og hurtig indsigt</p></li>
<li><p><strong>Opret simple regressionsmodeller</strong> til endnu mere
avancerede dataanalyser</p></li>
<li><p><strong>Download</strong> resultater som en rapport, hent det
ændrede datasæt og gem koden til læring og til senere reproduktion af
resultaterne</p></li>
</ol>
<p>The full <a href="https://agdamsbo.github.io/FreesearchR/">project
documentation is here</a> where youll find detailed descriptions of the
app and link to the source code! If you want to <a href="https://redcap.au.dk/surveys/?s=JPCLPTXYDKFA8DA8">share feedback,
please follow this link to a simple survey</a>.</p>
<p>Den fulde <a href="https://agdamsbo.github.io/FreesearchR/">projektdokumentation er
her</a>, hvor du finder detaljerede beskrivelser af appen og et link til
kildekoden! Hvis du vil <a href="https://redcap.au.dk/surveys/?s=JPCLPTXYDKFA8DA8">dele feedback,
kan du følge dette link til et enkelt spørgeskema</a>.</p>
</div>

View file

@ -14,12 +14,12 @@ Herunder kan du helt kort se, hvad du kan bruge ***FreesearchR*** til:
2. **Forbered** data til analys ved at filtrere, ændre variabler eller opret helt nye variabler
3. **Evaluate data** using descriptive analyses methods and inspect cross-correlations as well as [missing observations](https://agdamsbo.github.io/FreesearchR/articles/missingness.html "Read more about missing data")
3. **Evaluer data** ved hjælp af beskrivende analysemetoder og inspicer krydskorrelationer samt [manglende observationer](https://agdamsbo.github.io/FreesearchR/articles/missingness.html "Læs mere om manglende data")
4. **Visualise data** by [creating simple, clean plots](https://agdamsbo.github.io/FreesearchR/articles/visuals.html "See available plot types") for overview and quick insights
4. **Visualiser data** ved at [oprette enkle, rene plots](https://agdamsbo.github.io/FreesearchR/articles/visuals.html "Se tilgængelige plottyper") for overblik og hurtig indsigt
5. **Create simple regression models** for even more advanced data analyses
5. **Opret simple regressionsmodeller** til endnu mere avancerede dataanalyser
6. **Download** results as a report, get the modified data set and save the code for learning and to reproduce the results later
6. **Download** resultater som en rapport, hent det ændrede datasæt og gem koden til læring og til senere reproduktion af resultaterne
The full [project documentation is here](https://agdamsbo.github.io/FreesearchR/) where you'll find detailed descriptions of the app and link to the source code! If you want to [share feedback, please follow this link to a simple survey](https://redcap.au.dk/surveys/?s=JPCLPTXYDKFA8DA8).
Den fulde [projektdokumentation er her](https://agdamsbo.github.io/FreesearchR/), hvor du finder detaljerede beskrivelser af appen og et link til kildekoden! Hvis du vil [dele feedback, kan du følge dette link til et enkelt spørgeskema](https://redcap.au.dk/surveys/?s=JPCLPTXYDKFA8DA8).

File diff suppressed because one or more lines are too long

View file

@ -2,7 +2,7 @@
output: html_fragment
---
# Karibu <img src="FreesearchR-logo.png" style="float: right;"/>
# Karibu sana! <img src="FreesearchR-logo.png" style="float: right;"/>
Hii ni ***FreesearchR*** zana ya kuchanganua data, zana isiyolipishwa ya kutathmini na kuchanganua data msingi. Iwapo unahitaji zana za kina zaidi, anza na ***FreesearchR*** na basi pengine utakuwa bora kutumia *R* au sawa moja kwa moja.
@ -10,16 +10,16 @@ Tunajitahidi kutambulisha tafsiri kamili kwa Kiswahili. Ikiwa ungependa kuchangi
Na ***FreesearchR*** unaweza:
1. **Import data** from a spreadsheet/file on your machine, directly from a [REDCap](https://projectredcap.org/ "Read more on the data capture tool REDCap") server, try it with sample data or access data directly [if run in R locally](https://agdamsbo.github.io/FreesearchR//#run-locally-on-your-own-machine "Read about running FreesearchR on your local machine")
1. **Ingiza data** kutoka kwa lahajedwali/faili kwenye mashine yako, moja kwa moja kutoka kwa seva ya [REDCap](https://projectredcap.org/ "Soma zaidi kuhusu zana ya kunasa data ya REDCap"), ijaribu kwa sampuli ya data au ufikie data moja kwa moja [ikiwa inaendeshwa katika R ndani ya nchi](https://agdamsbo.github.io/Freesearchourcal-R/-#ownon-run-your-ruwnon-" FreesearchR kwenye mashine yako ya karibu")
2. **Prepare** data for analysis by filtering data, modifying variables or create new variables
2. **Andaa** data kwa uchanganuzi kwa kuchuja data, kurekebisha vigeu au kuunda vigeu vipya
3. **Evaluate data** using descriptive analyses methods and inspect cross-correlations as well as [missing observations](https://agdamsbo.github.io/FreesearchR/articles/missingness.html "Read more about missing data")
3. **Tathmini data** kwa kutumia mbinu za uchanganuzi wa maelezo na ukague miunganisho mtambuka pamoja na [maoni yanayokosekana](https://agdamsbo.github.io/FreesearchR/articles/missingness.html "Soma zaidi kuhusu kukosa data")
4. **Visualise data** by [creating simple, clean plots](https://agdamsbo.github.io/FreesearchR/articles/visuals.html "See available plot types") for overview and quick insights
4. **Onyesha data** kwa [kuunda viwanja rahisi na safi](https://agdamsbo.github.io/FreesearchR/articles/visuals.html "Angalia aina zinazopatikana za viwanja") kwa muhtasari na maarifa ya haraka
5. **Create simple regression models** for even more advanced data analyses
5. **Unda miundo rahisi ya kurejesha kumbukumbu** kwa uchanganuzi wa hali ya juu zaidi wa data
6. **Download** results as a report, get the modified data set and save the code for learning and to reproduce the results later
6. **Pakua** matokeo kama ripoti, pata seti ya data iliyorekebishwa na uhifadhi msimbo wa kujifunza na kutoa matokeo baadaye
The full [project documentation is here](https://agdamsbo.github.io/FreesearchR/) where you'll find detailed descriptions of the app and link to the source code! If you want to [share feedback, please follow this link to a simple survey](https://redcap.au.dk/surveys/?s=JPCLPTXYDKFA8DA8).
[Hati kamili za mradi ziko hapa](https://agdamsbo.github.io/FreesearchR/) ambapo utapata maelezo ya kina ya programu na kiungo cha msimbo wa chanzo! Iwapo ungependa [kushiriki maoni, tafadhali fuata kiungo hiki cha utafiti rahisi](https://redcap.au.dk/surveys/?s=JPCLPTXYDKFA8DA8).

View file

@ -176,11 +176,11 @@
"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"
"This window is aimed at advanced users and require some *R*-experience!","Dette vindue er primært for avancerede brugere med nogen *R*-erfaring!"
"Create new variables","Opret nye variabler"
"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."
"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.","Her har du en oversigt over hvordan data er blevet formateret, og hvor der er manglende observationer. Brug informationen til at overveje om manglende data mangler tilfældigt eller og der er et mønster, som kan være et udtryk for systematisk manglende data (observationsbias)."
"Specify covariables","Angiv kovariabler"
"If none are selected, all are included.","Hvis ingen er valgt inkluderes alle."
"Analyse","Analysér"
@ -191,67 +191,67 @@
"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"
"Web address","Serveradresse"
"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"
"API token","API-nøgle"
"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"
"Select fields/variables to import and click the funnel to apply optional filters","Vælg variabler, der skal importeres og tryk på tragten for at anvende valgfrie filtre"
"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."
"Click to see data dictionary","Tryk for at se metadata (Data Dictionary)"
"Connected to server!","Forbindelse til serveren oprettet!"
"The {data_rv$info$project_title} project is loaded.","{data_rv$info$project_title}-projektet er forbundet."
"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"
"Import a dataset from an environment","Import a dataset from an environment"
"Preview:","Forsmag:"
"Imported data set","Importeret datasæt"
"Select fields/variables to import:","Vælg variabler, der skal importeres:"
"Specify the data format","Specificér dataformatet"
"Fill missing values?","Skal manglende observationer udfyldes?"
"Requested data was retrieved!","Det udvalgte data blev hentet!"
"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 er hentet, men det ser ud til kun at indeholde ID-variablen. Du skal kontakte din REDCap-administrator og sikre dig at du har adgang til faktisk at hente de udvalgte data."
"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 er hentet, men det ser ud til kun at indeholde nogle af de udvalgte variabler. Du skal kontakte din REDCap-administrator og sikre dig at du har adgang til faktisk at hente de udvalgte data."
"Click to see the imported data","Tryk for at se de importerede data"
"Regression table","Regressionstabel"
"Import a dataset from an environment","Importer et datasæt fra et kodemiljø"
"Select a dataset:","Vælg datasæt:"
"List of datasets...","List of datasets..."
"List of datasets...","Liste af datasæt..."
"No data selected!","Ingen data valgt!"
"Use a datasat from your environment or from the environment of a package.","Use a datasat from your environment or from the environment of a package."
"No dataset here...","Ingen datasæt her..."
"Use a dataset from your environment or from the environment of a package.","Use a dataset from your environment or from the environment of a package."
"Use a dataset from your environment or from the environment of a package.","Brug et datasæt fra dit lokale kodemiljø eller fra en tilgængelig pakke."
"Not a data.frame","Ikke en data.frame"
"Select source","Vælg datakilde"
"Select a data source:","Vælg datakilde:"
"Yes","Ja"
"No","Nej"
"Coefficient plot","Coefficient plot"
"Select outcome variable","Select outcome variable"
"Choose regression analysis","Choose regression analysis"
"Covariables to format as categorical","Covariables to format as categorical"
"Select variable to stratify baseline","Select variable to stratify baseline"
"Select models to plot","Select models to plot"
"Creating regression models failed with the following error:","Creating regression models failed with the following error:"
"Creating a regression table failed with the following error:","Creating a regression table failed with the following error:"
"Saving the plot. Hold on for a moment..","Saving the plot. Hold on for a moment.."
"Running model assumptions checks failed with the following error:","Running model assumptions checks failed with the following error:"
"Select checks to plot","Select checks to plot"
"Multivariable regression model checks","Multivariable regression model checks"
"Grouped by {get_label(data,ter)}","Grouped by {get_label(data,ter)}"
"Option to perform statistical comparisons between strata in baseline table.","Option to perform statistical comparisons between strata in baseline table."
"Press 'Evaluate' to create the comparison table.","Press 'Evaluate' to create the comparison table."
"The data includes {n_col} variables. Please limit to 100.","The data includes {n_col} variables. Please limit to 100."
"Coefficient plot","Koefficientplot"
"Select outcome variable","Vælg svarvariablen"
"Choose regression analysis","Vælg regressionsanalysen"
"Covariables to format as categorical","Kovariabler, der skal omklassificeres som kategoriske"
"Select variable to stratify baseline","Vælg variabel til a stratificere tabellen"
"Select models to plot","Vælg de modeller, der skal visualiseres"
"Creating regression models failed with the following error:","Oprettelsen af en regressionsmodel fejlede med den følgende besked:"
"Creating a regression table failed with the following error:","Oprettelsen af en regressionstabel fejlede med den følgende besked:"
"Saving the plot. Hold on for a moment..","Gemmer grafikken. Vent et øjeblik.."
"Running model assumptions checks failed with the following error:","Tjek af antagelser for regressionsmodellen fejlede med den følgende besked:"
"Select checks to plot","Vælg modeltests, der skal visualiseres"
"Multivariable regression model checks","Tests af multivariabel regressionsmodel"
"Grouped by {get_label(data,ter)}","Grupperet efter {get_label(data,ter)}"
"Option to perform statistical comparisons between strata in baseline table.","Mulighed for at udføre statistiske tests mellem strata i oversigtstabellen."
"Press 'Evaluate' to create the comparison table.","Tryk 'Evaluér' for at oprette en oversigtstabel."
"The data includes {n_col} variables. Please limit to 100.","Data indeholder {n_col} variabler. Begræns venligst til 100."
"Data import","Data import"
"Data import formatting","Data import formatting"
"Data modifications","Data modifications"
"Data import formatting","Formatering af data ved import"
"Data modifications","Ændringer af data"
"Variables filter","Variables filter"
"Data filter","Data filter"
"Data characteristics table","Data characteristics table"
"The dataset without text variables","The dataset without text variables"
"Creating the table. Hold on for a moment..","Creating the table. Hold on for a moment.."
"Select variable to stratify analysis","Select variable to stratify analysis"
"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."
"Data characteristics table","Oversigtstabel"
"The dataset without text variables","Datasættet uden variabler formateret som tekst"
"Creating the table. Hold on for a moment..","Opretter tabellen. Vent et øjeblik.."
"Select variable to stratify analysis","Vælg variabler til at stratificere analysen"
"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'."

1 en da
176 Confirm Bekræft
177 The filtered data Filtreret data
178 Create new factor Ny kategorisk variabel
179 This window is aimed at advanced users and require some *R*-experience! This window is aimed at advanced users and require some *R*-experience! Dette vindue er primært for avancerede brugere med nogen *R*-erfaring!
180 Create new variables Opret ny variabel Opret nye variabler
181 Select data types to include Vælg datatyper, der skal inkluderes
182 Uploaded data overview Overblik over uploaded data
183 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. Her har du en oversigt over hvordan data er blevet formateret, og hvor der er manglende observationer. Brug informationen til at overveje om manglende data mangler tilfældigt eller og der er et mønster, som kan være et udtryk for systematisk manglende data (observationsbias).
184 Specify covariables Angiv kovariabler
185 If none are selected, all are included. Hvis ingen er valgt inkluderes alle.
186 Analyse Analysér
191 Please confirm data reset! Bekræft gendannelse af data!
192 Import data from REDCap Importér data fra REDCap
193 REDCap server REDCap-server
194 Web address Web address Serveradresse
195 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/'
196 API token API token API-nøgle
197 The token is a string of 32 numbers and letters. En API-nøgle består af ialt 32 tal og bogstaver.
198 Connect Forbind
199 Data import parameters Data import parameters
200 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 Vælg variabler, der skal importeres og tryk på tragten for at anvende valgfrie filtre
201 Import Import
202 Click to see data dictionary Click to see data dictionary Tryk for at se metadata (Data Dictionary)
203 Connected to server! Connected to server! Forbindelse til serveren oprettet!
204 The {data_rv$info$project_title} project is loaded. The {data_rv$info$project_title} project is loaded. {data_rv$info$project_title}-projektet er forbundet.
205 Data dictionary Data dictionary
206 Preview: Preview: Forsmag:
207 Imported data set Imported data set Importeret datasæt
208 Select fields/variables to import: Select fields/variables to import: Vælg variabler, der skal importeres:
209 Specify the data format Specify the data format Specificér dataformatet
210 Fill missing values? Fill missing values? Skal manglende observationer udfyldes?
211 Requested data was retrieved! Requested data was retrieved! Det udvalgte data blev hentet!
212 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 er hentet, men det ser ud til kun at indeholde ID-variablen. Du skal kontakte din REDCap-administrator og sikre dig at du har adgang til faktisk at hente de udvalgte data.
213 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. Data er hentet, men det ser ud til kun at indeholde nogle af de udvalgte variabler. Du skal kontakte din REDCap-administrator og sikre dig at du har adgang til faktisk at hente de udvalgte data.
214 Click to see the imported data Click to see the imported data Tryk for at se de importerede data
215 Regression table Regression table Regressionstabel
216 Import a dataset from an environment Import a dataset from an environment Importer et datasæt fra et kodemiljø
217 Select a dataset: Vælg datasæt:
218 List of datasets... List of datasets... Liste af datasæt...
219 No data selected! Ingen data valgt!
Use a datasat from your environment or from the environment of a package. Use a datasat from your environment or from the environment of a package.
220 No dataset here... Ingen datasæt her...
221 Use a dataset from your environment or from the environment of a package. Use a dataset from your environment or from the environment of a package. Brug et datasæt fra dit lokale kodemiljø eller fra en tilgængelig pakke.
222 Not a data.frame Ikke en data.frame
223 Select source Vælg datakilde
224 Select a data source: Vælg datakilde:
225 Yes Ja
226 No Nej
227 Coefficient plot Coefficient plot Koefficientplot
228 Select outcome variable Select outcome variable Vælg svarvariablen
229 Choose regression analysis Choose regression analysis Vælg regressionsanalysen
230 Covariables to format as categorical Covariables to format as categorical Kovariabler, der skal omklassificeres som kategoriske
231 Select variable to stratify baseline Select variable to stratify baseline Vælg variabel til a stratificere tabellen
232 Select models to plot Select models to plot Vælg de modeller, der skal visualiseres
233 Creating regression models failed with the following error: Creating regression models failed with the following error: Oprettelsen af en regressionsmodel fejlede med den følgende besked:
234 Creating a regression table failed with the following error: Creating a regression table failed with the following error: Oprettelsen af en regressionstabel fejlede med den følgende besked:
235 Saving the plot. Hold on for a moment.. Saving the plot. Hold on for a moment.. Gemmer grafikken. Vent et øjeblik..
236 Running model assumptions checks failed with the following error: Running model assumptions checks failed with the following error: Tjek af antagelser for regressionsmodellen fejlede med den følgende besked:
237 Select checks to plot Select checks to plot Vælg modeltests, der skal visualiseres
238 Multivariable regression model checks Multivariable regression model checks Tests af multivariabel regressionsmodel
239 Grouped by {get_label(data,ter)} Grouped by {get_label(data,ter)} Grupperet efter {get_label(data,ter)}
240 Option to perform statistical comparisons between strata in baseline table. Option to perform statistical comparisons between strata in baseline table. Mulighed for at udføre statistiske tests mellem strata i oversigtstabellen.
241 Press 'Evaluate' to create the comparison table. Press 'Evaluate' to create the comparison table. Tryk 'Evaluér' for at oprette en oversigtstabel.
242 The data includes {n_col} variables. Please limit to 100. The data includes {n_col} variables. Please limit to 100. Data indeholder {n_col} variabler. Begræns venligst til 100.
243 Data import Data import
244 Data import formatting Data import formatting Formatering af data ved import
245 Data modifications Data modifications Ændringer af data
246 Variables filter Variables filter
247 Data filter Data filter
248 Data characteristics table Data characteristics table Oversigtstabel
249 The dataset without text variables The dataset without text variables Datasættet uden variabler formateret som tekst
250 Creating the table. Hold on for a moment.. Creating the table. Hold on for a moment.. Opretter tabellen. Vent et øjeblik..
251 Select variable to stratify analysis Select variable to stratify analysis Vælg variabler til at stratificere analysen
252 Generating the report. Hold on for a moment.. Generating the report. Hold on for a moment.. Opretter rapporten. Vent et øjeblik..
253 We encountered the following error showing missingness: We encountered the following error showing missingness: Under analysen af manglende observationer opstod følgende fejl:
254 We encountered the following error browsing your data: We encountered the following error browsing your data: I forsøget på at vise en dataoversigt opstod følgende fejl:
255 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. 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.
256 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. 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.
257 Please fill in web address and API token, then press 'Connect'. Udfyld serveradresse og API-nøgle, og tryk så 'Fobind'.

View file

@ -217,7 +217,6 @@
"Select a dataset:","Select a dataset:"
"List of datasets...","List of datasets..."
"No data selected!","No data selected!"
"Use a datasat from your environment or from the environment of a package.","Use a datasat from your environment or from the environment of a package."
"No dataset here...","No dataset here..."
"Use a dataset from your environment or from the environment of a package.","Use a dataset from your environment or from the environment of a package."
"Not a data.frame","Not a data.frame"
@ -255,3 +254,4 @@
"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."
"Please fill in web address and API token, then press 'Connect'.","Please fill in web address and API token, then press 'Connect'."

1 en sw
217 Select a dataset: Select a dataset:
218 List of datasets... List of datasets...
219 No data selected! No data selected!
Use a datasat from your environment or from the environment of a package. Use a datasat from your environment or from the environment of a package.
220 No dataset here... No dataset here...
221 Use a dataset from your environment or from the environment of a package. Use a dataset from your environment or from the environment of a package.
222 Not a data.frame Not a data.frame
254 We encountered the following error browsing your data: We encountered the following error browsing your data:
255 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.
256 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.
257 Please fill in web address and API token, then press 'Connect'. Please fill in web address and API token, then press 'Connect'.

View file

@ -39,5 +39,5 @@ data.frame(
plot_sankey_single("first", "last", color.group = "pri")
mtcars |>
default_parsing() |>
plot_sankey_single("cyl", "vs", color.group = "pri")
plot_sankey_single("cyl", "vs", color.group = "pri")
}