From 713ee3c827de6e42b16a3b42438ac59344188d84 Mon Sep 17 00:00:00 2001 From: Nathan Hall Date: Tue, 1 Oct 2024 13:54:51 -0400 Subject: [PATCH 1/6] adding plots to db and cohort comparison adding scatterplots to characterization db and cohort compare tabs to address #294 --- .gitignore | 1 + R/characterization-cohorts.R | 169 +++++++++++++++++++-- R/characterization-database.R | 271 +++++++++++++++++++++++++++++++++- 3 files changed, 427 insertions(+), 14 deletions(-) diff --git a/.gitignore b/.gitignore index f6a14aa3..559ca9b5 100644 --- a/.gitignore +++ b/.gitignore @@ -5,3 +5,4 @@ /.idea/ rsconnect/rconnect.jnj.com/NHall6/phevaluator_v01.dcf errorReportSql.txt +tests/testthat/Rplots.pdf diff --git a/R/characterization-cohorts.R b/R/characterization-cohorts.R index 20ab24c6..aad9cb00 100644 --- a/R/characterization-cohorts.R +++ b/R/characterization-cohorts.R @@ -49,7 +49,20 @@ characterizationCohortComparisonViewer <- function(id) { ), shiny::tabPanel( title = 'Binary', - resultTableViewer(id = ns('mainTable'), boxTitle = 'Binary') + shiny::tabsetPanel( + type = 'pills', + id = ns('binaryPanel'), + shiny::tabPanel( + title = "Table", + resultTableViewer(id = ns('mainTable'), boxTitle = 'Binary') + ), + shiny::tabPanel( + title = "Plot", + shinycssloaders::withSpinner( + plotly::plotlyOutput(ns('scatterPlot')) + ) + ) + ) ), shiny::tabPanel( title = 'Continuous', @@ -281,9 +294,80 @@ characterizationCohortComparisonServer <- function( elementId = session$ns('count-table-filter') ), elementId = session$ns('count-table-filter') - )} + ) + + } + + #scatterplots + + plotDf <- shiny::reactive({ + + # Get the filtered and processed plot data + plotData <- resultTable %>% + replace(is.na(.), 0) %>% + dplyr::mutate(domain = dplyr::case_when( + grepl("condition_", covariateName) | sub("\\s.*", "", covariateName) == "condition" ~ "Condition", + grepl("drug_", covariateName) | sub("\\s.*", "", covariateName) == "drug" ~ "Drug", + grepl("procedure_", covariateName) | sub("\\s.*", "", covariateName) == "procedure" ~ "Procedure", + grepl("measurement_", covariateName) | sub("\\s.*", "", covariateName) == "measurement" ~ "Measurement", + grepl("observation_", covariateName) | sub("\\s.*", "", covariateName) == "observation" ~ "Observation", + grepl("device_", covariateName) | sub("\\s.*", "", covariateName) == "device" ~ "Device", + grepl("cohort_", covariateName) | sub("\\s.*", "", covariateName) == "cohort" ~ "Cohort", + grepl("visit_", covariateName) | sub("\\s.*", "", covariateName) == "visit" ~ "Visit", + .default = "Demographic" + )) + + # Create hover text for plotly + plotData$hoverText <- paste( + "Covariate Name:", plotData$covariateName, + "
", "Target", ":", scales::percent(plotData$averageValue_1), + "
", "Comparator", ":", scales::percent(plotData$averageValue_2) + ) + + #removing negatives, which come from "< min threshold" + plotData$averageValue_1[plotData$averageValue_1 < 0] <- 0 + plotData$averageValue_2[plotData$averageValue_2 < 0] <- 0 + + return(plotData) + + }) + + shiny::observe({ + output$scatterPlot <- plotly::renderPlotly({ + + plotData <- plotDf() + + # Create the scatter plot with the diagonal line (x = y) + p <- ggplot2::ggplot(plotData, ggplot2::aes( x = .data$averageValue_1, + y = .data$averageValue_2, + color = .data$domain, + text = .data$hoverText)) + # Use hoverText for hover labels + ggplot2::geom_point(size = 2) + # Smaller point size + ggplot2::geom_abline(slope = 1, intercept = 0, linetype = "dashed", color = "black") + # Diagonal x=y line in black + ggplot2::labs( + x = paste0("Target", " %"), + y = paste0("Comparator", " %"), + color = "Domain", + title = paste0("Database: ", names(inputVals()$databaseIds)[input$databaseId == inputVals()$databaseIds]) + ) + + ggplot2::theme_minimal() + # Optional: use a clean theme + ggplot2::theme( + plot.title = ggplot2::element_text(margin = ggplot2::margin(b = 10), hjust = 0.5, size = 25, face="bold"), + legend.position = "right", # Position legend as needed + axis.title = ggplot2::element_text(size = 12), # Adjust axis title size + axis.text = ggplot2::element_text(size = 10) # Adjust axis text size + ) + + ggplot2::scale_x_continuous(labels = scales::percent_format()) + # Format x-axis as percentage + ggplot2::scale_y_continuous(labels = scales::percent_format()) # Format y-axis as percentage + + # Convert to a plotly object for interactivity + plotly::ggplotly(p, tooltip = "text") # Use the custom hover text + }) + }) }) + + return(invisible(NULL)) @@ -776,9 +860,9 @@ characterizatonGetCohortData <- function( return(NULL) } - shiny::withProgress(message = 'characterizatonGetCohortData', value = 0, { - - shiny::incProgress(1/4, detail = paste("Setting types")) + # shiny::withProgress(message = 'characterizatonGetCohortData', value = 0, { + # + # shiny::incProgress(1/4, detail = paste("Setting types")) types <- data.frame( type = 1:(length(targetIds)*length(databaseIds)), @@ -786,7 +870,7 @@ characterizatonGetCohortData <- function( databaseId = rep(databaseIds, length(targetIds)) ) - shiny::incProgress(2/4, detail = paste("Extracting data")) + # shiny::incProgress(2/4, detail = paste("Extracting data")) sql <- "select ref.covariate_name, s.min_prior_observation, @@ -820,8 +904,8 @@ characterizatonGetCohortData <- function( min_threshold = minThreshold ) end <- Sys.time() - start - shiny::incProgress(3/4, detail = paste("Extracted data")) - message(paste0('Extracting ', nrow(res) ,' characterization cohort rows took: ', round(end, digits = 2), ' ', units(end))) + # shiny::incProgress(3/4, detail = paste("Extracted data")) + # message(paste0('Extracting ', nrow(res) ,' characterization cohort rows took: ', round(end, digits = 2), ' ', units(end))) # add the first/section type res <- merge(res, types, by = c('cohortDefinitionId','databaseId')) @@ -862,11 +946,12 @@ characterizatonGetCohortData <- function( result <- result %>% dplyr::select(-"firstVar",-"secondVar", -"N_1", -"N_2") } else{ - shiny::showNotification('Unable to add SMD due to missing columns') + NULL + # shiny::showNotification('Unable to add SMD due to missing columns') } - } - shiny::incProgress(4/4, detail = paste("Done")) - }) + # } + # shiny::incProgress(4/4, detail = paste("Done")) + } return(result) } @@ -1010,4 +1095,62 @@ characterizationGetCohortsInputs <- function( databaseIds = databaseIds ) ) -} \ No newline at end of file +} + +characterizationGetCohortComparisonDataRaw <- function( + connectionHandler, + resultDatabaseSettings, + targetIds, + databaseIds, + minThreshold = 0.01, + addSMD = F +){ + + if(is.null(targetIds) | is.null(databaseIds)){ + warning('Ids cannot be NULL') + return(NULL) + } + + sql <- "select d.cdm_source_abbreviation, + ref.covariate_name, + s.min_prior_observation, + cov.target_cohort_id as cohort_definition_id, + cg.cohort_name, + cov.* from + @schema.@c_table_prefixCOVARIATES cov + inner join + @schema.@c_table_prefixcovariate_ref ref + on cov.covariate_id = ref.covariate_id + and cov.setting_id = ref.setting_id + and cov.database_id = ref.database_id + inner join + @schema.@c_table_prefixsettings s + on s.database_id = cov.database_id + and s.setting_id = cov.setting_id + inner join + @schema.@database_table d + on cov.database_id = d.database_id + inner join + @schema.@cg_table_prefixcohort_definition cg + on cov.target_cohort_id = cg.cohort_definition_id + + where + cov.target_cohort_id in (@target_ids) + and cov.cohort_type = 'Target' + AND cov.database_id in (@database_ids) + AND cov.average_value >= @min_threshold;" + + # settings.min_characterization_mean needed? + res <- connectionHandler$queryDb( + sql = sql, + target_ids = paste0(targetIds, collapse = ','), + database_ids = paste0("'",databaseIds,"'", collapse = ','), + schema = resultDatabaseSettings$schema, + c_table_prefix = resultDatabaseSettings$cTablePrefix, + min_threshold = minThreshold, + database_table = resultDatabaseSettings$databaseTable, + cg_table_prefix = resultDatabaseSettings$cgTablePrefix + ) + + return(res) +} diff --git a/R/characterization-database.R b/R/characterization-database.R index e787ee8e..f0104a28 100644 --- a/R/characterization-database.R +++ b/R/characterization-database.R @@ -48,7 +48,21 @@ characterizationDatabaseComparisonViewer <- function(id) { ), shiny::tabPanel( title = 'Binary', - resultTableViewer(id = ns('mainTable'), boxTitle = 'Binary') + shiny::tabsetPanel( + type = 'pills', + id = ns('binaryPanel'), + shiny::tabPanel( + title = "Table", + resultTableViewer(id = ns('mainTable'), boxTitle = 'Binary') + ), + shiny::tabPanel( + title = "Plot", + shiny::uiOutput(ns('plotInputs')), + shinycssloaders::withSpinner( + plotly::plotlyOutput(ns('scatterPlot')) + ) + ) + ) ), shiny::tabPanel( title = 'Continuous', @@ -277,6 +291,208 @@ characterizationDatabaseComparisonServer <- function( ), elementId = session$ns('continuous-table-filter') ) + + + #scatterplots + + plotResult <- characterizatonGetDatabaseComparisonDataRaw( + connectionHandler = connectionHandler, + resultDatabaseSettings = resultDatabaseSettings, + targetIds = subTargetId(), + databaseIds = input$databaseIds, + minThreshold = input$minThreshold + ) + + names(plotResult$databaseId) <- plotResult$cdmSourceAbbreviation + + output$plotInputs <- shiny::renderUI({ + shiny::div( + shiny::fluidRow( + shiny::column(width = 5, + shinyWidgets::pickerInput( + inputId = session$ns('xAxis'), + label = 'X-Axis Database: ', + choices = unique(plotResult$cdmSourceAbbreviation), + selected = unique(plotResult$cdmSourceAbbreviation)[1], + multiple = F, + options = shinyWidgets::pickerOptions( + actionsBox = TRUE, + liveSearch = TRUE, + size = 10, + dropupAuto = TRUE, + liveSearchStyle = "contains", + liveSearchPlaceholder = "Type here to search", + virtualScroll = 50 + ) + ) + ), + shiny::column(width = 5, + shinyWidgets::pickerInput( + inputId = session$ns('yAxis'), + label = 'Y-Axis Database: ', + choices = unique(plotResult$cdmSourceAbbreviation), + selected = unique(plotResult$cdmSourceAbbreviation)[2], + multiple = F, + options = shinyWidgets::pickerOptions( + actionsBox = TRUE, + liveSearch = TRUE, + size = 10, + dropupAuto = TRUE, + liveSearchStyle = "contains", + liveSearchPlaceholder = "Type here to search", + virtualScroll = 50 + ) + ) + ) + ), + shiny::fluidRow( + shiny::column( + width = 4, + shiny::actionButton( + inputId = session$ns('generatePlot'), + label = 'Generate Plot' + ) + ) + ) + ) + }) + + #get results + selectedPlotDbs <- shiny::reactiveVal() + shiny::observeEvent(input$generatePlot,{ + + plotDf <- shiny::reactive({ + + # Filter the plot result based on selected xAxis and yAxis inputs + plotResult2 <- plotResult %>% + dplyr::filter(.data$cdmSourceAbbreviation %in% c(input$xAxis, input$yAxis)) + + # Group and split the data by cdmSourceAbbreviation + plotResultDbSplit <- plotResult2 %>% + dplyr::group_by(.data$cdmSourceAbbreviation) %>% + dplyr::group_split() + + # Initialize an empty list to store the processed dataframes + processedDfs <- list() + + # Loop over the split datasets and process each one + for (i in seq_along(plotResultDbSplit)) { + + currentDb <- plotResultDbSplit[[i]] + + currentDbDf <- currentDb %>% + dplyr::select(cdmSourceAbbreviation, + covariateName, + averageValue) + + # Ensure only rows with selected xAxis or yAxis inputs are kept + currentDbDf <- currentDbDf %>% + dplyr::filter(.data$cdmSourceAbbreviation %in% c(input$xAxis, input$yAxis)) + + # Get the name for this database (should be unique after filtering) + dbName <- unique(currentDbDf$cdmSourceAbbreviation) + + # Rename the averageValue column based on the database name + colnames(currentDbDf) <- c("cdmSourceAbbreviation", "covariateName", paste0(dbName, "_avg")) + + # Remove the cdmSourceAbbreviation column for joining later + currentDbDf <- currentDbDf %>% + dplyr::select(-cdmSourceAbbreviation) + + # Append the processed dataframe to the list + processedDfs[[i]] <- currentDbDf + } + + # Check if there's at least one dataframe to join + if (length(processedDfs) > 1) { + # Perform a left join across all processed dataframes + plotResultDbComb <- Reduce(function(x, y) dplyr::left_join(x, y, by = "covariateName"), processedDfs) + } else { + # If there's only one dataframe, no need for joining + plotResultDbComb <- processedDfs[[1]] + } + + # Replace NA values with 0 + plotResultDbComb <- plotResultDbComb %>% + replace(is.na(.), 0) %>% + dplyr::mutate(domain = dplyr::case_when( + grepl("condition_", covariateName) | sub("\\s.*", "", covariateName) == "condition" ~ "Condition", + grepl("drug_", covariateName) | sub("\\s.*", "", covariateName) == "drug" ~ "Drug", + grepl("procedure_", covariateName) | sub("\\s.*", "", covariateName) == "procedure" ~ "Procedure", + grepl("measurement_", covariateName) | sub("\\s.*", "", covariateName) == "measurement" ~ "Measurement", + grepl("observation_", covariateName) | sub("\\s.*", "", covariateName) == "observation" ~ "Observation", + grepl("device_", covariateName) | sub("\\s.*", "", covariateName) == "device" ~ "Device", + grepl("cohort_", covariateName) | sub("\\s.*", "", covariateName) == "cohort" ~ "Cohort", + grepl("visit_", covariateName) | sub("\\s.*", "", covariateName) == "visit" ~ "Visit", + .default = "Demographic" + )) + + return(plotResultDbComb) + + + + }) + + #plot + + shiny::observe({ + output$scatterPlot <- plotly::renderPlotly({ + + # Get the filtered and processed plot data + plotData <- plotDf() + + # Ensure that the reactive inputs are valid and accessible + xAxisInput <- input$xAxis + yAxisInput <- input$yAxis + + # Sanitize the xAxis and yAxis input values by replacing spaces with underscores + xAxisSafe <- gsub(" ", "_", xAxisInput) + yAxisSafe <- gsub(" ", "_", yAxisInput) + + # Sanitize column names in plotData to replace spaces with underscores + colnames(plotData) <- gsub(" ", "_", colnames(plotData)) + + # Ensure that the column names exist in plotData + if (!all(c(paste0(xAxisSafe, "_avg"), paste0(yAxisSafe, "_avg")) %in% colnames(plotData))) { + stop("Selected columns not found in data.") + } + + # Create hover text for plotly + plotData$hoverText <- paste( + "Covariate Name:", plotData$covariateName, + "
", xAxisInput, ":", scales::percent(plotData[[paste0(xAxisSafe, "_avg")]]), + "
", yAxisInput, ":", scales::percent(plotData[[paste0(yAxisSafe, "_avg")]]) + ) + + # Create the scatter plot with the diagonal line (x = y) + p <- ggplot2::ggplot(plotData, ggplot2::aes_string(x = paste0(xAxisSafe, "_avg"), + y = paste0(yAxisSafe, "_avg"), + color = "domain", + text = "hoverText")) + # Use hoverText for hover labels + ggplot2::geom_point(size = 2) + # Smaller point size + ggplot2::geom_abline(slope = 1, intercept = 0, linetype = "dashed", color = "black") + # Diagonal x=y line in black + ggplot2::labs( + x = paste0(xAxisInput, " %"), + y = paste0(yAxisInput, " %"), + color = "Domain" + ) + + ggplot2::theme_minimal() + # Optional: use a clean theme + ggplot2::theme( + legend.position = "right", # Position legend as needed + axis.title = ggplot2::element_text(size = 12), # Adjust axis title size + axis.text = ggplot2::element_text(size = 10) # Adjust axis text size + ) + + ggplot2::scale_x_continuous(labels = scales::percent_format()) + # Format x-axis as percentage + ggplot2::scale_y_continuous(labels = scales::percent_format()) # Format y-axis as percentage + + # Convert to a plotly object for interactivity + plotly::ggplotly(p, tooltip = "text") # Use the custom hover text + }) + }) + + + }) + }) @@ -327,3 +543,56 @@ characterizatonGetDatabaseComparisonData <- function( ) } + +characterizatonGetDatabaseComparisonDataRaw <- function( + connectionHandler, + resultDatabaseSettings, + targetIds, + databaseIds, + minThreshold = 0.01, + addSMD = F +){ + + if(is.null(targetIds) | is.null(databaseIds)){ + warning('Ids cannot be NULL') + return(NULL) + } + + sql <- "select d.cdm_source_abbreviation, + ref.covariate_name, + s.min_prior_observation, + cov.target_cohort_id as cohort_definition_id, + cov.* from + @schema.@c_table_prefixCOVARIATES cov + inner join + @schema.@c_table_prefixcovariate_ref ref + on cov.covariate_id = ref.covariate_id + and cov.setting_id = ref.setting_id + and cov.database_id = ref.database_id + inner join + @schema.@c_table_prefixsettings s + on s.database_id = cov.database_id + and s.setting_id = cov.setting_id + inner join + @schema.@database_table d + on cov.database_id = d.database_id + + where + cov.target_cohort_id in (@target_ids) + and cov.cohort_type = 'Target' + AND cov.database_id in (@database_ids) + AND cov.average_value >= @min_threshold;" + + # settings.min_characterization_mean needed? + res <- connectionHandler$queryDb( + sql = sql, + target_ids = paste0(targetIds, collapse = ','), + database_ids = paste0("'",databaseIds,"'", collapse = ','), + schema = resultDatabaseSettings$schema, + c_table_prefix = resultDatabaseSettings$cTablePrefix, + min_threshold = minThreshold, + database_table = resultDatabaseSettings$databaseTable + ) + + return(res) +} From b5cb001cd0c8248ed5c87343702befcf91ffff6f Mon Sep 17 00:00:00 2001 From: jreps Date: Wed, 2 Oct 2024 12:41:19 -0400 Subject: [PATCH 2/6] Update cohort-diagnostics-main.R adding check for column names used in filter and mutate to cohort-diagnostics --- R/cohort-diagnostics-main.R | 3 +++ 1 file changed, 3 insertions(+) diff --git a/R/cohort-diagnostics-main.R b/R/cohort-diagnostics-main.R index c669aaf9..825c9128 100644 --- a/R/cohort-diagnostics-main.R +++ b/R/cohort-diagnostics-main.R @@ -621,6 +621,9 @@ cohortDiagnosticsServer <- function(id, if (!hasData(targetCohortId())) { return(NULL) } + if (sum(c('cohortId','conceptSetName') %in% colnames(dataSource$conceptSets)) !=2) { + return(NULL) + } dataSource$conceptSets %>% dplyr::filter(.data$cohortId == targetCohortId()) %>% dplyr::mutate(name = .data$conceptSetName) %>% From 6be5c1268e64001f44e230d694ef457979ea1a76 Mon Sep 17 00:00:00 2001 From: Nathan Hall Date: Fri, 4 Oct 2024 11:06:23 -0400 Subject: [PATCH 3/6] updating about and website merging CM, SCCS, ES vignette articles into Estimation, and revising about modules to reflect new app structure --- R/about-main.R | 50 +- docs/404.html | 27 +- docs/articles/AddingShinyModules.html | 36 +- docs/articles/Characterization.html | 36 +- docs/articles/CohortDiagnostics.html | 36 +- docs/articles/Cohorts.html | 36 +- docs/articles/DataSources.html | 36 +- docs/articles/Estimation.html | 517 +++++++++++ docs/articles/EvidenceSynthesis.html | 36 +- docs/articles/Prediction.html | 36 +- docs/articles/ReportGenerator.html | 190 ++++ docs/articles/SelfControlledCaseSeries.html | 36 +- docs/articles/index.html | 33 +- docs/authors.html | 39 +- docs/index.html | 27 +- docs/news/index.html | 29 +- docs/pkgdown.yml | 8 +- docs/reference/LargeDataTable.html | 31 +- docs/reference/OhdsiShinyModules.html | 29 +- docs/reference/aboutHelperFile.html | 35 +- docs/reference/aboutServer.html | 45 +- docs/reference/aboutViewer.html | 39 +- .../reference/characterizationHelperFile.html | 35 +- .../characterizationIncidenceServer.html | 51 +- .../characterizationIncidenceViewer.html | 39 +- docs/reference/characterizationServer.html | 43 +- docs/reference/characterizationViewer.html | 39 +- docs/reference/cohortCountsModule.html | 47 +- docs/reference/cohortCountsView.html | 35 +- docs/reference/cohortDefinitionsModule.html | 45 +- docs/reference/cohortDefinitionsView.html | 35 +- .../cohortDiagCharacterizationView.html | 35 +- .../cohortDiagnosticsHelperFile.html | 35 +- docs/reference/cohortDiagnosticsServer.html | 41 +- docs/reference/cohortDiagnosticsView.html | 39 +- docs/reference/cohortGeneratorHelperFile.html | 35 +- docs/reference/cohortGeneratorServer.html | 43 +- docs/reference/cohortGeneratorViewer.html | 39 +- .../cohortMethodAttritionServer.html | 45 +- .../cohortMethodAttritionViewer.html | 39 +- .../cohortMethodCovariateBalanceServer.html | 47 +- .../cohortMethodCovariateBalanceViewer.html | 39 +- .../cohortMethodKaplanMeierServer.html | 45 +- .../cohortMethodKaplanMeierViewer.html | 39 +- ...MethodPopulationCharacteristicsServer.html | 45 +- ...MethodPopulationCharacteristicsViewer.html | 39 +- docs/reference/cohortMethodPowerServer.html | 45 +- docs/reference/cohortMethodPowerViewer.html | 39 +- .../cohortMethodPropensityModelServer.html | 45 +- .../cohortMethodPropensityModelViewer.html | 39 +- ...cohortMethodPropensityScoreDistServer.html | 47 +- ...cohortMethodPropensityScoreDistViewer.html | 39 +- .../cohortMethodSystematicErrorServer.html | 45 +- .../cohortMethodSystematicErrorViewer.html | 39 +- docs/reference/cohortOverlapView.html | 35 +- .../compareCohortCharacterizationView.html | 37 +- docs/reference/conceptsInDataSourceView.html | 35 +- .../reference/createCdDatabaseDataSource.html | 47 +- docs/reference/createCustomColDefList.html | 53 +- docs/reference/createLargeSqlQueryDt.html | 41 +- docs/reference/dataDiagnosticDrillServer.html | 43 +- docs/reference/dataDiagnosticDrillViewer.html | 39 +- docs/reference/dataDiagnosticHelperFile.html | 35 +- docs/reference/dataDiagnosticServer.html | 43 +- .../dataDiagnosticSummaryServer.html | 43 +- .../dataDiagnosticSummaryViewer.html | 39 +- docs/reference/dataDiagnosticViewer.html | 39 +- docs/reference/databaseInformationView.html | 35 +- docs/reference/datasourcesHelperFile.html | 37 +- docs/reference/datasourcesServer.html | 45 +- docs/reference/datasourcesViewer.html | 41 +- docs/reference/estimationHelperFile.html | 35 +- docs/reference/estimationServer.html | 43 +- docs/reference/estimationViewer.html | 39 +- .../reference/getCirceRenderedExpression.html | 43 +- docs/reference/getEnabledCdReports.html | 35 +- .../getExampleConnectionDetails.html | 35 +- docs/reference/getLogoImage.html | 33 +- docs/reference/homeHelperFile.html | 35 +- docs/reference/homeServer.html | 43 +- docs/reference/homeViewer.html | 39 +- docs/reference/incidenceRatesView.html | 35 +- docs/reference/inclusionRulesView.html | 35 +- docs/reference/index.html | 37 +- docs/reference/indexEventBreakdownView.html | 35 +- docs/reference/largeTableServer.html | 45 +- docs/reference/largeTableView.html | 41 +- docs/reference/makeButtonLabel.html | 41 +- docs/reference/orpahanConceptsView.html | 37 +- ...tientLevelPredictionCalibrationServer.html | 47 +- ...tientLevelPredictionCalibrationViewer.html | 39 +- ...LevelPredictionCovariateSummaryServer.html | 51 +- ...LevelPredictionCovariateSummaryViewer.html | 39 +- .../patientLevelPredictionCutoffServer.html | 47 +- .../patientLevelPredictionCutoffViewer.html | 39 +- ...entLevelPredictionDesignSummaryServer.html | 43 +- ...entLevelPredictionDesignSummaryViewer.html | 39 +- ...tientLevelPredictionDiagnosticsServer.html | 45 +- ...tientLevelPredictionDiagnosticsViewer.html | 39 +- ...ntLevelPredictionDiscriminationServer.html | 47 +- ...ntLevelPredictionDiscriminationViewer.html | 39 +- .../patientLevelPredictionHelperFile.html | 35 +- ...ientLevelPredictionModelSummaryServer.html | 45 +- ...ientLevelPredictionModelSummaryViewer.html | 39 +- .../patientLevelPredictionNbServer.html | 47 +- .../patientLevelPredictionNbViewer.html | 39 +- .../patientLevelPredictionServer.html | 43 +- .../patientLevelPredictionSettingsServer.html | 51 +- .../patientLevelPredictionSettingsViewer.html | 39 +- ...atientLevelPredictionValidationServer.html | 51 +- ...atientLevelPredictionValidationViewer.html | 39 +- .../patientLevelPredictionViewer.html | 39 +- docs/reference/phevaluatorHelperFile.html | 37 +- docs/reference/phevaluatorServer.html | 45 +- docs/reference/phevaluatorViewer.html | 41 +- docs/reference/reportHelperFile.html | 35 +- docs/reference/reportServer.html | 51 +- docs/reference/reportViewer.html | 39 +- docs/reference/resultTableServer.html | 59 +- docs/reference/resultTableViewer.html | 45 +- docs/reference/timeDistributionsView.html | 35 +- docs/reference/visitContextView.html | 35 +- docs/sitemap.xml | 826 +++++------------- vignettes/CohortMethod.Rmd | 60 -- vignettes/Estimation.Rmd | 136 +++ vignettes/EvidenceSynthesis.Rmd | 60 -- vignettes/ReportGenerator.Rmd | 47 + vignettes/SelfControlledCaseSeries.Rmd | 82 -- 128 files changed, 3668 insertions(+), 3018 deletions(-) create mode 100644 docs/articles/Estimation.html create mode 100644 docs/articles/ReportGenerator.html delete mode 100644 vignettes/CohortMethod.Rmd create mode 100644 vignettes/Estimation.Rmd delete mode 100644 vignettes/EvidenceSynthesis.Rmd create mode 100644 vignettes/ReportGenerator.Rmd delete mode 100644 vignettes/SelfControlledCaseSeries.Rmd diff --git a/R/about-main.R b/R/about-main.R index f5225ad7..2c0c9a4d 100644 --- a/R/about-main.R +++ b/R/about-main.R @@ -65,10 +65,12 @@ aboutViewer <- function(id = 'homepage') { shinydashboard::valueBoxOutput(ns("cohortDiagnosticsBox"), width = 3) ), shiny::fluidRow( - shinydashboard::valueBoxOutput(ns("cohortMethodBox"), width = 3), + shinydashboard::valueBoxOutput(ns("estimationBox"), width = 3), shinydashboard::valueBoxOutput(ns("predictionBox"), width = 3), - shinydashboard::valueBoxOutput(ns("sccsBox"), width = 3), - shinydashboard::valueBoxOutput(ns("evidenceSynthesisBox"), width = 3) + shinydashboard::valueBoxOutput(ns("reportGeneratorBox"), width = 3) + # , + # shinydashboard::valueBoxOutput(ns("sccsBox"), width = 3), + # shinydashboard::valueBoxOutput(ns("evidenceSynthesisBox"), width = 3) ) ) } @@ -127,7 +129,7 @@ aboutServer <- function(id = 'homepage', value = "Data Sources", subtitle = "Data sources used in this analysis", icon = shiny::icon("database"), - color = "aqua", + color = "olive", href = "https://ohdsi.github.io/OhdsiShinyModules/articles/DataSources.html" ) } else { @@ -169,7 +171,7 @@ aboutServer <- function(id = 'homepage', value = "Characterization", subtitle = "Characterization results for this analysis", icon = shiny::icon("table"), - color = "teal", + color = "red", href = "https://ohdsi.github.io/OhdsiShinyModules/articles/Characterization.html" ) } else { @@ -205,23 +207,23 @@ aboutServer <- function(id = 'homepage', }) - output$cohortMethodBox <- + output$estimationBox <- shinydashboard::renderValueBox({ - if ("CohortMethod" %in% tab_names) { + if ("Estimation" %in% tab_names) { targetedValueBox( - value = "Cohort Method", - subtitle = "Cohort Method results for this analysis", + value = "Estimation", + subtitle = "Population-level effect estimation results for this analysis", icon = shiny::icon("chart-column"), color = "maroon", - href = "https://ohdsi.github.io/OhdsiShinyModules/articles/CohortMethod.html" + href = "https://ohdsi.github.io/OhdsiShinyModules/articles/Estimation.html" ) } else { targetedValueBox( - value = "Cohort Method", + value = "Estimation", subtitle = "This module was not included in this analysis", icon = shiny::icon("chart-column"), color = "black", - href = "https://ohdsi.github.io/OhdsiShinyModules/articles/CohortMethod.html" + href = "https://ohdsi.github.io/OhdsiShinyModules/articles/Estimation.html" ) } }) @@ -231,7 +233,7 @@ aboutServer <- function(id = 'homepage', if ("Prediction" %in% tab_names) { targetedValueBox( value = "Prediction", - subtitle = "Patient-level Prediction results for this analysis", + subtitle = "Patient-level prediction results for this analysis", icon = shiny::icon("chart-line"), color = "blue", href = "https://ohdsi.github.io/OhdsiShinyModules/articles/Prediction.html" @@ -290,5 +292,27 @@ aboutServer <- function(id = 'homepage', } }) + output$reportGeneratorBox <- + shinydashboard::renderValueBox({ + if ("Report" %in% tab_names) { + targetedValueBox( + value = "Report", + subtitle = "Report Generator for this analysis", + icon = shiny::icon("book"), + color = "teal", + href = "https://ohdsi.github.io/OhdsiShinyModules/articles/ReportGenerator.html" + ) + } else { + targetedValueBox( + value = "Report", + subtitle = + "This module was not included in this analysis", + icon = shiny::icon("book"), + color = "black", + href = "https://ohdsi.github.io/OhdsiShinyModules/articles/ReportGenerator.html" + ) + } + }) + }) } diff --git a/docs/404.html b/docs/404.html index 34ed2cc6..99e5a026 100644 --- a/docs/404.html +++ b/docs/404.html @@ -18,7 +18,7 @@ - +
- +
@@ -136,16 +139,16 @@

