mirror of
https://github.com/agdamsbo/FreesearchR.git
synced 2025-09-12 18:09:39 +02:00
moved app to correctly include in package and allow load with dataset
This commit is contained in:
parent
419faca242
commit
8e73992b39
32 changed files with 5561 additions and 273 deletions
|
@ -1,6 +1,6 @@
|
|||
Package: webResearch
|
||||
Title: Browser Based Data Analysis
|
||||
Version: 0.0.0.9000
|
||||
Version: 24.11.1
|
||||
Authors@R:
|
||||
person("Andreas Gammelgaard", "Damsbo", , "agdamsbo@clin.au.dk", role = c("aut", "cre"),
|
||||
comment = c(ORCID = "0000-0002-7559-1154"))
|
||||
|
@ -14,7 +14,6 @@ Imports:
|
|||
bslib,
|
||||
dplyr,
|
||||
glue,
|
||||
gt,
|
||||
gtsummary,
|
||||
haven,
|
||||
here,
|
||||
|
|
|
@ -2,10 +2,11 @@
|
|||
|
||||
export(argsstring2list)
|
||||
export(baseline_table)
|
||||
export(file_extension)
|
||||
export(getfun)
|
||||
export(panel_space)
|
||||
export(read_input)
|
||||
export(regression_model)
|
||||
export(regression_table)
|
||||
export(shiny_webResearch)
|
||||
export(write_quarto)
|
||||
importFrom(stats,as.formula)
|
||||
|
|
34
R/app.R
Normal file
34
R/app.R
Normal file
|
@ -0,0 +1,34 @@
|
|||
#' Test version of the shiny_cast function to launch the app with a data set in
|
||||
#' the environment.
|
||||
#'
|
||||
#' @param data optional data set to provide for analysis
|
||||
#' @param ... arguments passed on to `shiny::runApp()`
|
||||
#'
|
||||
#' @return shiny app
|
||||
#' @export
|
||||
#'
|
||||
#' @examples
|
||||
#' \dontrun{
|
||||
#' mtcars |> shiny_webResearch(launch.browser = TRUE)
|
||||
#' }
|
||||
shiny_webResearch <- function(data = NULL, ...) {
|
||||
appDir <- system.file("apps", "data_analysis", package = "webResearch")
|
||||
if (appDir == "") {
|
||||
stop("Could not find example directory. Try re-installing `webResearch`.", call. = FALSE)
|
||||
}
|
||||
|
||||
G <- .GlobalEnv
|
||||
assign("webResearch_data", data, envir = G)
|
||||
a <- shiny::runApp(appDir = appDir, ...)
|
||||
return(invisible(a))
|
||||
}
|
||||
|
||||
|
||||
#' Wrapping nav_spacer to avoid errors on dependencies when packaging
|
||||
#'
|
||||
#' @return bslib object
|
||||
#' @export
|
||||
#'
|
||||
panel_space <- function() {
|
||||
bslib::nav_spacer()
|
||||
}
|
|
@ -13,7 +13,7 @@
|
|||
#' mtcars |> baseline_table(fun.args = list(by = "gear"))
|
||||
baseline_table <- function(data, fun.args = NULL, fun = gtsummary::tbl_summary, vars = NULL) {
|
||||
if (!is.null(vars)) {
|
||||
data <- dplyr::select(dplyr::all_of(vars))
|
||||
data <- data |> dplyr::select(dplyr::all_of(vars))
|
||||
}
|
||||
|
||||
out <- do.call(fun, c(list(data = data), fun.args))
|
||||
|
|
26
R/helpers.R
26
R/helpers.R
|
@ -48,24 +48,6 @@ write_quarto <- function(data,fileformat,qmd.file=here::here("analyses.qmd"),fil
|
|||
)
|
||||
}
|
||||
|
||||
#' Helper to import files correctly
|
||||
#'
|
||||
#' @param filenames file names
|
||||
#'
|
||||
#' @return character vector
|
||||
#' @export
|
||||
#'
|
||||
#' @examples
|
||||
#' file_extension(list.files(here::here(""))[[2]])[[1]]
|
||||
#' file_extension(c("file.cd..ks", "file"))
|
||||
file_extension <- function(filenames) {
|
||||
sub(
|
||||
pattern = "^(.*\\.|[^.]+)(?=[^.]*)", replacement = "",
|
||||
filenames,
|
||||
perl = TRUE
|
||||
)
|
||||
}
|
||||
|
||||
#' Flexible file import based on extension
|
||||
#'
|
||||
#' @param file file name
|
||||
|
@ -77,7 +59,7 @@ file_extension <- function(filenames) {
|
|||
#' @examples
|
||||
#' read_input("https://raw.githubusercontent.com/agdamsbo/cognitive.index.lookup/main/data/sample.csv")
|
||||
read_input <- function(file, consider.na = c("NA", '""', "")) {
|
||||
ext <- file_extension(file)
|
||||
ext <- tools::file_ext(file)
|
||||
|
||||
if (ext == "csv") {
|
||||
df <- readr::read_csv(file = file, na = consider.na)
|
||||
|
@ -86,10 +68,12 @@ read_input <- function(file, consider.na = c("NA", '""', "")) {
|
|||
} else if (ext == "dta") {
|
||||
df <- haven::read_dta(file = file)
|
||||
} else if (ext == "ods") {
|
||||
df <- readODS::read_ods(file = file)
|
||||
df <- readODS::read_ods(path = file)
|
||||
} else if (ext == "rds") {
|
||||
df <- readr::read_rds(file = file)
|
||||
} else {
|
||||
stop("Input file format has to be on of:
|
||||
'.csv', '.xls', '.xlsx', '.dta' or '.ods'")
|
||||
'.csv', '.xls', '.xlsx', '.dta', '.ods' or '.rds'")
|
||||
}
|
||||
|
||||
df
|
||||
|
|
|
@ -4,7 +4,7 @@
|
|||
#' @param fun Name of function as character vector or function to use for model creation.
|
||||
#' @param vars character vector of variables to include
|
||||
#' @param outcome.str Name of outcome variable. Character vector.
|
||||
#' @param auto.mode Make assumptions on function dependent on outcome data format.
|
||||
#' @param auto.mode Make assumptions on function dependent on outcome data format. Overwrites other arguments.
|
||||
#' @param formula.str Formula as string. Passed through 'glue::glue'. If given, 'outcome.str' and 'vars' are ignored. Optional.
|
||||
#' @param args.list List of arguments passed to 'fun' with 'do.call'.
|
||||
#'
|
||||
|
@ -15,16 +15,18 @@
|
|||
#'
|
||||
#' @examples
|
||||
#' gtsummary::trial |>
|
||||
#' regression_model(outcome.str = "age",)
|
||||
#' regression_model(outcome.str = "age")
|
||||
#' gtsummary::trial |>
|
||||
#' regression_model(
|
||||
#' outcome.str = "age",
|
||||
#' auto.mode = FALSE,
|
||||
#' fun = "stats::lm",
|
||||
#' formula.str = "{outcome.str}~.",
|
||||
#' args.list = NULL
|
||||
#' )
|
||||
#' gtsummary::trial |> regression_model(
|
||||
#' outcome.str = "trt",
|
||||
#' auto.mode = FALSE,
|
||||
#' fun = "stats::glm",
|
||||
#' args.list = list(family = binomial(link = "logit"))
|
||||
#' )
|
||||
|
@ -35,8 +37,10 @@ regression_model <- function(data,
|
|||
args.list = NULL,
|
||||
fun = NULL,
|
||||
vars = NULL) {
|
||||
if (formula.str==""){
|
||||
formula.str <- NULL
|
||||
if (!is.null(formula.str)) {
|
||||
if (formula.str == "") {
|
||||
formula.str <- NULL
|
||||
}
|
||||
}
|
||||
|
||||
if (!is.null(formula.str)) {
|
||||
|
@ -66,7 +70,7 @@ regression_model <- function(data,
|
|||
} else if (is.factor(data[[outcome.str]])) {
|
||||
if (length(levels(data[[outcome.str]])) == 2) {
|
||||
fun <- "stats::glm"
|
||||
args.list <- list(family = binomial(link = "logit"))
|
||||
args.list <- list(family = stats::binomial(link = "logit"))
|
||||
} else if (length(levels(data[[outcome.str]])) > 2) {
|
||||
fun <- "MASS::polr"
|
||||
args.list <- list(
|
||||
|
|
|
@ -13,7 +13,7 @@
|
|||
#' outcome.str = "stage",
|
||||
#' fun = "MASS::polr"
|
||||
#' ) |>
|
||||
#' regression_table(args.list = list(exponentiate = TRUE))
|
||||
#' regression_table(args.list = list("exponentiate" = TRUE))
|
||||
#' gtsummary::trial |>
|
||||
#' regression_model(
|
||||
#' outcome.str = "age",
|
||||
|
@ -32,7 +32,9 @@
|
|||
regression_table <- function(data, args.list = NULL, fun = "gtsummary::tbl_regression") {
|
||||
|
||||
if (any(c(length(class(data))!=1, class(data)!="lm"))){
|
||||
args.list <- c(args.list,list(exponentiate=TRUE))
|
||||
if (!"exponentiate" %in% names(args.list)){
|
||||
args.list <- c(args.list,list(exponentiate=TRUE))
|
||||
}
|
||||
}
|
||||
|
||||
out <- do.call(getfun(fun), c(list(x = data), args.list))
|
||||
|
|
140
app/ui.R
140
app/ui.R
|
@ -1,140 +0,0 @@
|
|||
require(shiny)
|
||||
require(bslib)
|
||||
# require(ggplot2)
|
||||
# source("https://raw.githubusercontent.com/agdamsbo/cognitive.index.lookup/main/R/index_from_raw.R")
|
||||
# source("https://raw.githubusercontent.com/agdamsbo/cognitive.index.lookup/main/R/plot_index.R")
|
||||
# source(here::here("R/index_from_raw.R"))
|
||||
# source(here::here("R/plot_index.R"))
|
||||
|
||||
# ui <- fluidPage(
|
||||
|
||||
cards <- list(
|
||||
bslib::card(
|
||||
max_height = "200px",
|
||||
full_screen = TRUE,
|
||||
bslib::card_header("Data overview"),
|
||||
shiny::uiOutput("data.input")
|
||||
),
|
||||
bslib::card(
|
||||
# max_height = "200px",
|
||||
full_screen = TRUE,
|
||||
bslib::card_header("Baseline characteristics"),
|
||||
gt::gt_output(outputId = "table1")
|
||||
),
|
||||
bslib::card(
|
||||
full_screen = TRUE,
|
||||
bslib::card_header("Multivariable regression table"),
|
||||
gt::gt_output(outputId = "table2")
|
||||
)
|
||||
)
|
||||
|
||||
panels <- list(
|
||||
bslib::nav_panel(title="Data overview",
|
||||
shiny::uiOutput("data.input")),
|
||||
bslib::nav_panel(title="Baseline characteristics",
|
||||
gt::gt_output(outputId = "table1")),
|
||||
bslib::nav_panel(title="Multivariable regression table",
|
||||
gt::gt_output(outputId = "table2"))
|
||||
)
|
||||
|
||||
|
||||
ui <- bslib::page_sidebar(
|
||||
theme = bslib::bs_theme(bootswatch = "minty"),
|
||||
title = "webResearcher for easy data analysis",
|
||||
window_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."),
|
||||
|
||||
# sidebarPanel(
|
||||
sidebar = bslib::sidebar(
|
||||
open = "open",
|
||||
h4("Upload your dataset"),
|
||||
|
||||
# Input: Select a file ----
|
||||
fileInput(
|
||||
inputId = "file",
|
||||
label = "Choose data file",
|
||||
multiple = FALSE,
|
||||
accept = c(
|
||||
"text/csv",
|
||||
"text/comma-separated-values,text/plain",
|
||||
".csv",
|
||||
".xlsx",
|
||||
".xls",
|
||||
".dta",
|
||||
".ods"
|
||||
)
|
||||
),
|
||||
conditionalPanel(
|
||||
condition = "output.uploaded=='yes'",
|
||||
h4("Parameter specifications"),
|
||||
radioButtons(
|
||||
inputId = "regression_auto",
|
||||
label = "Automatically choose function",
|
||||
inline = TRUE,
|
||||
choiceNames = c(
|
||||
"Yes",
|
||||
"No"
|
||||
),
|
||||
choiceValues = c(1, 2)
|
||||
),
|
||||
conditionalPanel(
|
||||
condition = "input.regression_auto==2",
|
||||
textInput(
|
||||
inputId = "regression_formula",
|
||||
label = "Formula string to render with 'glue::glue'",
|
||||
value = NULL
|
||||
),
|
||||
textInput(
|
||||
inputId = "regression_fun",
|
||||
label = "Function to use for analysis (needs pasckage and name)",
|
||||
value = "stats::lm"
|
||||
),
|
||||
textInput(
|
||||
inputId = "regression_args",
|
||||
label = "Arguments to pass to the function (provided as a string)",
|
||||
value = ""
|
||||
)
|
||||
),
|
||||
helpText(em("Please specify relevant columns from your data, and press 'Load data'")),
|
||||
uiOutput("outcome_var"),
|
||||
radioButtons(
|
||||
inputId = "all",
|
||||
label = "Specify covariables",
|
||||
inline = TRUE, selected = 2,
|
||||
choiceNames = c(
|
||||
"Yes",
|
||||
"No"
|
||||
),
|
||||
choiceValues = c(1, 2)
|
||||
),
|
||||
conditionalPanel(
|
||||
condition = "input.all==1",
|
||||
uiOutput("include_vars")
|
||||
),
|
||||
actionButton("load", "Analyse", class = "btn-primary")
|
||||
)
|
||||
# ,
|
||||
#
|
||||
# # Horizontal line ----
|
||||
# tags$hr(),
|
||||
# h4("Download results"),
|
||||
#
|
||||
# # Button
|
||||
# downloadButton(outputId="report",
|
||||
# label= "Download",
|
||||
# icon = shiny::icon("download"))
|
||||
),
|
||||
bslib::navset_card_underline(
|
||||
title="Data and results",
|
||||
panels[[1]],
|
||||
panels[[2]],
|
||||
panels[[3]]
|
||||
)
|
||||
|
||||
# layout_columns(
|
||||
# cards[[1]]
|
||||
# ),
|
||||
# layout_columns(
|
||||
# cards[[2]], cards[[3]]
|
||||
# )
|
||||
)
|
BIN
data.Rds
BIN
data.Rds
Binary file not shown.
1940
inst/apps/data_analysis/analyses.html
Normal file
1940
inst/apps/data_analysis/analyses.html
Normal file
File diff suppressed because it is too large
Load diff
|
@ -1,7 +1,54 @@
|
|||
|
||||
|
||||
########
|
||||
#### Current file: R//baseline_table.R
|
||||
#### Current file: /Users/au301842/webResearch/R//app.R
|
||||
########
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
shiny_webResearch <- function(data=NULL,...){
|
||||
appDir <- system.file("apps", "data_analysis", package = "webResearch")
|
||||
if (appDir == "") {
|
||||
stop("Could not find example directory. Try re-installing `webResearch`.", call. = FALSE)
|
||||
}
|
||||
|
||||
G <- .GlobalEnv
|
||||
assign("webResearch_data", data, envir=G)
|
||||
a=shiny::runApp(appDir = appDir, ...)
|
||||
return(invisible(a))
|
||||
}
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
page_panels <- function(data){
|
||||
bslib::navset_card_underline(
|
||||
title="Data and results",
|
||||
data[[1]],
|
||||
data[[2]],
|
||||
data[[3]]
|
||||
)
|
||||
}
|
||||
|
||||
|
||||
########
|
||||
#### Current file: /Users/au301842/webResearch/R//baseline_table.R
|
||||
########
|
||||
|
||||
|
||||
|
@ -19,7 +66,7 @@
|
|||
|
||||
baseline_table <- function(data, fun.args = NULL, fun = gtsummary::tbl_summary, vars = NULL) {
|
||||
if (!is.null(vars)) {
|
||||
data <- dplyr::select(dplyr::all_of(vars))
|
||||
data <- data |> dplyr::select(dplyr::all_of(vars))
|
||||
}
|
||||
|
||||
out <- do.call(fun, c(list(data = data), fun.args))
|
||||
|
@ -29,7 +76,7 @@ baseline_table <- function(data, fun.args = NULL, fun = gtsummary::tbl_summary,
|
|||
|
||||
|
||||
########
|
||||
#### Current file: R//helpers.R
|
||||
#### Current file: /Users/au301842/webResearch/R//helpers.R
|
||||
########
|
||||
|
||||
|
||||
|
@ -92,26 +139,8 @@ write_quarto <- function(data,fileformat,qmd.file=here::here("analyses.qmd"),fil
|
|||
|
||||
|
||||
|
||||
file_extension <- function(filenames) {
|
||||
sub(
|
||||
pattern = "^(.*\\.|[^.]+)(?=[^.]*)", replacement = "",
|
||||
filenames,
|
||||
perl = TRUE
|
||||
)
|
||||
}
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
read_input <- function(file, consider.na = c("NA", '""', "")) {
|
||||
ext <- file_extension(file)
|
||||
ext <- tools::file_ext(file)
|
||||
|
||||
if (ext == "csv") {
|
||||
df <- readr::read_csv(file = file, na = consider.na)
|
||||
|
@ -120,7 +149,7 @@ read_input <- function(file, consider.na = c("NA", '""', "")) {
|
|||
} else if (ext == "dta") {
|
||||
df <- haven::read_dta(file = file)
|
||||
} else if (ext == "ods") {
|
||||
df <- readODS::read_ods(file = file)
|
||||
df <- readODS::read_ods(path = file)
|
||||
} else {
|
||||
stop("Input file format has to be on of:
|
||||
'.csv', '.xls', '.xlsx', '.dta' or '.ods'")
|
||||
|
@ -145,7 +174,7 @@ argsstring2list <- function(string){
|
|||
|
||||
|
||||
########
|
||||
#### Current file: R//regression_model.R
|
||||
#### Current file: /Users/au301842/webResearch/R//regression_model.R
|
||||
########
|
||||
|
||||
|
||||
|
@ -175,6 +204,8 @@ argsstring2list <- function(string){
|
|||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
@ -185,8 +216,10 @@ regression_model <- function(data,
|
|||
args.list = NULL,
|
||||
fun = NULL,
|
||||
vars = NULL) {
|
||||
if (formula.str==""){
|
||||
formula.str <- NULL
|
||||
if (!is.null(formula.str)) {
|
||||
if (formula.str == "") {
|
||||
formula.str <- NULL
|
||||
}
|
||||
}
|
||||
|
||||
if (!is.null(formula.str)) {
|
||||
|
@ -216,7 +249,7 @@ regression_model <- function(data,
|
|||
} else if (is.factor(data[[outcome.str]])) {
|
||||
if (length(levels(data[[outcome.str]])) == 2) {
|
||||
fun <- "stats::glm"
|
||||
args.list <- list(family = binomial(link = "logit"))
|
||||
args.list <- list(family = stats::binomial(link = "logit"))
|
||||
} else if (length(levels(data[[outcome.str]])) > 2) {
|
||||
fun <- "MASS::polr"
|
||||
args.list <- list(
|
||||
|
@ -252,7 +285,7 @@ regression_model <- function(data,
|
|||
|
||||
|
||||
########
|
||||
#### Current file: R//regression_table.R
|
||||
#### Current file: /Users/au301842/webResearch/R//regression_table.R
|
||||
########
|
||||
|
||||
|
||||
|
@ -289,7 +322,9 @@ regression_model <- function(data,
|
|||
regression_table <- function(data, args.list = NULL, fun = "gtsummary::tbl_regression") {
|
||||
|
||||
if (any(c(length(class(data))!=1, class(data)!="lm"))){
|
||||
args.list <- c(args.list,list(exponentiate=TRUE))
|
||||
if (!"exponentiate" %in% names(args.list)){
|
||||
args.list <- c(args.list,list(exponentiate=TRUE))
|
||||
}
|
||||
}
|
||||
|
||||
out <- do.call(getfun(fun), c(list(x = data), args.list))
|
|
@ -5,6 +5,6 @@ account: agdamsbo
|
|||
server: shinyapps.io
|
||||
hostUrl: https://api.shinyapps.io/v1
|
||||
appId: 13276335
|
||||
bundleId: 9334619
|
||||
bundleId: 9370648
|
||||
url: https://agdamsbo.shinyapps.io/webResearch/
|
||||
version: 1
|
|
@ -1,13 +1,13 @@
|
|||
# project.aid::merge_scripts(list.files("R/",full.names = TRUE),dest = here::here("app/functions.R"))
|
||||
# source(here::here("app/functions.R"))
|
||||
|
||||
source("https://raw.githubusercontent.com/agdamsbo/webResearch/refs/heads/main/app/functions.R")
|
||||
# source("https://raw.githubusercontent.com/agdamsbo/webResearch/refs/heads/main/app/functions.R")
|
||||
|
||||
library(readr)
|
||||
library(MASS)
|
||||
library(stats)
|
||||
library(gt)
|
||||
library(gtsummary)
|
||||
library(gt)
|
||||
library(openxlsx2)
|
||||
library(haven)
|
||||
library(readODS)
|
||||
|
@ -19,23 +19,31 @@ library(quarto)
|
|||
library(here)
|
||||
library(broom)
|
||||
library(broom.helpers)
|
||||
|
||||
if (!requireNamespace("webResearch")) {
|
||||
devtools::install_github("agdamsbo/webResearch", quiet = TRUE, upgrade = "never")
|
||||
}
|
||||
library(webResearch)
|
||||
|
||||
server <- function(input, output, session) {
|
||||
v <- shiny::reactiveValues(
|
||||
list = NULL,
|
||||
ds = NULL
|
||||
ds = NULL,
|
||||
input = exists("webResearch_data"),
|
||||
local_temp = NULL
|
||||
)
|
||||
|
||||
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.
|
||||
|
||||
shiny::req(input$file)
|
||||
|
||||
if (v$input) {
|
||||
out <- webResearch_data
|
||||
} else {
|
||||
shiny::req(input$file)
|
||||
out <- read_input(input$file$datapath)
|
||||
}
|
||||
v$ds <- "present"
|
||||
return(read_input(input$file$datapath))
|
||||
return(out)
|
||||
})
|
||||
|
||||
output$include_vars <- shiny::renderUI({
|
||||
|
@ -59,7 +67,6 @@ server <- function(input, output, session) {
|
|||
})
|
||||
|
||||
output$data.input <- shiny::renderTable({
|
||||
shiny::req(input$file)
|
||||
ds()
|
||||
})
|
||||
|
||||
|
@ -80,26 +87,34 @@ server <- function(input, output, session) {
|
|||
by.var <- NULL
|
||||
}
|
||||
|
||||
if (is.null(input$include_vars)) {
|
||||
base_vars <- NULL
|
||||
} else {
|
||||
base_vars <- c(input$include_vars, input$outcome_var)
|
||||
}
|
||||
|
||||
|
||||
v$list <- list(
|
||||
data = data,
|
||||
table1 = data |>
|
||||
baseline_table(
|
||||
fun.args =
|
||||
list(
|
||||
by = by.var
|
||||
)
|
||||
),
|
||||
table2 = 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, ")"))),
|
||||
vars = input$include_vars
|
||||
) |>
|
||||
regression_table()
|
||||
)
|
||||
data = data,
|
||||
table1 = data |>
|
||||
baseline_table(
|
||||
vars = base_vars,
|
||||
fun.args =
|
||||
list(
|
||||
by = by.var
|
||||
)
|
||||
),
|
||||
table2 = 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, ")"))),
|
||||
vars = input$include_vars
|
||||
) |>
|
||||
regression_table()
|
||||
)
|
||||
|
||||
output$table1 <- gt::render_gt(
|
||||
v$list$table1 |>
|
||||
|
@ -124,6 +139,16 @@ server <- function(input, output, session) {
|
|||
|
||||
shiny::outputOptions(output, "uploaded", suspendWhenHidden = FALSE)
|
||||
|
||||
output$has_input <- shiny::reactive({
|
||||
if (v$input) {
|
||||
"yes"
|
||||
} else {
|
||||
"no"
|
||||
}
|
||||
})
|
||||
|
||||
shiny::outputOptions(output, "has_input", suspendWhenHidden = FALSE)
|
||||
|
||||
#####
|
||||
#### Generating output
|
||||
#####
|
||||
|
@ -136,14 +161,21 @@ server <- function(input, output, session) {
|
|||
# }
|
||||
# )
|
||||
|
||||
|
||||
# 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 = "analyses.html",
|
||||
content = function(file) {
|
||||
local.temp <- paste0("temp.", tools::file_ext(file))
|
||||
v$list |>
|
||||
write_quarto(
|
||||
file = file,
|
||||
qmd.file = "www/analyses.qmd"
|
||||
file = local.temp,
|
||||
qmd.file = file.path(getwd(), "www/analyses.qmd")
|
||||
)
|
||||
v$local_temp <- local.temp
|
||||
file.rename(v$local_temp, file)
|
||||
}
|
||||
)
|
||||
|
159
inst/apps/data_analysis/ui.R
Normal file
159
inst/apps/data_analysis/ui.R
Normal file
|
@ -0,0 +1,159 @@
|
|||
library(shiny)
|
||||
library(bslib)
|
||||
requireNamespace("gt")
|
||||
# require(ggplot2)
|
||||
# source("https://raw.githubusercontent.com/agdamsbo/cognitive.index.lookup/main/R/index_from_raw.R")
|
||||
# source("https://raw.githubusercontent.com/agdamsbo/cognitive.index.lookup/main/R/plot_index.R")
|
||||
# source(here::here("R/index_from_raw.R"))
|
||||
# source(here::here("R/plot_index.R"))
|
||||
|
||||
# ui <- fluidPage(
|
||||
|
||||
cards <- list(
|
||||
bslib::card(
|
||||
max_height = "200px",
|
||||
full_screen = TRUE,
|
||||
bslib::card_header("Data overview"),
|
||||
shiny::uiOutput("data.input")
|
||||
),
|
||||
bslib::card(
|
||||
# max_height = "200px",
|
||||
full_screen = TRUE,
|
||||
bslib::card_header("Baseline characteristics"),
|
||||
gt::gt_output(outputId = "table1")
|
||||
),
|
||||
bslib::card(
|
||||
full_screen = TRUE,
|
||||
bslib::card_header("Multivariable regression table"),
|
||||
gt::gt_output(outputId = "table2")
|
||||
)
|
||||
)
|
||||
|
||||
panels <- list(
|
||||
bslib::nav_panel(
|
||||
title = "Data overview",
|
||||
shiny::uiOutput("data.input")
|
||||
),
|
||||
bslib::nav_panel(
|
||||
title = "Baseline characteristics",
|
||||
gt::gt_output(outputId = "table1")
|
||||
),
|
||||
bslib::nav_panel(
|
||||
title = "Multivariable regression table",
|
||||
gt::gt_output(outputId = "table2")
|
||||
)
|
||||
)
|
||||
|
||||
|
||||
ui <- bslib::page(
|
||||
theme = bslib::bs_theme(bootswatch = "minty"),
|
||||
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."),
|
||||
|
||||
# sidebarPanel(
|
||||
sidebar = bslib::sidebar(
|
||||
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(
|
||||
"text/csv",
|
||||
"text/comma-separated-values,text/plain",
|
||||
".csv",
|
||||
".xlsx",
|
||||
".xls",
|
||||
".dta",
|
||||
".ods",
|
||||
".rds"
|
||||
)
|
||||
)
|
||||
),
|
||||
shiny::conditionalPanel(
|
||||
condition = "output.uploaded=='yes'",
|
||||
shiny::h4("Parameter specifications"),
|
||||
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 columns from your data, and press 'Load data'")),
|
||||
shiny::uiOutput("outcome_var"),
|
||||
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::actionButton("load", "Analyse", class = "btn-primary"),
|
||||
#
|
||||
# # Horizontal line ----
|
||||
tags$hr(),
|
||||
h4("Download results"),
|
||||
|
||||
shiny::helpText("The download currently works, but the output is not correctly formatted. Work in progress!"),
|
||||
|
||||
# Button
|
||||
downloadButton(
|
||||
outputId = "report",
|
||||
label = "Download",
|
||||
icon = shiny::icon("download")
|
||||
)
|
||||
|
||||
)
|
||||
),
|
||||
bslib::nav_spacer(),
|
||||
panels[[1]],
|
||||
panels[[2]],
|
||||
panels[[3]]
|
||||
|
||||
# layout_columns(
|
||||
# cards[[1]]
|
||||
# ),
|
||||
# layout_columns(
|
||||
# cards[[2]], cards[[3]]
|
||||
# )
|
||||
)
|
||||
)
|
2078
inst/apps/data_analysis/www/analyses_files/libs/bootstrap/bootstrap-icons.css
vendored
Normal file
2078
inst/apps/data_analysis/www/analyses_files/libs/bootstrap/bootstrap-icons.css
vendored
Normal file
File diff suppressed because it is too large
Load diff
Binary file not shown.
12
inst/apps/data_analysis/www/analyses_files/libs/bootstrap/bootstrap.min.css
vendored
Normal file
12
inst/apps/data_analysis/www/analyses_files/libs/bootstrap/bootstrap.min.css
vendored
Normal file
File diff suppressed because one or more lines are too long
7
inst/apps/data_analysis/www/analyses_files/libs/bootstrap/bootstrap.min.js
vendored
Normal file
7
inst/apps/data_analysis/www/analyses_files/libs/bootstrap/bootstrap.min.js
vendored
Normal file
File diff suppressed because one or more lines are too long
7
inst/apps/data_analysis/www/analyses_files/libs/clipboard/clipboard.min.js
vendored
Normal file
7
inst/apps/data_analysis/www/analyses_files/libs/clipboard/clipboard.min.js
vendored
Normal file
File diff suppressed because one or more lines are too long
9
inst/apps/data_analysis/www/analyses_files/libs/quarto-html/anchor.min.js
vendored
Normal file
9
inst/apps/data_analysis/www/analyses_files/libs/quarto-html/anchor.min.js
vendored
Normal file
File diff suppressed because one or more lines are too long
6
inst/apps/data_analysis/www/analyses_files/libs/quarto-html/popper.min.js
vendored
Normal file
6
inst/apps/data_analysis/www/analyses_files/libs/quarto-html/popper.min.js
vendored
Normal file
File diff suppressed because one or more lines are too long
|
@ -0,0 +1,205 @@
|
|||
/* quarto syntax highlight colors */
|
||||
:root {
|
||||
--quarto-hl-ot-color: #003B4F;
|
||||
--quarto-hl-at-color: #657422;
|
||||
--quarto-hl-ss-color: #20794D;
|
||||
--quarto-hl-an-color: #5E5E5E;
|
||||
--quarto-hl-fu-color: #4758AB;
|
||||
--quarto-hl-st-color: #20794D;
|
||||
--quarto-hl-cf-color: #003B4F;
|
||||
--quarto-hl-op-color: #5E5E5E;
|
||||
--quarto-hl-er-color: #AD0000;
|
||||
--quarto-hl-bn-color: #AD0000;
|
||||
--quarto-hl-al-color: #AD0000;
|
||||
--quarto-hl-va-color: #111111;
|
||||
--quarto-hl-bu-color: inherit;
|
||||
--quarto-hl-ex-color: inherit;
|
||||
--quarto-hl-pp-color: #AD0000;
|
||||
--quarto-hl-in-color: #5E5E5E;
|
||||
--quarto-hl-vs-color: #20794D;
|
||||
--quarto-hl-wa-color: #5E5E5E;
|
||||
--quarto-hl-do-color: #5E5E5E;
|
||||
--quarto-hl-im-color: #00769E;
|
||||
--quarto-hl-ch-color: #20794D;
|
||||
--quarto-hl-dt-color: #AD0000;
|
||||
--quarto-hl-fl-color: #AD0000;
|
||||
--quarto-hl-co-color: #5E5E5E;
|
||||
--quarto-hl-cv-color: #5E5E5E;
|
||||
--quarto-hl-cn-color: #8f5902;
|
||||
--quarto-hl-sc-color: #5E5E5E;
|
||||
--quarto-hl-dv-color: #AD0000;
|
||||
--quarto-hl-kw-color: #003B4F;
|
||||
}
|
||||
|
||||
/* other quarto variables */
|
||||
:root {
|
||||
--quarto-font-monospace: SFMono-Regular, Menlo, Monaco, Consolas, "Liberation Mono", "Courier New", monospace;
|
||||
}
|
||||
|
||||
pre > code.sourceCode > span {
|
||||
color: #003B4F;
|
||||
}
|
||||
|
||||
code span {
|
||||
color: #003B4F;
|
||||
}
|
||||
|
||||
code.sourceCode > span {
|
||||
color: #003B4F;
|
||||
}
|
||||
|
||||
div.sourceCode,
|
||||
div.sourceCode pre.sourceCode {
|
||||
color: #003B4F;
|
||||
}
|
||||
|
||||
code span.ot {
|
||||
color: #003B4F;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.at {
|
||||
color: #657422;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.ss {
|
||||
color: #20794D;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.an {
|
||||
color: #5E5E5E;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.fu {
|
||||
color: #4758AB;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.st {
|
||||
color: #20794D;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.cf {
|
||||
color: #003B4F;
|
||||
font-weight: bold;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.op {
|
||||
color: #5E5E5E;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.er {
|
||||
color: #AD0000;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.bn {
|
||||
color: #AD0000;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.al {
|
||||
color: #AD0000;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.va {
|
||||
color: #111111;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.bu {
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.ex {
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.pp {
|
||||
color: #AD0000;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.in {
|
||||
color: #5E5E5E;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.vs {
|
||||
color: #20794D;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.wa {
|
||||
color: #5E5E5E;
|
||||
font-style: italic;
|
||||
}
|
||||
|
||||
code span.do {
|
||||
color: #5E5E5E;
|
||||
font-style: italic;
|
||||
}
|
||||
|
||||
code span.im {
|
||||
color: #00769E;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.ch {
|
||||
color: #20794D;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.dt {
|
||||
color: #AD0000;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.fl {
|
||||
color: #AD0000;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.co {
|
||||
color: #5E5E5E;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.cv {
|
||||
color: #5E5E5E;
|
||||
font-style: italic;
|
||||
}
|
||||
|
||||
code span.cn {
|
||||
color: #8f5902;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.sc {
|
||||
color: #5E5E5E;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.dv {
|
||||
color: #AD0000;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
code span.kw {
|
||||
color: #003B4F;
|
||||
font-weight: bold;
|
||||
font-style: inherit;
|
||||
}
|
||||
|
||||
.prevent-inlining {
|
||||
content: "</";
|
||||
}
|
||||
|
||||
/*# sourceMappingURL=debc5d5d77c3f9108843748ff7464032.css.map */
|
|
@ -0,0 +1,908 @@
|
|||
const sectionChanged = new CustomEvent("quarto-sectionChanged", {
|
||||
detail: {},
|
||||
bubbles: true,
|
||||
cancelable: false,
|
||||
composed: false,
|
||||
});
|
||||
|
||||
const layoutMarginEls = () => {
|
||||
// Find any conflicting margin elements and add margins to the
|
||||
// top to prevent overlap
|
||||
const marginChildren = window.document.querySelectorAll(
|
||||
".column-margin.column-container > *, .margin-caption, .aside"
|
||||
);
|
||||
|
||||
let lastBottom = 0;
|
||||
for (const marginChild of marginChildren) {
|
||||
if (marginChild.offsetParent !== null) {
|
||||
// clear the top margin so we recompute it
|
||||
marginChild.style.marginTop = null;
|
||||
const top = marginChild.getBoundingClientRect().top + window.scrollY;
|
||||
if (top < lastBottom) {
|
||||
const marginChildStyle = window.getComputedStyle(marginChild);
|
||||
const marginBottom = parseFloat(marginChildStyle["marginBottom"]);
|
||||
const margin = lastBottom - top + marginBottom;
|
||||
marginChild.style.marginTop = `${margin}px`;
|
||||
}
|
||||
const styles = window.getComputedStyle(marginChild);
|
||||
const marginTop = parseFloat(styles["marginTop"]);
|
||||
lastBottom = top + marginChild.getBoundingClientRect().height + marginTop;
|
||||
}
|
||||
}
|
||||
};
|
||||
|
||||
window.document.addEventListener("DOMContentLoaded", function (_event) {
|
||||
// Recompute the position of margin elements anytime the body size changes
|
||||
if (window.ResizeObserver) {
|
||||
const resizeObserver = new window.ResizeObserver(
|
||||
throttle(() => {
|
||||
layoutMarginEls();
|
||||
if (
|
||||
window.document.body.getBoundingClientRect().width < 990 &&
|
||||
isReaderMode()
|
||||
) {
|
||||
quartoToggleReader();
|
||||
}
|
||||
}, 50)
|
||||
);
|
||||
resizeObserver.observe(window.document.body);
|
||||
}
|
||||
|
||||
const tocEl = window.document.querySelector('nav.toc-active[role="doc-toc"]');
|
||||
const sidebarEl = window.document.getElementById("quarto-sidebar");
|
||||
const leftTocEl = window.document.getElementById("quarto-sidebar-toc-left");
|
||||
const marginSidebarEl = window.document.getElementById(
|
||||
"quarto-margin-sidebar"
|
||||
);
|
||||
// function to determine whether the element has a previous sibling that is active
|
||||
const prevSiblingIsActiveLink = (el) => {
|
||||
const sibling = el.previousElementSibling;
|
||||
if (sibling && sibling.tagName === "A") {
|
||||
return sibling.classList.contains("active");
|
||||
} else {
|
||||
return false;
|
||||
}
|
||||
};
|
||||
|
||||
// fire slideEnter for bootstrap tab activations (for htmlwidget resize behavior)
|
||||
function fireSlideEnter(e) {
|
||||
const event = window.document.createEvent("Event");
|
||||
event.initEvent("slideenter", true, true);
|
||||
window.document.dispatchEvent(event);
|
||||
}
|
||||
const tabs = window.document.querySelectorAll('a[data-bs-toggle="tab"]');
|
||||
tabs.forEach((tab) => {
|
||||
tab.addEventListener("shown.bs.tab", fireSlideEnter);
|
||||
});
|
||||
|
||||
// fire slideEnter for tabby tab activations (for htmlwidget resize behavior)
|
||||
document.addEventListener("tabby", fireSlideEnter, false);
|
||||
|
||||
// Track scrolling and mark TOC links as active
|
||||
// get table of contents and sidebar (bail if we don't have at least one)
|
||||
const tocLinks = tocEl
|
||||
? [...tocEl.querySelectorAll("a[data-scroll-target]")]
|
||||
: [];
|
||||
const makeActive = (link) => tocLinks[link].classList.add("active");
|
||||
const removeActive = (link) => tocLinks[link].classList.remove("active");
|
||||
const removeAllActive = () =>
|
||||
[...Array(tocLinks.length).keys()].forEach((link) => removeActive(link));
|
||||
|
||||
// activate the anchor for a section associated with this TOC entry
|
||||
tocLinks.forEach((link) => {
|
||||
link.addEventListener("click", () => {
|
||||
if (link.href.indexOf("#") !== -1) {
|
||||
const anchor = link.href.split("#")[1];
|
||||
const heading = window.document.querySelector(
|
||||
`[data-anchor-id="${anchor}"]`
|
||||
);
|
||||
if (heading) {
|
||||
// Add the class
|
||||
heading.classList.add("reveal-anchorjs-link");
|
||||
|
||||
// function to show the anchor
|
||||
const handleMouseout = () => {
|
||||
heading.classList.remove("reveal-anchorjs-link");
|
||||
heading.removeEventListener("mouseout", handleMouseout);
|
||||
};
|
||||
|
||||
// add a function to clear the anchor when the user mouses out of it
|
||||
heading.addEventListener("mouseout", handleMouseout);
|
||||
}
|
||||
}
|
||||
});
|
||||
});
|
||||
|
||||
const sections = tocLinks.map((link) => {
|
||||
const target = link.getAttribute("data-scroll-target");
|
||||
if (target.startsWith("#")) {
|
||||
return window.document.getElementById(decodeURI(`${target.slice(1)}`));
|
||||
} else {
|
||||
return window.document.querySelector(decodeURI(`${target}`));
|
||||
}
|
||||
});
|
||||
|
||||
const sectionMargin = 200;
|
||||
let currentActive = 0;
|
||||
// track whether we've initialized state the first time
|
||||
let init = false;
|
||||
|
||||
const updateActiveLink = () => {
|
||||
// The index from bottom to top (e.g. reversed list)
|
||||
let sectionIndex = -1;
|
||||
if (
|
||||
window.innerHeight + window.pageYOffset >=
|
||||
window.document.body.offsetHeight
|
||||
) {
|
||||
// This is the no-scroll case where last section should be the active one
|
||||
sectionIndex = 0;
|
||||
} else {
|
||||
// This finds the last section visible on screen that should be made active
|
||||
sectionIndex = [...sections].reverse().findIndex((section) => {
|
||||
if (section) {
|
||||
return window.pageYOffset >= section.offsetTop - sectionMargin;
|
||||
} else {
|
||||
return false;
|
||||
}
|
||||
});
|
||||
}
|
||||
if (sectionIndex > -1) {
|
||||
const current = sections.length - sectionIndex - 1;
|
||||
if (current !== currentActive) {
|
||||
removeAllActive();
|
||||
currentActive = current;
|
||||
makeActive(current);
|
||||
if (init) {
|
||||
window.dispatchEvent(sectionChanged);
|
||||
}
|
||||
init = true;
|
||||
}
|
||||
}
|
||||
};
|
||||
|
||||
const inHiddenRegion = (top, bottom, hiddenRegions) => {
|
||||
for (const region of hiddenRegions) {
|
||||
if (top <= region.bottom && bottom >= region.top) {
|
||||
return true;
|
||||
}
|
||||
}
|
||||
return false;
|
||||
};
|
||||
|
||||
const categorySelector = "header.quarto-title-block .quarto-category";
|
||||
const activateCategories = (href) => {
|
||||
// Find any categories
|
||||
// Surround them with a link pointing back to:
|
||||
// #category=Authoring
|
||||
try {
|
||||
const categoryEls = window.document.querySelectorAll(categorySelector);
|
||||
for (const categoryEl of categoryEls) {
|
||||
const categoryText = categoryEl.textContent;
|
||||
if (categoryText) {
|
||||
const link = `${href}#category=${encodeURIComponent(categoryText)}`;
|
||||
const linkEl = window.document.createElement("a");
|
||||
linkEl.setAttribute("href", link);
|
||||
for (const child of categoryEl.childNodes) {
|
||||
linkEl.append(child);
|
||||
}
|
||||
categoryEl.appendChild(linkEl);
|
||||
}
|
||||
}
|
||||
} catch {
|
||||
// Ignore errors
|
||||
}
|
||||
};
|
||||
function hasTitleCategories() {
|
||||
return window.document.querySelector(categorySelector) !== null;
|
||||
}
|
||||
|
||||
function offsetRelativeUrl(url) {
|
||||
const offset = getMeta("quarto:offset");
|
||||
return offset ? offset + url : url;
|
||||
}
|
||||
|
||||
function offsetAbsoluteUrl(url) {
|
||||
const offset = getMeta("quarto:offset");
|
||||
const baseUrl = new URL(offset, window.location);
|
||||
|
||||
const projRelativeUrl = url.replace(baseUrl, "");
|
||||
if (projRelativeUrl.startsWith("/")) {
|
||||
return projRelativeUrl;
|
||||
} else {
|
||||
return "/" + projRelativeUrl;
|
||||
}
|
||||
}
|
||||
|
||||
// read a meta tag value
|
||||
function getMeta(metaName) {
|
||||
const metas = window.document.getElementsByTagName("meta");
|
||||
for (let i = 0; i < metas.length; i++) {
|
||||
if (metas[i].getAttribute("name") === metaName) {
|
||||
return metas[i].getAttribute("content");
|
||||
}
|
||||
}
|
||||
return "";
|
||||
}
|
||||
|
||||
async function findAndActivateCategories() {
|
||||
const currentPagePath = offsetAbsoluteUrl(window.location.href);
|
||||
const response = await fetch(offsetRelativeUrl("listings.json"));
|
||||
if (response.status == 200) {
|
||||
return response.json().then(function (listingPaths) {
|
||||
const listingHrefs = [];
|
||||
for (const listingPath of listingPaths) {
|
||||
const pathWithoutLeadingSlash = listingPath.listing.substring(1);
|
||||
for (const item of listingPath.items) {
|
||||
if (
|
||||
item === currentPagePath ||
|
||||
item === currentPagePath + "index.html"
|
||||
) {
|
||||
// Resolve this path against the offset to be sure
|
||||
// we already are using the correct path to the listing
|
||||
// (this adjusts the listing urls to be rooted against
|
||||
// whatever root the page is actually running against)
|
||||
const relative = offsetRelativeUrl(pathWithoutLeadingSlash);
|
||||
const baseUrl = window.location;
|
||||
const resolvedPath = new URL(relative, baseUrl);
|
||||
listingHrefs.push(resolvedPath.pathname);
|
||||
break;
|
||||
}
|
||||
}
|
||||
}
|
||||
|
||||
// Look up the tree for a nearby linting and use that if we find one
|
||||
const nearestListing = findNearestParentListing(
|
||||
offsetAbsoluteUrl(window.location.pathname),
|
||||
listingHrefs
|
||||
);
|
||||
if (nearestListing) {
|
||||
activateCategories(nearestListing);
|
||||
} else {
|
||||
// See if the referrer is a listing page for this item
|
||||
const referredRelativePath = offsetAbsoluteUrl(document.referrer);
|
||||
const referrerListing = listingHrefs.find((listingHref) => {
|
||||
const isListingReferrer =
|
||||
listingHref === referredRelativePath ||
|
||||
listingHref === referredRelativePath + "index.html";
|
||||
return isListingReferrer;
|
||||
});
|
||||
|
||||
if (referrerListing) {
|
||||
// Try to use the referrer if possible
|
||||
activateCategories(referrerListing);
|
||||
} else if (listingHrefs.length > 0) {
|
||||
// Otherwise, just fall back to the first listing
|
||||
activateCategories(listingHrefs[0]);
|
||||
}
|
||||
}
|
||||
});
|
||||
}
|
||||
}
|
||||
if (hasTitleCategories()) {
|
||||
findAndActivateCategories();
|
||||
}
|
||||
|
||||
const findNearestParentListing = (href, listingHrefs) => {
|
||||
if (!href || !listingHrefs) {
|
||||
return undefined;
|
||||
}
|
||||
// Look up the tree for a nearby linting and use that if we find one
|
||||
const relativeParts = href.substring(1).split("/");
|
||||
while (relativeParts.length > 0) {
|
||||
const path = relativeParts.join("/");
|
||||
for (const listingHref of listingHrefs) {
|
||||
if (listingHref.startsWith(path)) {
|
||||
return listingHref;
|
||||
}
|
||||
}
|
||||
relativeParts.pop();
|
||||
}
|
||||
|
||||
return undefined;
|
||||
};
|
||||
|
||||
const manageSidebarVisiblity = (el, placeholderDescriptor) => {
|
||||
let isVisible = true;
|
||||
let elRect;
|
||||
|
||||
return (hiddenRegions) => {
|
||||
if (el === null) {
|
||||
return;
|
||||
}
|
||||
|
||||
// Find the last element of the TOC
|
||||
const lastChildEl = el.lastElementChild;
|
||||
|
||||
if (lastChildEl) {
|
||||
// Converts the sidebar to a menu
|
||||
const convertToMenu = () => {
|
||||
for (const child of el.children) {
|
||||
child.style.opacity = 0;
|
||||
child.style.overflow = "hidden";
|
||||
child.style.pointerEvents = "none";
|
||||
}
|
||||
|
||||
nexttick(() => {
|
||||
const toggleContainer = window.document.createElement("div");
|
||||
toggleContainer.style.width = "100%";
|
||||
toggleContainer.classList.add("zindex-over-content");
|
||||
toggleContainer.classList.add("quarto-sidebar-toggle");
|
||||
toggleContainer.classList.add("headroom-target"); // Marks this to be managed by headeroom
|
||||
toggleContainer.id = placeholderDescriptor.id;
|
||||
toggleContainer.style.position = "fixed";
|
||||
|
||||
const toggleIcon = window.document.createElement("i");
|
||||
toggleIcon.classList.add("quarto-sidebar-toggle-icon");
|
||||
toggleIcon.classList.add("bi");
|
||||
toggleIcon.classList.add("bi-caret-down-fill");
|
||||
|
||||
const toggleTitle = window.document.createElement("div");
|
||||
const titleEl = window.document.body.querySelector(
|
||||
placeholderDescriptor.titleSelector
|
||||
);
|
||||
if (titleEl) {
|
||||
toggleTitle.append(
|
||||
titleEl.textContent || titleEl.innerText,
|
||||
toggleIcon
|
||||
);
|
||||
}
|
||||
toggleTitle.classList.add("zindex-over-content");
|
||||
toggleTitle.classList.add("quarto-sidebar-toggle-title");
|
||||
toggleContainer.append(toggleTitle);
|
||||
|
||||
const toggleContents = window.document.createElement("div");
|
||||
toggleContents.classList = el.classList;
|
||||
toggleContents.classList.add("zindex-over-content");
|
||||
toggleContents.classList.add("quarto-sidebar-toggle-contents");
|
||||
for (const child of el.children) {
|
||||
if (child.id === "toc-title") {
|
||||
continue;
|
||||
}
|
||||
|
||||
const clone = child.cloneNode(true);
|
||||
clone.style.opacity = 1;
|
||||
clone.style.pointerEvents = null;
|
||||
clone.style.display = null;
|
||||
toggleContents.append(clone);
|
||||
}
|
||||
toggleContents.style.height = "0px";
|
||||
const positionToggle = () => {
|
||||
// position the element (top left of parent, same width as parent)
|
||||
if (!elRect) {
|
||||
elRect = el.getBoundingClientRect();
|
||||
}
|
||||
toggleContainer.style.left = `${elRect.left}px`;
|
||||
toggleContainer.style.top = `${elRect.top}px`;
|
||||
toggleContainer.style.width = `${elRect.width}px`;
|
||||
};
|
||||
positionToggle();
|
||||
|
||||
toggleContainer.append(toggleContents);
|
||||
el.parentElement.prepend(toggleContainer);
|
||||
|
||||
// Process clicks
|
||||
let tocShowing = false;
|
||||
// Allow the caller to control whether this is dismissed
|
||||
// when it is clicked (e.g. sidebar navigation supports
|
||||
// opening and closing the nav tree, so don't dismiss on click)
|
||||
const clickEl = placeholderDescriptor.dismissOnClick
|
||||
? toggleContainer
|
||||
: toggleTitle;
|
||||
|
||||
const closeToggle = () => {
|
||||
if (tocShowing) {
|
||||
toggleContainer.classList.remove("expanded");
|
||||
toggleContents.style.height = "0px";
|
||||
tocShowing = false;
|
||||
}
|
||||
};
|
||||
|
||||
// Get rid of any expanded toggle if the user scrolls
|
||||
window.document.addEventListener(
|
||||
"scroll",
|
||||
throttle(() => {
|
||||
closeToggle();
|
||||
}, 50)
|
||||
);
|
||||
|
||||
// Handle positioning of the toggle
|
||||
window.addEventListener(
|
||||
"resize",
|
||||
throttle(() => {
|
||||
elRect = undefined;
|
||||
positionToggle();
|
||||
}, 50)
|
||||
);
|
||||
|
||||
window.addEventListener("quarto-hrChanged", () => {
|
||||
elRect = undefined;
|
||||
});
|
||||
|
||||
// Process the click
|
||||
clickEl.onclick = () => {
|
||||
if (!tocShowing) {
|
||||
toggleContainer.classList.add("expanded");
|
||||
toggleContents.style.height = null;
|
||||
tocShowing = true;
|
||||
} else {
|
||||
closeToggle();
|
||||
}
|
||||
};
|
||||
});
|
||||
};
|
||||
|
||||
// Converts a sidebar from a menu back to a sidebar
|
||||
const convertToSidebar = () => {
|
||||
for (const child of el.children) {
|
||||
child.style.opacity = 1;
|
||||
child.style.overflow = null;
|
||||
child.style.pointerEvents = null;
|
||||
}
|
||||
|
||||
const placeholderEl = window.document.getElementById(
|
||||
placeholderDescriptor.id
|
||||
);
|
||||
if (placeholderEl) {
|
||||
placeholderEl.remove();
|
||||
}
|
||||
|
||||
el.classList.remove("rollup");
|
||||
};
|
||||
|
||||
if (isReaderMode()) {
|
||||
convertToMenu();
|
||||
isVisible = false;
|
||||
} else {
|
||||
// Find the top and bottom o the element that is being managed
|
||||
const elTop = el.offsetTop;
|
||||
const elBottom =
|
||||
elTop + lastChildEl.offsetTop + lastChildEl.offsetHeight;
|
||||
|
||||
if (!isVisible) {
|
||||
// If the element is current not visible reveal if there are
|
||||
// no conflicts with overlay regions
|
||||
if (!inHiddenRegion(elTop, elBottom, hiddenRegions)) {
|
||||
convertToSidebar();
|
||||
isVisible = true;
|
||||
}
|
||||
} else {
|
||||
// If the element is visible, hide it if it conflicts with overlay regions
|
||||
// and insert a placeholder toggle (or if we're in reader mode)
|
||||
if (inHiddenRegion(elTop, elBottom, hiddenRegions)) {
|
||||
convertToMenu();
|
||||
isVisible = false;
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
};
|
||||
};
|
||||
|
||||
const tabEls = document.querySelectorAll('a[data-bs-toggle="tab"]');
|
||||
for (const tabEl of tabEls) {
|
||||
const id = tabEl.getAttribute("data-bs-target");
|
||||
if (id) {
|
||||
const columnEl = document.querySelector(
|
||||
`${id} .column-margin, .tabset-margin-content`
|
||||
);
|
||||
if (columnEl)
|
||||
tabEl.addEventListener("shown.bs.tab", function (event) {
|
||||
const el = event.srcElement;
|
||||
if (el) {
|
||||
const visibleCls = `${el.id}-margin-content`;
|
||||
// walk up until we find a parent tabset
|
||||
let panelTabsetEl = el.parentElement;
|
||||
while (panelTabsetEl) {
|
||||
if (panelTabsetEl.classList.contains("panel-tabset")) {
|
||||
break;
|
||||
}
|
||||
panelTabsetEl = panelTabsetEl.parentElement;
|
||||
}
|
||||
|
||||
if (panelTabsetEl) {
|
||||
const prevSib = panelTabsetEl.previousElementSibling;
|
||||
if (
|
||||
prevSib &&
|
||||
prevSib.classList.contains("tabset-margin-container")
|
||||
) {
|
||||
const childNodes = prevSib.querySelectorAll(
|
||||
".tabset-margin-content"
|
||||
);
|
||||
for (const childEl of childNodes) {
|
||||
if (childEl.classList.contains(visibleCls)) {
|
||||
childEl.classList.remove("collapse");
|
||||
} else {
|
||||
childEl.classList.add("collapse");
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
|
||||
layoutMarginEls();
|
||||
});
|
||||
}
|
||||
}
|
||||
|
||||
// Manage the visibility of the toc and the sidebar
|
||||
const marginScrollVisibility = manageSidebarVisiblity(marginSidebarEl, {
|
||||
id: "quarto-toc-toggle",
|
||||
titleSelector: "#toc-title",
|
||||
dismissOnClick: true,
|
||||
});
|
||||
const sidebarScrollVisiblity = manageSidebarVisiblity(sidebarEl, {
|
||||
id: "quarto-sidebarnav-toggle",
|
||||
titleSelector: ".title",
|
||||
dismissOnClick: false,
|
||||
});
|
||||
let tocLeftScrollVisibility;
|
||||
if (leftTocEl) {
|
||||
tocLeftScrollVisibility = manageSidebarVisiblity(leftTocEl, {
|
||||
id: "quarto-lefttoc-toggle",
|
||||
titleSelector: "#toc-title",
|
||||
dismissOnClick: true,
|
||||
});
|
||||
}
|
||||
|
||||
// Find the first element that uses formatting in special columns
|
||||
const conflictingEls = window.document.body.querySelectorAll(
|
||||
'[class^="column-"], [class*=" column-"], aside, [class*="margin-caption"], [class*=" margin-caption"], [class*="margin-ref"], [class*=" margin-ref"]'
|
||||
);
|
||||
|
||||
// Filter all the possibly conflicting elements into ones
|
||||
// the do conflict on the left or ride side
|
||||
const arrConflictingEls = Array.from(conflictingEls);
|
||||
const leftSideConflictEls = arrConflictingEls.filter((el) => {
|
||||
if (el.tagName === "ASIDE") {
|
||||
return false;
|
||||
}
|
||||
return Array.from(el.classList).find((className) => {
|
||||
return (
|
||||
className !== "column-body" &&
|
||||
className.startsWith("column-") &&
|
||||
!className.endsWith("right") &&
|
||||
!className.endsWith("container") &&
|
||||
className !== "column-margin"
|
||||
);
|
||||
});
|
||||
});
|
||||
const rightSideConflictEls = arrConflictingEls.filter((el) => {
|
||||
if (el.tagName === "ASIDE") {
|
||||
return true;
|
||||
}
|
||||
|
||||
const hasMarginCaption = Array.from(el.classList).find((className) => {
|
||||
return className == "margin-caption";
|
||||
});
|
||||
if (hasMarginCaption) {
|
||||
return true;
|
||||
}
|
||||
|
||||
return Array.from(el.classList).find((className) => {
|
||||
return (
|
||||
className !== "column-body" &&
|
||||
!className.endsWith("container") &&
|
||||
className.startsWith("column-") &&
|
||||
!className.endsWith("left")
|
||||
);
|
||||
});
|
||||
});
|
||||
|
||||
const kOverlapPaddingSize = 10;
|
||||
function toRegions(els) {
|
||||
return els.map((el) => {
|
||||
const boundRect = el.getBoundingClientRect();
|
||||
const top =
|
||||
boundRect.top +
|
||||
document.documentElement.scrollTop -
|
||||
kOverlapPaddingSize;
|
||||
return {
|
||||
top,
|
||||
bottom: top + el.scrollHeight + 2 * kOverlapPaddingSize,
|
||||
};
|
||||
});
|
||||
}
|
||||
|
||||
let hasObserved = false;
|
||||
const visibleItemObserver = (els) => {
|
||||
let visibleElements = [...els];
|
||||
const intersectionObserver = new IntersectionObserver(
|
||||
(entries, _observer) => {
|
||||
entries.forEach((entry) => {
|
||||
if (entry.isIntersecting) {
|
||||
if (visibleElements.indexOf(entry.target) === -1) {
|
||||
visibleElements.push(entry.target);
|
||||
}
|
||||
} else {
|
||||
visibleElements = visibleElements.filter((visibleEntry) => {
|
||||
return visibleEntry !== entry;
|
||||
});
|
||||
}
|
||||
});
|
||||
|
||||
if (!hasObserved) {
|
||||
hideOverlappedSidebars();
|
||||
}
|
||||
hasObserved = true;
|
||||
},
|
||||
{}
|
||||
);
|
||||
els.forEach((el) => {
|
||||
intersectionObserver.observe(el);
|
||||
});
|
||||
|
||||
return {
|
||||
getVisibleEntries: () => {
|
||||
return visibleElements;
|
||||
},
|
||||
};
|
||||
};
|
||||
|
||||
const rightElementObserver = visibleItemObserver(rightSideConflictEls);
|
||||
const leftElementObserver = visibleItemObserver(leftSideConflictEls);
|
||||
|
||||
const hideOverlappedSidebars = () => {
|
||||
marginScrollVisibility(toRegions(rightElementObserver.getVisibleEntries()));
|
||||
sidebarScrollVisiblity(toRegions(leftElementObserver.getVisibleEntries()));
|
||||
if (tocLeftScrollVisibility) {
|
||||
tocLeftScrollVisibility(
|
||||
toRegions(leftElementObserver.getVisibleEntries())
|
||||
);
|
||||
}
|
||||
};
|
||||
|
||||
window.quartoToggleReader = () => {
|
||||
// Applies a slow class (or removes it)
|
||||
// to update the transition speed
|
||||
const slowTransition = (slow) => {
|
||||
const manageTransition = (id, slow) => {
|
||||
const el = document.getElementById(id);
|
||||
if (el) {
|
||||
if (slow) {
|
||||
el.classList.add("slow");
|
||||
} else {
|
||||
el.classList.remove("slow");
|
||||
}
|
||||
}
|
||||
};
|
||||
|
||||
manageTransition("TOC", slow);
|
||||
manageTransition("quarto-sidebar", slow);
|
||||
};
|
||||
const readerMode = !isReaderMode();
|
||||
setReaderModeValue(readerMode);
|
||||
|
||||
// If we're entering reader mode, slow the transition
|
||||
if (readerMode) {
|
||||
slowTransition(readerMode);
|
||||
}
|
||||
highlightReaderToggle(readerMode);
|
||||
hideOverlappedSidebars();
|
||||
|
||||
// If we're exiting reader mode, restore the non-slow transition
|
||||
if (!readerMode) {
|
||||
slowTransition(!readerMode);
|
||||
}
|
||||
};
|
||||
|
||||
const highlightReaderToggle = (readerMode) => {
|
||||
const els = document.querySelectorAll(".quarto-reader-toggle");
|
||||
if (els) {
|
||||
els.forEach((el) => {
|
||||
if (readerMode) {
|
||||
el.classList.add("reader");
|
||||
} else {
|
||||
el.classList.remove("reader");
|
||||
}
|
||||
});
|
||||
}
|
||||
};
|
||||
|
||||
const setReaderModeValue = (val) => {
|
||||
if (window.location.protocol !== "file:") {
|
||||
window.localStorage.setItem("quarto-reader-mode", val);
|
||||
} else {
|
||||
localReaderMode = val;
|
||||
}
|
||||
};
|
||||
|
||||
const isReaderMode = () => {
|
||||
if (window.location.protocol !== "file:") {
|
||||
return window.localStorage.getItem("quarto-reader-mode") === "true";
|
||||
} else {
|
||||
return localReaderMode;
|
||||
}
|
||||
};
|
||||
let localReaderMode = null;
|
||||
|
||||
const tocOpenDepthStr = tocEl?.getAttribute("data-toc-expanded");
|
||||
const tocOpenDepth = tocOpenDepthStr ? Number(tocOpenDepthStr) : 1;
|
||||
|
||||
// Walk the TOC and collapse/expand nodes
|
||||
// Nodes are expanded if:
|
||||
// - they are top level
|
||||
// - they have children that are 'active' links
|
||||
// - they are directly below an link that is 'active'
|
||||
const walk = (el, depth) => {
|
||||
// Tick depth when we enter a UL
|
||||
if (el.tagName === "UL") {
|
||||
depth = depth + 1;
|
||||
}
|
||||
|
||||
// It this is active link
|
||||
let isActiveNode = false;
|
||||
if (el.tagName === "A" && el.classList.contains("active")) {
|
||||
isActiveNode = true;
|
||||
}
|
||||
|
||||
// See if there is an active child to this element
|
||||
let hasActiveChild = false;
|
||||
for (child of el.children) {
|
||||
hasActiveChild = walk(child, depth) || hasActiveChild;
|
||||
}
|
||||
|
||||
// Process the collapse state if this is an UL
|
||||
if (el.tagName === "UL") {
|
||||
if (tocOpenDepth === -1 && depth > 1) {
|
||||
// toc-expand: false
|
||||
el.classList.add("collapse");
|
||||
} else if (
|
||||
depth <= tocOpenDepth ||
|
||||
hasActiveChild ||
|
||||
prevSiblingIsActiveLink(el)
|
||||
) {
|
||||
el.classList.remove("collapse");
|
||||
} else {
|
||||
el.classList.add("collapse");
|
||||
}
|
||||
|
||||
// untick depth when we leave a UL
|
||||
depth = depth - 1;
|
||||
}
|
||||
return hasActiveChild || isActiveNode;
|
||||
};
|
||||
|
||||
// walk the TOC and expand / collapse any items that should be shown
|
||||
if (tocEl) {
|
||||
updateActiveLink();
|
||||
walk(tocEl, 0);
|
||||
}
|
||||
|
||||
// Throttle the scroll event and walk peridiocally
|
||||
window.document.addEventListener(
|
||||
"scroll",
|
||||
throttle(() => {
|
||||
if (tocEl) {
|
||||
updateActiveLink();
|
||||
walk(tocEl, 0);
|
||||
}
|
||||
if (!isReaderMode()) {
|
||||
hideOverlappedSidebars();
|
||||
}
|
||||
}, 5)
|
||||
);
|
||||
window.addEventListener(
|
||||
"resize",
|
||||
throttle(() => {
|
||||
if (tocEl) {
|
||||
updateActiveLink();
|
||||
walk(tocEl, 0);
|
||||
}
|
||||
if (!isReaderMode()) {
|
||||
hideOverlappedSidebars();
|
||||
}
|
||||
}, 10)
|
||||
);
|
||||
hideOverlappedSidebars();
|
||||
highlightReaderToggle(isReaderMode());
|
||||
});
|
||||
|
||||
// grouped tabsets
|
||||
window.addEventListener("pageshow", (_event) => {
|
||||
function getTabSettings() {
|
||||
const data = localStorage.getItem("quarto-persistent-tabsets-data");
|
||||
if (!data) {
|
||||
localStorage.setItem("quarto-persistent-tabsets-data", "{}");
|
||||
return {};
|
||||
}
|
||||
if (data) {
|
||||
return JSON.parse(data);
|
||||
}
|
||||
}
|
||||
|
||||
function setTabSettings(data) {
|
||||
localStorage.setItem(
|
||||
"quarto-persistent-tabsets-data",
|
||||
JSON.stringify(data)
|
||||
);
|
||||
}
|
||||
|
||||
function setTabState(groupName, groupValue) {
|
||||
const data = getTabSettings();
|
||||
data[groupName] = groupValue;
|
||||
setTabSettings(data);
|
||||
}
|
||||
|
||||
function toggleTab(tab, active) {
|
||||
const tabPanelId = tab.getAttribute("aria-controls");
|
||||
const tabPanel = document.getElementById(tabPanelId);
|
||||
if (active) {
|
||||
tab.classList.add("active");
|
||||
tabPanel.classList.add("active");
|
||||
} else {
|
||||
tab.classList.remove("active");
|
||||
tabPanel.classList.remove("active");
|
||||
}
|
||||
}
|
||||
|
||||
function toggleAll(selectedGroup, selectorsToSync) {
|
||||
for (const [thisGroup, tabs] of Object.entries(selectorsToSync)) {
|
||||
const active = selectedGroup === thisGroup;
|
||||
for (const tab of tabs) {
|
||||
toggleTab(tab, active);
|
||||
}
|
||||
}
|
||||
}
|
||||
|
||||
function findSelectorsToSyncByLanguage() {
|
||||
const result = {};
|
||||
const tabs = Array.from(
|
||||
document.querySelectorAll(`div[data-group] a[id^='tabset-']`)
|
||||
);
|
||||
for (const item of tabs) {
|
||||
const div = item.parentElement.parentElement.parentElement;
|
||||
const group = div.getAttribute("data-group");
|
||||
if (!result[group]) {
|
||||
result[group] = {};
|
||||
}
|
||||
const selectorsToSync = result[group];
|
||||
const value = item.innerHTML;
|
||||
if (!selectorsToSync[value]) {
|
||||
selectorsToSync[value] = [];
|
||||
}
|
||||
selectorsToSync[value].push(item);
|
||||
}
|
||||
return result;
|
||||
}
|
||||
|
||||
function setupSelectorSync() {
|
||||
const selectorsToSync = findSelectorsToSyncByLanguage();
|
||||
Object.entries(selectorsToSync).forEach(([group, tabSetsByValue]) => {
|
||||
Object.entries(tabSetsByValue).forEach(([value, items]) => {
|
||||
items.forEach((item) => {
|
||||
item.addEventListener("click", (_event) => {
|
||||
setTabState(group, value);
|
||||
toggleAll(value, selectorsToSync[group]);
|
||||
});
|
||||
});
|
||||
});
|
||||
});
|
||||
return selectorsToSync;
|
||||
}
|
||||
|
||||
const selectorsToSync = setupSelectorSync();
|
||||
for (const [group, selectedName] of Object.entries(getTabSettings())) {
|
||||
const selectors = selectorsToSync[group];
|
||||
// it's possible that stale state gives us empty selections, so we explicitly check here.
|
||||
if (selectors) {
|
||||
toggleAll(selectedName, selectors);
|
||||
}
|
||||
}
|
||||
});
|
||||
|
||||
function throttle(func, wait) {
|
||||
let waiting = false;
|
||||
return function () {
|
||||
if (!waiting) {
|
||||
func.apply(this, arguments);
|
||||
waiting = true;
|
||||
setTimeout(function () {
|
||||
waiting = false;
|
||||
}, wait);
|
||||
}
|
||||
};
|
||||
}
|
||||
|
||||
function nexttick(func) {
|
||||
return setTimeout(func, 0);
|
||||
}
|
|
@ -0,0 +1 @@
|
|||
.tippy-box[data-animation=fade][data-state=hidden]{opacity:0}[data-tippy-root]{max-width:calc(100vw - 10px)}.tippy-box{position:relative;background-color:#333;color:#fff;border-radius:4px;font-size:14px;line-height:1.4;white-space:normal;outline:0;transition-property:transform,visibility,opacity}.tippy-box[data-placement^=top]>.tippy-arrow{bottom:0}.tippy-box[data-placement^=top]>.tippy-arrow:before{bottom:-7px;left:0;border-width:8px 8px 0;border-top-color:initial;transform-origin:center top}.tippy-box[data-placement^=bottom]>.tippy-arrow{top:0}.tippy-box[data-placement^=bottom]>.tippy-arrow:before{top:-7px;left:0;border-width:0 8px 8px;border-bottom-color:initial;transform-origin:center bottom}.tippy-box[data-placement^=left]>.tippy-arrow{right:0}.tippy-box[data-placement^=left]>.tippy-arrow:before{border-width:8px 0 8px 8px;border-left-color:initial;right:-7px;transform-origin:center left}.tippy-box[data-placement^=right]>.tippy-arrow{left:0}.tippy-box[data-placement^=right]>.tippy-arrow:before{left:-7px;border-width:8px 8px 8px 0;border-right-color:initial;transform-origin:center right}.tippy-box[data-inertia][data-state=visible]{transition-timing-function:cubic-bezier(.54,1.5,.38,1.11)}.tippy-arrow{width:16px;height:16px;color:#333}.tippy-arrow:before{content:"";position:absolute;border-color:transparent;border-style:solid}.tippy-content{position:relative;padding:5px 9px;z-index:1}
|
2
inst/apps/data_analysis/www/analyses_files/libs/quarto-html/tippy.umd.min.js
vendored
Normal file
2
inst/apps/data_analysis/www/analyses_files/libs/quarto-html/tippy.umd.min.js
vendored
Normal file
File diff suppressed because one or more lines are too long
|
@ -1,21 +0,0 @@
|
|||
% Generated by roxygen2: do not edit by hand
|
||||
% Please edit documentation in R/helpers.R
|
||||
\name{file_extension}
|
||||
\alias{file_extension}
|
||||
\title{Helper to import files correctly}
|
||||
\usage{
|
||||
file_extension(filenames)
|
||||
}
|
||||
\arguments{
|
||||
\item{filenames}{file names}
|
||||
}
|
||||
\value{
|
||||
character vector
|
||||
}
|
||||
\description{
|
||||
Helper to import files correctly
|
||||
}
|
||||
\examples{
|
||||
file_extension(list.files(here::here(""))[[2]])[[1]]
|
||||
file_extension(c("file.cd..ks", "file"))
|
||||
}
|
14
man/panel_space.Rd
Normal file
14
man/panel_space.Rd
Normal file
|
@ -0,0 +1,14 @@
|
|||
% Generated by roxygen2: do not edit by hand
|
||||
% Please edit documentation in R/app.R
|
||||
\name{panel_space}
|
||||
\alias{panel_space}
|
||||
\title{Wrapping nav_spacer to avoid errors on dependencies when packaging}
|
||||
\usage{
|
||||
panel_space()
|
||||
}
|
||||
\value{
|
||||
bslib object
|
||||
}
|
||||
\description{
|
||||
Wrapping nav_spacer to avoid errors on dependencies when packaging
|
||||
}
|
|
@ -19,7 +19,7 @@ regression_model(
|
|||
|
||||
\item{outcome.str}{Name of outcome variable. Character vector.}
|
||||
|
||||
\item{auto.mode}{Make assumptions on function dependent on outcome data format.}
|
||||
\item{auto.mode}{Make assumptions on function dependent on outcome data format. Overwrites other arguments.}
|
||||
|
||||
\item{formula.str}{Formula as string. Passed through 'glue::glue'. If given, 'outcome.str' and 'vars' are ignored. Optional.}
|
||||
|
||||
|
@ -41,12 +41,14 @@ gtsummary::trial |>
|
|||
gtsummary::trial |>
|
||||
regression_model(
|
||||
outcome.str = "age",
|
||||
auto.mode = FALSE,
|
||||
fun = "stats::lm",
|
||||
formula.str = "{outcome.str}~.",
|
||||
args.list = NULL
|
||||
)
|
||||
gtsummary::trial |> regression_model(
|
||||
outcome.str = "trt",
|
||||
auto.mode = FALSE,
|
||||
fun = "stats::glm",
|
||||
args.list = list(family = binomial(link = "logit"))
|
||||
)
|
||||
|
|
|
@ -25,7 +25,7 @@ gtsummary::trial |>
|
|||
outcome.str = "stage",
|
||||
fun = "MASS::polr"
|
||||
) |>
|
||||
regression_table(args.list = list(exponentiate = TRUE))
|
||||
regression_table(args.list = list("exponentiate" = TRUE))
|
||||
gtsummary::trial |>
|
||||
regression_model(
|
||||
outcome.str = "age",
|
||||
|
|
26
man/shiny_webResearch.Rd
Normal file
26
man/shiny_webResearch.Rd
Normal file
|
@ -0,0 +1,26 @@
|
|||
% Generated by roxygen2: do not edit by hand
|
||||
% Please edit documentation in R/app.R
|
||||
\name{shiny_webResearch}
|
||||
\alias{shiny_webResearch}
|
||||
\title{Test version of the shiny_cast function to launch the app with a data set in
|
||||
the environment.}
|
||||
\usage{
|
||||
shiny_webResearch(data = NULL, ...)
|
||||
}
|
||||
\arguments{
|
||||
\item{data}{optional data set to provide for analysis}
|
||||
|
||||
\item{...}{arguments passed on to \code{shiny::runApp()}}
|
||||
}
|
||||
\value{
|
||||
shiny app
|
||||
}
|
||||
\description{
|
||||
Test version of the shiny_cast function to launch the app with a data set in
|
||||
the environment.
|
||||
}
|
||||
\examples{
|
||||
\dontrun{
|
||||
mtcars |> shiny_webResearch(launch.browser = TRUE)
|
||||
}
|
||||
}
|
|
@ -1,18 +0,0 @@
|
|||
# Prep for shiny
|
||||
# system2("cat ./R/index_from_raw.R ./R/plot_index.R ./R/read_file.R > ./R/functions.R")
|
||||
|
||||
project.aid::merge_scripts(list.files("R/",full.names = TRUE),dest = here::here("app/functions.R"))
|
||||
|
||||
# Typical shiny
|
||||
shiny::runApp(appDir = here::here("app/"))
|
||||
shiny::runApp(appDir = here::here("app/"), launch.browser = TRUE)
|
||||
|
||||
project.aid::deploy_shiny(
|
||||
path="app/",
|
||||
account.name = "agdamsbo",
|
||||
name.app = "webResearch",
|
||||
name.token = "rsconnect_agdamsbo_token",
|
||||
name.secret = "rsconnect_agdamsbo_secret"
|
||||
)
|
||||
|
||||
|
Loading…
Add table
Reference in a new issue