From 91465cd1193400053a48cca196d3fd777183c82c Mon Sep 17 00:00:00 2001 From: Naeem Model Date: Mon, 24 Jul 2023 21:49:40 +0000 Subject: Adjust indent level and enforce 80-character line limit --- R/app.R | 6 +- R/server.R | 509 +++++++++++++++++++++++++++++++++---------------------------- R/ui.R | 327 +++++++++++++++++++++++---------------- 3 files changed, 476 insertions(+), 366 deletions(-) (limited to 'R') diff --git a/R/app.R b/R/app.R index 1bf3e93..feb052f 100644 --- a/R/app.R +++ b/R/app.R @@ -2,8 +2,8 @@ #' #' @export app <- function() { - if (!requireNamespace("shiny", quietly=TRUE)) - stop("The package 'shiny' must be installed to launch the Rnaught web application.") + if (!requireNamespace("shiny", quietly = TRUE)) + stop("The package 'shiny' must be installed to launch the Rnaught web application.") - shiny::shinyApp(ui(), server) + shiny::shinyApp(ui, server) } diff --git a/R/server.R b/R/server.R index e8d2970..ed5ecd7 100644 --- a/R/server.R +++ b/R/server.R @@ -1,263 +1,312 @@ #' @importFrom methods is #' @importFrom utils read.csv write.csv server <- function(input, output) { - reactive <- shiny::reactiveValues( - data_table=data.frame(Name=character(0), `Reporting Frequency`=character(0), `Case Counts`=numeric(0), check.names=FALSE), - est_table=data.frame(Dataset=character(0)), - estimators=list() - ) - - # Validate and add datasets when button is clicked. - # Also evaluate the new datasets on existing estimators. - shiny::observeEvent(input$addData, { - # Option 1: Manual entry. - if (input$dataInputMethod == 1) { - checks_passed <- TRUE - - # Ensure the dataset name is not blank. - if (grepl("^\\s*$", input$dataName)) { - output$dataNameWarn <- shiny::renderText("Error: The dataset name cannot be blank.") - checks_passed <- FALSE - } - # Ensure the dataset name is not a duplicate. - else if (input$dataName %in% reactive$data_table[,1]) { - output$dataNameWarn <- shiny::renderText("Error: There is already a dataset with the specified name.") - checks_passed <- FALSE - } - else - output$dataNameWarn <- shiny::renderText("") - - # Ensure the case counts consist only of non-negative integers, separated by commas. - counts <- as.numeric(unlist(strsplit(input$dataCounts, split=","))) - if (any(is.na(counts)) || any(counts <= 0) || any(counts %% 1 != 0)) { - output$dataCountsWarn <- shiny::renderText("Error: The list of case counts should only contain non-negative integers, separated by commas.") - checks_passed <- FALSE - } - # Ensure the case counts contain at least two entries. - else if (length(counts) < 2) { - output$dataCountsWarn <- shiny::renderText("Error: The list of case counts should contain at least two entries.") - checks_passed <- FALSE - } - else - output$dataCountsWarn <- shiny::renderText("") + reactive <- shiny::reactiveValues( + data_table = data.frame(Name = character(0), + `Reporting Frequency` = character(0), + `Case Counts` = numeric(0), check.names = FALSE), + est_table = data.frame(Dataset = character(0)), + estimators = list() + ) + + # Validate and add datasets when button is clicked. + # Also evaluate the new datasets on existing estimators. + shiny::observeEvent(input$addData, { + # Option 1: Manual entry. + if (input$dataInputMethod == 1) { + checks_passed <- TRUE + + # Ensure the dataset name is not blank. + if (grepl("^\\s*$", input$dataName)) { + output$dataNameWarn <- shiny::renderText( + "Error: The dataset name cannot be blank.") + checks_passed <- FALSE + } + # Ensure the dataset name is not a duplicate. + else if (input$dataName %in% reactive$data_table[,1]) { + output$dataNameWarn <- shiny::renderText( + "Error: There is already a dataset with the specified name.") + checks_passed <- FALSE + } + else + output$dataNameWarn <- shiny::renderText("") + + # Ensure the case counts consist only of positive integers, separated by + # commas. + counts <- as.numeric(unlist(strsplit(input$dataCounts, split = ","))) + if (any(is.na(counts)) || any(counts <= 0) || any(counts %% 1 != 0)) { + output$dataCountsWarn <- shiny::renderText("Error: The list of case + counts should only contain positive integers, separated by commas.") + checks_passed <- FALSE + } + # Ensure the case counts contain at least two entries. + else if (length(counts) < 2) { + output$dataCountsWarn <- shiny::renderText( + "Error: The list of case counts should contain at least two entries.") + checks_passed <- FALSE + } + else + output$dataCountsWarn <- shiny::renderText("") - if (checks_passed) - d <- data.frame(input$dataName, input$dataUnits, t(counts)) - } + if (checks_passed) + d <- data.frame(input$dataName, input$dataUnits, t(counts)) + } - else { - checks_passed <- FALSE - - # Option 2: Upload .csv - if (input$dataInputMethod == 2) - d <- try(read.csv(input$dataUpload$datapath, header=FALSE)) - # Option 3: Paste .csv - else - d <- try(read.csv(text=input$dataPaste, header=FALSE)) - - if (is(d, "try-error")) - output$dataCSVWarn <- shiny::renderText("Error reading file.") - else if (ncol(d) < 4 || anyNA(d[,1]) || anyNA(sapply(d[,3:4], as.numeric)) || !all(trimws(d[,2]) %in% c("Daily", "Weekly"))) - output$dataCSVWarn <- shiny::renderText("Error: The provided .csv file does not match the required format.") - else if (length(intersect(reactive$data_table[,1], d[,1])) > 0) - output$dataCSVWarn <- shiny::renderText("Error: The provided .csv file contains dataset names which already exist.") - else if (length(unique(d[,1])) != length(d[,1])) - output$dataCSVWarn <- shiny::renderText("Error: The provided .csv file contains duplicate dataset names.") - else { - output$dataCSVWarn <- shiny::renderText("") - checks_passed <- TRUE - } - } + else { + checks_passed <- FALSE - if (checks_passed) { - d[,3:ncol(d)] <- apply(d[,3:ncol(d)], 2, as.numeric) - d[,3] <- data.frame(I(lapply(split(d[,3:ncol(d)], 1:nrow(d)), function(x) x[!is.na(x)]))) - d <- d[,1:3] - d[,2] <- trimws(d[,2]) - colnames(d) <- c("Name", "Reporting Frequency", "Case Counts") - reactive$data_table <- rbind(reactive$data_table, d) - reactive$est_table <- update_est_row(input, output, d, reactive$estimators, reactive$est_table) - } - }) - - output$dataTable <- shiny::renderDataTable(reactive$data_table, escape=FALSE) - output$estTable <- shiny::renderDataTable(reactive$est_table, escape=FALSE) + # Option 2: Upload .csv + if (input$dataInputMethod == 2) + d <- try(read.csv(input$dataUpload$datapath, header = FALSE)) + # Option 3: Paste .csv + else + d <- try(read.csv(text = input$dataPaste, header = FALSE)) + + if (is(d, "try-error")) + output$dataCSVWarn <- shiny::renderText("Error reading file.") + else if (ncol(d) < 4 || anyNA(d[,1]) || anyNA(sapply(d[,3:4], as.numeric)) + || !all(trimws(d[,2]) %in% c("Daily", "Weekly"))) + output$dataCSVWarn <- shiny::renderText( + "Error: The provided .csv file does not match the required format.") + else if (length(intersect(reactive$data_table[,1], d[,1])) > 0) + output$dataCSVWarn <- shiny::renderText("Error: The provided .csv file + contains dataset names which already exist.") + else if (length(unique(d[,1])) != length(d[,1])) + output$dataCSVWarn <- shiny::renderText( + "Error: The provided .csv file contains duplicate dataset names.") + else { + output$dataCSVWarn <- shiny::renderText("") + checks_passed <- TRUE + } + } + + if (checks_passed) { + d[,3:ncol(d)] <- apply(d[,3:ncol(d)], 2, as.numeric) + d[,3] <- data.frame(I(lapply(split(d[,3:ncol(d)], 1:nrow(d)), + function(x) x[!is.na(x)]))) + d <- d[,1:3] + d[,2] <- trimws(d[,2]) + colnames(d) <- c("Name", "Reporting Frequency", "Case Counts") + reactive$data_table <- rbind(reactive$data_table, d) + reactive$est_table <- update_est_row(input, output, d, + reactive$estimators, reactive$est_table) + } + }) - # Download table of estimates as a .csv file. - output$downloadEst <- shiny::downloadHandler( - filename=function() { paste0("Rnaught-", Sys.Date(), ".csv") }, - content=function(file) { write.csv(reactive$est_table, file) } - ) - - shiny::observeEvent(input$addWP, { - if (input$serialWPKnown == 1) { - serial <- validate_serial(input, output, "serialWPInput", "serialWPWarn") - if (!is.na(serial)) { - reactive$estimators[[length(reactive$estimators)+1]] <- list(method="WP", mu=serial, search=list(B=100, shape.max=10, scale.max=10), mu_units=input$serialWPUnits) - reactive$est_table <- update_est_col(input, output, reactive$data_table, reactive$estimators[[length(reactive$estimators)]], reactive$est_table) - } - } - else { - checks_passed <- TRUE - - grid_length <- as.numeric(input$gridLengthInput) - max_shape <- as.numeric(input$gridShapeInput) - max_scale <- as.numeric(input$gridScaleInput) - - if (is.na(grid_length) || grid_length <= 0 || grid_length %% 1 != 0) { - output$gridLengthWarn <- shiny::renderText("Error: The grid size must be a positive integer.") - output$gridShapeWarn <- shiny::renderText("") - output$gridScaleWarn <- shiny::renderText("") - checks_passed <- FALSE - } - else { - output$gridLengthWarn <- shiny::renderText("") - - if (is.na(max_shape) || max_shape < 1 / grid_length) { - output$gridShapeWarn <- shiny::renderText("Error: The maximum shape must be at least the reciprocal of the grid length.") - checks_passed <- FALSE - } - else - output$gridShapeWarn <- shiny::renderText("") - - if (is.na(max_scale) || max_scale < 1 / grid_length) { - output$gridShapeWarn <- shiny::renderText("Error: The maximum scale must be at least the reciprocal of the grid length.") - checks_passed <- FALSE - } - else - output$gridScaleWarn <- shiny::renderText("") - } - - if (checks_passed) { - reactive$estimators[[length(reactive$estimators)+1]] <- list(method="WP", mu=NA, search=list(B=grid_length, shape.max=max_shape, scale.max=max_scale), mu_units=input$serialWPUnits) - reactive$est_table <- update_est_col(input, output, reactive$data_table, reactive$estimators[[length(reactive$estimators)]], reactive$est_table) - } - } - }) - - shiny::observeEvent(input$addseqB, { - serial <- validate_serial(input, output, "serialseqBInput", "serialseqBWarn") - checks_passed <- !is.na(serial) - - kappa <- as.numeric(input$kappaInput) - if (is.na(kappa) || kappa <= 0) { - output$kappaWarn <- shiny::renderText("Error: The maximum value must be a positive number.") - checks_passed <- FALSE + output$dataTable <- shiny::renderDataTable(reactive$data_table, + escape = FALSE) + output$estTable <- shiny::renderDataTable(reactive$est_table, + escape = FALSE) + + # Download table of estimates as a .csv file. + output$downloadEst <- shiny::downloadHandler( + filename = function() { paste0("Rnaught-", Sys.Date(), ".csv") }, + content = function(file) { write.csv(reactive$est_table, file) } + ) + + shiny::observeEvent(input$addWP, { + if (input$serialWPKnown == 1) { + serial <- validate_serial(input, output, "serialWPInput", "serialWPWarn") + if (!is.na(serial)) { + reactive$estimators[[length(reactive$estimators) + 1]] <- list( + method = "WP", mu = serial, mu_units = input$serialWPUnits, + search = list(B = 100, shape.max = 10, scale.max = 10)) + reactive$est_table <- update_est_col(input, output, reactive$data_table, + reactive$estimators[[length(reactive$estimators)]], + reactive$est_table) + } + } + else { + checks_passed <- TRUE + + grid_length <- as.numeric(input$gridLengthInput) + max_shape <- as.numeric(input$gridShapeInput) + max_scale <- as.numeric(input$gridScaleInput) + + if (is.na(grid_length) || grid_length <= 0 || grid_length %% 1 != 0) { + output$gridLengthWarn <- shiny::renderText( + "Error: The grid size must be a positive integer.") + output$gridShapeWarn <- shiny::renderText("") + output$gridScaleWarn <- shiny::renderText("") + checks_passed <- FALSE + } + else { + output$gridLengthWarn <- shiny::renderText("") + + if (is.na(max_shape) || max_shape < 1 / grid_length) { + output$gridShapeWarn <- shiny::renderText("Error: The maximum shape + must be at least the reciprocal of the grid length.") + checks_passed <- FALSE } else - output$kappaWarn <- shiny::renderText("") - - if (checks_passed) { - reactive$estimators[[length(reactive$estimators)+1]] <- list(method="seqB", mu=serial, kappa=kappa, mu_units=input$serialseqBUnits) - reactive$est_table <- update_est_col(input, output, reactive$data_table, reactive$estimators[[length(reactive$estimators)]], reactive$est_table) - } - }) + output$gridShapeWarn <- shiny::renderText("") - shiny::observeEvent(input$addID, { - serial <- validate_serial(input, output, "serialIDInput", "serialIDWarn") - if (!is.na(serial)) { - reactive$estimators[[length(reactive$estimators)+1]] <- list(method="ID", mu=serial, mu_units=input$serialIDUnits) - reactive$est_table <- update_est_col(input, output, reactive$data_table, reactive$estimators[[length(reactive$estimators)]], reactive$est_table) + if (is.na(max_scale) || max_scale < 1 / grid_length) { + output$gridShapeWarn <- shiny::renderText("Error: The maximum scale + must be at least the reciprocal of the grid length.") + checks_passed <- FALSE } - }) + else + output$gridScaleWarn <- shiny::renderText("") + } - shiny::observeEvent(input$addIDEA, { - serial <- validate_serial(input, output, "serialIDEAInput", "serialIDEAWarn") - if (!is.na(serial)) { - reactive$estimators[[length(reactive$estimators)+1]] <- list(method="IDEA", mu=serial, mu_units=input$serialIDEAUnits) - reactive$est_table <- update_est_col(input, output, reactive$data_table, reactive$estimators[[length(reactive$estimators)]], reactive$est_table) - } - }) -} + if (checks_passed) { + reactive$estimators[[length(reactive$estimators) + 1]] <- list( + method = "WP", mu = NA, mu_units = input$serialWPUnits, + search = list(B = grid_length, shape.max = max_shape, + scale.max = max_scale)) + reactive$est_table <- update_est_col(input, output, reactive$data_table, + reactive$estimators[[length(reactive$estimators)]], + reactive$est_table) + } + } + }) -validate_serial <- function(input, output, serialInputId, serialWarnId) { - serial <- as.numeric(input[[serialInputId]]) - if (is.na(serial) || serial <= 0) { - output[[serialWarnId]] <- shiny::renderText("Error: The mean serial interval should be a non-negative number.") - serial <- NA + shiny::observeEvent(input$addseqB, { + serial <- validate_serial(input, output, "serialseqBInput", + "serialseqBWarn") + checks_passed <- !is.na(serial) + + kappa <- as.numeric(input$kappaInput) + if (is.na(kappa) || kappa <= 0) { + output$kappaWarn <- shiny::renderText( + "Error: The maximum value must be a positive number.") + checks_passed <- FALSE } else - output[[serialWarnId]] <- shiny::renderText("") # Clear warning text. - - return(serial) + output$kappaWarn <- shiny::renderText("") + + if (checks_passed) { + reactive$estimators[[length(reactive$estimators) + 1]] <- list( + method="seqB", mu = serial, kappa = kappa, + mu_units = input$serialseqBUnits) + reactive$est_table <- update_est_col(input, output, reactive$data_table, + reactive$estimators[[length(reactive$estimators)]], reactive$est_table) + } + }) + + shiny::observeEvent(input$addID, { + serial <- validate_serial(input, output, "serialIDInput", "serialIDWarn") + if (!is.na(serial)) { + reactive$estimators[[length(reactive$estimators) + 1]] <- list( + method = "ID", mu = serial, mu_units = input$serialIDUnits) + reactive$est_table <- update_est_col(input, output, reactive$data_table, + reactive$estimators[[length(reactive$estimators)]], reactive$est_table) + } + }) + + shiny::observeEvent(input$addIDEA, { + serial <- validate_serial(input, output, "serialIDEAInput", + "serialIDEAWarn") + if (!is.na(serial)) { + reactive$estimators[[length(reactive$estimators) + 1]] <- list( + method = "IDEA", mu = serial, mu_units = input$serialIDEAUnits) + reactive$est_table <- update_est_col(input, output, reactive$data_table, + reactive$estimators[[length(reactive$estimators)]], reactive$est_table) + } + }) } +validate_serial <- function(input, output, serialInputId, serialWarnId) { + serial <- as.numeric(input[[serialInputId]]) + if (is.na(serial) || serial <= 0) { + output[[serialWarnId]] <- shiny::renderText( + "Error: The mean serial interval should be a positive number.") + serial <- NA + } + else + output[[serialWarnId]] <- shiny::renderText("") # Clear warning text. + + return(serial) +} + +# Create a new column in the estimator table when a new estimator is added. update_est_col <- function(input, output, datasets, estimator, est_table) { - if (nrow(datasets) == 0) - new_est_table <- data.frame(matrix(nrow=0, ncol=ncol(est_table)+1)) - else { - estimates <- rep(NA, nrow(datasets)) + if (nrow(datasets) == 0) + new_est_table <- data.frame(matrix(nrow = 0, ncol = ncol(est_table) + 1)) + else { + estimates <- rep(NA, nrow(datasets)) for (row in 1:nrow(datasets)) - estimates[row] <- eval_estimator(input, output, estimator, datasets[row,]) + estimates[row] <- eval_estimator(input, output, estimator, datasets[row,]) - if (nrow(est_table) == 0) - new_est_table <- cbind(datasets[,1], estimates) - else - new_est_table <- cbind(est_table, estimates) - } + if (nrow(est_table) == 0) + new_est_table <- cbind(datasets[,1], estimates) + else + new_est_table <- cbind(est_table, estimates) + } - colnames(new_est_table) <- c(colnames(est_table), shiny::HTML(paste0(estimator$method, "
(μ = ", estimator$mu, " ", tolower(estimator$mu_units), ")"))) - return(new_est_table) + colnames(new_est_table) <- c(colnames(est_table), shiny::HTML( + paste0(estimator$method, "
(μ = ", estimator$mu, " ", + tolower(estimator$mu_units), ")"))) + + return(new_est_table) } - + +# Create a new row in the estimator table when new datasets are added. update_est_row <- function(input, output, datasets, estimators, est_table) { - if (length(estimators) == 0) { - if (nrow(est_table) == 0) - new_est_table <- data.frame(datasets[,1]) - else - new_est_table <- data.frame(c(est_table[,1], datasets[,1])) + if (length(estimators) == 0) { + if (nrow(est_table) == 0) + new_est_table <- data.frame(datasets[,1]) + else + new_est_table <- data.frame(c(est_table[,1], datasets[,1])) - colnames(new_est_table) <- colnames(est_table) - } - else { - new_est_table <- data.frame(matrix(nrow=nrow(datasets), ncol=length(estimators))) + colnames(new_est_table) <- colnames(est_table) + } + else { + new_est_table <- data.frame(matrix(nrow = nrow(datasets), + ncol = length(estimators))) - for (row in 1:nrow(datasets)) - for (col in 1:length(estimators)) - new_est_table[row, col] <- eval_estimator(input, output, estimators[[col]], datasets[row,]) + for (row in 1:nrow(datasets)) + for (col in 1:length(estimators)) + new_est_table[row, col] <- eval_estimator(input, output, + estimators[[col]], datasets[row,]) - new_est_table <- cbind(datasets[,1], new_est_table) - colnames(new_est_table) <- colnames(est_table) - new_est_table <- rbind(est_table, new_est_table) - } + new_est_table <- cbind(datasets[,1], new_est_table) + colnames(new_est_table) <- colnames(est_table) + new_est_table <- rbind(est_table, new_est_table) + } - return(new_est_table) + return(new_est_table) } +# Evaluate an estimator on a given dataset. eval_estimator <- function(input, output, estimator, dataset) { - # Adjust serial interval to match time unit of case counts. - serial <- estimator$mu - if (estimator$mu_units == "Days" && dataset[2] == "Weekly") - serial <- serial / 7 - else if (estimator$mu_units == "Weeks" && dataset[2] == "Daily") - serial <- serial * 7 - - # White and Panago - if (estimator$method == "WP") { - estimate <- WP(unlist(dataset[3]), mu=serial, search=estimator$search) - - if (!is.na(estimator$mu)) - estimate <- round(estimate$Rhat, 2) - # Display the estimated mean of the serial distribution if mu was not specified. - else { - if (dataset[2] == "Daily") - mu_units <- "days" - else - mu_units <- "weeks" - MSI <- sum(estimate$SD$supp * estimate$SD$pmf) - estimate <- shiny::HTML(paste0(round(estimate$Rhat, 2), "
(μ = ", round(MSI, 2), " ", mu_units, ")")) - } + # Adjust serial interval to match time unit of case counts. + serial <- estimator$mu + if (estimator$mu_units == "Days" && dataset[2] == "Weekly") + serial <- serial / 7 + else if (estimator$mu_units == "Weeks" && dataset[2] == "Daily") + serial <- serial * 7 + + # White and Panago + if (estimator$method == "WP") { + estimate <- WP(unlist(dataset[3]), mu = serial, search = estimator$search) + + if (!is.na(estimator$mu)) + estimate <- round(estimate$Rhat, 2) + # Display the estimated mean of the serial distribution if mu was not + # specified. + else { + if (dataset[2] == "Daily") + mu_units <- "days" + else + mu_units <- "weeks" + MSI <- sum(estimate$SD$supp * estimate$SD$pmf) + estimate <- shiny::HTML(paste0(round(estimate$Rhat, 2), "
(μ = ", + round(MSI, 2), " ", mu_units, ")")) } - # Sequential Bayes - else if (estimator$method == "seqB") - estimate <- round(seqB(unlist(dataset[3]), mu=serial, kappa=estimator$kappa)$Rhat, 2) - # Incidence Decay - else if (estimator$method == "ID") - estimate <- round(ID(unlist(dataset[3]), mu=serial), 2) - # Incidence Decay with Exponential Adjustement - else if (estimator$method == "IDEA") - estimate <- round(IDEA(unlist(dataset[3]), mu=serial), 2) - - return(estimate) + } + # Sequential Bayes + else if (estimator$method == "seqB") + estimate <- round(seqB(unlist(dataset[3]), mu = serial, + kappa = estimator$kappa)$Rhat, 2) + # Incidence Decay + else if (estimator$method == "ID") + estimate <- round(ID(unlist(dataset[3]), mu = serial), 2) + # Incidence Decay with Exponential Adjustement + else if (estimator$method == "IDEA") + estimate <- round(IDEA(unlist(dataset[3]), mu = serial), 2) + + return(estimate) } diff --git a/R/ui.R b/R/ui.R index d6102f9..4e4a500 100644 --- a/R/ui.R +++ b/R/ui.R @@ -1,136 +1,197 @@ -ui <- function() { - shiny::fluidPage( - # Title. - shiny::titlePanel(shiny::HTML(paste0("Rnaught: An Estimation Suite for R", shiny::tags$sub("0")))), - - # Sidebar layout. - shiny::sidebarLayout( - # Sidebar. Hidden if the 'About' tab is selected. - shiny::conditionalPanel(condition="input.tabset != 'About'", - shiny::sidebarPanel(id="sidebar", - # Data tab sidebar. - shiny::conditionalPanel(condition="input.tabset == 'Data'", - shiny::h3("Enter data"), - # Data input method selection. - shiny::radioButtons(inputId="dataInputMethod", label="", choices=list("Manually"=1, "Upload a .csv file"=2, "Paste a .csv file"=3)), - # Option 1: Manual entry. - shiny::conditionalPanel(condition="input.dataInputMethod == '1'", - shiny::textInput(inputId="dataName", label="Dataset name"), - shiny::span(shiny::textOutput(outputId="dataNameWarn"), style="color: red;"), - shiny::fluidRow( - shiny::column(8, shiny::textInput(inputId="dataCounts", label=shiny::HTML(paste0( - "Case counts", shiny::tags$sup("[?]", title="Enter as a comma-separated list of positive integers, with at least two entries. Ex: 1,1,2,3,5,8")))) - ), - shiny::column(4, shiny::selectInput(inputId="dataUnits", label="Reporting frequency", choices=list("Daily", "Weekly"))) - ), - shiny::span(shiny::textOutput(outputId="dataCountsWarn"), style="color: red;") - ), - # Option 2: Upload .csv file. - shiny::conditionalPanel(condition="input.dataInputMethod == '2'", - shiny::fileInput(inputId="dataUpload", label="", accept=c("text/csv", "text/comma-separated-values,text/plain", ".csv")), - ), - # Option 3: Paste .csv file. - shiny::conditionalPanel(condition="input.dataInputMethod == '3'", - shiny::textAreaInput(inputId="dataPaste", label="", rows=8, resize="none"), - ), - # Warning text for .csv upload / paste. - shiny::conditionalPanel(condition="['2', '3'].includes(input.dataInputMethod)", - shiny::span(shiny::textOutput(outputId="dataCSVWarn"), style="color: red;"), - ), - # Button to add data. - shiny::actionButton(inputId="addData", label="Add"), - ), - # Estimators tab sidebar (collapsable entries). - shiny::conditionalPanel(condition="input.tabset == 'Estimators'", - shiny::h3("Estimators"), - # WHITE & PANAGO (WP). - shiny::tags$details( - shiny::tags$summary(shiny::h4("White & Panago (WP)")), - shiny::p("This is a description of the method."), - shiny::br(), - shiny::radioButtons(inputId="serialWPKnown", label="Is the mean serial interval known?", inline=TRUE, choices=list("Yes"=1, "No"=2)), - # Known serial interval. - shiny::conditionalPanel(condition="input.serialWPKnown == '1'", - shiny::fluidRow( - shiny::column(8, shiny::textInput(inputId="serialWPInput", label="Mean Serial Interval")), - shiny::column(4, shiny::selectInput(inputId="serialWPUnits", label="Time units", choices=list("Days", "Weeks"))) - ), - shiny::span(shiny::textOutput(outputId="serialWPWarn"), style="color: red;") - ), - # Unknown serial interval. - shiny::conditionalPanel(condition="input.serialWPKnown == '2'", - shiny::h5("Grid Search Parameters"), - shiny::fluidRow( - shiny::column(4, shiny::textInput(inputId="gridLengthInput", label="Grid length", value="100")), - shiny::column(4, shiny::textInput(inputId="gridShapeInput", label="Max. shape", value="10")), - shiny::column(4, shiny::textInput(inputId="gridScaleInput", label="Max. scale", value="10")) - ), - shiny::fluidRow( - shiny::column(4, shiny::span(shiny::textOutput(outputId="gridLengthWarn"), style="color: red;")), - shiny::column(4, shiny::span(shiny::textOutput(outputId="gridShapeWarn"), style="color: red;")), - shiny::column(4, shiny::span(shiny::textOutput(outputId="gridScaleWarn"), style="color: red;")) - ) - ), - shiny::actionButton(inputId="addWP", label="Add") - ), - # SEQUENTIAL BAYES (seqB). - shiny::tags$details( - shiny::tags$summary(shiny::h4("Sequential Bayes (seqB)")), - shiny::p("This is a description of the method."), - shiny::br(), - shiny::fluidRow( - shiny::column(8, shiny::textInput(inputId="serialseqBInput", label="Mean Serial Interval")), - shiny::column(4, shiny::selectInput(inputId="serialseqBUnits", label="Time units", choices=list("Days", "Weeks"))) - ), - shiny::span(shiny::textOutput(outputId="serialseqBWarn"), style="color: red;"), - shiny::textInput(inputId="kappaInput", label=shiny::HTML(paste0("Maximum value of the uniform prior", - shiny::tags$sup("[?]", title="This describes the prior belief of R0, and should be set to a higher value if R0 is believed to be larger. (Default: 20)"))), - value="20" - ), - shiny::span(shiny::textOutput(outputId="kappaWarn"), style="color: red;"), - shiny::actionButton(inputId="addseqB", label="Add") - ), - # INCIDENCE DECAY (ID). - shiny::tags$details( - shiny::tags$summary(shiny::h4("Incidence Decay (ID)")), - shiny::p("This is a description of the method."), - shiny::br(), - shiny::fluidRow( - shiny::column(8, shiny::textInput(inputId="serialIDInput", label="Mean Serial Interval")), - shiny::column(4, shiny::selectInput(inputId="serialIDUnits", label="Time units", choices=list("Days", "Weeks"))) - ), - shiny::span(shiny::textOutput(outputId="serialIDWarn"), style="color: red;"), - shiny::actionButton(inputId="addID", label="Add") - ), - # INCIDENCE DECAY & EXPONENTIAL ADJUSTEMENT (IDEA). - shiny::tags$details( - shiny::tags$summary(shiny::h4("Incidence Decay and Exponential Adjustement (IDEA)")), - shiny::p("This is a description of the method."), - shiny::br(), - shiny::fluidRow( - shiny::column(8, shiny::textInput(inputId="serialIDEAInput", label="Mean Serial Interval")), - shiny::column(4, shiny::selectInput(inputId="serialIDEAUnits", label="Time units", choices=list("Days", "Weeks"))) - ), - shiny::span(shiny::textOutput(outputId="serialIDEAWarn"), style="color: red;"), - shiny::actionButton(inputId="addIDEA", label="Add") - ), - shiny::tags$style(type="text/css", "summary { display: list-item; cursor: pointer; }"), - shiny::tags$style(type="text/css", "summary h4 { display: inline; }") - ) - ) +ui <- shiny::fluidPage( + # Title. + shiny::titlePanel(shiny::HTML( + paste0("Rnaught: An Estimation Suite for R", shiny::tags$sub("0")))), + # Sidebar layout. + shiny::sidebarLayout( + # Sidebar. Hidden if the 'About' tab is selected. + shiny::conditionalPanel(condition = "input.tabset != 'About'", + shiny::sidebarPanel(id = "sidebar", + # Data tab sidebar. + shiny::conditionalPanel(condition = "input.tabset == 'Data'", + shiny::h3("Enter data"), + # Data input method selection. + shiny::radioButtons(inputId = "dataInputMethod", label = "", + choices=list("Manually" = 1, "Upload a .csv file" = 2, + "Paste a .csv file" = 3)), + # Option 1: Manual entry. + shiny::conditionalPanel(condition = "input.dataInputMethod == '1'", + shiny::textInput(inputId = "dataName", label = "Dataset name"), + shiny::span(shiny::textOutput(outputId = "dataNameWarn"), + style = "color: red;"), + shiny::fluidRow( + shiny::column(8, + shiny::textInput(inputId = "dataCounts", label = shiny::HTML( + paste0("Case counts", shiny::tags$sup("[?]", + title = "Enter as a comma-separated list of positive + integers, with at least two entries. + Example: 1,1,2,3,5,8"))))), + shiny::column(4, + shiny::selectInput(inputId = "dataUnits", + label = "Reporting frequency", + choices = list("Daily", "Weekly"))) ), - # Main panel. - shiny::mainPanel(id="main", - shiny::tabsetPanel(id="tabset", type="tabs", - shiny::tabPanel("About", shiny::br(), "Hello"), - shiny::tabPanel("Data", shiny::br(), shiny::dataTableOutput(outputId="dataTable"), shiny::tags$style(type="text/css", "#dataTable tfoot { display:none; }")), - shiny::tabPanel("Estimators", shiny::br(), - shiny::dataTableOutput(outputId="estTable"), - shiny::tags$style(type="text/css", "#estTable tfoot { display:none; }"), - shiny::downloadButton(outputId="downloadEst", label="Download table as .csv") - ) - ) - ) + shiny::span(shiny::textOutput(outputId = "dataCountsWarn"), + style = "color: red;") + ), + # Option 2: Upload .csv file. + shiny::conditionalPanel(condition = "input.dataInputMethod == '2'", + shiny::fileInput(inputId = "dataUpload", label = "", + accept = c("text/csv", "text/comma-separated-values,text/plain", + ".csv")), + ), + # Option 3: Paste .csv file. + shiny::conditionalPanel(condition = "input.dataInputMethod == '3'", + shiny::textAreaInput(inputId = "dataPaste", label = "", + rows = 8, resize = "none"), + ), + # Warning text for .csv upload / paste. + shiny::conditionalPanel( + condition = "['2', '3'].includes(input.dataInputMethod)", + shiny::span(shiny::textOutput(outputId = "dataCSVWarn"), + style = "color: red;"), + ), + # Button to add data. + shiny::actionButton(inputId = "addData", label = "Add"), + ), + # Estimators tab sidebar (collapsable entries). + shiny::conditionalPanel(condition = "input.tabset == 'Estimators'", + shiny::h3("Estimators"), + # WHITE & PANAGO (WP). + shiny::tags$details( + shiny::tags$summary(shiny::h4("White & Panago (WP)")), + shiny::p("This is a description of the method."), + shiny::br(), + shiny::radioButtons(inputId = "serialWPKnown", + label = "Is the mean serial interval known?", + inline = TRUE, + choices = list("Yes" = 1, "No" = 2)), + # Known serial interval. + shiny::conditionalPanel(condition = "input.serialWPKnown == '1'", + shiny::fluidRow( + shiny::column(8, + shiny::textInput(inputId = "serialWPInput", + label = "Mean Serial Interval")), + shiny::column(4, + shiny::selectInput(inputId = "serialWPUnits", + label = "Time units", + choices = list("Days", "Weeks"))) + ), + shiny::span(shiny::textOutput(outputId = "serialWPWarn"), + style = "color: red;") + ), + # Unknown serial interval. + shiny::conditionalPanel(condition = "input.serialWPKnown == '2'", + shiny::h5("Grid Search Parameters"), + shiny::fluidRow( + shiny::column(4, + shiny::textInput(inputId = "gridLengthInput", + label = "Grid length", value = "100")), + shiny::column(4, + shiny::textInput(inputId = "gridShapeInput", + label = "Max. shape", value = "10")), + shiny::column(4, + shiny::textInput(inputId = "gridScaleInput", + label = "Max. scale", value = "10")) + ), + shiny::fluidRow( + shiny::column(4, + shiny::span(shiny::textOutput(outputId = "gridLengthWarn"), + style = "color: red;")), + shiny::column(4, + shiny::span(shiny::textOutput(outputId = "gridShapeWarn"), + style = "color: red;")), + shiny::column(4, + shiny::span(shiny::textOutput(outputId = "gridScaleWarn"), + style = "color: red;")) + ) + ), + shiny::actionButton(inputId = "addWP", label = "Add") + ), + # SEQUENTIAL BAYES (seqB). + shiny::tags$details( + shiny::tags$summary(shiny::h4("Sequential Bayes (seqB)")), + shiny::p("This is a description of the method."), + shiny::br(), + shiny::fluidRow( + shiny::column(8, + shiny::textInput(inputId = "serialseqBInput", + label = "Mean Serial Interval")), + shiny::column(4, + shiny::selectInput(inputId = "serialseqBUnits", + label = "Time units", + choices = list("Days", "Weeks"))) + ), + shiny::span(shiny::textOutput(outputId = "serialseqBWarn"), + style = "color: red;"), + shiny::textInput(inputId = "kappaInput", label = shiny::HTML( + paste0("Maximum value", shiny::tags$sup("[?]", + title = "This describes the prior belief of R0, and should + be set to a higher value if R0 is believed to be + larger. (Default: 20)"))), value = "20"), + shiny::span(shiny::textOutput(outputId = "kappaWarn"), + style = "color: red;"), + shiny::actionButton(inputId = "addseqB", label = "Add") + ), + # INCIDENCE DECAY (ID). + shiny::tags$details( + shiny::tags$summary(shiny::h4("Incidence Decay (ID)")), + shiny::p("This is a description of the method."), + shiny::br(), + shiny::fluidRow( + shiny::column(8, + shiny::textInput(inputId = "serialIDInput", + label = "Mean Serial Interval")), + shiny::column(4, + shiny::selectInput(inputId = "serialIDUnits", + label = "Time units", + choices = list("Days", "Weeks"))) + ), + shiny::span(shiny::textOutput(outputId = "serialIDWarn"), + style = "color: red;"), + shiny::actionButton(inputId = "addID", label = "Add") + ), + # INCIDENCE DECAY & EXPONENTIAL ADJUSTEMENT (IDEA). + shiny::tags$details( + shiny::tags$summary( + shiny::h4("Incidence Decay and Exponential Adjustement (IDEA)")), + shiny::p("This is a description of the method."), + shiny::br(), + shiny::fluidRow( + shiny::column(8, + shiny::textInput(inputId = "serialIDEAInput", + label = "Mean Serial Interval")), + shiny::column(4, + shiny::selectInput(inputId = "serialIDEAUnits", + label = "Time units", + choices = list("Days", "Weeks"))) + ), + shiny::span(shiny::textOutput(outputId = "serialIDEAWarn"), + style = "color: red;"), + shiny::actionButton(inputId = "addIDEA", label = "Add") + ), + shiny::tags$style(type = "text/css", + "summary { display: list-item; cursor: pointer; }"), + shiny::tags$style(type = "text/css", + "summary h4 { display: inline; }") ) + ) + ), + # Main panel. + shiny::mainPanel(id = "main", + shiny::tabsetPanel(id = "tabset", type = "tabs", + shiny::tabPanel("About", shiny::br(), "Hello"), + shiny::tabPanel("Data", shiny::br(), + shiny::dataTableOutput(outputId = "dataTable"), + shiny::tags$style(type = "text/css", + "#dataTable tfoot { display:none; }")), + shiny::tabPanel("Estimators", shiny::br(), + shiny::dataTableOutput(outputId = "estTable"), + shiny::tags$style(type = "text/css", + "#estTable tfoot { display:none; }"), + shiny::downloadButton(outputId = "downloadEst", + label = "Download table as .csv")) + ) ) -} + ) +) -- cgit v1.2.3