Page not found (404)

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/articles/AddingShinyModules.html b/docs/articles/AddingShinyModules.html index 813f857d..813065b7 100644 --- a/docs/articles/AddingShinyModules.html +++ b/docs/articles/AddingShinyModules.html @@ -12,14 +12,13 @@ - - +
- +
@@ -118,9 +120,9 @@

Adding Shiny Modules

Jenna Reps, Jamie Gilbert, Josh Ide

-

2024-09-27

- +

2024-10-04

+
@@ -370,9 +372,7 @@

Dependencies - -

+
@@ -385,16 +385,16 @@

Dependencies

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/articles/Characterization.html b/docs/articles/Characterization.html index 0a17aba8..84db8cbe 100644 --- a/docs/articles/Characterization.html +++ b/docs/articles/Characterization.html @@ -12,14 +12,13 @@ - - +
- +
@@ -118,9 +120,9 @@

Characterization

Nathan Hall

-

2024-09-27

- +

2024-10-04

+
@@ -211,9 +213,7 @@

Utility and Application - -

+
@@ -226,16 +226,16 @@

Utility and Application

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/articles/CohortDiagnostics.html b/docs/articles/CohortDiagnostics.html index 1d21f98d..af316c6c 100644 --- a/docs/articles/CohortDiagnostics.html +++ b/docs/articles/CohortDiagnostics.html @@ -12,14 +12,13 @@ - - +
- +
@@ -118,9 +120,9 @@

Cohort Diagnostics

Nathan Hall

-

2024-09-27

- +

2024-10-04

+
@@ -267,9 +269,7 @@

Utility and Application - -

+
@@ -282,16 +282,16 @@

Utility and Application

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/articles/Cohorts.html b/docs/articles/Cohorts.html index 3f6eb9f3..1cb29117 100644 --- a/docs/articles/Cohorts.html +++ b/docs/articles/Cohorts.html @@ -12,14 +12,13 @@ - - +
- +
@@ -118,9 +120,9 @@

Cohorts

Nathan Hall

-

2024-09-27

- +

2024-10-04

+
@@ -225,9 +227,7 @@

Tools for Cohort Creation & +

@@ -240,16 +240,16 @@

Tools for Cohort Creation &

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/articles/DataSources.html b/docs/articles/DataSources.html index dbfd6cdb..0198d752 100644 --- a/docs/articles/DataSources.html +++ b/docs/articles/DataSources.html @@ -12,14 +12,13 @@ - - +
- +
@@ -118,9 +120,9 @@

Data Sources

Nathan Hall

-

2024-09-27

- +

2024-10-04

+
@@ -221,9 +223,7 @@

Example OMOP-mapped Datasets - -

+
@@ -236,16 +236,16 @@

Example OMOP-mapped Datasets

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/articles/Estimation.html b/docs/articles/Estimation.html new file mode 100644 index 00000000..d228dec7 --- /dev/null +++ b/docs/articles/Estimation.html @@ -0,0 +1,517 @@ + + + + + + + +Estimation • OhdsiShinyModules + + + + + + + + + + + +
+
+ + + + +
+
+ + + + + +
+

Introduction +

+

Observational healthcare data, comprising administrative claims and +electronic health records, present a rich source for generating +real-world evidence pertinent to treatment effects that directly impact +patient well-being. Within this realm, population-level effect +estimation assumes a pivotal role, focusing on elucidating the average +causal effects of exposures—such as medical interventions like drug +exposures or procedures—on specific health outcomes of interest. +Population-level effect estimation delves into two primary realms: +direct effect estimation and comparative effect estimation. In direct +effect estimation, the focus lies on discerning the effect of an +exposure on the risk of an outcome compared to no exposure, while +comparative effect estimation aims to delineate the effect of a target +exposure against a comparator exposure. By contrasting factual outcomes +with counterfactual scenarios—what happened versus what would have +occurred under different circumstances—these estimation tasks offer +critical insights into treatment selection, safety surveillance, and +comparative effectiveness. Whether probing individual hypotheses or +exploring multiple hypotheses concurrently, the overarching goal remains +consistent: to derive high-quality estimates of causal effects from the +intricate fabric of observational healthcare data.

+
+
+

1. CohortMethod +

+
+

Features and Functionalities +

+

The CohortMethod R package, a cornerstone of +population-level estimation within the OHDSI framework, offers a robust +methodology for conducting comparative effectiveness research and +pharmacoepidemiology studies. Some of the features offered by conducting +population-level effect estimation using the CohortMethod module +are:

+
    +
  1. +Data Extraction: Extracts necessary data from +databases structured in the OMOP Common Data Model (CDM) format, +ensuring uniformity and compatibility across diverse healthcare +settings.
  2. +
  3. +Covariate Selection: Utilizing a comprehensive set +of covariates, including drugs, diagnoses, procedures, age, and +comorbidity indexes, CohortMethod constructs propensity and outcome +models tailored to specific research questions.
  4. +
  5. +Large-Scale Regularized Regression: Employing +large-scale regularized regression techniques, CohortMethod fits +propensity and outcome models with precision and efficiency, +accommodating the complexities of real-world healthcare data.
  6. +
  7. +Propensity Score Adjustment: Facilitates propensity +score adjustment through trimming, stratification, matching, and +weighting, enabling researchers to address confounding and balance +covariate distributions across treatment groups. Results are viewable +both graphically and in tabular form to assess the model.
  8. +
  9. +Diagnostic Functions: Diagnostic functions within +CohortMethod offer insights into propensity score distributions and +covariate balance before and after matching or trimming, enhancing +transparency and robustness in estimation procedures.
  10. +
  11. +Supported Outcome Models: Supported outcome models +include (conditional) logistic regression, (conditional) Poisson +regression, and (conditional) Cox regression, providing flexibility in +modeling various types of outcomes in observational health data +research.
  12. +
  13. +Power: Incorporates power analysis techniques to +estimate the statistical power of the study design, aiding in sample +size determination and study planning, and provides a minimum-detectable +relative risk (MDRR) statistic.
  14. +
  15. +Attrition: Assesses attrition rates within cohorts, +providing insights into potential biases introduced by data loss during +the study period, and provides a visualization of attrition across +various cohort criteria.
  16. +
  17. +Population Characteristics: Analyzes population +characteristics to understand the demographic and clinical makeup of the +study cohorts, informing interpretation of estimation results both +before and after propensity score matching.
  18. +
  19. +Covariate Balance: Visually monitors covariate +balance before and after matching or trimming, ensuring that confounding +variables are adequately controlled for in the analysis.
  20. +
  21. +Systematic Error: Assesses effect size estimates +for negative controls (true hazard ratio = 1) and positive controls +(true hazard ratio > 1) both before and after calibration. Estimates +below the diagonal dashed lines are statistically significant (alpha = +0.05) different from the true effect size. A well-calibrated estimator +should have the true effect size within the 95 percent confidence +interval 95 percent of times, providing researchers with confidence in +the reliability of the estimation process and the accuracy of the +obtained results.
  22. +
+
+
+

Utility and Application +

+

Comparative Effectiveness Research: CohortMethod +empowers researchers to conduct comparative effectiveness studies by +estimating treatment effects while accounting for potential confounding +factors and bias inherent in observational data.

+

Pharmacoepidemiology and Drug Safety Studies: In +pharmacoepidemiology research, CohortMethod facilitates the evaluation +of drug safety and effectiveness by quantifying the association between +drug exposures and clinical outcomes in real-world populations.

+
+
+
+

2. Self-Controlled Case Series +

+
+

Introduction +

+

The Self-Controlled Case Series (SCCS) method offers a nuanced +approach to investigating the relationship between exposures and +outcomes within individual patients over time. SCCS designs are +particularly adept at comparing the rate of outcomes during times of +exposure to rates during periods of non-exposure, including before, +between, and after exposure episodes. By leveraging a Poisson regression +that is conditioned on the individual, the SCCS design inherently +addresses the question: “Given that a patient has the outcome, is the +outcome more likely to occur during exposed time compared to non-exposed +time?” The design choices outlined in the method are pivotal for +defining an SCCS question, with each choice playing a critical role in +the study’s design and outcomes:

+

Target Cohort: This represents the treatment under +investigation. Outcome Cohort: This cohort signifies +the outcome of interest. Time-at-Risk: Identifies the +specific times when the risk of the outcome is considered, often +relative to the start and end dates of the target cohort. +Model: Defines the statistical model used to estimate +the effect, including adjustments for time-varying confounders if +necessary.

+

One of the SCCS design’s strengths is its robustness to confounding +by factors that differ between individuals, as each participant serves +as their own control. However, it remains sensitive to time-varying +confounding factors. To mitigate this, adjustments can be made for +factors such as age, seasonality, and calendar time, enhancing the +model’s accuracy.

+

An advanced variant of the SCCS also considers all other drug +exposures recorded in the database, significantly expanding the model’s +variables. This approach employs L1-regularization, with +cross-validation used to select the regularization hyperparameter for +all exposures except the one of interest.

+

An important assumption of the SCCS is that the observation period’s +end is independent of the outcome date. This may not hold true for +outcomes that can be fatal, such as stroke. To address this, extensions +to the SCCS model have been developed that correct for any dependency +between the observation period end and the outcome.

+
+
+

Features and Functionalities +

+

The SelfControlledCaseSeries R package allows the user to +perform SCCS analyses in an observational database in the OMOP Common +Data Model. Some of the features offered by the SCCS module include:

+
    +
  1. **Data Extraction: Extracts necessary data from databases structured +in the OMOP Common Data Model (CDM) format, ensuring uniformity and +compatibility across diverse healthcare settings.
  2. +
  3. +Seasonality Adjustment: Offers the option to adjust +for seasonality effects using a spline function, enhancing the model’s +accuracy by accounting for seasonal variation in exposure and outcome +rates.
  4. +
  5. +Age Adjustment: Provides the option to incorporate +age adjustments using a spline function, allowing for more nuanced +analyses that consider the impact of age on the exposure-outcome +relationship.
  6. +
  7. +Calendar Time Adjustment: Enables the inclusion of +calendar time adjustments using a spline function, addressing potential +temporal trends in the data that could confound the exposure-outcome +relationship.
  8. +
  9. +Event-dependent Censoring Correction: Features the +ability to correct for event-dependent censoring of the observation +period, ensuring that the end of the observation period is appropriately +handled, especially in cases where it might be related to the +outcome.
  10. +
  11. +Comprehensive Covariate Inclusion: Allows for the +addition of a wide array of covariates in one analysis, such as all +recorded drug exposures, facilitating a thorough examination of +potential confounders and effect modifiers.
  12. +
  13. +Risk Window Customization: Supports the +construction of various types of covariates and risk windows, including +pre-exposure windows, to capture contra-indications and other relevant +temporal patterns related to exposure and outcome.
  14. +
  15. +Regularization of Covariates: Applies +regularization to all covariates except the outcome of interest, +employing techniques like L1-regularization with cross-validation for +selecting the regularization hyperparameter, thereby preventing +overfitting and enhancing model reliability.
  16. +
  17. +Self-Controlled Risk Interval Design: Incorporates +the self-controlled risk interval design as a specific application of +the SCCS method, offering additional methodological flexibility for +studying short-term effects of exposures.
  18. +
  19. +Power: Incorporates power analysis techniques to +estimate the statistical power of the study design, aiding in sample +size determination and study planning, and provides a minimum-detectable +relative risk (MDRR) statistic.
  20. +
  21. +Attrition: Assesses attrition rates within cohorts, +providing insights into potential biases introduced by data loss during +the study period, and provides a visualization of attrition across +various cohort criteria.
  22. +
  23. +Spanning: Analyzes the number of subjects observed +for 3 consecutive months, providing insights into the cohort’s +consistency and stability over time.
  24. +
  25. +Time Trend: Assesses the ratio of observed to +expected outcomes per month, with adjustments for calendar time, +seasonality, and/or age as specified in the model, to examine time +trends in the data.
  26. +
  27. +Time to Event: Evaluates the number of events and +subjects observed per week relative to the start of the first exposure, +offering critical insights into the temporal relationship between +exposure and outcome.
  28. +
  29. +Event-dependent Observation: Provides histograms +for the time between the first occurrence of the outcome and the end of +observation, stratified by censored and uncensored ends of observation, +to assess the impact of event-dependent observation periods.
  30. +
  31. +Systematic Error: Assesses effect size estimates +for negative controls (true hazard ratio = 1) and positive controls +(true hazard ratio > 1) both before and after calibration. Estimates +below the diagonal dashed lines are statistically significant (alpha = +0.05) different from the true effect size. A well-calibrated estimator +should have the true effect size within the 95 percent confidence +interval 95 percent of times, providing researchers with confidence in +the reliability of the estimation process and the accuracy of the +obtained results.
  32. +
+
+
+

Utility and Application +

+

The SCCS method is particularly applicable in several key areas of +epidemiological research and pharmacovigilance:

+

Drug Safety Surveillance: The SCCS method is widely +used in drug safety surveillance to identify adverse effects of +medications post-marketing. It is well-suited to detect short-term risks +associated with drug exposures, especially where the onset of the +adverse event is expected to be temporally close to the exposure.

+

Vaccine Safety Evaluation: The SCCS design is ideal +for assessing the safety of vaccines, especially in evaluating the risk +of adverse events following immunization. Its self-controlled nature +helps to address concerns about confounding by indication and other +biases that can affect observational studies in vaccine safety.

+

Comparative Effectiveness Research: While primarily +designed for evaluating the safety of medical interventions, the SCCS +method can also be adapted to compare the effectiveness of different +treatments or interventions within the same individual over time, +particularly for acute conditions.

+

Epidemiological Research: More broadly, the SCCS +method is used in epidemiological research to study the temporal +relationships between exposures and outcomes, offering insights into the +causality and mechanisms underlying health conditions and diseases.

+
+
+
+

3. Evidence Synthesis (Meta, Meta Analysis) +

+
+

Introduction +

+

Meta-analysis plays a pivotal role in healthcare research by enabling +the synthesis of findings from multiple studies to draw more +generalizable conclusions. In the context of distributed health data +networks, where data are spread across various sites with diverse +populations and practices, synthesizing evidence becomes both a +challenge and a necessity. The EvidenceSynthesis R package addresses +these challenges head-on. It offers a suite of tools designed for +combining causal effect estimates and study diagnostics from multiple +data sites, all while adhering to stringent patient privacy requirements +and navigating the complexities inherent to observational data. This +approach enhances the robustness of meta-analytical conclusions and +extends the utility of distributed health data for research +purposes.

+
+
+

Features and Functionalities +

+

