diff --git a/DESCRIPTION b/DESCRIPTION
index 2330ff7..9cfd9f5 100644
--- a/DESCRIPTION
+++ b/DESCRIPTION
@@ -36,7 +36,6 @@ Imports:
patchwork,
easystats,
DHARMa,
- teal,
IDEAFilter,
sparkline,
datamods,
@@ -52,7 +51,6 @@ Imports:
rlang,
data.table,
apexcharter,
- teal.modules.general,
esquisse,
janitor,
flextable,
@@ -64,7 +62,9 @@ Imports:
psych,
jtools,
Hmisc,
- ggstats
+ ggstats,
+ rempsyc,
+ ggridges
Suggests:
styler,
devtools,
diff --git a/NEWS.md b/NEWS.md
index 1fd7b4c..38c8584 100644
--- a/NEWS.md
+++ b/NEWS.md
@@ -4,6 +4,25 @@ First steps towards a more focused and simplified interface.
Focus will be on ease of use, handling basic functionality for data inspection and descriptive analyses.
+Inspired by the Stroke Center implementation guidelines of the WSO, we will apply a similar approach to this project in order to keep the interface simple and robust. Basic functions for descriptive analyses and data browsing are the basics. More advanced features like regression analyses are added for learning purposes, but really should be done by one self in software like *R* to ensure learning and reproducibility.
+
+Teal dependencies removed. The teal framework really seems very powerful and promising, but it will also mean less control and more clutter. May come up again later.
+
+All main components have been implemented.
+
+Next steps are:
+
+- Polished code export
+
+- Improved workflow and thorough step-wise guide/documentation
+
+- Implement in clinical projects
+
+- Implement in data analysis courses
+
+- Extensive testing and bug squashing
+
+
# freesearcheR 25.1.1
* UI tweaks.
diff --git a/QA.md b/QA.md
new file mode 100644
index 0000000..d200e37
--- /dev/null
+++ b/QA.md
@@ -0,0 +1,8 @@
+# Questions and answers
+
+A complete instructions set is not available, but below are a collection of questions and answers about the project and use of the app.
+
+## Are you keeping the uploaded data?
+
+No! All uploaded data is deleted when the session ends, so only stored for your analyses and the immediately deleted.
+
diff --git a/R/app_version.R b/R/app_version.R
index 4eb7c71..c5ebbf0 100644
--- a/R/app_version.R
+++ b/R/app_version.R
@@ -1 +1 @@
-app_version <- function()'250207_1709'
+app_version <- function()'250225_0948'
diff --git a/R/columnSelectInput.R b/R/columnSelectInput.R
new file mode 100644
index 0000000..a761392
--- /dev/null
+++ b/R/columnSelectInput.R
@@ -0,0 +1,82 @@
+#' A selectizeInput customized for data frames with column labels
+#'
+#' @description
+#' Copied and modified from the IDEAFilter package
+#' Adds the option to select "none" which is handled later
+#'
+#' @param inputId passed to \code{\link[shiny]{selectizeInput}}
+#' @param label passed to \code{\link[shiny]{selectizeInput}}
+#' @param data \code{data.frame} object from which fields should be populated
+#' @param selected default selection
+#' @param ... passed to \code{\link[shiny]{selectizeInput}}
+#' @param col_subset a \code{vector} containing the list of allowable columns to select
+#' @param placeholder passed to \code{\link[shiny]{selectizeInput}} options
+#' @param onInitialize passed to \code{\link[shiny]{selectizeInput}} options
+#' @param none_label label for "none" item
+#'
+#' @return a \code{\link[shiny]{selectizeInput}} dropdown element
+#'
+#' @importFrom shiny selectizeInput
+#' @keywords internal
+#'
+columnSelectInput <- function(inputId, label, data, selected = "", ...,
+ col_subset = NULL, placeholder = "", onInitialize, none_label="No variable selected") {
+ datar <- if (is.reactive(data)) data else reactive(data)
+ col_subsetr <- if (is.reactive(col_subset)) col_subset else reactive(col_subset)
+
+ labels <- Map(function(col) {
+ json <- sprintf(
+ IDEAFilter:::strip_leading_ws('
+ {
+ "name": "%s",
+ "label": "%s",
+ "datatype": "%s"
+ }'),
+ col,
+ attr(datar()[[col]], "label") %||% "",
+ IDEAFilter:::get_dataFilter_class(datar()[[col]])
+ )
+ }, col = names(datar()))
+
+ if (!"none" %in% names(datar())){
+ labels <- c("none"=list(sprintf('\n {\n \"name\": \"none\",\n \"label\": \"%s\",\n \"datatype\": \"\"\n }',none_label)),labels)
+ choices <- setNames(names(labels), labels)
+ choices <- choices[match(if (length(col_subsetr()) == 0 || isTRUE(col_subsetr() == "")) names(datar()) else col_subsetr(), choices)]
+ } else {
+ choices <- setNames(names(datar()), labels)
+ choices <- choices[match(if (length(col_subsetr()) == 0 || isTRUE(col_subsetr() == "")) choices else col_subsetr(), choices)]
+ }
+
+ shiny::selectizeInput(
+ inputId = inputId,
+ label = label,
+ choices = choices,
+ selected = selected,
+ ...,
+ options = c(
+ list(render = I("{
+ // format the way that options are rendered
+ option: function(item, escape) {
+ item.data = JSON.parse(item.label);
+ return '
' +
+ '
' +
+ escape(item.data.name) + ' ' +
+ ' ' +
+ item.data.datatype +
+ '
' +
+ '
' +
+ (item.data.label != '' ? '
' + escape(item.data.label) + '
' : '') +
+ '
';
+ },
+
+ // avoid data vomit splashing on screen when an option is selected
+ item: function(item, escape) {
+ item.data = JSON.parse(item.label);
+ return '' +
+ escape(item.data.name) +
+ '
';
+ }
+ }"))
+ )
+ )
+}
diff --git a/R/contrast_text.R b/R/contrast_text.R
new file mode 100644
index 0000000..9ea4c5b
--- /dev/null
+++ b/R/contrast_text.R
@@ -0,0 +1,51 @@
+#' @title Contrast Text Color
+#' @description Calculates the best contrast text color for a given
+#' background color.
+#' @param background A hex/named color value that represents the background.
+#' @param light_text A hex/named color value that represents the light text
+#' color.
+#' @param dark_text A hex/named color value that represents the dark text color.
+#' @param threshold A numeric value between 0 and 1 that is used to determine
+#' the luminance threshold of the background color for text color.
+#' @param method A character string that specifies the method for calculating
+#' the luminance. Three different methods are available:
+#' c("relative","perceived","perceived_2")
+#' @param ... parameter overflow. Ignored.
+#' @details
+#' This function aids in deciding the font color to print on a given background.
+#' The function is based on the example provided by teppo:
+#' https://stackoverflow.com/a/66669838/21019325.
+#' The different methods provided are based on the methods outlined in the
+#' StackOverflow thread:
+#' https://stackoverflow.com/questions/596216/formula-to-determine-perceived-brightness-of-rgb-color
+#' @return A character string that contains the best contrast text color.
+#' @examples
+#' contrast_text(c("#F2F2F2", "blue"))
+#'
+#' contrast_text(c("#F2F2F2", "blue"), method="relative")
+#' @export
+#'
+#' @importFrom grDevices col2rgb
+#'
+contrast_text <- function(background,
+ light_text = 'white',
+ dark_text = 'black',
+ threshold = 0.5,
+ method = "perceived_2",
+ ...) {
+ if (method == "relative") {
+ luminance <-
+ c(c(.2126, .7152, .0722) %*% grDevices::col2rgb(background) / 255)
+ } else if (method == "perceived") {
+ luminance <-
+ c(c(.299, .587, .114) %*% grDevices::col2rgb(background) / 255)
+ } else if (method == "perceived_2") {
+ luminance <- c(sqrt(colSums((
+ c(.299, .587, .114) * grDevices::col2rgb(background)
+ ) ^ 2)) / 255)
+ }
+
+ ifelse(luminance < threshold,
+ light_text,
+ dark_text)
+}
diff --git a/R/data_plots.R b/R/data_plots.R
new file mode 100644
index 0000000..484e83a
--- /dev/null
+++ b/R/data_plots.R
@@ -0,0 +1,619 @@
+# source(here::here("functions.R"))
+
+#' Data correlations evaluation module
+#'
+#' @param id Module id. (Use 'ns("id")')
+#'
+#' @name data-correlations
+#' @returns Shiny ui module
+#' @export
+#'
+data_visuals_ui <- function(id, tab_title="Plots", ...) {
+ ns <- shiny::NS(id)
+
+ # bslib::navset_bar(
+ list(
+
+ # Sidebar with a slider input
+ sidebar = bslib::sidebar(
+ bslib::accordion(
+ multiple = FALSE,
+ bslib::accordion_panel(
+ title = "Creating plot",
+ icon = bsicons::bs_icon("graph-up"),
+ shiny::uiOutput(outputId = ns("primary")),
+ shiny::uiOutput(outputId = ns("type")),
+ shiny::uiOutput(outputId = ns("secondary")),
+ shiny::uiOutput(outputId = ns("tertiary"))
+ ),
+ bslib::accordion_panel(
+ title = "Advanced",
+ icon = bsicons::bs_icon("gear")
+ ),
+ bslib::accordion_panel(
+ title = "Download",
+ icon = bsicons::bs_icon("download"),
+ shinyWidgets::noUiSliderInput(
+ inputId = ns("height"),
+ label = "Plot height (mm)",
+ min = 50,
+ max = 300,
+ value = 100,
+ step = 1,
+ format = shinyWidgets::wNumbFormat(decimals=0),
+ color = datamods:::get_primary_color()
+ ),
+ shinyWidgets::noUiSliderInput(
+ inputId = ns("width"),
+ label = "Plot width (mm)",
+ min = 50,
+ max = 300,
+ value = 100,
+ step = 1,
+ format = shinyWidgets::wNumbFormat(decimals=0),
+ color = datamods:::get_primary_color()
+ ),
+ shiny::selectInput(
+ inputId = ns("plot_type"),
+ label = "File format",
+ choices = list(
+ "png",
+ "tiff",
+ "eps",
+ "pdf",
+ "jpeg",
+ "svg"
+ )
+ ),
+ shiny::br(),
+ # Button
+ shiny::downloadButton(
+ outputId = ns("download_plot"),
+ label = "Download plot",
+ icon = shiny::icon("download")
+ )
+ )
+ )
+ ),
+ bslib::nav_panel(
+ title = tab_title,
+ shiny::plotOutput(ns("plot"))
+ )
+ )
+}
+
+
+#'
+#' @param data data
+#' @param ... ignored
+#'
+#' @name data-correlations
+#' @returns shiny server module
+#' @export
+data_visuals_server <- function(id,
+ data,
+ ...) {
+ shiny::moduleServer(
+ id = id,
+ module = function(input, output, session) {
+ ns <- session$ns
+
+ rv <- shiny::reactiveValues(
+ plot.params = NULL,
+ plot = NULL
+ )
+
+ output$primary <- shiny::renderUI({
+ columnSelectInput(
+ inputId = ns("primary"),
+ data = data,
+ placeholder = "Select variable",
+ label = "Response variable",
+ multiple = FALSE
+ )
+ })
+
+
+ output$type <- shiny::renderUI({
+ shiny::req(input$primary)
+ # browser()
+
+ if (!input$primary %in% names(data())) {
+ plot_data <- data()[1]
+ } else {
+ plot_data <- data()[input$primary]
+ }
+
+ plots <- possible_plots(
+ data = plot_data
+ )
+
+ shiny::selectizeInput(
+ inputId = ns("type"),
+ selected = NULL,
+ label = shiny::h4("Plot type"),
+ choices = plots,
+ multiple = FALSE
+ )
+ })
+
+ rv$plot.params <- shiny::reactive({
+ get_plot_options(input$type)
+ })
+
+ output$secondary <- shiny::renderUI({
+ shiny::req(input$type)
+ # browser()
+
+ columnSelectInput(
+ inputId = ns("secondary"),
+ data = data,
+ placeholder = "Select variable",
+ label = "Secondary/group variable",
+ multiple = FALSE,
+ col_subset = c(
+ purrr::pluck(rv$plot.params(), 1)[["secondary.extra"]],
+ all_but(
+ colnames(subset_types(
+ data(),
+ purrr::pluck(rv$plot.params(), 1)[["secondary.type"]]
+ )),
+ input$primary
+ )
+ ),
+ none_label = "No variable"
+ )
+
+ })
+
+ output$tertiary <- shiny::renderUI({
+ shiny::req(input$type)
+ columnSelectInput(
+ inputId = ns("tertiary"),
+ data = data,
+ placeholder = "Select variable",
+ label = "Strata variable",
+ multiple = FALSE,
+ col_subset = c(
+ "none",
+ all_but(
+ colnames(subset_types(
+ data(),
+ purrr::pluck(rv$plot.params(), 1)[["tertiary.type"]]
+ )),
+ input$primary,
+ input$secondary
+ )
+ ),
+ none_label = "No stratification"
+ )
+ })
+
+ rv$plot <- shiny::reactive({
+ shiny::req(input$primary)
+ shiny::req(input$type)
+ shiny::req(input$secondary)
+ shiny::req(input$tertiary)
+ create_plot(
+ data = data(),
+ type = names(rv$plot.params()),
+ x = input$primary,
+ y = input$secondary,
+ z = input$tertiary
+ )
+ })
+
+ output$plot <- shiny::renderPlot({
+ rv$plot()
+ })
+
+ output$download_plot <- shiny::downloadHandler(
+ filename = shiny::reactive({
+ paste0("plot.", input$plot_type)
+ }),
+ content = function(file) {
+ shiny::withProgress(message = "Drawing the plot. Hold on for a moment..", {
+ ggplot2::ggsave(filename = file,
+ plot = rv$plot(),
+ width = input$width,
+ height = input$height,
+ dpi = 300,
+ units = "mm",scale = 2)
+ })
+ }
+ )
+
+
+ shiny::observe(
+ return(rv$plot)
+ )
+ }
+ )
+}
+
+
+
+#' Select all from vector but
+#'
+#' @param data vector
+#' @param ... exclude
+#'
+#' @returns
+#' @export
+#'
+#' @examples
+#' all_but(1:10, c(2, 3), 11, 5)
+all_but <- function(data, ...) {
+ data[!data %in% c(...)]
+}
+
+#' Easily subset by data type function
+#'
+#' @param data data
+#' @param types desired types
+#' @param type.fun function to get type. Default is outcome_type
+#'
+#' @returns
+#' @export
+#'
+#' @examples
+#' default_parsing(mtcars) |> subset_types("ordinal")
+#' default_parsing(mtcars) |> subset_types(c("dichotomous", "ordinal"))
+#' #' default_parsing(mtcars) |> subset_types("factor",class)
+subset_types <- function(data, types, type.fun = outcome_type) {
+ data[sapply(data, type.fun) %in% types]
+}
+
+
+#' Implemented functions
+#'
+#' @description
+#' Library of supported functions. The list name and "descr" element should be
+#' unique for each element on list.
+#'
+#' - descr: Plot description
+#'
+#' - primary.type: Primary variable data type (continuous, dichotomous or ordinal)
+#'
+#' - secondary.type: Secondary variable data type (continuous, dichotomous or ordinal)
+#'
+#' - secondary.extra: "none" or NULL to have option to choose none.
+#'
+#' - tertiary.type: Tertiary variable data type (continuous, dichotomous or ordinal)
+#'
+#'
+#' @returns list
+#' @export
+#'
+#' @examples
+#' supported_plots() |> str()
+supported_plots <- function() {
+ list(
+ plot_hbars = list(
+ descr = "Stacked horizontal bars (Grotta bars)",
+ primary.type = c("dichotomous", "ordinal"),
+ secondary.type = c("dichotomous", "ordinal"),
+ tertiary.type = c("dichotomous", "ordinal"),
+ secondary.extra = "none"
+ ),
+ plot_violin = list(
+ descr = "Violin plot",
+ primary.type = c("continuous", "dichotomous", "ordinal"),
+ secondary.type = c("dichotomous", "ordinal"),
+ tertiary.type = c("dichotomous", "ordinal"),
+ secondary.extra = "none"
+ ),
+ plot_ridge = list(
+ descr = "Ridge plot",
+ primary.type = "continuous",
+ secondary.type = c("dichotomous", "ordinal"),
+ tertiary.type = c("dichotomous", "ordinal"),
+ secondary.extra = NULL
+ ),
+ plot_scatter = list(
+ descr = "Scatter plot",
+ primary.type = "continuous",
+ secondary.type = c("continuous", "ordinal"),
+ tertiary.type = c("dichotomous", "ordinal"),
+ secondary.extra = NULL
+ )
+ )
+}
+
+#' Title
+#'
+#' @returns
+#' @export
+#'
+#' @examples
+#' mtcars |>
+#' default_parsing() |>
+#' plot_ridge(x = "mpg", y = "cyl")
+#' mtcars |> plot_ridge(x = "mpg", y = "cyl", z = "gear")
+plot_ridge <- function(data, x, y, z = NULL, ...) {
+ if (!is.null(z)) {
+ ds <- split(data, data[z])
+ } else {
+ ds <- list(data)
+ }
+
+ out <- lapply(ds, \(.ds){
+ ggplot2::ggplot(.ds, ggplot2::aes(x = !!dplyr::sym(x), y = !!dplyr::sym(y), fill = !!dplyr::sym(y))) +
+ ggridges::geom_density_ridges() +
+ ggridges::theme_ridges() +
+ ggplot2::theme(legend.position = "none") |> rempsyc:::theme_apa()
+ })
+
+ patchwork::wrap_plots(out)
+}
+
+
+#' Get possible regression models
+#'
+#' @param data data
+#'
+#' @returns character vector
+#' @export
+#'
+#' @examples
+#' mtcars |>
+#' default_parsing() |>
+#' dplyr::pull("cyl") |>
+#' possible_plots()
+#'
+#' mtcars |>
+#' default_parsing() |>
+#' dplyr::select("mpg") |>
+#' possible_plots()
+possible_plots <- function(data) {
+ # browser()
+ if (is.data.frame(data)) {
+ data <- data[[1]]
+ }
+
+ type <- outcome_type(data)
+
+ if (type == "unknown") {
+ out <- type
+ } else {
+ out <- supported_plots() |>
+ lapply(\(.x){
+ if (type %in% .x$primary.type) {
+ .x$descr
+ }
+ }) |>
+ unlist()
+ }
+ unname(out)
+}
+
+#' Get the function options based on the selected function description
+#'
+#' @param data vector
+#'
+#' @returns list
+#' @export
+#'
+#' @examples
+#' ls <- mtcars |>
+#' default_parsing() |>
+#' dplyr::pull(mpg) |>
+#' possible_plots() |>
+#' (\(.x){
+#' .x[[1]]
+#' })() |>
+#' get_plot_options()
+get_plot_options <- function(data) {
+ descrs <- supported_plots() |>
+ lapply(\(.x){
+ .x$descr
+ }) |>
+ unlist()
+ supported_plots() |>
+ (\(.x){
+ .x[match(data, descrs)]
+ })()
+}
+
+
+
+#' Wrapper to create plot based on provided type
+#'
+#' @param type plot type (derived from possible_plots() and matches custom function)
+#' @param ... ignored for now
+#'
+#' @returns
+#' @export
+#'
+#' @examples
+#' create_plot(mtcars, "plot_violin", "mpg", "cyl")
+create_plot <- function(data, type, x, y, z = NULL, ...) {
+ if (!y %in% names(data)) {
+ y <- NULL
+ }
+
+ if (!z %in% names(data)) {
+ z <- NULL
+ }
+
+ do.call(
+ type,
+ list(data, x, y, z, ...)
+ )
+}
+
+
+#' Nice horizontal stacked bars (Grotta bars)
+#'
+#' @returns ggplot2 object
+#' @export
+#'
+#' @examples
+#' mtcars |> plot_hbars(x = "carb", y = "cyl")
+#' mtcars |> plot_hbars(x = "carb", y = NULL)
+plot_hbars <- function(data, x, y, z = NULL) {
+ out <- vertical_stacked_bars(data = data, score = x, group = y, strata = z)
+
+ out
+}
+
+
+#' Vertical stacked bar plot wrapper
+#'
+#' @param data
+#' @param score
+#' @param group
+#' @param strata
+#' @param t.size
+#'
+#' @return
+#' @export
+#'
+vertical_stacked_bars <- function(data,
+ score = "full_score",
+ group = "pase_0_q",
+ strata = NULL,
+ t.size = 10,
+ l.color = "black",
+ l.size = .5,
+ draw.lines = TRUE) {
+ if (is.null(group)) {
+ df.table <- data[c(score, group, strata)] |>
+ dplyr::mutate("All" = 1) |>
+ table()
+ group <- "All"
+ draw.lines <- FALSE
+ } else {
+ df.table <- data[c(score, group, strata)] |>
+ table()
+ }
+
+ p <- df.table |>
+ rankinPlot::grottaBar(
+ scoreName = score,
+ groupName = group,
+ textColor = c("black", "white"),
+ strataName = strata,
+ textCut = 6,
+ textSize = 20,
+ printNumbers = "none",
+ lineSize = l.size,
+ returnData = TRUE
+ )
+
+ colors <- viridisLite::viridis(nrow(df.table))
+ contrast_cut <-
+ sum(contrast_text(colors, threshold = .3) == "white")
+
+ score_label <- ifelse(is.na(REDCapCAST::get_attr(data$score, "label")), score, REDCapCAST::get_attr(data$score, "label"))
+ group_label <- ifelse(is.na(REDCapCAST::get_attr(data$group, "label")), group, REDCapCAST::get_attr(data$group, "label"))
+
+
+ p |>
+ (\(.x){
+ .x$plot +
+ ggplot2::geom_text(
+ data = .x$rectData[which(.x$rectData$n >
+ 0), ],
+ size = t.size,
+ fontface = "plain",
+ ggplot2::aes(
+ x = group,
+ y = p_prev + 0.49 * p,
+ color = as.numeric(score) > contrast_cut,
+ # label = paste0(sprintf("%2.0f", 100 * p),"%"),
+ label = sprintf("%2.0f", 100 * p)
+ )
+ ) +
+ ggplot2::labs(fill = score_label) +
+ ggplot2::scale_fill_manual(values = rev(colors)) +
+ ggplot2::theme(
+ legend.position = "bottom",
+ axis.title = ggplot2::element_text(),
+ ) +
+ ggplot2::xlab(group_label) +
+ ggplot2::ylab(NULL)
+ # viridis::scale_fill_viridis(discrete = TRUE, direction = -1, option = "D")
+ })()
+}
+
+
+#' Print label, and if missing print variable name
+#'
+#' @param data vector or data frame
+#'
+#' @returns character string
+#' @export
+#'
+#' @examples
+#' mtcars |> get_label(var = "mpg")
+#' mtcars$mpg |> get_label()
+#' gtsummary::trial |> get_label(var = "trt")
+#' 1:10 |> get_label()
+get_label <- function(data, var = NULL) {
+ if (!is.null(var)) {
+ data <- data[[var]]
+ }
+
+ out <- REDCapCAST::get_attr(data = data, attr = "label")
+ if (is.na(out)) {
+ if (is.null(var)) {
+ out <- deparse(substitute(data))
+ } else {
+ out <- gsub('\"', "", deparse(substitute(var)))
+ }
+ }
+ out
+}
+
+
+#' Beatiful violin plot
+#'
+#' @returns ggplot2 object
+#' @export
+#'
+#' @examples
+#' mtcars |> plot_violin(x = "mpg", y = "cyl", z = "gear")
+plot_violin <- function(data, x, y, z = NULL) {
+ if (!is.null(z)) {
+ ds <- split(data, data[z])
+ } else {
+ ds <- list(data)
+ }
+
+ out <- lapply(ds, \(.ds){
+ rempsyc::nice_violin(
+ data = .ds,
+ group = y,
+ response = x, xtitle = get_label(data, var = x), ytitle = get_label(data, var = y)
+ )
+ })
+
+ patchwork::wrap_plots(out)
+}
+
+
+#' Beatiful violin plot
+#'
+#' @returns ggplot2 object
+#' @export
+#'
+#' @examples
+#' mtcars |> plot_scatter(x = "mpg", y = "wt")
+plot_scatter <- function(data, x, y, z = NULL) {
+ if (is.null(z)) {
+ rempsyc::nice_scatter(
+ data = data,
+ predictor = y,
+ response = x, xtitle = get_label(data, var = x), ytitle = get_label(data, var = y)
+ )
+ } else {
+ rempsyc::nice_scatter(
+ data = data,
+ predictor = y,
+ response = x,
+ group = z
+ )
+ }
+}
+
diff --git a/R/file-import-module.R b/R/file-import-module.R
index 8210fc8..353c989 100644
--- a/R/file-import-module.R
+++ b/R/file-import-module.R
@@ -95,31 +95,31 @@ file_app <- function() {
file_app()
-tdm_data_upload <- teal::teal_data_module(
- ui <- function(id) {
- shiny::fluidPage(
- m_datafileUI(id)
- )
- },
- server = function(id) {
- m_datafileServer(id, output.format = "teal")
- }
-)
-
-tdm_data_read <- teal::teal_data_module(
- ui <- function(id) {
- shiny::fluidPage(
- m_redcap_readUI(id = "redcap")
- )
- },
- server = function(id) {
- moduleServer(
- id,
- function(input, output, session) {
- ns <- session$ns
-
- m_redcap_readServer(id = "redcap", output.format = "teal")
- }
- )
- }
-)
+# tdm_data_upload <- teal::teal_data_module(
+# ui <- function(id) {
+# shiny::fluidPage(
+# m_datafileUI(id)
+# )
+# },
+# server = function(id) {
+# m_datafileServer(id, output.format = "teal")
+# }
+# )
+#
+# tdm_data_read <- teal::teal_data_module(
+# ui <- function(id) {
+# shiny::fluidPage(
+# m_redcap_readUI(id = "redcap")
+# )
+# },
+# server = function(id) {
+# moduleServer(
+# id,
+# function(input, output, session) {
+# ns <- session$ns
+#
+# m_redcap_readServer(id = "redcap", output.format = "teal")
+# }
+# )
+# }
+# )
diff --git a/R/helpers.R b/R/helpers.R
index 5051bfd..8b8340b 100644
--- a/R/helpers.R
+++ b/R/helpers.R
@@ -266,3 +266,29 @@ remove_empty_cols <- function(data,cutoff=.7){
}) >= cutoff
data[filter]
}
+
+
+#' Append list with named index
+#'
+#' @param data data to add to list
+#' @param list list
+#' @param index index name
+#'
+#' @returns list
+#'
+#' @examples
+#' ls_d <- list(test=c(1:20))
+#' ls_d <- list()
+#' data.frame(letters[1:20],1:20) |> append_list(ls_d,"letters")
+#' letters[1:20]|> append_list(ls_d,"letters")
+append_list <- function(data,list,index){
+ ## This will overwrite and not warn
+ ## Not very safe, but convenient to append code to list
+ if (index %in% names(list)){
+ list[[index]] <- data
+ out <- list
+ } else {
+ out <- setNames(c(list,list(data)),c(names(list),index))
+ }
+ out
+}
diff --git a/R/redcap_read_shiny_module.R b/R/redcap_read_shiny_module.R
index bdcfb4c..96224b0 100644
--- a/R/redcap_read_shiny_module.R
+++ b/R/redcap_read_shiny_module.R
@@ -271,19 +271,19 @@ m_redcap_readServer <- function(id, output.format = c("df", "teal", "list")) {
)
}
-#' REDCap import teal data module
-#'
-#' @rdname redcap_read_shiny_module
-tdm_redcap_read <- teal::teal_data_module(
- ui <- function(id) {
- shiny::fluidPage(
- m_redcap_readUI(id)
- )
- },
- server = function(id) {
- m_redcap_readServer(id, output.format = "teal")
- }
-)
+# #' REDCap import teal data module
+# #'
+# #' @rdname redcap_read_shiny_module
+# tdm_redcap_read <- teal::teal_data_module(
+# ui <- function(id) {
+# shiny::fluidPage(
+# m_redcap_readUI(id)
+# )
+# },
+# server = function(id) {
+# m_redcap_readServer(id, output.format = "teal")
+# }
+# )
#' Test app for the redcap_read_shiny_module
diff --git a/R/shiny_freesearcheR.R b/R/shiny_freesearcheR.R
index 9a2095e..ce3020c 100644
--- a/R/shiny_freesearcheR.R
+++ b/R/shiny_freesearcheR.R
@@ -15,7 +15,7 @@
#' shiny_freesearcheR(launch.browser = TRUE)
#' }
shiny_freesearcheR <- function(...) {
- appDir <- system.file("apps", "data_analysis_modules", package = "freesearcheR")
+ appDir <- system.file("apps", "freesearcheR", package = "freesearcheR")
if (appDir == "") {
stop("Could not find the app directory. Try re-installing `freesearcheR`.", call. = FALSE)
}
diff --git a/R/update-factor-ext.R b/R/update-factor-ext.R
new file mode 100644
index 0000000..d67bf86
--- /dev/null
+++ b/R/update-factor-ext.R
@@ -0,0 +1,292 @@
+
+## Works, but not implemented
+##
+## These edits mainly allows for
+
+
+#' @title Module to Reorder the Levels of a Factor Variable
+#'
+#' @description
+#' This module contain an interface to reorder the levels of a factor variable.
+#'
+#'
+#' @param id Module ID.
+#'
+#' @return A [shiny::reactive()] function returning the data.
+#' @export
+#'
+#' @importFrom shiny NS fluidRow tagList column actionButton
+#' @importFrom shinyWidgets virtualSelectInput prettyCheckbox
+#' @importFrom toastui datagridOutput
+#' @importFrom htmltools tags
+#'
+#' @name update-factor
+#'
+#' @example examples/update_factor.R
+update_factor_ui <- function(id) {
+ ns <- NS(id)
+ tagList(
+ tags$style(
+ ".tui-grid-row-header-draggable span {width: 3px !important; height: 3px !important;}"
+ ),
+ fluidRow(
+ column(
+ width = 6,
+ virtualSelectInput(
+ inputId = ns("variable"),
+ label = i18n("Factor variable to reorder:"),
+ choices = NULL,
+ width = "100%",
+ zIndex = 50
+ )
+ ),
+ column(
+ width = 3,
+ class = "d-flex align-items-end",
+ actionButton(
+ inputId = ns("sort_levels"),
+ label = tagList(
+ ph("sort-ascending"),
+ i18n("Sort by levels")
+ ),
+ class = "btn-outline-primary mb-3",
+ width = "100%"
+ )
+ ),
+ column(
+ width = 3,
+ class = "d-flex align-items-end",
+ actionButton(
+ inputId = ns("sort_occurrences"),
+ label = tagList(
+ ph("sort-ascending"),
+ i18n("Sort by count")
+ ),
+ class = "btn-outline-primary mb-3",
+ width = "100%"
+ )
+ )
+ ),
+ datagridOutput(ns("grid")),
+ tags$div(
+ class = "float-end",
+ prettyCheckbox(
+ inputId = ns("new_var"),
+ label = i18n("Create a new variable (otherwise replaces the one selected)"),
+ value = FALSE,
+ status = "primary",
+ outline = TRUE,
+ inline = TRUE
+ ),
+ actionButton(
+ inputId = ns("create"),
+ label = tagList(ph("arrow-clockwise"), i18n("Update factor variable")),
+ class = "btn-outline-primary"
+ )
+ ),
+ tags$div(class = "clearfix")
+ )
+}
+
+
+#' @param data_r A [shiny::reactive()] function returning a `data.frame`.
+#'
+#' @export
+#'
+#' @importFrom shiny moduleServer observeEvent reactive reactiveValues req bindEvent isTruthy updateActionButton
+#' @importFrom shinyWidgets updateVirtualSelect
+#' @importFrom toastui renderDatagrid datagrid grid_columns grid_colorbar
+#'
+#' @rdname update-factor
+update_factor_server <- function(id, data_r = reactive(NULL)) {
+ moduleServer(
+ id,
+ function(input, output, session) {
+
+ rv <- reactiveValues(data = NULL, data_grid = NULL)
+
+ bindEvent(observe({
+ data <- data_r()
+ rv$data <- data
+ vars_factor <- vapply(data, is.factor, logical(1))
+ vars_factor <- names(vars_factor)[vars_factor]
+ updateVirtualSelect(
+ inputId = "variable",
+ choices = vars_factor,
+ selected = if (isTruthy(input$variable)) input$variable else vars_factor[1]
+ )
+ }), data_r(), input$hidden)
+
+ observeEvent(input$variable, {
+ data <- req(data_r())
+ variable <- req(input$variable)
+ grid <- as.data.frame(table(data[[variable]]))
+ rv$data_grid <- grid
+ })
+
+ observeEvent(input$sort_levels, {
+ if (input$sort_levels %% 2 == 1) {
+ decreasing <- FALSE
+ label <- tagList(
+ ph("sort-descending"),
+ "Sort Levels"
+ )
+ } else {
+ decreasing <- TRUE
+ label <- tagList(
+ ph("sort-ascending"),
+ "Sort Levels"
+ )
+ }
+ updateActionButton(inputId = "sort_levels", label = as.character(label))
+ rv$data_grid <- rv$data_grid[order(rv$data_grid[[1]], decreasing = decreasing), ]
+ })
+
+ observeEvent(input$sort_occurrences, {
+ if (input$sort_occurrences %% 2 == 1) {
+ decreasing <- FALSE
+ label <- tagList(
+ ph("sort-descending"),
+ i18n("Sort count")
+ )
+ } else {
+ decreasing <- TRUE
+ label <- tagList(
+ ph("sort-ascending"),
+ i18n("Sort count")
+ )
+ }
+ updateActionButton(inputId = "sort_occurrences", label = as.character(label))
+ rv$data_grid <- rv$data_grid[order(rv$data_grid[[2]], decreasing = decreasing), ]
+ })
+
+
+ output$grid <- renderDatagrid({
+ req(rv$data_grid)
+ gridTheme <- getOption("datagrid.theme")
+ if (length(gridTheme) < 1) {
+ datamods:::apply_grid_theme()
+ }
+ on.exit(toastui::reset_grid_theme())
+ data <- rv$data_grid
+ data <- add_var_toset(data, "Var1", "New label")
+
+ grid <- datagrid(
+ data = data,
+ draggable = TRUE,
+ sortable = FALSE,
+ data_as_input = TRUE
+ )
+ grid <- grid_columns(
+ grid,
+ columns = c("Var1", "Var1_toset", "Freq"),
+ header = c(i18n("Levels"), "New label", i18n("Count"))
+ )
+ grid <- grid_colorbar(
+ grid,
+ column = "Freq",
+ label_outside = TRUE,
+ label_width = "30px",
+ background = "#D8DEE9",
+ bar_bg = datamods:::get_primary_color(),
+ from = c(0, max(rv$data_grid$Freq) + 1)
+ )
+ grid <- toastui::grid_style_column(
+ grid = grid,
+ column = "Var1_toset",
+ fontStyle = "italic"
+ )
+ grid <- toastui::grid_editor(
+ grid = grid,
+ column = "Var1_toset",
+ type = "text"
+ )
+ grid
+ })
+
+ data_updated_r <- reactive({
+ data <- req(data_r())
+ variable <- req(input$variable)
+ grid <- req(input$grid_data)
+ name_var <- if (isTRUE(input$new_var)) {
+ paste0(variable, "_updated")
+ } else {
+ variable
+ }
+ data[[name_var]] <- factor(
+ as.character(data[[variable]]),
+ levels = grid[["Var1"]]
+ )
+ data[[name_var]] <- factor(
+ data[[variable]],
+ labels = ifelse(grid[["Var1_toset"]]=="New label",grid[["Var1"]],grid[["Var1_toset"]])
+ )
+ data
+ })
+
+ data_returned_r <- observeEvent(input$create, {
+ rv$data <- data_updated_r()
+ })
+ return(reactive(rv$data))
+ }
+ )
+}
+
+
+
+#' @inheritParams shiny::modalDialog
+#' @export
+#'
+#' @importFrom shiny showModal modalDialog textInput
+#' @importFrom htmltools tagList
+#'
+#' @rdname update-factor
+modal_update_factor <- function(id,
+ title = i18n("Update levels of a factor"),
+ easyClose = TRUE,
+ size = "l",
+ footer = NULL) {
+ ns <- NS(id)
+ showModal(modalDialog(
+ title = tagList(title, datamods:::button_close_modal()),
+ update_factor_ui(id),
+ tags$div(
+ style = "display: none;",
+ textInput(inputId = ns("hidden"), label = NULL, value = datamods:::genId())
+ ),
+ easyClose = easyClose,
+ size = size,
+ footer = footer
+ ))
+}
+
+
+#' @inheritParams shinyWidgets::WinBox
+#' @export
+#'
+#' @importFrom shinyWidgets WinBox wbOptions wbControls
+#' @importFrom htmltools tagList
+#' @rdname create-column
+winbox_update_factor <- function(id,
+ title = i18n("Update levels of a factor"),
+ options = shinyWidgets::wbOptions(),
+ controls = shinyWidgets::wbControls()) {
+ ns <- NS(id)
+ WinBox(
+ title = title,
+ ui = tagList(
+ update_factor_ui(id),
+ tags$div(
+ style = "display: none;",
+ textInput(inputId = ns("hidden"), label = NULL, value = genId())
+ )
+ ),
+ options = modifyList(
+ shinyWidgets::wbOptions(height = "615px", modal = TRUE),
+ options
+ ),
+ controls = controls,
+ auto_height = FALSE
+ )
+}
+
diff --git a/R/update-variables-ext.R b/R/update-variables-ext.R
index b319d36..2eeaa1f 100644
--- a/R/update-variables-ext.R
+++ b/R/update-variables-ext.R
@@ -367,8 +367,8 @@ summary_vars <- function(data) {
name = names(data),
label = lapply(data, \(.x) REDCapCAST::get_attr(.x, "label")) |> unlist(),
class = get_classes(data),
- # n_missing = unname(colSums(is.na(data))),
- # p_complete = 1 - n_missing / nrow(data),
+ n_missing = unname(colSums(is.na(data))),
+ p_complete = 1 - n_missing / nrow(data),
n_unique = get_n_unique(data)
)
@@ -440,11 +440,11 @@ update_variables_datagrid <- function(data, height = NULL, selectionId = NULL, b
minWidth = 100
)
- # grid <- toastui::grid_format(
- # grid = grid,
- # "p_complete",
- # formatter = toastui::JS("function(obj) {return (obj.value*100).toFixed(0) + '%';}")
- # )
+ grid <- toastui::grid_format(
+ grid = grid,
+ "p_complete",
+ formatter = toastui::JS("function(obj) {return (obj.value*100).toFixed(0) + '%';}")
+ )
grid <- toastui::grid_style_column(
grid = grid,
column = "name_toset",
diff --git a/ROADMAP.md b/ROADMAP.md
index 8cce845..e6fdce1 100644
--- a/ROADMAP.md
+++ b/ROADMAP.md
@@ -26,11 +26,9 @@ Below are some (the actual list is quite long and growing) of the planned featur
- [ ] Select analyses to include in report
-- [ ] Plot regression analyses results
-
- [x] Export modified data. 2025-01-16
-- [ ] Include reproducible code for all steps
+- [ ] Include reproducible code for all steps (maybe not all, but most steps, and the final dataset can be exported)
- [x] ~~Modify factor levels~~ Factor level modifications is possible through converting factors to numeric > cutting numeric with desired fixed values. 2024-12-12
@@ -38,8 +36,8 @@ Below are some (the actual list is quite long and growing) of the planned featur
- Graphs and plots
- - [ ] Correlation matrix plot for data exploration
+ - [x] Correlation matrix plot for data exploration 2025-2-20
- [ ] Grotta bars for ordianl outcomes
- - [ ] Coefficient plotting for regression analyses (forest plot)
+ - [x] Coefficient plotting for regression analyses (forest plot) 2025-2-20
diff --git a/_pkgdown.yml b/_pkgdown.yml
index bfcadfc..9c5b6ae 100644
--- a/_pkgdown.yml
+++ b/_pkgdown.yml
@@ -13,12 +13,15 @@ template:
navbar:
bg: primary
structure:
- left: [intro, reference, roadmap, news]
+ left: [intro, reference, roadmap, q_a, news]
right: [search, github]
components:
roadmap:
text: Roadmap
href: ROADMAP.md
+ q_a:
+ text: Q&A
+ href: QA.md
includes:
in_header: umami-page.html
diff --git a/examples/visuals_module_demo.R b/examples/visuals_module_demo.R
new file mode 100644
index 0000000..00a8c02
--- /dev/null
+++ b/examples/visuals_module_demo.R
@@ -0,0 +1,32 @@
+visuals_demo_app <- function() {
+ ui <- bslib::page_fixed(
+ do.call(
+ bslib::navset_bar,
+ c(
+ data_visuals_ui("visuals"),
+ shiny::tagList(
+ bslib::nav_spacer(),
+ bslib::nav_panel(
+ title = "Notes",
+ shiny::fluidRow(
+ shiny::column(width = 2),
+ shiny::column(
+ width = 8,
+ shiny::markdown("Look, it **works**!"),
+ shiny::column(width = 2)
+ )
+ )
+ )
+ )
+ )
+ )
+ )
+ server <- function(input, output, session) {
+ pl <- data_visuals_server("visuals", data = shiny::reactive(default_parsing(mtcars)))
+ }
+ shiny::shinyApp(ui, server)
+}
+
+if (FALSE){
+visuals_demo_app()
+}
diff --git a/inst/apps/data_analysis/server.R b/inst/apps/data_analysis/server.R
deleted file mode 100644
index 431e337..0000000
--- a/inst/apps/data_analysis/server.R
+++ /dev/null
@@ -1,315 +0,0 @@
-
-library(readr)
-library(MASS)
-library(stats)
-library(gtsummary)
-library(gt)
-library(openxlsx2)
-library(haven)
-library(readODS)
-library(shiny)
-library(bslib)
-library(assertthat)
-library(dplyr)
-library(quarto)
-library(here)
-library(broom)
-library(broom.helpers)
-# library(REDCapCAST)
-library(easystats)
-library(patchwork)
-library(DHARMa)
-# if (!requireNamespace("webResearch")) {
-# devtools::install_github("agdamsbo/webResearch", quiet = TRUE, upgrade = "never")
-# }
-# library(webResearch)
-
-if (file.exists(here::here("functions.R"))) {
- source(here::here("functions.R"))
-}
-
-server <- function(input, output, session) {
- ## Listing files in www in session start to keep when ending and removing
- ## everything else.
- files.to.keep <- list.files("www/")
-
- v <- shiny::reactiveValues(
- list = NULL,
- ds = NULL,
- input = exists("webResearch_data"),
- local_temp = NULL,
- quarto = NULL,
- test = "no"
- )
-
- test_data <- shiny::eventReactive(input$test_data, {
- v$test <- "test"
- })
-
- ds <- shiny::reactive({
- # input$file1 will be NULL initially. After the user selects
- # and uploads a file, head of that data file by default,
- # or all rows if selected, will be shown.
- if (v$input) {
- out <- webResearch_data
- } else if (v$test == "test") {
- out <- gtsummary::trial
- } else {
- shiny::req(input$file)
- out <- read_input(input$file$datapath)
- }
-
- v$ds <- "present"
- if (input$factorize == "yes") {
- out <- out |>
- (\(.x){
- suppressWarnings(
- REDCapCAST::numchar2fct(.x)
- )
- })()
- }
- return(out)
- })
-
- output$include_vars <- shiny::renderUI({
- selectizeInput(
- inputId = "include_vars",
- selected = NULL,
- label = "Covariables to include",
- choices = colnames(ds()),
- multiple = TRUE
- )
- })
-
- output$outcome_var <- shiny::renderUI({
- selectInput(
- inputId = "outcome_var",
- selected = NULL,
- label = "Select outcome variable",
- choices = colnames(ds()),
- multiple = FALSE
- )
- })
-
- output$strat_var <- shiny::renderUI({
- selectInput(
- inputId = "strat_var",
- selected = "none",
- label = "Select variable to stratify baseline",
- choices = c("none", colnames(ds()[base_vars()])),
- multiple = FALSE
- )
- })
-
- output$factor_vars <- shiny::renderUI({
- selectizeInput(
- inputId = "factor_vars",
- selected = colnames(ds())[sapply(ds(), is.factor)],
- label = "Covariables to format as categorical",
- choices = colnames(ds()),
- multiple = TRUE
- )
- })
-
- base_vars <- shiny::reactive({
- if (is.null(input$include_vars)) {
- out <- colnames(ds())
- } else {
- out <- unique(c(input$include_vars, input$outcome_var))
- }
- return(out)
- })
-
- output$data.input <-
- DT::renderDT({
- shiny::req(input$file)
- ds()[base_vars()]
- })
-
- output$data.classes <- gt::render_gt({
- shiny::req(input$file)
- data.frame(matrix(sapply(ds(), \(.x){
- class(.x)[1]
- }), nrow = 1)) |>
- stats::setNames(names(ds())) |>
- gt::gt()
- })
-
-
-
- shiny::observeEvent(
- {
- input$load
- },
- {
- shiny::req(input$outcome_var)
-
- # Assumes all character variables can be formatted as factors
- data <- ds() |>
- dplyr::mutate(dplyr::across(dplyr::where(is.character), as.factor))
-
- data <- data |> factorize(vars = input$factor_vars)
-
- # if (is.factor(data[[input$strat_var]])) {
- # by.var <- input$strat_var
- # } else {
- # by.var <- NULL
- # }
-
- if (input$strat_var == "none") {
- by.var <- NULL
- } else {
- by.var <- input$strat_var
- }
-
- data <- data[base_vars()]
-
- # model <- data |>
- # regression_model(
- # outcome.str = input$outcome_var,
- # auto.mode = input$regression_auto == 1,
- # formula.str = input$regression_formula,
- # fun = input$regression_fun,
- # args.list = eval(parse(text = paste0("list(", input$regression_args, ")")))
- # )
-
- models <- list(
- "Univariable" = regression_model_uv,
- "Multivariable" = regression_model
- ) |>
- lapply(\(.fun){
- do.call(
- .fun,
- c(
- list(data = data),
- list(outcome.str = input$outcome_var),
- list(formula.str = input$regression_formula),
- list(fun = input$regression_fun),
- list(args.list = eval(parse(text = paste0("list(", input$regression_args, ")"))))
- )
- )
- })
-
- # browser()
- # check <- performance::check_model(purrr::pluck(models,"Multivariable") |>
- # (\(x){
- # class(x) <- class(x)[class(x) != "webresearch_model"]
- # return(x)
- # })())
-
- check <- purrr::pluck(models, "Multivariable") |>
- performance::check_model()
-
-
- v$list <- list(
- data = data,
- check = check,
- table1 = data |>
- baseline_table(
- fun.args =
- list(
- by = by.var
- )
- ) |>
- (\(.x){
- if (!is.null(by.var)) {
- .x |> gtsummary::add_overall()
- } else {
- .x
- }
- })() |>
- (\(.x){
- if (input$add_p == "yes") {
- .x |>
- gtsummary::add_p() |>
- gtsummary::bold_p()
- } else {
- .x
- }
- })(),
- table2 = models |>
- purrr::map(regression_table) |>
- tbl_merge(),
- input = input
- )
-
- output$table1 <- gt::render_gt(
- v$list$table1 |>
- gtsummary::as_gt()
- )
-
- output$table2 <- gt::render_gt(
- v$list$table2 |>
- gtsummary::as_gt()
- )
-
- output$check <- shiny::renderPlot({
- p <- plot(check) +
- patchwork::plot_annotation(title = "Multivariable regression model checks")
- p
- # Generate checks in one column
- # layout <- sapply(seq_len(length(p)), \(.x){
- # patchwork::area(.x, 1)
- # })
- #
- # p + patchwork::plot_layout(design = Reduce(c, layout))
-
- # patchwork::wrap_plots(ncol=1) +
- # patchwork::plot_annotation(title = 'Multivariable regression model checks')
- })
- }
- )
-
-
-
-
- output$uploaded <- shiny::reactive({
- if (is.null(v$ds)) {
- "no"
- } else {
- "yes"
- }
- })
-
- shiny::outputOptions(output, "uploaded", suspendWhenHidden = FALSE)
-
- output$has_input <- shiny::reactive({
- if (v$input) {
- "yes"
- } else {
- "no"
- }
- })
-
- shiny::outputOptions(output, "has_input", suspendWhenHidden = FALSE)
-
- # Could be rendered with other tables or should show progress
- # Investigate quarto render problems
- # On temp file handling: https://github.com/quarto-dev/quarto-cli/issues/3992
- output$report <- downloadHandler(
- filename = shiny::reactive({
- paste0("report.", input$output_type)
- }),
- content = function(file, type = input$output_type) {
- ## Notification is not progressing
- ## Presumably due to missing
- shiny::withProgress(message = "Generating report. Hold on for a moment..", {
- v$list |>
- write_quarto(
- output_format = type,
- input = file.path(getwd(), "www/report.qmd")
- )
- })
- file.rename(paste0("www/report.", type), file)
- }
- )
-
- session$onSessionEnded(function() {
- cat("Session Ended\n")
- files <- list.files("www/")
- lapply(files[!files %in% files.to.keep], \(.x){
- unlink(paste0("www/", .x), recursive = FALSE)
- print(paste(.x, "deleted"))
- })
- })
-}
diff --git a/inst/apps/data_analysis/ui.R b/inst/apps/data_analysis/ui.R
deleted file mode 100644
index 9cb559f..0000000
--- a/inst/apps/data_analysis/ui.R
+++ /dev/null
@@ -1,212 +0,0 @@
-library(shiny)
-library(bslib)
-library(IDEAFilter)
-library(teal)
-requireNamespace("gt")
-
-panels <- list(
- bslib::nav_panel(
- title = "Data overview",
- # shiny::uiOutput("data.classes"),
- # shiny::uiOutput("data.input"),
- # shiny::p("Classes of uploaded data"),
- # gt::gt_output("data.classes"),
- shiny::p("Subset data"),
- DT::DTOutput("data.input")
- ),
- bslib::nav_panel(
- title = "Baseline characteristics",
- gt::gt_output(outputId = "table1")
- ),
- bslib::nav_panel(
- title = "Regression table",
- gt::gt_output(outputId = "table2")
- ),
- bslib::nav_panel(
- title = "Regression checks",
- shiny::plotOutput(outputId = "check")
- )
-)
-
-ui <- bslib::page(
- theme = bslib::bs_theme(
- bootswatch = "minty",
- base_font = font_google("Inter"),
- code_font = font_google("JetBrains Mono")
- ),
- title = "webResearcher for easy data analysis",
- bslib::page_navbar(
- title = "webResearcher",
- header = h6("Welcome to the webResearcher tool. This is an early alpha version to act as a proof-of-concept and in no way intended for wider public use."),
- sidebar = bslib::sidebar(
- width = 300,
- open = "open",
- shiny::h4("Upload your dataset"),
- shiny::conditionalPanel(
- condition = "output.has_input=='yes'",
- # Input: Select a file ----
- shiny::helpText("Analyses are performed on provided data")
- ),
- shiny::conditionalPanel(
- condition = "output.has_input=='no'",
- # Input: Select a file ----
- shiny::fileInput(
- inputId = "file",
- label = "Choose data file",
- multiple = FALSE,
- accept = c(
- ".csv",
- ".xlsx",
- ".xls",
- ".dta",
- ".ods",
- ".rds"
- )
- ),
- # Does not work??
- # shiny::actionButton(inputId = "test_data",
- # label = "Load test data", class = "btn-primary")
- ),
- shiny::conditionalPanel(
- condition = "output.uploaded=='yes'",
- shiny::h4("Parameter specifications"),
- shiny::radioButtons(
- inputId = "factorize",
- label = "Factorize variables with few levels?",
- selected = "yes",
- inline = TRUE,
- choices = list(
- "Yes" = "yes",
- "No" = "no"
- )
- ),
- shiny::radioButtons(
- inputId = "regression_auto",
- label = "Automatically choose function",
- inline = TRUE,
- choiceNames = c(
- "Yes",
- "No"
- ),
- choiceValues = c(1, 2)
- ),
- shiny::conditionalPanel(
- condition = "input.regression_auto==2",
- shiny::textInput(
- inputId = "regression_formula",
- label = "Formula string to render with 'glue::glue'",
- value = NULL
- ),
- shiny::textInput(
- inputId = "regression_fun",
- label = "Function to use for analysis (needs pasckage and name)",
- value = "stats::lm"
- ),
- shiny::textInput(
- inputId = "regression_args",
- label = "Arguments to pass to the function (provided as a string)",
- value = ""
- )
- ),
- shiny::helpText(em("Please specify relevant settings for your data, and press 'Analyse'")),
- shiny::uiOutput("outcome_var"),
- shiny::uiOutput("strat_var"),
- shiny::conditionalPanel(
- condition = "input.strat_var!='none'",
- shiny::radioButtons(
- inputId = "add_p",
- label = "Compare strata?",
- selected = "no",
- inline = TRUE,
- choices = list(
- "No" = "no",
- "Yes" = "yes"
- )
- ),
- shiny::helpText("Option to perform statistical comparisons between strata in baseline table.")
- ),
- shiny::radioButtons(
- inputId = "all",
- label = "Specify covariables",
- inline = TRUE, selected = 2,
- choiceNames = c(
- "Yes",
- "No"
- ),
- choiceValues = c(1, 2)
- ),
- shiny::conditionalPanel(
- condition = "input.all==1",
- shiny::uiOutput("include_vars")
- ),
- shiny::radioButtons(
- inputId = "specify_factors",
- label = "Specify categorical variables?",
- selected = "no",
- inline = TRUE,
- choices = list(
- "Yes" = "yes",
- "No" = "no"
- )
- ),
- shiny::conditionalPanel(
- condition = "input.specify_factors=='yes'",
- shiny::uiOutput("factor_vars")
- ),
- bslib::input_task_button(
- id = "load",
- label = "Analyse",
- icon = shiny::icon("pencil", lib = "glyphicon"),
- label_busy = "Working...",
- icon_busy = fontawesome::fa_i("arrows-rotate",
- class = "fa-spin",
- "aria-hidden" = "true"
- ),
- type = "primary",
- auto_reset = TRUE
- ),
- shiny::helpText("If you change the parameters, press 'Analyse' again to update the tables"),
- # shiny::actionButton("load", "Analyse", class = "btn-primary"),
- #
- # # Horizontal line ----
- tags$hr(),
- shiny::conditionalPanel(
- condition = "input.load",
- h4("Download results"),
- shiny::helpText("Choose your favourite output file format for further work."),
- shiny::selectInput(
- inputId = "output_type",
- label = "Choose your desired output format",
- selected = NULL,
- choices = list(
- "Word" = "docx",
- "LibreOffice" = "odt"
- # ,
- # "PDF" = "pdf",
- # "All the above" = "all"
- )
- ),
-
- # Button
- downloadButton(
- outputId = "report",
- label = "Download",
- icon = shiny::icon("download")
- )
- )
- )
- ),
- bslib::nav_spacer(),
- panels[[1]],
- panels[[2]],
- panels[[3]],
- panels[[4]]
-
- # layout_columns(
- # cards[[1]]
- # ),
- # layout_columns(
- # cards[[2]], cards[[3]]
- # )
- )
-)
diff --git a/inst/apps/data_analysis/www/report.qmd b/inst/apps/data_analysis/www/report.qmd
deleted file mode 100644
index 51e3faa..0000000
--- a/inst/apps/data_analysis/www/report.qmd
+++ /dev/null
@@ -1,68 +0,0 @@
----
-format:
- html:
- embed-resources: true
-title: "webResearch analysis results"
-date: today
-author: webResearch Tool
-toc: true
-execute:
- echo: false
-params:
- data.file: NA
----
-
-```{r setup}
-web_data <- readr::read_rds(file = params$data.file)
-library(gtsummary)
-library(gt)
-library(easystats)
-library(patchwork)
-# library(webResearch)
-```
-
-## Introduction
-
-Research should be free and open with easy access for all. The webResearch tool attempts to help lower the bar to participate in contributing to science.
-
-## Methods
-
-Analyses were conducted in R version `r paste(version["major"],version["minor"],sep=".")`.
-
-## Results
-
-Below is the baseline characteristics plotted.
-
-```{r}
-#| label: tbl-baseline
-#| tbl-cap: Baseline characteristics of included data
-web_data$table1
-```
-
-Here are the regression results.
-
-```{r}
-#| label: tbl-regression
-#| tbl-cap: Regression analysis results
-web_data$table2
-```
-
-## Discussion
-
-Good luck on your further work!
-
-## Sensitivity
-
-Here are the results from testing the regression model:
-
-
-```{r}
-#| label: tbl-checks
-#| fig-cap: Regression analysis checks
-#| fig-height: 8
-#| fig-width: 6
-#| fig-dpi: 600
-
-plot(web_data$check)
-
-```
diff --git a/inst/apps/data_analysis_modules/rsconnect/shinyapps.io/agdamsbo/webResearch.dcf b/inst/apps/data_analysis_modules/rsconnect/shinyapps.io/agdamsbo/webResearch.dcf
deleted file mode 100644
index 6fa449f..0000000
--- a/inst/apps/data_analysis_modules/rsconnect/shinyapps.io/agdamsbo/webResearch.dcf
+++ /dev/null
@@ -1,10 +0,0 @@
-name: webResearch
-title:
-username: agdamsbo
-account: agdamsbo
-server: shinyapps.io
-hostUrl: https://api.shinyapps.io/v1
-appId: 13276335
-bundleId: 9436643
-url: https://agdamsbo.shinyapps.io/webResearch/
-version: 1
diff --git a/inst/apps/data_analysis_modules/app.R b/inst/apps/freesearcheR/app.R
similarity index 78%
rename from inst/apps/data_analysis_modules/app.R
rename to inst/apps/freesearcheR/app.R
index 95dfbb5..a1817ad 100644
--- a/inst/apps/data_analysis_modules/app.R
+++ b/inst/apps/freesearcheR/app.R
@@ -1,7 +1,7 @@
########
-#### Current file: /Users/au301842/freesearcheR/inst/apps/data_analysis_modules/functions.R
+#### Current file: /Users/au301842/freesearcheR/inst/apps/freesearcheR/functions.R
########
@@ -10,7 +10,7 @@
#### Current file: R//app_version.R
########
-app_version <- function()'250207_1709'
+app_version <- function()'250225_0948'
########
@@ -41,6 +41,151 @@ baseline_table <- function(data, fun.args = NULL, fun = gtsummary::tbl_summary,
+########
+#### Current file: R//columnSelectInput.R
+########
+
+#' A selectizeInput customized for data frames with column labels
+#'
+#' @description
+#' Copied and modified from the IDEAFilter package
+#' Adds the option to select "none" which is handled later
+#'
+#' @param inputId passed to \code{\link[shiny]{selectizeInput}}
+#' @param label passed to \code{\link[shiny]{selectizeInput}}
+#' @param data \code{data.frame} object from which fields should be populated
+#' @param selected default selection
+#' @param ... passed to \code{\link[shiny]{selectizeInput}}
+#' @param col_subset a \code{vector} containing the list of allowable columns to select
+#' @param placeholder passed to \code{\link[shiny]{selectizeInput}} options
+#' @param onInitialize passed to \code{\link[shiny]{selectizeInput}} options
+#' @param none_label label for "none" item
+#'
+#' @return a \code{\link[shiny]{selectizeInput}} dropdown element
+#'
+#' @importFrom shiny selectizeInput
+#' @keywords internal
+#'
+columnSelectInput <- function(inputId, label, data, selected = "", ...,
+ col_subset = NULL, placeholder = "", onInitialize, none_label="No variable selected") {
+ datar <- if (is.reactive(data)) data else reactive(data)
+ col_subsetr <- if (is.reactive(col_subset)) col_subset else reactive(col_subset)
+
+ labels <- Map(function(col) {
+ json <- sprintf(
+ IDEAFilter:::strip_leading_ws('
+ {
+ "name": "%s",
+ "label": "%s",
+ "datatype": "%s"
+ }'),
+ col,
+ attr(datar()[[col]], "label") %||% "",
+ IDEAFilter:::get_dataFilter_class(datar()[[col]])
+ )
+ }, col = names(datar()))
+
+ if (!"none" %in% names(datar())){
+ labels <- c("none"=list(sprintf('\n {\n \"name\": \"none\",\n \"label\": \"%s\",\n \"datatype\": \"\"\n }',none_label)),labels)
+ choices <- setNames(names(labels), labels)
+ choices <- choices[match(if (length(col_subsetr()) == 0 || isTRUE(col_subsetr() == "")) names(datar()) else col_subsetr(), choices)]
+ } else {
+ choices <- setNames(names(datar()), labels)
+ choices <- choices[match(if (length(col_subsetr()) == 0 || isTRUE(col_subsetr() == "")) choices else col_subsetr(), choices)]
+ }
+
+ shiny::selectizeInput(
+ inputId = inputId,
+ label = label,
+ choices = choices,
+ selected = selected,
+ ...,
+ options = c(
+ list(render = I("{
+ // format the way that options are rendered
+ option: function(item, escape) {
+ item.data = JSON.parse(item.label);
+ return '' +
+ '
' +
+ escape(item.data.name) + ' ' +
+ ' ' +
+ item.data.datatype +
+ '
' +
+ '
' +
+ (item.data.label != '' ? '
' + escape(item.data.label) + '
' : '') +
+ '
';
+ },
+
+ // avoid data vomit splashing on screen when an option is selected
+ item: function(item, escape) {
+ item.data = JSON.parse(item.label);
+ return '' +
+ escape(item.data.name) +
+ '
';
+ }
+ }"))
+ )
+ )
+}
+
+
+########
+#### Current file: R//contrast_text.R
+########
+
+#' @title Contrast Text Color
+#' @description Calculates the best contrast text color for a given
+#' background color.
+#' @param background A hex/named color value that represents the background.
+#' @param light_text A hex/named color value that represents the light text
+#' color.
+#' @param dark_text A hex/named color value that represents the dark text color.
+#' @param threshold A numeric value between 0 and 1 that is used to determine
+#' the luminance threshold of the background color for text color.
+#' @param method A character string that specifies the method for calculating
+#' the luminance. Three different methods are available:
+#' c("relative","perceived","perceived_2")
+#' @param ... parameter overflow. Ignored.
+#' @details
+#' This function aids in deciding the font color to print on a given background.
+#' The function is based on the example provided by teppo:
+#' https://stackoverflow.com/a/66669838/21019325.
+#' The different methods provided are based on the methods outlined in the
+#' StackOverflow thread:
+#' https://stackoverflow.com/questions/596216/formula-to-determine-perceived-brightness-of-rgb-color
+#' @return A character string that contains the best contrast text color.
+#' @examples
+#' contrast_text(c("#F2F2F2", "blue"))
+#'
+#' contrast_text(c("#F2F2F2", "blue"), method="relative")
+#' @export
+#'
+#' @importFrom grDevices col2rgb
+#'
+contrast_text <- function(background,
+ light_text = 'white',
+ dark_text = 'black',
+ threshold = 0.5,
+ method = "perceived_2",
+ ...) {
+ if (method == "relative") {
+ luminance <-
+ c(c(.2126, .7152, .0722) %*% grDevices::col2rgb(background) / 255)
+ } else if (method == "perceived") {
+ luminance <-
+ c(c(.299, .587, .114) %*% grDevices::col2rgb(background) / 255)
+ } else if (method == "perceived_2") {
+ luminance <- c(sqrt(colSums((
+ c(.299, .587, .114) * grDevices::col2rgb(background)
+ ) ^ 2)) / 255)
+ }
+
+ ifelse(luminance < threshold,
+ light_text,
+ dark_text)
+}
+
+
########
#### Current file: R//correlations-module.R
########
@@ -53,7 +198,7 @@ baseline_table <- function(data, fun.args = NULL, fun = gtsummary::tbl_summary,
#' @returns Shiny ui module
#' @export
data_correlations_ui <- function(id, ...) {
- ns <- NS(id)
+ ns <- shiny::NS(id)
shiny::tagList(
shiny::textOutput(outputId = ns("suggest")),
@@ -825,6 +970,631 @@ plot_histogram <- function(data, column, bins = 30, breaks = NULL, color = "#112
}
+########
+#### Current file: R//data_plots.R
+########
+
+# source(here::here("functions.R"))
+
+#' Data correlations evaluation module
+#'
+#' @param id Module id. (Use 'ns("id")')
+#'
+#' @name data-correlations
+#' @returns Shiny ui module
+#' @export
+#'
+data_visuals_ui <- function(id, tab_title="Plots", ...) {
+ ns <- shiny::NS(id)
+
+ # bslib::navset_bar(
+ list(
+
+ # Sidebar with a slider input
+ sidebar = bslib::sidebar(
+ bslib::accordion(
+ multiple = FALSE,
+ bslib::accordion_panel(
+ title = "Creating plot",
+ icon = bsicons::bs_icon("graph-up"),
+ shiny::uiOutput(outputId = ns("primary")),
+ shiny::uiOutput(outputId = ns("type")),
+ shiny::uiOutput(outputId = ns("secondary")),
+ shiny::uiOutput(outputId = ns("tertiary"))
+ ),
+ bslib::accordion_panel(
+ title = "Advanced",
+ icon = bsicons::bs_icon("gear")
+ ),
+ bslib::accordion_panel(
+ title = "Download",
+ icon = bsicons::bs_icon("download"),
+ shinyWidgets::noUiSliderInput(
+ inputId = ns("height"),
+ label = "Plot height (mm)",
+ min = 50,
+ max = 300,
+ value = 100,
+ step = 1,
+ format = shinyWidgets::wNumbFormat(decimals=0),
+ color = datamods:::get_primary_color()
+ ),
+ shinyWidgets::noUiSliderInput(
+ inputId = ns("width"),
+ label = "Plot width (mm)",
+ min = 50,
+ max = 300,
+ value = 100,
+ step = 1,
+ format = shinyWidgets::wNumbFormat(decimals=0),
+ color = datamods:::get_primary_color()
+ ),
+ shiny::selectInput(
+ inputId = ns("plot_type"),
+ label = "File format",
+ choices = list(
+ "png",
+ "tiff",
+ "eps",
+ "pdf",
+ "jpeg",
+ "svg"
+ )
+ ),
+ shiny::br(),
+ # Button
+ shiny::downloadButton(
+ outputId = ns("download_plot"),
+ label = "Download plot",
+ icon = shiny::icon("download")
+ )
+ )
+ )
+ ),
+ bslib::nav_panel(
+ title = tab_title,
+ shiny::plotOutput(ns("plot"))
+ )
+ )
+}
+
+
+#'
+#' @param data data
+#' @param ... ignored
+#'
+#' @name data-correlations
+#' @returns shiny server module
+#' @export
+data_visuals_server <- function(id,
+ data,
+ ...) {
+ shiny::moduleServer(
+ id = id,
+ module = function(input, output, session) {
+ ns <- session$ns
+
+ rv <- shiny::reactiveValues(
+ plot.params = NULL,
+ plot = NULL
+ )
+
+ output$primary <- shiny::renderUI({
+ columnSelectInput(
+ inputId = ns("primary"),
+ data = data,
+ placeholder = "Select variable",
+ label = "Response variable",
+ multiple = FALSE
+ )
+ })
+
+
+ output$type <- shiny::renderUI({
+ shiny::req(input$primary)
+ # browser()
+
+ if (!input$primary %in% names(data())) {
+ plot_data <- data()[1]
+ } else {
+ plot_data <- data()[input$primary]
+ }
+
+ plots <- possible_plots(
+ data = plot_data
+ )
+
+ shiny::selectizeInput(
+ inputId = ns("type"),
+ selected = NULL,
+ label = shiny::h4("Plot type"),
+ choices = plots,
+ multiple = FALSE
+ )
+ })
+
+ rv$plot.params <- shiny::reactive({
+ get_plot_options(input$type)
+ })
+
+ output$secondary <- shiny::renderUI({
+ shiny::req(input$type)
+ # browser()
+
+ columnSelectInput(
+ inputId = ns("secondary"),
+ data = data,
+ placeholder = "Select variable",
+ label = "Secondary/group variable",
+ multiple = FALSE,
+ col_subset = c(
+ purrr::pluck(rv$plot.params(), 1)[["secondary.extra"]],
+ all_but(
+ colnames(subset_types(
+ data(),
+ purrr::pluck(rv$plot.params(), 1)[["secondary.type"]]
+ )),
+ input$primary
+ )
+ ),
+ none_label = "No variable"
+ )
+
+ })
+
+ output$tertiary <- shiny::renderUI({
+ shiny::req(input$type)
+ columnSelectInput(
+ inputId = ns("tertiary"),
+ data = data,
+ placeholder = "Select variable",
+ label = "Strata variable",
+ multiple = FALSE,
+ col_subset = c(
+ "none",
+ all_but(
+ colnames(subset_types(
+ data(),
+ purrr::pluck(rv$plot.params(), 1)[["tertiary.type"]]
+ )),
+ input$primary,
+ input$secondary
+ )
+ ),
+ none_label = "No stratification"
+ )
+ })
+
+ rv$plot <- shiny::reactive({
+ shiny::req(input$primary)
+ shiny::req(input$type)
+ shiny::req(input$secondary)
+ shiny::req(input$tertiary)
+ create_plot(
+ data = data(),
+ type = names(rv$plot.params()),
+ x = input$primary,
+ y = input$secondary,
+ z = input$tertiary
+ )
+ })
+
+ output$plot <- shiny::renderPlot({
+ rv$plot()
+ })
+
+ output$download_plot <- shiny::downloadHandler(
+ filename = shiny::reactive({
+ paste0("plot.", input$plot_type)
+ }),
+ content = function(file) {
+ shiny::withProgress(message = "Drawing the plot. Hold on for a moment..", {
+ ggplot2::ggsave(filename = file,
+ plot = rv$plot(),
+ width = input$width,
+ height = input$height,
+ dpi = 300,
+ units = "mm",scale = 2)
+ })
+ }
+ )
+
+
+ shiny::observe(
+ return(rv$plot)
+ )
+ }
+ )
+}
+
+
+
+#' Select all from vector but
+#'
+#' @param data vector
+#' @param ... exclude
+#'
+#' @returns
+#' @export
+#'
+#' @examples
+#' all_but(1:10, c(2, 3), 11, 5)
+all_but <- function(data, ...) {
+ data[!data %in% c(...)]
+}
+
+#' Easily subset by data type function
+#'
+#' @param data data
+#' @param types desired types
+#' @param type.fun function to get type. Default is outcome_type
+#'
+#' @returns
+#' @export
+#'
+#' @examples
+#' default_parsing(mtcars) |> subset_types("ordinal")
+#' default_parsing(mtcars) |> subset_types(c("dichotomous", "ordinal"))
+#' #' default_parsing(mtcars) |> subset_types("factor",class)
+subset_types <- function(data, types, type.fun = outcome_type) {
+ data[sapply(data, type.fun) %in% types]
+}
+
+
+#' Implemented functions
+#'
+#' @description
+#' Library of supported functions. The list name and "descr" element should be
+#' unique for each element on list.
+#'
+#' - descr: Plot description
+#'
+#' - primary.type: Primary variable data type (continuous, dichotomous or ordinal)
+#'
+#' - secondary.type: Secondary variable data type (continuous, dichotomous or ordinal)
+#'
+#' - secondary.extra: "none" or NULL to have option to choose none.
+#'
+#' - tertiary.type: Tertiary variable data type (continuous, dichotomous or ordinal)
+#'
+#'
+#' @returns list
+#' @export
+#'
+#' @examples
+#' supported_plots() |> str()
+supported_plots <- function() {
+ list(
+ plot_hbars = list(
+ descr = "Stacked horizontal bars (Grotta bars)",
+ primary.type = c("dichotomous", "ordinal"),
+ secondary.type = c("dichotomous", "ordinal"),
+ tertiary.type = c("dichotomous", "ordinal"),
+ secondary.extra = "none"
+ ),
+ plot_violin = list(
+ descr = "Violin plot",
+ primary.type = c("continuous", "dichotomous", "ordinal"),
+ secondary.type = c("dichotomous", "ordinal"),
+ tertiary.type = c("dichotomous", "ordinal"),
+ secondary.extra = "none"
+ ),
+ plot_ridge = list(
+ descr = "Ridge plot",
+ primary.type = "continuous",
+ secondary.type = c("dichotomous", "ordinal"),
+ tertiary.type = c("dichotomous", "ordinal"),
+ secondary.extra = NULL
+ ),
+ plot_scatter = list(
+ descr = "Scatter plot",
+ primary.type = "continuous",
+ secondary.type = c("continuous", "ordinal"),
+ tertiary.type = c("dichotomous", "ordinal"),
+ secondary.extra = NULL
+ )
+ )
+}
+
+#' Title
+#'
+#' @returns
+#' @export
+#'
+#' @examples
+#' mtcars |>
+#' default_parsing() |>
+#' plot_ridge(x = "mpg", y = "cyl")
+#' mtcars |> plot_ridge(x = "mpg", y = "cyl", z = "gear")
+plot_ridge <- function(data, x, y, z = NULL, ...) {
+ if (!is.null(z)) {
+ ds <- split(data, data[z])
+ } else {
+ ds <- list(data)
+ }
+
+ out <- lapply(ds, \(.ds){
+ ggplot2::ggplot(.ds, ggplot2::aes(x = !!dplyr::sym(x), y = !!dplyr::sym(y), fill = !!dplyr::sym(y))) +
+ ggridges::geom_density_ridges() +
+ ggridges::theme_ridges() +
+ ggplot2::theme(legend.position = "none") |> rempsyc:::theme_apa()
+ })
+
+ patchwork::wrap_plots(out)
+}
+
+
+#' Get possible regression models
+#'
+#' @param data data
+#'
+#' @returns character vector
+#' @export
+#'
+#' @examples
+#' mtcars |>
+#' default_parsing() |>
+#' dplyr::pull("cyl") |>
+#' possible_plots()
+#'
+#' mtcars |>
+#' default_parsing() |>
+#' dplyr::select("mpg") |>
+#' possible_plots()
+possible_plots <- function(data) {
+ # browser()
+ if (is.data.frame(data)) {
+ data <- data[[1]]
+ }
+
+ type <- outcome_type(data)
+
+ if (type == "unknown") {
+ out <- type
+ } else {
+ out <- supported_plots() |>
+ lapply(\(.x){
+ if (type %in% .x$primary.type) {
+ .x$descr
+ }
+ }) |>
+ unlist()
+ }
+ unname(out)
+}
+
+#' Get the function options based on the selected function description
+#'
+#' @param data vector
+#'
+#' @returns list
+#' @export
+#'
+#' @examples
+#' ls <- mtcars |>
+#' default_parsing() |>
+#' dplyr::pull(mpg) |>
+#' possible_plots() |>
+#' (\(.x){
+#' .x[[1]]
+#' })() |>
+#' get_plot_options()
+get_plot_options <- function(data) {
+ descrs <- supported_plots() |>
+ lapply(\(.x){
+ .x$descr
+ }) |>
+ unlist()
+ supported_plots() |>
+ (\(.x){
+ .x[match(data, descrs)]
+ })()
+}
+
+
+
+#' Wrapper to create plot based on provided type
+#'
+#' @param type plot type (derived from possible_plots() and matches custom function)
+#' @param ... ignored for now
+#'
+#' @returns
+#' @export
+#'
+#' @examples
+#' create_plot(mtcars, "plot_violin", "mpg", "cyl")
+create_plot <- function(data, type, x, y, z = NULL, ...) {
+ if (!y %in% names(data)) {
+ y <- NULL
+ }
+
+ if (!z %in% names(data)) {
+ z <- NULL
+ }
+
+ do.call(
+ type,
+ list(data, x, y, z, ...)
+ )
+}
+
+
+#' Nice horizontal stacked bars (Grotta bars)
+#'
+#' @returns ggplot2 object
+#' @export
+#'
+#' @examples
+#' mtcars |> plot_hbars(x = "carb", y = "cyl")
+#' mtcars |> plot_hbars(x = "carb", y = NULL)
+plot_hbars <- function(data, x, y, z = NULL) {
+ out <- vertical_stacked_bars(data = data, score = x, group = y, strata = z)
+
+ out
+}
+
+
+#' Vertical stacked bar plot wrapper
+#'
+#' @param data
+#' @param score
+#' @param group
+#' @param strata
+#' @param t.size
+#'
+#' @return
+#' @export
+#'
+vertical_stacked_bars <- function(data,
+ score = "full_score",
+ group = "pase_0_q",
+ strata = NULL,
+ t.size = 10,
+ l.color = "black",
+ l.size = .5,
+ draw.lines = TRUE) {
+ if (is.null(group)) {
+ df.table <- data[c(score, group, strata)] |>
+ dplyr::mutate("All" = 1) |>
+ table()
+ group <- "All"
+ draw.lines <- FALSE
+ } else {
+ df.table <- data[c(score, group, strata)] |>
+ table()
+ }
+
+ p <- df.table |>
+ rankinPlot::grottaBar(
+ scoreName = score,
+ groupName = group,
+ textColor = c("black", "white"),
+ strataName = strata,
+ textCut = 6,
+ textSize = 20,
+ printNumbers = "none",
+ lineSize = l.size,
+ returnData = TRUE
+ )
+
+ colors <- viridisLite::viridis(nrow(df.table))
+ contrast_cut <-
+ sum(contrast_text(colors, threshold = .3) == "white")
+
+ score_label <- ifelse(is.na(REDCapCAST::get_attr(data$score, "label")), score, REDCapCAST::get_attr(data$score, "label"))
+ group_label <- ifelse(is.na(REDCapCAST::get_attr(data$group, "label")), group, REDCapCAST::get_attr(data$group, "label"))
+
+
+ p |>
+ (\(.x){
+ .x$plot +
+ ggplot2::geom_text(
+ data = .x$rectData[which(.x$rectData$n >
+ 0), ],
+ size = t.size,
+ fontface = "plain",
+ ggplot2::aes(
+ x = group,
+ y = p_prev + 0.49 * p,
+ color = as.numeric(score) > contrast_cut,
+ # label = paste0(sprintf("%2.0f", 100 * p),"%"),
+ label = sprintf("%2.0f", 100 * p)
+ )
+ ) +
+ ggplot2::labs(fill = score_label) +
+ ggplot2::scale_fill_manual(values = rev(colors)) +
+ ggplot2::theme(
+ legend.position = "bottom",
+ axis.title = ggplot2::element_text(),
+ ) +
+ ggplot2::xlab(group_label) +
+ ggplot2::ylab(NULL)
+ # viridis::scale_fill_viridis(discrete = TRUE, direction = -1, option = "D")
+ })()
+}
+
+
+#' Print label, and if missing print variable name
+#'
+#' @param data vector or data frame
+#'
+#' @returns character string
+#' @export
+#'
+#' @examples
+#' mtcars |> get_label(var = "mpg")
+#' mtcars$mpg |> get_label()
+#' gtsummary::trial |> get_label(var = "trt")
+#' 1:10 |> get_label()
+get_label <- function(data, var = NULL) {
+ if (!is.null(var)) {
+ data <- data[[var]]
+ }
+
+ out <- REDCapCAST::get_attr(data = data, attr = "label")
+ if (is.na(out)) {
+ if (is.null(var)) {
+ out <- deparse(substitute(data))
+ } else {
+ out <- gsub('\"', "", deparse(substitute(var)))
+ }
+ }
+ out
+}
+
+
+#' Beatiful violin plot
+#'
+#' @returns ggplot2 object
+#' @export
+#'
+#' @examples
+#' mtcars |> plot_violin(x = "mpg", y = "cyl", z = "gear")
+plot_violin <- function(data, x, y, z = NULL) {
+ if (!is.null(z)) {
+ ds <- split(data, data[z])
+ } else {
+ ds <- list(data)
+ }
+
+ out <- lapply(ds, \(.ds){
+ rempsyc::nice_violin(
+ data = .ds,
+ group = y,
+ response = x, xtitle = get_label(data, var = x), ytitle = get_label(data, var = y)
+ )
+ })
+
+ patchwork::wrap_plots(out)
+}
+
+
+#' Beatiful violin plot
+#'
+#' @returns ggplot2 object
+#' @export
+#'
+#' @examples
+#' mtcars |> plot_scatter(x = "mpg", y = "wt")
+plot_scatter <- function(data, x, y, z = NULL) {
+ if (is.null(z)) {
+ rempsyc::nice_scatter(
+ data = data,
+ predictor = y,
+ response = x, xtitle = get_label(data, var = x), ytitle = get_label(data, var = y)
+ )
+ } else {
+ rempsyc::nice_scatter(
+ data = data,
+ predictor = y,
+ response = x,
+ group = z
+ )
+ }
+}
+
+
+
########
#### Current file: R//data-summary.R
########
@@ -1223,34 +1993,34 @@ file_app <- function() {
file_app()
-tdm_data_upload <- teal::teal_data_module(
- ui <- function(id) {
- shiny::fluidPage(
- m_datafileUI(id)
- )
- },
- server = function(id) {
- m_datafileServer(id, output.format = "teal")
- }
-)
-
-tdm_data_read <- teal::teal_data_module(
- ui <- function(id) {
- shiny::fluidPage(
- m_redcap_readUI(id = "redcap")
- )
- },
- server = function(id) {
- moduleServer(
- id,
- function(input, output, session) {
- ns <- session$ns
-
- m_redcap_readServer(id = "redcap", output.format = "teal")
- }
- )
- }
-)
+# tdm_data_upload <- teal::teal_data_module(
+# ui <- function(id) {
+# shiny::fluidPage(
+# m_datafileUI(id)
+# )
+# },
+# server = function(id) {
+# m_datafileServer(id, output.format = "teal")
+# }
+# )
+#
+# tdm_data_read <- teal::teal_data_module(
+# ui <- function(id) {
+# shiny::fluidPage(
+# m_redcap_readUI(id = "redcap")
+# )
+# },
+# server = function(id) {
+# moduleServer(
+# id,
+# function(input, output, session) {
+# ns <- session$ns
+#
+# m_redcap_readServer(id = "redcap", output.format = "teal")
+# }
+# )
+# }
+# )
########
@@ -1527,6 +2297,32 @@ remove_empty_cols <- function(data,cutoff=.7){
}
+#' Append list with named index
+#'
+#' @param data data to add to list
+#' @param list list
+#' @param index index name
+#'
+#' @returns list
+#'
+#' @examples
+#' ls_d <- list(test=c(1:20))
+#' ls_d <- list()
+#' data.frame(letters[1:20],1:20) |> append_list(ls_d,"letters")
+#' letters[1:20]|> append_list(ls_d,"letters")
+append_list <- function(data,list,index){
+ ## This will overwrite and not warn
+ ## Not very safe, but convenient to append code to list
+ if (index %in% names(list)){
+ list[[index]] <- data
+ out <- list
+ } else {
+ out <- setNames(c(list,list(data)),c(names(list),index))
+ }
+ out
+}
+
+
########
#### Current file: R//redcap_read_shiny_module.R
########
@@ -1804,19 +2600,19 @@ m_redcap_readServer <- function(id, output.format = c("df", "teal", "list")) {
)
}
-#' REDCap import teal data module
-#'
-#' @rdname redcap_read_shiny_module
-tdm_redcap_read <- teal::teal_data_module(
- ui <- function(id) {
- shiny::fluidPage(
- m_redcap_readUI(id)
- )
- },
- server = function(id) {
- m_redcap_readServer(id, output.format = "teal")
- }
-)
+# #' REDCap import teal data module
+# #'
+# #' @rdname redcap_read_shiny_module
+# tdm_redcap_read <- teal::teal_data_module(
+# ui <- function(id) {
+# shiny::fluidPage(
+# m_redcap_readUI(id)
+# )
+# },
+# server = function(id) {
+# m_redcap_readServer(id, output.format = "teal")
+# }
+# )
#' Test app for the redcap_read_shiny_module
@@ -1928,6 +2724,7 @@ redcap_app <- function() {
#'
#' @return object of standard class for fun
#' @export
+#' @rdname regression_model
#'
#' @examples
#' gtsummary::trial |>
@@ -2064,6 +2861,7 @@ regression_model <- function(data,
#' @param ... ignored for now
#'
#' @importFrom stats as.formula
+#' @rdname regression_model
#'
#' @return object of standard class for fun
#' @export
@@ -2238,7 +3036,7 @@ supported_functions <- function() {
#'
#' @param data data
#'
-#' @returns
+#' @returns character vector
#' @export
#'
#' @examples
@@ -2327,8 +3125,9 @@ get_fun_options <- function(data) {
#' argsstring2list() or list of arguments. Default is NULL.
#' @param ... ignored
#'
-#' @returns
+#' @returns list
#' @export
+#' @rdname regression_model
#'
#' @examples
#' \dontrun{
@@ -2443,19 +3242,9 @@ list2str <- function(data) {
}
-#' Title
-#'
-#' @param data
-#' @param outcome.str
-#' @param fun.descr
-#' @param fun
-#' @param formula.str
-#' @param args.list
-#' @param vars
-#' @param ...
-#'
#' @returns list
#' @export
+#' @rdname regression_model
#'
#' @examples
#' \dontrun{
@@ -2924,7 +3713,7 @@ modify_qmd <- function(file, format) {
#' shiny_freesearcheR(launch.browser = TRUE)
#' }
shiny_freesearcheR <- function(...) {
- appDir <- system.file("apps", "data_analysis_modules", package = "freesearcheR")
+ appDir <- system.file("apps", "freesearcheR", package = "freesearcheR")
if (appDir == "") {
stop("Could not find the app directory. Try re-installing `freesearcheR`.", call. = FALSE)
}
@@ -2934,6 +3723,18 @@ shiny_freesearcheR <- function(...) {
}
+#' Easily launch the freesearcheR app
+#'
+#' @param ... passed on to `shiny::runApp()`
+#'
+#' @returns shiny app
+#' @export
+#'
+launch <- function(...){
+ shiny_freesearcheR(...)
+}
+
+
########
#### Current file: R//theme.R
########
@@ -3016,6 +3817,304 @@ gg_theme_export <- function(){
}
+########
+#### Current file: R//update-factor-ext.R
+########
+
+
+## Works, but not implemented
+##
+## These edits mainly allows for
+
+
+#' @title Module to Reorder the Levels of a Factor Variable
+#'
+#' @description
+#' This module contain an interface to reorder the levels of a factor variable.
+#'
+#'
+#' @param id Module ID.
+#'
+#' @return A [shiny::reactive()] function returning the data.
+#' @export
+#'
+#' @importFrom shiny NS fluidRow tagList column actionButton
+#' @importFrom shinyWidgets virtualSelectInput prettyCheckbox
+#' @importFrom toastui datagridOutput
+#' @importFrom htmltools tags
+#'
+#' @name update-factor
+#'
+#' @example examples/update_factor.R
+update_factor_ui <- function(id) {
+ ns <- NS(id)
+ tagList(
+ tags$style(
+ ".tui-grid-row-header-draggable span {width: 3px !important; height: 3px !important;}"
+ ),
+ fluidRow(
+ column(
+ width = 6,
+ virtualSelectInput(
+ inputId = ns("variable"),
+ label = i18n("Factor variable to reorder:"),
+ choices = NULL,
+ width = "100%",
+ zIndex = 50
+ )
+ ),
+ column(
+ width = 3,
+ class = "d-flex align-items-end",
+ actionButton(
+ inputId = ns("sort_levels"),
+ label = tagList(
+ ph("sort-ascending"),
+ i18n("Sort by levels")
+ ),
+ class = "btn-outline-primary mb-3",
+ width = "100%"
+ )
+ ),
+ column(
+ width = 3,
+ class = "d-flex align-items-end",
+ actionButton(
+ inputId = ns("sort_occurrences"),
+ label = tagList(
+ ph("sort-ascending"),
+ i18n("Sort by count")
+ ),
+ class = "btn-outline-primary mb-3",
+ width = "100%"
+ )
+ )
+ ),
+ datagridOutput(ns("grid")),
+ tags$div(
+ class = "float-end",
+ prettyCheckbox(
+ inputId = ns("new_var"),
+ label = i18n("Create a new variable (otherwise replaces the one selected)"),
+ value = FALSE,
+ status = "primary",
+ outline = TRUE,
+ inline = TRUE
+ ),
+ actionButton(
+ inputId = ns("create"),
+ label = tagList(ph("arrow-clockwise"), i18n("Update factor variable")),
+ class = "btn-outline-primary"
+ )
+ ),
+ tags$div(class = "clearfix")
+ )
+}
+
+
+#' @param data_r A [shiny::reactive()] function returning a `data.frame`.
+#'
+#' @export
+#'
+#' @importFrom shiny moduleServer observeEvent reactive reactiveValues req bindEvent isTruthy updateActionButton
+#' @importFrom shinyWidgets updateVirtualSelect
+#' @importFrom toastui renderDatagrid datagrid grid_columns grid_colorbar
+#'
+#' @rdname update-factor
+update_factor_server <- function(id, data_r = reactive(NULL)) {
+ moduleServer(
+ id,
+ function(input, output, session) {
+
+ rv <- reactiveValues(data = NULL, data_grid = NULL)
+
+ bindEvent(observe({
+ data <- data_r()
+ rv$data <- data
+ vars_factor <- vapply(data, is.factor, logical(1))
+ vars_factor <- names(vars_factor)[vars_factor]
+ updateVirtualSelect(
+ inputId = "variable",
+ choices = vars_factor,
+ selected = if (isTruthy(input$variable)) input$variable else vars_factor[1]
+ )
+ }), data_r(), input$hidden)
+
+ observeEvent(input$variable, {
+ data <- req(data_r())
+ variable <- req(input$variable)
+ grid <- as.data.frame(table(data[[variable]]))
+ rv$data_grid <- grid
+ })
+
+ observeEvent(input$sort_levels, {
+ if (input$sort_levels %% 2 == 1) {
+ decreasing <- FALSE
+ label <- tagList(
+ ph("sort-descending"),
+ "Sort Levels"
+ )
+ } else {
+ decreasing <- TRUE
+ label <- tagList(
+ ph("sort-ascending"),
+ "Sort Levels"
+ )
+ }
+ updateActionButton(inputId = "sort_levels", label = as.character(label))
+ rv$data_grid <- rv$data_grid[order(rv$data_grid[[1]], decreasing = decreasing), ]
+ })
+
+ observeEvent(input$sort_occurrences, {
+ if (input$sort_occurrences %% 2 == 1) {
+ decreasing <- FALSE
+ label <- tagList(
+ ph("sort-descending"),
+ i18n("Sort count")
+ )
+ } else {
+ decreasing <- TRUE
+ label <- tagList(
+ ph("sort-ascending"),
+ i18n("Sort count")
+ )
+ }
+ updateActionButton(inputId = "sort_occurrences", label = as.character(label))
+ rv$data_grid <- rv$data_grid[order(rv$data_grid[[2]], decreasing = decreasing), ]
+ })
+
+
+ output$grid <- renderDatagrid({
+ req(rv$data_grid)
+ gridTheme <- getOption("datagrid.theme")
+ if (length(gridTheme) < 1) {
+ datamods:::apply_grid_theme()
+ }
+ on.exit(toastui::reset_grid_theme())
+ data <- rv$data_grid
+ data <- add_var_toset(data, "Var1", "New label")
+
+ grid <- datagrid(
+ data = data,
+ draggable = TRUE,
+ sortable = FALSE,
+ data_as_input = TRUE
+ )
+ grid <- grid_columns(
+ grid,
+ columns = c("Var1", "Var1_toset", "Freq"),
+ header = c(i18n("Levels"), "New label", i18n("Count"))
+ )
+ grid <- grid_colorbar(
+ grid,
+ column = "Freq",
+ label_outside = TRUE,
+ label_width = "30px",
+ background = "#D8DEE9",
+ bar_bg = datamods:::get_primary_color(),
+ from = c(0, max(rv$data_grid$Freq) + 1)
+ )
+ grid <- toastui::grid_style_column(
+ grid = grid,
+ column = "Var1_toset",
+ fontStyle = "italic"
+ )
+ grid <- toastui::grid_editor(
+ grid = grid,
+ column = "Var1_toset",
+ type = "text"
+ )
+ grid
+ })
+
+ data_updated_r <- reactive({
+ data <- req(data_r())
+ variable <- req(input$variable)
+ grid <- req(input$grid_data)
+ name_var <- if (isTRUE(input$new_var)) {
+ paste0(variable, "_updated")
+ } else {
+ variable
+ }
+ data[[name_var]] <- factor(
+ as.character(data[[variable]]),
+ levels = grid[["Var1"]]
+ )
+ data[[name_var]] <- factor(
+ data[[variable]],
+ labels = ifelse(grid[["Var1_toset"]]=="New label",grid[["Var1"]],grid[["Var1_toset"]])
+ )
+ data
+ })
+
+ data_returned_r <- observeEvent(input$create, {
+ rv$data <- data_updated_r()
+ })
+ return(reactive(rv$data))
+ }
+ )
+}
+
+
+
+#' @inheritParams shiny::modalDialog
+#' @export
+#'
+#' @importFrom shiny showModal modalDialog textInput
+#' @importFrom htmltools tagList
+#'
+#' @rdname update-factor
+modal_update_factor <- function(id,
+ title = i18n("Update levels of a factor"),
+ easyClose = TRUE,
+ size = "l",
+ footer = NULL) {
+ ns <- NS(id)
+ showModal(modalDialog(
+ title = tagList(title, datamods:::button_close_modal()),
+ update_factor_ui(id),
+ tags$div(
+ style = "display: none;",
+ textInput(inputId = ns("hidden"), label = NULL, value = datamods:::genId())
+ ),
+ easyClose = easyClose,
+ size = size,
+ footer = footer
+ ))
+}
+
+
+#' @inheritParams shinyWidgets::WinBox
+#' @export
+#'
+#' @importFrom shinyWidgets WinBox wbOptions wbControls
+#' @importFrom htmltools tagList
+#' @rdname create-column
+winbox_update_factor <- function(id,
+ title = i18n("Update levels of a factor"),
+ options = shinyWidgets::wbOptions(),
+ controls = shinyWidgets::wbControls()) {
+ ns <- NS(id)
+ WinBox(
+ title = title,
+ ui = tagList(
+ update_factor_ui(id),
+ tags$div(
+ style = "display: none;",
+ textInput(inputId = ns("hidden"), label = NULL, value = genId())
+ )
+ ),
+ options = modifyList(
+ shinyWidgets::wbOptions(height = "615px", modal = TRUE),
+ options
+ ),
+ controls = controls,
+ auto_height = FALSE
+ )
+}
+
+
+
########
#### Current file: R//update-variables-ext.R
########
@@ -3389,8 +4488,8 @@ summary_vars <- function(data) {
name = names(data),
label = lapply(data, \(.x) REDCapCAST::get_attr(.x, "label")) |> unlist(),
class = get_classes(data),
- # n_missing = unname(colSums(is.na(data))),
- # p_complete = 1 - n_missing / nrow(data),
+ n_missing = unname(colSums(is.na(data))),
+ p_complete = 1 - n_missing / nrow(data),
n_unique = get_n_unique(data)
)
@@ -3462,11 +4561,11 @@ update_variables_datagrid <- function(data, height = NULL, selectionId = NULL, b
minWidth = 100
)
- # grid <- toastui::grid_format(
- # grid = grid,
- # "p_complete",
- # formatter = toastui::JS("function(obj) {return (obj.value*100).toFixed(0) + '%';}")
- # )
+ grid <- toastui::grid_format(
+ grid = grid,
+ "p_complete",
+ formatter = toastui::JS("function(obj) {return (obj.value*100).toFixed(0) + '%';}")
+ )
grid <- toastui::grid_style_column(
grid = grid,
column = "name_toset",
@@ -3781,7 +4880,7 @@ clean_date <- function(data){
########
-#### Current file: /Users/au301842/freesearcheR/inst/apps/data_analysis_modules/ui.R
+#### Current file: /Users/au301842/freesearcheR/inst/apps/freesearcheR/ui.R
########
# ns <- NS(id)
@@ -3794,7 +4893,14 @@ ui_elements <- list(
##############################################################################
"home" = bslib::nav_panel(
title = "freesearcheR",
- shiny::markdown(readLines("www/intro.md")),
+ shiny::fluidRow(
+ shiny::column(width = 2),
+ shiny::column(
+ width = 8,
+ shiny::markdown(readLines("www/intro.md")),
+ shiny::column(width = 2)
+ )
+ ),
icon = shiny::icon("home")
),
##############################################################################
@@ -3804,21 +4910,22 @@ ui_elements <- list(
##############################################################################
"import" = bslib::nav_panel(
title = "Import",
+ shiny::fluidRow(
+ shiny::column(width = 2),
+ shiny::column(
+ width = 8,
+
+
shiny::h4("Choose your data source"),
shiny::br(),
shinyWidgets::radioGroupButtons(
inputId = "source",
selected = "env",
- # label = "Choice: ",
choices = c(
"File upload" = "file",
"REDCap server" = "redcap",
"Local data" = "env"
),
- # checkIcon = list(
- # yes = icon("square-check"),
- # no = icon("square")
- # ),
width = "100%"
),
shiny::helpText("Upload a file from your device, get data directly from REDCap or select a sample data set for testing from the app."),
@@ -3846,14 +4953,15 @@ ui_elements <- list(
shiny::h5("Exclude in-complete variables"),
shiny::p("Before going further, you can exclude variables with a low degree of completeness."),
shiny::br(),
- shiny::sliderInput(
+ shinyWidgets::noUiSliderInput(
inputId = "complete_cutoff",
label = "Choose completeness threshold (%)",
min = 0,
max = 100,
step = 10,
value = 70,
- ticks = FALSE
+ format = shinyWidgets::wNumbFormat(decimals = 0),
+ color = datamods:::get_primary_color()
),
shiny::helpText("Only include variables with completeness above a specified percentage."),
shiny::br(),
@@ -3866,7 +4974,10 @@ ui_elements <- list(
),
shiny::helpText('After importing, hit "Start" or navigate to the desired tab.'),
shiny::br(),
- shiny::br()
+ shiny::br(),
+ shiny::column(width = 2)
+ )
+ )
),
##############################################################################
#########
@@ -3880,75 +4991,15 @@ ui_elements <- list(
title = "Data",
bslib::navset_bar(
fillable = TRUE,
- bslib::nav_panel(
- title = "Summary & filter",
- tags$h3("Data summary and filtering"),
- fluidRow(
- shiny::column(
- width = 9,
- shiny::tags$p(
- "Below is a short summary table of the provided data.
- On the right hand side you have the option to create filters.
- At the bottom you'll find a raw overview of the original vs the modified data."
- )
- )
- ),
- fluidRow(
- # column(
- # width = 3,
- # shiny::uiOutput("filter_vars"),
- # shiny::conditionalPanel(
- # condition = "(typeof input.filter_vars !== 'undefined' && input.filter_vars.length > 0)",
- # datamods::filter_data_ui("filtering", max_height = "500px")
- # )
- # ),
- # column(
- # width = 9,
- # DT::DTOutput(outputId = "filtered_table"),
- # tags$b("Code dplyr:"),
- # verbatimTextOutput(outputId = "filtered_code")
- # ),
- shiny::column(
- width = 9,
- data_summary_ui(id = "data_summary")
- ),
- shiny::column(
- width = 3,
- IDEAFilter::IDEAFilter_ui("data_filter"),
- shiny::tags$br(),
- shiny::tags$b("Filter code:"),
- shiny::verbatimTextOutput(outputId = "filtered_code"),
- shiny::tags$br()
- )
- ),
- fluidRow(
- column(
- width = 6,
- tags$b("Original data:"),
- # verbatimTextOutput("original"),
- verbatimTextOutput("original_str")
- ),
- column(
- width = 6,
- tags$b("Modified data:"),
- # verbatimTextOutput("modified"),
- verbatimTextOutput("modified_str")
- )
- )
- ),
- # bslib::nav_panel(
- # title = "Overview",
- # DT::DTOutput(outputId = "table")
- # ),
bslib::nav_panel(
title = "Modify",
tags$h3("Subset, rename and convert variables"),
fluidRow(
shiny::column(
width = 9,
- shiny::tags$p("Below, you can subset the data (select variables to include on clicking 'Apply changes'), rename variables, set new labels (for nicer tables in the report) and change variable classes (numeric, factor/categorical etc.).
+ shiny::tags$p(shiny::markdown("Below, you can subset the data (select variables to include on clicking 'Apply changes'), rename variables, set new labels (for nicer tables in the report) and change variable classes (numeric, factor/categorical etc.).
Italic text can be edited/changed.
- On the right, you can create and modify factor/categorical variables as well as resetting the data to the originally imported data.")
+ On the right, you can create and modify factor/categorical variables as well as create new variables with *R* code."))
)
),
fluidRow(
@@ -3985,17 +5036,8 @@ ui_elements <- list(
width = "100%"
),
shiny::tags$br(),
- shiny::helpText("Create a new variable/column based on an R-expression."),
+ shiny::helpText(shiny::markdown("Create a new variable/column based on an *R*-expression.")),
shiny::tags$br(),
- shiny::tags$br(),
- tags$h4("Restore"),
- shiny::actionButton(
- inputId = "data_reset",
- label = "Restore original data",
- width = "100%"
- ),
- shiny::tags$br(),
- shiny::helpText("Reset to original imported dataset. Careful! There is no un-doing."),
shiny::tags$br() # ,
# shiny::tags$br(),
# shiny::tags$br(),
@@ -4006,10 +5048,88 @@ ui_elements <- list(
)
),
bslib::nav_panel(
- title = "Browser",
+ title = "Filter",
+ tags$h3("Data filtering"),
+ fluidRow(
+ shiny::column(
+ width = 9,
+ shiny::tags$p(
+ "Below is a short summary table of the provided data.
+ On the right hand side you have the option to create filters.
+ At the bottom you'll find a raw overview of the original vs the modified data."
+ )
+ )
+ ),
+ fluidRow(
+ # column(
+ # width = 3,
+ # shiny::uiOutput("filter_vars"),
+ # shiny::conditionalPanel(
+ # condition = "(typeof input.filter_vars !== 'undefined' && input.filter_vars.length > 0)",
+ # datamods::filter_data_ui("filtering", max_height = "500px")
+ # )
+ # ),
+ # column(
+ # width = 9,
+ # DT::DTOutput(outputId = "filtered_table"),
+ # tags$b("Code dplyr:"),
+ # verbatimTextOutput(outputId = "filtered_code")
+ # ),
+ shiny::column(
+ width = 9,
+ data_summary_ui(id = "data_summary")
+ ),
+ shiny::column(
+ width = 3,
+ IDEAFilter::IDEAFilter_ui("data_filter"),
+ # shiny::tags$br(),
+ # shiny::tags$b("Filter code:"),
+ # shiny::verbatimTextOutput(outputId = "filtered_code"),
+ shiny::tags$br()
+ )
+ )
+ ),
+ bslib::nav_panel(
+ title = "Restore",
+ tags$h3("Compare to original and restore"),
+ fluidRow(
+ shiny::column(
+ width = 9,
+ shiny::tags$p(
+ "Right below, you have the option to restore to the originally imported data.
+ At the bottom you'll find a raw overview of the original vs the modified data."
+ )
+ ),
+ shiny::tags$br(),
+ tags$h4("Restore"),
+ shiny::actionButton(
+ inputId = "data_reset",
+ label = "Restore original data",
+ width = "100%"
+ ),
+ shiny::tags$br(),
+ shiny::helpText("Reset to original imported dataset. Careful! There is no un-doing.")
+ ),
+ fluidRow(
+ column(
+ width = 6,
+ tags$b("Original data:"),
+ # verbatimTextOutput("original"),
+ verbatimTextOutput("original_str")
+ ),
+ column(
+ width = 6,
+ tags$b("Modified data:"),
+ # verbatimTextOutput("modified"),
+ verbatimTextOutput("modified_str")
+ )
+ )
+ ),
+ bslib::nav_panel(
+ title = "Browse",
tags$h3("Browse the provided data"),
shiny::tags$p(
- "Below is a data table with all the modified data provided to browse and understand data."
+ "Below is a table with all the modified data provided to browse and understand data."
),
shinyWidgets::html_dependency_winbox(),
# fluidRow(
@@ -4109,14 +5229,15 @@ ui_elements <- list(
shiny::uiOutput("outcome_var_cor"),
shiny::helpText("This variable will be excluded from the correlation plot."),
shiny::br(),
- shiny::sliderInput(
+ shinyWidgets::noUiSliderInput(
inputId = "cor_cutoff",
label = "Correlation cut-off",
min = 0,
max = 1,
- step = .02,
+ step = .01,
value = .8,
- ticks = FALSE
+ format = shinyWidgets::wNumbFormat(decimals = 2),
+ color = datamods:::get_primary_color()
)
)
)
@@ -4133,6 +5254,35 @@ ui_elements <- list(
),
##############################################################################
#########
+ ######### Download panel
+ #########
+ ##############################################################################
+ "visuals" = bslib::nav_panel(
+ title = "Visuals",
+ id = "navvisuals",
+ do.call(
+ bslib::navset_bar,
+ c(
+ data_visuals_ui("visuals"),
+ shiny::tagList(
+ bslib::nav_spacer(),
+ bslib::nav_panel(
+ title = "Notes",
+ shiny::fluidRow(
+ shiny::column(width = 2),
+ shiny::column(
+ width = 8,
+ shiny::markdown(readLines("www/notes_visuals.md")),
+ shiny::column(width = 2)
+ )
+ )
+ )
+ )
+ )
+ )
+ ),
+ ##############################################################################
+ #########
######### Regression analyses panel
#########
##############################################################################
@@ -4253,11 +5403,17 @@ ui_elements <- list(
bslib::nav_panel(
title = "Download",
id = "navdownload",
+ shiny::fluidRow(
+ shiny::column(width = 2),
+ shiny::column(
+ width = 8,
shiny::fluidRow(
shiny::column(
width = 6,
shiny::h4("Report"),
shiny::helpText("Choose your favourite output file format for further work, and download, when the analyses are done."),
+ shiny::br(),
+ shiny::br(),
shiny::selectInput(
inputId = "output_type",
label = "Output format",
@@ -4283,6 +5439,8 @@ ui_elements <- list(
width = 6,
shiny::h4("Data"),
shiny::helpText("Choose your favourite output data format to download the modified data."),
+ shiny::br(),
+ shiny::br(),
shiny::selectInput(
inputId = "data_type",
label = "Data format",
@@ -4293,6 +5451,8 @@ ui_elements <- list(
"CSV" = "csv"
)
),
+ shiny::helpText("No metadata is saved when exporting to csv."),
+ shiny::br(),
shiny::br(),
# Button
shiny::downloadButton(
@@ -4302,7 +5462,17 @@ ui_elements <- list(
)
)
),
- shiny::br()
+ shiny::br(),
+ shiny::br(),
+ shiny::tags$b("Code snippets:"),
+ shiny::verbatimTextOutput(outputId = "code_import"),
+ shiny::verbatimTextOutput(outputId = "code_data"),
+ shiny::verbatimTextOutput(outputId = "code_filter"),
+ shiny::tags$br(),
+ shiny::br(),
+ shiny::column(width = 2)
+ )
+ )
),
##############################################################################
#########
@@ -4354,6 +5524,7 @@ ui <- bslib::page_fixed(
ui_elements$import,
ui_elements$overview,
ui_elements$describe,
+ ui_elements$visuals,
ui_elements$analyze,
ui_elements$download,
bslib::nav_spacer(),
@@ -4375,7 +5546,7 @@ ui <- bslib::page_fixed(
########
-#### Current file: /Users/au301842/freesearcheR/inst/apps/data_analysis_modules/server.R
+#### Current file: /Users/au301842/freesearcheR/inst/apps/freesearcheR/server.R
########
library(readr)
@@ -4395,6 +5566,7 @@ library(broom)
library(broom.helpers)
# library(REDCapCAST)
library(easystats)
+library(esquisse)
library(patchwork)
library(DHARMa)
library(apexcharter)
@@ -4461,7 +5633,8 @@ server <- function(input, output, session) {
data_original = NULL,
data = NULL,
data_filtered = NULL,
- models = NULL
+ models = NULL,
+ code = list()
)
##############################################################################
@@ -4479,23 +5652,48 @@ server <- function(input, output, session) {
return_class = "data.frame",
read_fns = list(
ods = function(file) {
- readODS::read_ods(path = file, na = consider.na)
+ readODS::read_ods(
+ path = file,
+ # Sheet and skip not implemented for .ods in the original implementation
+ # sheet = sheet,
+ # skip = skip,
+ na = consider.na
+ )
},
dta = function(file) {
- haven::read_dta(file = file, .name_repair = "unique_quiet")
+ haven::read_dta(
+ file = file,
+ .name_repair = "unique_quiet"
+ )
},
csv = function(file) {
- readr::read_csv(file = file, na = consider.na, name_repair = "unique_quiet") #|>
- # janitor::remove_empty(which = "cols", cutoff = 1, quiet = TRUE)
+ readr::read_csv(
+ file = file,
+ na = consider.na,
+ name_repair = "unique_quiet"
+ )
+ },
+ xls = function(file) {
+ openxlsx2::read_xlsx(
+ file = file,
+ sheet = sheet,
+ skip_empty_rows = TRUE,
+ start_row = skip - 1,
+ na.strings = consider.na
+ )
+ },
+ xlsx = function(file) {
+ openxlsx2::read_xlsx(
+ file = file,
+ sheet = sheet,
+ skip_empty_rows = TRUE,
+ start_row = skip - 1,
+ na.strings = consider.na)
},
- # xls = function(file){
- # openxlsx2::read_xlsx(file = file, na.strings = consider.na,)
- # },
- # xlsx = function(file){
- # openxlsx2::read_xlsx(file = file, na.strings = consider.na,)
- # },
rds = function(file) {
- readr::read_rds(file = file, name_repair = "unique_quiet")
+ readr::read_rds(
+ file = file,
+ name_repair = "unique_quiet")
}
)
)
@@ -4503,6 +5701,7 @@ server <- function(input, output, session) {
shiny::observeEvent(data_file$data(), {
shiny::req(data_file$data())
rv$data_original <- data_file$data()
+ rv$code <- append_list(data = data_file$code(), list = rv$code, index = "import")
})
data_redcap <- m_redcap_readServer(
@@ -4523,7 +5722,7 @@ server <- function(input, output, session) {
server = TRUE
)
- from_env <- import_globalenv_server(
+ from_env <- datamods::import_globalenv_server(
id = "env",
trigger_return = "change",
btn_show_data = FALSE,
@@ -4533,6 +5732,7 @@ server <- function(input, output, session) {
shiny::observeEvent(from_env$data(), {
shiny::req(from_env$data())
rv$data_original <- from_env$data()
+ # rv$code <- append_list(data = from_env$code(),list = rv$code,index = "import")
})
@@ -4594,12 +5794,14 @@ server <- function(input, output, session) {
shiny::observeEvent(
input$modal_cut,
- modal_cut_variable("modal_cut")
+ modal_cut_variable("modal_cut",title = "Modify factor levels")
)
+
data_modal_cut <- cut_variable_server(
id = "modal_cut",
data_r = shiny::reactive(rv$data)
)
+
shiny::observeEvent(data_modal_cut(), rv$data <- data_modal_cut())
######### Modify factor
@@ -4608,10 +5810,12 @@ server <- function(input, output, session) {
input$modal_update,
datamods::modal_update_factor(id = "modal_update")
)
+
data_modal_update <- datamods::update_factor_server(
id = "modal_update",
data_r = reactive(rv$data)
)
+
shiny::observeEvent(data_modal_update(), {
shiny::removeModal()
rv$data <- data_modal_update()
@@ -4637,25 +5841,26 @@ server <- function(input, output, session) {
######### Show result
tryCatch(
{
- output$table_mod <- toastui::renderDatagrid({
- shiny::req(rv$data)
- # data <- rv$data
- toastui::datagrid(
- # data = rv$data # ,
- data = data_filter(),
- pagination = 10
- # bordered = TRUE,
- # compact = TRUE,
- # striped = TRUE
- )
- })
+ output$table_mod <- toastui::renderDatagrid({
+ shiny::req(rv$data)
+ # data <- rv$data
+ toastui::datagrid(
+ # data = rv$data # ,
+ data = data_filter(),
+ pagination = 10
+ # bordered = TRUE,
+ # compact = TRUE,
+ # striped = TRUE
+ )
+ })
},
- warning = function(warn) {
- showNotification(paste0(warn), type = "warning")
- },
- error = function(err) {
- showNotification(paste0(err), type = "err")
- })
+ warning = function(warn) {
+ showNotification(paste0(warn), type = "warning")
+ },
+ error = function(err) {
+ showNotification(paste0(err), type = "err")
+ }
+ )
output$code <- renderPrint({
attr(rv$data, "code")
@@ -4692,46 +5897,78 @@ server <- function(input, output, session) {
shiny::reactive(rv$data),
shiny::reactive(rv$data_original),
data_filter(),
- base_vars(),
+ regression_vars(),
input$complete_cutoff
),
{
rv$data_filtered <- data_filter()
rv$list$data <- data_filter() |>
- REDCapCAST::fct_drop() |>
- (\(.x){
- .x[base_vars()]
- })() #|>
- # janitor::remove_empty(
- # which = "cols",
- # cutoff = input$complete_cutoff / 100
- # )
+ REDCapCAST::fct_drop()
}
)
- output$filtered_code <- shiny::renderPrint({
- out <- gsub(
- "filter", "dplyr::filter",
- gsub(
- "\\s{2,}", " ",
- paste0(
- capture.output(attr(rv$data_filtered, "code")),
- collapse = " "
+ shiny::observeEvent(
+ list(
+ shiny::reactive(rv$data),
+ shiny::reactive(rv$data_original),
+ data_filter(),
+ shiny::reactive(rv$data_filtered)
+ ),
+ {
+ out <- gsub(
+ "filter", "dplyr::filter",
+ gsub(
+ "\\s{2,}", " ",
+ paste0(
+ capture.output(attr(rv$data_filtered, "code")),
+ collapse = " "
+ )
)
)
- )
- out <- strsplit(out, "%>%") |>
- unlist() |>
- (\(.x){
- paste(c("data", .x[-1]), collapse = "|> \n ")
- })()
+ out <- strsplit(out, "%>%") |>
+ unlist() |>
+ (\(.x){
+ paste(c("data", .x[-1]), collapse = "|> \n ")
+ })()
- cat(out)
+ rv$code <- append_list(data = out, list = rv$code, index = "filter")
+ }
+ )
+
+ # output$filtered_code <- shiny::renderPrint({
+ # out <- gsub(
+ # "filter", "dplyr::filter",
+ # gsub(
+ # "\\s{2,}", " ",
+ # paste0(
+ # capture.output(attr(rv$data_filtered, "code")),
+ # collapse = " "
+ # )
+ # )
+ # )
+ #
+ # out <- strsplit(out, "%>%") |>
+ # unlist() |>
+ # (\(.x){
+ # paste(c("data", .x[-1]), collapse = "|> \n ")
+ # })()
+ #
+ # cat(out)
+ # })
+
+ output$code_import <- shiny::renderPrint({
+ cat(rv$code$import)
+ })
+
+ output$code_data <- shiny::renderPrint({
+ attr(rv$data, "code")
})
-
+ output$code_filter <- shiny::renderPrint({
+ cat(rv$code$filter)
+ })
##############################################################################
#########
@@ -4790,7 +6027,8 @@ server <- function(input, output, session) {
)
})
- base_vars <- shiny::reactive({
+ ## Collected regression variables
+ regression_vars <- shiny::reactive({
if (is.null(input$include_vars)) {
out <- colnames(rv$data_filtered)
} else {
@@ -4806,7 +6044,7 @@ server <- function(input, output, session) {
label = "Select variable to stratify baseline",
choices = c(
"none",
- rv$data_filtered[base_vars()] |>
+ rv$data_filtered |>
(\(.x){
lapply(.x, \(.c){
if (identical("factor", class(.c))) {
@@ -4878,7 +6116,7 @@ server <- function(input, output, session) {
}
})() |>
(\(.x){
- if (input$add_p == "yes") {
+ if (input$add_p == "yes" & !is.null(by.var)) {
.x |>
gtsummary::add_p() |>
gtsummary::bold_p()
@@ -4900,7 +6138,7 @@ server <- function(input, output, session) {
choices = c(
colnames(rv$list$data)
# ,"none"
- ),
+ ),
multiple = FALSE
)
})
@@ -4913,17 +6151,26 @@ server <- function(input, output, session) {
gt::tab_header(gt::md("**Table 1: Baseline Characteristics**"))
})
- data_correlations_server(id = "correlations",
- data = shiny::reactive({
- out <- dplyr::select(rv$list$data,-!!input$outcome_var_cor)
- # input$outcome_var_cor=="none"){
- # out <- rv$list$data
- # }
- out
- }),
- cutoff = shiny::reactive(input$cor_cutoff))
+ data_correlations_server(
+ id = "correlations",
+ data = shiny::reactive({
+ shiny::req(rv$list$data)
+ out <- dplyr::select(rv$list$data, -!!input$outcome_var_cor)
+ # input$outcome_var_cor=="none"){
+ # out <- rv$list$data
+ # }
+ out
+ }),
+ cutoff = shiny::reactive(input$cor_cutoff)
+ )
+ ##############################################################################
+ #########
+ ######### Data visuals
+ #########
+ ##############################################################################
+ pl <- data_visuals_server("visuals", data = shiny::reactive(rv$data))
##############################################################################
#########
@@ -4952,7 +6199,10 @@ server <- function(input, output, session) {
ls <- do.call(
.fun,
c(
- list(data = rv$list$data),
+ list(data = rv$list$data|>
+ (\(.x){
+ .x[regression_vars()]
+ })()),
list(outcome.str = input$outcome_var),
list(fun.descr = input$regression_type)
)
@@ -5245,7 +6495,7 @@ server <- function(input, output, session) {
readr::write_rds(rv$list$data, file = file)
} else if (type == "dta") {
haven::write_dta(as.data.frame(rv$list$data), path = file)
- } else if (type == "csv"){
+ } else if (type == "csv") {
readr::write_csv(rv$list$data, file = file)
}
}
@@ -5269,7 +6519,7 @@ server <- function(input, output, session) {
########
-#### Current file: /Users/au301842/freesearcheR/inst/apps/data_analysis_modules/launch.R
+#### Current file: /Users/au301842/freesearcheR/inst/apps/freesearcheR/launch.R
########
shinyApp(ui, server)
diff --git a/inst/apps/data_analysis_modules/launch.R b/inst/apps/freesearcheR/launch.R
similarity index 100%
rename from inst/apps/data_analysis_modules/launch.R
rename to inst/apps/freesearcheR/launch.R
diff --git a/inst/apps/data_analysis_modules/rsconnect/shinyapps.io/agdamsbo/freesearcheR.dcf b/inst/apps/freesearcheR/rsconnect/shinyapps.io/agdamsbo/freesearcheR.dcf
similarity index 91%
rename from inst/apps/data_analysis_modules/rsconnect/shinyapps.io/agdamsbo/freesearcheR.dcf
rename to inst/apps/freesearcheR/rsconnect/shinyapps.io/agdamsbo/freesearcheR.dcf
index 6890278..4547950 100644
--- a/inst/apps/data_analysis_modules/rsconnect/shinyapps.io/agdamsbo/freesearcheR.dcf
+++ b/inst/apps/freesearcheR/rsconnect/shinyapps.io/agdamsbo/freesearcheR.dcf
@@ -5,6 +5,6 @@ account: agdamsbo
server: shinyapps.io
hostUrl: https://api.shinyapps.io/v1
appId: 13611288
-bundleId: 9765526
+bundleId: 9852208
url: https://agdamsbo.shinyapps.io/freesearcheR/
version: 1
diff --git a/inst/apps/data_analysis/rsconnect/shinyapps.io/agdamsbo/webResearch.dcf b/inst/apps/freesearcheR/rsconnect/shinyapps.io/agdamsbo/webResearch.dcf
similarity index 100%
rename from inst/apps/data_analysis/rsconnect/shinyapps.io/agdamsbo/webResearch.dcf
rename to inst/apps/freesearcheR/rsconnect/shinyapps.io/agdamsbo/webResearch.dcf
diff --git a/inst/apps/data_analysis_modules/rsconnect/shinyapps.io/cognitiveindex/freesearcheR_dev.dcf b/inst/apps/freesearcheR/rsconnect/shinyapps.io/cognitiveindex/freesearcheR_dev.dcf
similarity index 100%
rename from inst/apps/data_analysis_modules/rsconnect/shinyapps.io/cognitiveindex/freesearcheR_dev.dcf
rename to inst/apps/freesearcheR/rsconnect/shinyapps.io/cognitiveindex/freesearcheR_dev.dcf
diff --git a/inst/apps/data_analysis_modules/rsconnect/shinyapps.io/cognitiveindex/freesearcheR_extra.dcf b/inst/apps/freesearcheR/rsconnect/shinyapps.io/cognitiveindex/freesearcheR_extra.dcf
similarity index 100%
rename from inst/apps/data_analysis_modules/rsconnect/shinyapps.io/cognitiveindex/freesearcheR_extra.dcf
rename to inst/apps/freesearcheR/rsconnect/shinyapps.io/cognitiveindex/freesearcheR_extra.dcf
diff --git a/inst/apps/data_analysis_modules/server.R b/inst/apps/freesearcheR/server.R
similarity index 83%
rename from inst/apps/data_analysis_modules/server.R
rename to inst/apps/freesearcheR/server.R
index 55e55d4..601224b 100644
--- a/inst/apps/data_analysis_modules/server.R
+++ b/inst/apps/freesearcheR/server.R
@@ -15,6 +15,7 @@ library(broom)
library(broom.helpers)
# library(REDCapCAST)
library(easystats)
+library(esquisse)
library(patchwork)
library(DHARMa)
library(apexcharter)
@@ -81,7 +82,8 @@ server <- function(input, output, session) {
data_original = NULL,
data = NULL,
data_filtered = NULL,
- models = NULL
+ models = NULL,
+ code = list()
)
##############################################################################
@@ -99,23 +101,48 @@ server <- function(input, output, session) {
return_class = "data.frame",
read_fns = list(
ods = function(file) {
- readODS::read_ods(path = file, na = consider.na)
+ readODS::read_ods(
+ path = file,
+ # Sheet and skip not implemented for .ods in the original implementation
+ # sheet = sheet,
+ # skip = skip,
+ na = consider.na
+ )
},
dta = function(file) {
- haven::read_dta(file = file, .name_repair = "unique_quiet")
+ haven::read_dta(
+ file = file,
+ .name_repair = "unique_quiet"
+ )
},
csv = function(file) {
- readr::read_csv(file = file, na = consider.na, name_repair = "unique_quiet") #|>
- # janitor::remove_empty(which = "cols", cutoff = 1, quiet = TRUE)
+ readr::read_csv(
+ file = file,
+ na = consider.na,
+ name_repair = "unique_quiet"
+ )
+ },
+ xls = function(file) {
+ openxlsx2::read_xlsx(
+ file = file,
+ sheet = sheet,
+ skip_empty_rows = TRUE,
+ start_row = skip - 1,
+ na.strings = consider.na
+ )
+ },
+ xlsx = function(file) {
+ openxlsx2::read_xlsx(
+ file = file,
+ sheet = sheet,
+ skip_empty_rows = TRUE,
+ start_row = skip - 1,
+ na.strings = consider.na)
},
- # xls = function(file){
- # openxlsx2::read_xlsx(file = file, na.strings = consider.na,)
- # },
- # xlsx = function(file){
- # openxlsx2::read_xlsx(file = file, na.strings = consider.na,)
- # },
rds = function(file) {
- readr::read_rds(file = file, name_repair = "unique_quiet")
+ readr::read_rds(
+ file = file,
+ name_repair = "unique_quiet")
}
)
)
@@ -123,6 +150,7 @@ server <- function(input, output, session) {
shiny::observeEvent(data_file$data(), {
shiny::req(data_file$data())
rv$data_original <- data_file$data()
+ rv$code <- append_list(data = data_file$code(), list = rv$code, index = "import")
})
data_redcap <- m_redcap_readServer(
@@ -143,7 +171,7 @@ server <- function(input, output, session) {
server = TRUE
)
- from_env <- import_globalenv_server(
+ from_env <- datamods::import_globalenv_server(
id = "env",
trigger_return = "change",
btn_show_data = FALSE,
@@ -153,6 +181,7 @@ server <- function(input, output, session) {
shiny::observeEvent(from_env$data(), {
shiny::req(from_env$data())
rv$data_original <- from_env$data()
+ # rv$code <- append_list(data = from_env$code(),list = rv$code,index = "import")
})
@@ -214,12 +243,14 @@ server <- function(input, output, session) {
shiny::observeEvent(
input$modal_cut,
- modal_cut_variable("modal_cut")
+ modal_cut_variable("modal_cut",title = "Modify factor levels")
)
+
data_modal_cut <- cut_variable_server(
id = "modal_cut",
data_r = shiny::reactive(rv$data)
)
+
shiny::observeEvent(data_modal_cut(), rv$data <- data_modal_cut())
######### Modify factor
@@ -228,10 +259,12 @@ server <- function(input, output, session) {
input$modal_update,
datamods::modal_update_factor(id = "modal_update")
)
+
data_modal_update <- datamods::update_factor_server(
id = "modal_update",
data_r = reactive(rv$data)
)
+
shiny::observeEvent(data_modal_update(), {
shiny::removeModal()
rv$data <- data_modal_update()
@@ -257,25 +290,26 @@ server <- function(input, output, session) {
######### Show result
tryCatch(
{
- output$table_mod <- toastui::renderDatagrid({
- shiny::req(rv$data)
- # data <- rv$data
- toastui::datagrid(
- # data = rv$data # ,
- data = data_filter(),
- pagination = 10
- # bordered = TRUE,
- # compact = TRUE,
- # striped = TRUE
- )
- })
+ output$table_mod <- toastui::renderDatagrid({
+ shiny::req(rv$data)
+ # data <- rv$data
+ toastui::datagrid(
+ # data = rv$data # ,
+ data = data_filter(),
+ pagination = 10
+ # bordered = TRUE,
+ # compact = TRUE,
+ # striped = TRUE
+ )
+ })
},
- warning = function(warn) {
- showNotification(paste0(warn), type = "warning")
- },
- error = function(err) {
- showNotification(paste0(err), type = "err")
- })
+ warning = function(warn) {
+ showNotification(paste0(warn), type = "warning")
+ },
+ error = function(err) {
+ showNotification(paste0(err), type = "err")
+ }
+ )
output$code <- renderPrint({
attr(rv$data, "code")
@@ -312,46 +346,78 @@ server <- function(input, output, session) {
shiny::reactive(rv$data),
shiny::reactive(rv$data_original),
data_filter(),
- base_vars(),
+ regression_vars(),
input$complete_cutoff
),
{
rv$data_filtered <- data_filter()
rv$list$data <- data_filter() |>
- REDCapCAST::fct_drop() |>
- (\(.x){
- .x[base_vars()]
- })() #|>
- # janitor::remove_empty(
- # which = "cols",
- # cutoff = input$complete_cutoff / 100
- # )
+ REDCapCAST::fct_drop()
}
)
- output$filtered_code <- shiny::renderPrint({
- out <- gsub(
- "filter", "dplyr::filter",
- gsub(
- "\\s{2,}", " ",
- paste0(
- capture.output(attr(rv$data_filtered, "code")),
- collapse = " "
+ shiny::observeEvent(
+ list(
+ shiny::reactive(rv$data),
+ shiny::reactive(rv$data_original),
+ data_filter(),
+ shiny::reactive(rv$data_filtered)
+ ),
+ {
+ out <- gsub(
+ "filter", "dplyr::filter",
+ gsub(
+ "\\s{2,}", " ",
+ paste0(
+ capture.output(attr(rv$data_filtered, "code")),
+ collapse = " "
+ )
)
)
- )
- out <- strsplit(out, "%>%") |>
- unlist() |>
- (\(.x){
- paste(c("data", .x[-1]), collapse = "|> \n ")
- })()
+ out <- strsplit(out, "%>%") |>
+ unlist() |>
+ (\(.x){
+ paste(c("data", .x[-1]), collapse = "|> \n ")
+ })()
- cat(out)
+ rv$code <- append_list(data = out, list = rv$code, index = "filter")
+ }
+ )
+
+ # output$filtered_code <- shiny::renderPrint({
+ # out <- gsub(
+ # "filter", "dplyr::filter",
+ # gsub(
+ # "\\s{2,}", " ",
+ # paste0(
+ # capture.output(attr(rv$data_filtered, "code")),
+ # collapse = " "
+ # )
+ # )
+ # )
+ #
+ # out <- strsplit(out, "%>%") |>
+ # unlist() |>
+ # (\(.x){
+ # paste(c("data", .x[-1]), collapse = "|> \n ")
+ # })()
+ #
+ # cat(out)
+ # })
+
+ output$code_import <- shiny::renderPrint({
+ cat(rv$code$import)
+ })
+
+ output$code_data <- shiny::renderPrint({
+ attr(rv$data, "code")
})
-
+ output$code_filter <- shiny::renderPrint({
+ cat(rv$code$filter)
+ })
##############################################################################
#########
@@ -410,7 +476,8 @@ server <- function(input, output, session) {
)
})
- base_vars <- shiny::reactive({
+ ## Collected regression variables
+ regression_vars <- shiny::reactive({
if (is.null(input$include_vars)) {
out <- colnames(rv$data_filtered)
} else {
@@ -426,7 +493,7 @@ server <- function(input, output, session) {
label = "Select variable to stratify baseline",
choices = c(
"none",
- rv$data_filtered[base_vars()] |>
+ rv$data_filtered |>
(\(.x){
lapply(.x, \(.c){
if (identical("factor", class(.c))) {
@@ -520,7 +587,7 @@ server <- function(input, output, session) {
choices = c(
colnames(rv$list$data)
# ,"none"
- ),
+ ),
multiple = FALSE
)
})
@@ -533,17 +600,26 @@ server <- function(input, output, session) {
gt::tab_header(gt::md("**Table 1: Baseline Characteristics**"))
})
- data_correlations_server(id = "correlations",
- data = shiny::reactive({
- out <- dplyr::select(rv$list$data,-!!input$outcome_var_cor)
- # input$outcome_var_cor=="none"){
- # out <- rv$list$data
- # }
- out
- }),
- cutoff = shiny::reactive(input$cor_cutoff))
+ data_correlations_server(
+ id = "correlations",
+ data = shiny::reactive({
+ shiny::req(rv$list$data)
+ out <- dplyr::select(rv$list$data, -!!input$outcome_var_cor)
+ # input$outcome_var_cor=="none"){
+ # out <- rv$list$data
+ # }
+ out
+ }),
+ cutoff = shiny::reactive(input$cor_cutoff)
+ )
+ ##############################################################################
+ #########
+ ######### Data visuals
+ #########
+ ##############################################################################
+ pl <- data_visuals_server("visuals", data = shiny::reactive(rv$data))
##############################################################################
#########
@@ -572,7 +648,10 @@ server <- function(input, output, session) {
ls <- do.call(
.fun,
c(
- list(data = rv$list$data),
+ list(data = rv$list$data|>
+ (\(.x){
+ .x[regression_vars()]
+ })()),
list(outcome.str = input$outcome_var),
list(fun.descr = input$regression_type)
)
@@ -865,7 +944,7 @@ server <- function(input, output, session) {
readr::write_rds(rv$list$data, file = file)
} else if (type == "dta") {
haven::write_dta(as.data.frame(rv$list$data), path = file)
- } else if (type == "csv"){
+ } else if (type == "csv") {
readr::write_csv(rv$list$data, file = file)
}
}
diff --git a/inst/apps/data_analysis_modules/ui.R b/inst/apps/freesearcheR/ui.R
similarity index 83%
rename from inst/apps/data_analysis_modules/ui.R
rename to inst/apps/freesearcheR/ui.R
index bc4caa8..bb3e712 100644
--- a/inst/apps/data_analysis_modules/ui.R
+++ b/inst/apps/freesearcheR/ui.R
@@ -8,7 +8,14 @@ ui_elements <- list(
##############################################################################
"home" = bslib::nav_panel(
title = "freesearcheR",
- shiny::markdown(readLines("www/intro.md")),
+ shiny::fluidRow(
+ shiny::column(width = 2),
+ shiny::column(
+ width = 8,
+ shiny::markdown(readLines("www/intro.md")),
+ shiny::column(width = 2)
+ )
+ ),
icon = shiny::icon("home")
),
##############################################################################
@@ -18,21 +25,22 @@ ui_elements <- list(
##############################################################################
"import" = bslib::nav_panel(
title = "Import",
+ shiny::fluidRow(
+ shiny::column(width = 2),
+ shiny::column(
+ width = 8,
+
+
shiny::h4("Choose your data source"),
shiny::br(),
shinyWidgets::radioGroupButtons(
inputId = "source",
selected = "env",
- # label = "Choice: ",
choices = c(
"File upload" = "file",
"REDCap server" = "redcap",
"Local data" = "env"
),
- # checkIcon = list(
- # yes = icon("square-check"),
- # no = icon("square")
- # ),
width = "100%"
),
shiny::helpText("Upload a file from your device, get data directly from REDCap or select a sample data set for testing from the app."),
@@ -60,14 +68,15 @@ ui_elements <- list(
shiny::h5("Exclude in-complete variables"),
shiny::p("Before going further, you can exclude variables with a low degree of completeness."),
shiny::br(),
- shiny::sliderInput(
+ shinyWidgets::noUiSliderInput(
inputId = "complete_cutoff",
label = "Choose completeness threshold (%)",
min = 0,
max = 100,
step = 10,
value = 70,
- ticks = FALSE
+ format = shinyWidgets::wNumbFormat(decimals = 0),
+ color = datamods:::get_primary_color()
),
shiny::helpText("Only include variables with completeness above a specified percentage."),
shiny::br(),
@@ -80,7 +89,10 @@ ui_elements <- list(
),
shiny::helpText('After importing, hit "Start" or navigate to the desired tab.'),
shiny::br(),
- shiny::br()
+ shiny::br(),
+ shiny::column(width = 2)
+ )
+ )
),
##############################################################################
#########
@@ -94,75 +106,15 @@ ui_elements <- list(
title = "Data",
bslib::navset_bar(
fillable = TRUE,
- bslib::nav_panel(
- title = "Summary & filter",
- tags$h3("Data summary and filtering"),
- fluidRow(
- shiny::column(
- width = 9,
- shiny::tags$p(
- "Below is a short summary table of the provided data.
- On the right hand side you have the option to create filters.
- At the bottom you'll find a raw overview of the original vs the modified data."
- )
- )
- ),
- fluidRow(
- # column(
- # width = 3,
- # shiny::uiOutput("filter_vars"),
- # shiny::conditionalPanel(
- # condition = "(typeof input.filter_vars !== 'undefined' && input.filter_vars.length > 0)",
- # datamods::filter_data_ui("filtering", max_height = "500px")
- # )
- # ),
- # column(
- # width = 9,
- # DT::DTOutput(outputId = "filtered_table"),
- # tags$b("Code dplyr:"),
- # verbatimTextOutput(outputId = "filtered_code")
- # ),
- shiny::column(
- width = 9,
- data_summary_ui(id = "data_summary")
- ),
- shiny::column(
- width = 3,
- IDEAFilter::IDEAFilter_ui("data_filter"),
- shiny::tags$br(),
- shiny::tags$b("Filter code:"),
- shiny::verbatimTextOutput(outputId = "filtered_code"),
- shiny::tags$br()
- )
- ),
- fluidRow(
- column(
- width = 6,
- tags$b("Original data:"),
- # verbatimTextOutput("original"),
- verbatimTextOutput("original_str")
- ),
- column(
- width = 6,
- tags$b("Modified data:"),
- # verbatimTextOutput("modified"),
- verbatimTextOutput("modified_str")
- )
- )
- ),
- # bslib::nav_panel(
- # title = "Overview",
- # DT::DTOutput(outputId = "table")
- # ),
bslib::nav_panel(
title = "Modify",
tags$h3("Subset, rename and convert variables"),
fluidRow(
shiny::column(
width = 9,
- shiny::tags$p("Below, you can subset the data (select variables to include on clicking 'Apply changes'), rename variables, set new labels (for nicer tables in the report) and change variable classes (numeric, factor/categorical etc.).
+ shiny::tags$p(shiny::markdown("Below, you can subset the data (select variables to include on clicking 'Apply changes'), rename variables, set new labels (for nicer tables in the report) and change variable classes (numeric, factor/categorical etc.).
Italic text can be edited/changed.
- On the right, you can create and modify factor/categorical variables as well as resetting the data to the originally imported data.")
+ On the right, you can create and modify factor/categorical variables as well as create new variables with *R* code."))
)
),
fluidRow(
@@ -199,17 +151,8 @@ ui_elements <- list(
width = "100%"
),
shiny::tags$br(),
- shiny::helpText("Create a new variable/column based on an R-expression."),
+ shiny::helpText(shiny::markdown("Create a new variable/column based on an *R*-expression.")),
shiny::tags$br(),
- shiny::tags$br(),
- tags$h4("Restore"),
- shiny::actionButton(
- inputId = "data_reset",
- label = "Restore original data",
- width = "100%"
- ),
- shiny::tags$br(),
- shiny::helpText("Reset to original imported dataset. Careful! There is no un-doing."),
shiny::tags$br() # ,
# shiny::tags$br(),
# shiny::tags$br(),
@@ -220,10 +163,88 @@ ui_elements <- list(
)
),
bslib::nav_panel(
- title = "Browser",
+ title = "Filter",
+ tags$h3("Data filtering"),
+ fluidRow(
+ shiny::column(
+ width = 9,
+ shiny::tags$p(
+ "Below is a short summary table of the provided data.
+ On the right hand side you have the option to create filters.
+ At the bottom you'll find a raw overview of the original vs the modified data."
+ )
+ )
+ ),
+ fluidRow(
+ # column(
+ # width = 3,
+ # shiny::uiOutput("filter_vars"),
+ # shiny::conditionalPanel(
+ # condition = "(typeof input.filter_vars !== 'undefined' && input.filter_vars.length > 0)",
+ # datamods::filter_data_ui("filtering", max_height = "500px")
+ # )
+ # ),
+ # column(
+ # width = 9,
+ # DT::DTOutput(outputId = "filtered_table"),
+ # tags$b("Code dplyr:"),
+ # verbatimTextOutput(outputId = "filtered_code")
+ # ),
+ shiny::column(
+ width = 9,
+ data_summary_ui(id = "data_summary")
+ ),
+ shiny::column(
+ width = 3,
+ IDEAFilter::IDEAFilter_ui("data_filter"),
+ # shiny::tags$br(),
+ # shiny::tags$b("Filter code:"),
+ # shiny::verbatimTextOutput(outputId = "filtered_code"),
+ shiny::tags$br()
+ )
+ )
+ ),
+ bslib::nav_panel(
+ title = "Restore",
+ tags$h3("Compare to original and restore"),
+ fluidRow(
+ shiny::column(
+ width = 9,
+ shiny::tags$p(
+ "Right below, you have the option to restore to the originally imported data.
+ At the bottom you'll find a raw overview of the original vs the modified data."
+ )
+ ),
+ shiny::tags$br(),
+ tags$h4("Restore"),
+ shiny::actionButton(
+ inputId = "data_reset",
+ label = "Restore original data",
+ width = "100%"
+ ),
+ shiny::tags$br(),
+ shiny::helpText("Reset to original imported dataset. Careful! There is no un-doing.")
+ ),
+ fluidRow(
+ column(
+ width = 6,
+ tags$b("Original data:"),
+ # verbatimTextOutput("original"),
+ verbatimTextOutput("original_str")
+ ),
+ column(
+ width = 6,
+ tags$b("Modified data:"),
+ # verbatimTextOutput("modified"),
+ verbatimTextOutput("modified_str")
+ )
+ )
+ ),
+ bslib::nav_panel(
+ title = "Browse",
tags$h3("Browse the provided data"),
shiny::tags$p(
- "Below is a data table with all the modified data provided to browse and understand data."
+ "Below is a table with all the modified data provided to browse and understand data."
),
shinyWidgets::html_dependency_winbox(),
# fluidRow(
@@ -323,14 +344,15 @@ ui_elements <- list(
shiny::uiOutput("outcome_var_cor"),
shiny::helpText("This variable will be excluded from the correlation plot."),
shiny::br(),
- shiny::sliderInput(
+ shinyWidgets::noUiSliderInput(
inputId = "cor_cutoff",
label = "Correlation cut-off",
min = 0,
max = 1,
- step = .02,
+ step = .01,
value = .8,
- ticks = FALSE
+ format = shinyWidgets::wNumbFormat(decimals = 2),
+ color = datamods:::get_primary_color()
)
)
)
@@ -347,6 +369,35 @@ ui_elements <- list(
),
##############################################################################
#########
+ ######### Download panel
+ #########
+ ##############################################################################
+ "visuals" = bslib::nav_panel(
+ title = "Visuals",
+ id = "navvisuals",
+ do.call(
+ bslib::navset_bar,
+ c(
+ data_visuals_ui("visuals"),
+ shiny::tagList(
+ bslib::nav_spacer(),
+ bslib::nav_panel(
+ title = "Notes",
+ shiny::fluidRow(
+ shiny::column(width = 2),
+ shiny::column(
+ width = 8,
+ shiny::markdown(readLines("www/notes_visuals.md")),
+ shiny::column(width = 2)
+ )
+ )
+ )
+ )
+ )
+ )
+ ),
+ ##############################################################################
+ #########
######### Regression analyses panel
#########
##############################################################################
@@ -467,11 +518,17 @@ ui_elements <- list(
bslib::nav_panel(
title = "Download",
id = "navdownload",
+ shiny::fluidRow(
+ shiny::column(width = 2),
+ shiny::column(
+ width = 8,
shiny::fluidRow(
shiny::column(
width = 6,
shiny::h4("Report"),
shiny::helpText("Choose your favourite output file format for further work, and download, when the analyses are done."),
+ shiny::br(),
+ shiny::br(),
shiny::selectInput(
inputId = "output_type",
label = "Output format",
@@ -497,6 +554,8 @@ ui_elements <- list(
width = 6,
shiny::h4("Data"),
shiny::helpText("Choose your favourite output data format to download the modified data."),
+ shiny::br(),
+ shiny::br(),
shiny::selectInput(
inputId = "data_type",
label = "Data format",
@@ -507,6 +566,8 @@ ui_elements <- list(
"CSV" = "csv"
)
),
+ shiny::helpText("No metadata is saved when exporting to csv."),
+ shiny::br(),
shiny::br(),
# Button
shiny::downloadButton(
@@ -516,7 +577,17 @@ ui_elements <- list(
)
)
),
- shiny::br()
+ shiny::br(),
+ shiny::br(),
+ shiny::tags$b("Code snippets:"),
+ shiny::verbatimTextOutput(outputId = "code_import"),
+ shiny::verbatimTextOutput(outputId = "code_data"),
+ shiny::verbatimTextOutput(outputId = "code_filter"),
+ shiny::tags$br(),
+ shiny::br(),
+ shiny::column(width = 2)
+ )
+ )
),
##############################################################################
#########
@@ -568,6 +639,7 @@ ui <- bslib::page_fixed(
ui_elements$import,
ui_elements$overview,
ui_elements$describe,
+ ui_elements$visuals,
ui_elements$analyze,
ui_elements$download,
bslib::nav_spacer(),
diff --git a/inst/apps/data_analysis_modules/www/intro.html b/inst/apps/freesearcheR/www/intro.html
similarity index 100%
rename from inst/apps/data_analysis_modules/www/intro.html
rename to inst/apps/freesearcheR/www/intro.html
diff --git a/inst/apps/data_analysis_modules/www/intro.md b/inst/apps/freesearcheR/www/intro.md
similarity index 86%
rename from inst/apps/data_analysis_modules/www/intro.md
rename to inst/apps/freesearcheR/www/intro.md
index 56cc8e3..337fd2c 100644
--- a/inst/apps/data_analysis_modules/www/intro.md
+++ b/inst/apps/freesearcheR/www/intro.md
@@ -1,6 +1,6 @@
# Welcome
-This is the ***freesearcheR*** data analysis tool. We intend the ***freesearcheR*** to be a powerful and free tool for easy data evaluation and analysis at the hands of the clinician.
+This is the ***freesearcheR*** data analysis tool. We intend the ***freesearcheR*** to be a powerful and free tool for easy data evaluation and analysis at the hands of the clinician. If you need more advanced tools for regression models or plotting, you'll probably be better off using *R* or similar directly on your own machine.
By intention, this tool has been designed to be simple to use with a minimum of mandatory options to keep the workflow streamlined, while also including a few options to go even further.
@@ -12,6 +12,8 @@ There are some simple steps to go through (see corresponding tabs in the top):
1. Evaluate data using descriptive analyses methods and inspect cross-correlations
+1. Create simple, clean plots for data overview.
+
1. Create regression models for even more advanced data analyses
- Linear, dichotomous or ordinal logistic regression will be used depending on specified outcome variable
diff --git a/inst/apps/freesearcheR/www/notes_visuals.html b/inst/apps/freesearcheR/www/notes_visuals.html
new file mode 100644
index 0000000..b5f8545
--- /dev/null
+++ b/inst/apps/freesearcheR/www/notes_visuals.html
@@ -0,0 +1,413 @@
+
+
+
+
+
+
+
+
+
+
+
+
+
+notes_visuals
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
Basic visualisations
+
This section on plotting data is kept very minimal, and includes only
+the most common plot types for clinical projects.
+
If you want to go further, have a look at these sites with
+suggestions and sample code for data plotting:
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
diff --git a/inst/apps/freesearcheR/www/notes_visuals.md b/inst/apps/freesearcheR/www/notes_visuals.md
new file mode 100644
index 0000000..6ae6f70
--- /dev/null
+++ b/inst/apps/freesearcheR/www/notes_visuals.md
@@ -0,0 +1,11 @@
+# Basic visualisations
+
+This section on plotting data is kept very minimal, and includes only the most common plot types for clinical projects.
+
+If you want to go further, have a look at these sites with suggestions and sample code for data plotting:
+
+- [*R* Charts](https://r-charts.com/): Extensive gallery with great plots
+
+- [*R* Graph gallery](https://r-graph-gallery.com/): Another gallery with great graphs
+
+- [grphics principles](https://graphicsprinciples.github.io/): Easy to follow recommendations for clear visuals.
diff --git a/inst/apps/data_analysis_modules/www/report.rmd b/inst/apps/freesearcheR/www/report.rmd
similarity index 100%
rename from inst/apps/data_analysis_modules/www/report.rmd
rename to inst/apps/freesearcheR/www/report.rmd
diff --git a/inst/apps/data_analysis_modules/www/umami-app.html b/inst/apps/freesearcheR/www/umami-app.html
similarity index 100%
rename from inst/apps/data_analysis_modules/www/umami-app.html
rename to inst/apps/freesearcheR/www/umami-app.html
diff --git a/inst/apps/teal_test/app.R b/inst/apps/teal_test/app.R
deleted file mode 100644
index 24292d9..0000000
--- a/inst/apps/teal_test/app.R
+++ /dev/null
@@ -1,113 +0,0 @@
-library(teal)
-library(teal.modules.general)
-library(teal.widgets)
-library(readr)
-library(MASS)
-library(stats)
-library(gtsummary)
-library(gt)
-library(openxlsx2)
-library(haven)
-library(readODS)
-library(shiny)
-library(bslib)
-library(assertthat)
-library(dplyr)
-library(quarto)
-library(here)
-library(broom)
-library(broom.helpers)
-library(REDCapCAST)
-library(easystats)
-library(patchwork)
-library(DHARMa)
-# library(IDEAFilter)
-# if (!requireNamespace("webResearch")) {
-# devtools::install_github("agdamsbo/webResearch", quiet = TRUE, upgrade = "never")
-# }
-# library(webResearch)
-
-if (file.exists(here::here("functions.R"))) {
- source(here::here("functions.R"))
-}
-
-## This setup works for a single possible source
-## The UI will work, even with server dependent selection and REDCap exports,
-## but when submitting, it only works for the module mentioned first in the server function
-## Also most data formatting is lost when passing to a teal_data_object. Bummer!
-##
-## FRUSTRATION!!
-##
-## As I read this, two different apps has to be created as things are now: one for upload, one for REDCap.
-## https://insightsengineering.github.io/teal/latest-tag/articles/data-as-shiny-module.html#warning
-##
-##
-##
-## Ad option to widen data or keep long (new function, would allow easy(ish) MMRM analyses)
-
-
-
-tm_variable_browser_module <- tm_variable_browser(
- label = "Variable browser",
- ggplot2_args = ggplot2_args(
- labs = list(subtitle = "Plot generated by Variable Browser Module")
- )
-)
-
-filters <- teal::teal_slices()
-
-app_source <- "https://github.com/agdamsbo/freesearcheR"
-gh_issues_page <- "https://github.com/agdamsbo/freesearcheR/issues"
-
-header <- tags$span(
- style = "display: flex; align-items: center; justify-content: space-between; margin: 10px 0 10px 0;",
- tags$span("REDCap data evaluation", style = "font-size: 30px;") # ,
- # tags$span(
- # style = "display: flex; align-items: center;",
- # tags$img(src = nest_logo, alt = "NEST logo", height = "45px", style = "margin-right:10px;"),
- # tags$span(style = "font-size: 24px;", "agdamsbo")
- # )
-)
-
-footer <- tags$p(
- "This is a simple, app for REDCap-based data browsing and evaluation. Data is only stored temporarily and deleted when the browser is refreshed or closed. The app was developed by AGDamsbo using the {teal} framework for building Shiny apps:",
- tags$a(href = app_source, target = "_blank", "Source Code"), ", ",
- tags$a(href = gh_issues_page, target = "_blank", "Report Issues")
-)
-
-# teal_init <- function(data = tdm_redcap_read,
-# filter = filters,
-# modules = teal::modules(
-# teal.modules.general::tm_data_table("Data Table"),
-# tm_variable_browser_module
-# ),
-# title = teal::build_app_title("REDCap browser (teal)"),
-# header = header,
-# footer = footer, ...) {
-# teal::init(data,
-# filter,
-# modules,
-# title,
-# header,
-# footer,
-# ...
-# )
-# }
-#
-# redcap_browser_app <- teal_init(data = tdm_data_upload)
-
-app <- teal::init(
- data=tdm_data_read,
- # data = tdm_data_upload,
- # data = tdm_redcap_read,
- filter = filters,
- modules = modules(
- tm_data_table("Data Table"),
- tm_variable_browser_module
- ),
- title = build_app_title("REDCap data evaluation"),
- header = header,
- footer = footer
-)
-
-shinyApp(app$ui, app$server)
diff --git a/renv.lock b/renv.lock
index 135b316..a4543d5 100644
--- a/renv.lock
+++ b/renv.lock
@@ -128,29 +128,6 @@
"Maintainer": "Joe Cheng ",
"Repository": "CRAN"
},
- "Deriv": {
- "Package": "Deriv",
- "Version": "4.1.6",
- "Source": "Repository",
- "Type": "Package",
- "Title": "Symbolic Differentiation",
- "Date": "2024-09-12",
- "Authors@R": "c(person(given=\"Andrew\", family=\"Clausen\", role=\"aut\"), person(given=\"Serguei\", family=\"Sokol\", role=c(\"aut\", \"cre\"), email=\"sokol@insa-toulouse.fr\", comment = c(ORCID = \"0000-0002-5674-3327\")), person(given=\"Andreas\", family=\"Rappold\", role=\"ctb\", email=\"arappold@gmx.at\"))",
- "Description": "R-based solution for symbolic differentiation. It admits user-defined function as well as function substitution in arguments of functions to be differentiated. Some symbolic simplification is part of the work.",
- "License": "GPL (>= 3)",
- "Suggests": [
- "testthat (>= 0.11.0)"
- ],
- "BugReports": "https://github.com/sgsokol/Deriv/issues",
- "RoxygenNote": "7.3.1",
- "Imports": [
- "methods"
- ],
- "NeedsCompilation": "no",
- "Author": "Andrew Clausen [aut], Serguei Sokol [aut, cre] (), Andreas Rappold [ctb]",
- "Maintainer": "Serguei Sokol ",
- "Repository": "CRAN"
- },
"Formula": {
"Package": "Formula",
"Version": "1.2-5",
@@ -411,60 +388,6 @@
"Maintainer": "Martin Maechler ",
"Repository": "CRAN"
},
- "MatrixModels": {
- "Package": "MatrixModels",
- "Version": "0.5-3",
- "Source": "Repository",
- "Date": "2023-11-06",
- "Title": "Modelling with Sparse and Dense Matrices",
- "Author": "Douglas Bates and Martin Maechler ",
- "Maintainer": "Martin Maechler ",
- "Contact": "Matrix-authors@R-project.org",
- "Description": "Modelling with sparse and dense 'Matrix' matrices, using modular prediction and response module classes.",
- "Depends": [
- "R (>= 3.6.0)"
- ],
- "Imports": [
- "stats",
- "methods",
- "Matrix (>= 1.6-0)"
- ],
- "ImportsNote": "_not_yet_stats4",
- "Encoding": "UTF-8",
- "LazyLoad": "yes",
- "License": "GPL (>= 2)",
- "URL": "https://Matrix.R-forge.R-project.org/, https://r-forge.r-project.org/R/?group_id=61",
- "BugReports": "https://R-forge.R-project.org/tracker/?func=add&atid=294&group_id=61",
- "NeedsCompilation": "no",
- "Repository": "CRAN"
- },
- "R.cache": {
- "Package": "R.cache",
- "Version": "0.16.0",
- "Source": "Repository",
- "Depends": [
- "R (>= 2.14.0)"
- ],
- "Imports": [
- "utils",
- "R.methodsS3 (>= 1.8.1)",
- "R.oo (>= 1.24.0)",
- "R.utils (>= 2.10.1)",
- "digest (>= 0.6.13)"
- ],
- "Title": "Fast and Light-Weight Caching (Memoization) of Objects and Results to Speed Up Computations",
- "Authors@R": "c(person(\"Henrik\", \"Bengtsson\", role=c(\"aut\", \"cre\", \"cph\"), email = \"henrikb@braju.com\"))",
- "Author": "Henrik Bengtsson [aut, cre, cph]",
- "Maintainer": "Henrik Bengtsson ",
- "Description": "Memoization can be used to speed up repetitive and computational expensive function calls. The first time a function that implements memoization is called the results are stored in a cache memory. The next time the function is called with the same set of parameters, the results are momentarily retrieved from the cache avoiding repeating the calculations. With this package, any R object can be cached in a key-value storage where the key can be an arbitrary set of R objects. The cache memory is persistent (on the file system).",
- "License": "LGPL (>= 2.1)",
- "LazyLoad": "TRUE",
- "URL": "https://github.com/HenrikBengtsson/R.cache",
- "BugReports": "https://github.com/HenrikBengtsson/R.cache/issues",
- "RoxygenNote": "7.2.1",
- "NeedsCompilation": "no",
- "Repository": "CRAN"
- },
"R.methodsS3": {
"Package": "R.methodsS3",
"Version": "1.8.2",
@@ -798,33 +721,6 @@
"Maintainer": "Georgi N. Boshnakov ",
"Repository": "CRAN"
},
- "SparseM": {
- "Package": "SparseM",
- "Version": "1.84-2",
- "Source": "Repository",
- "Authors@R": "c( person(\"Roger\", \"Koenker\", role = c(\"cre\",\"aut\"), email = \"rkoenker@uiuc.edu\"), person(c(\"Pin\", \"Tian\"), \"Ng\", role = c(\"ctb\"), comment = \"Contributions to Sparse QR code\", email = \"pin.ng@nau.edu\") , person(\"Yousef\", \"Saad\", role = c(\"ctb\"), comment = \"author of sparskit2\") , person(\"Ben\", \"Shaby\", role = c(\"ctb\"), comment = \"author of chol2csr\") , person(\"Martin\", \"Maechler\", role = \"ctb\", comment = c(\"chol() tweaks; S4\", ORCID = \"0000-0002-8685-9910\")) )",
- "Maintainer": "Roger Koenker ",
- "Depends": [
- "R (>= 2.15)",
- "methods"
- ],
- "Imports": [
- "graphics",
- "stats",
- "utils"
- ],
- "VignetteBuilder": "knitr",
- "Suggests": [
- "knitr"
- ],
- "Description": "Some basic linear algebra functionality for sparse matrices is provided: including Cholesky decomposition and backsolving as well as standard R subsetting and Kronecker products.",
- "License": "GPL (>= 2)",
- "Title": "Sparse Linear Algebra",
- "URL": "http://www.econ.uiuc.edu/~roger/research/sparse/sparse.html",
- "NeedsCompilation": "yes",
- "Author": "Roger Koenker [cre, aut], Pin Tian Ng [ctb] (Contributions to Sparse QR code), Yousef Saad [ctb] (author of sparskit2), Ben Shaby [ctb] (author of chol2csr), Martin Maechler [ctb] (chol() tweaks; S4, )",
- "Repository": "CRAN"
- },
"V8": {
"Package": "V8",
"Version": "6.0.1",
@@ -861,27 +757,6 @@
"Maintainer": "Jeroen Ooms ",
"Repository": "CRAN"
},
- "abind": {
- "Package": "abind",
- "Version": "1.4-8",
- "Source": "Repository",
- "Date": "2024-09-08",
- "Title": "Combine Multidimensional Arrays",
- "Authors@R": "c(person(\"Tony\", \"Plate\", email = \"tplate@acm.org\", role = c(\"aut\", \"cre\")), person(\"Richard\", \"Heiberger\", role = c(\"aut\")))",
- "Maintainer": "Tony Plate ",
- "Description": "Combine multidimensional arrays into a single array. This is a generalization of 'cbind' and 'rbind'. Works with vectors, matrices, and higher-dimensional arrays (aka tensors). Also provides functions 'adrop', 'asub', and 'afill' for manipulating, extracting and replacing data in arrays.",
- "Depends": [
- "R (>= 1.5.0)"
- ],
- "Imports": [
- "methods",
- "utils"
- ],
- "License": "MIT + file LICENSE",
- "NeedsCompilation": "no",
- "Author": "Tony Plate [aut, cre], Richard Heiberger [aut]",
- "Repository": "CRAN"
- },
"ape": {
"Package": "ape",
"Version": "5.8-1",
@@ -1749,90 +1624,6 @@
"Maintainer": "Gábor Csárdi ",
"Repository": "CRAN"
},
- "car": {
- "Package": "car",
- "Version": "3.1-3",
- "Source": "Repository",
- "Date": "2024-09-23",
- "Title": "Companion to Applied Regression",
- "Authors@R": "c(person(\"John\", \"Fox\", role = c(\"aut\", \"cre\"), email = \"jfox@mcmaster.ca\"), person(\"Sanford\", \"Weisberg\", role = \"aut\", email = \"sandy@umn.edu\"), person(\"Brad\", \"Price\", role = \"aut\", email = \"brad.price@mail.wvu.edu\"), person(\"Daniel\", \"Adler\", role=\"ctb\"), person(\"Douglas\", \"Bates\", role = \"ctb\"), person(\"Gabriel\", \"Baud-Bovy\", role = \"ctb\"), person(\"Ben\", \"Bolker\", role=\"ctb\"), person(\"Steve\", \"Ellison\", role=\"ctb\"), person(\"David\", \"Firth\", role = \"ctb\"), person(\"Michael\", \"Friendly\", role = \"ctb\"), person(\"Gregor\", \"Gorjanc\", role = \"ctb\"), person(\"Spencer\", \"Graves\", role = \"ctb\"), person(\"Richard\", \"Heiberger\", role = \"ctb\"), person(\"Pavel\", \"Krivitsky\", role = \"ctb\"), person(\"Rafael\", \"Laboissiere\", role = \"ctb\"), person(\"Martin\", \"Maechler\", role=\"ctb\"), person(\"Georges\", \"Monette\", role = \"ctb\"), person(\"Duncan\", \"Murdoch\", role=\"ctb\"), person(\"Henric\", \"Nilsson\", role = \"ctb\"), person(\"Derek\", \"Ogle\", role = \"ctb\"), person(\"Brian\", \"Ripley\", role = \"ctb\"), person(\"Tom\", \"Short\", role=\"ctb\"), person(\"William\", \"Venables\", role = \"ctb\"), person(\"Steve\", \"Walker\", role=\"ctb\"), person(\"David\", \"Winsemius\", role=\"ctb\"), person(\"Achim\", \"Zeileis\", role = \"ctb\"), person(\"R-Core\", role=\"ctb\"))",
- "Depends": [
- "R (>= 3.5.0)",
- "carData (>= 3.0-0)"
- ],
- "Imports": [
- "abind",
- "Formula",
- "MASS",
- "mgcv",
- "nnet",
- "pbkrtest (>= 0.4-4)",
- "quantreg",
- "grDevices",
- "utils",
- "stats",
- "graphics",
- "lme4 (>= 1.1-27.1)",
- "nlme",
- "scales"
- ],
- "Suggests": [
- "alr4",
- "boot",
- "coxme",
- "effects",
- "knitr",
- "leaps",
- "lmtest",
- "Matrix",
- "MatrixModels",
- "ordinal",
- "plotrix",
- "mvtnorm",
- "rgl (>= 0.111.3)",
- "rio",
- "sandwich",
- "SparseM",
- "survival",
- "survey"
- ],
- "ByteCompile": "yes",
- "LazyLoad": "yes",
- "Description": "Functions to Accompany J. Fox and S. Weisberg, An R Companion to Applied Regression, Third Edition, Sage, 2019.",
- "License": "GPL (>= 2)",
- "URL": "https://r-forge.r-project.org/projects/car/, https://CRAN.R-project.org/package=car, https://www.john-fox.ca/Companion/index.html",
- "VignetteBuilder": "knitr",
- "NeedsCompilation": "no",
- "Author": "John Fox [aut, cre], Sanford Weisberg [aut], Brad Price [aut], Daniel Adler [ctb], Douglas Bates [ctb], Gabriel Baud-Bovy [ctb], Ben Bolker [ctb], Steve Ellison [ctb], David Firth [ctb], Michael Friendly [ctb], Gregor Gorjanc [ctb], Spencer Graves [ctb], Richard Heiberger [ctb], Pavel Krivitsky [ctb], Rafael Laboissiere [ctb], Martin Maechler [ctb], Georges Monette [ctb], Duncan Murdoch [ctb], Henric Nilsson [ctb], Derek Ogle [ctb], Brian Ripley [ctb], Tom Short [ctb], William Venables [ctb], Steve Walker [ctb], David Winsemius [ctb], Achim Zeileis [ctb], R-Core [ctb]",
- "Maintainer": "John Fox ",
- "Repository": "CRAN"
- },
- "carData": {
- "Package": "carData",
- "Version": "3.0-5",
- "Source": "Repository",
- "Date": "2022-01-05",
- "Title": "Companion to Applied Regression Data Sets",
- "Authors@R": "c(person(\"John\", \"Fox\", role = c(\"aut\", \"cre\"), email = \"jfox@mcmaster.ca\"), person(\"Sanford\", \"Weisberg\", role = \"aut\", email = \"sandy@umn.edu\"), person(\"Brad\", \"Price\", role = \"aut\", email = \"brad.price@mail.wvu.edu\"))",
- "Depends": [
- "R (>= 3.5.0)"
- ],
- "Suggests": [
- "car (>= 3.0-0)"
- ],
- "LazyLoad": "yes",
- "LazyData": "yes",
- "Description": "Datasets to Accompany J. Fox and S. Weisberg, An R Companion to Applied Regression, Third Edition, Sage (2019).",
- "License": "GPL (>= 2)",
- "URL": "https://r-forge.r-project.org/projects/car/, https://CRAN.R-project.org/package=carData, https://socialsciences.mcmaster.ca/jfox/Books/Companion/index.html",
- "Author": "John Fox [aut, cre], Sanford Weisberg [aut], Brad Price [aut]",
- "Maintainer": "John Fox ",
- "Repository": "CRAN",
- "Repository/R-Forge/Project": "car",
- "Repository/R-Forge/Revision": "694",
- "Repository/R-Forge/DateTimeStamp": "2022-01-05 19:40:37",
- "NeedsCompilation": "no"
- },
"cards": {
"Package": "cards",
"Version": "0.4.0",
@@ -2354,56 +2145,6 @@
"Author": "Dominique Makowski [aut, inv] (), Brenton M. Wiernik [aut, cre] (), Indrajeet Patil [aut] (), Daniel Lüdecke [aut] (), Mattan S. Ben-Shachar [aut] (), Rémi Thériault [aut] (), Mark White [rev], Maximilian M. Rabe [rev] ()",
"Repository": "CRAN"
},
- "cowplot": {
- "Package": "cowplot",
- "Version": "1.1.3",
- "Source": "Repository",
- "Title": "Streamlined Plot Theme and Plot Annotations for 'ggplot2'",
- "Authors@R": "person( given = \"Claus O.\", family = \"Wilke\", role = c(\"aut\", \"cre\"), email = \"wilke@austin.utexas.edu\", comment = c(ORCID = \"0000-0002-7470-9261\") )",
- "Description": "Provides various features that help with creating publication-quality figures with 'ggplot2', such as a set of themes, functions to align plots and arrange them into complex compound figures, and functions that make it easy to annotate plots and or mix plots with images. The package was originally written for internal use in the Wilke lab, hence the name (Claus O. Wilke's plot package). It has also been used extensively in the book Fundamentals of Data Visualization.",
- "URL": "https://wilkelab.org/cowplot/",
- "BugReports": "https://github.com/wilkelab/cowplot/issues",
- "Depends": [
- "R (>= 3.5.0)"
- ],
- "Imports": [
- "ggplot2 (>= 3.4.0)",
- "grid",
- "gtable",
- "grDevices",
- "methods",
- "rlang",
- "scales"
- ],
- "License": "GPL-2",
- "Suggests": [
- "Cairo",
- "covr",
- "dplyr",
- "forcats",
- "gridGraphics (>= 0.4-0)",
- "knitr",
- "lattice",
- "magick",
- "maps",
- "PASWR",
- "patchwork",
- "rmarkdown",
- "ragg",
- "testthat (>= 1.0.0)",
- "tidyr",
- "vdiffr (>= 0.3.0)",
- "VennDiagram"
- ],
- "VignetteBuilder": "knitr",
- "Collate": "'add_sub.R' 'align_plots.R' 'as_grob.R' 'as_gtable.R' 'axis_canvas.R' 'cowplot.R' 'draw.R' 'get_plot_component.R' 'get_axes.R' 'get_titles.R' 'get_legend.R' 'get_panel.R' 'gtable.R' 'key_glyph.R' 'plot_grid.R' 'save.R' 'set_null_device.R' 'setup.R' 'stamp.R' 'themes.R' 'utils_ggplot2.R'",
- "RoxygenNote": "7.2.3",
- "Encoding": "UTF-8",
- "NeedsCompilation": "no",
- "Author": "Claus O. Wilke [aut, cre] ()",
- "Maintainer": "Claus O. Wilke ",
- "Repository": "CRAN"
- },
"cpp11": {
"Package": "cpp11",
"Version": "0.5.1",
@@ -2758,54 +2499,6 @@
"Maintainer": "Dirk Eddelbuettel ",
"Repository": "CRAN"
},
- "doBy": {
- "Package": "doBy",
- "Version": "4.6.25",
- "Source": "Repository",
- "Title": "Groupwise Statistics, LSmeans, Linear Estimates, Utilities",
- "Authors@R": "c( person(given = \"Ulrich\", family = \"Halekoh\", email = \"uhalekoh@health.sdu.dk\", role = c(\"aut\", \"cph\")), person(given = \"Søren\", family = \"Højsgaard\", email = \"sorenh@math.aau.dk\", role = c(\"aut\", \"cre\", \"cph\")) )",
- "Maintainer": "Søren Højsgaard ",
- "Description": "Utility package containing: 1) Facilities for working with grouped data: 'do' something to data stratified 'by' some variables. 2) LSmeans (least-squares means), general linear estimates. 3) Restrict functions to a smaller domain. 4) Miscellaneous other utilities.",
- "Encoding": "UTF-8",
- "VignetteBuilder": "knitr",
- "LazyData": "true",
- "LazyDataCompression": "xz",
- "URL": "https://github.com/hojsgaard/doBy",
- "License": "GPL (>= 2)",
- "Depends": [
- "R (>= 4.2.0)",
- "methods"
- ],
- "Imports": [
- "boot",
- "broom",
- "cowplot",
- "Deriv",
- "dplyr",
- "ggplot2",
- "MASS",
- "Matrix",
- "modelr",
- "microbenchmark",
- "rlang",
- "tibble",
- "tidyr"
- ],
- "Suggests": [
- "geepack",
- "knitr",
- "lme4",
- "markdown",
- "multcomp",
- "pbkrtest (>= 0.5.2)",
- "survival",
- "testthat (>= 2.1.0)"
- ],
- "RoxygenNote": "7.3.2",
- "NeedsCompilation": "no",
- "Author": "Ulrich Halekoh [aut, cph], Søren Højsgaard [aut, cre, cph]",
- "Repository": "CRAN"
- },
"doParallel": {
"Package": "doParallel",
"Version": "1.0.17",
@@ -3098,86 +2791,6 @@
"Author": "Mattan S. Ben-Shachar [aut, cre] (), Dominique Makowski [aut] (), Daniel Lüdecke [aut] (), Indrajeet Patil [aut] (), Brenton M. Wiernik [aut] (), Rémi Thériault [aut] (), Ken Kelley [ctb], David Stanley [ctb], Aaron Caldwell [ctb] (), Jessica Burnett [rev] (), Johannes Karreth [rev] (), Philip Waggoner [aut, ctb] ()",
"Repository": "CRAN"
},
- "emmeans": {
- "Package": "emmeans",
- "Version": "1.10.7",
- "Source": "Repository",
- "Type": "Package",
- "Title": "Estimated Marginal Means, aka Least-Squares Means",
- "Date": "2025-01-30",
- "Authors@R": "c(person(\"Russell V.\", \"Lenth\", role = c(\"aut\", \"cre\", \"cph\"), email = \"russell-lenth@uiowa.edu\"), person(\"Balazs\", \"Banfai\", role = \"ctb\"), person(\"Ben\", \"Bolker\", role = \"ctb\"), person(\"Paul\", \"Buerkner\", role = \"ctb\"), person(\"Iago\", \"Giné-Vázquez\", role = \"ctb\"), person(\"Maxime\", \"Herve\", role = \"ctb\"), person(\"Maarten\", \"Jung\", role = \"ctb\"), person(\"Jonathon\", \"Love\", role = \"ctb\"), person(\"Fernando\", \"Miguez\", role = \"ctb\"), person(\"Julia\", \"Piaskowski\", role = \"ctb\"), person(\"Hannes\", \"Riebl\", role = \"ctb\"), person(\"Henrik\", \"Singmann\", role = \"ctb\"))",
- "Depends": [
- "R (>= 4.1.0)"
- ],
- "Imports": [
- "estimability (>= 1.4.1)",
- "graphics",
- "methods",
- "numDeriv",
- "stats",
- "utils",
- "mvtnorm"
- ],
- "Suggests": [
- "bayesplot",
- "bayestestR",
- "biglm",
- "brms",
- "car",
- "coda (>= 0.17)",
- "compositions",
- "ggplot2",
- "lattice",
- "logspline",
- "mediation",
- "mgcv",
- "multcomp",
- "multcompView",
- "nlme",
- "ordinal (>= 2014.11-12)",
- "pbkrtest (>= 0.4-1)",
- "lme4",
- "lmerTest (>= 2.0.32)",
- "MASS",
- "MuMIn",
- "rsm",
- "knitr",
- "rmarkdown",
- "sandwich",
- "scales",
- "splines",
- "testthat",
- "tibble",
- "xtable (>= 1.8-2)"
- ],
- "Enhances": [
- "CARBayes",
- "coxme",
- "gee",
- "geepack",
- "MCMCglmm",
- "MCMCpack",
- "mice",
- "nnet",
- "pscl",
- "rstanarm",
- "sommer",
- "survival"
- ],
- "URL": "https://rvlenth.github.io/emmeans/,https://rvlenth.github.io/emmeans/",
- "BugReports": "https://github.com/rvlenth/emmeans/issues",
- "LazyData": "yes",
- "ByteCompile": "yes",
- "Description": "Obtain estimated marginal means (EMMs) for many linear, generalized linear, and mixed models. Compute contrasts or linear functions of EMMs, trends, and comparisons of slopes. Plots and other displays. Least-squares means are discussed, and the term \"estimated marginal means\" is suggested, in Searle, Speed, and Milliken (1980) Population marginal means in the linear model: An alternative to least squares means, The American Statistician 34(4), 216-221 .",
- "License": "GPL-2 | GPL-3",
- "Encoding": "UTF-8",
- "RoxygenNote": "7.3.2",
- "VignetteBuilder": "knitr",
- "NeedsCompilation": "no",
- "Author": "Russell V. Lenth [aut, cre, cph], Balazs Banfai [ctb], Ben Bolker [ctb], Paul Buerkner [ctb], Iago Giné-Vázquez [ctb], Maxime Herve [ctb], Maarten Jung [ctb], Jonathon Love [ctb], Fernando Miguez [ctb], Julia Piaskowski [ctb], Hannes Riebl [ctb], Henrik Singmann [ctb]",
- "Maintainer": "Russell V. Lenth ",
- "Repository": "CRAN"
- },
"esquisse": {
"Package": "esquisse",
"Version": "2.0.1",
@@ -3224,33 +2837,6 @@
"Maintainer": "Victor Perrier ",
"Repository": "CRAN"
},
- "estimability": {
- "Package": "estimability",
- "Version": "1.5.1",
- "Source": "Repository",
- "Type": "Package",
- "Title": "Tools for Assessing Estimability of Linear Predictions",
- "Date": "2024-05-12",
- "Authors@R": "c(person(\"Russell\", \"Lenth\", role = c(\"aut\", \"cre\", \"cph\"), email = \"russell-lenth@uiowa.edu\"))",
- "Depends": [
- "stats",
- "R(>= 4.1.0)"
- ],
- "Suggests": [
- "knitr",
- "rmarkdown"
- ],
- "Description": "Provides tools for determining estimability of linear functions of regression coefficients, and 'epredict' methods that handle non-estimable cases correctly. Estimability theory is discussed in many linear-models textbooks including Chapter 3 of Monahan, JF (2008), \"A Primer on Linear Models\", Chapman and Hall (ISBN 978-1-4200-6201-4).",
- "URL": "https://github.com/rvlenth/estimability, https://rvlenth.github.io/estimability/",
- "BugReports": "https://github.com/rvlenth/estimability/issues",
- "ByteCompile": "yes",
- "License": "GPL (>= 3)",
- "VignetteBuilder": "knitr",
- "NeedsCompilation": "no",
- "Author": "Russell Lenth [aut, cre, cph]",
- "Maintainer": "Russell Lenth ",
- "Repository": "CRAN"
- },
"evaluate": {
"Package": "evaluate",
"Version": "1.0.3",
@@ -3659,51 +3245,6 @@
"Maintainer": "R Core Team ",
"Repository": "CRAN"
},
- "formatters": {
- "Package": "formatters",
- "Version": "0.5.10",
- "Source": "Repository",
- "Title": "ASCII Formatting for Values and Tables",
- "Date": "2025-01-08",
- "Authors@R": "c( person(\"Gabriel\", \"Becker\", , \"gabembecker@gmail.com\", role = \"aut\", comment = \"original creator of the package\"), person(\"Adrian\", \"Waddell\", , \"adrian.waddell@gene.com\", role = \"aut\"), person(\"Davide\", \"Garolini\", , \"davide.garolini@roche.com\", role = \"aut\"), person(\"Emily\", \"de la Rua\", , \"emily.de_la_rua@contractors.roche.com\", role = \"aut\"), person(\"Abinaya\", \"Yogasekaram\", , \"abinaya.yogasekaram@contractors.roche.com\", role = \"ctb\"), person(\"Joe\", \"Zhu\", , \"joe.zhu@roche.com\", role = c(\"aut\", \"cre\"), comment = c(ORCID = \"0000-0001-7566-2787\")), person(\"F. Hoffmann-La Roche AG\", role = c(\"cph\", \"fnd\")) )",
- "Description": "We provide a framework for rendering complex tables to ASCII, and a set of formatters for transforming values or sets of values into ASCII-ready display strings.",
- "License": "Apache License 2.0",
- "URL": "https://insightsengineering.github.io/formatters/, https://github.com/insightsengineering/formatters/",
- "BugReports": "https://github.com/insightsengineering/formatters/issues",
- "Depends": [
- "methods",
- "R (>= 2.10)"
- ],
- "Imports": [
- "checkmate (>= 2.1.0)",
- "grid",
- "htmltools (>= 0.5.3)",
- "lifecycle (>= 0.2.0)",
- "stringi (>= 1.7.12)"
- ],
- "Suggests": [
- "dplyr (>= 1.0.9)",
- "gt (>= 0.10.0)",
- "huxtable (>= 2.0.0)",
- "knitr (>= 1.42)",
- "r2rtf (>= 0.3.2)",
- "rmarkdown (>= 2.23)",
- "testthat (>= 3.0.4)",
- "withr (>= 2.0.0)"
- ],
- "VignetteBuilder": "knitr, rmarkdown",
- "Config/Needs/verdepcheck": "mllg/checkmate, rstudio/htmltools, r-lib/lifecycle, tidyverse/dplyr, rstudio/gt, hughjonesd/huxtable, yihui/knitr, Merck/r2rtf, rstudio/rmarkdown, gagolews/stringi, r-lib/testthat, r-lib/withr",
- "Config/Needs/website": "insightsengineering/nesttemplate",
- "Encoding": "UTF-8",
- "Language": "en-US",
- "LazyData": "true",
- "RoxygenNote": "7.3.2",
- "Collate": "'data.R' 'format_value.R' 'matrix_form.R' 'generics.R' 'labels.R' 'mpf_exporters.R' 'package.R' 'page_size.R' 'pagination.R' 'tostring.R' 'utils.R' 'zzz.R'",
- "NeedsCompilation": "no",
- "Author": "Gabriel Becker [aut] (original creator of the package), Adrian Waddell [aut], Davide Garolini [aut], Emily de la Rua [aut], Abinaya Yogasekaram [ctb], Joe Zhu [aut, cre] (), F. Hoffmann-La Roche AG [cph, fnd]",
- "Maintainer": "Joe Zhu ",
- "Repository": "CRAN"
- },
"fs": {
"Package": "fs",
"Version": "1.6.5",
@@ -4150,46 +3691,6 @@
"Maintainer": "David Gohel ",
"Repository": "CRAN"
},
- "ggmosaic": {
- "Package": "ggmosaic",
- "Version": "0.3.3",
- "Source": "Repository",
- "Title": "Mosaic Plots in the 'ggplot2' Framework",
- "Authors@R": "c(person(given = \"Haley\", family = \"Jeppson\", role = c(\"aut\", \"cre\"), email = \"hjeppson@iastate.edu\"), person(given = \"Heike\", family = \"Hofmann\", role = \"aut\", email = \"hofmann@iastate.edu\"), person(given = \"Di\", family = \"Cook\", role = \"aut\", email = \"dicook@monash.edu\"), person(given = \"Hadley\", family = \"Wickham\", role = \"ctb\", email = \"hadley@rstudio.com\"))",
- "Description": "Mosaic plots in the 'ggplot2' framework. Mosaic plot functionality is provided in a single 'ggplot2' layer by calling the geom 'mosaic'.",
- "License": "GPL (>= 2)",
- "URL": "https://github.com/haleyjeppson/ggmosaic",
- "BugReports": "https://github.com/haleyjeppson/ggmosaic",
- "Depends": [
- "ggplot2 (>= 3.3.0)",
- "R (>= 3.5.0)"
- ],
- "Imports": [
- "productplots",
- "dplyr",
- "plotly (>= 4.5.5)",
- "purrr",
- "rlang",
- "tidyr",
- "ggrepel",
- "scales"
- ],
- "Suggests": [
- "gridExtra",
- "knitr",
- "NHANES",
- "rmarkdown",
- "patchwork"
- ],
- "VignetteBuilder": "knitr",
- "Encoding": "UTF-8",
- "LazyData": "true",
- "RoxygenNote": "7.1.1",
- "NeedsCompilation": "no",
- "Author": "Haley Jeppson [aut, cre], Heike Hofmann [aut], Di Cook [aut], Hadley Wickham [ctb]",
- "Maintainer": "Haley Jeppson ",
- "Repository": "CRAN"
- },
"ggplot2": {
"Package": "ggplot2",
"Version": "3.5.1",
@@ -4259,53 +3760,45 @@
"Maintainer": "Thomas Lin Pedersen ",
"Repository": "CRAN"
},
- "ggrepel": {
- "Package": "ggrepel",
- "Version": "0.9.6",
+ "ggridges": {
+ "Package": "ggridges",
+ "Version": "0.5.6",
"Source": "Repository",
- "Authors@R": "c( person(\"Kamil\", \"Slowikowski\", email = \"kslowikowski@gmail.com\", role = c(\"aut\", \"cre\"), comment = c(ORCID = \"0000-0002-2843-6370\")), person(\"Alicia\", \"Schep\", role = \"ctb\", comment = c(ORCID = \"0000-0002-3915-0618\")), person(\"Sean\", \"Hughes\", role = \"ctb\", comment = c(ORCID = \"0000-0002-9409-9405\")), person(\"Trung Kien\", \"Dang\", role = \"ctb\", comment = c(ORCID = \"0000-0001-7562-6495\")), person(\"Saulius\", \"Lukauskas\", role = \"ctb\"), person(\"Jean-Olivier\", \"Irisson\", role = \"ctb\", comment = c(ORCID = \"0000-0003-4920-3880\")), person(\"Zhian N\", \"Kamvar\", role = \"ctb\", comment = c(ORCID = \"0000-0003-1458-7108\")), person(\"Thompson\", \"Ryan\", role = \"ctb\", comment = c(ORCID = \"0000-0002-0450-8181\")), person(\"Dervieux\", \"Christophe\", role = \"ctb\", comment = c(ORCID = \"0000-0003-4474-2498\")), person(\"Yutani\", \"Hiroaki\", role = \"ctb\"), person(\"Pierre\", \"Gramme\", role = \"ctb\"), person(\"Amir Masoud\", \"Abdol\", role = \"ctb\"), person(\"Malcolm\", \"Barrett\", role = \"ctb\", comment = c(ORCID = \"0000-0003-0299-5825\")), person(\"Robrecht\", \"Cannoodt\", role = \"ctb\", comment = c(ORCID = \"0000-0003-3641-729X\")), person(\"Michał\", \"Krassowski\", role = \"ctb\", comment = c(ORCID = \"0000-0002-9638-7785\")), person(\"Michael\", \"Chirico\", role = \"ctb\", comment = c(ORCID = \"0000-0003-0787-087X\")), person(\"Pedro\", \"Aphalo\", role = \"ctb\", comment = c(ORCID = \"0000-0003-3385-972X\")), person(\"Francis\", \"Barton\", role = \"ctb\") )",
- "Title": "Automatically Position Non-Overlapping Text Labels with 'ggplot2'",
- "Description": "Provides text and label geoms for 'ggplot2' that help to avoid overlapping text labels. Labels repel away from each other and away from the data points.",
+ "Type": "Package",
+ "Title": "Ridgeline Plots in 'ggplot2'",
+ "Authors@R": "person( given = \"Claus O.\", family = \"Wilke\", role = c(\"aut\", \"cre\"), email = \"wilke@austin.utexas.edu\", comment = c(ORCID = \"0000-0002-7470-9261\") )",
+ "Description": "Ridgeline plots provide a convenient way of visualizing changes in distributions over time or space. This package enables the creation of such plots in 'ggplot2'.",
+ "URL": "https://wilkelab.org/ggridges/",
+ "BugReports": "https://github.com/wilkelab/ggridges/issues",
"Depends": [
- "R (>= 3.0.0)",
- "ggplot2 (>= 2.2.0)"
+ "R (>= 3.2)"
],
"Imports": [
- "grid",
- "Rcpp",
- "rlang (>= 0.3.0)",
- "scales (>= 0.5.0)",
- "withr (>= 2.5.0)"
+ "ggplot2 (>= 3.4.0)",
+ "grid (>= 3.0.0)",
+ "scales (>= 0.4.1)",
+ "withr (>= 2.1.1)"
],
+ "License": "GPL-2 | file LICENSE",
+ "LazyData": "true",
"Suggests": [
+ "covr",
+ "dplyr",
+ "patchwork",
+ "ggplot2movies",
+ "forcats",
"knitr",
"rmarkdown",
"testthat",
- "svglite",
- "vdiffr",
- "gridExtra",
- "ggpp",
- "patchwork",
- "devtools",
- "prettydoc",
- "ggbeeswarm",
- "dplyr",
- "magrittr",
- "readr",
- "stringr"
+ "vdiffr"
],
"VignetteBuilder": "knitr",
- "License": "GPL-3 | file LICENSE",
- "URL": "https://ggrepel.slowkow.com/, https://github.com/slowkow/ggrepel",
- "BugReports": "https://github.com/slowkow/ggrepel/issues",
- "RoxygenNote": "7.3.1",
- "LinkingTo": [
- "Rcpp"
- ],
+ "Collate": "'data.R' 'ggridges.R' 'geoms.R' 'geomsv.R' 'geoms-gradient.R' 'geom-density-line.R' 'position.R' 'scale-cyclical.R' 'scale-point.R' 'scale-vline.R' 'stats.R' 'theme.R' 'utils_ggplot2.R' 'utils.R'",
+ "RoxygenNote": "7.2.3",
"Encoding": "UTF-8",
- "NeedsCompilation": "yes",
- "Author": "Kamil Slowikowski [aut, cre] (), Alicia Schep [ctb] (), Sean Hughes [ctb] (), Trung Kien Dang [ctb] (), Saulius Lukauskas [ctb], Jean-Olivier Irisson [ctb] (), Zhian N Kamvar [ctb] (), Thompson Ryan [ctb] (), Dervieux Christophe [ctb] (), Yutani Hiroaki [ctb], Pierre Gramme [ctb], Amir Masoud Abdol [ctb], Malcolm Barrett [ctb] (), Robrecht Cannoodt [ctb] (), Michał Krassowski [ctb] (), Michael Chirico [ctb] (), Pedro Aphalo [ctb] (), Francis Barton [ctb]",
- "Maintainer": "Kamil Slowikowski ",
+ "NeedsCompilation": "no",
+ "Author": "Claus O. Wilke [aut, cre] ()",
+ "Maintainer": "Claus O. Wilke ",
"Repository": "CRAN"
},
"ggstats": {
@@ -5899,62 +5392,6 @@
"Maintainer": "Achim Zeileis ",
"Repository": "CRAN"
},
- "logger": {
- "Package": "logger",
- "Version": "0.4.0",
- "Source": "Repository",
- "Type": "Package",
- "Title": "A Lightweight, Modern and Flexible Logging Utility",
- "Date": "2024-10-19",
- "Authors@R": "c( person(\"Gergely\", \"Daróczi\", , \"daroczig@rapporter.net\", role = c(\"aut\", \"cre\"), comment = c(ORCID = \"0000-0003-3149-8537\")), person(\"Hadley\", \"Wickham\", , \"hadley@posit.co\", role = \"aut\", comment = c(ORCID = \"0000-0003-4757-117X\")), person(\"System1\", role = \"fnd\") )",
- "Description": "Inspired by the the 'futile.logger' R package and 'logging' Python module, this utility provides a flexible and extensible way of formatting and delivering log messages with low overhead.",
- "License": "MIT + file LICENSE",
- "URL": "https://daroczig.github.io/logger/",
- "BugReports": "https://github.com/daroczig/logger/issues",
- "Depends": [
- "R (>= 4.0.0)"
- ],
- "Imports": [
- "utils"
- ],
- "Suggests": [
- "botor",
- "covr",
- "crayon",
- "devtools",
- "glue",
- "jsonlite",
- "knitr",
- "mirai (>= 1.3.0)",
- "pander",
- "parallel",
- "R.utils",
- "rmarkdown",
- "roxygen2",
- "RPushbullet",
- "rsyslog",
- "shiny",
- "slackr (>= 1.4.1)",
- "syslognet",
- "telegram",
- "testthat (>= 3.0.0)",
- "withr"
- ],
- "Enhances": [
- "futile.logger",
- "log4r",
- "logging"
- ],
- "VignetteBuilder": "knitr",
- "Config/testthat/edition": "3",
- "Config/testthat/parallel": "TRUE",
- "Encoding": "UTF-8",
- "RoxygenNote": "7.3.2",
- "NeedsCompilation": "no",
- "Author": "Gergely Daróczi [aut, cre] (), Hadley Wickham [aut] (), System1 [fnd]",
- "Maintainer": "Gergely Daróczi ",
- "Repository": "CRAN"
- },
"lubridate": {
"Package": "lubridate",
"Version": "1.9.4",
@@ -6126,35 +5563,6 @@
"NeedsCompilation": "yes",
"Repository": "CRAN"
},
- "microbenchmark": {
- "Package": "microbenchmark",
- "Version": "1.5.0",
- "Source": "Repository",
- "Title": "Accurate Timing Functions",
- "Description": "Provides infrastructure to accurately measure and compare the execution time of R expressions.",
- "Authors@R": "c(person(\"Olaf\", \"Mersmann\", role=c(\"aut\")), person(\"Claudia\", \"Beleites\", role=c(\"ctb\")), person(\"Rainer\", \"Hurling\", role=c(\"ctb\")), person(\"Ari\", \"Friedman\", role=c(\"ctb\")), person(given=c(\"Joshua\",\"M.\"), family=\"Ulrich\", role=\"cre\", email=\"josh.m.ulrich@gmail.com\"))",
- "URL": "https://github.com/joshuaulrich/microbenchmark/",
- "BugReports": "https://github.com/joshuaulrich/microbenchmark/issues/",
- "License": "BSD_2_clause + file LICENSE",
- "Depends": [
- "R (>= 3.2.0)"
- ],
- "Imports": [
- "graphics",
- "stats"
- ],
- "Suggests": [
- "ggplot2",
- "multcomp",
- "RUnit"
- ],
- "SystemRequirements": "On a Unix-alike, one of the C functions mach_absolute_time (macOS), clock_gettime or gethrtime. If none of these is found, the obsolescent POSIX function gettimeofday will be tried.",
- "ByteCompile": "yes",
- "NeedsCompilation": "yes",
- "Author": "Olaf Mersmann [aut], Claudia Beleites [ctb], Rainer Hurling [ctb], Ari Friedman [ctb], Joshua M. Ulrich [cre]",
- "Maintainer": "Joshua M. Ulrich ",
- "Repository": "CRAN"
- },
"mime": {
"Package": "mime",
"Version": "0.12",
@@ -6331,45 +5739,6 @@
"Author": "Dominique Makowski [aut, cre] (), Daniel Lüdecke [aut] (), Mattan S. Ben-Shachar [aut] (), Indrajeet Patil [aut] ()",
"Repository": "CRAN"
},
- "modelr": {
- "Package": "modelr",
- "Version": "0.1.11",
- "Source": "Repository",
- "Title": "Modelling Functions that Work with the Pipe",
- "Authors@R": "c( person(\"Hadley\", \"Wickham\", , \"hadley@posit.co\", role = c(\"aut\", \"cre\")), person(\"Posit Software, PBC\", role = c(\"cph\", \"fnd\")) )",
- "Description": "Functions for modelling that help you seamlessly integrate modelling into a pipeline of data manipulation and visualisation.",
- "License": "GPL-3",
- "URL": "https://modelr.tidyverse.org, https://github.com/tidyverse/modelr",
- "BugReports": "https://github.com/tidyverse/modelr/issues",
- "Depends": [
- "R (>= 3.2)"
- ],
- "Imports": [
- "broom",
- "magrittr",
- "purrr (>= 0.2.2)",
- "rlang (>= 1.0.6)",
- "tibble",
- "tidyr (>= 0.8.0)",
- "tidyselect",
- "vctrs"
- ],
- "Suggests": [
- "compiler",
- "covr",
- "ggplot2",
- "testthat (>= 3.0.0)"
- ],
- "Config/Needs/website": "tidyverse/tidytemplate",
- "Encoding": "UTF-8",
- "LazyData": "true",
- "RoxygenNote": "7.2.3",
- "Config/testthat/edition": "3",
- "NeedsCompilation": "no",
- "Author": "Hadley Wickham [aut, cre], Posit Software, PBC [cph, fnd]",
- "Maintainer": "Hadley Wickham ",
- "Repository": "CRAN"
- },
"munsell": {
"Package": "munsell",
"Version": "0.5.1",
@@ -6395,68 +5764,6 @@
"NeedsCompilation": "no",
"Repository": "CRAN"
},
- "mvtnorm": {
- "Package": "mvtnorm",
- "Version": "1.3-3",
- "Source": "Repository",
- "Title": "Multivariate Normal and t Distributions",
- "Date": "2025-01-09",
- "Authors@R": "c(person(\"Alan\", \"Genz\", role = \"aut\"), person(\"Frank\", \"Bretz\", role = \"aut\"), person(\"Tetsuhisa\", \"Miwa\", role = \"aut\"), person(\"Xuefei\", \"Mi\", role = \"aut\"), person(\"Friedrich\", \"Leisch\", role = \"ctb\"), person(\"Fabian\", \"Scheipl\", role = \"ctb\"), person(\"Bjoern\", \"Bornkamp\", role = \"ctb\", comment = c(ORCID = \"0000-0002-6294-8185\")), person(\"Martin\", \"Maechler\", role = \"ctb\", comment = c(ORCID = \"0000-0002-8685-9910\")), person(\"Torsten\", \"Hothorn\", role = c(\"aut\", \"cre\"), email = \"Torsten.Hothorn@R-project.org\", comment = c(ORCID = \"0000-0001-8301-0471\")))",
- "Description": "Computes multivariate normal and t probabilities, quantiles, random deviates, and densities. Log-likelihoods for multivariate Gaussian models and Gaussian copulae parameterised by Cholesky factors of covariance or precision matrices are implemented for interval-censored and exact data, or a mix thereof. Score functions for these log-likelihoods are available. A class representing multiple lower triangular matrices and corresponding methods are part of this package.",
- "Imports": [
- "stats"
- ],
- "Depends": [
- "R(>= 3.5.0)"
- ],
- "Suggests": [
- "qrng",
- "numDeriv"
- ],
- "License": "GPL-2",
- "URL": "http://mvtnorm.R-forge.R-project.org",
- "NeedsCompilation": "yes",
- "Author": "Alan Genz [aut], Frank Bretz [aut], Tetsuhisa Miwa [aut], Xuefei Mi [aut], Friedrich Leisch [ctb], Fabian Scheipl [ctb], Bjoern Bornkamp [ctb] (), Martin Maechler [ctb] (), Torsten Hothorn [aut, cre] ()",
- "Maintainer": "Torsten Hothorn ",
- "Repository": "CRAN"
- },
- "nestcolor": {
- "Package": "nestcolor",
- "Version": "0.1.3",
- "Source": "Repository",
- "Type": "Package",
- "Title": "Colors for NEST Graphs",
- "Date": "2025-01-21",
- "Authors@R": "c( person(\"Joe\", \"Zhu\", , \"joe.zhu@roche.com\", role = c(\"aut\", \"cre\"), comment = c(ORCID = \"0000-0001-7566-2787\")), person(\"Emily\", \"de la Rua\", , \"emily.de_la_rua@contractors.roche.com\", role = \"aut\"), person(\"F. Hoffmann-La Roche AG\", role = c(\"cph\", \"fnd\")) )",
- "Description": "Clinical reporting figures require to use consistent colors and configurations. As a part of the Roche open-source clinical reporting project, namely the NEST project, the 'nestcolor' package specifies the color code and default theme with specifying 'ggplot2' theme parameters. Users can easily customize color and theme settings before using the reset of NEST packages to ensure consistent settings in both static and interactive output at the downstream.",
- "License": "Apache License 2.0",
- "URL": "https://insightsengineering.github.io/nestcolor/, https://github.com/insightsengineering/nestcolor/",
- "BugReports": "https://github.com/insightsengineering/nestcolor/issues",
- "Depends": [
- "R (>= 3.6)"
- ],
- "Imports": [
- "checkmate (>= 2.1.0)",
- "ggplot2 (>= 3.5.0)",
- "lifecycle (>= 1.0.3)"
- ],
- "Suggests": [
- "knitr (>= 1.42)",
- "rmarkdown (>= 2.19)",
- "testthat (>= 3.0.4)"
- ],
- "VignetteBuilder": "knitr, rmarkdown",
- "RdMacros": "lifecycle",
- "Config/Needs/verdepcheck": "mllg/checkmate, tidyverse/ggplot2, r-lib/lifecycle, yihui/knitr, rstudio/rmarkdown, r-lib/testthat",
- "Config/Needs/website": "insightsengineering/nesttemplate",
- "Encoding": "UTF-8",
- "Language": "en-US",
- "RoxygenNote": "7.3.2",
- "NeedsCompilation": "no",
- "Author": "Joe Zhu [aut, cre] (), Emily de la Rua [aut], F. Hoffmann-La Roche AG [cph, fnd]",
- "Maintainer": "Joe Zhu ",
- "Repository": "CRAN"
- },
"nlme": {
"Package": "nlme",
"Version": "3.1-167",
@@ -6543,26 +5850,6 @@
"Maintainer": "Brian Ripley ",
"Repository": "CRAN"
},
- "numDeriv": {
- "Package": "numDeriv",
- "Version": "2016.8-1.1",
- "Source": "Repository",
- "Title": "Accurate Numerical Derivatives",
- "Description": "Methods for calculating (usually) accurate numerical first and second order derivatives. Accurate calculations are done using 'Richardson''s' extrapolation or, when applicable, a complex step derivative is available. A simple difference method is also provided. Simple difference is (usually) less accurate but is much quicker than 'Richardson''s' extrapolation and provides a useful cross-check. Methods are provided for real scalar and vector valued functions.",
- "Depends": [
- "R (>= 2.11.1)"
- ],
- "LazyLoad": "yes",
- "ByteCompile": "yes",
- "License": "GPL-2",
- "Copyright": "2006-2011, Bank of Canada. 2012-2016, Paul Gilbert",
- "Author": "Paul Gilbert and Ravi Varadhan",
- "Maintainer": "Paul Gilbert ",
- "URL": "http://optimizer.r-forge.r-project.org/",
- "NeedsCompilation": "no",
- "Repository": "RSPM",
- "Encoding": "UTF-8"
- },
"officer": {
"Package": "officer",
"Version": "0.6.7",
@@ -7020,42 +6307,6 @@
"Author": "Thomas Lin Pedersen [cre, aut] ()",
"Repository": "CRAN"
},
- "pbkrtest": {
- "Package": "pbkrtest",
- "Version": "0.5.3",
- "Source": "Repository",
- "Title": "Parametric Bootstrap, Kenward-Roger and Satterthwaite Based Methods for Test in Mixed Models",
- "Authors@R": "c( person(given = \"Ulrich\", family = \"Halekoh\", email = \"uhalekoh@health.sdu.dk\", role = c(\"aut\", \"cph\")), person(given = \"Søren\", family = \"Højsgaard\", email = \"sorenh@math.aau.dk\", role = c(\"aut\", \"cre\", \"cph\")) )",
- "Maintainer": "Søren Højsgaard ",
- "Description": "Computes p-values based on (a) Satterthwaite or Kenward-Rogers degree of freedom methods and (b) parametric bootstrap for mixed effects models as implemented in the 'lme4' package. Implements parametric bootstrap test for generalized linear mixed models as implemented in 'lme4' and generalized linear models. The package is documented in the paper by Halekoh and Højsgaard, (2012, ). Please see 'citation(\"pbkrtest\")' for citation details.",
- "URL": "https://people.math.aau.dk/~sorenh/software/pbkrtest/",
- "Depends": [
- "R (>= 4.2.0)",
- "lme4 (>= 1.1.31)"
- ],
- "Imports": [
- "broom",
- "dplyr",
- "MASS",
- "methods",
- "numDeriv",
- "Matrix (>= 1.2.3)",
- "doBy"
- ],
- "Suggests": [
- "markdown",
- "knitr"
- ],
- "Encoding": "UTF-8",
- "VignetteBuilder": "knitr",
- "License": "GPL (>= 2)",
- "ByteCompile": "Yes",
- "RoxygenNote": "7.3.1",
- "LazyData": "true",
- "NeedsCompilation": "no",
- "Author": "Ulrich Halekoh [aut, cph], Søren Højsgaard [aut, cre, cph]",
- "Repository": "CRAN"
- },
"pbmcapply": {
"Package": "pbmcapply",
"Version": "1.5.1",
@@ -7499,32 +6750,6 @@
"Maintainer": "Gábor Csárdi ",
"Repository": "CRAN"
},
- "productplots": {
- "Package": "productplots",
- "Version": "0.1.1",
- "Source": "Repository",
- "Title": "Product Plots for R",
- "Description": "Framework for visualising tables of counts, proportions and probabilities. The framework is called product plots, alluding to the computation of area as a product of height and width, and the statistical concept of generating a joint distribution from the product of conditional and marginal distributions. The framework, with extensions, is sufficient to encompass over 20 visualisations previously described in fields of statistical graphics and 'infovis', including bar charts, mosaic plots, 'treemaps', equal area plots and fluctuation diagrams.",
- "Authors@R": "c( person(\"Hadley\", \"Wickham\", , \"hadley@rstudio.com\", c(\"aut\", \"cre\")), person(\"Heike\", \"Hofmann\", , \"heike.hofmann@gmail.com\", role = \"aut\") )",
- "Imports": [
- "plyr",
- "ggplot2"
- ],
- "Suggests": [
- "reshape2",
- "testthat",
- "covr"
- ],
- "License": "GPL-2",
- "LazyData": "true",
- "RoxygenNote": "5.0.1",
- "URL": "https://github.com/hadley/productplots",
- "BugReports": "https://github.com/hadley/productplots/issues",
- "NeedsCompilation": "no",
- "Author": "Hadley Wickham [aut, cre], Heike Hofmann [aut]",
- "Maintainer": "Hadley Wickham ",
- "Repository": "CRAN"
- },
"progress": {
"Package": "progress",
"Version": "1.2.3",
@@ -7862,44 +7087,6 @@
"Maintainer": "Adam Loy ",
"Repository": "CRAN"
},
- "quantreg": {
- "Package": "quantreg",
- "Version": "6.00",
- "Source": "Repository",
- "Title": "Quantile Regression",
- "Description": "Estimation and inference methods for models for conditional quantile functions: Linear and nonlinear parametric and non-parametric (total variation penalized) models for conditional quantiles of a univariate response and several methods for handling censored survival data. Portfolio selection methods based on expected shortfall risk are also now included. See Koenker, R. (2005) Quantile Regression, Cambridge U. Press, and Koenker, R. et al. (2017) Handbook of Quantile Regression, CRC Press, .",
- "Authors@R": "c( person(\"Roger\", \"Koenker\", role = c(\"cre\",\"aut\"), email = \"rkoenker@illinois.edu\"), person(\"Stephen\", \"Portnoy\", role = c(\"ctb\"), comment = \"Contributions to Censored QR code\", email = \"sportnoy@illinois.edu\"), person(c(\"Pin\", \"Tian\"), \"Ng\", role = c(\"ctb\"), comment = \"Contributions to Sparse QR code\", email = \"pin.ng@nau.edu\"), person(\"Blaise\", \"Melly\", role = c(\"ctb\"), comment = \"Contributions to preprocessing code\", email = \"mellyblaise@gmail.com\"), person(\"Achim\", \"Zeileis\", role = c(\"ctb\"), comment = \"Contributions to dynrq code essentially identical to his dynlm code\", email = \"Achim.Zeileis@uibk.ac.at\"), person(\"Philip\", \"Grosjean\", role = c(\"ctb\"), comment = \"Contributions to nlrq code\", email = \"phgrosjean@sciviews.org\"), person(\"Cleve\", \"Moler\", role = c(\"ctb\"), comment = \"author of several linpack routines\"), person(\"Yousef\", \"Saad\", role = c(\"ctb\"), comment = \"author of sparskit2\"), person(\"Victor\", \"Chernozhukov\", role = c(\"ctb\"), comment = \"contributions to extreme value inference code\"), person(\"Ivan\", \"Fernandez-Val\", role = c(\"ctb\"), comment = \"contributions to extreme value inference code\"), person(\"Martin\", \"Maechler\", role = \"ctb\", comment = c(\"tweaks (src/chlfct.f, 'tiny','Large')\", ORCID = \"0000-0002-8685-9910\")), person(c(\"Brian\", \"D\"), \"Ripley\", role = c(\"trl\",\"ctb\"), comment = \"Initial (2001) R port from S (to my everlasting shame -- how could I have been so slow to adopt R!) and for numerous other suggestions and useful advice\", email = \"ripley@stats.ox.ac.uk\"))",
- "Maintainer": "Roger Koenker ",
- "Repository": "CRAN",
- "Depends": [
- "R (>= 3.5)",
- "stats",
- "SparseM"
- ],
- "Imports": [
- "methods",
- "graphics",
- "Matrix",
- "MatrixModels",
- "survival",
- "MASS"
- ],
- "Suggests": [
- "interp",
- "rgl",
- "logspline",
- "nor1mix",
- "Formula",
- "zoo",
- "R.rsp",
- "conquer"
- ],
- "License": "GPL (>= 2)",
- "URL": "https://www.r-project.org",
- "NeedsCompilation": "yes",
- "VignetteBuilder": "R.rsp",
- "Author": "Roger Koenker [cre, aut], Stephen Portnoy [ctb] (Contributions to Censored QR code), Pin Tian Ng [ctb] (Contributions to Sparse QR code), Blaise Melly [ctb] (Contributions to preprocessing code), Achim Zeileis [ctb] (Contributions to dynrq code essentially identical to his dynlm code), Philip Grosjean [ctb] (Contributions to nlrq code), Cleve Moler [ctb] (author of several linpack routines), Yousef Saad [ctb] (author of sparskit2), Victor Chernozhukov [ctb] (contributions to extreme value inference code), Ivan Fernandez-Val [ctb] (contributions to extreme value inference code), Martin Maechler [ctb] (tweaks (src/chlfct.f, 'tiny','Large'), ), Brian D Ripley [trl, ctb] (Initial (2001) R port from S (to my everlasting shame -- how could I have been so slow to adopt R!) and for numerous other suggestions and useful advice)"
- },
"quarto": {
"Package": "quarto",
"Version": "1.4.4",
@@ -8326,6 +7513,66 @@
"NeedsCompilation": "no",
"Repository": "CRAN"
},
+ "rempsyc": {
+ "Package": "rempsyc",
+ "Version": "0.1.9",
+ "Source": "Repository",
+ "Title": "Convenience Functions for Psychology",
+ "Date": "2025-02-01",
+ "Authors@R": "person(\"Rémi\", \"Thériault\", , \"remi.theriault@mail.mcgill.ca\", role = c(\"aut\", \"cre\"), comment = c(ORCID = \"0000-0003-4315-6788\"))",
+ "Description": "Make your workflow faster and easier. Easily customizable plots (via 'ggplot2'), nice APA tables (following the style of the *American Psychological Association*) exportable to Word (via 'flextable'), easily run statistical tests or check assumptions, and automatize various other tasks.",
+ "License": "GPL (>= 3)",
+ "URL": "https://rempsyc.remi-theriault.com",
+ "BugReports": "https://github.com/rempsyc/rempsyc/issues",
+ "Depends": [
+ "R (>= 3.6)"
+ ],
+ "Imports": [
+ "rlang",
+ "dplyr (>= 1.1.0)"
+ ],
+ "Suggests": [
+ "flextable (>= 0.9.1)",
+ "ggplot2 (>= 3.4.0)",
+ "effectsize (>= 0.8.5)",
+ "performance (>= 0.10.0)",
+ "insight (>= 0.18.4)",
+ "correlation",
+ "datawizard (>= 0.5.0)",
+ "report (>= 0.5.1)",
+ "modelbased",
+ "see",
+ "lmtest",
+ "ggrepel",
+ "boot",
+ "bootES",
+ "ggsignif",
+ "qqplotr (>= 0.0.6)",
+ "broom",
+ "emmeans",
+ "ggpubr",
+ "interactions",
+ "openxlsx2 (>= 0.8)",
+ "patchwork",
+ "psych",
+ "VennDiagram",
+ "Rmisc",
+ "methods",
+ "tidyr",
+ "testthat (>= 3.0.0)",
+ "knitr",
+ "markdown",
+ "rmarkdown"
+ ],
+ "VignetteBuilder": "knitr",
+ "Config/testthat/edition": "3",
+ "Encoding": "UTF-8",
+ "RoxygenNote": "7.3.2",
+ "NeedsCompilation": "no",
+ "Author": "Rémi Thériault [aut, cre] ()",
+ "Maintainer": "Rémi Thériault ",
+ "Repository": "CRAN"
+ },
"renv": {
"Package": "renv",
"Version": "1.1.0",
@@ -8577,50 +7824,6 @@
"Maintainer": "Lionel Henry ",
"Repository": "CRAN"
},
- "rlistings": {
- "Package": "rlistings",
- "Version": "0.2.10",
- "Source": "Repository",
- "Title": "Clinical Trial Style Data Readout Listings",
- "Date": "2025-01-07",
- "Authors@R": "c( person(\"Gabriel\", \"Becker\", , \"gabembecker@gmail.com\", role = \"aut\", comment = \"original creator of the package\"), person(\"Adrian\", \"Waddell\", , \"adrian.waddell@gene.com\", role = \"aut\"), person(\"Joe\", \"Zhu\", , \"joe.zhu@roche.com\", role = c(\"aut\", \"cre\"), comment = c(ORCID = \"0000-0001-7566-2787\")), person(\"Davide\", \"Garolini\", , \"davide.garolini@roche.com\", role = \"aut\"), person(\"Emily\", \"de la Rua\", , \"emily.de_la_rua@contractors.roche.com\", role = \"aut\"), person(\"Abinaya\", \"Yogasekaram\", , \"abinaya.yogasekaram@contractors.roche.com\", role = \"ctb\"), person(\"F. Hoffmann-La Roche AG\", role = c(\"cph\", \"fnd\")) )",
- "Description": "Listings are often part of the submission of clinical trial data in regulatory settings. We provide a framework for the specific formatting features often used when displaying large datasets in that context.",
- "License": "Apache License 2.0",
- "URL": "https://insightsengineering.github.io/rlistings/, https://github.com/insightsengineering/rlistings/",
- "BugReports": "https://github.com/insightsengineering/rlistings/issues",
- "Depends": [
- "formatters (>= 0.5.10)",
- "methods",
- "tibble (>= 2.0.0)"
- ],
- "Imports": [
- "checkmate (>= 2.1.0)",
- "grDevices",
- "grid",
- "stats",
- "utils"
- ],
- "Suggests": [
- "dplyr (>= 1.0.2)",
- "knitr (>= 1.42)",
- "lifecycle (>= 0.2.0)",
- "rmarkdown (>= 2.23)",
- "stringi (>= 1.6)",
- "testthat (>= 3.1.5)",
- "withr (>= 2.0.0)"
- ],
- "VignetteBuilder": "knitr, rmarkdown",
- "Config/Needs/verdepcheck": "insightsengineering/formatters, tidyverse/tibble, mllg/checkmate, tidyverse/dplyr, yihui/knitr, r-lib/lifecycle, rstudio/rmarkdown, gagolews/stringi, r-lib/testthat, r-lib/withr",
- "Config/Needs/website": "insightsengineering/nesttemplate",
- "Config/testthat/edition": "3",
- "Encoding": "UTF-8",
- "Language": "en-US",
- "RoxygenNote": "7.3.2",
- "NeedsCompilation": "no",
- "Author": "Gabriel Becker [aut] (original creator of the package), Adrian Waddell [aut], Joe Zhu [aut, cre] (), Davide Garolini [aut], Emily de la Rua [aut], Abinaya Yogasekaram [ctb], F. Hoffmann-La Roche AG [cph, fnd]",
- "Maintainer": "Joe Zhu ",
- "Repository": "CRAN"
- },
"rmarkdown": {
"Package": "rmarkdown",
"Version": "2.29",
@@ -8820,107 +8023,6 @@
"Author": "Kevin Ushey [aut, cre], JJ Allaire [aut], Hadley Wickham [aut], Gary Ritchie [aut], RStudio [cph]",
"Repository": "CRAN"
},
- "rtables": {
- "Package": "rtables",
- "Version": "0.6.11",
- "Source": "Repository",
- "Title": "Reporting Tables",
- "Date": "2025-01-09",
- "Authors@R": "c( person(\"Gabriel\", \"Becker\", , \"gabembecker@gmail.com\", role = \"aut\", comment = \"Original creator of the package\"), person(\"Adrian\", \"Waddell\", , \"adrian.waddell@gene.com\", role = \"aut\"), person(\"Daniel\", \"Sabanés Bové\", , \"daniel.sabanes_bove@roche.com\", role = \"ctb\"), person(\"Maximilian\", \"Mordig\", , \"maximilian_oliver.mordig@roche.com\", role = \"ctb\"), person(\"Davide\", \"Garolini\", , \"davide.garolini@roche.com\", role = \"aut\"), person(\"Emily\", \"de la Rua\", , \"emily.de_la_rua@contractors.roche.com\", role = \"aut\"), person(\"Abinaya\", \"Yogasekaram\", , \"abinaya.yogasekaram@contractors.roche.com\", role = \"ctb\"), person(\"Joe\", \"Zhu\", , \"joe.zhu@roche.com\", role = c(\"aut\", \"cre\"), comment = c(ORCID = \"0000-0001-7566-2787\")), person(\"F. Hoffmann-La Roche AG\", role = c(\"cph\", \"fnd\")) )",
- "Description": "Reporting tables often have structure that goes beyond simple rectangular data. The 'rtables' package provides a framework for declaring complex multi-level tabulations and then applying them to data. This framework models both tabulation and the resulting tables as hierarchical, tree-like objects which support sibling sub-tables, arbitrary splitting or grouping of data in row and column dimensions, cells containing multiple values, and the concept of contextual summary computations. A convenient pipe-able interface is provided for declaring table layouts and the corresponding computations, and then applying them to data.",
- "License": "Apache License 2.0 | file LICENSE",
- "URL": "https://github.com/insightsengineering/rtables, https://insightsengineering.github.io/rtables/",
- "BugReports": "https://github.com/insightsengineering/rtables/issues",
- "Depends": [
- "formatters (>= 0.5.10)",
- "magrittr (>= 1.5)",
- "methods",
- "R (>= 2.10)"
- ],
- "Imports": [
- "checkmate (>= 2.1.0)",
- "htmltools (>= 0.5.4)",
- "lifecycle (>= 0.2.0)",
- "stats",
- "stringi (>= 1.6)"
- ],
- "Suggests": [
- "broom (>= 1.0.5)",
- "car (>= 3.0-13)",
- "dplyr (>= 1.0.5)",
- "knitr (>= 1.42)",
- "r2rtf (>= 0.3.2)",
- "rmarkdown (>= 2.23)",
- "survival (>= 3.3-1)",
- "testthat (>= 3.0.4)",
- "tibble (>= 3.2.1)",
- "tidyr (>= 1.1.3)",
- "withr (>= 2.0.0)",
- "xml2 (>= 1.1.0)"
- ],
- "VignetteBuilder": "knitr, rmarkdown",
- "Config/Needs/verdepcheck": "insightsengineering/formatters, tidyverse/magrittr, mllg/checkmate, rstudio/htmltools, gagolews/stringi, tidymodels/broom, cran/car, tidyverse/dplyr, davidgohel/flextable, yihui/knitr, r-lib/lifecycle, davidgohel/officer, Merck/r2rtf, rstudio/rmarkdown, therneau/survival, r-lib/testthat, tidyverse/tibble, tidyverse/tidyr, r-lib/withr, r-lib/xml2",
- "Encoding": "UTF-8",
- "Language": "en-US",
- "RoxygenNote": "7.3.2",
- "Collate": "'00tabletrees.R' 'Viewer.R' 'argument_conventions.R' 'as_html.R' 'utils.R' 'colby_constructors.R' 'compare_rtables.R' 'format_rcell.R' 'indent.R' 'make_subset_expr.R' 'custom_split_funs.R' 'default_split_funs.R' 'make_split_fun.R' 'summary.R' 'package.R' 'tree_accessors.R' 'tt_afun_utils.R' 'tt_as_df.R' 'tt_compare_tables.R' 'tt_compatibility.R' 'tt_dotabulation.R' 'tt_paginate.R' 'tt_pos_and_access.R' 'tt_showmethods.R' 'tt_sort.R' 'tt_test_afuns.R' 'tt_toString.R' 'tt_export.R' 'index_footnotes.R' 'tt_from_df.R' 'validate_table_struct.R' 'zzz_constants.R'",
- "NeedsCompilation": "no",
- "Author": "Gabriel Becker [aut] (Original creator of the package), Adrian Waddell [aut], Daniel Sabanés Bové [ctb], Maximilian Mordig [ctb], Davide Garolini [aut], Emily de la Rua [aut], Abinaya Yogasekaram [ctb], Joe Zhu [aut, cre] (), F. Hoffmann-La Roche AG [cph, fnd]",
- "Maintainer": "Joe Zhu ",
- "Repository": "CRAN"
- },
- "rtables.officer": {
- "Package": "rtables.officer",
- "Version": "0.0.2",
- "Source": "Repository",
- "Title": "Exporting Tools for 'rtables'",
- "Date": "2025-01-14",
- "Authors@R": "c( person(\"Gabriel\", \"Becker\", , \"gabembecker@gmail.com\", role = \"ctb\"), person(\"Davide\", \"Garolini\", , \"davide.garolini@roche.com\", role = \"aut\"), person(\"Emily\", \"de la Rua\", , \"emily.de_la_rua@contractors.roche.com\", role = \"aut\"), person(\"Abinaya\", \"Yogasekaram\", , \"abinaya.yogasekaram@contractors.roche.com\", role = \"aut\"), person(\"Joe\", \"Zhu\", , \"joe.zhu@roche.com\", role = c(\"aut\", \"cre\"), comment = c(ORCID = \"0000-0001-7566-2787\")), person(\"F. Hoffmann-La Roche AG\", role = c(\"cph\", \"fnd\")) )",
- "Description": "Designed to create and display complex tables with R, the 'rtables' R package allows cells in an 'rtables' object to contain any high-dimensional data structure, which can then be displayed with cell-specific formatting instructions. Additionally, the 'rtables.officer' package supports export formats related to the Microsoft Office software suite, including Microsoft Word ('docx') and Microsoft PowerPoint ('pptx').",
- "License": "Apache License 2.0",
- "URL": "https://github.com/insightsengineering/rtables.officer, https://insightsengineering.github.io/rtables.officer/",
- "BugReports": "https://github.com/insightsengineering/rtables.officer/issues",
- "Depends": [
- "formatters (>= 0.5.10)",
- "magrittr (>= 1.5)",
- "methods",
- "R (>= 2.10)",
- "rtables (>= 0.6.11)"
- ],
- "Imports": [
- "checkmate (>= 2.1.0)",
- "flextable (>= 0.9.6)",
- "lifecycle (>= 0.2.0)",
- "officer (>= 0.6.6)",
- "stats",
- "stringi (>= 1.6)"
- ],
- "Suggests": [
- "broom (>= 1.0.5)",
- "car (>= 3.0-13)",
- "dplyr (>= 1.0.5)",
- "knitr (>= 1.42)",
- "r2rtf (>= 0.3.2)",
- "rmarkdown (>= 2.23)",
- "survival (>= 3.3-1)",
- "testthat (>= 3.0.4)",
- "tibble (>= 3.2.1)",
- "tidyr (>= 1.1.3)",
- "withr (>= 2.0.0)",
- "xml2 (>= 1.1.0)"
- ],
- "VignetteBuilder": "knitr, rmarkdown",
- "Config/Needs/verdepcheck": "insightsengineering/formatters, insightsengineering/rtables, tidyverse/magrittr, mllg/checkmate, rstudio/htmltools, gagolews/stringi, tidymodels/broom, cran/car, tidyverse/dplyr, davidgohel/flextable, yihui/knitr, r-lib/lifecycle, davidgohel/officer, Merck/r2rtf, rstudio/rmarkdown, therneau/survival, r-lib/testthat, tidyverse/tibble, tidyverse/tidyr, r-lib/withr, r-lib/xml2",
- "Config/testthat/edition": "3",
- "Encoding": "UTF-8",
- "Language": "en-US",
- "RoxygenNote": "7.3.2",
- "Collate": "'package.R' 'export_as_docx.R' 'as_flextable.R'",
- "NeedsCompilation": "no",
- "Author": "Gabriel Becker [ctb], Davide Garolini [aut], Emily de la Rua [aut], Abinaya Yogasekaram [aut], Joe Zhu [aut, cre] (), F. Hoffmann-La Roche AG [cph, fnd]",
- "Maintainer": "Joe Zhu ",
- "Repository": "CRAN"
- },
"sandwich": {
"Package": "sandwich",
"Version": "3.1-1",
@@ -9225,40 +8327,6 @@
"Maintainer": "Gerhard Burger ",
"Repository": "CRAN"
},
- "shinyTree": {
- "Package": "shinyTree",
- "Version": "0.3.1",
- "Source": "Repository",
- "Type": "Package",
- "Title": "jsTree Bindings for Shiny",
- "Date": "2023-7-21",
- "Authors@R": "c( person(family=\"Trestle Technology, LLC\", role=\"aut\", email=\"cran@trestletechnology.net\"), person(\"Jeff\", \"Allen\", role=\"aut\", email=\"cran@trestletechnology.net\"), person(family=\"Institut de Radioprotection et de Sûreté Nucléaire\", role=c(\"cph\"), email = \"yann.richet@irsn.fr\"), person(\"Ivan\", \"Bozhanov\", role=c(\"ctb\", \"cph\"), comment = \"jsTree\"), person(family=\"The Dojo Foundation\", role=c(\"ctb\", \"cph\"), comment=\"require.js\"), person(family=\"jQuery Foundation, Inc.\", role=c(\"ctb\", \"cph\")), person(\"Mike\", \"Schaffer\", role=c(\"ctb\"), email=\"mschaff@gmail.com\"), person(\"Timm\", \"Danker\", role=c(\"ctb\"), email=\"tidafr@carina.uberspace.de\"), person(\"Michael\", \"Bell\", role=c(\"cre\"), email=\"bell_michael_a@lilly.com\"), person(\"Sebastian\", \"Gatscha\", role=c(\"ctb\"), email=\"kona1@gmx.at\"), person(\"Thorn\", \"Thaler\", role = c(\"ctb\"), email = \"thorn.thaler@thothal.at\"))",
- "Maintainer": "Michael Bell ",
- "Description": "Exposes bindings to jsTree -- a JavaScript library that supports interactive trees -- to enable a rich, editable trees in Shiny.",
- "License": "MIT + file LICENSE",
- "Depends": [
- "R (>= 2.15.1)",
- "methods"
- ],
- "Imports": [
- "shiny (>= 0.9.0)",
- "htmlwidgets",
- "jsonlite",
- "stringr",
- "promises"
- ],
- "Suggests": [
- "testthat",
- "shinytest",
- "data.tree"
- ],
- "BugReports": "https://github.com/shinyTree/shinyTree/issues",
- "RoxygenNote": "7.2.3",
- "Encoding": "UTF-8",
- "NeedsCompilation": "no",
- "Author": "Trestle Technology, LLC [aut], Jeff Allen [aut], Institut de Radioprotection et de Sûreté Nucléaire [cph], Ivan Bozhanov [ctb, cph] (jsTree), The Dojo Foundation [ctb, cph] (require.js), jQuery Foundation, Inc. [ctb, cph], Mike Schaffer [ctb], Timm Danker [ctb], Michael Bell [cre], Sebastian Gatscha [ctb], Thorn Thaler [ctb]",
- "Repository": "CRAN"
- },
"shinyWidgets": {
"Package": "shinyWidgets",
"Version": "0.8.7",
@@ -9328,102 +8396,6 @@
"Maintainer": "Victor Perrier ",
"Repository": "CRAN"
},
- "shinycssloaders": {
- "Package": "shinycssloaders",
- "Version": "1.1.0",
- "Source": "Repository",
- "Title": "Add Loading Animations to a 'shiny' Output While It's Recalculating",
- "Authors@R": "c( person(\"Dean\",\"Attali\",email=\"daattali@gmail.com\",role=c(\"aut\",\"cre\"), comment = c(\"Maintainer/developer of shinycssloaders since 2019\", ORCID=\"0000-0002-5645-3493\")), person(\"Andras\",\"Sali\",email=\"andras.sali@alphacruncher.hu\",role=c(\"aut\"),comment=\"Original creator of shinycssloaders package\"), person(\"Luke\",\"Hass\",role=c(\"ctb\",\"cph\"),comment=\"Author of included CSS loader code\") )",
- "Description": "When a 'Shiny' output (such as a plot, table, map, etc.) is recalculating, it remains visible but gets greyed out. Using 'shinycssloaders', you can add a loading animation (\"spinner\") to outputs instead. By wrapping a 'Shiny' output in 'withSpinner()', a spinner will automatically appear while the output is recalculating. You can also manually show and hide the spinner, or add a full-page spinner to cover the entire page. See the demo online at .",
- "License": "MIT + file LICENSE",
- "URL": "https://github.com/daattali/shinycssloaders, https://daattali.com/shiny/shinycssloaders-demo/",
- "BugReports": "https://github.com/daattali/shinycssloaders/issues",
- "Depends": [
- "R (>= 3.1)"
- ],
- "Imports": [
- "digest",
- "glue",
- "grDevices",
- "htmltools (>= 0.3.5)",
- "shiny"
- ],
- "Suggests": [
- "knitr",
- "shinydisconnect",
- "shinyjs"
- ],
- "RoxygenNote": "7.2.3",
- "Encoding": "UTF-8",
- "NeedsCompilation": "no",
- "Author": "Dean Attali [aut, cre] (Maintainer/developer of shinycssloaders since 2019, ), Andras Sali [aut] (Original creator of shinycssloaders package), Luke Hass [ctb, cph] (Author of included CSS loader code)",
- "Maintainer": "Dean Attali ",
- "Repository": "CRAN"
- },
- "shinyjs": {
- "Package": "shinyjs",
- "Version": "2.1.0",
- "Source": "Repository",
- "Title": "Easily Improve the User Experience of Your Shiny Apps in Seconds",
- "Authors@R": "person(\"Dean\", \"Attali\", email = \"daattali@gmail.com\", role = c(\"aut\", \"cre\"), comment= c(ORCID=\"0000-0002-5645-3493\"))",
- "Description": "Perform common useful JavaScript operations in Shiny apps that will greatly improve your apps without having to know any JavaScript. Examples include: hiding an element, disabling an input, resetting an input back to its original value, delaying code execution by a few seconds, and many more useful functions for both the end user and the developer. 'shinyjs' can also be used to easily call your own custom JavaScript functions from R.",
- "URL": "https://deanattali.com/shinyjs/",
- "BugReports": "https://github.com/daattali/shinyjs/issues",
- "Depends": [
- "R (>= 3.1.0)"
- ],
- "Imports": [
- "digest (>= 0.6.8)",
- "jsonlite",
- "shiny (>= 1.0.0)"
- ],
- "Suggests": [
- "htmltools (>= 0.2.9)",
- "knitr (>= 1.7)",
- "rmarkdown",
- "shinyAce",
- "shinydisconnect",
- "testthat (>= 0.9.1)"
- ],
- "License": "MIT + file LICENSE",
- "VignetteBuilder": "knitr",
- "RoxygenNote": "7.1.1",
- "Encoding": "UTF-8",
- "NeedsCompilation": "no",
- "Author": "Dean Attali [aut, cre] ()",
- "Maintainer": "Dean Attali ",
- "Repository": "CRAN"
- },
- "shinyvalidate": {
- "Package": "shinyvalidate",
- "Version": "0.1.3",
- "Source": "Repository",
- "Title": "Input Validation for Shiny Apps",
- "Authors@R": "c( person(\"Carson\", \"Sievert\", , \"carson@posit.co\", role = c(\"aut\", \"cre\"), comment = c(ORCID = \"0000-0002-4958-2844\")), person(\"Richard\", \"Iannone\", , \"rich@posit.co\", c(\"aut\"), comment = c(ORCID = \"0000-0003-3925-190X\")), person(\"Joe\", \"Cheng\", , \"joe@posit.co\", c(\"aut\")), person(\"Posit Software, PBC\", role = c(\"cph\", \"fnd\")) )",
- "Description": "Improves the user experience of Shiny apps by helping to provide feedback when required inputs are missing, or input values are not valid.",
- "License": "MIT + file LICENSE",
- "URL": "https://rstudio.github.io/shinyvalidate/, https://github.com/rstudio/shinyvalidate",
- "BugReports": "https://github.com/rstudio/shinyvalidate/issues",
- "Encoding": "UTF-8",
- "Imports": [
- "shiny (>= 1.6)",
- "htmltools (>= 0.5.1.1)",
- "rlang (>= 0.4.10)",
- "glue (>= 1.4.2)"
- ],
- "RoxygenNote": "7.2.3",
- "Suggests": [
- "testthat",
- "knitr",
- "rmarkdown",
- "covr"
- ],
- "Config/testthat/edition": "3",
- "NeedsCompilation": "no",
- "Author": "Carson Sievert [aut, cre] (), Richard Iannone [aut] (), Joe Cheng [aut], Posit Software, PBC [cph, fnd]",
- "Maintainer": "Carson Sievert ",
- "Repository": "CRAN"
- },
"sjPlot": {
"Package": "sjPlot",
"Version": "2.8.17",
@@ -9809,84 +8781,6 @@
"Maintainer": "Hadley Wickham ",
"Repository": "CRAN"
},
- "styler": {
- "Package": "styler",
- "Version": "1.10.3",
- "Source": "Repository",
- "Type": "Package",
- "Title": "Non-Invasive Pretty Printing of R Code",
- "Authors@R": "c(person(given = \"Kirill\", family = \"Müller\", role = \"aut\", email = \"kirill@cynkra.com\", comment = c(ORCID = \"0000-0002-1416-3412\")), person(given = \"Lorenz\", family = \"Walthert\", role = c(\"cre\", \"aut\"), email = \"lorenz.walthert@icloud.com\"), person(given = \"Indrajeet\", family = \"Patil\", role = \"ctb\", email = \"patilindrajeet.science@gmail.com\", comment = c(ORCID = \"0000-0003-1995-6531\", Twitter = \"@patilindrajeets\")))",
- "Description": "Pretty-prints R code without changing the user's formatting intent.",
- "License": "MIT + file LICENSE",
- "URL": "https://github.com/r-lib/styler, https://styler.r-lib.org",
- "BugReports": "https://github.com/r-lib/styler/issues",
- "Depends": [
- "R (>= 3.6.0)"
- ],
- "Imports": [
- "cli (>= 3.1.1)",
- "magrittr (>= 2.0.0)",
- "purrr (>= 0.2.3)",
- "R.cache (>= 0.15.0)",
- "rlang (>= 1.0.0)",
- "rprojroot (>= 1.1)",
- "tools",
- "vctrs (>= 0.4.1)",
- "withr (>= 2.3.0)"
- ],
- "Suggests": [
- "data.tree (>= 0.1.6)",
- "digest",
- "here",
- "knitr",
- "prettycode",
- "rmarkdown",
- "roxygen2",
- "rstudioapi (>= 0.7)",
- "tibble (>= 1.4.2)",
- "testthat (>= 3.0.0)"
- ],
- "VignetteBuilder": "knitr",
- "Encoding": "UTF-8",
- "RoxygenNote": "7.3.1",
- "Config/testthat/edition": "3",
- "Config/testthat/parallel": "true",
- "Collate": "'addins.R' 'communicate.R' 'compat-dplyr.R' 'compat-tidyr.R' 'detect-alignment-utils.R' 'detect-alignment.R' 'environments.R' 'expr-is.R' 'indent.R' 'initialize.R' 'io.R' 'nest.R' 'nested-to-tree.R' 'parse.R' 'reindent.R' 'token-define.R' 'relevel.R' 'roxygen-examples-add-remove.R' 'roxygen-examples-find.R' 'roxygen-examples-parse.R' 'roxygen-examples.R' 'rules-indention.R' 'rules-line-breaks.R' 'rules-spaces.R' 'rules-tokens.R' 'serialize.R' 'set-assert-args.R' 'style-guides.R' 'styler-package.R' 'stylerignore.R' 'testing-mocks.R' 'testing-public-api.R' 'ui-caching.R' 'testing.R' 'token-create.R' 'transform-block.R' 'transform-code.R' 'transform-files.R' 'ui-styling.R' 'unindent.R' 'utils-cache.R' 'utils-files.R' 'utils-navigate-nest.R' 'utils-strings.R' 'utils.R' 'vertical.R' 'visit.R' 'zzz.R'",
- "NeedsCompilation": "no",
- "Author": "Kirill Müller [aut] (), Lorenz Walthert [cre, aut], Indrajeet Patil [ctb] (, @patilindrajeets)",
- "Maintainer": "Lorenz Walthert ",
- "Repository": "CRAN"
- },
- "survival": {
- "Package": "survival",
- "Version": "3.8-3",
- "Source": "Repository",
- "Title": "Survival Analysis",
- "Priority": "recommended",
- "Date": "2024-12-17",
- "Depends": [
- "R (>= 3.5.0)"
- ],
- "Imports": [
- "graphics",
- "Matrix",
- "methods",
- "splines",
- "stats",
- "utils"
- ],
- "LazyData": "Yes",
- "LazyDataCompression": "xz",
- "ByteCompile": "Yes",
- "Authors@R": "c(person(c(\"Terry\", \"M\"), \"Therneau\", email=\"therneau.terry@mayo.edu\", role=c(\"aut\", \"cre\")), person(\"Thomas\", \"Lumley\", role=c(\"ctb\", \"trl\"), comment=\"original S->R port and R maintainer until 2009\"), person(\"Atkinson\", \"Elizabeth\", role=\"ctb\"), person(\"Crowson\", \"Cynthia\", role=\"ctb\"))",
- "Description": "Contains the core survival analysis routines, including definition of Surv objects, Kaplan-Meier and Aalen-Johansen (multi-state) curves, Cox models, and parametric accelerated failure time models.",
- "License": "LGPL (>= 2)",
- "URL": "https://github.com/therneau/survival",
- "NeedsCompilation": "yes",
- "Author": "Terry M Therneau [aut, cre], Thomas Lumley [ctb, trl] (original S->R port and R maintainer until 2009), Atkinson Elizabeth [ctb], Crowson Cynthia [ctb]",
- "Maintainer": "Terry M Therneau ",
- "Repository": "CRAN"
- },
"svglite": {
"Package": "svglite",
"Version": "2.1.3",
@@ -9994,551 +8888,6 @@
"Maintainer": "Thomas Lin Pedersen ",
"Repository": "CRAN"
},
- "teal": {
- "Package": "teal",
- "Version": "0.15.2",
- "Source": "Repository",
- "Type": "Package",
- "Title": "Exploratory Web Apps for Analyzing Clinical Trials Data",
- "Date": "2024-03-07",
- "Authors@R": "c( person(\"Dawid\", \"Kaledkowski\", , \"dawid.kaledkowski@roche.com\", role = c(\"aut\", \"cre\"), comment = c(ORCID = \"0000-0001-9533-457X\")), person(\"Pawel\", \"Rucki\", , \"pawel.rucki@roche.com\", role = \"aut\"), person(\"Aleksander\", \"Chlebowski\", , \"aleksander.chlebowski@contractors.roche.com\", role = \"aut\", comment = c(ORCID = \"0000-0001-5018-6294\")), person(\"Andre\", \"Verissimo\", , \"andre.verissimo@roche.com\", role = \"aut\", comment = c(ORCID = \"0000-0002-2212-339X\")), person(\"Kartikeya\", \"Kirar\", , \"kartikeya.kirar@businesspartner.roche.com\", role = \"aut\"), person(\"Vedha\", \"Viyash\", , \"vedha.viyash@roche.com\", role = \"aut\"), person(\"Marcin\", \"Kosinski\", , \"marcin.kosinski.mk1@roche.com\", role = \"aut\"), person(\"Adrian\", \"Waddell\", , \"adrian.waddell@gene.com\", role = \"aut\"), person(\"Chendi\", \"Liao\", , \"chendi.liao@roche.com\", role = \"rev\"), person(\"Dony\", \"Unardi\", , \"unardid@gene.com\", role = \"rev\"), person(\"Nikolas\", \"Burkoff\", role = \"aut\"), person(\"Mahmoud\", \"Hallal\", role = \"aut\"), person(\"Maciej\", \"Nasinski\", role = \"aut\"), person(\"Konrad\", \"Pagacz\", role = \"aut\"), person(\"Junlue\", \"Zhao\", role = \"aut\"), person(\"Tadeusz\", \"Lewandowski\", role = \"aut\"), person(\"F. Hoffmann-La Roche AG\", role = c(\"cph\", \"fnd\")), person(\"Maximilian\", \"Mordig\", role = \"ctb\") )",
- "Description": "A 'shiny' based interactive exploration framework for analyzing clinical trials data. 'teal' currently provides a dynamic filtering facility and different data viewers. 'teal' 'shiny' applications are built using standard 'shiny' modules.",
- "License": "Apache License 2.0",
- "URL": "https://insightsengineering.github.io/teal/, https://github.com/insightsengineering/teal/",
- "BugReports": "https://github.com/insightsengineering/teal/issues",
- "Depends": [
- "R (>= 4.0)",
- "shiny (>= 1.7.0)",
- "teal.data (>= 0.4.0)",
- "teal.slice (>= 0.5.0)"
- ],
- "Imports": [
- "checkmate (>= 2.1.0)",
- "jsonlite",
- "lifecycle (>= 0.2.0)",
- "logger (>= 0.2.0)",
- "magrittr (>= 1.5)",
- "methods",
- "rlang (>= 1.0.0)",
- "shinyjs",
- "stats",
- "teal.code (>= 0.5.0)",
- "teal.logger (>= 0.1.1)",
- "teal.reporter (>= 0.2.0)",
- "teal.widgets (>= 0.4.0)",
- "utils"
- ],
- "Suggests": [
- "bslib",
- "knitr (>= 1.42)",
- "MultiAssayExperiment",
- "R6",
- "rmarkdown (>= 2.19)",
- "shinyvalidate",
- "testthat (>= 3.1.5)",
- "withr (>= 2.1.0)",
- "yaml (>= 1.1.0)"
- ],
- "VignetteBuilder": "knitr",
- "RdMacros": "lifecycle",
- "Config/Needs/verdepcheck": "rstudio/shiny, insightsengineering/teal.data, insightsengineering/teal.slice, mllg/checkmate, jeroen/jsonlite, r-lib/lifecycle, daroczig/logger, tidyverse/magrittr, r-lib/rlang, daattali/shinyjs, insightsengineering/teal.logger, insightsengineering/teal.reporter, insightsengineering/teal.widgets, rstudio/bslib, yihui/knitr, bioc::MultiAssayExperiment, r-lib/R6, rstudio/rmarkdown, rstudio/shinyvalidate, insightsengineering/teal.code, r-lib/testthat, r-lib/withr, yaml=vubiostat/r-yaml",
- "Config/Needs/website": "insightsengineering/nesttemplate",
- "Encoding": "UTF-8",
- "Language": "en-US",
- "RoxygenNote": "7.3.1",
- "Collate": "'dummy_functions.R' 'get_rcode_utils.R' 'include_css_js.R' 'modules.R' 'init.R' 'landing_popup_module.R' 'module_filter_manager.R' 'module_nested_tabs.R' 'module_snapshot_manager.R' 'module_tabs_with_filters.R' 'module_teal.R' 'module_teal_with_splash.R' 'reporter_previewer_module.R' 'show_rcode_modal.R' 'tdata.R' 'teal.R' 'teal_data_module.R' 'teal_data_module-eval_code.R' 'teal_data_module-within.R' 'teal_reporter.R' 'teal_slices-store.R' 'teal_slices.R' 'utils.R' 'validate_inputs.R' 'validations.R' 'zzz.R'",
- "NeedsCompilation": "no",
- "Author": "Dawid Kaledkowski [aut, cre] (), Pawel Rucki [aut], Aleksander Chlebowski [aut] (), Andre Verissimo [aut] (), Kartikeya Kirar [aut], Vedha Viyash [aut], Marcin Kosinski [aut], Adrian Waddell [aut], Chendi Liao [rev], Dony Unardi [rev], Nikolas Burkoff [aut], Mahmoud Hallal [aut], Maciej Nasinski [aut], Konrad Pagacz [aut], Junlue Zhao [aut], Tadeusz Lewandowski [aut], F. Hoffmann-La Roche AG [cph, fnd], Maximilian Mordig [ctb]",
- "Maintainer": "Dawid Kaledkowski ",
- "Repository": "CRAN"
- },
- "teal.code": {
- "Package": "teal.code",
- "Version": "0.6.0",
- "Source": "Repository",
- "Type": "Package",
- "Title": "Code Storage and Execution Class for 'teal' Applications",
- "Date": "2025-01-24",
- "Authors@R": "c( person(\"Dawid\", \"Kaledkowski\", , \"dawid.kaledkowski@roche.com\", role = c(\"aut\", \"cre\")), person(\"Aleksander\", \"Chlebowski\", , \"aleksander.chlebowski@contractors.roche.com\", role = \"aut\"), person(\"Marcin\", \"Kosinski\", , \"marcin.kosinski.mk1@roche.com\", role = \"aut\"), person(\"Pawel\", \"Rucki\", , \"pawel.rucki@roche.com\", role = \"aut\"), person(\"Nikolas\", \"Burkoff\", , \"nikolas.burkoff@roche.com\", role = \"aut\"), person(\"Mahmoud\", \"Hallal\", , \"mahmoud.hallal@roche.com\", role = \"aut\"), person(\"Maciej\", \"Nasinski\", , \"maciej.nasinski@contractors.roche.com\", role = \"aut\"), person(\"Konrad\", \"Pagacz\", , \"konrad.pagacz@contractors.roche.com\", role = \"aut\"), person(\"Junlue\", \"Zhao\", , \"zhaoj88@gene.com\", role = \"aut\"), person(\"Chendi\", \"Liao\", , \"chendi.liao@roche.com\", role = \"rev\"), person(\"Dony\", \"Unardi\", , \"unardid@gene.com\", role = \"rev\"), person(\"F. Hoffmann-La Roche AG\", role = c(\"cph\", \"fnd\")) )",
- "Description": "Introduction of 'qenv' S4 class, that facilitates code execution and reproducibility in 'teal' applications.",
- "License": "Apache License 2.0",
- "URL": "https://insightsengineering.github.io/teal.code/, https://github.com/insightsengineering/teal.code",
- "BugReports": "https://github.com/insightsengineering/teal.code/issues",
- "Depends": [
- "methods",
- "R (>= 4.0)"
- ],
- "Imports": [
- "checkmate (>= 2.1.0)",
- "cli (>= 3.4.0)",
- "grDevices",
- "lifecycle (>= 0.2.0)",
- "rlang (>= 1.1.0)",
- "stats",
- "utils"
- ],
- "Suggests": [
- "knitr (>= 1.42)",
- "rmarkdown (>= 2.23)",
- "shiny (>= 1.6.0)",
- "testthat (>= 3.1.8)",
- "withr (>= 2.0.0)"
- ],
- "VignetteBuilder": "knitr, rmarkdown",
- "RdMacros": "lifecycle",
- "Config/Needs/verdepcheck": "mllg/checkmate, r-lib/cli, r-lib/lifecycle, r-lib/rlang, r-lib/cli, yihui/knitr, rstudio/rmarkdown, rstudio/shiny, r-lib/testthat, r-lib/withr",
- "Config/Needs/website": "insightsengineering/nesttemplate",
- "Encoding": "UTF-8",
- "Language": "en-US",
- "RoxygenNote": "7.3.2",
- "Collate": "'qenv-c.R' 'qenv-class.R' 'qenv-errors.R' 'qenv-concat.R' 'qenv-constructor.R' 'qenv-eval_code.R' 'qenv-extract.R' 'qenv-get_code.R' 'qenv-get_env.R' 'qenv-get_messages.r' 'qenv-get_var.R' 'qenv-get_warnings.R' 'qenv-join.R' 'qenv-length.R' 'qenv-show.R' 'qenv-within.R' 'teal.code-package.R' 'utils-get_code_dependency.R' 'utils.R'",
- "NeedsCompilation": "no",
- "Author": "Dawid Kaledkowski [aut, cre], Aleksander Chlebowski [aut], Marcin Kosinski [aut], Pawel Rucki [aut], Nikolas Burkoff [aut], Mahmoud Hallal [aut], Maciej Nasinski [aut], Konrad Pagacz [aut], Junlue Zhao [aut], Chendi Liao [rev], Dony Unardi [rev], F. Hoffmann-La Roche AG [cph, fnd]",
- "Maintainer": "Dawid Kaledkowski ",
- "Repository": "CRAN"
- },
- "teal.data": {
- "Package": "teal.data",
- "Version": "0.7.0",
- "Source": "Repository",
- "Type": "Package",
- "Title": "Data Model for 'teal' Applications",
- "Date": "2025-01-27",
- "Authors@R": "c( person(\"Dawid\", \"Kaledkowski\", , \"dawid.kaledkowski@roche.com\", role = c(\"aut\", \"cre\"), comment = c(ORCID = \"0000-0001-9533-457X\")), person(\"Aleksander\", \"Chlebowski\", , \"aleksander.chlebowski@contractors.roche.com\", role = \"aut\", comment = c(ORCID = \"0000-0001-5018-6294\")), person(\"Marcin\", \"Kosinski\", , \"marcin.kosinski.mk1@roche.com\", role = \"aut\"), person(\"Andre\", \"Verissimo\", , \"andre.verissimo@roche.com\", role = \"aut\", comment = c(ORCID = \"0000-0002-2212-339X\")), person(\"Pawel\", \"Rucki\", , \"pawel.rucki@roche.com\", role = \"aut\"), person(\"Mahmoud\", \"Hallal\", , \"mahmoud.hallal@roche.com\", role = \"aut\"), person(\"Nikolas\", \"Burkoff\", role = \"aut\"), person(\"Maciej\", \"Nasinski\", role = \"aut\"), person(\"Konrad\", \"Pagacz\", role = \"aut\"), person(\"Junlue\", \"Zhao\", role = \"aut\"), person(\"Chendi\", \"Liao\", , \"chendi.liao@roche.com\", role = \"rev\"), person(\"Dony\", \"Unardi\", , \"unardid@gene.com\", role = \"rev\"), person(\"F. Hoffmann-La Roche AG\", role = c(\"cph\", \"fnd\")) )",
- "Description": "Provides a 'teal_data' class as a unified data model for 'teal' applications focusing on reproducibility and relational data.",
- "License": "Apache License 2.0",
- "URL": "https://insightsengineering.github.io/teal.data/, https://github.com/insightsengineering/teal.data/",
- "BugReports": "https://github.com/insightsengineering/teal.data/issues",
- "Depends": [
- "R (>= 4.0)",
- "teal.code (>= 0.6.0)"
- ],
- "Imports": [
- "checkmate (>= 2.1.0)",
- "lifecycle (>= 0.2.0)",
- "methods",
- "rlang (>= 1.1.0)",
- "stats",
- "utils"
- ],
- "Suggests": [
- "knitr (>= 1.42)",
- "rmarkdown (>= 2.23)",
- "testthat (>= 3.2.2)",
- "withr (>= 2.0.0)"
- ],
- "VignetteBuilder": "knitr, rmarkdown",
- "RdMacros": "lifecycle",
- "Config/Needs/verdepcheck": "insightsengineering/teal.code, mllg/checkmate, r-lib/lifecycle, r-lib/rlang, yihui/knitr, rstudio/rmarkdown, r-lib/testthat, r-lib/withr",
- "Config/Needs/website": "insightsengineering/nesttemplate",
- "Encoding": "UTF-8",
- "Language": "en-US",
- "LazyData": "true",
- "RoxygenNote": "7.3.2",
- "Collate": "'cdisc_data.R' 'data.R' 'formatters_var_labels.R' 'deprecated.R' 'dummy_function.R' 'join_key.R' 'join_keys-c.R' 'join_keys-extract.R' 'join_keys-names.R' 'join_keys-parents.R' 'join_keys-print.R' 'join_keys-utils.R' 'join_keys.R' 'teal.data.R' 'teal_data-class.R' 'teal_data-constructor.R' 'teal_data-extract.R' 'teal_data-get_code.R' 'teal_data-names.R' 'teal_data-show.R' 'testhat-helpers.R' 'topological_sort.R' 'verify.R' 'zzz.R'",
- "NeedsCompilation": "no",
- "Author": "Dawid Kaledkowski [aut, cre] (), Aleksander Chlebowski [aut] (), Marcin Kosinski [aut], Andre Verissimo [aut] (), Pawel Rucki [aut], Mahmoud Hallal [aut], Nikolas Burkoff [aut], Maciej Nasinski [aut], Konrad Pagacz [aut], Junlue Zhao [aut], Chendi Liao [rev], Dony Unardi [rev], F. Hoffmann-La Roche AG [cph, fnd]",
- "Maintainer": "Dawid Kaledkowski ",
- "Repository": "CRAN"
- },
- "teal.logger": {
- "Package": "teal.logger",
- "Version": "0.3.1",
- "Source": "Repository",
- "Title": "Logging Setup for the 'teal' Family of Packages",
- "Date": "2025-01-21",
- "Authors@R": "c( person(\"Dawid\", \"Kaledkowski\", , \"dawid.kaledkowski@roche.com\", role = c(\"aut\", \"cre\")), person(\"Konrad\", \"Pagacz\", role = \"aut\"), person(\"F. Hoffmann-La Roche AG\", role = c(\"cph\", \"fnd\")) )",
- "Description": "Utilizing the 'logger' framework to record events within a package, specific to 'teal' family of packages. Supports logging namespaces, hierarchical logging, various log destinations, vectorization, and more.",
- "License": "Apache License 2.0",
- "URL": "https://insightsengineering.github.io/teal.logger/, https://github.com/insightsengineering/teal.logger/",
- "BugReports": "https://github.com/insightsengineering/teal.logger/issues",
- "Depends": [
- "R (>= 3.6)"
- ],
- "Imports": [
- "glue (>= 1.0.0)",
- "lifecycle (>= 0.2.0)",
- "logger (>= 0.3.0)",
- "methods",
- "shiny (>= 1.6.0)",
- "utils",
- "withr (>= 2.1.0)"
- ],
- "Suggests": [
- "knitr (>= 1.42)",
- "rmarkdown (>= 2.23)",
- "testthat (>= 3.1.7)"
- ],
- "VignetteBuilder": "knitr, rmarkdown",
- "RdMacros": "lifecycle",
- "Config/Needs/verdepcheck": "tidyverse/glue, r-lib/lifecycle, daroczig/logger, rstudio/shiny, r-lib/withr, yihui/knitr, rstudio/rmarkdown, r-lib/testthat",
- "Config/Needs/website": "insightsengineering/nesttemplate",
- "Encoding": "UTF-8",
- "Language": "en-US",
- "RoxygenNote": "7.3.2",
- "NeedsCompilation": "no",
- "Author": "Dawid Kaledkowski [aut, cre], Konrad Pagacz [aut], F. Hoffmann-La Roche AG [cph, fnd]",
- "Maintainer": "Dawid Kaledkowski ",
- "Repository": "CRAN"
- },
- "teal.modules.general": {
- "Package": "teal.modules.general",
- "Version": "0.3.0",
- "Source": "Repository",
- "Type": "Package",
- "Title": "General Modules for 'teal' Applications",
- "Date": "2024-03-01",
- "Authors@R": "c( person(\"Dawid\", \"Kaledkowski\", , \"dawid.kaledkowski@roche.com\", role = c(\"aut\", \"cre\")), person(\"Pawel\", \"Rucki\", , \"pawel.rucki@roche.com\", role = \"aut\"), person(\"Mahmoud\", \"Hallal\", , \"mahmoud.hallal@roche.com\", role = \"aut\"), person(\"Ondrej\", \"Slama\", , \"ondrej.slama@roche.com\", role = \"ctb\"), person(\"Maciej\", \"Nasinski\", role = \"aut\"), person(\"Konrad\", \"Pagacz\", role = \"aut\"), person(\"Nikolas\", \"Burkoff\", role = \"aut\"), person(\"F. Hoffmann-La Roche AG\", role = c(\"cph\", \"fnd\")) )",
- "Description": "Prebuilt 'shiny' modules containing tools for viewing data, visualizing data, understanding missing and outlier values within your data and performing simple data analysis. This extends 'teal' framework that supports reproducible research and analysis.",
- "License": "Apache License 2.0",
- "URL": "https://insightsengineering.github.io/teal.modules.general/, https://github.com/insightsengineering/teal.modules.general/",
- "BugReports": "https://github.com/insightsengineering/teal.modules.general/issues",
- "Depends": [
- "ggmosaic (>= 0.3.0)",
- "ggplot2 (>= 3.4.0)",
- "R (>= 3.6)",
- "shiny (>= 1.6.0)",
- "teal (>= 0.15.1)",
- "teal.transform (>= 0.5.0)"
- ],
- "Imports": [
- "checkmate (>= 2.1.0)",
- "dplyr (>= 1.0.5)",
- "DT (>= 0.13)",
- "forcats (>= 1.0.0)",
- "grid",
- "logger (>= 0.2.0)",
- "scales",
- "shinyjs",
- "shinyTree (>= 0.2.8)",
- "shinyvalidate",
- "shinyWidgets (>= 0.5.1)",
- "stats",
- "stringr (>= 1.4.1)",
- "teal.code (>= 0.5.0)",
- "teal.data (>= 0.5.0)",
- "teal.logger (>= 0.1.1)",
- "teal.reporter (>= 0.3.0)",
- "teal.widgets (>= 0.4.0)",
- "tern (>= 0.9.3)",
- "tibble (>= 2.0.0)",
- "tidyr (>= 0.8.3)",
- "tools",
- "utils"
- ],
- "Suggests": [
- "broom (>= 0.7.10)",
- "colourpicker",
- "ggExtra",
- "ggpmisc (>= 0.4.3)",
- "ggpp",
- "ggrepel",
- "goftest",
- "gridExtra",
- "htmlwidgets",
- "jsonlite",
- "knitr (>= 1.42)",
- "lattice (>= 0.18-4)",
- "MASS",
- "nestcolor (>= 0.1.0)",
- "rlang (>= 1.0.0)",
- "rtables (>= 0.6.6)",
- "sparkline",
- "testthat (>= 3.0.4)"
- ],
- "VignetteBuilder": "knitr",
- "Config/Needs/verdepcheck": "haleyjeppson/ggmosaic, tidyverse/ggplot2, rstudio/shiny, insightsengineering/teal, insightsengineering/teal.transform, mllg/checkmate, tidyverse/dplyr, rstudio/DT, tidyverse/forcats, daroczig/logger, r-lib/scales, daattali/shinyjs, shinyTree/shinyTree, rstudio/shinyvalidate, dreamRs/shinyWidgets, tidyverse/stringr, insightsengineering/teal.code, insightsengineering/teal.data, insightsengineering/teal.logger, insightsengineering/teal.reporter, insightsengineering/teal.widgets, insightsengineering/tern, tidyverse/tibble, tidyverse/tidyr, tidymodels/broom, daattali/colourpicker, daattali/ggExtra, aphalo/ggpmisc, aphalo/ggpp, slowkow/ggrepel, baddstats/goftest, gridExtra, ramnathv/htmlwidgets, jeroen/jsonlite, yihui/knitr, deepayan/lattice, MASS, insightsengineering/nestcolor, r-lib/rlang, insightsengineering/rtables, sparkline, insightsengineering/teal.data, r-lib/testthat",
- "Config/Needs/website": "insightsengineering/nesttemplate",
- "Encoding": "UTF-8",
- "Language": "en-US",
- "LazyData": "true",
- "RoxygenNote": "7.3.1",
- "NeedsCompilation": "no",
- "Author": "Dawid Kaledkowski [aut, cre], Pawel Rucki [aut], Mahmoud Hallal [aut], Ondrej Slama [ctb], Maciej Nasinski [aut], Konrad Pagacz [aut], Nikolas Burkoff [aut], F. Hoffmann-La Roche AG [cph, fnd]",
- "Maintainer": "Dawid Kaledkowski ",
- "Repository": "CRAN"
- },
- "teal.reporter": {
- "Package": "teal.reporter",
- "Version": "0.4.0",
- "Source": "Repository",
- "Title": "Reporting Tools for 'shiny' Modules",
- "Date": "2025-01-22",
- "Authors@R": "c( person(\"Dawid\", \"Kaledkowski\", , \"dawid.kaledkowski@roche.com\", role = c(\"aut\", \"cre\"), comment = c(ORCID = \"0000-0001-9533-457X\")), person(\"Kartikeya\", \"Kirar\", , \"kartikeya.kirar@businesspartner.roche.com\", role = \"aut\", comment = c(ORCID = \"0009-0005-1258-4757\")), person(\"Marcin\", \"Kosinski\", , \"marcin.kosinski.mk1@roche.com\", role = \"aut\"), person(\"Maciej\", \"Nasinski\", role = \"aut\"), person(\"Konrad\", \"Pagacz\", role = \"aut\"), person(\"Mahmoud\", \"Hallal\", , \"mahmoud.hallal@roche.com\", role = \"aut\"), person(\"Chendi\", \"Liao\", , \"chendi.liao@roche.com\", role = \"rev\"), person(\"Dony\", \"Unardi\", , \"unardid@gene.com\", role = \"rev\"), person(\"F. Hoffmann-La Roche AG\", role = c(\"cph\", \"fnd\")) )",
- "Description": "Prebuilt 'shiny' modules containing tools for the generation of 'rmarkdown' reports, supporting reproducible research and analysis.",
- "License": "Apache License 2.0",
- "URL": "https://github.com/insightsengineering/teal.reporter, https://insightsengineering.github.io/teal.reporter/",
- "BugReports": "https://github.com/insightsengineering/teal.reporter/issues",
- "Imports": [
- "bslib",
- "checkmate (>= 2.1.0)",
- "flextable (>= 0.9.2)",
- "grid",
- "htmltools (>= 0.5.4)",
- "knitr (>= 1.42)",
- "lifecycle (>= 0.2.0)",
- "R6",
- "rlistings (>= 0.2.10)",
- "rmarkdown (>= 2.23)",
- "rtables (>= 0.6.11)",
- "rtables.officer (>= 0.0.2)",
- "shiny (>= 1.6.0)",
- "shinybusy (>= 0.3.2)",
- "shinyWidgets (>= 0.5.1)",
- "yaml (>= 1.1.0)",
- "zip (>= 1.1.0)"
- ],
- "Suggests": [
- "DT (>= 0.13)",
- "formatR (>= 1.5)",
- "formatters (>= 0.5.10)",
- "ggplot2 (>= 3.4.3)",
- "lattice (>= 0.18-4)",
- "png",
- "testthat (>= 3.2.2)",
- "tinytex",
- "withr (>= 2.0.0)"
- ],
- "VignetteBuilder": "knitr, rmarkdown",
- "RdMacros": "lifecycle",
- "Config/Needs/verdepcheck": "rstudio/bslib, mllg/checkmate, davidgohel/flextable, rstudio/htmltools, yihui/knitr, r-lib/lifecycle, r-lib/R6, insightsengineering/rlistings, rstudio/rmarkdown, insightsengineering/rtables, insightsengineering/rtables.officer, rstudio/shiny, dreamRs/shinybusy, dreamRs/shinyWidgets, yaml=vubiostat/r-yaml, r-lib/zip, rstudio/DT, yihui/formatR, insightsengineering/formatters, tidyverse/ggplot2, deepayan/lattice, cran/png, r-lib/testthat, rstudio/tinytex, r-lib/withr",
- "Config/Needs/website": "insightsengineering/nesttemplate",
- "Encoding": "UTF-8",
- "Language": "en-US",
- "RoxygenNote": "7.3.2",
- "NeedsCompilation": "no",
- "Author": "Dawid Kaledkowski [aut, cre] (), Kartikeya Kirar [aut] (), Marcin Kosinski [aut], Maciej Nasinski [aut], Konrad Pagacz [aut], Mahmoud Hallal [aut], Chendi Liao [rev], Dony Unardi [rev], F. Hoffmann-La Roche AG [cph, fnd]",
- "Maintainer": "Dawid Kaledkowski ",
- "Repository": "CRAN"
- },
- "teal.slice": {
- "Package": "teal.slice",
- "Version": "0.6.0",
- "Source": "Repository",
- "Type": "Package",
- "Title": "Filter Module for 'teal' Applications",
- "Date": "2025-01-31",
- "Authors@R": "c( person(\"Dawid\", \"Kaledkowski\", , \"dawid.kaledkowski@roche.com\", role = c(\"aut\", \"cre\"), comment = c(ORCID = \"0000-0001-9533-457X\")), person(\"Pawel\", \"Rucki\", , \"pawel.rucki@roche.com\", role = \"aut\"), person(\"Aleksander\", \"Chlebowski\", , \"aleksander.chlebowski@contractors.roche.com\", role = \"aut\", comment = c(ORCID = \"0000-0001-5018-6294\")), person(\"Andre\", \"Verissimo\", , \"andre.verissimo@roche.com\", role = \"aut\", comment = c(ORCID = \"0000-0002-2212-339X\")), person(\"Kartikeya\", \"Kirar\", , \"kartikeya.kirar@businesspartner.roche.com\", role = \"aut\"), person(\"Marcin\", \"Kosinski\", , \"marcin.kosinski.mk1@roche.com\", role = \"aut\"), person(\"Chendi\", \"Liao\", , \"chendi.liao@roche.com\", role = \"rev\"), person(\"Dony\", \"Unardi\", , \"unardid@gene.com\", role = \"rev\"), person(\"Andrew\", \"Bates\", role = \"aut\"), person(\"Mahmoud\", \"Hallal\", role = \"aut\"), person(\"Nikolas\", \"Burkoff\", role = \"aut\"), person(\"Maciej\", \"Nasinski\", role = \"aut\"), person(\"Konrad\", \"Pagacz\", role = \"aut\"), person(\"Junlue\", \"Zhao\", role = \"aut\"), person(\"F. Hoffmann-La Roche AG\", role = c(\"cph\", \"fnd\")) )",
- "Description": "Data filtering module for 'teal' applications. Allows for interactive filtering of data stored in 'data.frame' and 'MultiAssayExperiment' objects. Also displays filtered and unfiltered observation counts.",
- "License": "Apache License 2.0",
- "URL": "https://insightsengineering.github.io/teal.slice/, https://github.com/insightsengineering/teal.slice/",
- "BugReports": "https://github.com/insightsengineering/teal.slice/issues",
- "Depends": [
- "R (>= 4.0)"
- ],
- "Imports": [
- "bslib (>= 0.4.0)",
- "checkmate (>= 2.1.0)",
- "dplyr (>= 1.0.5)",
- "grDevices",
- "htmltools (>= 0.5.4)",
- "jsonlite",
- "lifecycle (>= 0.2.0)",
- "logger (>= 0.3.0)",
- "methods",
- "plotly (>= 4.9.2.2)",
- "R6 (>= 2.2.0)",
- "rlang (>= 1.0.0)",
- "shiny (>= 1.6.0)",
- "shinycssloaders (>= 1.0.0)",
- "shinyjs",
- "shinyWidgets (>= 0.6.2)",
- "teal.data (>= 0.7.0)",
- "teal.logger (>= 0.3.1)",
- "teal.widgets (>= 0.4.3)",
- "utils"
- ],
- "Suggests": [
- "knitr (>= 1.42)",
- "MultiAssayExperiment",
- "rmarkdown (>= 2.23)",
- "SummarizedExperiment",
- "testthat (>= 3.2.2)",
- "withr (>= 3.0.2)"
- ],
- "VignetteBuilder": "knitr, rmarkdown",
- "RdMacros": "lifecycle",
- "Config/Needs/verdepcheck": "rstudio/shiny, rstudio/bslib, mllg/checkmate, tidyverse/dplyr, rstudio/htmltools, jeroen/jsonlite, r-lib/lifecycle, daroczig/logger, plotly/plotly, r-lib/R6, daattali/shinycssloaders, daattali/shinyjs, dreamRs/shinyWidgets, insightsengineering/teal.data, insightsengineering/teal.logger, insightsengineering/teal.widgets, yihui/knitr, bioc::MultiAssayExperiment, bioc::SummarizedExperiment, rstudio/rmarkdown, r-lib/testthat, r-lib/withr, bioc::matrixStats",
- "Config/Needs/website": "insightsengineering/nesttemplate",
- "Encoding": "UTF-8",
- "Language": "en-US",
- "RoxygenNote": "7.3.2",
- "NeedsCompilation": "no",
- "Author": "Dawid Kaledkowski [aut, cre] (), Pawel Rucki [aut], Aleksander Chlebowski [aut] (), Andre Verissimo [aut] (), Kartikeya Kirar [aut], Marcin Kosinski [aut], Chendi Liao [rev], Dony Unardi [rev], Andrew Bates [aut], Mahmoud Hallal [aut], Nikolas Burkoff [aut], Maciej Nasinski [aut], Konrad Pagacz [aut], Junlue Zhao [aut], F. Hoffmann-La Roche AG [cph, fnd]",
- "Maintainer": "Dawid Kaledkowski ",
- "Repository": "CRAN"
- },
- "teal.transform": {
- "Package": "teal.transform",
- "Version": "0.5.0",
- "Source": "Repository",
- "Title": "Functions for Extracting and Merging Data in the 'teal' Framework",
- "Date": "2024-02-16",
- "Authors@R": "c( person(\"Dawid\", \"Kaledkowski\", , \"dawid.kaledkowski@roche.com\", role = c(\"aut\", \"cre\")), person(\"Pawel\", \"Rucki\", , \"pawel.rucki@roche.com\", role = \"aut\"), person(\"Mahmoud\", \"Hallal\", , \"mahmoud.hallal@roche.com\", role = \"aut\"), person(\"Nikolas\", \"Burkoff\", role = \"aut\"), person(\"Maciej\", \"Nasinski\", role = \"aut\"), person(\"Konrad\", \"Pagacz\", role = \"aut\"), person(\"Junlue\", \"Zhao\", role = \"aut\"), person(\"F. Hoffmann-La Roche AG\", role = c(\"cph\", \"fnd\")) )",
- "Description": "A standardized user interface for column selection, that facilitates dataset merging in 'teal' framework.",
- "License": "Apache License 2.0",
- "URL": "https://insightsengineering.github.io/teal.transform/, https://github.com/insightsengineering/teal.transform/",
- "BugReports": "https://github.com/insightsengineering/teal.transform/issues",
- "Depends": [
- "R (>= 3.6)"
- ],
- "Imports": [
- "checkmate (>= 2.1.0)",
- "dplyr (>= 1.1.0)",
- "lifecycle (>= 0.2.0)",
- "logger (>= 0.2.0)",
- "methods",
- "rlang (>= 1.0.0)",
- "shiny (>= 1.6.0)",
- "shinyjs",
- "shinyvalidate",
- "stats",
- "teal.data (>= 0.5.0)",
- "teal.logger (>= 0.1.1)",
- "teal.widgets (>= 0.4.0)",
- "tidyr (>= 0.8.3)",
- "tidyselect"
- ],
- "Suggests": [
- "knitr (>= 1.42)",
- "rmarkdown (>= 2.19)",
- "teal.code (>= 0.5.0)",
- "testthat (>= 3.1.5)"
- ],
- "VignetteBuilder": "knitr",
- "RdMacros": "lifecycle",
- "Config/Needs/verdepcheck": "mllg/checkmate, tidyverse/dplyr, r-lib/lifecycle, daroczig/logger, r-lib/rlang, rstudio/rmarkdown, rstudio/shiny, daattali/shinyjs, rstudio/shinyvalidate, insightsengineering/teal.data, insightsengineering/teal.logger, insightsengineering/teal.widgets, tidyverse/tidyr, r-lib/tidyselect, yihui/knitr, insightsengineering/teal.code, r-lib/testthat",
- "Config/Needs/website": "insightsengineering/nesttemplate",
- "Encoding": "UTF-8",
- "Language": "en-US",
- "LazyData": "true",
- "RoxygenNote": "7.3.1",
- "NeedsCompilation": "no",
- "Author": "Dawid Kaledkowski [aut, cre], Pawel Rucki [aut], Mahmoud Hallal [aut], Nikolas Burkoff [aut], Maciej Nasinski [aut], Konrad Pagacz [aut], Junlue Zhao [aut], F. Hoffmann-La Roche AG [cph, fnd]",
- "Maintainer": "Dawid Kaledkowski ",
- "Repository": "CRAN"
- },
- "teal.widgets": {
- "Package": "teal.widgets",
- "Version": "0.4.3",
- "Source": "Repository",
- "Title": "'shiny' Widgets for 'teal' Applications",
- "Date": "2025-01-31",
- "Authors@R": "c( person(\"Dawid\", \"Kaledkowski\", , \"dawid.kaledkowski@roche.com\", role = c(\"aut\", \"cre\")), person(\"Pawel\", \"Rucki\", , \"pawel.rucki@roche.com\", role = \"aut\"), person(\"Mahmoud\", \"Hallal\", , \"mahmoud.hallal@roche.com\", role = \"aut\"), person(\"Nikolas\", \"Burkoff\", role = \"aut\"), person(\"Maciej\", \"Nasinski\", role = \"aut\"), person(\"Konrad\", \"Pagacz\", role = \"aut\"), person(\"Junlue\", \"Zhao\", role = \"aut\"), person(\"F. Hoffmann-La Roche AG\", role = c(\"cph\", \"fnd\")) )",
- "Description": "Collection of 'shiny' widgets to support 'teal' applications. Enables the manipulation of application layout and plot or table settings.",
- "License": "Apache License 2.0",
- "URL": "https://insightsengineering.github.io/teal.widgets/, https://github.com/insightsengineering/teal.widgets",
- "BugReports": "https://github.com/insightsengineering/teal.widgets/issues",
- "Depends": [
- "R (>= 3.6)"
- ],
- "Imports": [
- "bslib",
- "checkmate (>= 2.1.0)",
- "ggplot2 (>= 3.4.3)",
- "graphics",
- "grDevices",
- "htmltools (>= 0.5.4)",
- "lifecycle (>= 0.2.0)",
- "methods",
- "rtables (>= 0.6.6)",
- "shiny (>= 1.6.0)",
- "shinyjs",
- "shinyWidgets (>= 0.5.1)",
- "styler (>= 1.2.0)"
- ],
- "Suggests": [
- "DT",
- "knitr (>= 1.42)",
- "lattice (>= 0.18-4)",
- "magrittr (>= 1.5)",
- "png",
- "rmarkdown (>= 2.23)",
- "rvest (>= 1.0.3)",
- "shinytest2 (>= 0.2.0)",
- "shinyvalidate",
- "testthat (>= 3.1.5)",
- "withr (>= 2.1.0)"
- ],
- "VignetteBuilder": "knitr, rmarkdown",
- "Config/Needs/verdepcheck": "rstudio/bslib, mllg/checkmate, tidyverse/ggplot2, rstudio/htmltools, r-lib/lifecycle, insightsengineering/rtables, rstudio/shiny, daattali/shinyjs, dreamRs/shinyWidgets, r-lib/styler, rstudio/DT, yihui/knitr, deepayan/lattice, tidyverse/magrittr, cran/png, tidyverse/rvest, rstudio/rmarkdown, rstudio/shinytest2, rstudio/shinyvalidate, r-lib/testthat, r-lib/withr",
- "Config/Needs/website": "insightsengineering/nesttemplate",
- "Encoding": "UTF-8",
- "Language": "en-US",
- "RoxygenNote": "7.3.2",
- "NeedsCompilation": "no",
- "Author": "Dawid Kaledkowski [aut, cre], Pawel Rucki [aut], Mahmoud Hallal [aut], Nikolas Burkoff [aut], Maciej Nasinski [aut], Konrad Pagacz [aut], Junlue Zhao [aut], F. Hoffmann-La Roche AG [cph, fnd]",
- "Maintainer": "Dawid Kaledkowski ",
- "Repository": "CRAN"
- },
- "tern": {
- "Package": "tern",
- "Version": "0.9.7",
- "Source": "Repository",
- "Title": "Create Common TLGs Used in Clinical Trials",
- "Date": "2025-01-17",
- "Authors@R": "c( person(\"Joe\", \"Zhu\", , \"joe.zhu@roche.com\", role = c(\"aut\", \"cre\")), person(\"Daniel\", \"Sabanés Bové\", , \"daniel.sabanes_bove@roche.com\", role = \"aut\"), person(\"Jana\", \"Stoilova\", , \"jana.stoilova@roche.com\", role = \"aut\"), person(\"Davide\", \"Garolini\", , \"davide.garolini@roche.com\", role = \"aut\"), person(\"Emily\", \"de la Rua\", , \"emily.de_la_rua@contractors.roche.com\", role = \"aut\"), person(\"Abinaya\", \"Yogasekaram\", , \"abinaya.yogasekaram@contractors.roche.com\", role = \"aut\"), person(\"Heng\", \"Wang\", , \"wang.heng@gene.com\", role = \"aut\"), person(\"Francois\", \"Collin\", role = \"aut\"), person(\"Adrian\", \"Waddell\", , \"adrian.waddell@gene.com\", role = \"aut\"), person(\"Pawel\", \"Rucki\", , \"pawel.rucki@roche.com\", role = \"aut\"), person(\"Chendi\", \"Liao\", , \"chendi.liao@roche.com\", role = \"aut\"), person(\"Jennifer\", \"Li\", , \"li.jing@gene.com\", role = \"aut\"), person(\"F. Hoffmann-La Roche AG\", role = c(\"cph\", \"fnd\")) )",
- "Description": "Table, Listings, and Graphs (TLG) library for common outputs used in clinical trials.",
- "License": "Apache License 2.0",
- "URL": "https://insightsengineering.github.io/tern/, https://github.com/insightsengineering/tern/",
- "BugReports": "https://github.com/insightsengineering/tern/issues",
- "Depends": [
- "R (>= 3.6)",
- "rtables (>= 0.6.11)"
- ],
- "Imports": [
- "broom (>= 0.5.4)",
- "car (>= 3.0-13)",
- "checkmate (>= 2.1.0)",
- "cowplot (>= 1.0.0)",
- "dplyr (>= 1.0.0)",
- "emmeans (>= 1.10.4)",
- "forcats (>= 1.0.0)",
- "formatters (>= 0.5.10)",
- "ggplot2 (>= 3.5.0)",
- "grid",
- "gridExtra (>= 2.0.0)",
- "gtable (>= 0.3.0)",
- "labeling",
- "lifecycle (>= 0.2.0)",
- "magrittr (>= 1.5)",
- "MASS (>= 7.3-60)",
- "methods",
- "nestcolor (>= 0.1.1)",
- "Rdpack (>= 2.4)",
- "rlang (>= 1.1.0)",
- "scales (>= 1.2.0)",
- "stats",
- "survival (>= 3.6-4)",
- "tibble (>= 2.0.0)",
- "tidyr (>= 0.8.3)",
- "utils"
- ],
- "Suggests": [
- "knitr (>= 1.42)",
- "lattice (>= 0.18-4)",
- "lubridate (>= 1.7.9)",
- "rmarkdown (>= 2.23)",
- "stringr (>= 1.4.1)",
- "svglite (>= 2.1.2)",
- "testthat (>= 3.1.9)",
- "withr (>= 2.0.0)"
- ],
- "VignetteBuilder": "knitr, rmarkdown",
- "RdMacros": "lifecycle, Rdpack",
- "Config/Needs/verdepcheck": "insightsengineering/rtables, tidymodels/broom, cran/car, mllg/checkmate, wilkelab/cowplot, tidyverse/dplyr, rvlenth/emmeans, tidyverse/forcats, insightsengineering/formatters, tidyverse/ggplot2, r-lib/gtable, r-lib/lifecycle, tidyverse/magrittr, GeoBosh/Rdpack, r-lib/rlang, r-lib/scales, therneau/survival, tidyverse/tibble, tidyverse/tidyr, yihui/knitr, deepayan/lattice, tidyverse/lubridate, insightsengineering/nestcolor, rstudio/rmarkdown, tidyverse/stringr, r-lib/svglite, r-lib/testthat, r-lib/withr",
- "Config/Needs/website": "insightsengineering/nesttemplate",
- "Config/testthat/edition": "3",
- "Encoding": "UTF-8",
- "Language": "en-US",
- "LazyData": "true",
- "RoxygenNote": "7.3.2",
- "Collate": "'formatting_functions.R' 'abnormal.R' 'abnormal_by_baseline.R' 'abnormal_by_marked.R' 'abnormal_by_worst_grade.R' 'abnormal_by_worst_grade_worsen.R' 'analyze_colvars_functions.R' 'analyze_functions.R' 'analyze_variables.R' 'analyze_vars_in_cols.R' 'argument_convention.R' 'bland_altman.R' 'combination_function.R' 'compare_variables.R' 'control_incidence_rate.R' 'control_logistic.R' 'control_step.R' 'control_survival.R' 'count_cumulative.R' 'count_missed_doses.R' 'count_occurrences.R' 'count_occurrences_by_grade.R' 'count_patients_events_in_cols.R' 'count_patients_with_event.R' 'count_patients_with_flags.R' 'count_values.R' 'cox_regression.R' 'cox_regression_inter.R' 'coxph.R' 'd_pkparam.R' 'data.R' 'decorate_grob.R' 'desctools_binom_diff.R' 'df_explicit_na.R' 'estimate_multinomial_rsp.R' 'estimate_proportion.R' 'fit_rsp_step.R' 'fit_survival_step.R' 'g_forest.R' 'g_ipp.R' 'g_km.R' 'g_lineplot.R' 'g_step.R' 'g_waterfall.R' 'h_adsl_adlb_merge_using_worst_flag.R' 'h_biomarkers_subgroups.R' 'h_cox_regression.R' 'h_incidence_rate.R' 'h_km.R' 'h_logistic_regression.R' 'h_map_for_count_abnormal.R' 'h_pkparam_sort.R' 'h_response_biomarkers_subgroups.R' 'h_response_subgroups.R' 'h_stack_by_baskets.R' 'h_step.R' 'h_survival_biomarkers_subgroups.R' 'h_survival_duration_subgroups.R' 'imputation_rule.R' 'incidence_rate.R' 'logistic_regression.R' 'missing_data.R' 'odds_ratio.R' 'package.R' 'prop_diff.R' 'prop_diff_test.R' 'prune_occurrences.R' 'response_biomarkers_subgroups.R' 'response_subgroups.R' 'riskdiff.R' 'rtables_access.R' 'score_occurrences.R' 'split_cols_by_groups.R' 'stat.R' 'summarize_ancova.R' 'summarize_change.R' 'summarize_colvars.R' 'summarize_coxreg.R' 'summarize_functions.R' 'summarize_glm_count.R' 'summarize_num_patients.R' 'summarize_patients_exposure_in_cols.R' 'survival_biomarkers_subgroups.R' 'survival_coxph_pairwise.R' 'survival_duration_subgroups.R' 'survival_time.R' 'survival_timepoint.R' 'utils.R' 'utils_checkmate.R' 'utils_default_stats_formats_labels.R' 'utils_factor.R' 'utils_ggplot.R' 'utils_grid.R' 'utils_rtables.R' 'utils_split_funs.R'",
- "NeedsCompilation": "no",
- "Author": "Joe Zhu [aut, cre], Daniel Sabanés Bové [aut], Jana Stoilova [aut], Davide Garolini [aut], Emily de la Rua [aut], Abinaya Yogasekaram [aut], Heng Wang [aut], Francois Collin [aut], Adrian Waddell [aut], Pawel Rucki [aut], Chendi Liao [aut], Jennifer Li [aut], F. Hoffmann-La Roche AG [cph, fnd]",
- "Maintainer": "Joe Zhu ",
- "Repository": "CRAN"
- },
"textshaping": {
"Package": "textshaping",
"Version": "1.0.0",