The Meta module which utilizes the EvidenceSynthesis R package makes +use of the following features to summarize the results of a study:

+
    +
  1. +Meta-Analysis Methods: Facilitates both traditional +fixed-effects and random-effects meta-analyses, accommodating studies +with different degrees of between-site or between-database +variability.
  2. +
  3. +Forest Plot Generation: Provides capabilities for +creating forest plots, visual summaries that illustrate the effects +estimated by individual studies, their confidence intervals, and the +synthesized overall effect.
  4. +
  5. +Non-Normal Likelihood Approximations: Utilizes +non-normal approximations for the per-data-site likelihood function to +reduce bias in scenarios with small or zero counts, a frequent issue in +distributed research environments.
  6. +
+

The syntheses are generated for both Cohort Method and +Self-Controlled Case Series estimation results from the study, providing +both information on the diagnostic results within each database and the +visualized and tabular results of the meta analysis.

+
+
+

Utility and Application +

+

The EvidenceSynthesis package is instrumental in synthesizing +evidence from observational studies across multiple healthcare +databases. Its significance is underscored in scenarios characterized +by:

+

Comparative Effectiveness Research: Synthesizing +evidence from disparate sources allows for stronger, more reliable +comparisons of treatment outcomes, enriching the foundation for clinical +decision-making.

+

Safety Surveillance: Aggregated safety data across +databases enhance the detection and understanding of adverse drug +reactions, contributing to safer patient care.

+

Policy and Clinical Guidelines Development: +Meta-analytical findings informed by comprehensive, real-world data can +guide policy formulation and the updating of clinical guidelines, +ensuring they are grounded in broad-based evidence.

+

Addressing Challenges of Small Sample Sizes: The +EvidenceSynthesis package notably advances the field by tackling the +issue of small sample sizes and zero event counts, which traditional +meta-analytical methods often handle poorly. Its innovative use of +non-normal likelihood approximations enables more precise effect size +estimation under such conditions, ensuring that the insights derived +from meta-analyses are both accurate and meaningful. This attribute is +particularly beneficial in distributed health data networks, where +individual site/database data may be limited but collectively hold +significant informational value.

+
+
+
+ + + +
+ + + +
+ +
+

+

Site built with pkgdown 2.1.0.

+
+ +
+
+ + + + + + + + diff --git a/docs/articles/EvidenceSynthesis.html b/docs/articles/EvidenceSynthesis.html index 7c3cd941..41bdc584 100644 --- a/docs/articles/EvidenceSynthesis.html +++ b/docs/articles/EvidenceSynthesis.html @@ -12,14 +12,13 @@ - - +
- +
@@ -118,9 +120,9 @@

Evidence Synthesis (Meta, Meta Analysis)

Nathan Hall

-

2024-09-27

- +

2024-10-04

+
@@ -208,9 +210,7 @@

Utility and Application - -

+
@@ -223,16 +223,16 @@

Utility and Application

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/articles/Prediction.html b/docs/articles/Prediction.html index 9b4a0827..29286a2f 100644 --- a/docs/articles/Prediction.html +++ b/docs/articles/Prediction.html @@ -12,14 +12,13 @@ - - +
- +
@@ -118,9 +120,9 @@

Prediction

Nathan Hall

-

2024-09-27

- +

2024-10-04

+
@@ -211,9 +213,7 @@

Utility and Application - -

+
@@ -226,16 +226,16 @@

Utility and Application

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/articles/ReportGenerator.html b/docs/articles/ReportGenerator.html new file mode 100644 index 00000000..54dbcc0f --- /dev/null +++ b/docs/articles/ReportGenerator.html @@ -0,0 +1,190 @@ + + + + + + + +Report Generator • OhdsiShinyModules + + + + + + + + + + + +
+
+ + + + +
+
+ + + + + +
+

Introduction +

+

ReportGenerator is a tool used to create a summary presentation +document using results from a Strategus execution which should be stored +in a results database.

+
+
+

Description +

+

The Report Generator module allows the user to choose which target +(T), subgroup (indication & extra inclusions), comparator (C), and +outcome(s) (O) they would like a downloaded report on. In the last +section of the module, the user’s selections are reported back to them +for review before downloading. Here, the user can also choose to +restrict the study date and/or the age range of people included in the +report.

+
+

Notes +

+

Please note that this package is currently under development, so +results may vary or may not be available at the time of report +generation.

+
+
+
+ + + +
+ + + +
+ +
+

+

Site built with pkgdown 2.1.0.

+
+ +
+
+ + + + + + + + diff --git a/docs/articles/SelfControlledCaseSeries.html b/docs/articles/SelfControlledCaseSeries.html index 30c6697c..47e7ef38 100644 --- a/docs/articles/SelfControlledCaseSeries.html +++ b/docs/articles/SelfControlledCaseSeries.html @@ -12,14 +12,13 @@ - - +
- +
@@ -118,9 +120,9 @@

Self-Controlled Case Series

Nathan Hall

-

2024-09-27

- +

2024-10-04

+
@@ -293,9 +295,7 @@

Utility and Application - -

+
@@ -308,16 +308,16 @@

Utility and Application

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/articles/index.html b/docs/articles/index.html index 2a478dbe..bdb53db3 100644 --- a/docs/articles/index.html +++ b/docs/articles/index.html @@ -3,7 +3,7 @@ - +
- +
-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/authors.html b/docs/authors.html index 4702d974..5590400a 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -3,7 +3,7 @@ - + - +
@@ -93,31 +96,31 @@

Authors and Citation

- +
  • -

    Jenna Reps. Author, maintainer. +

    Jenna Reps. Author, maintainer.

  • -

    Nathan Hall. Author. +

    Nathan Hall. Author.

  • -

    Jamie Gibert. Author. +

    Jamie Gibert. Author.

Citation

- +

Reps J, Hall N, Gibert J (2024). OhdsiShinyModules: Repository of Shiny Modules for OHDSI Result Viewers. -R package version 3.0.2. +R package version 3.0.2.

@Manual{,
   title = {OhdsiShinyModules: Repository of Shiny Modules for OHDSI Result Viewers},
@@ -137,15 +140,15 @@ 

Citation

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/index.html b/docs/index.html index 779fc3a2..916e7e01 100644 --- a/docs/index.html +++ b/docs/index.html @@ -19,7 +19,7 @@ - +
- +
@@ -242,16 +245,16 @@

Developers

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/news/index.html b/docs/news/index.html index 9f4d13a6..5cd795d5 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -3,7 +3,7 @@ - +
- +
@@ -208,15 +211,15 @@
-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/pkgdown.yml b/docs/pkgdown.yml index 49657cad..0c235b9d 100644 --- a/docs/pkgdown.yml +++ b/docs/pkgdown.yml @@ -1,15 +1,15 @@ pandoc: '3.2' -pkgdown: 2.0.9 +pkgdown: 2.1.0 pkgdown_sha: ~ articles: AddingShinyModules: AddingShinyModules.html Characterization: Characterization.html CohortDiagnostics: CohortDiagnostics.html - CohortMethod: CohortMethod.html Cohorts: Cohorts.html DataSources: DataSources.html + Estimation: Estimation.html EvidenceSynthesis: EvidenceSynthesis.html Prediction: Prediction.html + ReportGenerator: ReportGenerator.html SelfControlledCaseSeries: SelfControlledCaseSeries.html -last_built: 2024-09-27T15:53Z - +last_built: 2024-10-04T14:25Z diff --git a/docs/reference/LargeDataTable.html b/docs/reference/LargeDataTable.html index 2841ef56..7c725564 100644 --- a/docs/reference/LargeDataTable.html +++ b/docs/reference/LargeDataTable.html @@ -10,7 +10,7 @@ - +
- +
@@ -132,7 +135,7 @@

Public fields

Methods

- +

Public methods

@@ -276,15 +279,15 @@

Arguments -

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/OhdsiShinyModules.html b/docs/reference/OhdsiShinyModules.html index 71e1b8be..9972a765 100644 --- a/docs/reference/OhdsiShinyModules.html +++ b/docs/reference/OhdsiShinyModules.html @@ -3,7 +3,7 @@ - +
- +
@@ -118,15 +121,15 @@

Author

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/aboutHelperFile.html b/docs/reference/aboutHelperFile.html index 9711c7ed..ebae9e46 100644 --- a/docs/reference/aboutHelperFile.html +++ b/docs/reference/aboutHelperFile.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,9 +107,7 @@

The location of the about module helper file

Value

- - -

string location of the about helper file

+

string location of the about helper file

Details

@@ -114,7 +115,7 @@

Details

See also

-

Other About: +

Other About: aboutServer(), aboutViewer()

@@ -131,15 +132,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/aboutServer.html b/docs/reference/aboutServer.html index ca5897ff..d47dca91 100644 --- a/docs/reference/aboutServer.html +++ b/docs/reference/aboutServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -109,27 +112,27 @@

The module server for the shiny app home

Arguments

-
id
+ + +
id

the unique reference id for the module

-
connectionHandler
+
connectionHandler

a connection to the database with the results

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the characterization result schema, dbms, tablePrefix, databaseTable and cgTablePrefix

-
config
+
config

the config from the app.R file that contains a list of which modules to include

Value

- - -

The server for the shiny app home

+

The server for the shiny app home

Details

@@ -137,7 +140,7 @@

Details

See also

-

Other About: +

Other About: aboutHelperFile(), aboutViewer()

@@ -154,15 +157,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/aboutViewer.html b/docs/reference/aboutViewer.html index 99df8738..3e8198c8 100644 --- a/docs/reference/aboutViewer.html +++ b/docs/reference/aboutViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

The module viewer for the shiny app home

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the home page module

+

The user interface to the home page module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other About: +

Other About: aboutHelperFile(), aboutServer()

@@ -137,15 +140,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/characterizationHelperFile.html b/docs/reference/characterizationHelperFile.html index 226eaacd..c595d2c5 100644 --- a/docs/reference/characterizationHelperFile.html +++ b/docs/reference/characterizationHelperFile.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,9 +107,7 @@

The location of the characterization module helper file

Value

- - -

string location of the characterization helper file

+

string location of the characterization helper file

Details

@@ -114,7 +115,7 @@

Details

See also

-

Other Characterization: +

Other Characterization: characterizationIncidenceServer(), characterizationIncidenceViewer(), characterizationServer(), @@ -133,15 +134,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/characterizationIncidenceServer.html b/docs/reference/characterizationIncidenceServer.html index d2b96876..c1a9314b 100644 --- a/docs/reference/characterizationIncidenceServer.html +++ b/docs/reference/characterizationIncidenceServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -112,39 +115,39 @@

The module server for exploring incidence results

Arguments

-
id
+ + +
id

the unique reference id for the module

-
connectionHandler
+
connectionHandler

the connection to the prediction result database

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the characterization result schema, dbms, tablePrefix, databaseTable and cgTablePrefix

-
parents
+
parents

a list of parent cohorts

-
parentIndex
+
parentIndex

an integer specifying the parent index of interest

-
outcomes
+
outcomes

a reactive object specifying the outcomes of interest

-
targetIds
+
targetIds

a reactive vector of integer specifying the targetIds of interest

Value

- - -

The server to the prediction incidence module

+

The server to the prediction incidence module

Details

@@ -152,7 +155,7 @@

Details

See also

-

Other Characterization: +

Other Characterization: characterizationHelperFile(), characterizationIncidenceViewer(), characterizationServer(), @@ -171,15 +174,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/characterizationIncidenceViewer.html b/docs/reference/characterizationIncidenceViewer.html index f2c55350..e5689a32 100644 --- a/docs/reference/characterizationIncidenceViewer.html +++ b/docs/reference/characterizationIncidenceViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

The module viewer for exploring incidence results

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the description incidence module

+

The user interface to the description incidence module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other Characterization: +

Other Characterization: characterizationHelperFile(), characterizationIncidenceServer(), characterizationServer(), @@ -139,15 +142,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/characterizationServer.html b/docs/reference/characterizationServer.html index c6e908ac..bb5b4407 100644 --- a/docs/reference/characterizationServer.html +++ b/docs/reference/characterizationServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -108,23 +111,23 @@

The module server for exploring characterization studies

Arguments

-
id
+ + +
id

the unique reference id for the module

-
connectionHandler
+
connectionHandler

a connection to the database with the results

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the characterization result schema, dbms, tablePrefix, databaseTable and cgTablePrefix

Value

- - -

The server for the characterization module

+

The server for the characterization module

Details

@@ -132,7 +135,7 @@

Details

See also

-

Other Characterization: +

Other Characterization: characterizationHelperFile(), characterizationIncidenceServer(), characterizationIncidenceViewer(), @@ -151,15 +154,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/characterizationViewer.html b/docs/reference/characterizationViewer.html index f7b57dd0..c7abce46 100644 --- a/docs/reference/characterizationViewer.html +++ b/docs/reference/characterizationViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

The module viewer for exploring characterization studies

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the characterization viewer module

+

The user interface to the characterization viewer module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other Characterization: +

Other Characterization: characterizationHelperFile(), characterizationIncidenceServer(), characterizationIncidenceViewer(), @@ -139,15 +142,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortCountsModule.html b/docs/reference/cohortCountsModule.html index 8cc8482c..0b4f7d34 100644 --- a/docs/reference/cohortCountsModule.html +++ b/docs/reference/cohortCountsModule.html @@ -3,7 +3,7 @@ - +
- +
@@ -112,37 +115,39 @@

Shiny module for cohort counts

Arguments

-
id
+ + +
id

namespace id

-
dataSource
+
dataSource

Backend Data source (DatabaseConnection)

-
cohortTable
+
cohortTable

data.frame of all cohorts

-
databaseTable
+
databaseTable

data.frame of all databases

-
selectedCohorts
+
selectedCohorts

shiny::reactive - should return cohorts selected or NULL

-
selectedDatabaseIds
+
selectedDatabaseIds

shiny::reactive - should return cohorts selected or NULL

-
cohortIds
+
cohortIds

shiny::reactive - should return cohorts selected integers or NULL

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsView(), cohortDefinitionsModule(), cohortDefinitionsView(), @@ -177,15 +182,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortCountsView.html b/docs/reference/cohortCountsView.html index 80699c75..62fd1953 100644 --- a/docs/reference/cohortCountsView.html +++ b/docs/reference/cohortCountsView.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,13 +107,15 @@

Cohort Counts View

Arguments

-
id
+ + +
id

Namespace id

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortDefinitionsModule(), cohortDefinitionsView(), @@ -145,15 +150,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortDefinitionsModule.html b/docs/reference/cohortDefinitionsModule.html index d9b447b3..1d85344f 100644 --- a/docs/reference/cohortDefinitionsModule.html +++ b/docs/reference/cohortDefinitionsModule.html @@ -3,7 +3,7 @@ - +
- +
@@ -111,33 +114,35 @@

Cohort Definition module

Arguments

-
id
+ + +
id

Namespace id

-
dataSource
+
dataSource

DatabaseConnection

-
cohortDefinitions
+
cohortDefinitions

reactive of cohort definitions to display

-
cohortTable
+
cohortTable

data.frame of cohorts, cohortId, cohortName

-
cohortCountTable
+
cohortCountTable

data.frame of cohortCounts, cohortId, subjects records

-
databaseTable
+
databaseTable

data.frame of databasese, databaseId, name

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortCountsView(), cohortDefinitionsView(), @@ -172,15 +177,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortDefinitionsView.html b/docs/reference/cohortDefinitionsView.html index 01bc64f7..b2b5135f 100644 --- a/docs/reference/cohortDefinitionsView.html +++ b/docs/reference/cohortDefinitionsView.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,13 +107,15 @@

Cohort Definitions View

Arguments

-
id
+ + +
id

Namespace id for module

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortCountsView(), cohortDefinitionsModule(), @@ -145,15 +150,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortDiagCharacterizationView.html b/docs/reference/cohortDiagCharacterizationView.html index d03da87e..2a54b811 100644 --- a/docs/reference/cohortDiagCharacterizationView.html +++ b/docs/reference/cohortDiagCharacterizationView.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,13 +107,15 @@

characterization

Arguments

-
id
+ + +
id

Namespace Id - use namespaced id ns("characterization") inside diagnosticsExplorer module

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortCountsView(), cohortDefinitionsModule(), @@ -145,15 +150,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortDiagnosticsHelperFile.html b/docs/reference/cohortDiagnosticsHelperFile.html index b6320ccf..c42cdcf4 100644 --- a/docs/reference/cohortDiagnosticsHelperFile.html +++ b/docs/reference/cohortDiagnosticsHelperFile.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,9 +107,7 @@

The location of the description module helper file

Value

- - -

string location of the description helper file

+

string location of the description helper file

Details

@@ -114,7 +115,7 @@

Details

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortCountsView(), cohortDefinitionsModule(), @@ -149,15 +150,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortDiagnosticsServer.html b/docs/reference/cohortDiagnosticsServer.html index 6aeb4d86..bac7e1f0 100644 --- a/docs/reference/cohortDiagnosticsServer.html +++ b/docs/reference/cohortDiagnosticsServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -109,25 +112,27 @@

Cohort Diagnostics Explorer main module

Arguments

-
id
+ + +
id

module Id

-
connectionHandler
+
connectionHandler

ResultModelManager ConnectionHander instance

-
resultDatabaseSettings
+
resultDatabaseSettings

results database settings

-
dataSource
+
dataSource

dataSource optionally created with createCdDatabaseDataSource

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortCountsView(), cohortDefinitionsModule(), @@ -162,15 +167,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortDiagnosticsView.html b/docs/reference/cohortDiagnosticsView.html index 7ee9cd06..6116b10b 100644 --- a/docs/reference/cohortDiagnosticsView.html +++ b/docs/reference/cohortDiagnosticsView.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

View for cohort diagnostics module

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the cohort diagnostics viewer module

+

The user interface to the cohort diagnostics viewer module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortCountsView(), cohortDefinitionsModule(), @@ -155,15 +158,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortGeneratorHelperFile.html b/docs/reference/cohortGeneratorHelperFile.html index de343e98..a1a20887 100644 --- a/docs/reference/cohortGeneratorHelperFile.html +++ b/docs/reference/cohortGeneratorHelperFile.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,9 +107,7 @@

The location of the cohort-generator module helper file

Value

- - -

string location of the cohort-generator helper file

+

string location of the cohort-generator helper file

Details

@@ -114,7 +115,7 @@

Details

See also

-

Other CohortGenerator: +

Other CohortGenerator: cohortGeneratorServer(), cohortGeneratorViewer()

@@ -131,15 +132,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortGeneratorServer.html b/docs/reference/cohortGeneratorServer.html index a651ac75..27732369 100644 --- a/docs/reference/cohortGeneratorServer.html +++ b/docs/reference/cohortGeneratorServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,27 +107,27 @@

The module server for the main cohort generator module

Arguments

-
id
+ + +
id

the unique reference id for the module

-
connectionHandler
+
connectionHandler

a connection to the database with the results

-
resultDatabaseSettings
+
resultDatabaseSettings

a named list containing the cohort generator results database details (schema, table prefix)

Value

- - -

the cohort generator results viewer main module server

+

the cohort generator results viewer main module server

See also

-

Other CohortGenerator: +

@@ -141,15 +144,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortGeneratorViewer.html b/docs/reference/cohortGeneratorViewer.html index 2e62987b..4a3122ee 100644 --- a/docs/reference/cohortGeneratorViewer.html +++ b/docs/reference/cohortGeneratorViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,19 +107,19 @@

The viewer of the main cohort generator module

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the cohort generator results viewer

+

The user interface to the cohort generator results viewer

See also

-

Other CohortGenerator: +

@@ -133,15 +136,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortMethodAttritionServer.html b/docs/reference/cohortMethodAttritionServer.html index 2990e32e..aaf26a8f 100644 --- a/docs/reference/cohortMethodAttritionServer.html +++ b/docs/reference/cohortMethodAttritionServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -109,31 +112,31 @@

The module server for rendering the PLE attrition results

Arguments

-
id
+ + +
id

the unique reference id for the module

-
selectedRow
+
selectedRow

the selected row from the main results table

-
connectionHandler
+
connectionHandler

the connection to the PLE results database

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

Value

- - -

the PLE attrition results content server

+

the PLE attrition results content server

See also

-

Other Estimation: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortMethodAttritionViewer.html b/docs/reference/cohortMethodAttritionViewer.html index d569dc7e..08719d42 100644 --- a/docs/reference/cohortMethodAttritionViewer.html +++ b/docs/reference/cohortMethodAttritionViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,19 +107,19 @@

The module viewer for rendering the PLE attrition results

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the cohort method attrition

+

The user interface to the cohort method attrition

See also

-

Other Estimation: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortMethodCovariateBalanceServer.html b/docs/reference/cohortMethodCovariateBalanceServer.html index 363194f0..ddbae153 100644 --- a/docs/reference/cohortMethodCovariateBalanceServer.html +++ b/docs/reference/cohortMethodCovariateBalanceServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -110,35 +113,35 @@

The module server for rendering the covariate balance plot

Arguments

-
id
+ + +
id

the unique reference id for the module

-
selectedRow
+
selectedRow

the selected row from the main results table

-
connectionHandler
+
connectionHandler

the connection to the PLE results database

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

-
metaAnalysisDbIds
+
metaAnalysisDbIds

metaAnalysisDbIds

Value

- - -

the PLE covariate balance content server

+

the PLE covariate balance content server

See also

-

Other Estimation: +

Other Estimation: cohortMethodAttritionServer(), cohortMethodAttritionViewer(), cohortMethodCovariateBalanceViewer(), @@ -171,15 +174,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortMethodCovariateBalanceViewer.html b/docs/reference/cohortMethodCovariateBalanceViewer.html index a0903dce..425a8fd8 100644 --- a/docs/reference/cohortMethodCovariateBalanceViewer.html +++ b/docs/reference/cohortMethodCovariateBalanceViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,19 +107,19 @@

The module viewer for rendering the PLE covariate balance analysis

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the cohort method covariate balance results

+

The user interface to the cohort method covariate balance results

See also

-

Other Estimation: +

Other Estimation: cohortMethodAttritionServer(), cohortMethodAttritionViewer(), cohortMethodCovariateBalanceServer(), @@ -149,15 +152,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortMethodKaplanMeierServer.html b/docs/reference/cohortMethodKaplanMeierServer.html index cbe646e4..ba9f4f12 100644 --- a/docs/reference/cohortMethodKaplanMeierServer.html +++ b/docs/reference/cohortMethodKaplanMeierServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -109,31 +112,31 @@

The module server for rendering the Kaplan Meier curve

Arguments

-
id
+ + +
id

the unique reference id for the module

-
selectedRow
+
selectedRow

the selected row from the main results table

-
connectionHandler
+
connectionHandler

the connection to the PLE results database

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

Value

- - -

the PLE Kaplain Meier content server

+

the PLE Kaplain Meier content server

See also

-

Other Estimation: +

Other Estimation: cohortMethodAttritionServer(), cohortMethodAttritionViewer(), cohortMethodCovariateBalanceServer(), @@ -166,15 +169,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortMethodKaplanMeierViewer.html b/docs/reference/cohortMethodKaplanMeierViewer.html index fdc47ec0..3999e34f 100644 --- a/docs/reference/cohortMethodKaplanMeierViewer.html +++ b/docs/reference/cohortMethodKaplanMeierViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,19 +107,19 @@

The module viewer for rendering the PLE Kaplan Meier curve

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The module viewer for Kaplan Meier objects

+

The module viewer for Kaplan Meier objects

See also

-

Other Estimation: +

Other Estimation: cohortMethodAttritionServer(), cohortMethodAttritionViewer(), cohortMethodCovariateBalanceServer(), @@ -149,15 +152,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortMethodPopulationCharacteristicsServer.html b/docs/reference/cohortMethodPopulationCharacteristicsServer.html index 33fc26a4..1b5f6a6f 100644 --- a/docs/reference/cohortMethodPopulationCharacteristicsServer.html +++ b/docs/reference/cohortMethodPopulationCharacteristicsServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -109,31 +112,31 @@

The module server for rendering the population characteristics

Arguments

-
id
+ + +
id

the unique reference id for the module

-
selectedRow
+
selectedRow

the selected row from the main results table

-
connectionHandler
+
connectionHandler

the connection to the PLE results database

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

Value

- - -

the PLE population characteristics content server

+

the PLE population characteristics content server

See also

-

Other Estimation: +

Other Estimation: cohortMethodAttritionServer(), cohortMethodAttritionViewer(), cohortMethodCovariateBalanceServer(), @@ -166,15 +169,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortMethodPopulationCharacteristicsViewer.html b/docs/reference/cohortMethodPopulationCharacteristicsViewer.html index 007f58ab..1166c66e 100644 --- a/docs/reference/cohortMethodPopulationCharacteristicsViewer.html +++ b/docs/reference/cohortMethodPopulationCharacteristicsViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,19 +107,19 @@

The module viewer for rendering the PLE population characteristics

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the cohort method population characteristics objects

+

The user interface to the cohort method population characteristics objects

See also

-

Other Estimation: +

Other Estimation: cohortMethodAttritionServer(), cohortMethodAttritionViewer(), cohortMethodCovariateBalanceServer(), @@ -149,15 +152,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortMethodPowerServer.html b/docs/reference/cohortMethodPowerServer.html index 481f7a2e..60283388 100644 --- a/docs/reference/cohortMethodPowerServer.html +++ b/docs/reference/cohortMethodPowerServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -109,31 +112,31 @@

The module server for rendering the PLE power analysis results

Arguments

-
id
+ + +
id

the unique reference id for the module

-
selectedRow
+
selectedRow

the selected row from the main results table

-
connectionHandler
+
connectionHandler

the connection to the PLE results database

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

Value

- - -

the PLE systematic error power server

+

the PLE systematic error power server

See also

-

Other Estimation: +

Other Estimation: cohortMethodAttritionServer(), cohortMethodAttritionViewer(), cohortMethodCovariateBalanceServer(), @@ -166,15 +169,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortMethodPowerViewer.html b/docs/reference/cohortMethodPowerViewer.html index 8e0e388e..f4cf4774 100644 --- a/docs/reference/cohortMethodPowerViewer.html +++ b/docs/reference/cohortMethodPowerViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,19 +107,19 @@

The module viewer for rendering the PLE power analysis

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the cohort method power calculation results

+

The user interface to the cohort method power calculation results

See also

-

Other Estimation: +

Other Estimation: cohortMethodAttritionServer(), cohortMethodAttritionViewer(), cohortMethodCovariateBalanceServer(), @@ -149,15 +152,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortMethodPropensityModelServer.html b/docs/reference/cohortMethodPropensityModelServer.html index 290b58a6..5e9523f6 100644 --- a/docs/reference/cohortMethodPropensityModelServer.html +++ b/docs/reference/cohortMethodPropensityModelServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -109,31 +112,31 @@

The module server for rendering the propensity score model

Arguments

-
id
+ + +
id

the unique reference id for the module

-
selectedRow
+
selectedRow

the selected row from the main results table

-
connectionHandler
+
connectionHandler

the connection to the PLE results database

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

Value

- - -

the PLE propensity score model

+

the PLE propensity score model

See also

-

Other Estimation: +

Other Estimation: cohortMethodAttritionServer(), cohortMethodAttritionViewer(), cohortMethodCovariateBalanceServer(), @@ -166,15 +169,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortMethodPropensityModelViewer.html b/docs/reference/cohortMethodPropensityModelViewer.html index 42b9618f..581359a6 100644 --- a/docs/reference/cohortMethodPropensityModelViewer.html +++ b/docs/reference/cohortMethodPropensityModelViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,19 +107,19 @@

The module viewer for rendering the PLE propensity score model covariates/co

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the cohort method propensity score model covariates/coefficients

+

The user interface to the cohort method propensity score model covariates/coefficients

See also

-

Other Estimation: +

Other Estimation: cohortMethodAttritionServer(), cohortMethodAttritionViewer(), cohortMethodCovariateBalanceServer(), @@ -149,15 +152,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortMethodPropensityScoreDistServer.html b/docs/reference/cohortMethodPropensityScoreDistServer.html index e0fbf118..3f3f95fe 100644 --- a/docs/reference/cohortMethodPropensityScoreDistServer.html +++ b/docs/reference/cohortMethodPropensityScoreDistServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -110,35 +113,35 @@

The module server for rendering a PLE propensity score distribution

Arguments

-
id
+ + +
id

the unique reference id for the module

-
selectedRow
+
selectedRow

the selected row from the main results table

-
connectionHandler
+
connectionHandler

the connection to the PLE results database

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

-
metaAnalysisDbIds
+
metaAnalysisDbIds

metaAnalysisDbIds

Value

- - -

the PLE propensity score distribution content server

+

the PLE propensity score distribution content server

See also

-

Other Estimation: +

Other Estimation: cohortMethodAttritionServer(), cohortMethodAttritionViewer(), cohortMethodCovariateBalanceServer(), @@ -171,15 +174,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortMethodPropensityScoreDistViewer.html b/docs/reference/cohortMethodPropensityScoreDistViewer.html index c4a7e2fd..da6bd95d 100644 --- a/docs/reference/cohortMethodPropensityScoreDistViewer.html +++ b/docs/reference/cohortMethodPropensityScoreDistViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,19 +107,19 @@

The module viewer for rendering the propensity score distribution

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the cohort method propensity score distribution

+

The user interface to the cohort method propensity score distribution

See also

-

Other Estimation: +

Other Estimation: cohortMethodAttritionServer(), cohortMethodAttritionViewer(), cohortMethodCovariateBalanceServer(), @@ -149,15 +152,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortMethodSystematicErrorServer.html b/docs/reference/cohortMethodSystematicErrorServer.html index 0f252d3d..569f0cf3 100644 --- a/docs/reference/cohortMethodSystematicErrorServer.html +++ b/docs/reference/cohortMethodSystematicErrorServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -109,31 +112,31 @@

The module server for rendering the systematic error objects

Arguments

-
id
+ + +
id

the unique reference id for the module

-
selectedRow
+
selectedRow

the selected row from the main results table

-
connectionHandler
+
connectionHandler

the connection handler to the result databases

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

Value

- - -

the PLE systematic error content server

+

the PLE systematic error content server

See also

-

Other Estimation: +

Other Estimation: cohortMethodAttritionServer(), cohortMethodAttritionViewer(), cohortMethodCovariateBalanceServer(), @@ -166,15 +169,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortMethodSystematicErrorViewer.html b/docs/reference/cohortMethodSystematicErrorViewer.html index 802e49bb..9f3e5968 100644 --- a/docs/reference/cohortMethodSystematicErrorViewer.html +++ b/docs/reference/cohortMethodSystematicErrorViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,19 +107,19 @@

The module viewer for rendering the PLE systematic error objects

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the cohort method systematic error module

+

The user interface to the cohort method systematic error module

See also

-

Other Estimation: +

Other Estimation: cohortMethodAttritionServer(), cohortMethodAttritionViewer(), cohortMethodCovariateBalanceServer(), @@ -149,15 +152,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/cohortOverlapView.html b/docs/reference/cohortOverlapView.html index 9ba81967..aa8359cf 100644 --- a/docs/reference/cohortOverlapView.html +++ b/docs/reference/cohortOverlapView.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,13 +107,15 @@

Cohort Overlap View

Arguments

-
id
+ + +
id

Namespace Id - use namespaced id ns("cohortOverlap") inside diagnosticsExplorer module

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortCountsView(), cohortDefinitionsModule(), @@ -145,15 +150,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/compareCohortCharacterizationView.html b/docs/reference/compareCohortCharacterizationView.html index 2b58695e..7633f18f 100644 --- a/docs/reference/compareCohortCharacterizationView.html +++ b/docs/reference/compareCohortCharacterizationView.html @@ -3,7 +3,7 @@ - +
- +
@@ -107,17 +110,19 @@

compare characterization view

Arguments

-
id
+ + +
id

Namespace Id - use namespaced id ns("compareCohortCharacterization") inside diagnosticsExplorer module

-
title
+
title

Optional string title field

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortCountsView(), cohortDefinitionsModule(), @@ -152,15 +157,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/conceptsInDataSourceView.html b/docs/reference/conceptsInDataSourceView.html index 26065376..b964d042 100644 --- a/docs/reference/conceptsInDataSourceView.html +++ b/docs/reference/conceptsInDataSourceView.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,13 +107,15 @@

concepts In DataSource View

Arguments

-
id
+ + +
id

Namespace Id - use namespaced id ns("conceptsInDataSource") inside diagnosticsExplorer module

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortCountsView(), cohortDefinitionsModule(), @@ -145,15 +150,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/createCdDatabaseDataSource.html b/docs/reference/createCdDatabaseDataSource.html index 2edf10c7..4aef35ff 100644 --- a/docs/reference/createCdDatabaseDataSource.html +++ b/docs/reference/createCdDatabaseDataSource.html @@ -5,7 +5,7 @@ - +
- +
@@ -116,35 +119,35 @@

Create a CD data source from a database

Arguments

-
connectionHandler
+ + +
connectionHandler

An instance of a ResultModelManager::connectionHander - manages a connection to a database.

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

-
dataModelSpecificationsPath
+
dataModelSpecificationsPath

The path to a file containing specifications for the data model used by the database.

-
dataMigrationsRef
+
dataMigrationsRef

The path to a file listing all migrations for the data model that should have been applied

-
displayProgress
+
displayProgress

display a progress messaage (can only be used inside a shiny reactive context)

Value

- - -

An object of class `CdDataSource`.

+

An object of class `CdDataSource`.

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortCountsView(), cohortDefinitionsModule(), @@ -179,15 +182,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/createCustomColDefList.html b/docs/reference/createCustomColDefList.html index 4e388552..b48f1f44 100644 --- a/docs/reference/createCustomColDefList.html +++ b/docs/reference/createCustomColDefList.html @@ -3,7 +3,7 @@ - +
- +
@@ -110,47 +113,47 @@

Creating a list of custom column definitions for use in reactables

Arguments

-
rawColNames
+ + +
rawColNames

The raw column names taken directly from the source data table that are to be overwritten in the reactable

-
niceColNames
-

The formatted column names that will appear as-specified in +

niceColNames
+

The formatted column names that will appear as-specified in the reactable

-
tooltipText
-

The text to be displayed in a toolTip when hovering over the +

tooltipText
+

The text to be displayed in a toolTip when hovering over the column in the reactable

-
case
+
case

Optional argument to convert raw column names to snake or camel case. Defaults to NULL and preserves whatever raw column names are passed in

-
customColDefOptions
+
customColDefOptions

A list of lists, where the inner lists are any custom options from reactable::colDef for each column

Value

- - -

A named list of reactable::colDef objects

+

A named list of reactable::colDef objects

See also

-

Other Utils: +

Other Utils: datasourcesHelperFile(), datasourcesServer(), datasourcesViewer(), makeButtonLabel(), resultTableServer(), resultTableViewer()

-

Other Utils: +

Other Utils: datasourcesHelperFile(), datasourcesServer(), datasourcesViewer(), @@ -171,15 +174,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/createLargeSqlQueryDt.html b/docs/reference/createLargeSqlQueryDt.html index 4491c923..279acb72 100644 --- a/docs/reference/createLargeSqlQueryDt.html +++ b/docs/reference/createLargeSqlQueryDt.html @@ -5,7 +5,7 @@ - +
- +
@@ -113,26 +116,28 @@

Create Large Sql Query Data Table

Arguments

-
connectionHandler
+ + +
connectionHandler

ResultModelManager connectionHandler instance

-
connectionDetails
+
connectionDetails

DatabaseConnector connectionDetails instance

-
baseQuery
+
baseQuery

base sql query

-
countQuery
+
countQuery

count query string (should match query). Can be auto generated with sub query (default) but this will likely result in slow results

See also

-

Other LargeTables: +

Other LargeTables: largeTableServer(), largeTableView()

@@ -149,15 +154,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/dataDiagnosticDrillServer.html b/docs/reference/dataDiagnosticDrillServer.html index a75e3083..62d0f9db 100644 --- a/docs/reference/dataDiagnosticDrillServer.html +++ b/docs/reference/dataDiagnosticDrillServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,23 +107,23 @@

The module server for exploring prediction summary results

Arguments

-
id
+ + +
id

the unique reference id for the module

-
connectionHandler
+
connectionHandler

the connection to the prediction result database

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

Value

- - -

The server to the summary module

+

The server to the summary module

Details

@@ -128,7 +131,7 @@

Details

See also

-

Other DataDiagnostics: +

Other DataDiagnostics: dataDiagnosticDrillViewer(), dataDiagnosticHelperFile(), dataDiagnosticServer(), @@ -149,15 +152,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/dataDiagnosticDrillViewer.html b/docs/reference/dataDiagnosticDrillViewer.html index dcd08cd2..b5e4fa34 100644 --- a/docs/reference/dataDiagnosticDrillViewer.html +++ b/docs/reference/dataDiagnosticDrillViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

The module viewer for exploring data-diagnostic results in more detail

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the summary module

+

The user interface to the summary module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other DataDiagnostics: +

Other DataDiagnostics: dataDiagnosticDrillServer(), dataDiagnosticHelperFile(), dataDiagnosticServer(), @@ -141,15 +144,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/dataDiagnosticHelperFile.html b/docs/reference/dataDiagnosticHelperFile.html index 458085b7..b27f5ff3 100644 --- a/docs/reference/dataDiagnosticHelperFile.html +++ b/docs/reference/dataDiagnosticHelperFile.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,9 +107,7 @@

The location of the data-diagnostic module helper file

Value

- - -

string location of the data-diagnostic helper file

+

string location of the data-diagnostic helper file

Details

@@ -114,7 +115,7 @@

Details

See also

-

Other DataDiagnostics: +

Other DataDiagnostics: dataDiagnosticDrillServer(), dataDiagnosticDrillViewer(), dataDiagnosticServer(), @@ -135,15 +136,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/dataDiagnosticServer.html b/docs/reference/dataDiagnosticServer.html index 9335f5de..dc10ee98 100644 --- a/docs/reference/dataDiagnosticServer.html +++ b/docs/reference/dataDiagnosticServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -108,23 +111,23 @@

The module server for exploring data-diagnostic

Arguments

-
id
+ + +
id

the unique reference id for the module

-
connectionHandler
+
connectionHandler

a connection to the database with the results

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the data-diagnostic result schema

Value

- - -

The server for the data-diagnostic module

+

The server for the data-diagnostic module

Details

@@ -132,7 +135,7 @@

Details

See also

-

Other DataDiagnostics: +

Other DataDiagnostics: dataDiagnosticDrillServer(), dataDiagnosticDrillViewer(), dataDiagnosticHelperFile(), @@ -153,15 +156,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/dataDiagnosticSummaryServer.html b/docs/reference/dataDiagnosticSummaryServer.html index 3e540d66..0e44f980 100644 --- a/docs/reference/dataDiagnosticSummaryServer.html +++ b/docs/reference/dataDiagnosticSummaryServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,23 +107,23 @@

The module server for exploring prediction summary results

Arguments

-
id
+ + +
id

the unique reference id for the module

-
connectionHandler
+
connectionHandler

the connection to the prediction result database

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

Value

- - -

The server to the summary module

+

The server to the summary module

Details

@@ -128,7 +131,7 @@

Details

See also

-

Other DataDiagnostics: +

Other DataDiagnostics: dataDiagnosticDrillServer(), dataDiagnosticDrillViewer(), dataDiagnosticHelperFile(), @@ -149,15 +152,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/dataDiagnosticSummaryViewer.html b/docs/reference/dataDiagnosticSummaryViewer.html index a0256093..b6767385 100644 --- a/docs/reference/dataDiagnosticSummaryViewer.html +++ b/docs/reference/dataDiagnosticSummaryViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

The module viewer for exploring data-diagnostic summary results

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the summary module

+

The user interface to the summary module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other DataDiagnostics: +

Other DataDiagnostics: dataDiagnosticDrillServer(), dataDiagnosticDrillViewer(), dataDiagnosticHelperFile(), @@ -141,15 +144,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/dataDiagnosticViewer.html b/docs/reference/dataDiagnosticViewer.html index f961a438..0a521298 100644 --- a/docs/reference/dataDiagnosticViewer.html +++ b/docs/reference/dataDiagnosticViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

The module viewer for exploring data-diagnostic

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the data-diagnostic viewer module

+

The user interface to the data-diagnostic viewer module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other DataDiagnostics: +

Other DataDiagnostics: dataDiagnosticDrillServer(), dataDiagnosticDrillViewer(), dataDiagnosticHelperFile(), @@ -141,15 +144,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/databaseInformationView.html b/docs/reference/databaseInformationView.html index 80f092e6..2fe605ec 100644 --- a/docs/reference/databaseInformationView.html +++ b/docs/reference/databaseInformationView.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,13 +107,15 @@

database Information View

Arguments

-
id
+ + +
id

Namespace Id - use namespaced id ns("databaseInformation") inside diagnosticsExplorer module

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortCountsView(), cohortDefinitionsModule(), @@ -145,15 +150,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/datasourcesHelperFile.html b/docs/reference/datasourcesHelperFile.html index e4c54363..b8556914 100644 --- a/docs/reference/datasourcesHelperFile.html +++ b/docs/reference/datasourcesHelperFile.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,20 +107,18 @@

Define the helper file for the module

Value

- - -

The helper html file for the datasources module

+

The helper html file for the datasources module

See also

-

Other Utils: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/datasourcesServer.html b/docs/reference/datasourcesServer.html index 82cb6f10..75c99a5d 100644 --- a/docs/reference/datasourcesServer.html +++ b/docs/reference/datasourcesServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,34 +107,34 @@

The server function for the datasources module

Arguments

-
id
+ + +
id

The unique id for the datasources server namespace

-
connectionHandler
+
connectionHandler

A connection to the database with the results

-
resultDatabaseSettings
+
resultDatabaseSettings

A named list containing the cohort generator results database details (schema, table prefix)

Value

- - -

The server for the datasources module

+

The server for the datasources module

See also

-

Other Utils: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/datasourcesViewer.html b/docs/reference/datasourcesViewer.html index 728f4b32..c5246b1a 100644 --- a/docs/reference/datasourcesViewer.html +++ b/docs/reference/datasourcesViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,26 +107,26 @@

The viewer function for hte datasources module

Arguments

-
id
+ + +
id

The unique id for the datasources viewer namespace

Value

- - -

The UI for the datasources module

+

The UI for the datasources module

See also

-

Other Utils: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/estimationHelperFile.html b/docs/reference/estimationHelperFile.html index 75ab4e3a..c49bf5c3 100644 --- a/docs/reference/estimationHelperFile.html +++ b/docs/reference/estimationHelperFile.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,9 +107,7 @@

The location of the estimation module helper file

Value

- - -

string location of the characterization helper file

+

string location of the characterization helper file

Details

@@ -114,7 +115,7 @@

Details

See also

-

Other Estimation: +

Other Estimation: cohortMethodAttritionServer(), cohortMethodAttritionViewer(), cohortMethodCovariateBalanceServer(), @@ -147,15 +148,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/estimationServer.html b/docs/reference/estimationServer.html index 6d53766d..daffbd3c 100644 --- a/docs/reference/estimationServer.html +++ b/docs/reference/estimationServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -108,23 +111,23 @@

The module server for exploring estimation studies

Arguments

-
id
+ + +
id

the unique reference id for the module

-
connectionHandler
+
connectionHandler

a connection to the database with the results

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the characterization result schema, dbms, tablePrefix, databaseTable and cgTablePrefix

Value

- - -

The server for the estimation module

+

The server for the estimation module

Details

@@ -132,7 +135,7 @@

Details

See also

-

Other Estimation: +

Other Estimation: cohortMethodAttritionServer(), cohortMethodAttritionViewer(), cohortMethodCovariateBalanceServer(), @@ -165,15 +168,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/estimationViewer.html b/docs/reference/estimationViewer.html index 1e4b5261..9b59594e 100644 --- a/docs/reference/estimationViewer.html +++ b/docs/reference/estimationViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

The module viewer for exploring characterization studies

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the characterization viewer module

+

The user interface to the characterization viewer module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other Estimation: +

Other Estimation: cohortMethodAttritionServer(), cohortMethodAttritionViewer(), cohortMethodCovariateBalanceServer(), @@ -153,15 +156,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/getCirceRenderedExpression.html b/docs/reference/getCirceRenderedExpression.html index dbf3b9cd..e1b4c58d 100644 --- a/docs/reference/getCirceRenderedExpression.html +++ b/docs/reference/getCirceRenderedExpression.html @@ -3,7 +3,7 @@ - +
- +
@@ -108,29 +111,29 @@

Returns list with circe generated documentation

Arguments

-
cohortDefinition
+ + +
cohortDefinition

An R object (list) with a list representation of the cohort definition expression, that may be converted to a cohort expression JSON using RJSONIO::toJSON(x = cohortDefinition, digits = 23, pretty = TRUE)

-
cohortName
+
cohortName

Name for the cohort definition

-
includeConceptSets
+
includeConceptSets

Do you want to inclued concept set in the documentation

Value

- - -

list object

+

list object

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortCountsView(), cohortDefinitionsModule(), @@ -165,15 +168,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/getEnabledCdReports.html b/docs/reference/getEnabledCdReports.html index afbaffe0..03b3d553 100644 --- a/docs/reference/getEnabledCdReports.html +++ b/docs/reference/getEnabledCdReports.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,13 +107,15 @@

Get enable cd reports from available data

Arguments

-
dataSource
+ + +
dataSource

Cohort diagnostics data source

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortCountsView(), cohortDefinitionsModule(), @@ -145,15 +150,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/getExampleConnectionDetails.html b/docs/reference/getExampleConnectionDetails.html index 5d1acf1e..69652fe9 100644 --- a/docs/reference/getExampleConnectionDetails.html +++ b/docs/reference/getExampleConnectionDetails.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,13 +107,11 @@

A connection details to an example result database

Value

- - -

The connection details to an example result database

+

The connection details to an example result database

Details

-

Finds the location within the package of an sqlite database with example results for 1) CohortGenerator, +

Finds the location within the package of an sqlite database with example results for 1) CohortGenerator, 2) Characterization, 3) PatientLevelPrediction, 4) CohortMethod, 5) SelfControlledCaseSeries and 6) CohortIncidence

@@ -126,15 +127,15 @@

Details

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/getLogoImage.html b/docs/reference/getLogoImage.html index 7a15d928..cdfe1c5b 100644 --- a/docs/reference/getLogoImage.html +++ b/docs/reference/getLogoImage.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,9 +107,7 @@

The location of the OHDSI logo

Value

- - -

string location of the OHDSI logo

+

string location of the OHDSI logo

Details

@@ -125,15 +126,15 @@

Details

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/homeHelperFile.html b/docs/reference/homeHelperFile.html index f625900b..8a820c9d 100644 --- a/docs/reference/homeHelperFile.html +++ b/docs/reference/homeHelperFile.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,9 +107,7 @@

The location of the home module helper file

Value

- - -

string location of the home helper file

+

string location of the home helper file

Details

@@ -114,7 +115,7 @@

Details

See also

-

Other Home: +

Other Home: homeServer(), homeViewer()

@@ -131,15 +132,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/homeServer.html b/docs/reference/homeServer.html index af67ea4e..356aae4e 100644 --- a/docs/reference/homeServer.html +++ b/docs/reference/homeServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,23 +107,23 @@

The module server for exploring home

Arguments

-
id
+ + +
id

the unique reference id for the module

-
connectionHandler
+
connectionHandler

a connection to the database with the results

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the prediction result schema and connection details

Value

- - -

The server for the home module

+

The server for the home module

Details

@@ -128,7 +131,7 @@

Details

See also

-

Other Home: +

Other Home: homeHelperFile(), homeViewer()

@@ -145,15 +148,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/homeViewer.html b/docs/reference/homeViewer.html index e8a509d2..3c4c2085 100644 --- a/docs/reference/homeViewer.html +++ b/docs/reference/homeViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

The module viewer for exploring home

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the home viewer module

+

The user interface to the home viewer module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other Home: +

Other Home: homeHelperFile(), homeServer()

@@ -137,15 +140,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/incidenceRatesView.html b/docs/reference/incidenceRatesView.html index 8051dbcc..6f704fe7 100644 --- a/docs/reference/incidenceRatesView.html +++ b/docs/reference/incidenceRatesView.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,13 +107,15 @@

incidence Rates View

Arguments

-
id
+ + +
id

Namespace Id - use namespaced id ns("incidenceRates") inside diagnosticsExplorer module

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortCountsView(), cohortDefinitionsModule(), @@ -145,15 +150,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/inclusionRulesView.html b/docs/reference/inclusionRulesView.html index 162511c5..b9be562c 100644 --- a/docs/reference/inclusionRulesView.html +++ b/docs/reference/inclusionRulesView.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,13 +107,15 @@

inclusion Rules View

Arguments

-
id
+ + +
id

Namespace Id - use namespaced id ns("inclusionRules") inside diagnosticsExplorer module

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortCountsView(), cohortDefinitionsModule(), @@ -145,15 +150,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/index.html b/docs/reference/index.html index b4e80c30..befe20c7 100644 --- a/docs/reference/index.html +++ b/docs/reference/index.html @@ -1,9 +1,9 @@ -Function reference • OhdsiShinyModulesPackage index • OhdsiShinyModules - +
- +
@@ -581,13 +584,13 @@

Large Table

Utilities for tables that contain large amounts of rows

-

LargeDataTable

- -

Large Data Table

-

createLargeSqlQueryDt()

Create Large Sql Query Data Table

+ +

LargeDataTable

+ +

Large Data Table

largeTableServer()

@@ -665,15 +668,15 @@

Home

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/indexEventBreakdownView.html b/docs/reference/indexEventBreakdownView.html index 967c4f1c..fa8d3301 100644 --- a/docs/reference/indexEventBreakdownView.html +++ b/docs/reference/indexEventBreakdownView.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,13 +107,15 @@

Index event breakdown view

Arguments

-
id
+ + +
id

Namespace Id - use namespaced id ns("indexEvents") inside diagnosticsExplorer module

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortCountsView(), cohortDefinitionsModule(), @@ -145,15 +150,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/largeTableServer.html b/docs/reference/largeTableServer.html index 9072de7a..881f075e 100644 --- a/docs/reference/largeTableServer.html +++ b/docs/reference/largeTableServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -111,34 +114,36 @@

Large Table Component Server

Arguments

-
id
+ + +
id

Shiny module id. Must match Large Table Viewer

-
ldt
+
ldt

LargeDataTable instance

-
inputParams
+
inputParams

reactive that returns list of parameters to be passed to ldt

-
modifyData
+
modifyData

optional callback function that takes the data page, page number, page size as parameters must return data.frame compatable instance

-
columns
+
columns

List or reactable returning list of reactable::columnDef objects

-
...
+
...

Additional reactable options (searchable, sortable

See also

-

Other LargeTables: +

Other LargeTables: createLargeSqlQueryDt(), largeTableView()

@@ -155,15 +160,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/largeTableView.html b/docs/reference/largeTableView.html index 29b69dea..3a6ffb46 100644 --- a/docs/reference/largeTableView.html +++ b/docs/reference/largeTableView.html @@ -5,7 +5,7 @@ - +
- +
@@ -113,25 +116,27 @@

Large Table Component Viewer

Arguments

-
id
+ + +
id

Shiny module id. Must match largeTableServer

-
pageSizeChoices
+
pageSizeChoices

numeric selection options for pages

-
selectedPageSize
+
selectedPageSize

numeric selection options for pages

-
fullDownloads
+
fullDownloads

allow download button of full dataset from query

See also

-

Other LargeTables: +

Other LargeTables: createLargeSqlQueryDt(), largeTableServer()

@@ -148,15 +153,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/makeButtonLabel.html b/docs/reference/makeButtonLabel.html index 187fce70..dfef80fa 100644 --- a/docs/reference/makeButtonLabel.html +++ b/docs/reference/makeButtonLabel.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,26 +107,26 @@

Make a label for an html button

Arguments

-
label
+ + +
label

The desired label for hte button

Value

- - -

html code to make a button label

+

html code to make a button label

See also

-

Other Utils: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/orpahanConceptsView.html b/docs/reference/orpahanConceptsView.html index 9c52f45f..74c32b1a 100644 --- a/docs/reference/orpahanConceptsView.html +++ b/docs/reference/orpahanConceptsView.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,13 +107,15 @@

Orphan Concepts View

Arguments

-
id
+ + +
id

Namespace Id - use namespaced id ns("orphanConcepts") inside diagnosticsExplorer module

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortCountsView(), cohortDefinitionsModule(), @@ -131,7 +136,7 @@

See also

indexEventBreakdownView(), timeDistributionsView(), visitContextView()

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortCountsView(), cohortDefinitionsModule(), @@ -166,15 +171,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionCalibrationServer.html b/docs/reference/patientLevelPredictionCalibrationServer.html index 2864b7f4..bd79675b 100644 --- a/docs/reference/patientLevelPredictionCalibrationServer.html +++ b/docs/reference/patientLevelPredictionCalibrationServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -110,31 +113,31 @@

The module server for exploring prediction validation results

Arguments

-
id
+ + +
id

the unique reference id for the module

-
performanceId
+
performanceId

the performance id in the database

-
connectionHandler
+
connectionHandler

the connection to the prediction result database

-
inputSingleView
+
inputSingleView

the current tab

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

Value

- - -

The server to the prediction calibration module

+

The server to the prediction calibration module

Details

@@ -142,7 +145,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionCalibrationViewer.html b/docs/reference/patientLevelPredictionCalibrationViewer.html index 4d58ab9e..4ea22e49 100644 --- a/docs/reference/patientLevelPredictionCalibrationViewer.html +++ b/docs/reference/patientLevelPredictionCalibrationViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

The module viewer for exploring prediction model calibration results

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the prediction model calibration module

+

The user interface to the prediction model calibration module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionCovariateSummaryServer.html b/docs/reference/patientLevelPredictionCovariateSummaryServer.html index 300ee090..26c9a008 100644 --- a/docs/reference/patientLevelPredictionCovariateSummaryServer.html +++ b/docs/reference/patientLevelPredictionCovariateSummaryServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -112,39 +115,39 @@

The module server for exploring prediction covariate summary results

Arguments

-
id
+ + +
id

the unique reference id for the module

-
modelDesignId
+
modelDesignId

unique id for the model design

-
developmentDatabaseId
+
developmentDatabaseId

unique id for the development database

-
performanceId
+
performanceId

unique id for the performance results

-
connectionHandler
+
connectionHandler

the connection to the prediction result database

-
inputSingleView
+
inputSingleView

the current tab

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

Value

- - -

The server to the covariate summary module

+

The server to the covariate summary module

Details

@@ -152,7 +155,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionCovariateSummaryViewer.html b/docs/reference/patientLevelPredictionCovariateSummaryViewer.html index ab3b3670..52d2caba 100644 --- a/docs/reference/patientLevelPredictionCovariateSummaryViewer.html +++ b/docs/reference/patientLevelPredictionCovariateSummaryViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

The module viewer for exploring prediction covariate summary results

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the covariate summary module

+

The user interface to the covariate summary module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionCutoffServer.html b/docs/reference/patientLevelPredictionCutoffServer.html index 3594b29c..ca40a92c 100644 --- a/docs/reference/patientLevelPredictionCutoffServer.html +++ b/docs/reference/patientLevelPredictionCutoffServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -110,31 +113,31 @@

The module server for exploring prediction cut-off results

Arguments

-
id
+ + +
id

the unique reference id for the module

-
performanceId
+
performanceId

the performance id in the database

-
connectionHandler
+
connectionHandler

the connection to the prediction result database

-
inputSingleView
+
inputSingleView

the current tab

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

Value

- - -

The server to the prediction cut-off module

+

The server to the prediction cut-off module

Details

@@ -142,7 +145,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionCutoffViewer.html b/docs/reference/patientLevelPredictionCutoffViewer.html index 261243b4..001ab905 100644 --- a/docs/reference/patientLevelPredictionCutoffViewer.html +++ b/docs/reference/patientLevelPredictionCutoffViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

The module viewer for exploring prediction cut-off results

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the prediction cut-off module

+

The user interface to the prediction cut-off module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionDesignSummaryServer.html b/docs/reference/patientLevelPredictionDesignSummaryServer.html index b8672abf..3b340c28 100644 --- a/docs/reference/patientLevelPredictionDesignSummaryServer.html +++ b/docs/reference/patientLevelPredictionDesignSummaryServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -108,23 +111,23 @@

The module server for exploring prediction designs in the results

Arguments

-
id
+ + +
id

the unique reference id for the module

-
connectionHandler
+
connectionHandler

the connection to the prediction result database

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

Value

- - -

The server to the prediction design module

+

The server to the prediction design module

Details

@@ -132,7 +135,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionDesignSummaryViewer.html b/docs/reference/patientLevelPredictionDesignSummaryViewer.html index fc18ade8..193e12ed 100644 --- a/docs/reference/patientLevelPredictionDesignSummaryViewer.html +++ b/docs/reference/patientLevelPredictionDesignSummaryViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

The module viewer for exploring prediction designs that have been run

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the prediction design module

+

The user interface to the prediction design module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionDiagnosticsServer.html b/docs/reference/patientLevelPredictionDiagnosticsServer.html index c5c61e2d..75b66a72 100644 --- a/docs/reference/patientLevelPredictionDiagnosticsServer.html +++ b/docs/reference/patientLevelPredictionDiagnosticsServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -109,27 +112,27 @@

The module server for exploring prediction diagnostic results

Arguments

-
id
+ + +
id

the unique reference id for the module

-
modelDesignId
+
modelDesignId

the unique id for the model design

-
connectionHandler
+
connectionHandler

the connection to the prediction result database

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

Value

- - -

The server to the prediction diagnostic module

+

The server to the prediction diagnostic module

Details

@@ -137,7 +140,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionDiagnosticsViewer.html b/docs/reference/patientLevelPredictionDiagnosticsViewer.html index 16a5f280..73c6afbf 100644 --- a/docs/reference/patientLevelPredictionDiagnosticsViewer.html +++ b/docs/reference/patientLevelPredictionDiagnosticsViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

The module viewer for exploring prediction diagnostic results

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the prediction diagnostic module

+

The user interface to the prediction diagnostic module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionDiscriminationServer.html b/docs/reference/patientLevelPredictionDiscriminationServer.html index 201fea37..8935506b 100644 --- a/docs/reference/patientLevelPredictionDiscriminationServer.html +++ b/docs/reference/patientLevelPredictionDiscriminationServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -110,31 +113,31 @@

The module server for exploring prediction model discrimination results

Arguments

-
id
+ + +
id

the unique reference id for the module

-
performanceId
+
performanceId

the performance id in the database

-
connectionHandler
+
connectionHandler

the connection to the prediction result database

-
inputSingleView
+
inputSingleView

the current tab

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

Value

- - -

The server to the model discrimination module

+

The server to the model discrimination module

Details

@@ -142,7 +145,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionDiscriminationViewer.html b/docs/reference/patientLevelPredictionDiscriminationViewer.html index 73819ec8..b9fae3a9 100644 --- a/docs/reference/patientLevelPredictionDiscriminationViewer.html +++ b/docs/reference/patientLevelPredictionDiscriminationViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

The module viewer for exploring prediction model discrimination results

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the model discrimination results module

+

The user interface to the model discrimination results module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionHelperFile.html b/docs/reference/patientLevelPredictionHelperFile.html index 8acbbb03..1326b561 100644 --- a/docs/reference/patientLevelPredictionHelperFile.html +++ b/docs/reference/patientLevelPredictionHelperFile.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,9 +107,7 @@

The location of the prediction module helper file

Value

- - -

string location of the prediction helper file

+

string location of the prediction helper file

Details

@@ -114,7 +115,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionModelSummaryServer.html b/docs/reference/patientLevelPredictionModelSummaryServer.html index e3b6ab8a..390aeae5 100644 --- a/docs/reference/patientLevelPredictionModelSummaryServer.html +++ b/docs/reference/patientLevelPredictionModelSummaryServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -109,27 +112,27 @@

The module server for exploring prediction summary results

Arguments

-
id
+ + +
id

the unique reference id for the module

-
connectionHandler
+
connectionHandler

the connection to the prediction result database

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

-
modelDesignId
+
modelDesignId

a reactable id specifying the prediction model design identifier

Value

- - -

The server to the summary module

+

The server to the summary module

Details

@@ -137,7 +140,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionModelSummaryViewer.html b/docs/reference/patientLevelPredictionModelSummaryViewer.html index edf6c8d6..fcf3d5ac 100644 --- a/docs/reference/patientLevelPredictionModelSummaryViewer.html +++ b/docs/reference/patientLevelPredictionModelSummaryViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

The module viewer for exploring prediction summary results

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the summary module

+

The user interface to the summary module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionNbServer.html b/docs/reference/patientLevelPredictionNbServer.html index 5f03799b..2887f8ee 100644 --- a/docs/reference/patientLevelPredictionNbServer.html +++ b/docs/reference/patientLevelPredictionNbServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -110,31 +113,31 @@

The module server for exploring prediction net-benefit results

Arguments

-
id
+ + +
id

the unique reference id for the module

-
performanceId
+
performanceId

the performance id in the database

-
connectionHandler
+
connectionHandler

the connection to the prediction result database

-
inputSingleView
+
inputSingleView

the current tab

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

Value

- - -

The server to the net-benefit module

+

The server to the net-benefit module

Details

@@ -142,7 +145,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionNbViewer.html b/docs/reference/patientLevelPredictionNbViewer.html index 4c234760..bf523c1e 100644 --- a/docs/reference/patientLevelPredictionNbViewer.html +++ b/docs/reference/patientLevelPredictionNbViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

The module viewer for exploring prediction net-benefit results

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the net-benefit module

+

The user interface to the net-benefit module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionServer.html b/docs/reference/patientLevelPredictionServer.html index 395816b4..5ecb403f 100644 --- a/docs/reference/patientLevelPredictionServer.html +++ b/docs/reference/patientLevelPredictionServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -108,23 +111,23 @@

The module server for exploring PatientLevelPrediction

Arguments

-
id
+ + +
id

the unique reference id for the module

-
connectionHandler
+
connectionHandler

a connection to the database with the results

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the prediction result schema and connection details

Value

- - -

The server for the PatientLevelPrediction module

+

The server for the PatientLevelPrediction module

Details

@@ -132,7 +135,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionSettingsServer.html b/docs/reference/patientLevelPredictionSettingsServer.html index 2417f42b..92b6a0b3 100644 --- a/docs/reference/patientLevelPredictionSettingsServer.html +++ b/docs/reference/patientLevelPredictionSettingsServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -112,39 +115,39 @@

The module server for exploring prediction settings

Arguments

-
id
+ + +
id

the unique reference id for the module

-
modelDesignId
+
modelDesignId

unique id for the model design

-
developmentDatabaseId
+
developmentDatabaseId

unique id for the development database

-
performanceId
+
performanceId

unique id for the performance results

-
connectionHandler
+
connectionHandler

the connection to the prediction result database

-
inputSingleView
+
inputSingleView

the current tab

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

Value

- - -

The server to the settings module

+

The server to the settings module

Details

@@ -152,7 +155,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionSettingsViewer.html b/docs/reference/patientLevelPredictionSettingsViewer.html index 80eaf807..af3800f0 100644 --- a/docs/reference/patientLevelPredictionSettingsViewer.html +++ b/docs/reference/patientLevelPredictionSettingsViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

The module viewer for exploring prediction settings

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the settings module

+

The user interface to the settings module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionValidationServer.html b/docs/reference/patientLevelPredictionValidationServer.html index 6685163e..ad1460c9 100644 --- a/docs/reference/patientLevelPredictionValidationServer.html +++ b/docs/reference/patientLevelPredictionValidationServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -112,39 +115,39 @@

The module server for exploring prediction validation results

Arguments

-
id
+ + +
id

the unique reference id for the module

-
modelDesignId
+
modelDesignId

identifier for the model design

-
developmentDatabaseId
+
developmentDatabaseId

identifier for the development database

-
performanceId
+
performanceId

identifier for the performance

-
connectionHandler
+
connectionHandler

the connection to the prediction result database

-
inputSingleView
+
inputSingleView

the current tab

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the result schema and prefixes

Value

- - -

The server to the validation module

+

The server to the validation module

Details

@@ -152,7 +155,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionValidationViewer.html b/docs/reference/patientLevelPredictionValidationViewer.html index e79e22ad..6eee506d 100644 --- a/docs/reference/patientLevelPredictionValidationViewer.html +++ b/docs/reference/patientLevelPredictionValidationViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

The module viewer for exploring prediction validation results

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the validation module

+

The user interface to the validation module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/patientLevelPredictionViewer.html b/docs/reference/patientLevelPredictionViewer.html index 332d3f10..50532578 100644 --- a/docs/reference/patientLevelPredictionViewer.html +++ b/docs/reference/patientLevelPredictionViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

The module viewer for exploring PatientLevelPrediction

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the PatientLevelPrediction viewer module

+

The user interface to the PatientLevelPrediction viewer module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other PatientLevelPrediction: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/phevaluatorHelperFile.html b/docs/reference/phevaluatorHelperFile.html index f98d15c6..375dc50a 100644 --- a/docs/reference/phevaluatorHelperFile.html +++ b/docs/reference/phevaluatorHelperFile.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,9 +107,7 @@

The location of the phevaluator module helper file

Value

- - -

String location of the phevaluator helper file

+

String location of the phevaluator helper file

Details

@@ -114,10 +115,10 @@

Details

See also

-

Other PheValuator: +

Other PheValuator: phevaluatorServer(), phevaluatorViewer()

-

Other PheValuator: +

Other PheValuator: phevaluatorServer(), phevaluatorViewer()

@@ -134,15 +135,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/phevaluatorServer.html b/docs/reference/phevaluatorServer.html index b162161d..6724cf57 100644 --- a/docs/reference/phevaluatorServer.html +++ b/docs/reference/phevaluatorServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,30 +107,30 @@

The module server for the main phevaluator module

Arguments

-
id
+ + +
id

The unique reference id for the module

-
connectionHandler
+
connectionHandler

A connection to the database with the results

-
resultDatabaseSettings
+
resultDatabaseSettings

A named list containing the cohort generator results database details (schema, table prefix)

Value

- - -

The phevaluator main module server

+

The phevaluator main module server

See also

-

Other PheValuator: +

Other PheValuator: phevaluatorHelperFile(), phevaluatorViewer()

-

Other PheValuator: +

Other PheValuator: phevaluatorHelperFile(), phevaluatorViewer()

@@ -144,15 +147,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/phevaluatorViewer.html b/docs/reference/phevaluatorViewer.html index af8507e9..8b02852b 100644 --- a/docs/reference/phevaluatorViewer.html +++ b/docs/reference/phevaluatorViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,22 +107,22 @@

The viewer of the phevaluator module

Arguments

-
id
+ + +
id

The unique reference id for the module

Value

- - -

The user interface to the phevaluator results viewer

+

The user interface to the phevaluator results viewer

See also

-

Other PheValuator: +

Other PheValuator: phevaluatorHelperFile(), phevaluatorServer()

-

Other PheValuator: +

Other PheValuator: phevaluatorHelperFile(), phevaluatorServer()

@@ -136,15 +139,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/reportHelperFile.html b/docs/reference/reportHelperFile.html index 719b2588..747703a7 100644 --- a/docs/reference/reportHelperFile.html +++ b/docs/reference/reportHelperFile.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,9 +107,7 @@

The location of the report module helper file

Value

- - -

string location of the report helper file

+

string location of the report helper file

Details

@@ -114,7 +115,7 @@

Details

See also

-

Other Report: +

Other Report: reportServer(), reportViewer()

@@ -131,15 +132,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/reportServer.html b/docs/reference/reportServer.html index 0037752a..89590026 100644 --- a/docs/reference/reportServer.html +++ b/docs/reference/reportServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -112,39 +115,39 @@

The module server for the shiny app report module

Arguments

-
id
+ + +
id

the unique reference id for the module

-
connectionHandler
+
connectionHandler

a connection to the database with the results

-
resultDatabaseSettings
+
resultDatabaseSettings

a list containing the characterization result schema, dbms, tablePrefix, databaseTable and cgTablePrefix

-
server
+
server

server for the connection to the results for quarto

-
username
+
username

username for the connection to the results for quarto

-
password
+
password

password for the connection to the results for quarto

-
dbms
+
dbms

dbms for the connection to the results for quarto

Value

- - -

The server for the shiny app home

+

The server for the shiny app home

Details

@@ -152,7 +155,7 @@

Details

See also

-

Other Report: +

Other Report: reportHelperFile(), reportViewer()

@@ -169,15 +172,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/reportViewer.html b/docs/reference/reportViewer.html index 0e88f6ff..1f558053 100644 --- a/docs/reference/reportViewer.html +++ b/docs/reference/reportViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,15 +107,15 @@

The module viewer for the shiny app report module

Arguments

-
id
+ + +
id

the unique reference id for the module

Value

- - -

The user interface to the home page module

+

The user interface to the home page module

Details

@@ -120,7 +123,7 @@

Details

See also

-

Other Report: +

Other Report: reportHelperFile(), reportServer()

@@ -137,15 +140,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/resultTableServer.html b/docs/reference/resultTableServer.html index 0f1bd74a..9d204135 100644 --- a/docs/reference/resultTableServer.html +++ b/docs/reference/resultTableServer.html @@ -3,7 +3,7 @@ - +
- +
@@ -115,63 +118,63 @@

Result Table Server

Arguments

-
id
+ + +
id

string, table id must match resultsTableViewer function

-
df
+
df

reactive that returns a data frame

-
colDefsInput
+
colDefsInput

named list of reactable::colDefs

-
details
+
details

The details of the results such as cohort names and database names

-
selectedCols
+
selectedCols

string vector of columns the reactable should display to start by default. Defaults to ALL if not specified.

-
sortedCols
+
sortedCols

string vector of columns the reactable should sort by by default. Defaults to no sort if not specified.

-
elementId
+
elementId

optional string vector of element Id name for custom dropdown filtering if present in the customColDef list. Defaults to NULL.

-
addActions
+
addActions

add a button row selector column to the table to a column called 'actions'. actions must be a column in df

-
downloadedFileName
+
downloadedFileName

string, desired name of downloaded data file. can use the name from the module that is being used

-
groupBy
+
groupBy

The columns to group by

Value

- - -

shiny module server

+

shiny module server

See also

-

Other Utils: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/resultTableViewer.html b/docs/reference/resultTableViewer.html index 3121d1c1..7f601d85 100644 --- a/docs/reference/resultTableViewer.html +++ b/docs/reference/resultTableViewer.html @@ -3,7 +3,7 @@ - +
- +
@@ -108,34 +111,34 @@

Result Table Viewer

Arguments

-
id
+ + +
id

string

-
downloadedFileName
+
downloadedFileName

string, desired name of downloaded data file. can use the name from the module that is being used

-
boxTitle
+
boxTitle

the title added to the box

Value

- - -

shiny module UI

+

shiny module UI

See also

-

Other Utils: +

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/timeDistributionsView.html b/docs/reference/timeDistributionsView.html index c504ffe5..ade0d56c 100644 --- a/docs/reference/timeDistributionsView.html +++ b/docs/reference/timeDistributionsView.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,13 +107,15 @@

timeDistributions view

Arguments

-
id
+ + +
id

Namespace Id - use namespaced id ns("imeDistributions") inside diagnosticsExplorer module

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortCountsView(), cohortDefinitionsModule(), @@ -145,15 +150,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/reference/visitContextView.html b/docs/reference/visitContextView.html index 10cc2f30..4df4d3fc 100644 --- a/docs/reference/visitContextView.html +++ b/docs/reference/visitContextView.html @@ -3,7 +3,7 @@ - +
- +
@@ -104,13 +107,15 @@

Visit context module view

Arguments

-
id
+ + +
id

Namespace Id - use namespaced id ns("vistConext") inside diagnosticsExplorer module

See also

-

Other CohortDiagnostics: +

Other CohortDiagnostics: cohortCountsModule(), cohortCountsView(), cohortDefinitionsModule(), @@ -145,15 +150,15 @@

See also

-

Site built with pkgdown 2.0.9.

+

Site built with pkgdown 2.1.0.

- - + + diff --git a/docs/sitemap.xml b/docs/sitemap.xml index b2bdf26e..4ac5ca64 100644 --- a/docs/sitemap.xml +++ b/docs/sitemap.xml @@ -1,618 +1,210 @@ - - - - /404.html - - - /articles/AddingShinyModules.html - - - /articles/Characterization.html - - - /articles/CohortDiagnostics.html - - - /articles/CohortMethod.html - - - /articles/Cohorts.html - - - /articles/DataSources.html - - - /articles/EvidenceSynthesis.html - - - /articles/Prediction.html - - - /articles/SelfControlledCaseSeries.html - - - /articles/index.html - - - /authors.html - - - /index.html - - - /news/index.html - - - /reference/LargeDataTable.html - - - /reference/OhdsiShinyModules.html - - - /reference/aboutHelperFile.html - - - /reference/aboutServer.html - - - /reference/aboutViewer.html - - - /reference/characterizationAggregateFeaturesServer.html - - - /reference/characterizationAggregateFeaturesViewer.html - - - /reference/characterizationDechallengeRechallengeServer.html - - - /reference/characterizationDechallengeRechallengeViewer.html - - - /reference/characterizationHelperFile.html - - - /reference/characterizationIncidenceServer.html - - - /reference/characterizationIncidenceViewer.html - - - /reference/characterizationServer.html - - - /reference/characterizationTableServer.html - - - /reference/characterizationTableViewer.html - - - /reference/characterizationTimeToEventServer.html - - - /reference/characterizationTimeToEventViewer.html - - - /reference/characterizationView.html - - - /reference/characterizationViewer.html - - - /reference/cohortCountsModule.html - - - /reference/cohortCountsView.html - - - /reference/cohortDefinitionsModule.html - - - /reference/cohortDefinitionsView.html - - - /reference/cohortDiagCharacterizationView.html - - - /reference/cohortDiagnosticsHelperFile.html - - - /reference/cohortDiagnosticsServer.html - - - /reference/cohortDiagnosticsSever.html - - - /reference/cohortDiagnosticsView.html - - - /reference/cohortGeneratorHelperFile.html - - - /reference/cohortGeneratorServer.html - - - /reference/cohortGeneratorViewer.html - - - /reference/cohortMethodAttritionServer.html - - - /reference/cohortMethodAttritionViewer.html - - - /reference/cohortMethodCovariateBalanceServer.html - - - /reference/cohortMethodCovariateBalanceViewer.html - - - /reference/cohortMethodDiagnosticsSummaryServer.html - - - /reference/cohortMethodDiagnosticsSummaryViewer.html - - - /reference/cohortMethodHelperFile.html - - - /reference/cohortMethodKaplanMeierServer.html - - - /reference/cohortMethodKaplanMeierViewer.html - - - /reference/cohortMethodPopulationCharacteristicsServer.html - - - /reference/cohortMethodPopulationCharacteristicsViewer.html - - - /reference/cohortMethodPowerServer.html - - - /reference/cohortMethodPowerViewer.html - - - /reference/cohortMethodPropensityModelServer.html - - - /reference/cohortMethodPropensityModelViewer.html - - - /reference/cohortMethodPropensityScoreDistServer.html - - - /reference/cohortMethodPropensityScoreDistViewer.html - - - /reference/cohortMethodResultSummaryServer.html - - - /reference/cohortMethodResultSummaryViewer.html - - - /reference/cohortMethodServer.html - - - /reference/cohortMethodSystematicErrorServer.html - - - /reference/cohortMethodSystematicErrorViewer.html - - - /reference/cohortMethodViewer.html - - - /reference/cohortOverlapView.html - - - /reference/compareCohortCharacterizationView.html - - - /reference/conceptsInDataSourceView.html - - - /reference/createCdDatabaseDataSource.html - - - /reference/createCustomColDefList.html - - - /reference/createLargeSqlQueryDt.html - - - /reference/dataDiagnosticDrillServer.html - - - /reference/dataDiagnosticDrillViewer.html - - - /reference/dataDiagnosticHelperFile.html - - - /reference/dataDiagnosticServer.html - - - /reference/dataDiagnosticSummaryServer.html - - - /reference/dataDiagnosticSummaryViewer.html - - - /reference/dataDiagnosticViewer.html - - - /reference/databaseInformationView.html - - - /reference/datasourcesHelperFile.html - - - /reference/datasourcesServer.html - - - /reference/datasourcesViewer.html - - - /reference/descriptionAggregateFeaturesServer.html - - - /reference/descriptionAggregateFeaturesViewer.html - - - /reference/descriptionDechallengeRechallengeServer.html - - - /reference/descriptionDechallengeRechallengeViewer.html - - - /reference/descriptionHelperFile.html - - - /reference/descriptionIncidenceServer.html - - - /reference/descriptionIncidenceViewer.html - - - /reference/descriptionServer.html - - - /reference/descriptionTableServer.html - - - /reference/descriptionTableViewer.html - - - /reference/descriptionTimeToEventServer.html - - - /reference/descriptionTimeToEventViewer.html - - - /reference/descriptionViewer.html - - - /reference/estimationAttritionServer.html - - - /reference/estimationAttritionViewer.html - - - /reference/estimationCovariateBalanceServer.html - - - /reference/estimationCovariateBalanceViewer.html - - - /reference/estimationDiagnosticsSummaryServer.html - - - /reference/estimationDiagnosticsSummaryViewer.html - - - /reference/estimationForestPlotServer.html - - - /reference/estimationForestPlotViewer.html - - - /reference/estimationHelperFile.html - - - /reference/estimationKaplanMeierServer.html - - - /reference/estimationKaplanMeierViewer.html - - - /reference/estimationPopulationCharacteristicsServer.html - - - /reference/estimationPopulationCharacteristicsViewer.html - - - /reference/estimationPowerServer.html - - - /reference/estimationPowerViewer.html - - - /reference/estimationPropensityModelServer.html - - - /reference/estimationPropensityModelViewer.html - - - /reference/estimationPropensityScoreDistServer.html - - - /reference/estimationPropensityScoreDistViewer.html - - - /reference/estimationResultsTableServer.html - - - /reference/estimationResultsTableViewer.html - - - /reference/estimationServer.html - - - /reference/estimationSubgroupsServer.html - - - /reference/estimationSubgroupsViewer.html - - - /reference/estimationSystematicErrorServer.html - - - /reference/estimationSystematicErrorViewer.html - - - /reference/estimationTitlePanelServer.html - - - /reference/estimationTitlePanelViewer.html - - - /reference/estimationViewer.html - - - /reference/evidenceSynthesisHelperFile.html - - - /reference/evidenceSynthesisServer.html - - - /reference/evidenceSynthesisViewer.html - - - /reference/getCirceRenderedExpression.html - - - /reference/getEnabledCdReports.html - - - /reference/getExampleConnectionDetails.html - - - /reference/getLogoImage.html - - - /reference/homeHelperFile.html - - - /reference/homeServer.html - - - /reference/homeViewer.html - - - /reference/incidenceRatesView.html - - - /reference/inclusionRulesView.html - - - /reference/index.html - - - /reference/indexEventBreakdownView.html - - - /reference/largeTableServer.html - - - /reference/largeTableView.html - - - /reference/makeButtonLabel.html - - - /reference/orpahanConceptsView.html - - - /reference/patientLevelPredictionCalibrationServer.html - - - /reference/patientLevelPredictionCalibrationViewer.html - - - /reference/patientLevelPredictionCovariateSummaryServer.html - - - /reference/patientLevelPredictionCovariateSummaryViewer.html - - - /reference/patientLevelPredictionCutoffServer.html - - - /reference/patientLevelPredictionCutoffViewer.html - - - /reference/patientLevelPredictionDesignSummaryServer.html - - - /reference/patientLevelPredictionDesignSummaryViewer.html - - - /reference/patientLevelPredictionDiagnosticsServer.html - - - /reference/patientLevelPredictionDiagnosticsViewer.html - - - /reference/patientLevelPredictionDiscriminationServer.html - - - /reference/patientLevelPredictionDiscriminationViewer.html - - - /reference/patientLevelPredictionHelperFile.html - - - /reference/patientLevelPredictionModelSummaryServer.html - - - /reference/patientLevelPredictionModelSummaryViewer.html - - - /reference/patientLevelPredictionNbServer.html - - - /reference/patientLevelPredictionNbViewer.html - - - /reference/patientLevelPredictionServer.html - - - /reference/patientLevelPredictionSettingsServer.html - - - /reference/patientLevelPredictionSettingsViewer.html - - - /reference/patientLevelPredictionValidationServer.html - - - /reference/patientLevelPredictionValidationViewer.html - - - /reference/patientLevelPredictionViewer.html - - - /reference/phevaluatorHelperFile.html - - - /reference/phevaluatorServer.html - - - /reference/phevaluatorViewer.html - - - /reference/predictionCalibrationServer.html - - - /reference/predictionCalibrationViewer.html - - - /reference/predictionCovariateSummaryServer.html - - - /reference/predictionCovariateSummaryViewer.html - - - /reference/predictionCutoffServer.html - - - /reference/predictionCutoffViewer.html - - - /reference/predictionDesignSummaryServer.html - - - /reference/predictionDesignSummaryViewer.html - - - /reference/predictionDiagnosticsServer.html - - - /reference/predictionDiagnosticsViewer.html - - - /reference/predictionDiscriminationServer.html - - - /reference/predictionDiscriminationViewer.html - - - /reference/predictionHelperFile.html - - - /reference/predictionModelSummaryServer.html - - - /reference/predictionModelSummaryViewer.html - - - /reference/predictionNbServer.html - - - /reference/predictionNbViewer.html - - - /reference/predictionServer.html - - - /reference/predictionSetingsServer.html - - - /reference/predictionSettingsServer.html - - - /reference/predictionSettingsViewer.html - - - /reference/predictionValidationServer.html - - - /reference/predictionValidationViewer.html - - - /reference/predictionViewer.html - - - /reference/reportHelperFile.html - - - /reference/reportServer.html - - - /reference/reportViewer.html - - - /reference/resultTableServer.html - - - /reference/resultTableViewer.html - - - /reference/sccsHelperFile.html - - - /reference/sccsServer.html - - - /reference/sccsView.html - - - /reference/timeDistributionsView.html - - - /reference/visitContextView.html - + +/404.html +/articles/AddingShinyModules.html +/articles/Characterization.html +/articles/CohortDiagnostics.html +/articles/CohortMethod.html +/articles/Cohorts.html +/articles/DataSources.html +/articles/Estimation.html +/articles/EvidenceSynthesis.html +/articles/index.html +/articles/Prediction.html +/articles/ReportGenerator.html +/articles/SelfControlledCaseSeries.html +/authors.html +/index.html +/news/index.html +/reference/aboutHelperFile.html +/reference/aboutServer.html +/reference/aboutViewer.html +/reference/characterizationAggregateFeaturesServer.html +/reference/characterizationAggregateFeaturesViewer.html +/reference/characterizationDechallengeRechallengeServer.html +/reference/characterizationDechallengeRechallengeViewer.html +/reference/characterizationHelperFile.html +/reference/characterizationIncidenceServer.html +/reference/characterizationIncidenceViewer.html +/reference/characterizationServer.html +/reference/characterizationTableServer.html +/reference/characterizationTableViewer.html +/reference/characterizationTimeToEventServer.html +/reference/characterizationTimeToEventViewer.html +/reference/characterizationView.html +/reference/characterizationViewer.html +/reference/cohortCountsModule.html +/reference/cohortCountsView.html +/reference/cohortDefinitionsModule.html +/reference/cohortDefinitionsView.html +/reference/cohortDiagCharacterizationView.html +/reference/cohortDiagnosticsHelperFile.html +/reference/cohortDiagnosticsServer.html +/reference/cohortDiagnosticsSever.html +/reference/cohortDiagnosticsView.html +/reference/cohortGeneratorHelperFile.html +/reference/cohortGeneratorServer.html +/reference/cohortGeneratorViewer.html +/reference/cohortMethodAttritionServer.html +/reference/cohortMethodAttritionViewer.html +/reference/cohortMethodCovariateBalanceServer.html +/reference/cohortMethodCovariateBalanceViewer.html +/reference/cohortMethodDiagnosticsSummaryServer.html +/reference/cohortMethodDiagnosticsSummaryViewer.html +/reference/cohortMethodHelperFile.html +/reference/cohortMethodKaplanMeierServer.html +/reference/cohortMethodKaplanMeierViewer.html +/reference/cohortMethodPopulationCharacteristicsServer.html +/reference/cohortMethodPopulationCharacteristicsViewer.html +/reference/cohortMethodPowerServer.html +/reference/cohortMethodPowerViewer.html +/reference/cohortMethodPropensityModelServer.html +/reference/cohortMethodPropensityModelViewer.html +/reference/cohortMethodPropensityScoreDistServer.html +/reference/cohortMethodPropensityScoreDistViewer.html +/reference/cohortMethodResultSummaryServer.html +/reference/cohortMethodResultSummaryViewer.html +/reference/cohortMethodServer.html +/reference/cohortMethodSystematicErrorServer.html +/reference/cohortMethodSystematicErrorViewer.html +/reference/cohortMethodViewer.html +/reference/cohortOverlapView.html +/reference/compareCohortCharacterizationView.html +/reference/conceptsInDataSourceView.html +/reference/createCdDatabaseDataSource.html +/reference/createCustomColDefList.html +/reference/createLargeSqlQueryDt.html +/reference/databaseInformationView.html +/reference/dataDiagnosticDrillServer.html +/reference/dataDiagnosticDrillViewer.html +/reference/dataDiagnosticHelperFile.html +/reference/dataDiagnosticServer.html +/reference/dataDiagnosticSummaryServer.html +/reference/dataDiagnosticSummaryViewer.html +/reference/dataDiagnosticViewer.html +/reference/datasourcesHelperFile.html +/reference/datasourcesServer.html +/reference/datasourcesViewer.html +/reference/descriptionAggregateFeaturesServer.html +/reference/descriptionAggregateFeaturesViewer.html +/reference/descriptionDechallengeRechallengeServer.html +/reference/descriptionDechallengeRechallengeViewer.html +/reference/descriptionHelperFile.html +/reference/descriptionIncidenceServer.html +/reference/descriptionIncidenceViewer.html +/reference/descriptionServer.html +/reference/descriptionTableServer.html +/reference/descriptionTableViewer.html +/reference/descriptionTimeToEventServer.html +/reference/descriptionTimeToEventViewer.html +/reference/descriptionViewer.html +/reference/estimationAttritionServer.html +/reference/estimationAttritionViewer.html +/reference/estimationCovariateBalanceServer.html +/reference/estimationCovariateBalanceViewer.html +/reference/estimationDiagnosticsSummaryServer.html +/reference/estimationDiagnosticsSummaryViewer.html +/reference/estimationForestPlotServer.html +/reference/estimationForestPlotViewer.html +/reference/estimationHelperFile.html +/reference/estimationKaplanMeierServer.html +/reference/estimationKaplanMeierViewer.html +/reference/estimationPopulationCharacteristicsServer.html +/reference/estimationPopulationCharacteristicsViewer.html +/reference/estimationPowerServer.html +/reference/estimationPowerViewer.html +/reference/estimationPropensityModelServer.html +/reference/estimationPropensityModelViewer.html +/reference/estimationPropensityScoreDistServer.html +/reference/estimationPropensityScoreDistViewer.html +/reference/estimationResultsTableServer.html +/reference/estimationResultsTableViewer.html +/reference/estimationServer.html +/reference/estimationSubgroupsServer.html +/reference/estimationSubgroupsViewer.html +/reference/estimationSystematicErrorServer.html +/reference/estimationSystematicErrorViewer.html +/reference/estimationTitlePanelServer.html +/reference/estimationTitlePanelViewer.html +/reference/estimationViewer.html +/reference/evidenceSynthesisHelperFile.html +/reference/evidenceSynthesisServer.html +/reference/evidenceSynthesisViewer.html +/reference/getCirceRenderedExpression.html +/reference/getEnabledCdReports.html +/reference/getExampleConnectionDetails.html +/reference/getLogoImage.html +/reference/homeHelperFile.html +/reference/homeServer.html +/reference/homeViewer.html +/reference/incidenceRatesView.html +/reference/inclusionRulesView.html +/reference/index.html +/reference/indexEventBreakdownView.html +/reference/LargeDataTable.html +/reference/largeTableServer.html +/reference/largeTableView.html +/reference/makeButtonLabel.html +/reference/OhdsiShinyModules.html +/reference/orpahanConceptsView.html +/reference/patientLevelPredictionCalibrationServer.html +/reference/patientLevelPredictionCalibrationViewer.html +/reference/patientLevelPredictionCovariateSummaryServer.html +/reference/patientLevelPredictionCovariateSummaryViewer.html +/reference/patientLevelPredictionCutoffServer.html +/reference/patientLevelPredictionCutoffViewer.html +/reference/patientLevelPredictionDesignSummaryServer.html +/reference/patientLevelPredictionDesignSummaryViewer.html +/reference/patientLevelPredictionDiagnosticsServer.html +/reference/patientLevelPredictionDiagnosticsViewer.html +/reference/patientLevelPredictionDiscriminationServer.html +/reference/patientLevelPredictionDiscriminationViewer.html +/reference/patientLevelPredictionHelperFile.html +/reference/patientLevelPredictionModelSummaryServer.html +/reference/patientLevelPredictionModelSummaryViewer.html +/reference/patientLevelPredictionNbServer.html +/reference/patientLevelPredictionNbViewer.html +/reference/patientLevelPredictionServer.html +/reference/patientLevelPredictionSettingsServer.html +/reference/patientLevelPredictionSettingsViewer.html +/reference/patientLevelPredictionValidationServer.html +/reference/patientLevelPredictionValidationViewer.html +/reference/patientLevelPredictionViewer.html +/reference/phevaluatorHelperFile.html +/reference/phevaluatorServer.html +/reference/phevaluatorViewer.html +/reference/predictionCalibrationServer.html +/reference/predictionCalibrationViewer.html +/reference/predictionCovariateSummaryServer.html +/reference/predictionCovariateSummaryViewer.html +/reference/predictionCutoffServer.html +/reference/predictionCutoffViewer.html +/reference/predictionDesignSummaryServer.html +/reference/predictionDesignSummaryViewer.html +/reference/predictionDiagnosticsServer.html +/reference/predictionDiagnosticsViewer.html +/reference/predictionDiscriminationServer.html +/reference/predictionDiscriminationViewer.html +/reference/predictionHelperFile.html +/reference/predictionModelSummaryServer.html +/reference/predictionModelSummaryViewer.html +/reference/predictionNbServer.html +/reference/predictionNbViewer.html +/reference/predictionServer.html +/reference/predictionSetingsServer.html +/reference/predictionSettingsServer.html +/reference/predictionSettingsViewer.html +/reference/predictionValidationServer.html +/reference/predictionValidationViewer.html +/reference/predictionViewer.html +/reference/reportHelperFile.html +/reference/reportServer.html +/reference/reportViewer.html +/reference/resultTableServer.html +/reference/resultTableViewer.html +/reference/sccsHelperFile.html +/reference/sccsServer.html +/reference/sccsView.html +/reference/timeDistributionsView.html +/reference/visitContextView.html + diff --git a/vignettes/CohortMethod.Rmd b/vignettes/CohortMethod.Rmd deleted file mode 100644 index e83f05d6..00000000 --- a/vignettes/CohortMethod.Rmd +++ /dev/null @@ -1,60 +0,0 @@ ---- -title: "Cohort Method (Estimation)" -author: "Nathan Hall" -date: '`r Sys.Date()`' -header-includes: - - \usepackage{fancyhdr} - - \pagestyle{fancy} - - \fancyhead{} - - \fancyfoot[LE,RO]{\thepage} - - \renewcommand{\headrulewidth}{0.4pt} - - \renewcommand{\footrulewidth}{0.4pt} - - \fancyfoot[CO,CE]{OhdsiShinyModules Package Version `r utils::packageVersion("OhdsiShinyModules")`} -output: - html_document: - number_sections: yes - toc: yes - word_document: - toc: yes - pdf_document: - includes: - in_header: preamble.tex - number_sections: yes - toc: yes ---- - -```{=html} - -``` -```{r include=FALSE} -knitr::opts_chunk$set(echo = TRUE) -``` - -# Introduction - -Observational healthcare data, comprising administrative claims and electronic health records, present a rich source for generating real-world evidence pertinent to treatment effects that directly impact patient well-being. Within this realm, population-level effect estimation assumes a pivotal role, focusing on elucidating the average causal effects of exposures—such as medical interventions like drug exposures or procedures—on specific health outcomes of interest. Population-level effect estimation delves into two primary realms: direct effect estimation and comparative effect estimation. In direct effect estimation, the focus lies on discerning the effect of an exposure on the risk of an outcome compared to no exposure, while comparative effect estimation aims to delineate the effect of a target exposure against a comparator exposure. By contrasting factual outcomes with counterfactual scenarios—what happened versus what would have occurred under different circumstances—these estimation tasks offer critical insights into treatment selection, safety surveillance, and comparative effectiveness. Whether probing individual hypotheses or exploring multiple hypotheses concurrently, the overarching goal remains consistent: to derive high-quality estimates of causal effects from the intricate fabric of observational healthcare data. - -# Features and Functionalities - -The [CohortMethod](https://ohdsi.github.io/CohortMethod/ "CohortMethod") R package, a cornerstone of population-level estimation within the OHDSI framework, offers a robust methodology for conducting comparative effectiveness research and pharmacoepidemiology studies. Some of the features offered by conducting population-level effect estimation using the CohortMethod module are: - -1. **Data Extraction**: Extracts necessary data from databases structured in the OMOP Common Data Model (CDM) format, ensuring uniformity and compatibility across diverse healthcare settings. -2. **Covariate Selection**: Utilizing a comprehensive set of covariates, including drugs, diagnoses, procedures, age, and comorbidity indexes, CohortMethod constructs propensity and outcome models tailored to specific research questions. -3. **Large-Scale Regularized Regression**: Employing large-scale regularized regression techniques, CohortMethod fits propensity and outcome models with precision and efficiency, accommodating the complexities of real-world healthcare data. -4. **Propensity Score Adjustment**: Facilitates propensity score adjustment through trimming, stratification, matching, and weighting, enabling researchers to address confounding and balance covariate distributions across treatment groups. Results are viewable both graphically and in tabular form to assess the model. -5. **Diagnostic Functions**: Diagnostic functions within CohortMethod offer insights into propensity score distributions and covariate balance before and after matching or trimming, enhancing transparency and robustness in estimation procedures. -6. **Supported Outcome Models**: Supported outcome models include (conditional) logistic regression, (conditional) Poisson regression, and (conditional) Cox regression, providing flexibility in modeling various types of outcomes in observational health data research. -7. **Power**: Incorporates power analysis techniques to estimate the statistical power of the study design, aiding in sample size determination and study planning, and provides a minimum-detectable relative risk (MDRR) statistic. -8. **Attrition**: Assesses attrition rates within cohorts, providing insights into potential biases introduced by data loss during the study period, and provides a visualization of attrition across various cohort criteria. -9. **Population Characteristics**: Analyzes population characteristics to understand the demographic and clinical makeup of the study cohorts, informing interpretation of estimation results both before and after propensity score matching. -10. **Covariate Balance**: Visually monitors covariate balance before and after matching or trimming, ensuring that confounding variables are adequately controlled for in the analysis. -11. **Systematic Error**: Assesses effect size estimates for negative controls (true hazard ratio = 1) and positive controls (true hazard ratio > 1) both before and after calibration. Estimates below the diagonal dashed lines are statistically significant (alpha = 0.05) different from the true effect size. A well-calibrated estimator should have the true effect size within the 95 percent confidence interval 95 percent of times, providing researchers with confidence in the reliability of the estimation process and the accuracy of the obtained results. - -# Utility and Application - -**Comparative Effectiveness Research**: CohortMethod empowers researchers to conduct comparative effectiveness studies by estimating treatment effects while accounting for potential confounding factors and bias inherent in observational data. - -**Pharmacoepidemiology and Drug Safety Studies**: In pharmacoepidemiology research, CohortMethod facilitates the evaluation of drug safety and effectiveness by quantifying the association between drug exposures and clinical outcomes in real-world populations. diff --git a/vignettes/Estimation.Rmd b/vignettes/Estimation.Rmd new file mode 100644 index 00000000..72a32e33 --- /dev/null +++ b/vignettes/Estimation.Rmd @@ -0,0 +1,136 @@ +--- +title: "Estimation" +author: "Nathan Hall" +date: '`r Sys.Date()`' +header-includes: + - \usepackage{fancyhdr} + - \pagestyle{fancy} + - \fancyhead{} + - \fancyfoot[LE,RO]{\thepage} + - \renewcommand{\headrulewidth}{0.4pt} + - \renewcommand{\footrulewidth}{0.4pt} + - \fancyfoot[CO,CE]{OhdsiShinyModules Package Version `r utils::packageVersion("OhdsiShinyModules")`} +output: + html_document: + number_sections: yes + toc: yes + word_document: + toc: yes + pdf_document: + includes: + in_header: preamble.tex + number_sections: yes + toc: yes +--- + + + +```{r include=FALSE} +knitr::opts_chunk$set(echo = TRUE) +``` + +## Introduction + +Observational healthcare data, comprising administrative claims and electronic health records, present a rich source for generating real-world evidence pertinent to treatment effects that directly impact patient well-being. Within this realm, population-level effect estimation assumes a pivotal role, focusing on elucidating the average causal effects of exposures—such as medical interventions like drug exposures or procedures—on specific health outcomes of interest. Population-level effect estimation delves into two primary realms: direct effect estimation and comparative effect estimation. In direct effect estimation, the focus lies on discerning the effect of an exposure on the risk of an outcome compared to no exposure, while comparative effect estimation aims to delineate the effect of a target exposure against a comparator exposure. By contrasting factual outcomes with counterfactual scenarios—what happened versus what would have occurred under different circumstances—these estimation tasks offer critical insights into treatment selection, safety surveillance, and comparative effectiveness. Whether probing individual hypotheses or exploring multiple hypotheses concurrently, the overarching goal remains consistent: to derive high-quality estimates of causal effects from the intricate fabric of observational healthcare data. + +# 1. CohortMethod + +## Features and Functionalities + +The [CohortMethod](https://ohdsi.github.io/CohortMethod/ "CohortMethod") R package, a cornerstone of population-level estimation within the OHDSI framework, offers a robust methodology for conducting comparative effectiveness research and pharmacoepidemiology studies. Some of the features offered by conducting population-level effect estimation using the CohortMethod module are: + +1. **Data Extraction**: Extracts necessary data from databases structured in the OMOP Common Data Model (CDM) format, ensuring uniformity and compatibility across diverse healthcare settings. +2. **Covariate Selection**: Utilizing a comprehensive set of covariates, including drugs, diagnoses, procedures, age, and comorbidity indexes, CohortMethod constructs propensity and outcome models tailored to specific research questions. +3. **Large-Scale Regularized Regression**: Employing large-scale regularized regression techniques, CohortMethod fits propensity and outcome models with precision and efficiency, accommodating the complexities of real-world healthcare data. +4. **Propensity Score Adjustment**: Facilitates propensity score adjustment through trimming, stratification, matching, and weighting, enabling researchers to address confounding and balance covariate distributions across treatment groups. Results are viewable both graphically and in tabular form to assess the model. +5. **Diagnostic Functions**: Diagnostic functions within CohortMethod offer insights into propensity score distributions and covariate balance before and after matching or trimming, enhancing transparency and robustness in estimation procedures. +6. **Supported Outcome Models**: Supported outcome models include (conditional) logistic regression, (conditional) Poisson regression, and (conditional) Cox regression, providing flexibility in modeling various types of outcomes in observational health data research. +7. **Power**: Incorporates power analysis techniques to estimate the statistical power of the study design, aiding in sample size determination and study planning, and provides a minimum-detectable relative risk (MDRR) statistic. +8. **Attrition**: Assesses attrition rates within cohorts, providing insights into potential biases introduced by data loss during the study period, and provides a visualization of attrition across various cohort criteria. +9. **Population Characteristics**: Analyzes population characteristics to understand the demographic and clinical makeup of the study cohorts, informing interpretation of estimation results both before and after propensity score matching. +10. **Covariate Balance**: Visually monitors covariate balance before and after matching or trimming, ensuring that confounding variables are adequately controlled for in the analysis. +11. **Systematic Error**: Assesses effect size estimates for negative controls (true hazard ratio = 1) and positive controls (true hazard ratio \> 1) both before and after calibration. Estimates below the diagonal dashed lines are statistically significant (alpha = 0.05) different from the true effect size. A well-calibrated estimator should have the true effect size within the 95 percent confidence interval 95 percent of times, providing researchers with confidence in the reliability of the estimation process and the accuracy of the obtained results. + +## Utility and Application + +**Comparative Effectiveness Research**: CohortMethod empowers researchers to conduct comparative effectiveness studies by estimating treatment effects while accounting for potential confounding factors and bias inherent in observational data. + +**Pharmacoepidemiology and Drug Safety Studies**: In pharmacoepidemiology research, CohortMethod facilitates the evaluation of drug safety and effectiveness by quantifying the association between drug exposures and clinical outcomes in real-world populations. + +# 2. Self-Controlled Case Series + +## Introduction + +The Self-Controlled Case Series (SCCS) method offers a nuanced approach to investigating the relationship between exposures and outcomes within individual patients over time. SCCS designs are particularly adept at comparing the rate of outcomes during times of exposure to rates during periods of non-exposure, including before, between, and after exposure episodes. By leveraging a Poisson regression that is conditioned on the individual, the SCCS design inherently addresses the question: “Given that a patient has the outcome, is the outcome more likely to occur during exposed time compared to non-exposed time?” The design choices outlined in the method are pivotal for defining an SCCS question, with each choice playing a critical role in the study's design and outcomes: + +**Target Cohort**: This represents the treatment under investigation. **Outcome Cohort**: This cohort signifies the outcome of interest. **Time-at-Risk**: Identifies the specific times when the risk of the outcome is considered, often relative to the start and end dates of the target cohort. **Model**: Defines the statistical model used to estimate the effect, including adjustments for time-varying confounders if necessary. + +One of the SCCS design's strengths is its robustness to confounding by factors that differ between individuals, as each participant serves as their own control. However, it remains sensitive to time-varying confounding factors. To mitigate this, adjustments can be made for factors such as age, seasonality, and calendar time, enhancing the model's accuracy. + +An advanced variant of the SCCS also considers all other drug exposures recorded in the database, significantly expanding the model's variables. This approach employs L1-regularization, with cross-validation used to select the regularization hyperparameter for all exposures except the one of interest. + +An important assumption of the SCCS is that the observation period's end is independent of the outcome date. This may not hold true for outcomes that can be fatal, such as stroke. To address this, extensions to the SCCS model have been developed that correct for any dependency between the observation period end and the outcome. + +## Features and Functionalities + +The [SelfControlledCaseSeries](https://ohdsi.github.io/SelfControlledCaseSeries/ "SCCS") R package allows the user to perform SCCS analyses in an observational database in the OMOP Common Data Model. Some of the features offered by the SCCS module include: + +1. \*\*Data Extraction: Extracts necessary data from databases structured in the OMOP Common Data Model (CDM) format, ensuring uniformity and compatibility across diverse healthcare settings. +2. **Seasonality Adjustment**: Offers the option to adjust for seasonality effects using a spline function, enhancing the model's accuracy by accounting for seasonal variation in exposure and outcome rates. +3. **Age Adjustment**: Provides the option to incorporate age adjustments using a spline function, allowing for more nuanced analyses that consider the impact of age on the exposure-outcome relationship. +4. **Calendar Time Adjustment**: Enables the inclusion of calendar time adjustments using a spline function, addressing potential temporal trends in the data that could confound the exposure-outcome relationship. +5. **Event-dependent Censoring Correction**: Features the ability to correct for event-dependent censoring of the observation period, ensuring that the end of the observation period is appropriately handled, especially in cases where it might be related to the outcome. +6. **Comprehensive Covariate Inclusion**: Allows for the addition of a wide array of covariates in one analysis, such as all recorded drug exposures, facilitating a thorough examination of potential confounders and effect modifiers. +7. **Risk Window Customization**: Supports the construction of various types of covariates and risk windows, including pre-exposure windows, to capture contra-indications and other relevant temporal patterns related to exposure and outcome. +8. **Regularization of Covariates**: Applies regularization to all covariates except the outcome of interest, employing techniques like L1-regularization with cross-validation for selecting the regularization hyperparameter, thereby preventing overfitting and enhancing model reliability. +9. **Self-Controlled Risk Interval Design**: Incorporates the self-controlled risk interval design as a specific application of the SCCS method, offering additional methodological flexibility for studying short-term effects of exposures. +10. **Power**: Incorporates power analysis techniques to estimate the statistical power of the study design, aiding in sample size determination and study planning, and provides a minimum-detectable relative risk (MDRR) statistic. +11. **Attrition**: Assesses attrition rates within cohorts, providing insights into potential biases introduced by data loss during the study period, and provides a visualization of attrition across various cohort criteria. +12. **Spanning**: Analyzes the number of subjects observed for 3 consecutive months, providing insights into the cohort's consistency and stability over time. +13. **Time Trend**: Assesses the ratio of observed to expected outcomes per month, with adjustments for calendar time, seasonality, and/or age as specified in the model, to examine time trends in the data. +14. **Time to Event**: Evaluates the number of events and subjects observed per week relative to the start of the first exposure, offering critical insights into the temporal relationship between exposure and outcome. +15. **Event-dependent Observation**: Provides histograms for the time between the first occurrence of the outcome and the end of observation, stratified by censored and uncensored ends of observation, to assess the impact of event-dependent observation periods. +16. **Systematic Error**: Assesses effect size estimates for negative controls (true hazard ratio = 1) and positive controls (true hazard ratio \> 1) both before and after calibration. Estimates below the diagonal dashed lines are statistically significant (alpha = 0.05) different from the true effect size. A well-calibrated estimator should have the true effect size within the 95 percent confidence interval 95 percent of times, providing researchers with confidence in the reliability of the estimation process and the accuracy of the obtained results. + +## Utility and Application + +The SCCS method is particularly applicable in several key areas of epidemiological research and pharmacovigilance: + +**Drug Safety Surveillance**: The SCCS method is widely used in drug safety surveillance to identify adverse effects of medications post-marketing. It is well-suited to detect short-term risks associated with drug exposures, especially where the onset of the adverse event is expected to be temporally close to the exposure. + +**Vaccine Safety Evaluation**: The SCCS design is ideal for assessing the safety of vaccines, especially in evaluating the risk of adverse events following immunization. Its self-controlled nature helps to address concerns about confounding by indication and other biases that can affect observational studies in vaccine safety. + +**Comparative Effectiveness Research**: While primarily designed for evaluating the safety of medical interventions, the SCCS method can also be adapted to compare the effectiveness of different treatments or interventions within the same individual over time, particularly for acute conditions. + +**Epidemiological Research**: More broadly, the SCCS method is used in epidemiological research to study the temporal relationships between exposures and outcomes, offering insights into the causality and mechanisms underlying health conditions and diseases. + +# 3. Evidence Synthesis (Meta, Meta Analysis) + +## Introduction + +Meta-analysis plays a pivotal role in healthcare research by enabling the synthesis of findings from multiple studies to draw more generalizable conclusions. In the context of distributed health data networks, where data are spread across various sites with diverse populations and practices, synthesizing evidence becomes both a challenge and a necessity. The [EvidenceSynthesis](https://github.com/OHDSI/EvidenceSynthesis "EvidenceSynthesis") R package addresses these challenges head-on. It offers a suite of tools designed for combining causal effect estimates and study diagnostics from multiple data sites, all while adhering to stringent patient privacy requirements and navigating the complexities inherent to observational data. This approach enhances the robustness of meta-analytical conclusions and extends the utility of distributed health data for research purposes. + +## Features and Functionalities + +The Meta module which utilizes the EvidenceSynthesis R package makes use of the following features to summarize the results of a study: + +1. **Meta-Analysis Methods**: Facilitates both traditional fixed-effects and random-effects meta-analyses, accommodating studies with different degrees of between-site or between-database variability. +2. **Forest Plot Generation**: Provides capabilities for creating forest plots, visual summaries that illustrate the effects estimated by individual studies, their confidence intervals, and the synthesized overall effect. +3. **Non-Normal Likelihood Approximations**: Utilizes non-normal approximations for the per-data-site likelihood function to reduce bias in scenarios with small or zero counts, a frequent issue in distributed research environments. + +The syntheses are generated for both Cohort Method and Self-Controlled Case Series estimation results from the study, providing both information on the diagnostic results within each database and the visualized and tabular results of the meta analysis. + +## Utility and Application + +The EvidenceSynthesis package is instrumental in synthesizing evidence from observational studies across multiple healthcare databases. Its significance is underscored in scenarios characterized by: + +**Comparative Effectiveness Research**: Synthesizing evidence from disparate sources allows for stronger, more reliable comparisons of treatment outcomes, enriching the foundation for clinical decision-making. + +**Safety Surveillance**: Aggregated safety data across databases enhance the detection and understanding of adverse drug reactions, contributing to safer patient care. + +**Policy and Clinical Guidelines Development**: Meta-analytical findings informed by comprehensive, real-world data can guide policy formulation and the updating of clinical guidelines, ensuring they are grounded in broad-based evidence. + +**Addressing Challenges of Small Sample Sizes**: The EvidenceSynthesis package notably advances the field by tackling the issue of small sample sizes and zero event counts, which traditional meta-analytical methods often handle poorly. Its innovative use of non-normal likelihood approximations enables more precise effect size estimation under such conditions, ensuring that the insights derived from meta-analyses are both accurate and meaningful. This attribute is particularly beneficial in distributed health data networks, where individual site/database data may be limited but collectively hold significant informational value. diff --git a/vignettes/EvidenceSynthesis.Rmd b/vignettes/EvidenceSynthesis.Rmd deleted file mode 100644 index 39e2edcc..00000000 --- a/vignettes/EvidenceSynthesis.Rmd +++ /dev/null @@ -1,60 +0,0 @@ ---- -title: "Evidence Synthesis (Meta, Meta Analysis)" -author: "Nathan Hall" -date: '`r Sys.Date()`' -header-includes: - - \usepackage{fancyhdr} - - \pagestyle{fancy} - - \fancyhead{} - - \fancyfoot[LE,RO]{\thepage} - - \renewcommand{\headrulewidth}{0.4pt} - - \renewcommand{\footrulewidth}{0.4pt} - - \fancyfoot[CO,CE]{OhdsiShinyModules Package Version `r utils::packageVersion("OhdsiShinyModules")`} -output: - html_document: - number_sections: yes - toc: yes - word_document: - toc: yes - pdf_document: - includes: - in_header: preamble.tex - number_sections: yes - toc: yes ---- - -```{=html} - -``` -```{r include=FALSE} -knitr::opts_chunk$set(echo = TRUE) -``` - -# Introduction - -Meta-analysis plays a pivotal role in healthcare research by enabling the synthesis of findings from multiple studies to draw more generalizable conclusions. In the context of distributed health data networks, where data are spread across various sites with diverse populations and practices, synthesizing evidence becomes both a challenge and a necessity. The [EvidenceSynthesis](https://github.com/OHDSI/EvidenceSynthesis "EvidenceSynthesis") R package addresses these challenges head-on. It offers a suite of tools designed for combining causal effect estimates and study diagnostics from multiple data sites, all while adhering to stringent patient privacy requirements and navigating the complexities inherent to observational data. This approach enhances the robustness of meta-analytical conclusions and extends the utility of distributed health data for research purposes. - -# Features and Functionalities - -The Meta module which utilizes the EvidenceSynthesis R package makes use of the following features to summarize the results of a study: - -1. **Meta-Analysis Methods**: Facilitates both traditional fixed-effects and random-effects meta-analyses, accommodating studies with different degrees of between-site or between-database variability. -2. **Forest Plot Generation**: Provides capabilities for creating forest plots, visual summaries that illustrate the effects estimated by individual studies, their confidence intervals, and the synthesized overall effect. -3. **Non-Normal Likelihood Approximations**: Utilizes non-normal approximations for the per-data-site likelihood function to reduce bias in scenarios with small or zero counts, a frequent issue in distributed research environments. - -The syntheses are generated for both Cohort Method and Self-Controlled Case Series estimation results from the study, providing both information on the diagnostic results within each database and the visualized and tabular results of the meta analysis. - -# Utility and Application - -The EvidenceSynthesis package is instrumental in synthesizing evidence from observational studies across multiple healthcare databases. Its significance is underscored in scenarios characterized by: - -**Comparative Effectiveness Research**: Synthesizing evidence from disparate sources allows for stronger, more reliable comparisons of treatment outcomes, enriching the foundation for clinical decision-making. - -**Safety Surveillance**: Aggregated safety data across databases enhance the detection and understanding of adverse drug reactions, contributing to safer patient care. - -**Policy and Clinical Guidelines Development**: Meta-analytical findings informed by comprehensive, real-world data can guide policy formulation and the updating of clinical guidelines, ensuring they are grounded in broad-based evidence. - -**Addressing Challenges of Small Sample Sizes**: The EvidenceSynthesis package notably advances the field by tackling the issue of small sample sizes and zero event counts, which traditional meta-analytical methods often handle poorly. Its innovative use of non-normal likelihood approximations enables more precise effect size estimation under such conditions, ensuring that the insights derived from meta-analyses are both accurate and meaningful. This attribute is particularly beneficial in distributed health data networks, where individual site/database data may be limited but collectively hold significant informational value. diff --git a/vignettes/ReportGenerator.Rmd b/vignettes/ReportGenerator.Rmd new file mode 100644 index 00000000..14df6222 --- /dev/null +++ b/vignettes/ReportGenerator.Rmd @@ -0,0 +1,47 @@ +--- +title: "Report Generator" +author: "Nathan Hall" +date: '`r Sys.Date()`' +header-includes: + - \usepackage{fancyhdr} + - \pagestyle{fancy} + - \fancyhead{} + - \fancyfoot[CO,CE]{OhdsiShinyModules Package Version `r utils::packageVersion("OhdsiShinyModules")`} + - \fancyfoot[LE,RO]{\thepage} + - \renewcommand{\headrulewidth}{0.4pt} + - \renewcommand{\footrulewidth}{0.4pt} +output: + pdf_document: + includes: + in_header: preamble.tex + number_sections: yes + toc: yes + word_document: + toc: yes + html_document: + number_sections: yes + toc: yes +--- + + +```{r include=FALSE} +knitr::opts_chunk$set(echo = TRUE) +``` + +# Introduction + +ReportGenerator is a tool used to create a summary presentation document using results from a Strategus execution which should be stored in a results database. + +# Description + +The Report Generator module allows the user to choose which target (T), subgroup (indication & extra inclusions), comparator (C), and outcome(s) (O) they would like a downloaded report on. In the last section of the module, the user's selections are reported back to them for review before downloading. Here, the user can also choose to restrict the study date and/or the age range of people included in the report. + +## Notes + +Please note that this package is currently under development, so results may vary or may not be available at the time of report generation. + + + diff --git a/vignettes/SelfControlledCaseSeries.Rmd b/vignettes/SelfControlledCaseSeries.Rmd deleted file mode 100644 index 9f72d894..00000000 --- a/vignettes/SelfControlledCaseSeries.Rmd +++ /dev/null @@ -1,82 +0,0 @@ ---- -title: "Self-Controlled Case Series" -author: "Nathan Hall" -date: '`r Sys.Date()`' -header-includes: - - \usepackage{fancyhdr} - - \pagestyle{fancy} - - \fancyhead{} - - \fancyfoot[LE,RO]{\thepage} - - \renewcommand{\headrulewidth}{0.4pt} - - \renewcommand{\footrulewidth}{0.4pt} - - \fancyfoot[CO,CE]{OhdsiShinyModules Package Version `r utils::packageVersion("OhdsiShinyModules")`} -output: - html_document: - number_sections: yes - toc: yes - word_document: - toc: yes - pdf_document: - includes: - in_header: preamble.tex - number_sections: yes - toc: yes ---- - -```{=html} - -``` -```{r include=FALSE} -knitr::opts_chunk$set(echo = TRUE) -``` - -# Introduction - -The Self-Controlled Case Series (SCCS) method offers a nuanced approach to investigating the relationship between exposures and outcomes within individual patients over time. SCCS designs are particularly adept at comparing the rate of outcomes during times of exposure to rates during periods of non-exposure, including before, between, and after exposure episodes. By leveraging a Poisson regression that is conditioned on the individual, the SCCS design inherently addresses the question: “Given that a patient has the outcome, is the outcome more likely to occur during exposed time compared to non-exposed time?” The design choices outlined in the method are pivotal for defining an SCCS question, with each choice playing a critical role in the study's design and outcomes: - -**Target Cohort**: This represents the treatment under investigation. -**Outcome Cohort**: This cohort signifies the outcome of interest. -**Time-at-Risk**: Identifies the specific times when the risk of the outcome is considered, often relative to the start and end dates of the target cohort. -**Model**: Defines the statistical model used to estimate the effect, including adjustments for time-varying confounders if necessary. - -One of the SCCS design's strengths is its robustness to confounding by factors that differ between individuals, as each participant serves as their own control. However, it remains sensitive to time-varying confounding factors. To mitigate this, adjustments can be made for factors such as age, seasonality, and calendar time, enhancing the model's accuracy. - -An advanced variant of the SCCS also considers all other drug exposures recorded in the database, significantly expanding the model's variables. This approach employs L1-regularization, with cross-validation used to select the regularization hyperparameter for all exposures except the one of interest. - -An important assumption of the SCCS is that the observation period's end is independent of the outcome date. This may not hold true for outcomes that can be fatal, such as stroke. To address this, extensions to the SCCS model have been developed that correct for any dependency between the observation period end and the outcome. - -# Features and Functionalities - -The [SelfControlledCaseSeries](https://ohdsi.github.io/SelfControlledCaseSeries/ "SCCS") R package allows the user to perform SCCS analyses in an observational database in the OMOP Common Data Model. Some of the features offered by the SCCS module include: - -1. **Data Extraction: Extracts necessary data from databases structured in the OMOP Common Data Model (CDM) format, ensuring uniformity and compatibility across diverse healthcare settings. -2. **Seasonality Adjustment**: Offers the option to adjust for seasonality effects using a spline function, enhancing the model's accuracy by accounting for seasonal variation in exposure and outcome rates. -3. **Age Adjustment**: Provides the option to incorporate age adjustments using a spline function, allowing for more nuanced analyses that consider the impact of age on the exposure-outcome relationship. -4. **Calendar Time Adjustment**: Enables the inclusion of calendar time adjustments using a spline function, addressing potential temporal trends in the data that could confound the exposure-outcome relationship. -5. **Event-dependent Censoring Correction**: Features the ability to correct for event-dependent censoring of the observation period, ensuring that the end of the observation period is appropriately handled, especially in cases where it might be related to the outcome. -6. **Comprehensive Covariate Inclusion**: Allows for the addition of a wide array of covariates in one analysis, such as all recorded drug exposures, facilitating a thorough examination of potential confounders and effect modifiers. -7. **Risk Window Customization**: Supports the construction of various types of covariates and risk windows, including pre-exposure windows, to capture contra-indications and other relevant temporal patterns related to exposure and outcome. -8. **Regularization of Covariates**: Applies regularization to all covariates except the outcome of interest, employing techniques like L1-regularization with cross-validation for selecting the regularization hyperparameter, thereby preventing overfitting and enhancing model reliability. -9. **Self-Controlled Risk Interval Design**: Incorporates the self-controlled risk interval design as a specific application of the SCCS method, offering additional methodological flexibility for studying short-term effects of exposures. -10. **Power**: Incorporates power analysis techniques to estimate the statistical power of the study design, aiding in sample size determination and study planning, and provides a minimum-detectable relative risk (MDRR) statistic. -11. **Attrition**: Assesses attrition rates within cohorts, providing insights into potential biases introduced by data loss during the study period, and provides a visualization of attrition across various cohort criteria. -12. **Spanning**: Analyzes the number of subjects observed for 3 consecutive months, providing insights into the cohort's consistency and stability over time. -13. **Time Trend**: Assesses the ratio of observed to expected outcomes per month, with adjustments for calendar time, seasonality, and/or age as specified in the model, to examine time trends in the data. -14. **Time to Event**: Evaluates the number of events and subjects observed per week relative to the start of the first exposure, offering critical insights into the temporal relationship between exposure and outcome. -15. **Event-dependent Observation**: Provides histograms for the time between the first occurrence of the outcome and the end of observation, stratified by censored and uncensored ends of observation, to assess the impact of event-dependent observation periods. -16. **Systematic Error**: Assesses effect size estimates for negative controls (true hazard ratio = 1) and positive controls (true hazard ratio > 1) both before and after calibration. Estimates below the diagonal dashed lines are statistically significant (alpha = 0.05) different from the true effect size. A well-calibrated estimator should have the true effect size within the 95 percent confidence interval 95 percent of times, providing researchers with confidence in the reliability of the estimation process and the accuracy of the obtained results. - -# Utility and Application - -The SCCS method is particularly applicable in several key areas of epidemiological research and pharmacovigilance: - -**Drug Safety Surveillance**: The SCCS method is widely used in drug safety surveillance to identify adverse effects of medications post-marketing. It is well-suited to detect short-term risks associated with drug exposures, especially where the onset of the adverse event is expected to be temporally close to the exposure. - -**Vaccine Safety Evaluation**: The SCCS design is ideal for assessing the safety of vaccines, especially in evaluating the risk of adverse events following immunization. Its self-controlled nature helps to address concerns about confounding by indication and other biases that can affect observational studies in vaccine safety. - -**Comparative Effectiveness Research**: While primarily designed for evaluating the safety of medical interventions, the SCCS method can also be adapted to compare the effectiveness of different treatments or interventions within the same individual over time, particularly for acute conditions. - -**Epidemiological Research**: More broadly, the SCCS method is used in epidemiological research to study the temporal relationships between exposures and outcomes, offering insights into the causality and mechanisms underlying health conditions and diseases. From ca276449f69498c82a0a06eebcf3a5ad0a395b37 Mon Sep 17 00:00:00 2001 From: Nathan Hall Date: Fri, 4 Oct 2024 11:15:32 -0400 Subject: [PATCH 4/6] fixing shiny incremental progress --- R/characterization-cohorts.R | 23 ++++++++++++----------- 1 file changed, 12 insertions(+), 11 deletions(-) diff --git a/R/characterization-cohorts.R b/R/characterization-cohorts.R index aad9cb00..aab7ba28 100644 --- a/R/characterization-cohorts.R +++ b/R/characterization-cohorts.R @@ -860,9 +860,9 @@ characterizatonGetCohortData <- function( return(NULL) } - # shiny::withProgress(message = 'characterizatonGetCohortData', value = 0, { - # - # shiny::incProgress(1/4, detail = paste("Setting types")) + shiny::withProgress(message = 'characterizatonGetCohortData', value = 0, { + + shiny::incProgress(1/4, detail = paste("Setting types")) types <- data.frame( type = 1:(length(targetIds)*length(databaseIds)), @@ -870,7 +870,7 @@ characterizatonGetCohortData <- function( databaseId = rep(databaseIds, length(targetIds)) ) - # shiny::incProgress(2/4, detail = paste("Extracting data")) + shiny::incProgress(2/4, detail = paste("Extracting data")) sql <- "select ref.covariate_name, s.min_prior_observation, @@ -904,8 +904,8 @@ characterizatonGetCohortData <- function( min_threshold = minThreshold ) end <- Sys.time() - start - # shiny::incProgress(3/4, detail = paste("Extracted data")) - # message(paste0('Extracting ', nrow(res) ,' characterization cohort rows took: ', round(end, digits = 2), ' ', units(end))) + shiny::incProgress(3/4, detail = paste("Extracted data")) + message(paste0('Extracting ', nrow(res) ,' characterization cohort rows took: ', round(end, digits = 2), ' ', units(end))) # add the first/section type res <- merge(res, types, by = c('cohortDefinitionId','databaseId')) @@ -947,13 +947,14 @@ characterizatonGetCohortData <- function( } else{ NULL - # shiny::showNotification('Unable to add SMD due to missing columns') + shiny::showNotification('Unable to add SMD due to missing columns') } - # } - # shiny::incProgress(4/4, detail = paste("Done")) - } + } + shiny::incProgress(4/4, detail = paste("Done")) + }) + + return(result) - return(result) } From ba24e4d87d40fcb8c42b7ef9703e31606f261c9d Mon Sep 17 00:00:00 2001 From: Jamie Gilbert Date: Fri, 4 Oct 2024 19:06:54 -0700 Subject: [PATCH 5/6] Remove percentage calculation from records field in cd ieb (#358) --- R/cohort-diagnostics-indexEventBreakdown.R | 14 +++++++++----- 1 file changed, 9 insertions(+), 5 deletions(-) diff --git a/R/cohort-diagnostics-indexEventBreakdown.R b/R/cohort-diagnostics-indexEventBreakdown.R index 25a3ea2f..b47416c9 100644 --- a/R/cohort-diagnostics-indexEventBreakdown.R +++ b/R/cohort-diagnostics-indexEventBreakdown.R @@ -69,7 +69,7 @@ indexEventBreakdownView <- function(id) { shiny::tags$td( shiny::checkboxInput( inputId = ns("showAsPercent"), - label = "Show as percentage", + label = "Show persons as percentage", value = TRUE ) ) @@ -232,17 +232,20 @@ indexEventBreakdownModule <- function(id, if (showDataAsPercent) { data <- data %>% dplyr::rename( - "persons" = "subjectPercent", - "records" = "conceptPercent" + "persons" = "subjectPercent" ) } else { data <- data %>% dplyr::rename( - "persons" = "subjectCount", - "records" = "conceptCount" + "persons" = "subjectCount" ) } + data <- data %>% + dplyr::rename( + "records" = "conceptCount" + ) + data <- data %>% dplyr::arrange(dplyr::desc(abs(dplyr::across( c("records", "persons") @@ -278,6 +281,7 @@ indexEventBreakdownModule <- function(id, countLocation = countLocation, dataColumns = dataColumnFields, showDataAsPercent = showDataAsPercent, + excludedColumnFromPercentage = "records", sort = TRUE ) }) From dadb250b4609783822e16571f1c867e1331288e7 Mon Sep 17 00:00:00 2001 From: Nathan Hall Date: Mon, 7 Oct 2024 11:28:11 -0400 Subject: [PATCH 6/6] updating website, news, and version --- DESCRIPTION | 2 +- NEWS.md | 7 +++++++ docs/404.html | 10 ++-------- docs/articles/AddingShinyModules.html | 12 +++--------- docs/articles/Characterization.html | 12 +++--------- docs/articles/CohortDiagnostics.html | 12 +++--------- docs/articles/Cohorts.html | 12 +++--------- docs/articles/DataSources.html | 12 +++--------- docs/articles/Estimation.html | 12 +++--------- docs/articles/EvidenceSynthesis.html | 2 +- docs/articles/Prediction.html | 12 +++--------- docs/articles/ReportGenerator.html | 12 +++--------- docs/articles/SelfControlledCaseSeries.html | 2 +- docs/articles/index.html | 14 ++------------ docs/authors.html | 14 ++++---------- docs/index.html | 10 ++-------- docs/news/index.html | 17 +++++++++-------- docs/pkgdown.yml | 4 +--- docs/reference/LargeDataTable.html | 10 ++-------- docs/reference/OhdsiShinyModules.html | 10 ++-------- docs/reference/aboutHelperFile.html | 10 ++-------- docs/reference/aboutServer.html | 10 ++-------- docs/reference/aboutViewer.html | 10 ++-------- docs/reference/characterizationHelperFile.html | 10 ++-------- .../characterizationIncidenceServer.html | 10 ++-------- .../characterizationIncidenceViewer.html | 10 ++-------- docs/reference/characterizationServer.html | 10 ++-------- docs/reference/characterizationViewer.html | 10 ++-------- docs/reference/cohortCountsModule.html | 10 ++-------- docs/reference/cohortCountsView.html | 10 ++-------- docs/reference/cohortDefinitionsModule.html | 10 ++-------- docs/reference/cohortDefinitionsView.html | 10 ++-------- .../cohortDiagCharacterizationView.html | 10 ++-------- docs/reference/cohortDiagnosticsHelperFile.html | 10 ++-------- docs/reference/cohortDiagnosticsServer.html | 10 ++-------- docs/reference/cohortDiagnosticsView.html | 10 ++-------- docs/reference/cohortGeneratorHelperFile.html | 10 ++-------- docs/reference/cohortGeneratorServer.html | 10 ++-------- docs/reference/cohortGeneratorViewer.html | 10 ++-------- docs/reference/cohortMethodAttritionServer.html | 10 ++-------- docs/reference/cohortMethodAttritionViewer.html | 10 ++-------- .../cohortMethodCovariateBalanceServer.html | 10 ++-------- .../cohortMethodCovariateBalanceViewer.html | 10 ++-------- .../cohortMethodKaplanMeierServer.html | 10 ++-------- .../cohortMethodKaplanMeierViewer.html | 10 ++-------- ...rtMethodPopulationCharacteristicsServer.html | 10 ++-------- ...rtMethodPopulationCharacteristicsViewer.html | 10 ++-------- docs/reference/cohortMethodPowerServer.html | 10 ++-------- docs/reference/cohortMethodPowerViewer.html | 10 ++-------- .../cohortMethodPropensityModelServer.html | 10 ++-------- .../cohortMethodPropensityModelViewer.html | 10 ++-------- .../cohortMethodPropensityScoreDistServer.html | 10 ++-------- .../cohortMethodPropensityScoreDistViewer.html | 10 ++-------- .../cohortMethodSystematicErrorServer.html | 10 ++-------- .../cohortMethodSystematicErrorViewer.html | 10 ++-------- docs/reference/cohortOverlapView.html | 10 ++-------- .../compareCohortCharacterizationView.html | 10 ++-------- docs/reference/conceptsInDataSourceView.html | 10 ++-------- docs/reference/createCdDatabaseDataSource.html | 10 ++-------- docs/reference/createCustomColDefList.html | 10 ++-------- docs/reference/createLargeSqlQueryDt.html | 10 ++-------- docs/reference/dataDiagnosticDrillServer.html | 10 ++-------- docs/reference/dataDiagnosticDrillViewer.html | 10 ++-------- docs/reference/dataDiagnosticHelperFile.html | 10 ++-------- docs/reference/dataDiagnosticServer.html | 10 ++-------- docs/reference/dataDiagnosticSummaryServer.html | 10 ++-------- docs/reference/dataDiagnosticSummaryViewer.html | 10 ++-------- docs/reference/dataDiagnosticViewer.html | 10 ++-------- docs/reference/databaseInformationView.html | 10 ++-------- docs/reference/datasourcesHelperFile.html | 10 ++-------- docs/reference/datasourcesServer.html | 10 ++-------- docs/reference/datasourcesViewer.html | 10 ++-------- docs/reference/estimationHelperFile.html | 10 ++-------- docs/reference/estimationServer.html | 10 ++-------- docs/reference/estimationViewer.html | 10 ++-------- docs/reference/getCirceRenderedExpression.html | 10 ++-------- docs/reference/getEnabledCdReports.html | 10 ++-------- docs/reference/getExampleConnectionDetails.html | 10 ++-------- docs/reference/getLogoImage.html | 10 ++-------- docs/reference/homeHelperFile.html | 10 ++-------- docs/reference/homeServer.html | 10 ++-------- docs/reference/homeViewer.html | 10 ++-------- docs/reference/incidenceRatesView.html | 10 ++-------- docs/reference/inclusionRulesView.html | 10 ++-------- docs/reference/index.html | 10 ++-------- docs/reference/indexEventBreakdownView.html | 10 ++-------- docs/reference/largeTableServer.html | 10 ++-------- docs/reference/largeTableView.html | 10 ++-------- docs/reference/makeButtonLabel.html | 10 ++-------- docs/reference/orpahanConceptsView.html | 10 ++-------- ...patientLevelPredictionCalibrationServer.html | 10 ++-------- ...patientLevelPredictionCalibrationViewer.html | 10 ++-------- ...ntLevelPredictionCovariateSummaryServer.html | 10 ++-------- ...ntLevelPredictionCovariateSummaryViewer.html | 10 ++-------- .../patientLevelPredictionCutoffServer.html | 10 ++-------- .../patientLevelPredictionCutoffViewer.html | 10 ++-------- ...tientLevelPredictionDesignSummaryServer.html | 10 ++-------- ...tientLevelPredictionDesignSummaryViewer.html | 10 ++-------- ...patientLevelPredictionDiagnosticsServer.html | 10 ++-------- ...patientLevelPredictionDiagnosticsViewer.html | 10 ++-------- ...ientLevelPredictionDiscriminationServer.html | 10 ++-------- ...ientLevelPredictionDiscriminationViewer.html | 10 ++-------- .../patientLevelPredictionHelperFile.html | 10 ++-------- ...atientLevelPredictionModelSummaryServer.html | 10 ++-------- ...atientLevelPredictionModelSummaryViewer.html | 10 ++-------- .../patientLevelPredictionNbServer.html | 10 ++-------- .../patientLevelPredictionNbViewer.html | 10 ++-------- .../reference/patientLevelPredictionServer.html | 10 ++-------- .../patientLevelPredictionSettingsServer.html | 10 ++-------- .../patientLevelPredictionSettingsViewer.html | 10 ++-------- .../patientLevelPredictionValidationServer.html | 10 ++-------- .../patientLevelPredictionValidationViewer.html | 10 ++-------- .../reference/patientLevelPredictionViewer.html | 10 ++-------- docs/reference/phevaluatorHelperFile.html | 10 ++-------- docs/reference/phevaluatorServer.html | 10 ++-------- docs/reference/phevaluatorViewer.html | 10 ++-------- docs/reference/reportHelperFile.html | 10 ++-------- docs/reference/reportServer.html | 10 ++-------- docs/reference/reportViewer.html | 10 ++-------- docs/reference/resultTableServer.html | 10 ++-------- docs/reference/resultTableViewer.html | 10 ++-------- docs/reference/timeDistributionsView.html | 10 ++-------- docs/reference/visitContextView.html | 10 ++-------- 123 files changed, 264 insertions(+), 964 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 435a7e89..02eff0e2 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,7 +1,7 @@ Package: OhdsiShinyModules Type: Package Title: Repository of Shiny Modules for OHDSI Result Viewers -Version: 3.0.2 +Version: 3.1.0 Authors@R: c( person("Jenna", "Reps", email = "jreps@its.jnj.com", role = c("aut", "cre")), person("Nathan", "Hall", role = c("aut")), diff --git a/NEWS.md b/NEWS.md index 47bfb716..cb3823d9 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,3 +1,10 @@ +OhdsiShinyModules v3.1.0 +======================== +- Removed percentage calculation from records field in CohortDiagnostics +- Updated the About module to reflect new module names and structure +- Updated module description vignette files to reflect new module names and structure +- Added interactive scatterplots for binary covariates when doing database and cohort comparisons in Characterization + OhdsiShinyModules v3.0.2 ======================== - Fixed bug with orphan concepts not loading diff --git a/docs/404.html b/docs/404.html index 99e5a026..8ad319b3 100644 --- a/docs/404.html +++ b/docs/404.html @@ -32,7 +32,7 @@ OhdsiShinyModules - 3.0.2 + 3.1.0
@@ -75,18 +75,12 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • @@ -95,7 +89,7 @@
  • @@ -75,18 +75,12 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • @@ -95,7 +89,7 @@
  • @@ -75,18 +75,12 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • @@ -95,7 +89,7 @@
  • @@ -75,18 +75,12 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • @@ -95,7 +89,7 @@
  • @@ -75,18 +75,12 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • @@ -95,7 +89,7 @@
  • @@ -75,18 +75,12 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • @@ -95,7 +89,7 @@
  • @@ -75,18 +75,12 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • @@ -95,7 +89,7 @@
  • @@ -75,18 +75,12 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • @@ -95,7 +89,7 @@
  • @@ -75,18 +75,12 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • @@ -95,7 +89,7 @@
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • diff --git a/docs/authors.html b/docs/authors.html index 5590400a..bec37db2 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -17,7 +17,7 @@ OhdsiShinyModules - 3.0.2 + 3.1.0
    @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • diff --git a/docs/index.html b/docs/index.html index 916e7e01..600565e8 100644 --- a/docs/index.html +++ b/docs/index.html @@ -33,7 +33,7 @@ OhdsiShinyModules - 3.0.2 + 3.1.0
    @@ -76,18 +76,12 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • @@ -96,7 +90,7 @@
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • +
    + +
    • Removed percentage calculation from records field in CohortDiagnostics
    • +
    • Updated the About module to reflect new module names and structure
    • +
    • Updated module description vignette files to reflect new module names and structure
    • +
    • Added interactive scatterplots for binary covariates when doing database and cohort comparisons in Characterization
    • +
    • Fixed bug with orphan concepts not loading
    • diff --git a/docs/pkgdown.yml b/docs/pkgdown.yml index 0c235b9d..9449d457 100644 --- a/docs/pkgdown.yml +++ b/docs/pkgdown.yml @@ -8,8 +8,6 @@ articles: Cohorts: Cohorts.html DataSources: DataSources.html Estimation: Estimation.html - EvidenceSynthesis: EvidenceSynthesis.html Prediction: Prediction.html ReportGenerator: ReportGenerator.html - SelfControlledCaseSeries: SelfControlledCaseSeries.html -last_built: 2024-10-04T14:25Z +last_built: 2024-10-07T15:13Z diff --git a/docs/reference/LargeDataTable.html b/docs/reference/LargeDataTable.html index 7c725564..13f6b753 100644 --- a/docs/reference/LargeDataTable.html +++ b/docs/reference/LargeDataTable.html @@ -24,7 +24,7 @@ OhdsiShinyModules - 3.0.2 + 3.1.0
    @@ -65,24 +65,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -60,24 +60,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -60,24 +60,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -60,24 +60,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog
  • @@ -58,24 +58,18 @@
  • Estimation
  • -
  • - Evidence Synthesis (Meta, Meta Analysis) -
  • Prediction
  • Report Generator
  • -
  • - Self-Controlled Case Series -
  • Changelog