From 700588a2a164603b756e32b2dc9286dfde753e85 Mon Sep 17 00:00:00 2001 From: Nathan Hall Date: Thu, 12 Sep 2024 13:48:55 -0400 Subject: [PATCH 1/8] Fixing Power tables re: #114 Standardizing power table outputs to adhere to OSM standard theme (reactable via resultTableViewer and resultTableServer). Also split the tables into 2 sub-tabs for easier readability --- R/estimation-cohort-method-power.R | 238 ++++++++++++++++++++++++----- 1 file changed, 202 insertions(+), 36 deletions(-) diff --git a/R/estimation-cohort-method-power.R b/R/estimation-cohort-method-power.R index 2acec47..d54cb99 100644 --- a/R/estimation-cohort-method-power.R +++ b/R/estimation-cohort-method-power.R @@ -30,10 +30,25 @@ cohortMethodPowerViewer <- function(id) { ns <- shiny::NS(id) shiny::div( - shiny::uiOutput(outputId = ns("powerTableCaption")), - shiny::tableOutput(outputId = ns("powerTable")), - shiny::uiOutput(outputId = ns("timeAtRiskTableCaption")), - shiny::tableOutput(outputId = ns("timeAtRiskTable")) + shiny::tabsetPanel( + type = 'pills', + id = ns('power'), + + shiny::tabPanel( + title = "Power Table", + resultTableViewer(ns("powerTable"), + downloadedFileName = "powerTable-"), + shiny::uiOutput(outputId = ns("powerTableCaption")) + ), + + shiny::tabPanel( + title = "TAR Table", + resultTableViewer(ns("timeAtRiskTable"), + downloadedFileName = "timeAtRiskTable-"), + shiny::uiOutput(outputId = ns("timeAtRiskTableCaption")) + ) + + ) ) } @@ -74,36 +89,102 @@ cohortMethodPowerServer <- function( } }) - output$powerTable <- shiny::renderTable({ + powerTable <- shiny::reactive({ row <- selectedRow() if (is.null(row$target)) { return(NULL) } else { - table <- prepareCohortMethodPowerTable( - row, - connectionHandler = connectionHandler, - resultDatabaseSettings = resultDatabaseSettings - ) - if (!row$unblind) { - table$targetOutcomes <- NA - table$comparatorOutcomes <- NA - table$targetIr <- NA - table$comparatorIr <- NA - } - colnames(table) <- c("Target subjects", - "Comparator subjects", - "Target years", - "Comparator years", - "Target events", - "Comparator events", - "Target IR (per 1,000 PY)", - "Comparator IR (per 1,000 PY)", - "MDRR") + table <- prepareCohortMethodPowerTable( + row, + connectionHandler = connectionHandler, + resultDatabaseSettings = resultDatabaseSettings + ) + if (!row$unblind) { + table$targetOutcomes <- NA + table$comparatorOutcomes <- NA + table$targetIr <- NA + table$comparatorIr <- NA + } + colnames(table) <- c("targetSubjects", + "comparatorSubjects", + "targetYears", + "comparatorYears", + "targetEvents", + "comparatorEvents", + "targetIr", # (per 1,000 PY)", + "comparatorIr", # (per 1,000 PY)", + "mdrr") return(table) } }) + estimationPowerTableColDefs <- function(){ + result <- list( + targetSubjects = reactable::colDef( + header = withTooltip("Target Subjects", + "Number of subjects in the target cohort"), + filterable = T + ), + comparatorSubjects = reactable::colDef( + header = withTooltip("Comparator Subjects", + "Number of subjects in the comparator cohort"), + filterable = T + ), + targetYears = reactable::colDef( + header = withTooltip("Target Years", + "Number of years of follow-up time in the target cohort"), + filterable = T + ), + comparatorYears = reactable::colDef( + header = withTooltip("Comparator Years", + "Number of years of follow-up time in the comparator cohort"), + filterable = T + ), + targetEvents = reactable::colDef( + header = withTooltip("Target Events", + "Distinct number of outcome events in the target cohort"), + filterable = T + # cell = function(value) { + # # Add < if cencored + # if (value < 0 ) paste("<", abs(value)) else abs(value) + # } + ), + comparatorEvents = reactable::colDef( + header = withTooltip("Comparator Events", + "Distinct number of outcome events in the comparator cohort"), + filterable = T + # cell = function(value) { + # # Add < if cencored + # if (value < 0 ) paste("<", abs(value)) else abs(value) + # } + ), + targetIr = reactable::colDef( + header = withTooltip("Target IR (per 1,000 PY)", + "Incidence rate per 1,000 person-years in the target cohort"), + filterable = T + ), + comparatorIr = reactable::colDef( + header = withTooltip("Comparator IR (per 1,000 PY)", + "Incidence rate per 1,000 person-years in the comparator cohort"), + filterable = T + ), + mdrr = reactable::colDef( + header = withTooltip("MDRR", + "The minimum detectable relative risk"), + filterable = T + ) + ) + return(result) + } + + resultTableServer( + id = "powerTable", + df = powerTable, + colDefsInput = estimationPowerTableColDefs(), + downloadedFileName = "powerTable-" + ) + output$timeAtRiskTableCaption <- shiny::renderUI({ row <- selectedRow() if (!is.null(row$target)) { @@ -116,25 +197,110 @@ cohortMethodPowerServer <- function( } }) - output$timeAtRiskTable <- shiny::renderTable({ + timeAtRiskTable <- shiny::reactive({ row <- selectedRow() if (is.null(row$target)) { return(NULL) } else { - followUpDist <- getCmFollowUpDist( - connectionHandler = connectionHandler, - resultDatabaseSettings = resultDatabaseSettings, - targetId = row$targetId, - comparatorId = row$comparatorId, - outcomeId = row$outcomeId, - databaseId = row$databaseId, - analysisId = row$analysisId - ) + followUpDist <- getCmFollowUpDist( + connectionHandler = connectionHandler, + resultDatabaseSettings = resultDatabaseSettings, + targetId = row$targetId, + comparatorId = row$comparatorId, + outcomeId = row$outcomeId, + databaseId = row$databaseId, + analysisId = row$analysisId + ) table <- prepareCohortMethodFollowUpDistTable(followUpDist) return(table) } }) + + estimationTimeAtRiskTableColDefs <- function(){ + result <- list( + Cohort = reactable::colDef( + header = withTooltip("Cohort", + "Indicates which cohort (target or comparator)"), + filterable = T + ), + Min = reactable::colDef( + header = withTooltip("Min", + "Minimum time (days) at-risk"), + filterable = T + ), + P10 = reactable::colDef( + header = withTooltip("P10", + "10th percentile time (days) at-risk"), + filterable = T + ), + P25 = reactable::colDef( + header = withTooltip("P25", + "25th percentile time (days) at-risk"), + filterable = T + ), + Median = reactable::colDef( + header = withTooltip("Median", + "Median time (days) at-risk"), + filterable = T + ), + P75 = reactable::colDef( + header = withTooltip("P75", + "75th percentile time (days) at-risk"), + filterable = T + ), + P90 = reactable::colDef( + header = withTooltip("P90", + "90th percentile time (days) at-risk"), + filterable = T + ), + Max = reactable::colDef( + header = withTooltip("Max", + "Maximum time (days) at-risk"), + filterable = T + ) + ) + return(result) + } + + resultTableServer( + id = "timeAtRiskTable", + df = timeAtRiskTable, + colDefsInput = estimationTimeAtRiskTableColDefs(), + downloadedFileName = "timeAtRiskTable-" + ) + + output$timeAtRiskTableCaption <- shiny::renderUI({ + row <- selectedRow() + if (!is.null(row$target)) { + text <- "Table 1b. Time (days) at risk distribution expressed as + minimum (min), 25th percentile (P25), median, 75th percentile (P75), and maximum (max) in the target + (%s) and comparator (%s) cohort after propensity score adjustment." + return(shiny::HTML(sprintf(text, row$target, row$comparator))) + } else { + return(NULL) + } + }) + + # output$timeAtRiskTable <- shiny::renderTable({ + # row <- selectedRow() + # if (is.null(row$target)) { + # return(NULL) + # } else { + # followUpDist <- getCmFollowUpDist( + # connectionHandler = connectionHandler, + # resultDatabaseSettings = resultDatabaseSettings, + # targetId = row$targetId, + # comparatorId = row$comparatorId, + # outcomeId = row$outcomeId, + # databaseId = row$databaseId, + # analysisId = row$analysisId + # ) + # + # table <- prepareCohortMethodFollowUpDistTable(followUpDist) + # return(table) + # } + # }) }) } @@ -280,4 +446,4 @@ getCmFollowUpDist <- function( database_id = databaseId ) ) -} +} \ No newline at end of file From 7dbdbe68e732a4d51b956d589131a79499362e6e Mon Sep 17 00:00:00 2001 From: Nathan Hall Date: Thu, 12 Sep 2024 15:32:58 -0400 Subject: [PATCH 2/8] Updating propensity score table Adding conditional formatting of colors to values to aid in interpretation, and also adding an absolute value of beta column. --- R/estimation-cohort-method-propensityModel.R | 40 +++++++++++++++++++- 1 file changed, 38 insertions(+), 2 deletions(-) diff --git a/R/estimation-cohort-method-propensityModel.R b/R/estimation-cohort-method-propensityModel.R index 9cc201b..2084a96 100644 --- a/R/estimation-cohort-method-propensityModel.R +++ b/R/estimation-cohort-method-propensityModel.R @@ -66,9 +66,22 @@ cohortMethodPropensityModelServer <- function( comparatorId = selectedRow()$comparatorId, databaseId = selectedRow()$databaseId, analysisId = selectedRow()$analysisId - ) + ) %>% + dplyr::mutate(absBeta = abs(coefficient)) }) + # ColorBrewer-inspired 3-color scale + Yellows <- function(x) grDevices::rgb(grDevices::colorRamp(c("#FFFFDD", "#FFFFB9", "#FFFF79")) + (x), maxColorValue = 255) + + # ColorBrewer-inspired 3-color scale + Blues <- function(x) grDevices::rgb(grDevices::colorRamp(c("aliceblue", "lightblue1", "skyblue2")) + (x), maxColorValue = 255) + + # ColorBrewer-inspired 3-color scale + Greens <- function(x) grDevices::rgb(grDevices::colorRamp(c("#E8FDCF", "yellowgreen")) + (x), maxColorValue = 255) + resultTableServer( id = 'propensityModelTable', df = data, @@ -77,11 +90,34 @@ cohortMethodPropensityModelServer <- function( show = F ), coefficient = reactable::colDef( - name = 'Beta', + name = 'Beta', + cell = function(value) { + if (value >= 0) paste0("+", round(value, 3)) else round(value, 3) + }, + style = function(value) { + color <- if (value > 0) { + "#B0D5FE" + } else if (value < 0) { + "#FEBABA" + } + list(background = color) + }, format = reactable::colFormat( digits = 3 ) ), + absBeta = reactable::colDef( + name = 'Beta (Absolute Value)', + format = reactable::colFormat( + digits = 3 + ), + style = function(value) { + if (!is.numeric(value)) return() + normalized <- (value - min(data()$absBeta)) / (max(data()$absBeta) - min(data()$absBeta)) + color <- Greens(normalized) + list(background = color) + } + ), covariateName = reactable::colDef( name = 'Covariate' ) From faf2b6670a28a8d387996c7d4f1596f6f57092b2 Mon Sep 17 00:00:00 2001 From: Nathan Hall Date: Wed, 18 Sep 2024 08:32:32 -0400 Subject: [PATCH 3/8] Updates to propensity score plot Overlaying equipoise statistic onto the plot, and truncating cohort names in legend --- ...ohort-method-propensityScoreDistribution.R | 69 ++++++++++++++++++- 1 file changed, 66 insertions(+), 3 deletions(-) diff --git a/R/estimation-cohort-method-propensityScoreDistribution.R b/R/estimation-cohort-method-propensityScoreDistribution.R index 7a5eb20..0f2e412 100644 --- a/R/estimation-cohort-method-propensityScoreDistribution.R +++ b/R/estimation-cohort-method-propensityScoreDistribution.R @@ -88,7 +88,17 @@ cohortMethodPropensityScoreDistServer <- function( comparatorName <- row$comparator - plot <- plotCohortMethodPs(ps, targetName, comparatorName) + equipoiseStatistic <- getCohortMethodEquipoise( + connectionHandler = connectionHandler, + resultDatabaseSettings = resultDatabaseSettings, + targetId = row$targetId, + comparatorId = row$comparatorId, + outcomeId = row$outcomeId, + analysisId = row$analysisId, + databaseId = row$databaseId + ) + + plot <- plotCohortMethodPs(ps, targetName, comparatorName, equipoiseStatistic) return(plot) } }) @@ -113,6 +123,55 @@ cohortMethodPropensityScoreDistServer <- function( ) } +getCohortMethodEquipoise <- function( + connectionHandler, + resultDatabaseSettings, + targetId, + comparatorId, + outcomeId, + analysisId, + databaseId = NULL +) { + if(is.null(targetId)){ + return(NULL) + } + sql <- " + SELECT + database_id, target_id, comparator_id, outcome_id, analysis_id, equipoise + FROM + @schema.@cm_table_prefixdiagnostics_summary cmpsd + WHERE + cmpsd.target_id = @target_id + AND cmpsd.comparator_id = @comparator_id + AND cmpsd.analysis_id = @analysis_id + AND cmpsd.outcome_id = @outcome_id + " + if(!is.null(databaseId)) { + sql <- paste(sql, paste("AND cmpsd.database_id = '@database_id'"), collapse = "\n") + } + + + result <- connectionHandler$queryDb( + sql = sql, + schema = resultDatabaseSettings$schema, + cm_table_prefix = resultDatabaseSettings$cmTablePrefix, + target_id = targetId, + comparator_id = comparatorId, + outcome_id = outcomeId, + analysis_id = analysisId, + database_id = databaseId + ) + + + if (!is.null(databaseId)) { + result$databaseId <- NULL + } + + eq <- round(result$equipoise, 4) + + return(eq) +} + getCohortMethodPs <- function( connectionHandler, resultDatabaseSettings, @@ -157,7 +216,7 @@ getCohortMethodPs <- function( } # CohortMethod-propensityScoreDist -plotCohortMethodPs <- function(ps, targetName, comparatorName) { +plotCohortMethodPs <- function(ps, targetName, comparatorName, equipoiseStatistic) { if(is.null(ps$preferenceScore)){ return(NULL) } @@ -180,13 +239,17 @@ plotCohortMethodPs <- function(ps, targetName, comparatorName) { grDevices::rgb(0, 0, 0.8, alpha = 0.5))) + ggplot2::scale_x_continuous("Preference score", limits = c(0, 1)) + ggplot2::scale_y_continuous("Density") + + ggplot2::ggtitle(paste0("Equipoise Statistic = ", equipoiseStatistic)) + ggplot2::theme(legend.title = ggplot2::element_blank(), panel.grid.major = ggplot2::element_blank(), panel.grid.minor = ggplot2::element_blank(), legend.position = "top", legend.text = theme, axis.text = theme, - axis.title = theme) + axis.title = theme, + plot.title = ggplot2::element_text(vjust = -20, face = "bold") + ) + + ggplot2::guides(fill = ggplot2::guide_legend(nrow = 2)) if (!is.null(ps$databaseId)) { plot <- plot + ggplot2::facet_grid(databaseId~., switch = "both") + ggplot2::theme(legend.position = "right") From 755f2da5cd2cfa33b0de87816a9236ecb134a388 Mon Sep 17 00:00:00 2001 From: Nathan Hall Date: Wed, 18 Sep 2024 10:26:39 -0400 Subject: [PATCH 4/8] Updating covariate balance plot Adding maxSDM to covariate balance plot --- R/estimation-cohort-method-covariateBalance.R | 87 ++++++++++++++++++- 1 file changed, 84 insertions(+), 3 deletions(-) diff --git a/R/estimation-cohort-method-covariateBalance.R b/R/estimation-cohort-method-covariateBalance.R index 7041056..45f3324 100644 --- a/R/estimation-cohort-method-covariateBalance.R +++ b/R/estimation-cohort-method-covariateBalance.R @@ -112,6 +112,7 @@ cohortMethodCovariateBalanceServer <- function( analysisId = row$analysisId)}, error = function(e){return(data.frame())} ) + return(balance) }) @@ -127,6 +128,22 @@ cohortMethodCovariateBalanceServer <- function( ) balancePlot <- shiny::reactive({ + + row <- selectedRow() + if(is.null(row$targetId)){ + return(NULL) + } + + maxSdmStatistic <- estimationGetMaxSdm( + connectionHandler = connectionHandler, + resultDatabaseSettings = resultDatabaseSettings, + targetId = row$targetId, + comparatorId = row$comparatorId, + outcomeId = row$outcomeId, + analysisId = row$analysisId, + databaseId = row$databaseId + ) + if (is.null(balance()) || nrow(balance()) == 0) { return(NULL) } else { @@ -134,7 +151,8 @@ cohortMethodCovariateBalanceServer <- function( balance = balance(), beforeLabel = "Before propensity score adjustment", afterLabel = "After propensity score adjustment", - textsearch = textSearchCohortMethod + textsearch = textSearchCohortMethod, + maxSdmStatistic ) return(plot) } @@ -151,7 +169,7 @@ cohortMethodCovariateBalanceServer <- function( row <- selectedRow() text <- "Figure 3. Covariate balance before and after propensity score adjustment. Each dot represents the standardizes difference of means for a single covariate before and after propensity score adjustment on the propensity - score. Move the mouse arrow over a dot for more details." + score. The maximum standardized difference of the mean (Max SDM) is given at the top of the figure. Move the mouse arrow over a dot for more details." return(shiny::HTML(sprintf(text))) } }) @@ -421,13 +439,24 @@ getCohortMethodCovariateBalanceSummary <- function( } +cmDiagnostics <- shiny::reactive({ + estimationGetCmDiagnostics( + connectionHandler = connectionHandler, + resultDatabaseSettings = resultDatabaseSettings, + targetIds = targetIds, + comparatorIds = comparatorIds, + outcomeId = outcomeId + ) +}) + plotCohortMethodCovariateBalanceScatterPlotNew <- function( balance, beforeLabel = "Before propensity score adjustment", afterLabel = "After propensity score adjustment", - textsearch = shiny::reactiveVal(NULL) + textsearch = shiny::reactiveVal(NULL), + maxSdmStatistic ){ if(is.null(textsearch())){ @@ -469,6 +498,7 @@ plotCohortMethodCovariateBalanceScatterPlotNew <- function( ) %>% plotly::layout( #shapes = list(xyline(limits)), + title = paste0("Max SDM: ", maxSdmStatistic), shapes = list(list( type = "line", x0 = 0, @@ -589,6 +619,57 @@ getCmOptions <- function(connectionHandler, } +estimationGetMaxSdm <- function( + connectionHandler = connectionHandler, + resultDatabaseSettings = resultDatabaseSettings, + targetId = targetId, + comparatorId = comparatorId, + outcomeId = outcomeId, + analysisId = analysisId, + databaseId = databaseId +){ + + sql <- " + SELECT DISTINCT + dmd.cdm_source_abbreviation database_name, + cmds.analysis_id, + cmds.target_id, + cmds.comparator_id, + cmds.outcome_id, + cmds.max_sdm, + cmds.ease + FROM + @schema.@cm_table_prefixdiagnostics_summary cmds + INNER JOIN @schema.@database_table dmd ON dmd.database_id = cmds.database_id + + where cmds.target_id = @target_id + and cmds.comparator_id = @comparator_id + and cmds.outcome_id = @outcome_id + and cmds.analysis_id = @analysis_id + and cmds.database_id = '@database_id' + ; + " + + result <- connectionHandler$queryDb( + sql = sql, + schema = resultDatabaseSettings$schema, + cm_table_prefix = resultDatabaseSettings$cmTablePrefix, + database_table = resultDatabaseSettings$databaseTable, + target_id = targetId, + comparator_id = comparatorId, + outcome_id = outcomeId, + analysis_id = analysisId, + database_id = databaseId + ) + + maxSdm <- round(result$maxSdm, 4) + + return( + maxSdm + ) + +} + From 5027d544b8c968220f115c9395ce659036ca0ad5 Mon Sep 17 00:00:00 2001 From: Nathan Hall Date: Wed, 18 Sep 2024 10:50:53 -0400 Subject: [PATCH 5/8] Updating captions and systematic error Adding to caption descriptions in figures and overlaying EASE statistic on systematic error plot --- R/estimation-cohort-method-covariateBalance.R | 4 +- ...ohort-method-propensityScoreDistribution.R | 5 +- R/estimation-cohort-method-systematicError.R | 71 +++++++++++++++++-- 3 files changed, 71 insertions(+), 9 deletions(-) diff --git a/R/estimation-cohort-method-covariateBalance.R b/R/estimation-cohort-method-covariateBalance.R index 45f3324..52a5c9b 100644 --- a/R/estimation-cohort-method-covariateBalance.R +++ b/R/estimation-cohort-method-covariateBalance.R @@ -169,7 +169,7 @@ cohortMethodCovariateBalanceServer <- function( row <- selectedRow() text <- "Figure 3. Covariate balance before and after propensity score adjustment. Each dot represents the standardizes difference of means for a single covariate before and after propensity score adjustment on the propensity - score. The maximum standardized difference of the mean (Max SDM) is given at the top of the figure. Move the mouse arrow over a dot for more details." + score. The maximum absolute standardized difference of the mean (Max SDM) is given at the top of the figure. Move the mouse arrow over a dot for more details." return(shiny::HTML(sprintf(text))) } }) @@ -498,7 +498,7 @@ plotCohortMethodCovariateBalanceScatterPlotNew <- function( ) %>% plotly::layout( #shapes = list(xyline(limits)), - title = paste0("Max SDM: ", maxSdmStatistic), + title = paste0("Max SDM Statistic = ", maxSdmStatistic), shapes = list(list( type = "line", x0 = 0, diff --git a/R/estimation-cohort-method-propensityScoreDistribution.R b/R/estimation-cohort-method-propensityScoreDistribution.R index 0f2e412..cbac7f1 100644 --- a/R/estimation-cohort-method-propensityScoreDistribution.R +++ b/R/estimation-cohort-method-propensityScoreDistribution.R @@ -32,7 +32,8 @@ cohortMethodPropensityScoreDistViewer <- function(id) { shiny::plotOutput(outputId = ns("psDistPlot")), shiny::div(shiny::strong("Figure 2."),"Preference score distribution. The preference score is a transformation of the propensity score that adjusts for differences in the sizes of the two treatment groups. A higher overlap indicates subjects in the - two groups were more similar in terms of their predicted probability of receiving one treatment over the other."), + two groups were more similar in terms of their predicted probability of receiving one treatment over the other. + The equipoise statistic is also given at the top of the figure."), shiny::div(style = "display: inline-block;vertical-align: top;margin-bottom: 10px;", shiny::downloadButton(outputId = ns("downloadPsDistPlotPng"), label = "Download plot as PNG"), @@ -247,7 +248,7 @@ plotCohortMethodPs <- function(ps, targetName, comparatorName, equipoiseStatisti legend.text = theme, axis.text = theme, axis.title = theme, - plot.title = ggplot2::element_text(vjust = -20, face = "bold") + plot.title = ggplot2::element_text(vjust = -20) ) + ggplot2::guides(fill = ggplot2::guide_legend(nrow = 2)) if (!is.null(ps$databaseId)) { diff --git a/R/estimation-cohort-method-systematicError.R b/R/estimation-cohort-method-systematicError.R index fa1ce54..65e39bc 100644 --- a/R/estimation-cohort-method-systematicError.R +++ b/R/estimation-cohort-method-systematicError.R @@ -33,7 +33,8 @@ cohortMethodSystematicErrorViewer <- function(id) { shiny::div(shiny::strong("Figure 4."),"Systematic error. Effect size estimates for the negative controls (true hazard ratio = 1) and positive controls (true hazard ratio > 1), 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."), + estimator should have the true effect size within the 95 percent confidence interval 95 percent of times. + The expected absolute systematic error (EASE) statistic is also shown at the top of the figure."), shiny::div(style = "display: inline-block;vertical-align: top;margin-bottom: 10px;", shiny::downloadButton(outputId = ns("downloadSystematicErrorPlotPng"), label = "Download plot as PNG"), @@ -82,6 +83,15 @@ cohortMethodSystematicErrorServer <- function( databaseId = row$databaseId ) + ease <- estimationGetEase( + connectionHandler = connectionHandler, + resultDatabaseSettings = resultDatabaseSettings, + targetId = row$targetId, + comparatorId = row$comparatorId, + analysisId = row$analysisId, + databaseId = row$databaseId + ) + # remove the RR zeros that replace NAs during data upload controlResults$logRr[controlResults$logRr == 0] <- NA controlResults$ci95Lb[controlResults$ci95Lb == 0] <- NA @@ -90,7 +100,7 @@ cohortMethodSystematicErrorServer <- function( controlResults$calibratedCi95Lb[controlResults$calibratedCi95Lb == 0] <- NA controlResults$calibratedCi95Ub[controlResults$calibratedCi95Ub == 0] <- NA - plot <- plotCohortMethodScatter(controlResults) + plot <- plotCohortMethodScatter(controlResults, ease) return(plot) } }) @@ -175,7 +185,7 @@ getCohortMethodControlResults <- function( } -plotCohortMethodScatter <- function(controlResults) { +plotCohortMethodScatter <- function(controlResults, ease) { if(nrow(controlResults)==0){ return(NULL) @@ -262,6 +272,7 @@ plotCohortMethodScatter <- function(controlResults) { labels = breaks) + ggplot2::scale_y_continuous("Standard Error", limits = c(0, 1)) + ggplot2::facet_grid(yGroup ~ Group) + + ggplot2::ggtitle(paste0("EASE Statistic = ", ease)) + ggplot2::theme(panel.grid.minor = ggplot2::element_blank(), panel.background = ggplot2::element_blank(), panel.grid.major = ggplot2::element_blank(), @@ -272,10 +283,60 @@ plotCohortMethodScatter <- function(controlResults) { legend.key = ggplot2::element_blank(), strip.text.x = theme, strip.text.y = theme, - strip.background = ggplot2::element_blank(), - legend.position = "none") + strip.background = ggplot2::element_blank() + # , + # legend.position = "top", + # legend.text = paste0("EASE = ", ease) + ) return(plot) } +estimationGetEase <- function( + connectionHandler = connectionHandler, + resultDatabaseSettings = resultDatabaseSettings, + targetId = targetId, + comparatorId = comparatorId, + analysisId = analysisId, + databaseId = databaseId +){ + + sql <- " + SELECT DISTINCT + dmd.cdm_source_abbreviation database_name, + cmds.analysis_id, + cmds.target_id, + cmds.comparator_id, + cmds.max_sdm, + cmds.ease + FROM + @schema.@cm_table_prefixdiagnostics_summary cmds + INNER JOIN @schema.@database_table dmd ON dmd.database_id = cmds.database_id + + where cmds.target_id = @target_id + and cmds.comparator_id = @comparator_id + and cmds.analysis_id = @analysis_id + and cmds.database_id = '@database_id' + ; + " + + result <- connectionHandler$queryDb( + sql = sql, + schema = resultDatabaseSettings$schema, + cm_table_prefix = resultDatabaseSettings$cmTablePrefix, + database_table = resultDatabaseSettings$databaseTable, + target_id = targetId, + comparator_id = comparatorId, + analysis_id = analysisId, + database_id = databaseId + ) + + ease <- round(result$ease, 4) + + return( + ease + ) + +} + From d07fff0d2a9f791513e0103988a9843a4fc05559 Mon Sep 17 00:00:00 2001 From: Nathan Hall Date: Wed, 18 Sep 2024 11:29:24 -0400 Subject: [PATCH 6/8] Updating systematic error Adding more descriptive filenames for plot downloads --- R/estimation-cohort-method-systematicError.R | 21 ++++++++++++++++++-- 1 file changed, 19 insertions(+), 2 deletions(-) diff --git a/R/estimation-cohort-method-systematicError.R b/R/estimation-cohort-method-systematicError.R index 65e39bc..d530322 100644 --- a/R/estimation-cohort-method-systematicError.R +++ b/R/estimation-cohort-method-systematicError.R @@ -109,8 +109,25 @@ cohortMethodSystematicErrorServer <- function( return(systematicErrorPlot()) }) + picName <- shiny::reactive({ + row <- selectedRow() + if (is.null(row)) { + return(NULL) + } else { + picName <- paste0("Target=", stringr::str_trunc(row$target, 35), "_", + "Comparator=",stringr::str_trunc(row$comparator, 35), "_", + "Analysis=",row$description, "_", + "DB=",row$cdmSourceAbbreviation, "_", + Sys.Date()) + } + + return(picName) + + }) + output$downloadSystematicErrorPlotPng <- shiny::downloadHandler( - filename = "SystematicError.png", + + filename = paste0("SystematicErrorPlot_", picName(), ".png"), contentType = "image/png", content = function(file) { ggplot2::ggsave(file, plot = systematicErrorPlot(), width = 12, height = 5.5, dpi = 400) @@ -118,7 +135,7 @@ cohortMethodSystematicErrorServer <- function( ) output$downloadSystematicErrorPlotPdf <- shiny::downloadHandler( - filename = "SystematicError.pdf", + filename = paste0("SystematicErrorPlot_", picName(), ".pdf"), contentType = "application/pdf", content = function(file) { ggplot2::ggsave(file = file, plot = systematicErrorPlot(), width = 12, height = 5.5) From b423a2815c7c817109a18d758692c2c7c4480923 Mon Sep 17 00:00:00 2001 From: jreps Date: Thu, 19 Sep 2024 13:35:07 -0400 Subject: [PATCH 7/8] Develop (#340) * Fixing #301 (#326) Adding alphabetical sort to DB input options * Fixing #296 (#327) Standardizing pickerInput type for database selection where multiple options are possible to improve UX. Also fixed some colDefs in Exposed Cases * Fixing #302 and Filtered Data Downloads (#332) * Fixing #302 and Filtered Data Downloads All filtered data downloads across all modules should work now, with a button styled the same as the full download. It needs to be a CSV handler though due to the reactable statte * Updating the fix Also fixed download buttons in Cohorts module, addressing #298 * Update R_CMD_check_Hades.yaml * Update R_CMD_check_Hades.yaml * Update R_CMD_check_Hades.yaml * fixing R checks fixing R checks * Update cohort-diagnostics-databaseInformation.R (#333) Fixing the issue reported in https://github.com/OHDSI/OhdsiShinyModules/issues/162 * fixing issue issue_330 (#334) fixing time plot x-axis * fixing issue 167 (#335) added code to get long database names on multiple lines * Update cohort-diagnostics-timeDistributions.R (#336) adding fix for issue 168 * Update patient-level-prediction-modelSummary.R (#337) --------- Co-authored-by: Nathan Hall <106178605+nhall6@users.noreply.github.com> --- .github/workflows/R_CMD_check_Hades.yaml | 8 +- R/characterization-caseSeries.R | 26 +- R/characterization-database.R | 13 +- R/characterization-incidence.R | 18 +- R/characterization-riskFactors.R | 37 +- R/characterization-timeToEvent.R | 13 +- R/cohort-diagnostics-cohort-overlap.R | 5 +- R/cohort-diagnostics-databaseInformation.R | 2 +- R/cohort-diagnostics-timeDistributions.R | 5 +- R/cohort-generator-main.R | 136 +-- R/components-data-viewer.R | 67 +- R/helpers-emptyPlotly.R | 26 + R/helpers-sccsPlots.R | 10 +- R/patient-level-prediction-modelSummary.R | 9 +- hs_err_pid47729.log | 1199 -------------------- 15 files changed, 269 insertions(+), 1305 deletions(-) delete mode 100644 hs_err_pid47729.log diff --git a/.github/workflows/R_CMD_check_Hades.yaml b/.github/workflows/R_CMD_check_Hades.yaml index 36fe3f0..2a960c6 100644 --- a/.github/workflows/R_CMD_check_Hades.yaml +++ b/.github/workflows/R_CMD_check_Hades.yaml @@ -52,7 +52,7 @@ jobs: CDM5_SPARK_CONNECTION_STRING: ${{ secrets.CDM5_SPARK_CONNECTION_STRING }} steps: - - uses: actions/checkout@v2 + - uses: actions/checkout@v4 - uses: r-lib/actions/setup-r@v2 with: @@ -85,7 +85,7 @@ jobs: - name: Upload source package if: success() && runner.os == 'macOS' && github.event_name != 'pull_request' && github.ref == 'refs/heads/main' - uses: actions/upload-artifact@v2 + uses: actions/upload-artifact@v4 with: name: package_tarball path: check/*.tar.gz @@ -113,7 +113,7 @@ jobs: steps: - - uses: actions/checkout@v2 + - uses: actions/checkout@v4 with: fetch-depth: 0 @@ -155,7 +155,7 @@ jobs: - name: Download package tarball if: ${{ env.new_version != '' }} - uses: actions/download-artifact@v2 + uses: actions/download-artifact@v4 with: name: package_tarball diff --git a/R/characterization-caseSeries.R b/R/characterization-caseSeries.R index 9a3ef0f..af791b5 100644 --- a/R/characterization-caseSeries.R +++ b/R/characterization-caseSeries.R @@ -74,20 +74,38 @@ characterizationCaseSeriesServer <- function( output$inputs <- shiny::renderUI({ # need to make reactive? shiny::div( - shiny::selectInput( + shinyWidgets::pickerInput( inputId = session$ns('databaseId'), label = 'Database: ', choices = options()$databaseIds, selected = options()$databaseIds[1], - multiple = F + multiple = F, + options = shinyWidgets::pickerOptions( + actionsBox = TRUE, + liveSearch = TRUE, + size = 10, + dropupAuto = TRUE, + liveSearchStyle = "contains", + liveSearchPlaceholder = "Type here to search", + virtualScroll = 50 + ) ), - shiny::selectInput( + shinyWidgets::pickerInput( inputId = session$ns('tarInd'), label = 'Time-at-risk: ', choices = options()$tarInds, selected = options()$tarInds[1], - multiple = F + multiple = F, + options = shinyWidgets::pickerOptions( + actionsBox = TRUE, + liveSearch = TRUE, + size = 10, + dropupAuto = TRUE, + liveSearchStyle = "contains", + liveSearchPlaceholder = "Type here to search", + virtualScroll = 50 + ) ), shiny::actionButton( diff --git a/R/characterization-database.R b/R/characterization-database.R index 46b3b31..e787ee8 100644 --- a/R/characterization-database.R +++ b/R/characterization-database.R @@ -85,12 +85,21 @@ characterizationDatabaseComparisonServer <- function( output$inputs <- shiny::renderUI({ shiny::div( - shiny::selectInput( + shinyWidgets::pickerInput( inputId = session$ns('databaseIds'), label = 'Databases: ', choices = inputVals()$databaseIds, selected = inputVals()$databaseIds[1], - multiple = T + multiple = T, + options = shinyWidgets::pickerOptions( + actionsBox = TRUE, + liveSearch = TRUE, + size = 10, + dropupAuto = TRUE, + liveSearchStyle = "contains", + liveSearchPlaceholder = "Type here to search", + virtualScroll = 50 + ) ), shiny::sliderInput( diff --git a/R/characterization-incidence.R b/R/characterization-incidence.R index 60a2d20..4f6ca8e 100644 --- a/R/characterization-incidence.R +++ b/R/characterization-incidence.R @@ -268,21 +268,27 @@ characterizationIncidenceServer <- function( style = "font-weight: bold; font-size: 20px; text-align: center; margin-bottom: 20px;" ), - shiny::selectInput( + shinyWidgets::pickerInput( inputId = session$ns('outcomeIds'), label = 'Outcome: ', choices = outcomes(), - selected = 1, + selected = outcomes()[1], multiple = T, - selectize = TRUE, - width = NULL, - size = NULL + options = shinyWidgets::pickerOptions( + actionsBox = TRUE, + liveSearch = TRUE, + size = 10, + dropupAuto = TRUE, + liveSearchStyle = "contains", + liveSearchPlaceholder = "Type here to search", + virtualScroll = 50 + ) ), shinyWidgets::pickerInput( inputId = session$ns('databaseSelector'), label = 'Filter By Database: ', - choices = ciOptions$databases, + choices = sort(ciOptions$databases), selected = ciOptions$databases, multiple = T, options = shinyWidgets::pickerOptions( diff --git a/R/characterization-riskFactors.R b/R/characterization-riskFactors.R index 7623c0e..373ef5a 100644 --- a/R/characterization-riskFactors.R +++ b/R/characterization-riskFactors.R @@ -684,8 +684,41 @@ characteriationCountsColDefs <- function( filterable = T ), + minPriorObservation = reactable::colDef( + header = withTooltip("Min Prior Observation", + "Minimum prior observation time (days)"), + filterable = T, + filterInput = function(values, name) { + shiny::tags$select( + # Set to undefined to clear the filter + onchange = sprintf("Reactable.setFilter('%s', '%s', event.target.value || undefined)", elementId, name), + # "All" has an empty value to clear the filter, and is the default option + shiny::tags$option(value = "", "All"), + lapply(unique(values), shiny::tags$option), + "aria-label" = sprintf("Filter %s", name), + style = "width: 100%; height: 28px;" + ) + } + ), + outcomeWashoutDays = reactable::colDef( + header = withTooltip("Outcome Washout Days", + "Number of days for the outcome washout"), + filterable = T, + filterInput = function(values, name) { + shiny::tags$select( + # Set to undefined to clear the filter + onchange = sprintf("Reactable.setFilter('%s', '%s', event.target.value || undefined)", elementId, name), + # "All" has an empty value to clear the filter, and is the default option + shiny::tags$option(value = "", "All"), + lapply(unique(values), shiny::tags$option), + "aria-label" = sprintf("Filter %s", name), + style = "width: 100%; height: 28px;" + ) + } + ), + rowCount = reactable::colDef( - header = withTooltip("# rows", + header = withTooltip("# Rows", "Number of exposures in the cohort (people can be in more than once)"), cell = function(value) { if(is.null(value)){return('< min threshold')} @@ -694,7 +727,7 @@ characteriationCountsColDefs <- function( } ), personCount = reactable::colDef( - header = withTooltip("# persons", + header = withTooltip("# Persons", "Number of distinct people in the cohort"), cell = function(value) { if(is.null(value)){return('< min threshold')} diff --git a/R/characterization-timeToEvent.R b/R/characterization-timeToEvent.R index abfb322..0252ed7 100644 --- a/R/characterization-timeToEvent.R +++ b/R/characterization-timeToEvent.R @@ -174,12 +174,21 @@ characterizationTimeToEventServer <- function( shiny::fluidPage( shiny::fluidRow( - shiny::selectInput( + shinyWidgets::pickerInput( inputId = session$ns("databases"), label = "Databases:", multiple = T, choices = unique(allData()$databaseName), - selected = unique(allData()$databaseName) + selected = unique(allData()$databaseName), + options = shinyWidgets::pickerOptions( + actionsBox = TRUE, + liveSearch = TRUE, + size = 10, + dropupAuto = TRUE, + liveSearchStyle = "contains", + liveSearchPlaceholder = "Type here to search", + virtualScroll = 50 + ) ), shiny::fluidRow( diff --git a/R/cohort-diagnostics-cohort-overlap.R b/R/cohort-diagnostics-cohort-overlap.R index 0d37664..efe4f5b 100644 --- a/R/cohort-diagnostics-cohort-overlap.R +++ b/R/cohort-diagnostics-cohort-overlap.R @@ -128,7 +128,10 @@ plotCohortOverlap <- function(data, title = "", gridcolor = 'ffff'), yaxis = list(zerolinecolor = '#ffff', - title = database, + title = addTextBreaks( + text = database, + length = 25 + ), zerolinewidth = 1, gridcolor = 'ffff')) diff --git a/R/cohort-diagnostics-databaseInformation.R b/R/cohort-diagnostics-databaseInformation.R index 6e1ac0d..a75e390 100644 --- a/R/cohort-diagnostics-databaseInformation.R +++ b/R/cohort-diagnostics-databaseInformation.R @@ -29,7 +29,7 @@ databaseInformationView <- function(id) { shinydashboard::box( width = NULL, title = "Execution meta-data", - shiny::tags$p("Each entry relates to execution on a given cdm. Results are merged between executions incrementally"), + shiny::tags$p("Each entry relates to execution on a given CDM. Results are merged between executions incrementally"), shinycssloaders::withSpinner(reactable::reactableOutput(outputId = ns("databaseInformationTable"))), shiny::conditionalPanel( "output.databaseInformationTableIsSelected == true", diff --git a/R/cohort-diagnostics-timeDistributions.R b/R/cohort-diagnostics-timeDistributions.R index 764809f..eadb641 100644 --- a/R/cohort-diagnostics-timeDistributions.R +++ b/R/cohort-diagnostics-timeDistributions.R @@ -176,7 +176,10 @@ plotTimeDistribution <- function(data, shortNameRef = NULL, showMax = FALSE) { zerolinewidth = 2, gridcolor = 'ffff'), yaxis = list( - title = db, + title = addTextBreaks( + text = db, + length = 25 # change this based on plot height? + ), showTitle = FALSE, zerolinecolor = '#ffff', zerolinewidth = 2, diff --git a/R/cohort-generator-main.R b/R/cohort-generator-main.R index 2e2f7b8..ee7fb97 100644 --- a/R/cohort-generator-main.R +++ b/R/cohort-generator-main.R @@ -64,35 +64,41 @@ cohortGeneratorViewer <- function(id) { collapsible = T, collapsed = F, width = '100%', - title = shiny::span( shiny::icon("file-arrow-down"),'Download Data'), - #solidHeader = TRUE, - - shiny::downloadButton( - ns('downloadCohortCountsFull'), - label = "Download (Full)", - icon = shiny::icon("download") - ), - - shiny::actionButton( - ns('downloadCohortCountsFiltered'), - label = "Download (Filtered)", - icon = shiny::icon("download"), - onclick = paste0("Reactable.downloadDataCSV('", ns('cohortCounts'), - "', 'cohort-count-data-filtered-", Sys.Date(), ".csv')") - ) - ), + # title = shiny::span( shiny::icon("file-arrow-down"),'Download Data'), + # #solidHeader = TRUE, + # + # shiny::downloadButton( + # ns('downloadCohortCountsFull'), + # label = "Download (Full)", + # icon = shiny::icon("download") + # ), + # + # shiny::actionButton( + # ns('downloadCohortCountsFiltered'), + # label = "Download (Filtered)", + # icon = shiny::icon("download"), + # onclick = paste0("Reactable.downloadDataCSV('", ns('cohortCounts'), + # "', 'cohort-count-data-filtered-", Sys.Date(), ".csv')") + # ) + # ), - shinydashboard::box( - width = '100%', - title = shiny::span( shiny::icon("table"), 'Counts Table'), - #solidHeader = TRUE, - - shiny::uiOutput(ns("selectColsCohortCounts") - ), - - reactable::reactableOutput( - outputId = ns("cohortCounts") - ) + # shinydashboard::box( + # width = '100%', + # title = shiny::span( shiny::icon("table"), 'Counts Table'), + # #solidHeader = TRUE, + # + # shiny::uiOutput(ns("selectColsCohortCounts") + # ), + # + # reactable::reactableOutput( + # outputId = ns("cohortCounts") + # ) + # ) + + resultTableViewer( + ns("cohortCounts"), + downloadedFileName = "cohortCountsTable-" + ) ) ), @@ -103,29 +109,30 @@ cohortGeneratorViewer <- function(id) { collapsible = T, collapsed = F, width = '100%', - title = shiny::span( shiny::icon("file-arrow-down"),'Download Data'), - #solidHeader = TRUE, + # title = shiny::span( shiny::icon("file-arrow-down"),'Download Data'), + # #solidHeader = TRUE, + # + # shiny::downloadButton( + # ns('downloadCohortGeneration'), + # label = "Download", + # icon = shiny::icon("download") + # ) + # ), + # + # shinydashboard::box( + # status = 'info', + # width = '100%', + # title = shiny::span( shiny::icon("table"), 'Generation Table'), + # #solidHeader = TRUE, + # + # shiny::uiOutput(ns("selectColsCohortGeneration") + # ), - shiny::downloadButton( - ns('downloadCohortGeneration'), - label = "Download", - icon = shiny::icon("download") - ) - ), - - shinydashboard::box( - status = 'info', - width = '100%', - title = shiny::span( shiny::icon("table"), 'Generation Table'), - #solidHeader = TRUE, - - shiny::uiOutput(ns("selectColsCohortGeneration") - ), - - reactable::reactableOutput( - outputId = ns("cohortGeneration") - ) + resultTableViewer( + ns("cohortGeneration"), + downloadedFileName = "cohortGenerationTable-" ) + ) ), shiny::tabPanel( @@ -148,20 +155,20 @@ cohortGeneratorViewer <- function(id) { shiny::uiOutput(ns("inputsText")), - shinydashboard::box( - collapsible = T, - collapsed = F, - width = '100%', - title = shiny::span( shiny::icon("file-arrow-down"),'Download Data'), - #solidHeader = TRUE, - - shiny::downloadButton( - ns('downloadAttritionTable'), - label = "Download", - icon = shiny::icon("download") - ) - ), - + # shinydashboard::box( + # collapsible = T, + # collapsed = F, + # width = '100%', + # title = shiny::span( shiny::icon("file-arrow-down"),'Download Data'), + # #solidHeader = TRUE, + # + # shiny::downloadButton( + # ns('downloadAttritionTable'), + # label = "Download", + # icon = shiny::icon("download") + # ) + # ), + # shinydashboard::box( @@ -173,7 +180,8 @@ cohortGeneratorViewer <- function(id) { # shiny::uiOutput(ns("selectColsCohortAttrition") # ), - resultTableViewer(ns('attritionTable')) + resultTableViewer(ns('attritionTable'), + downloadedFileName = "cohortAttritionTable-") ), shinydashboard::box( diff --git a/R/components-data-viewer.R b/R/components-data-viewer.R index 6f54453..39bc33b 100644 --- a/R/components-data-viewer.R +++ b/R/components-data-viewer.R @@ -5,6 +5,22 @@ #output: download buttons, table, and column selector +filteredDownloadButton <- function( + tableId, + label = "Download (Filtered)", + filename = "filteredData.csv", + icon = shiny::icon("download") + ) { + shiny::tags$div(class = "col-sm-3", + htmltools::tags$button( + class = "btn btn-default", + shiny::tags$i(class = "fas fa-download", role = "presentation", "aria-label" = "download icon"), + label, + onclick = sprintf("Reactable.downloadDataCSV('%s', '%s')", tableId, filename) + ) + ) +} + #' Result Table Viewer #' #' @param id string @@ -37,32 +53,41 @@ resultTableViewer <- function( icon = shiny::icon("download") ) ), + + # shiny::column( + # width = 3, + # shiny::downloadButton( + # ns('downloadDataFiltered'), + # label = "Download (Filtered)", + # icon = shiny::icon("download"), + # onClick = "Shiny.setInputValue('table_state:to_csv', + # Reactable.getState('resultData').sortedData)" + # ) + # ) + shiny::column( width = 3, - shiny::actionButton( - ns('downloadDataFiltered'), - label = "Download (Filtered)", - icon = shiny::icon("download"), - onclick = paste0( - "Reactable.downloadDataCSV('", - ns('resultData'), - "', 'result-data-filtered-", - downloadedFileName, - Sys.Date(), - ".csv')" + htmltools::browsable( + htmltools::tagList( + filteredDownloadButton("resultDataFiltered", "Download (Filtered)", + filename = paste('result-data-filtered-', downloadedFileName, Sys.Date(), '.csv', sep = ''), ) + ) ) ) ), + shiny::fluidRow( shinycssloaders::withSpinner( reactable::reactableOutput( outputId = ns("resultData"), - width = "100%") + width = "100%" ) - ) + ) + ) ) - )) + ) + ) } @@ -349,6 +374,8 @@ fuzzySearch<- reactable::JS('function(rows, columnIds, filterValue) { }); }') + + output$resultData <- reactable::renderReactable({ if (is.null(input$dataCols)) { data = newdf() @@ -388,7 +415,7 @@ fuzzySearch<- reactable::JS('function(rows, columnIds, filterValue) { rowStyle = list( height = height ), - elementId = elementIdName() + elementId = 'resultDataFiltered' #, experimental #theme = ohdsiReactableTheme ) @@ -396,6 +423,16 @@ fuzzySearch<- reactable::JS('function(rows, columnIds, filterValue) { # ) }) + output$downloadDataFiltered <- shiny::downloadHandler( + filename = function() { + paste("result-data-filtered-", Sys.Date(), ".csv", sep = "") + }, + content = function(file) { + data <- input$table_state + utils::write.csv(data, file) + } + ) + # download full data button output$downloadDataFull <- shiny::downloadHandler( diff --git a/R/helpers-emptyPlotly.R b/R/helpers-emptyPlotly.R index cac00fe..359b5e8 100644 --- a/R/helpers-emptyPlotly.R +++ b/R/helpers-emptyPlotly.R @@ -12,3 +12,29 @@ emptyPlot <- function(title = NULL){ ) return(p) } + +# takes a vector of 'text' and add
every 'length' characters +addTextBreaks <- function( + text, + length +){ + + textBreakVector <- c() + + for(textVal in text){ + textBreak <- "" + reps <- 1:ceiling(nchar(textVal)/length) + for(repsI in reps){ + space <- substr(textVal, (repsI-1)*length, (repsI-1)*length) == ' ' + if(space){ + breakText <- '
' + } else{ + breakText <- '
-' + } + textBreak <- paste0(textBreak, ifelse(repsI==1, '', breakText),substr(textVal, (repsI-1)*length+1, min(nchar(textVal), (repsI)*length))) + } + textBreakVector <- c(textBreakVector, textBreak) + } + +return(textBreakVector) +} diff --git a/R/helpers-sccsPlots.R b/R/helpers-sccsPlots.R index 947557f..f066808 100644 --- a/R/helpers-sccsPlots.R +++ b/R/helpers-sccsPlots.R @@ -488,7 +488,15 @@ plotSeasonSpline <- function(seasonSpline, rrLim = c(0.1, 10)) { # unknown function? convertMonthToStartDate <- function(x){ - return(as.Date(x, origin = "1950-01-01")) + #return(as.Date(x, origin = "1950-01-01")) + year <- floor(x / 12) + month <- floor(x %% 12) + 1 + return(as.Date(sprintf( + "%s-%s-%s", + year, + month, + 1 + ))) } # adding missing sccsModel as input plotCalendarTimeSpline <- function(calendarTimeSpline, rrLim = c(0.1, 10)) { diff --git a/R/patient-level-prediction-modelSummary.R b/R/patient-level-prediction-modelSummary.R index 8b0a734..9dee5c0 100644 --- a/R/patient-level-prediction-modelSummary.R +++ b/R/patient-level-prediction-modelSummary.R @@ -387,9 +387,12 @@ getModelDesignInfo <- function( } modelType <- connectionHandler$queryDb( - 'select distinct model_type from - @schema.@plp_table_prefixmodels - where model_design_id = @model_design_id;', + 'select distinct ms.model_type from + @schema.@plp_table_prefixmodel_settings ms + inner join + @schema.@plp_table_prefixmodel_designs md + on ms.model_setting_id = md.model_setting_id + where md.model_design_id = @model_design_id;', schema = resultDatabaseSettings$schema, plp_table_prefix = resultDatabaseSettings$plpTablePrefix, model_design_id = modelDesignId() diff --git a/hs_err_pid47729.log b/hs_err_pid47729.log deleted file mode 100644 index 9a096be..0000000 --- a/hs_err_pid47729.log +++ /dev/null @@ -1,1199 +0,0 @@ -# -# A fatal error has been detected by the Java Runtime Environment: -# -# SIGSEGV (0xb) at pc=0x000000010d4ca9d8, pid=47729, tid=259 -# -# JRE version: OpenJDK Runtime Environment Corretto-17.0.5.8.1 (17.0.5+8) (build 17.0.5+8-LTS) -# Java VM: OpenJDK 64-Bit Server VM Corretto-17.0.5.8.1 (17.0.5+8-LTS, mixed mode, sharing, tiered, compressed oops, compressed class ptrs, g1 gc, bsd-aarch64) -# Problematic frame: -# V [libjvm.dylib+0x4ca9d8] jni_GetObjectClass+0x124 -# -# No core dump will be written. Core dumps have been disabled. To enable core dumping, try "ulimit -c unlimited" before starting Java again -# -# If you would like to submit a bug report, please visit: -# https://github.com/corretto/corretto-17/issues/ -# - ---------------- S U M M A R Y ------------ - -Command Line: -Djava.awt.headless=true -Xmx512m -Xrs vfprintf exit -Xss2m - -Host: "MacBookPro18,3" arm64, 8 cores, 16G, Darwin 23.5.0, macOS 14.5 (23F79) -Time: Wed May 22 09:03:48 2024 EDT elapsed time: 74.128281 seconds (0d 0h 1m 14s) - ---------------- T H R E A D --------------- - -Current thread (0x000000011e307600): JavaThread "main" [_thread_in_vm, id=259, stack(0x000000016b494000,0x000000016bc90000)] - -Stack: [0x000000016b494000,0x000000016bc90000], sp=0x000000016bc7a5c0, free space=8089k -Native frames: (J=compiled Java code, j=interpreted, Vv=VM code, C=native code) -V [libjvm.dylib+0x4ca9d8] jni_GetObjectClass+0x124 -C [rJava.so+0x60fc] RcallMethod+0x37c -C [libR.dylib+0x847ec] do_External+0x12c -C [libR.dylib+0xbb9ec] bcEval+0x6eec -C [libR.dylib+0xb44c8] Rf_eval+0x248 -C [libR.dylib+0xd1ad4] R_execClosure+0xc54 -C [libR.dylib+0xd030c] Rf_applyClosure+0x20c -C [libR.dylib+0xbb6b0] bcEval+0x6bb0 -C [libR.dylib+0xb44c8] Rf_eval+0x248 -C [libR.dylib+0xd1ad4] R_execClosure+0xc54 -C [libR.dylib+0xd030c] Rf_applyClosure+0x20c -C [libR.dylib+0x11d400] dispatchMethod+0x300 -C [libR.dylib+0x11d0c0] Rf_usemethod+0x300 -C [libR.dylib+0x11d768] do_usemethod+0x2e8 -C [libR.dylib+0xbc0b0] bcEval+0x75b0 -C [libR.dylib+0xb44c8] Rf_eval+0x248 -C [libR.dylib+0xd1ad4] R_execClosure+0xc54 -C [libR.dylib+0xd030c] Rf_applyClosure+0x20c -C [libR.dylib+0xb479c] Rf_eval+0x51c -C [libR.dylib+0xd4264] do_begin+0x1a4 -C [libR.dylib+0xb46c8] Rf_eval+0x448 -C [libR.dylib+0xd1ad4] R_execClosure+0xc54 -C [libR.dylib+0xd030c] Rf_applyClosure+0x20c -C [libR.dylib+0xbb6b0] bcEval+0x6bb0 -C [libR.dylib+0xb44c8] Rf_eval+0x248 -C [libR.dylib+0xd1ad4] R_execClosure+0xc54 -C [libR.dylib+0xd28e4] R_execMethod+0x2a4 -C [methods.so+0x3db0] R_dispatchGeneric+0x9b0 -C [libR.dylib+0x11fdb8] do_standardGeneric+0x1b8 -C [libR.dylib+0xbb9ec] bcEval+0x6eec -C [libR.dylib+0xb44c8] Rf_eval+0x248 -C [libR.dylib+0xd1ad4] R_execClosure+0xc54 -C [libR.dylib+0xd030c] Rf_applyClosure+0x20c -C [libR.dylib+0xbb6b0] bcEval+0x6bb0 -C [libR.dylib+0xb44c8] Rf_eval+0x248 -C [libR.dylib+0xd1ad4] R_execClosure+0xc54 -C [libR.dylib+0xd28e4] R_execMethod+0x2a4 -C [methods.so+0x3db0] R_dispatchGeneric+0x9b0 -C [libR.dylib+0x11fdb8] do_standardGeneric+0x1b8 -C [libR.dylib+0xbb9ec] bcEval+0x6eec -C [libR.dylib+0xb44c8] Rf_eval+0x248 -C [libR.dylib+0xd1ad4] R_execClosure+0xc54 -C [libR.dylib+0xd030c] Rf_applyClosure+0x20c -C [libR.dylib+0xb479c] Rf_eval+0x51c -C [libR.dylib+0xd4264] do_begin+0x1a4 -C [libR.dylib+0xb46c8] Rf_eval+0x448 -C [libR.dylib+0xcfa24] forcePromise+0xa4 -C [libR.dylib+0xdb938] getvar+0x2b8 -C [libR.dylib+0xb8a90] bcEval+0x3f90 -C [libR.dylib+0xb44c8] Rf_eval+0x248 -C [libR.dylib+0xcfa24] forcePromise+0xa4 -C [libR.dylib+0xdb938] getvar+0x2b8 -C [libR.dylib+0xb8a90] bcEval+0x3f90 -C [libR.dylib+0xb44c8] Rf_eval+0x248 -C [libR.dylib+0xcfa24] forcePromise+0xa4 -C [libR.dylib+0xdb938] getvar+0x2b8 -C [libR.dylib+0xb8a90] bcEval+0x3f90 -C [libR.dylib+0xb44c8] Rf_eval+0x248 -C [libR.dylib+0xcfa24] forcePromise+0xa4 -C [libR.dylib+0xdb938] getvar+0x2b8 -C [libR.dylib+0xb8a90] bcEval+0x3f90 -C [libR.dylib+0xb44c8] Rf_eval+0x248 -C [libR.dylib+0xd1ad4] R_execClosure+0xc54 -C [libR.dylib+0xd030c] Rf_applyClosure+0x20c -C [libR.dylib+0xbb6b0] bcEval+0x6bb0 -C [libR.dylib+0xb44c8] Rf_eval+0x248 -C [libR.dylib+0xd1ad4] R_execClosure+0xc54 -C [libR.dylib+0xd030c] Rf_applyClosure+0x20c -C [libR.dylib+0xbb6b0] bcEval+0x6bb0 -C [libR.dylib+0xb44c8] Rf_eval+0x248 -C [libR.dylib+0xd1ad4] R_execClosure+0xc54 -C [libR.dylib+0xd030c] Rf_applyClosure+0x20c -C [libR.dylib+0xbb6b0] bcEval+0x6bb0 -C [libR.dylib+0xb44c8] Rf_eval+0x248 -C [libR.dylib+0xd1ad4] R_execClosure+0xc54 -C [libR.dylib+0xd030c] Rf_applyClosure+0x20c -C [libR.dylib+0xb479c] Rf_eval+0x51c -C [libR.dylib+0xd4264] do_begin+0x1a4 -C [libR.dylib+0xb46c8] Rf_eval+0x448 -C [libR.dylib+0xd1ad4] R_execClosure+0xc54 -C [libR.dylib+0xd030c] Rf_applyClosure+0x20c -C [libR.dylib+0xbb6b0] bcEval+0x6bb0 -C [libR.dylib+0xb44c8] Rf_eval+0x248 -C [libR.dylib+0xd1ad4] R_execClosure+0xc54 -C [libR.dylib+0xd030c] Rf_applyClosure+0x20c -C [libR.dylib+0xb479c] Rf_eval+0x51c -C [libR.dylib+0xd4264] do_begin+0x1a4 -C [libR.dylib+0xb46c8] Rf_eval+0x448 -C [libR.dylib+0xd36d0] do_for+0xa50 -C [libR.dylib+0xb46c8] Rf_eval+0x448 -C [libR.dylib+0xd4264] do_begin+0x1a4 -C [libR.dylib+0xb46c8] Rf_eval+0x448 -C [libR.dylib+0xd1ad4] R_execClosure+0xc54 -C [libR.dylib+0xd030c] Rf_applyClosure+0x20c -C [libR.dylib+0xbb6b0] bcEval+0x6bb0 -C [libR.dylib+0xb44c8] Rf_eval+0x248 -C [libR.dylib+0xd1ad4] R_execClosure+0xc54 -C [libR.dylib+0xd28e4] R_execMethod+0x2a4 -C [methods.so+0x3db0] R_dispatchGeneric+0x9b0 -C [libR.dylib+0x11fdb8] do_standardGeneric+0x1b8 -...... - - -siginfo: si_signo: 11 (SIGSEGV), si_code: 2 (SEGV_ACCERR), si_addr: 0x0000000000000000 - -Register to memory mapping: - - x0=0x0 is NULL - x1=0x000000011c7d4198 points into unknown readable memory: 0x0000000000000000 | 00 00 00 00 00 00 00 00 - x2=0x000000010d4ca8b4: jni_GetObjectClass+0 in /Library/Java/JavaVirtualMachines/amazon-corretto-17.jdk/Contents/Home/lib/server/libjvm.dylib at 0x000000010d000000 - x3=0x000000016bc7a9e0 is pointing into the stack for thread: 0x000000011e307600 - x4=0x000000016bc7aa08 is pointing into the stack for thread: 0x000000011e307600 - x5=0x0 is NULL - x6=0x000000010b0b2cf8 points into unknown readable memory: 0x0000000611000006 | 06 00 00 11 06 00 00 00 - x7=0x000000017af81398 points into unknown readable memory: 0x0000000400100004 | 04 00 10 00 04 00 00 00 - x8=0x0000000000000001 is an unknown value - x9=0x0000000000000006 is an unknown value -x10=0x2010002030300000 is an unknown value -x11=0x0000ffff11000000 is an unknown value -x12=0xffff0000eeffffff is an unknown value -x13=0x000000000000ffff is an unknown value -x14=0x000000011e03d840 points into unknown readable memory: 0x0000000211000008 | 08 00 00 11 02 00 00 00 -x15=0xffff0000eeffffff is an unknown value -x16=0x000000018cd9bd7c: pthread_jit_write_protect_np+0 in /usr/lib/system/libsystem_pthread.dylib at 0x000000018cd94000 -x17=0x000000011d9f76e0 points into unknown readable memory: 0xfffffffffffffffe | fe ff ff ff ff ff ff ff -x18=0x0 is NULL -x19=0x0000000000000001 is an unknown value -x20=0x000000011e307600 is a thread -x21=0x000000011e307600 is a thread -x22=0x000000011c7d4198 points into unknown readable memory: 0x0000000000000000 | 00 00 00 00 00 00 00 00 -x23=0x000000010dc15000: _dyld_private+0 in /Library/Java/JavaVirtualMachines/amazon-corretto-17.jdk/Contents/Home/lib/server/libjvm.dylib at 0x000000010d000000 -x24=0x0 is NULL -x25=0x000000011e285800 points into unknown readable memory: 0x00000001f1000013 | 13 00 00 f1 01 00 00 00 -x26=0x0000000105ccdd50: R_NilValue+0 in /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/lib/libR.dylib at 0x0000000105890000 -x27=0x0000000105ccdd50: R_NilValue+0 in /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/lib/libR.dylib at 0x0000000105890000 -x28=0x0000000105ccdb58: R_BCNodeStackTop+0 in /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/lib/libR.dylib at 0x0000000105890000 - - -Registers: - x0=0x0000000000000000 x1=0x000000011c7d4198 x2=0x000000010d4ca8b4 x3=0x000000016bc7a9e0 - x4=0x000000016bc7aa08 x5=0x0000000000000000 x6=0x000000010b0b2cf8 x7=0x000000017af81398 - x8=0x0000000000000001 x9=0x0000000000000006 x10=0x2010002030300000 x11=0x0000ffff11000000 -x12=0xffff0000eeffffff x13=0x000000000000ffff x14=0x000000011e03d840 x15=0xffff0000eeffffff -x16=0x000000018cd9bd7c x17=0x000000011d9f76e0 x18=0x0000000000000000 x19=0x0000000000000001 -x20=0x000000011e307600 x21=0x000000011e307600 x22=0x000000011c7d4198 x23=0x000000010dc15000 -x24=0x0000000000000000 x25=0x000000011e285800 x26=0x0000000105ccdd50 x27=0x0000000105ccdd50 -x28=0x0000000105ccdb58 fp=0x000000016bc7a610 lr=0x000000010d4ca9c8 sp=0x000000016bc7a5c0 -pc=0x000000010d4ca9d8 cpsr=0x0000000040001000 -Top of Stack: (sp=0x000000016bc7a5c0) -0x000000016bc7a5c0: 000000011e307600 0000000000000000 -0x000000016bc7a5d0: 000000016bc7a610 000000010520d230 -0x000000016bc7a5e0: 0000000105ccdd50 000000017a753600 -0x000000016bc7a5f0: 000000017a753670 000000011c7d4198 -0x000000016bc7a600: 0000000000000000 000000011e3078a8 -0x000000016bc7a610: 000000016bc7a9b0 00000001052060fc -0x000000016bc7a620: 0000000163d2af48 00000001787e85d8 -0x000000016bc7a630: 000000016bc7b348 000000010b0b03c8 -0x000000016bc7a640: 0000000000000000 000000011e0207c8 -0x000000016bc7a650: 00000001200d9e10 00000001635143d8 -0x000000016bc7a660: 0000000163a1a580 0000000163a1a510 -0x000000016bc7a670: 0000000163a1a468 a9885dc159fb0020 -0x000000016bc7a680: 000000016bc7a6e0 0000000105961fac -0x000000016bc7a690: 0000000105ccdd50 0000000105ccdce8 -0x000000016bc7a6a0: 000000011e0208e0 0000000105ccdd68 -0x000000016bc7a6b0: 0000000000000000 000000011e0511c8 -0x000000016bc7a6c0: 0000000163a1dd90 0000000163a1a468 -0x000000016bc7a6d0: 000000011e084408 000000011e0d2198 -0x000000016bc7a6e0: 000000016bc7a750 000000010596031c -0x000000016bc7a6f0: 0000000105ccd570 000000011e020758 -0x000000016bc7a700: 0000000105ccdb58 0000000163a1dd90 -0x000000016bc7a710: 000000016bc7a750 0000000105960410 -0x000000016bc7a720: 000000010b35a0e0 000000011e084408 -0x000000016bc7a730: 0000000000000000 000000011e012c48 -0x000000016bc7a740: 0000000000000000 0000000105ccdd50 -0x000000016bc7a750: 000000011e01fdf0 000000011e609be0 -0x000000016bc7a760: 0000000178bb8e78 0000000178bb8dd0 -0x000000016bc7a770: 000000016bc7a7b0 00000001058c396c -0x000000016bc7a780: 0000000000000000 000000010b0b2c50 -0x000000016bc7a790: 0000000105bc4000 0000000105ccdd50 -0x000000016bc7a7a0: 00000001200d9e28 0000000105ccdfd0 -0x000000016bc7a7b0: 0000000105ccdd00 000000017a753670 - -Instructions: (pc=0x000000010d4ca9d8) -0x000000010d4ca8d8: 9102e008 b8bfc108 129bd549 0b090108 -0x000000010d4ca8e8: 7100091f 540000a3 aa1503e0 941361b9 -0x000000010d4ca8f8: d2800015 1400000a b4000135 b9427ab3 -0x000000010d4ca908: 34000093 b9027abf 52800000 940be1db -0x000000010d4ca918: 52800018 aa1503f4 14000004 d2800014 -0x000000010d4ca928: 52800013 52800038 910ce288 528000a9 -0x000000010d4ca938: 889ffd09 d5033bbf 910d0288 f8bfc108 -0x000000010d4ca948: 36000088 aa1403e0 52800021 940e0293 -0x000000010d4ca958: b9432e88 35000088 b9432a88 721e051f -0x000000010d4ca968: 54000080 aa1403e0 52800001 941367d1 -0x000000010d4ca978: 910ce288 528000c9 889ffd09 a9007ff4 -0x000000010d4ca988: f9400688 b4000068 910003e0 940cdcca -0x000000010d4ca998: aa1703e0 aa1603e1 d503201f f0003a57 -0x000000010d4ca9a8: 37000096 f94046e8 aa1603e0 14000004 -0x000000010d4ca9b8: d10006c0 f0003a68 f9471108 d63f0100 -0x000000010d4ca9c8: d0003c68 91168508 39400108 340001c8 -0x000000010d4ca9d8: b9400808 90003a89 911e0129 f940012a -0x000000010d4ca9e8: b9400929 9ac92108 8b0a0108 f9403900 -0x000000010d4ca9f8: b4000100 f94046e8 d63f0100 aa0003e1 -0x000000010d4caa08: 14000005 f9400408 f9403900 b5ffff40 -0x000000010d4caa18: d2800001 aa1503e0 52800002 9400fc69 -0x000000010d4caa28: aa0003f5 d503201f f94007e8 b4000068 -0x000000010d4caa38: 910003e0 940cdcca f9407696 f9400ac8 -0x000000010d4caa48: f9400109 b4000089 aa1603e0 97fd1692 -0x000000010d4caa58: f9400ac8 f94006c9 f9000928 f9400ec8 -0x000000010d4caa68: f94006c9 f9000d28 f94012c8 f94006c9 -0x000000010d4caa78: f9001128 910a2280 97fa5350 d5033bbf -0x000000010d4caa88: 910ce288 52800089 889ffd09 370000f8 -0x000000010d4caa98: b9427a88 6b13011f 54000080 b9027a93 -0x000000010d4caaa8: aa1303e0 940be175 aa1503e0 a9457bfd -0x000000010d4caab8: a9444ff4 a94357f6 a9425ff8 910183ff -0x000000010d4caac8: d65f03c0 a9bc5ff8 a90157f6 a9024ff4 - - -Stack slot to memory mapping: -stack at sp + 0 slots: 0x000000011e307600 is a thread -stack at sp + 1 slots: 0x0 is NULL -stack at sp + 2 slots: 0x000000016bc7a610 is pointing into the stack for thread: 0x000000011e307600 -stack at sp + 3 slots: 0x000000010520d230: getJNIEnv+0x70 in /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/rJava/libs/rJava.so at 0x0000000105200000 -stack at sp + 4 slots: 0x0000000105ccdd50: R_NilValue+0 in /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/lib/libR.dylib at 0x0000000105890000 -stack at sp + 5 slots: 0x000000017a753600 points into unknown readable memory: 0x0000000000000002 | 02 00 00 00 00 00 00 00 -stack at sp + 6 slots: 0x000000017a753670 points into unknown readable memory: 0x0000000100000002 | 02 00 00 00 01 00 00 00 -stack at sp + 7 slots: 0x000000011c7d4198 points into unknown readable memory: 0x0000000000000000 | 00 00 00 00 00 00 00 00 - - ---------------- P R O C E S S --------------- - -Threads class SMR info: -_java_thread_list=0x000000010c704350, length=11, elements={ -0x000000011e307600, 0x000000010c88d400, 0x000000010c8c7400, 0x000000011e7fa800, -0x000000011e2bd600, 0x000000011e32f600, 0x000000010cac2200, 0x000000011cc09200, -0x000000011f155600, 0x000000011ce61800, 0x000000011e71fe00 -} - -Java Threads: ( => current thread ) -=>0x000000011e307600 JavaThread "main" [_thread_in_vm, id=259, stack(0x000000016b494000,0x000000016bc90000)] - 0x000000010c88d400 JavaThread "Reference Handler" daemon [_thread_blocked, id=18179, stack(0x000000016ccb0000,0x000000016ceb3000)] - 0x000000010c8c7400 JavaThread "Finalizer" daemon [_thread_blocked, id=19971, stack(0x000000016cebc000,0x000000016d0bf000)] - 0x000000011e7fa800 JavaThread "Attach Listener" daemon [_thread_blocked, id=31491, stack(0x000000016d1e0000,0x000000016d3e3000)] - 0x000000011e2bd600 JavaThread "Service Thread" daemon [_thread_blocked, id=31235, stack(0x000000016d3ec000,0x000000016d5ef000)] - 0x000000011e32f600 JavaThread "Monitor Deflation Thread" daemon [_thread_blocked, id=30979, stack(0x000000016d5f8000,0x000000016d7fb000)] - 0x000000010cac2200 JavaThread "C2 CompilerThread0" daemon [_thread_blocked, id=23043, stack(0x000000016d804000,0x000000016da07000)] - 0x000000011cc09200 JavaThread "C1 CompilerThread0" daemon [_thread_blocked, id=23299, stack(0x000000016da10000,0x000000016dc13000)] - 0x000000011f155600 JavaThread "Sweeper thread" daemon [_thread_blocked, id=23555, stack(0x000000016dc1c000,0x000000016de1f000)] - 0x000000011ce61800 JavaThread "Notification Thread" daemon [_thread_blocked, id=23811, stack(0x000000016de28000,0x000000016e02b000)] - 0x000000011e71fe00 JavaThread "Common-Cleaner" daemon [_thread_blocked, id=29187, stack(0x000000016e240000,0x000000016e443000)] - -Other Threads: - 0x000000011d9c8140 VMThread "VM Thread" [stack: 0x000000016caa4000,0x000000016cca7000] [id=17411] - 0x000000011c7dcb70 WatcherThread [stack: 0x000000016e034000,0x000000016e237000] [id=29443] - 0x0000000105723230 GCTaskThread "GC Thread#0" [stack: 0x000000016c068000,0x000000016c26b000] [id=12035] - 0x000000010e199ff0 GCTaskThread "GC Thread#1" [stack: 0x000000016e7fc000,0x000000016e9ff000] [id=43015] - 0x000000010e196760 GCTaskThread "GC Thread#2" [stack: 0x000000016ea08000,0x000000016ec0b000] [id=33795] - 0x00000001057bab20 GCTaskThread "GC Thread#3" [stack: 0x000000016ec14000,0x000000016ee17000] [id=34051] - 0x00000001057bb320 GCTaskThread "GC Thread#4" [stack: 0x000000016ee20000,0x000000016f023000] [id=34307] - 0x000000010e195130 GCTaskThread "GC Thread#5" [stack: 0x000000016f02c000,0x000000016f22f000] [id=41987] - 0x000000011dae5a70 ConcurrentGCThread "G1 Main Marker" [stack: 0x000000016c274000,0x000000016c477000] [id=14595] - 0x000000011d9e4db0 ConcurrentGCThread "G1 Conc#0" [stack: 0x000000016c480000,0x000000016c683000] [id=12803] - 0x000000011dcc0640 ConcurrentGCThread "G1 Conc#1" [stack: 0x000000016e5f0000,0x000000016e7f3000] [id=43283] - 0x000000011c7212a0 ConcurrentGCThread "G1 Refine#0" [stack: 0x000000016c68c000,0x000000016c88f000] [id=13315] - 0x000000011c710c20 ConcurrentGCThread "G1 Service" [stack: 0x000000016c898000,0x000000016ca9b000] [id=13827] - -Threads with active compile tasks: - -VM state: not at safepoint (normal execution) - -VM Mutex/Monitor currently owned by a thread: None - -Heap address: 0x00000007e0000000, size: 512 MB, Compressed Oops mode: Zero based, Oop shift amount: 3 - -CDS archive(s) mapped at: [0x0000000800000000-0x0000000800bd8000-0x0000000800bd8000), size 12419072, SharedBaseAddress: 0x0000000800000000, ArchiveRelocationMode: 0. -Compressed class space mapped at: 0x0000000800c00000-0x0000000840c00000, reserved size: 1073741824 -Narrow klass base: 0x0000000800000000, Narrow klass shift: 0, Narrow klass range: 0x100000000 - -GC Precious Log: - CPUs: 8 total, 8 available - Memory: 16384M - Large Page Support: Disabled - NUMA Support: Disabled - Compressed Oops: Enabled (Zero based) - Heap Region Size: 1M - Heap Min Capacity: 8M - Heap Initial Capacity: 256M - Heap Max Capacity: 512M - Pre-touch: Disabled - Parallel Workers: 8 - Concurrent Workers: 2 - Concurrent Refinement Workers: 8 - Periodic GC: Disabled - -Heap: - garbage-first heap total 24576K, used 10704K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 3 young (3072K), 1 survivors (1024K) - Metaspace used 9354K, committed 9472K, reserved 1064960K - class space used 1004K, committed 1088K, reserved 1048576K - -Heap Regions: E=young(eden), S=young(survivor), O=old, HS=humongous(starts), HC=humongous(continues), CS=collection set, F=free, OA=open archive, CA=closed archive, TAMS=top-at-mark-start (previous, next) -| 0|0x00000007e0000000, 0x00000007e00b3090, 0x00000007e0100000| 69%| O| |TAMS 0x00000007e00b3090, 0x00000007e0000000| Untracked -| 1|0x00000007e0100000, 0x00000007e01ffff0, 0x00000007e0200000| 99%| O| |TAMS 0x00000007e01ffff0, 0x00000007e0100000| Untracked -| 2|0x00000007e0200000, 0x00000007e0203e20, 0x00000007e0300000| 1%| O| |TAMS 0x00000007e0203e20, 0x00000007e0200000| Complete -| 3|0x00000007e0300000, 0x00000007e0400000, 0x00000007e0400000|100%|HS| |TAMS 0x00000007e0400000, 0x00000007e0300000| Complete -| 4|0x00000007e0400000, 0x00000007e0500000, 0x00000007e0500000|100%|HS| |TAMS 0x00000007e0500000, 0x00000007e0400000| Complete -| 5|0x00000007e0500000, 0x00000007e0600000, 0x00000007e0600000|100%|HS| |TAMS 0x00000007e0600000, 0x00000007e0500000| Complete -| 6|0x00000007e0600000, 0x00000007e06c4200, 0x00000007e0700000| 76%| O| |TAMS 0x00000007e0600000, 0x00000007e0600000| Untracked -| 7|0x00000007e0700000, 0x00000007e0800000, 0x00000007e0800000|100%|HS| |TAMS 0x00000007e0700000, 0x00000007e0700000| Complete -| 8|0x00000007e0800000, 0x00000007e0800000, 0x00000007e0900000| 0%| F| |TAMS 0x00000007e0800000, 0x00000007e0800000| Untracked -| 9|0x00000007e0900000, 0x00000007e0900000, 0x00000007e0a00000| 0%| F| |TAMS 0x00000007e0900000, 0x00000007e0900000| Untracked -| 10|0x00000007e0a00000, 0x00000007e0a00000, 0x00000007e0b00000| 0%| F| |TAMS 0x00000007e0a00000, 0x00000007e0a00000| Untracked -| 11|0x00000007e0b00000, 0x00000007e0b00000, 0x00000007e0c00000| 0%| F| |TAMS 0x00000007e0b00000, 0x00000007e0b00000| Untracked -| 12|0x00000007e0c00000, 0x00000007e0c00000, 0x00000007e0d00000| 0%| F| |TAMS 0x00000007e0c00000, 0x00000007e0c00000| Untracked -| 13|0x00000007e0d00000, 0x00000007e0d00f70, 0x00000007e0e00000| 0%| S|CS|TAMS 0x00000007e0d00000, 0x00000007e0d00000| Complete -| 14|0x00000007e0e00000, 0x00000007e0e00000, 0x00000007e0f00000| 0%| F| |TAMS 0x00000007e0e00000, 0x00000007e0e00000| Untracked -| 15|0x00000007e0f00000, 0x00000007e1000000, 0x00000007e1000000|100%| E|CS|TAMS 0x00000007e0f00000, 0x00000007e0f00000| Complete -| 16|0x00000007e1000000, 0x00000007e1000000, 0x00000007e1100000| 0%| F| |TAMS 0x00000007e1000000, 0x00000007e1000000| Untracked -| 17|0x00000007e1100000, 0x00000007e1100000, 0x00000007e1200000| 0%| F| |TAMS 0x00000007e1100000, 0x00000007e1100000| Untracked -| 18|0x00000007e1200000, 0x00000007e1200000, 0x00000007e1300000| 0%| F| |TAMS 0x00000007e1200000, 0x00000007e1200000| Untracked -| 19|0x00000007e1300000, 0x00000007e136e288, 0x00000007e1400000| 43%| E| |TAMS 0x00000007e1300000, 0x00000007e1300000| Complete -| 231|0x00000007ee700000, 0x00000007ee800000, 0x00000007ee800000|100%| O| |TAMS 0x00000007ee800000, 0x00000007ee700000| Untracked -| 232|0x00000007ee800000, 0x00000007ee900000, 0x00000007ee900000|100%| O| |TAMS 0x00000007ee900000, 0x00000007ee800000| Untracked -| 510|0x00000007ffe00000, 0x00000007ffe78000, 0x00000007fff00000| 46%|OA| |TAMS 0x00000007ffe78000, 0x00000007ffe00000| Untracked -| 511|0x00000007fff00000, 0x00000007fff80000, 0x0000000800000000| 50%|CA| |TAMS 0x00000007fff80000, 0x00000007fff00000| Untracked - -Card table byte_map: [0x000000010c100000,0x000000010c200000] _byte_map_base: 0x0000000108200000 - -Marking Bits (Prev, Next): (CMBitMap*) 0x000000011f7a4410, (CMBitMap*) 0x000000011f7a4450 - Prev Bits: [0x000000010f800000, 0x0000000110000000) - Next Bits: [0x0000000118000000, 0x0000000118800000) - -Polling page: 0x000000010507c000 - -Metaspace: - -Usage: - Non-class: 8.15 MB used. - Class: 1004.40 KB used. - Both: 9.14 MB used. - -Virtual space: - Non-class space: 16.00 MB reserved, 8.19 MB ( 51%) committed, 2 nodes. - Class space: 1.00 GB reserved, 1.06 MB ( <1%) committed, 1 nodes. - Both: 1.02 GB reserved, 9.25 MB ( <1%) committed. - -Chunk freelists: - Non-Class: 3.81 MB - Class: 2.95 MB - Both: 6.77 MB - -MaxMetaspaceSize: unlimited -CompressedClassSpaceSize: 1.00 GB -Initial GC threshold: 21.00 MB -Current GC threshold: 21.00 MB -CDS: on -MetaspaceReclaimPolicy: balanced - - commit_granule_bytes: 65536. - - commit_granule_words: 8192. - - virtual_space_node_default_size: 1048576. - - enlarge_chunks_in_place: 1. - - new_chunks_are_fully_committed: 0. - - uncommit_free_chunks: 1. - - use_allocation_guard: 0. - - handle_deallocations: 1. - - -Internal statistics: - -num_allocs_failed_limit: 0. -num_arena_births: 38. -num_arena_deaths: 0. -num_vsnodes_births: 3. -num_vsnodes_deaths: 0. -num_space_committed: 148. -num_space_uncommitted: 0. -num_chunks_returned_to_freelist: 0. -num_chunks_taken_from_freelist: 163. -num_chunk_merges: 0. -num_chunk_splits: 97. -num_chunks_enlarged: 61. -num_purges: 0. -num_inconsistent_stats: 0. - -CodeHeap 'non-profiled nmethods': size=120032Kb used=697Kb max_used=697Kb free=119334Kb - bounds [0x000000014f4dc000, 0x000000014f74c000, 0x0000000156a14000] -CodeHeap 'profiled nmethods': size=120016Kb used=3427Kb max_used=3427Kb free=116588Kb - bounds [0x0000000147fa8000, 0x0000000148308000, 0x000000014f4dc000] -CodeHeap 'non-nmethods': size=5712Kb used=1180Kb max_used=1235Kb free=4531Kb - bounds [0x0000000147a14000, 0x0000000147c84000, 0x0000000147fa8000] - total_blobs=2051 nmethods=1560 adapters=408 - compilation: enabled - stopped_count=0, restarted_count=0 - full_count=0 - -Compilation events (20 events): -Event: 23.905 Thread 0x000000011b6e6a00 1552 4 java.util.concurrent.locks.AbstractQueuedSynchronizer::signalNext (34 bytes) -Event: 23.905 Thread 0x000000011b6e6a00 nmethod 1552 0x000000014f586490 code [0x000000014f586600, 0x000000014f5866b0] -Event: 23.907 Thread 0x000000011cc09200 1553 3 org.postgresql.jdbc.PgResultSet::next (259 bytes) -Event: 23.907 Thread 0x000000011b6e6a00 1554 4 org.postgresql.jdbc.PgResultSet::checkClosed (29 bytes) -Event: 23.907 Thread 0x000000010cac2200 1555 4 org.postgresql.util.internal.Nullness::castNonNull (39 bytes) -Event: 23.907 Thread 0x000000011b6e6a00 nmethod 1554 0x000000014f586790 code [0x000000014f586900, 0x000000014f5869b0] -Event: 23.907 Thread 0x000000010cac2200 nmethod 1555 0x000000014f586a90 code [0x000000014f586c00, 0x000000014f586c60] -Event: 23.907 Thread 0x000000011b6e6a00 1556 ! 4 jdk.internal.math.FloatingDecimal::readJavaFormatString (826 bytes) -Event: 23.907 Thread 0x000000010cac2200 1557 ! 4 org.postgresql.jdbc.PgResultSet::getLong (121 bytes) -Event: 23.907 Thread 0x000000011cc09200 nmethod 1553 0x00000001482ff110 code [0x00000001482ff480, 0x00000001483006a8] -Event: 23.912 Thread 0x000000010cac2200 nmethod 1557 0x000000014f586d90 code [0x000000014f587000, 0x000000014f587770] -Event: 23.912 Thread 0x000000010cac2200 1558 4 java.lang.StringLatin1::trim (76 bytes) -Event: 23.912 Thread 0x000000010cac2200 nmethod 1558 0x000000014f587d90 code [0x000000014f587f40, 0x000000014f588070] -Event: 23.916 Thread 0x000000011b6e6a00 nmethod 1556 0x000000014f588190 code [0x000000014f588440, 0x000000014f589080] -Event: 23.937 Thread 0x000000010cac2200 1559 4 java.nio.HeapByteBuffer::putLong (32 bytes) -Event: 23.937 Thread 0x000000011b6e6a00 1560 4 java.nio.HeapByteBuffer::getDouble (35 bytes) -Event: 23.937 Thread 0x000000010cac2200 nmethod 1559 0x000000014f589990 code [0x000000014f589b40, 0x000000014f589ce0] -Event: 23.937 Thread 0x000000011b6e6a00 nmethod 1560 0x000000014f589e90 code [0x000000014f58a040, 0x000000014f58a1a0] -Event: 45.448 Thread 0x000000011cc09200 1561 1 org.postgresql.core.QueryExecutorBase::isClosed (5 bytes) -Event: 45.448 Thread 0x000000011cc09200 nmethod 1561 0x000000014f58a390 code [0x000000014f58a500, 0x000000014f58a5e8] - -GC Heap History (20 events): -Event: 9.766 GC heap before -{Heap before GC invocations=8 (full 2): - garbage-first heap total 35840K, used 20680K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 9 young (9216K), 0 survivors (0K) - Metaspace used 9266K, committed 9472K, reserved 1064960K - class space used 1002K, committed 1088K, reserved 1048576K -} -Event: 9.767 GC heap after -{Heap after GC invocations=9 (full 2): - garbage-first heap total 35840K, used 21683K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 2 young (2048K), 2 survivors (2048K) - Metaspace used 9266K, committed 9472K, reserved 1064960K - class space used 1002K, committed 1088K, reserved 1048576K -} -Event: 9.861 GC heap before -{Heap before GC invocations=9 (full 2): - garbage-first heap total 35840K, used 23731K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 4 young (4096K), 2 survivors (2048K) - Metaspace used 9293K, committed 9472K, reserved 1064960K - class space used 1002K, committed 1088K, reserved 1048576K -} -Event: 9.862 GC heap after -{Heap after GC invocations=10 (full 2): - garbage-first heap total 149504K, used 21468K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 1 young (1024K), 1 survivors (1024K) - Metaspace used 9293K, committed 9472K, reserved 1064960K - class space used 1002K, committed 1088K, reserved 1048576K -} -Event: 9.862 GC heap before -{Heap before GC invocations=10 (full 2): - garbage-first heap total 149504K, used 21468K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 2 young (2048K), 1 survivors (1024K) - Metaspace used 9293K, committed 9472K, reserved 1064960K - class space used 1002K, committed 1088K, reserved 1048576K -} -Event: 9.866 GC heap after -{Heap after GC invocations=11 (full 3): - garbage-first heap total 48128K, used 12544K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 0 young (0K), 0 survivors (0K) - Metaspace used 9293K, committed 9472K, reserved 1064960K - class space used 1002K, committed 1088K, reserved 1048576K -} -Event: 9.945 GC heap before -{Heap before GC invocations=11 (full 3): - garbage-first heap total 48128K, used 13568K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 3 young (3072K), 0 survivors (0K) - Metaspace used 9305K, committed 9472K, reserved 1064960K - class space used 1002K, committed 1088K, reserved 1048576K -} -Event: 9.949 GC heap after -{Heap after GC invocations=12 (full 4): - garbage-first heap total 48128K, used 12554K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 0 young (0K), 0 survivors (0K) - Metaspace used 9305K, committed 9472K, reserved 1064960K - class space used 1002K, committed 1088K, reserved 1048576K -} -Event: 10.626 GC heap before -{Heap before GC invocations=12 (full 4): - garbage-first heap total 48128K, used 14602K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 3 young (3072K), 0 survivors (0K) - Metaspace used 9327K, committed 9472K, reserved 1064960K - class space used 1003K, committed 1088K, reserved 1048576K -} -Event: 10.630 GC heap after -{Heap after GC invocations=13 (full 5): - garbage-first heap total 20480K, used 4212K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 0 young (0K), 0 survivors (0K) - Metaspace used 9327K, committed 9472K, reserved 1064960K - class space used 1003K, committed 1088K, reserved 1048576K -} -Event: 19.612 GC heap before -{Heap before GC invocations=13 (full 5): - garbage-first heap total 20480K, used 6260K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 3 young (3072K), 0 survivors (0K) - Metaspace used 9329K, committed 9472K, reserved 1064960K - class space used 1003K, committed 1088K, reserved 1048576K -} -Event: 19.618 GC heap after -{Heap after GC invocations=14 (full 6): - garbage-first heap total 20480K, used 4145K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 0 young (0K), 0 survivors (0K) - Metaspace used 9329K, committed 9472K, reserved 1064960K - class space used 1003K, committed 1088K, reserved 1048576K -} -Event: 23.636 GC heap before -{Heap before GC invocations=14 (full 6): - garbage-first heap total 20480K, used 6193K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 3 young (3072K), 0 survivors (0K) - Metaspace used 9330K, committed 9472K, reserved 1064960K - class space used 1003K, committed 1088K, reserved 1048576K -} -Event: 23.639 GC heap after -{Heap after GC invocations=15 (full 7): - garbage-first heap total 20480K, used 4155K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 0 young (0K), 0 survivors (0K) - Metaspace used 9330K, committed 9472K, reserved 1064960K - class space used 1003K, committed 1088K, reserved 1048576K -} -Event: 23.871 GC heap before -{Heap before GC invocations=15 (full 7): - garbage-first heap total 20480K, used 8251K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 3 young (3072K), 0 survivors (0K) - Metaspace used 9330K, committed 9472K, reserved 1064960K - class space used 1003K, committed 1088K, reserved 1048576K -} -Event: 23.876 GC heap after -{Heap after GC invocations=16 (full 8): - garbage-first heap total 20480K, used 4795K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 0 young (0K), 0 survivors (0K) - Metaspace used 9330K, committed 9472K, reserved 1064960K - class space used 1003K, committed 1088K, reserved 1048576K -} -Event: 23.876 GC heap before -{Heap before GC invocations=16 (full 8): - garbage-first heap total 20480K, used 6843K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 1 young (1024K), 0 survivors (0K) - Metaspace used 9330K, committed 9472K, reserved 1064960K - class space used 1003K, committed 1088K, reserved 1048576K -} -Event: 23.876 GC heap after -{Heap after GC invocations=17 (full 8): - garbage-first heap total 20480K, used 7617K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 1 young (1024K), 1 survivors (1024K) - Metaspace used 9330K, committed 9472K, reserved 1064960K - class space used 1003K, committed 1088K, reserved 1048576K -} -Event: 23.876 GC heap before -{Heap before GC invocations=17 (full 8): - garbage-first heap total 20480K, used 8641K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 2 young (2048K), 1 survivors (1024K) - Metaspace used 9330K, committed 9472K, reserved 1064960K - class space used 1003K, committed 1088K, reserved 1048576K -} -Event: 23.877 GC heap after -{Heap after GC invocations=18 (full 8): - garbage-first heap total 20480K, used 8656K [0x00000007e0000000, 0x0000000800000000) - region size 1024K, 1 young (1024K), 1 survivors (1024K) - Metaspace used 9330K, committed 9472K, reserved 1064960K - class space used 1003K, committed 1088K, reserved 1048576K -} - -Dll operation events (8 events): -Event: 0.004 Loaded shared library /Library/Java/JavaVirtualMachines/amazon-corretto-17.jdk/Contents/Home/lib/libjava.dylib -Event: 0.025 Loaded shared library /Library/Java/JavaVirtualMachines/amazon-corretto-17.jdk/Contents/Home/lib/libnio.dylib -Event: 0.026 Loaded shared library /Library/Java/JavaVirtualMachines/amazon-corretto-17.jdk/Contents/Home/lib/libzip.dylib -Event: 3.973 Loaded shared library /Library/Java/JavaVirtualMachines/amazon-corretto-17.jdk/Contents/Home/lib/libjimage.dylib -Event: 4.013 Loaded shared library /Library/Java/JavaVirtualMachines/amazon-corretto-17.jdk/Contents/Home/lib/libnet.dylib -Event: 4.076 Loaded shared library /Library/Java/JavaVirtualMachines/amazon-corretto-17.jdk/Contents/Home/lib/libextnet.dylib -Event: 4.083 Loaded shared library /Library/Java/JavaVirtualMachines/amazon-corretto-17.jdk/Contents/Home/lib/libmanagement.dylib -Event: 4.084 Loaded shared library /Library/Java/JavaVirtualMachines/amazon-corretto-17.jdk/Contents/Home/lib/libmanagement_ext.dylib - -Deoptimization events (20 events): -Event: 9.898 Thread 0x000000011e307600 DEOPT PACKING pc=0x00000001481e45fc sp=0x000000016bc2a950 -Event: 9.898 Thread 0x000000011e307600 DEOPT UNPACKING pc=0x0000000147a52b7c sp=0x000000016bc2a6c0 mode 0 -Event: 9.949 Thread 0x000000011e307600 DEOPT PACKING pc=0x0000000148287a14 sp=0x000000016bc1e4c0 -Event: 9.949 Thread 0x000000011e307600 DEOPT UNPACKING pc=0x0000000147a52b7c sp=0x000000016bc1e160 mode 0 -Event: 10.061 Thread 0x000000011e307600 Uncommon trap: trap_request=0xffffff45 fr.pc=0x000000014f556890 relative=0x0000000000000390 -Event: 10.061 Thread 0x000000011e307600 Uncommon trap: reason=unstable_if action=reinterpret pc=0x000000014f556890 method=java.nio.Buffer.(IIIILjdk/internal/access/foreign/MemorySegmentProxy;)V @ 50 c2 -Event: 10.061 Thread 0x000000011e307600 DEOPT PACKING pc=0x000000014f556890 sp=0x000000016bc2bc10 -Event: 10.061 Thread 0x000000011e307600 DEOPT UNPACKING pc=0x0000000147a52d1c sp=0x000000016bc2baf0 mode 2 -Event: 10.162 Thread 0x000000011e307600 DEOPT PACKING pc=0x00000001481a215c sp=0x000000016bc2c0c0 -Event: 10.162 Thread 0x000000011e307600 DEOPT UNPACKING pc=0x0000000147a52b7c sp=0x000000016bc2bd60 mode 0 -Event: 10.281 Thread 0x000000011e307600 Uncommon trap: trap_request=0xffffffde fr.pc=0x000000014f540b04 relative=0x0000000000000184 -Event: 10.281 Thread 0x000000011e307600 Uncommon trap: reason=class_check action=maybe_recompile pc=0x000000014f540b04 method=java.util.regex.Pattern$BmpCharProperty.match(Ljava/util/regex/Matcher;ILjava/lang/CharSequence;)Z @ 19 c2 -Event: 10.281 Thread 0x000000011e307600 DEOPT PACKING pc=0x000000014f540b04 sp=0x000000016bc2cd00 -Event: 10.281 Thread 0x000000011e307600 DEOPT UNPACKING pc=0x0000000147a52d1c sp=0x000000016bc2cc90 mode 2 -Event: 10.281 Thread 0x000000011e307600 Uncommon trap: trap_request=0xffffffde fr.pc=0x000000014f540b04 relative=0x0000000000000184 -Event: 10.281 Thread 0x000000011e307600 Uncommon trap: reason=class_check action=maybe_recompile pc=0x000000014f540b04 method=java.util.regex.Pattern$BmpCharProperty.match(Ljava/util/regex/Matcher;ILjava/lang/CharSequence;)Z @ 19 c2 -Event: 10.281 Thread 0x000000011e307600 DEOPT PACKING pc=0x000000014f540b04 sp=0x000000016bc2cd00 -Event: 10.281 Thread 0x000000011e307600 DEOPT UNPACKING pc=0x0000000147a52d1c sp=0x000000016bc2cc90 mode 2 -Event: 23.883 Thread 0x000000011e307600 DEOPT PACKING pc=0x0000000148297d44 sp=0x000000016bc2be30 -Event: 23.883 Thread 0x000000011e307600 DEOPT UNPACKING pc=0x0000000147a52b7c sp=0x000000016bc2bb40 mode 3 - -Classes unloaded (0 events): -No events - -Classes redefined (0 events): -No events - -Internal exceptions (20 events): -Event: 8.723 Thread 0x000000011e307600 Exception (0x00000007efb25268) -thrown [src/hotspot/share/prims/jni.cpp, line 516] -Event: 8.723 Thread 0x000000011e307600 Exception (0x00000007efb258d8) -thrown [src/hotspot/share/prims/jni.cpp, line 516] -Event: 8.723 Thread 0x000000011e307600 Exception (0x00000007efb25f48) -thrown [src/hotspot/share/prims/jni.cpp, line 516] -Event: 8.723 Thread 0x000000011e307600 Exception (0x00000007efb26618) -thrown [src/hotspot/share/prims/jni.cpp, line 516] -Event: 8.723 Thread 0x000000011e307600 Exception (0x00000007efb26c88) -thrown [src/hotspot/share/prims/jni.cpp, line 516] -Event: 8.723 Thread 0x000000011e307600 Exception (0x00000007efb272f8) -thrown [src/hotspot/share/prims/jni.cpp, line 516] -Event: 8.723 Thread 0x000000011e307600 Exception (0x00000007efb279c8) -thrown [src/hotspot/share/prims/jni.cpp, line 516] -Event: 10.062 Thread 0x000000011e307600 Exception (0x00000007e2afcc10) -thrown [src/hotspot/share/prims/jni.cpp, line 516] -Event: 10.062 Thread 0x000000011e307600 Exception (0x00000007e2afd2e0) -thrown [src/hotspot/share/prims/jni.cpp, line 516] -Event: 10.062 Thread 0x000000011e307600 Exception (0x00000007e2afd950) -thrown [src/hotspot/share/prims/jni.cpp, line 516] -Event: 10.062 Thread 0x000000011e307600 Exception (0x00000007e2afe020) -thrown [src/hotspot/share/prims/jni.cpp, line 516] -Event: 10.062 Thread 0x000000011e307600 Exception (0x00000007e2afe690) -thrown [src/hotspot/share/prims/jni.cpp, line 516] -Event: 10.062 Thread 0x000000011e307600 Exception (0x00000007e2afed00) -thrown [src/hotspot/share/prims/jni.cpp, line 516] -Event: 10.063 Thread 0x000000011e307600 Exception (0x00000007e2aff3d0) -thrown [src/hotspot/share/prims/jni.cpp, line 516] -Event: 10.063 Thread 0x000000011e307600 Exception (0x00000007e2affa40) -thrown [src/hotspot/share/prims/jni.cpp, line 516] -Event: 10.063 Thread 0x000000011e307600 Exception (0x00000007e2961388) -thrown [src/hotspot/share/prims/jni.cpp, line 516] -Event: 10.063 Thread 0x000000011e307600 Exception (0x00000007e2961a58) -thrown [src/hotspot/share/prims/jni.cpp, line 516] -Event: 10.063 Thread 0x000000011e307600 Exception (0x00000007e29620c8) -thrown [src/hotspot/share/prims/jni.cpp, line 516] -Event: 10.063 Thread 0x000000011e307600 Exception (0x00000007e2962738) -thrown [src/hotspot/share/prims/jni.cpp, line 516] -Event: 10.063 Thread 0x000000011e307600 Exception (0x00000007e2962e08) -thrown [src/hotspot/share/prims/jni.cpp, line 516] - -VM Operations (20 events): -Event: 9.945 Executing VM operation: G1CollectFull -Event: 9.949 Executing VM operation: G1CollectFull done -Event: 10.626 Executing VM operation: G1CollectFull -Event: 10.630 Executing VM operation: G1CollectFull done -Event: 19.612 Executing VM operation: G1CollectFull -Event: 19.618 Executing VM operation: G1CollectFull done -Event: 23.632 Executing VM operation: Cleanup -Event: 23.632 Executing VM operation: Cleanup done -Event: 23.636 Executing VM operation: G1CollectFull -Event: 23.639 Executing VM operation: G1CollectFull done -Event: 23.871 Executing VM operation: G1CollectFull -Event: 23.876 Executing VM operation: G1CollectFull done -Event: 23.876 Executing VM operation: G1TryInitiateConcMark -Event: 23.876 Executing VM operation: G1TryInitiateConcMark done -Event: 23.876 Executing VM operation: G1TryInitiateConcMark -Event: 23.877 Executing VM operation: G1TryInitiateConcMark done -Event: 23.879 Executing VM operation: G1Concurrent -Event: 23.880 Executing VM operation: G1Concurrent done -Event: 23.881 Executing VM operation: G1Concurrent -Event: 23.881 Executing VM operation: G1Concurrent done - -Events (20 events): -Event: 8.863 loading class java/util/concurrent/atomic/AtomicReferenceFieldUpdater -Event: 8.863 loading class java/util/concurrent/atomic/AtomicReferenceFieldUpdater done -Event: 8.863 loading class java/util/concurrent/atomic/AtomicReferenceFieldUpdater$AtomicReferenceFieldUpdaterImpl -Event: 8.863 loading class java/util/concurrent/atomic/AtomicReferenceFieldUpdater$AtomicReferenceFieldUpdaterImpl done -Event: 8.863 loading class java/util/concurrent/atomic/AtomicReferenceFieldUpdater$AtomicReferenceFieldUpdaterImpl$1 -Event: 8.863 loading class java/util/concurrent/atomic/AtomicReferenceFieldUpdater$AtomicReferenceFieldUpdaterImpl$1 done -Event: 8.863 loading class sun/reflect/misc/ReflectUtil -Event: 8.863 loading class sun/reflect/misc/ReflectUtil done -Event: 8.882 loading class java/io/CharArrayReader -Event: 8.882 loading class java/io/CharArrayReader done -Event: 8.882 loading class java/net/UnknownHostException -Event: 8.882 loading class java/net/UnknownHostException done -Event: 9.638 loading class jdk/internal/access/foreign/MemorySegmentProxy -Event: 9.638 loading class jdk/internal/access/foreign/MemorySegmentProxy done -Event: 23.883 Thread 0x000000011b6e6a00 Thread added: 0x000000011b6e6a00 -Event: 23.883 Protecting memory [0x000000016facc000,0x000000016fad8000] with protection modes 0 -Event: 23.905 loading class java/util/concurrent/locks/AbstractQueuedSynchronizer$Node -Event: 23.905 loading class java/util/concurrent/locks/AbstractQueuedSynchronizer$Node done -Event: 28.942 Protecting memory [0x000000016facc000,0x000000016fad8000] with protection modes 3 -Event: 28.943 Thread 0x000000011b6e6a00 Thread exited: 0x000000011b6e6a00 - - -Dynamic libraries: -0x0000000104170000 /Applications/RStudio.app/Contents/Resources/app/bin/rsession-arm64 -0x0000000105584000 /Applications/RStudio.app/Contents/Resources/app/Frameworks/arm64/libssl.3.dylib -0x0000000106184000 /Applications/RStudio.app/Contents/Resources/app/Frameworks/arm64/libcrypto.3.dylib -0x000000019069e000 /System/Library/Frameworks/AppKit.framework/Versions/C/AppKit -0x00000001919db000 /System/Library/PrivateFrameworks/UIFoundation.framework/Versions/A/UIFoundation -0x00000002285bb000 /System/Library/PrivateFrameworks/CollectionViewCore.framework/Versions/A/CollectionViewCore -0x00000001a0c91000 /System/Library/PrivateFrameworks/RemoteViewServices.framework/Versions/A/RemoteViewServices -0x00000001978c5000 /System/Library/PrivateFrameworks/XCTTargetBootstrap.framework/Versions/A/XCTTargetBootstrap -0x000000019c054000 /System/Library/PrivateFrameworks/InternationalSupport.framework/Versions/A/InternationalSupport -0x000000019c0a8000 /System/Library/PrivateFrameworks/UserActivity.framework/Versions/A/UserActivity -0x000000024ca12000 /System/Library/PrivateFrameworks/WindowManagement.framework/Versions/A/WindowManagement -0x000000018dbd1000 /System/Library/Frameworks/SystemConfiguration.framework/Versions/A/SystemConfiguration -0x000000019b4c2000 /usr/lib/libspindump.dylib -0x0000000191b90000 /System/Library/Frameworks/UniformTypeIdentifiers.framework/Versions/A/UniformTypeIdentifiers -0x000000019573c000 /usr/lib/libapp_launch_measurement.dylib -0x0000000194b62000 /System/Library/PrivateFrameworks/CoreAnalytics.framework/Versions/A/CoreAnalytics -0x0000000195743000 /System/Library/PrivateFrameworks/CoreAutoLayout.framework/Versions/A/CoreAutoLayout -0x000000019370a000 /System/Library/Frameworks/CoreData.framework/Versions/A/CoreData -0x00000001970e5000 /System/Library/Frameworks/Metal.framework/Versions/A/Metal -0x000000019806d000 /usr/lib/liblangid.dylib -0x00000001978cb000 /System/Library/PrivateFrameworks/CoreSVG.framework/Versions/A/CoreSVG -0x0000000192555000 /System/Library/PrivateFrameworks/SkyLight.framework/Versions/A/SkyLight -0x00000001929f6000 /System/Library/Frameworks/CoreGraphics.framework/Versions/A/CoreGraphics -0x00000001a136b000 /System/Library/Frameworks/Accelerate.framework/Versions/A/Accelerate -0x000000019b31c000 /System/Library/PrivateFrameworks/IconServices.framework/Versions/A/IconServices -0x00000001970c3000 /System/Library/Frameworks/IOSurface.framework/Versions/A/IOSurface -0x0000000194b91000 /usr/lib/libDiagnosticMessagesClient.dylib -0x000000019995a000 /usr/lib/libz.1.dylib -0x00000001a4b10000 /System/Library/Frameworks/ApplicationServices.framework/Versions/A/ApplicationServices -0x00000001978ad000 /System/Library/PrivateFrameworks/DFRFoundation.framework/Versions/A/DFRFoundation -0x000000018fef8000 /usr/lib/libicucore.A.dylib -0x000000019d0b2000 /System/Library/Frameworks/AudioToolbox.framework/Versions/A/AudioToolbox -0x000000019c063000 /System/Library/PrivateFrameworks/DataDetectorsCore.framework/Versions/A/DataDetectorsCore -0x00000001b5ad6000 /System/Library/PrivateFrameworks/TextInput.framework/Versions/A/TextInput -0x000000018df51000 /System/Library/Frameworks/Foundation.framework/Versions/C/Foundation -0x00000001924a6000 /usr/lib/libMobileGestalt.dylib -0x00000001975e9000 /System/Library/Frameworks/Carbon.framework/Versions/A/Frameworks/HIToolbox.framework/Versions/A/HIToolbox -0x0000000195068000 /System/Library/Frameworks/QuartzCore.framework/Versions/A/QuartzCore -0x000000018fb25000 /System/Library/Frameworks/Security.framework/Versions/A/Security -0x00000001a0cd1000 /System/Library/Frameworks/Carbon.framework/Versions/A/Frameworks/SpeechRecognition.framework/Versions/A/SpeechRecognition -0x000000019546a000 /System/Library/PrivateFrameworks/CoreUI.framework/Versions/A/CoreUI -0x000000018f41e000 /System/Library/Frameworks/CoreAudio.framework/Versions/A/CoreAudio -0x0000000194c75000 /System/Library/Frameworks/DiskArbitration.framework/Versions/A/DiskArbitration -0x000000019b91e000 /System/Library/PrivateFrameworks/MultitouchSupport.framework/Versions/A/MultitouchSupport -0x00000001924a4000 /usr/lib/libenergytrace.dylib -0x00000001ab1cf000 /System/Library/PrivateFrameworks/RenderBox.framework/Versions/A/RenderBox -0x0000000190552000 /System/Library/Frameworks/IOKit.framework/Versions/A/IOKit -0x00000001a10a6000 /System/Library/Frameworks/CoreServices.framework/Versions/A/CoreServices -0x00000001956c8000 /System/Library/PrivateFrameworks/PerformanceAnalysis.framework/Versions/A/PerformanceAnalysis -0x00000001e3a7b000 /System/Library/Frameworks/OpenGL.framework/Versions/A/OpenGL -0x000000019578d000 /usr/lib/libxml2.2.dylib -0x0000000198d9c000 /System/Library/PrivateFrameworks/MobileKeyBag.framework/Versions/A/MobileKeyBag -0x000000018c9bc000 /usr/lib/libobjc.A.dylib -0x000000018ccb0000 /usr/lib/libc++.1.dylib -0x0000000199a18000 /usr/lib/libSystem.B.dylib -0x00000001a1023000 /System/Library/Frameworks/Accessibility.framework/Versions/A/Accessibility -0x00000001930d6000 /System/Library/Frameworks/ColorSync.framework/Versions/A/ColorSync -0x000000018cdfc000 /System/Library/Frameworks/CoreFoundation.framework/Versions/A/CoreFoundation -0x0000000197c28000 /System/Library/Frameworks/CoreImage.framework/Versions/A/CoreImage -0x000000018f229000 /System/Library/Frameworks/CoreText.framework/Versions/A/CoreText -0x00000001e82da000 /System/Library/Frameworks/CoreTransferable.framework/Versions/A/CoreTransferable -0x00000001e879f000 /System/Library/Frameworks/DeveloperToolsSupport.framework/Versions/A/DeveloperToolsSupport -0x0000000197906000 /System/Library/Frameworks/ImageIO.framework/Versions/A/ImageIO -0x000000022275b000 /System/Library/Frameworks/Symbols.framework/Versions/A/Symbols -0x0000000199a1e000 /System/Library/PrivateFrameworks/SoftLinking.framework/Versions/A/SoftLinking -0x000000019ca64000 /usr/lib/swift/libswiftCore.dylib -0x00000001b2763000 /usr/lib/swift/libswiftCoreFoundation.dylib -0x00000001b01cc000 /usr/lib/swift/libswiftCoreGraphics.dylib -0x00000001b27ad000 /usr/lib/swift/libswiftCoreImage.dylib -0x00000001b01d3000 /usr/lib/swift/libswiftDarwin.dylib -0x00000001a2716000 /usr/lib/swift/libswiftDispatch.dylib -0x00000001b27ae000 /usr/lib/swift/libswiftIOKit.dylib -0x00000001be208000 /usr/lib/swift/libswiftMetal.dylib -0x00000001cb8cd000 /usr/lib/swift/libswiftOSLog.dylib -0x00000001a4f8b000 /usr/lib/swift/libswiftObjectiveC.dylib -0x00000001c293c000 /usr/lib/swift/libswiftQuartzCore.dylib -0x00000001c6a41000 /usr/lib/swift/libswiftUniformTypeIdentifiers.dylib -0x00000001b2775000 /usr/lib/swift/libswiftXPC.dylib -0x0000000254eb9000 /usr/lib/swift/libswift_Concurrency.dylib -0x00000001a4f8f000 /usr/lib/swift/libswiftos.dylib -0x00000001b5a3a000 /usr/lib/swift/libswiftsimd.dylib -0x0000000199bcd000 /usr/lib/libcompression.dylib -0x000000019bfae000 /System/Library/PrivateFrameworks/TextureIO.framework/Versions/A/TextureIO -0x000000019afc8000 /usr/lib/libate.dylib -0x0000000199a12000 /usr/lib/system/libcache.dylib -0x00000001999cc000 /usr/lib/system/libcommonCrypto.dylib -0x00000001999f8000 /usr/lib/system/libcompiler_rt.dylib -0x00000001999ee000 /usr/lib/system/libcopyfile.dylib -0x000000018cb00000 /usr/lib/system/libcorecrypto.dylib -0x000000018cbe6000 /usr/lib/system/libdispatch.dylib -0x000000018cda1000 /usr/lib/system/libdyld.dylib -0x0000000199a08000 /usr/lib/system/libkeymgr.dylib -0x00000001999a4000 /usr/lib/system/libmacho.dylib -0x0000000198e84000 /usr/lib/system/libquarantine.dylib -0x0000000199a05000 /usr/lib/system/libremovefile.dylib -0x000000019251c000 /usr/lib/system/libsystem_asl.dylib -0x000000018ca95000 /usr/lib/system/libsystem_blocks.dylib -0x000000018cc31000 /usr/lib/system/libsystem_c.dylib -0x00000001999fc000 /usr/lib/system/libsystem_collections.dylib -0x000000019805c000 /usr/lib/system/libsystem_configuration.dylib -0x0000000197098000 /usr/lib/system/libsystem_containermanager.dylib -0x000000019963b000 /usr/lib/system/libsystem_coreservices.dylib -0x00000001901bf000 /usr/lib/system/libsystem_darwin.dylib -0x0000000255206000 /usr/lib/system/libsystem_darwindirectory.dylib -0x0000000199a09000 /usr/lib/system/libsystem_dnssd.dylib -0x000000025520a000 /usr/lib/system/libsystem_eligibility.dylib -0x000000018cc2e000 /usr/lib/system/libsystem_featureflags.dylib -0x000000018cdcf000 /usr/lib/system/libsystem_info.dylib -0x0000000199969000 /usr/lib/system/libsystem_m.dylib -0x000000018cba9000 /usr/lib/system/libsystem_malloc.dylib -0x0000000192489000 /usr/lib/system/libsystem_networkextension.dylib -0x0000000190635000 /usr/lib/system/libsystem_notify.dylib -0x0000000198061000 /usr/lib/system/libsystem_sandbox.dylib -0x000000025520e000 /usr/lib/system/libsystem_sanitizers.dylib -0x0000000199a01000 /usr/lib/system/libsystem_secinit.dylib -0x000000018cd59000 /usr/lib/system/libsystem_kernel.dylib -0x000000018cdc7000 /usr/lib/system/libsystem_platform.dylib -0x000000018cd94000 /usr/lib/system/libsystem_pthread.dylib -0x0000000193f0c000 /usr/lib/system/libsystem_symptoms.dylib -0x000000018cae5000 /usr/lib/system/libsystem_trace.dylib -0x00000001999da000 /usr/lib/system/libunwind.dylib -0x000000018ca9a000 /usr/lib/system/libxpc.dylib -0x000000018cd3d000 /usr/lib/libc++abi.dylib -0x00000001999e6000 /usr/lib/liboah.dylib -0x000000019ae74000 /usr/lib/liblzma.5.dylib -0x0000000199a1a000 /usr/lib/libfakelink.dylib -0x00000001920b5000 /System/Library/Frameworks/CFNetwork.framework/Versions/A/CFNetwork -0x0000000199a6e000 /usr/lib/libarchive.2.dylib -0x000000019efa4000 /System/Library/Frameworks/Combine.framework/Versions/A/Combine -0x00000002285cf000 /System/Library/PrivateFrameworks/CollectionsInternal.framework/Versions/A/CollectionsInternal -0x000000023ef7f000 /System/Library/PrivateFrameworks/ReflectionInternal.framework/Versions/A/ReflectionInternal -0x000000023f511000 /System/Library/PrivateFrameworks/RuntimeInternal.framework/Versions/A/RuntimeInternal -0x000000025500d000 /usr/lib/swift/libswift_StringProcessing.dylib -0x00000001904d0000 /System/Library/PrivateFrameworks/CoreServicesInternal.framework/Versions/A/CoreServicesInternal -0x0000000198eab000 /usr/lib/libbsm.0.dylib -0x00000001999ac000 /usr/lib/system/libkxld.dylib -0x0000000195704000 /System/Library/Frameworks/CoreServices.framework/Versions/A/Frameworks/FSEvents.framework/Versions/A/FSEvents -0x00000001901ca000 /System/Library/Frameworks/CoreServices.framework/Versions/A/Frameworks/CarbonCore.framework/Versions/A/CarbonCore -0x0000000194bda000 /System/Library/Frameworks/CoreServices.framework/Versions/A/Frameworks/Metadata.framework/Versions/A/Metadata -0x0000000199641000 /System/Library/Frameworks/CoreServices.framework/Versions/A/Frameworks/OSServices.framework/Versions/A/OSServices -0x0000000199af7000 /System/Library/Frameworks/CoreServices.framework/Versions/A/Frameworks/SearchKit.framework/Versions/A/SearchKit -0x0000000193e8d000 /System/Library/Frameworks/CoreServices.framework/Versions/A/Frameworks/AE.framework/Versions/A/AE -0x000000018d2d5000 /System/Library/Frameworks/CoreServices.framework/Versions/A/Frameworks/LaunchServices.framework/Versions/A/LaunchServices -0x000000019ae1d000 /System/Library/Frameworks/CoreServices.framework/Versions/A/Frameworks/DictionaryServices.framework/Versions/A/DictionaryServices -0x0000000195711000 /System/Library/Frameworks/CoreServices.framework/Versions/A/Frameworks/SharedFileList.framework/Versions/A/SharedFileList -0x0000000199b97000 /usr/lib/libapple_nghttp2.dylib -0x0000000193b01000 /usr/lib/libsqlite3.dylib -0x0000000193f15000 /System/Library/Frameworks/Network.framework/Versions/A/Network -0x00000002538ca000 /usr/lib/libCoreEntitlements.dylib -0x0000000239e89000 /System/Library/PrivateFrameworks/MessageSecurity.framework/Versions/A/MessageSecurity -0x0000000193ae7000 /System/Library/PrivateFrameworks/ProtocolBuffer.framework/Versions/A/ProtocolBuffer -0x000000019956a000 /System/Library/PrivateFrameworks/AppleFSCompression.framework/Versions/A/AppleFSCompression -0x0000000198e93000 /usr/lib/libcoretls.dylib -0x000000019ae93000 /usr/lib/libcoretls_cfhelpers.dylib -0x0000000199bc7000 /usr/lib/libpam.2.dylib -0x000000019af05000 /usr/lib/libxar.1.dylib -0x000000019b2f3000 /usr/lib/libheimdal-asn1.dylib -0x00000001920b4000 /usr/lib/libnetwork.dylib -0x0000000199a1f000 /usr/lib/libpcap.A.dylib -0x0000000193f01000 /usr/lib/libdns_services.dylib -0x0000000198069000 /System/Library/PrivateFrameworks/AppleSystemInfo.framework/Versions/A/AppleSystemInfo -0x0000000198b91000 /System/Library/PrivateFrameworks/IOMobileFramebuffer.framework/Versions/A/IOMobileFramebuffer -0x0000000254f64000 /usr/lib/swift/libswift_RegexParser.dylib -0x000000019962e000 /usr/lib/libbz2.1.0.dylib -0x0000000198e87000 /usr/lib/libCheckFix.dylib -0x0000000192534000 /System/Library/PrivateFrameworks/TCC.framework/Versions/A/TCC -0x000000019806f000 /System/Library/PrivateFrameworks/CoreNLP.framework/Versions/A/CoreNLP -0x0000000194b93000 /System/Library/PrivateFrameworks/MetadataUtilities.framework/Versions/A/MetadataUtilities -0x0000000198ebd000 /usr/lib/libmecab.dylib -0x000000018dc65000 /usr/lib/libCRFSuite.dylib -0x0000000198f19000 /usr/lib/libgermantok.dylib -0x0000000199b6e000 /usr/lib/libThaiTokenizer.dylib -0x0000000194c7e000 /System/Library/Frameworks/Accelerate.framework/Versions/A/Frameworks/vImage.framework/Versions/A/vImage -0x00000001a107d000 /System/Library/Frameworks/Accelerate.framework/Versions/A/Frameworks/vecLib.framework/Versions/A/vecLib -0x000000019af4c000 /System/Library/Frameworks/Accelerate.framework/Versions/A/Frameworks/vecLib.framework/Versions/A/libvMisc.dylib -0x0000000198a6c000 /System/Library/Frameworks/Accelerate.framework/Versions/A/Frameworks/vecLib.framework/Versions/A/libvDSP.dylib -0x000000018d6dc000 /System/Library/Frameworks/Accelerate.framework/Versions/A/Frameworks/vecLib.framework/Versions/A/libBLAS.dylib -0x0000000199ca2000 /System/Library/Frameworks/Accelerate.framework/Versions/A/Frameworks/vecLib.framework/Versions/A/libLAPACK.dylib -0x0000000198f1c000 /System/Library/Frameworks/Accelerate.framework/Versions/A/Frameworks/vecLib.framework/Versions/A/libLinearAlgebra.dylib -0x0000000199bb2000 /System/Library/Frameworks/Accelerate.framework/Versions/A/Frameworks/vecLib.framework/Versions/A/libSparseBLAS.dylib -0x0000000199c9d000 /System/Library/Frameworks/Accelerate.framework/Versions/A/Frameworks/vecLib.framework/Versions/A/libQuadrature.dylib -0x0000000198198000 /System/Library/Frameworks/Accelerate.framework/Versions/A/Frameworks/vecLib.framework/Versions/A/libBNNS.dylib -0x000000018db6a000 /System/Library/Frameworks/Accelerate.framework/Versions/A/Frameworks/vecLib.framework/Versions/A/libSparse.dylib -0x00000002385d8000 /System/Library/PrivateFrameworks/MIL.framework/Versions/A/MIL -0x0000000199a55000 /usr/lib/libiconv.2.dylib -0x00000001999a0000 /usr/lib/libcharset.1.dylib -0x00000001956e4000 /System/Library/Frameworks/OpenDirectory.framework/Versions/A/Frameworks/CFOpenDirectory.framework/Versions/A/CFOpenDirectory -0x00000001956d4000 /System/Library/Frameworks/OpenDirectory.framework/Versions/A/OpenDirectory -0x000000019ae95000 /System/Library/PrivateFrameworks/APFS.framework/Versions/A/APFS -0x0000000198dc3000 /System/Library/Frameworks/SecurityFoundation.framework/Versions/A/SecurityFoundation -0x000000019af14000 /usr/lib/libutil.dylib -0x0000000236739000 /System/Library/PrivateFrameworks/InstalledContentLibrary.framework/Versions/A/InstalledContentLibrary -0x0000000190511000 /System/Library/PrivateFrameworks/CoreServicesStore.framework/Versions/A/CoreServicesStore -0x0000000225d7c000 /System/Library/PrivateFrameworks/AppleMobileFileIntegrity.framework/Versions/A/AppleMobileFileIntegrity -0x00000001b2731000 /usr/lib/libmis.dylib -0x00000001c2e23000 /System/Library/PrivateFrameworks/MobileSystemServices.framework/Versions/A/MobileSystemServices -0x00000001e0e85000 /System/Library/PrivateFrameworks/ConfigProfileHelper.framework/Versions/A/ConfigProfileHelper -0x0000000199b70000 /System/Library/PrivateFrameworks/AppleSauce.framework/Versions/A/AppleSauce -0x000000018ebaf000 /System/Library/PrivateFrameworks/LanguageModeling.framework/Versions/A/LanguageModeling -0x000000019af18000 /usr/lib/libxslt.1.dylib -0x0000000199a5c000 /usr/lib/libcmph.dylib -0x0000000198b5d000 /System/Library/PrivateFrameworks/CoreEmoji.framework/Versions/A/CoreEmoji -0x0000000198192000 /System/Library/PrivateFrameworks/LinguisticData.framework/Versions/A/LinguisticData -0x000000018da78000 /System/Library/PrivateFrameworks/Lexicon.framework/Versions/A/Lexicon -0x0000000198e51000 /System/Library/PrivateFrameworks/BackgroundTaskManagement.framework/Versions/A/BackgroundTaskManagement -0x0000000253ab4000 /usr/lib/libTLE.dylib -0x000000019b7e4000 /System/Library/PrivateFrameworks/AppleJPEG.framework/Versions/A/AppleJPEG -0x000000019b2d8000 /usr/lib/libexpat.1.dylib -0x000000019be0c000 /System/Library/Frameworks/ImageIO.framework/Versions/A/Resources/libPng.dylib -0x000000019be37000 /System/Library/Frameworks/ImageIO.framework/Versions/A/Resources/libTIFF.dylib -0x000000019bf22000 /System/Library/Frameworks/ImageIO.framework/Versions/A/Resources/libGIF.dylib -0x000000019b82a000 /System/Library/Frameworks/ImageIO.framework/Versions/A/Resources/libJP2.dylib -0x000000019bec7000 /System/Library/Frameworks/ImageIO.framework/Versions/A/Resources/libJPEG.dylib -0x000000019bebe000 /System/Library/Frameworks/ImageIO.framework/Versions/A/Resources/libRadiance.dylib -0x0000000197484000 /System/Library/PrivateFrameworks/FontServices.framework/libFontParser.dylib -0x0000000193e26000 /System/Library/PrivateFrameworks/RunningBoardServices.framework/Versions/A/RunningBoardServices -0x00000001a79d1000 /System/Library/PrivateFrameworks/IOSurfaceAccelerator.framework/Versions/A/IOSurfaceAccelerator -0x000000019b91a000 /System/Library/PrivateFrameworks/WatchdogClient.framework/Versions/A/WatchdogClient -0x000000018ed95000 /System/Library/Frameworks/CoreDisplay.framework/Versions/A/CoreDisplay -0x000000019733b000 /System/Library/Frameworks/CoreMedia.framework/Versions/A/CoreMedia -0x00000001970db000 /System/Library/PrivateFrameworks/IOAccelerator.framework/Versions/A/IOAccelerator -0x0000000195877000 /System/Library/Frameworks/CoreVideo.framework/Versions/A/CoreVideo -0x0000000199bc5000 /System/Library/Frameworks/MetalPerformanceShaders.framework/Versions/A/MetalPerformanceShaders -0x000000019b95d000 /System/Library/Frameworks/VideoToolbox.framework/Versions/A/VideoToolbox -0x0000000195913000 /System/Library/PrivateFrameworks/UserManagement.framework/Versions/A/UserManagement -0x0000000193d4d000 /System/Library/PrivateFrameworks/BaseBoard.framework/Versions/A/BaseBoard -0x0000000198067000 /System/Library/PrivateFrameworks/AggregateDictionary.framework/Versions/A/AggregateDictionary -0x0000000225bb6000 /System/Library/PrivateFrameworks/AppleKeyStore.framework/Versions/A/AppleKeyStore -0x000000019beb9000 /System/Library/PrivateFrameworks/GPUWrangler.framework/Versions/A/GPUWrangler -0x000000019be99000 /System/Library/PrivateFrameworks/IOPresentment.framework/Versions/A/IOPresentment -0x000000019bec1000 /System/Library/PrivateFrameworks/DSExternalDisplay.framework/Versions/A/DSExternalDisplay -0x00000002327c6000 /System/Library/PrivateFrameworks/GPUCompiler.framework/Versions/32023/Libraries/libllvm-flatbuffers.dylib -0x00000001e3a6e000 /System/Library/Frameworks/OpenGL.framework/Versions/A/Libraries/libCoreFSCache.dylib -0x000000022f42a000 /System/Library/PrivateFrameworks/GPUCompiler.framework/Versions/32023/Libraries/libGPUCompilerUtils.dylib -0x000000019bf28000 /System/Library/PrivateFrameworks/CMCaptureCore.framework/Versions/A/CMCaptureCore -0x00000001e88c2000 /System/Library/Frameworks/ExtensionFoundation.framework/Versions/A/ExtensionFoundation -0x00000001a2f7f000 /System/Library/PrivateFrameworks/CoreTime.framework/Versions/A/CoreTime -0x000000019b4ac000 /System/Library/PrivateFrameworks/AppServerSupport.framework/Versions/A/AppServerSupport -0x000000019da40000 /System/Library/PrivateFrameworks/perfdata.framework/Versions/A/perfdata -0x000000018eeb9000 /System/Library/PrivateFrameworks/AudioToolboxCore.framework/Versions/A/AudioToolboxCore -0x0000000197311000 /System/Library/PrivateFrameworks/caulk.framework/Versions/A/caulk -0x000000019d2ae000 /usr/lib/libAudioStatistics.dylib -0x00000001b1a6a000 /System/Library/PrivateFrameworks/SystemPolicy.framework/Versions/A/SystemPolicy -0x000000019d587000 /usr/lib/libSMC.dylib -0x00000001a6f79000 /System/Library/Frameworks/CoreMIDI.framework/Versions/A/CoreMIDI -0x000000019bdd3000 /usr/lib/libAudioToolboxUtility.dylib -0x00000001ace6b000 /System/Library/PrivateFrameworks/OSAServicesClient.framework/Versions/A/OSAServicesClient -0x000000019da4e000 /usr/lib/libperfcheck.dylib -0x00000001a2a36000 /System/Library/PrivateFrameworks/BoardServices.framework/Versions/A/BoardServices -0x000000019b1c0000 /System/Library/PrivateFrameworks/PlugInKit.framework/Versions/A/PlugInKit -0x0000000198db5000 /System/Library/PrivateFrameworks/AssertionServices.framework/Versions/A/AssertionServices -0x00000001a608a000 /System/Library/PrivateFrameworks/ASEProcessing.framework/Versions/A/ASEProcessing -0x00000001ced54000 /System/Library/PrivateFrameworks/Symbolication.framework/Versions/A/Symbolication -0x000000023dd6c000 /System/Library/PrivateFrameworks/PhotosensitivityProcessing.framework/Versions/A/PhotosensitivityProcessing -0x000000019b45d000 /System/Library/PrivateFrameworks/GraphVisualizer.framework/Versions/A/GraphVisualizer -0x00000001e3ad0000 /System/Library/Frameworks/OpenGL.framework/Versions/A/Libraries/libGLU.dylib -0x00000001e3a8f000 /System/Library/Frameworks/OpenGL.framework/Versions/A/Libraries/libGFXShared.dylib -0x00000001e3c68000 /System/Library/Frameworks/OpenGL.framework/Versions/A/Libraries/libGL.dylib -0x00000001e3a98000 /System/Library/Frameworks/OpenGL.framework/Versions/A/Libraries/libGLImage.dylib -0x00000001e3a8c000 /System/Library/Frameworks/OpenGL.framework/Versions/A/Libraries/libCVMSPluginSupport.dylib -0x0000000253a6c000 /usr/lib/libRosetta.dylib -0x00000001e3a75000 /System/Library/Frameworks/OpenGL.framework/Versions/A/Libraries/libCoreVMClient.dylib -0x000000022d630000 /System/Library/PrivateFrameworks/FontServices.framework/Versions/A/FontServices -0x000000019b469000 /System/Library/PrivateFrameworks/OTSVG.framework/Versions/A/OTSVG -0x0000000195418000 /System/Library/Frameworks/ApplicationServices.framework/Versions/A/Frameworks/ATS.framework/Versions/A/Resources/libFontRegistry.dylib -0x000000019b4b7000 /System/Library/PrivateFrameworks/FontServices.framework/libhvf.dylib -0x000000022d631000 /System/Library/PrivateFrameworks/FontServices.framework/libXTFontStaticRegistryData.dylib -0x0000000197fae000 /System/Library/Frameworks/MetalPerformanceShaders.framework/Versions/A/Frameworks/MPSCore.framework/Versions/A/MPSCore -0x00000001994d8000 /System/Library/Frameworks/MetalPerformanceShaders.framework/Versions/A/Frameworks/MPSImage.framework/Versions/A/MPSImage -0x0000000198f31000 /System/Library/Frameworks/MetalPerformanceShaders.framework/Versions/A/Frameworks/MPSNeuralNetwork.framework/Versions/A/MPSNeuralNetwork -0x000000019937c000 /System/Library/Frameworks/MetalPerformanceShaders.framework/Versions/A/Frameworks/MPSMatrix.framework/Versions/A/MPSMatrix -0x0000000199187000 /System/Library/Frameworks/MetalPerformanceShaders.framework/Versions/A/Frameworks/MPSRayIntersector.framework/Versions/A/MPSRayIntersector -0x00000001993ae000 /System/Library/Frameworks/MetalPerformanceShaders.framework/Versions/A/Frameworks/MPSNDArray.framework/Versions/A/MPSNDArray -0x00000001ea19c000 /System/Library/Frameworks/MetalPerformanceShaders.framework/Versions/A/Frameworks/MPSFunctions.framework/Versions/A/MPSFunctions -0x00000001ea181000 /System/Library/Frameworks/MetalPerformanceShaders.framework/Versions/A/Frameworks/MPSBenchmarkLoop.framework/Versions/A/MPSBenchmarkLoop -0x000000018d590000 /System/Library/PrivateFrameworks/MetalTools.framework/Versions/A/MetalTools -0x00000001b6c13000 /System/Library/PrivateFrameworks/IOAccelMemoryInfo.framework/Versions/A/IOAccelMemoryInfo -0x00000001c2d1c000 /System/Library/PrivateFrameworks/kperf.framework/Versions/A/kperf -0x00000001b2756000 /System/Library/PrivateFrameworks/GPURawCounter.framework/Versions/A/GPURawCounter -0x00000001a2e51000 /System/Library/PrivateFrameworks/CoreSymbolication.framework/Versions/A/CoreSymbolication -0x00000001b2702000 /System/Library/PrivateFrameworks/MallocStackLogging.framework/Versions/A/MallocStackLogging -0x000000019b062000 /System/Library/PrivateFrameworks/CrashReporterSupport.framework/Versions/A/CrashReporterSupport -0x00000001a2e0c000 /System/Library/PrivateFrameworks/DebugSymbols.framework/Versions/A/DebugSymbols -0x00000001c1683000 /System/Library/PrivateFrameworks/OSAnalytics.framework/Versions/A/OSAnalytics -0x000000024ac65000 /System/Library/PrivateFrameworks/VideoToolboxParavirtualizationSupport.framework/Versions/A/VideoToolboxParavirtualizationSupport -0x000000019b28c000 /System/Library/PrivateFrameworks/AppleVA.framework/Versions/A/AppleVA -0x000000019d2f6000 /System/Library/Frameworks/ApplicationServices.framework/Versions/A/Frameworks/ATS.framework/Versions/A/ATS -0x0000000193285000 /System/Library/Frameworks/ApplicationServices.framework/Versions/A/Frameworks/HIServices.framework/Versions/A/HIServices -0x000000019bf36000 /System/Library/Frameworks/ApplicationServices.framework/Versions/A/Frameworks/PrintCore.framework/Versions/A/PrintCore -0x000000019d6e0000 /System/Library/Frameworks/ApplicationServices.framework/Versions/A/Frameworks/QD.framework/Versions/A/QD -0x000000019d6d4000 /System/Library/Frameworks/ApplicationServices.framework/Versions/A/Frameworks/ColorSyncLegacy.framework/Versions/A/ColorSyncLegacy -0x000000019d2c6000 /System/Library/Frameworks/ApplicationServices.framework/Versions/A/Frameworks/SpeechSynthesis.framework/Versions/A/SpeechSynthesis -0x000000019bef2000 /System/Library/Frameworks/ApplicationServices.framework/Versions/A/Frameworks/ATSUI.framework/Versions/A/ATSUI -0x000000019d667000 /usr/lib/libcups.2.dylib -0x000000019da5c000 /System/Library/Frameworks/Kerberos.framework/Versions/A/Kerberos -0x000000019da6d000 /System/Library/Frameworks/GSS.framework/Versions/A/GSS -0x000000019d375000 /usr/lib/libresolv.9.dylib -0x000000019b4c8000 /System/Library/PrivateFrameworks/Heimdal.framework/Versions/A/Heimdal -0x00000001a4ef8000 /System/Library/Frameworks/Kerberos.framework/Versions/A/Libraries/libHeimdalProxy.dylib -0x000000019dac7000 /System/Library/PrivateFrameworks/CommonAuth.framework/Versions/A/CommonAuth -0x00000001e76a8000 /System/Library/Frameworks/AVFAudio.framework/Versions/A/AVFAudio -0x00000001aceba000 /System/Library/PrivateFrameworks/AXCoreUtilities.framework/Versions/A/AXCoreUtilities -0x0000000237cb0000 /System/Library/PrivateFrameworks/IsolatedCoreAudioClient.framework/Versions/A/IsolatedCoreAudioClient -0x000000019d232000 /System/Library/PrivateFrameworks/AudioSession.framework/Versions/A/AudioSession -0x000000019ed43000 /System/Library/Frameworks/IOBluetooth.framework/Versions/A/IOBluetooth -0x000000019b397000 /System/Library/PrivateFrameworks/MediaExperience.framework/Versions/A/MediaExperience -0x000000019d071000 /System/Library/PrivateFrameworks/AudioSession.framework/libSessionUtility.dylib -0x000000019d6ec000 /System/Library/PrivateFrameworks/AudioResourceArbitration.framework/Versions/A/AudioResourceArbitration -0x00000001a1dc4000 /System/Library/PrivateFrameworks/PowerLog.framework/Versions/A/PowerLog -0x00000001a1ce2000 /System/Library/Frameworks/CoreBluetooth.framework/Versions/A/CoreBluetooth -0x00000001a4ef9000 /System/Library/Frameworks/AudioUnit.framework/Versions/A/AudioUnit -0x0000000198c1e000 /System/Library/PrivateFrameworks/CoreUtils.framework/Versions/A/CoreUtils -0x000000022b87b000 /System/Library/PrivateFrameworks/CoreUtilsExtras.framework/Versions/A/CoreUtilsExtras -0x00000002365c6000 /System/Library/PrivateFrameworks/IO80211.framework/Versions/A/IO80211 -0x00000001a297a000 /System/Library/PrivateFrameworks/FrontBoardServices.framework/Versions/A/FrontBoardServices -0x00000001a44c1000 /System/Library/PrivateFrameworks/BackBoardServices.framework/Versions/A/BackBoardServices -0x000000019b2fe000 /System/Library/PrivateFrameworks/IconFoundation.framework/Versions/A/IconFoundation -0x00000001a0cbd000 /System/Library/PrivateFrameworks/SpeechRecognitionCore.framework/Versions/A/SpeechRecognitionCore -0x00000001aced9000 /usr/lib/libAccessibility.dylib -0x00000001a13b7000 /System/Library/Frameworks/MediaAccessibility.framework/Versions/A/MediaAccessibility -0x00000001d2408000 /System/Library/Frameworks/OSLog.framework/Versions/A/OSLog -0x00000001b2690000 /System/Library/PrivateFrameworks/LoggingSupport.framework/Versions/A/LoggingSupport -0x00000001054f0000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/lib/libRblas.0.dylib -0x0000000105d84000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/lib/libgfortran.5.dylib -0x0000000105648000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/lib/libquadmath.0.dylib -0x0000000105520000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/lib/libgcc_s.1.1.dylib -0x00000001b6bdf000 /usr/lib/libncurses.5.4.dylib -0x0000000105098000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/methods/libs/methods.so -0x00000001050d4000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/utils/libs/utils.so -0x0000000105264000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/grDevices/libs/grDevices.so -0x000000019b598000 /System/Library/PrivateFrameworks/login.framework/Versions/A/login -0x00000001a2b50000 /System/Library/Frameworks/LocalAuthentication.framework/Versions/A/LocalAuthentication -0x00000001958d6000 /System/Library/PrivateFrameworks/login.framework/Versions/A/Frameworks/loginsupport.framework/Versions/A/loginsupport -0x0000000238462000 /System/Library/PrivateFrameworks/LocalAuthenticationCore.framework/Versions/A/LocalAuthenticationCore -0x00000001a2b9b000 /System/Library/Frameworks/LocalAuthentication.framework/Support/SharedUtils.framework/Versions/A/SharedUtils -0x00000001a2aeb000 /System/Library/Frameworks/CryptoTokenKit.framework/Versions/A/CryptoTokenKit -0x00000001052c8000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/graphics/libs/graphics.so -0x00000001053bc000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/stats/libs/stats.so -0x0000000105f4c000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/lib/libRlapack.dylib -0x0000000253757000 /usr/lib/i18n/libiconv_std.dylib -0x000000025373f000 /usr/lib/i18n/libUTF8.dylib -0x000000025375f000 /usr/lib/i18n/libmapper_none.dylib -0x0000000105314000 /Users/jreps/Library/R/arm64/4.2/library/cli/libs/cli.so -0x000000010d000000 /Library/Java/JavaVirtualMachines/amazon-corretto-17.jdk/Contents/Home/lib/server/libjvm.dylib -0x0000000105200000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/rJava/libs/rJava.so -0x0000000105350000 /Users/jreps/Library/R/arm64/4.2/library/bit/libs/bit.so -0x000000010537c000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/bit64/libs/bit64.so -0x0000000106110000 /Users/jreps/Library/R/arm64/4.2/library/rlang/libs/rlang.so -0x00000001050b4000 /Library/Java/JavaVirtualMachines/amazon-corretto-17.jdk/Contents/Home/lib/libjimage.dylib -0x0000000105800000 /Library/Java/JavaVirtualMachines/amazon-corretto-17.jdk/Contents/Home/lib/libjava.dylib -0x0000000253737000 /usr/lib/i18n/libUTF1632.dylib -0x0000000105834000 /Library/Java/JavaVirtualMachines/amazon-corretto-17.jdk/Contents/Home/lib/libnio.dylib -0x0000000105854000 /Library/Java/JavaVirtualMachines/amazon-corretto-17.jdk/Contents/Home/lib/libnet.dylib -0x0000000108498000 /Library/Java/JavaVirtualMachines/amazon-corretto-17.jdk/Contents/Home/lib/libzip.dylib -0x000000015b000000 /Library/Developer/CommandLineTools/usr/lib/libclang.dylib -0x00000001084c0000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/tools/libs/tools.so -0x000000010c400000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/modules/internet.so -0x00000001a4813000 /usr/lib/libcurl.4.dylib -0x0000000253e1a000 /usr/lib/libcrypto.46.dylib -0x0000000254b3c000 /usr/lib/libssl.48.dylib -0x00000001a44e7000 /System/Library/Frameworks/LDAP.framework/Versions/A/LDAP -0x00000001a4523000 /System/Library/PrivateFrameworks/TrustEvaluationAgent.framework/Versions/A/TrustEvaluationAgent -0x000000019d38e000 /usr/lib/libsasl2.2.dylib -0x000000010c554000 /Users/jreps/Library/R/arm64/4.2/library/digest/libs/digest.so -0x0000000105464000 /Users/jreps/Library/R/arm64/4.2/library/fastmap/libs/fastmap.so -0x000000010524c000 /Users/jreps/Library/R/arm64/4.2/library/htmltools/libs/htmltools.so -0x000000010e290000 /Users/jreps/Library/R/arm64/4.2/library/Rcpp/libs/Rcpp.so -0x000000010e07c000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/later/libs/later.so -0x00000001053a8000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/magrittr/libs/magrittr.so -0x000000010c528000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/promises/libs/promises.so -0x000000010e434000 /Users/jreps/Library/R/arm64/4.2/library/httpuv/libs/httpuv.so -0x0000000105574000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/mime/libs/mime.so -0x00000001056e4000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/ellipsis/libs/ellipsis.so -0x000000010e544000 /Users/jreps/Library/R/arm64/4.2/library/vctrs/libs/vctrs.so -0x0000000105878000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/glue/libs/glue.so -0x000000010c580000 /Users/jreps/Library/R/arm64/4.2/library/fansi/libs/fansi.so -0x000000010e200000 /Users/jreps/Library/R/arm64/4.2/library/utf8/libs/utf8.so -0x0000000106168000 /Users/jreps/Library/R/arm64/4.2/library/tibble/libs/tibble.so -0x000000010c5a4000 /Users/jreps/Library/R/arm64/4.2/library/dplyr/libs/dplyr.so -0x000000010c5c0000 /Users/jreps/Library/R/arm64/4.2/library/checkmate/libs/checkmate.so -0x00000001084e8000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/backports/libs/backports.so -0x000000011c000000 /Users/jreps/Library/R/arm64/4.2/library/readr/libs/readr.so -0x000000010e374000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/tzdb/libs/tzdb.so -0x000000019ca06000 /usr/lib/libusrtcp.dylib -0x0000000191feb000 /usr/lib/libboringssl.dylib -0x00000001087ec000 /Library/Java/JavaVirtualMachines/amazon-corretto-17.jdk/Contents/Home/lib/libextnet.dylib -0x000000010c5e0000 /Library/Java/JavaVirtualMachines/amazon-corretto-17.jdk/Contents/Home/lib/libmanagement.dylib -0x000000010e0c8000 /Library/Java/JavaVirtualMachines/amazon-corretto-17.jdk/Contents/Home/lib/libmanagement_ext.dylib -0x000000011c098000 /Users/jreps/Library/R/arm64/4.2/library/triebeard/libs/triebeard.so -0x000000010e3c4000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/urltools/libs/urltools.so -0x0000000156cb0000 /Users/jreps/Library/R/arm64/4.2/library/sass/libs/sass.so -0x000000010e258000 /Users/jreps/Library/R/arm64/4.2/library/jsonlite/libs/jsonlite.so -0x00000001087d8000 /Users/jreps/Library/R/arm64/4.2/library/cachem/libs/cachem.so -0x000000010e6a0000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/yaml/libs/yaml.so -0x000000011de00000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/grid/libs/grid.so -0x000000010e274000 /Users/jreps/Library/R/arm64/4.2/library/colorspace/libs/colorspace.so -0x000000011deb8000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/data.table/libs/data_table.so -0x000000010e0dc000 /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/lazyeval/libs/lazyeval.so -0x000000010e324000 /Users/jreps/Library/R/arm64/4.2/library/purrr/libs/purrr.so -0x000000010e6d0000 /Users/jreps/Library/R/arm64/4.2/library/tidyr/libs/tidyr.so -0x0000000253767000 /usr/lib/i18n/libmapper_serial.dylib -0x0000000253763000 /usr/lib/i18n/libmapper_parallel.dylib -0x000000025375b000 /usr/lib/i18n/libmapper_646.dylib -0x000000025376b000 /usr/lib/i18n/libmapper_std.dylib - - -VM Arguments: -jvm_args: -Djava.awt.headless=true -Xmx512m -Xrs vfprintf exit -Xss2m -java_command: -java_class_path (initial): /Library/Frameworks/R.framework/Versions/4.2-arm64/Resources/library/rJava/java/boot -Launcher Type: generic - -[Global flags] - intx CICompilerCount = 4 {product} {ergonomic} - uint ConcGCThreads = 2 {product} {ergonomic} - uint G1ConcRefinementThreads = 8 {product} {ergonomic} - size_t G1HeapRegionSize = 1048576 {product} {ergonomic} - uintx GCDrainStackTargetSize = 64 {product} {ergonomic} - size_t InitialHeapSize = 268435456 {product} {ergonomic} - size_t MarkStackSize = 4194304 {product} {ergonomic} - size_t MaxHeapSize = 536870912 {product} {command line} - size_t MaxNewSize = 321912832 {product} {ergonomic} - size_t MinHeapDeltaBytes = 1048576 {product} {ergonomic} - size_t MinHeapSize = 8388608 {product} {ergonomic} - uintx NonNMethodCodeHeapSize = 5839564 {pd product} {ergonomic} - uintx NonProfiledCodeHeapSize = 122909338 {pd product} {ergonomic} - uintx ProfiledCodeHeapSize = 122909338 {pd product} {ergonomic} - bool ReduceSignalUsage = true {product} {command line} - uintx ReservedCodeCacheSize = 251658240 {pd product} {ergonomic} - bool SegmentedCodeCache = true {product} {ergonomic} - size_t SoftMaxHeapSize = 536870912 {manageable} {ergonomic} - intx ThreadStackSize = 2048 {pd product} {command line} - bool UseCompressedClassPointers = true {product lp64_product} {ergonomic} - bool UseCompressedOops = true {product lp64_product} {ergonomic} - bool UseG1GC = true {product} {ergonomic} - bool UseNUMA = false {product} {ergonomic} - bool UseNUMAInterleaving = false {product} {ergonomic} - -Logging: -Log output configuration: - #0: stdout all=warning uptime,level,tags - #1: stderr all=off uptime,level,tags - -Environment Variables: -PATH=/Library/Frameworks/Python.framework/Versions/3.11/bin:/Library/Frameworks/Python.framework/Versions/3.11/bin:/Library/Frameworks/Python.framework/Versions/3.11/bin:/Library/Frameworks/Python.framework/Versions/3.11/bin:/Library/Frameworks/Python.framework/Versions/3.11/bin:/usr/local/bin:/System/Cryptexes/App/usr/bin:/usr/bin:/bin:/usr/sbin:/sbin:/var/run/com.apple.security.cryptexd/codex.system/bootstrap/usr/local/bin:/var/run/com.apple.security.cryptexd/codex.system/bootstrap/usr/bin:/var/run/com.apple.security.cryptexd/codex.system/bootstrap/usr/appleinternal/bin:/Library/TeX/texbin:/Users/jreps/Applications/quarto/bin:/usr/ucb:/Applications/quarto/bin:/usr/texbin:/Applications/RStudio.app/Contents/Resources/app/bin/postback:/Applications/RStudio.app/Contents/Resources/app/bin/postback:/Applications/RStudio.app/Contents/Resources/app/bin/postback:/Applications/RStudio.app/Contents/Resources/app/bin/postback -SHELL=/bin/zsh -DISPLAY=:0 -LANG=en_US.UTF-8 -LC_CTYPE=en_US.UTF-8 -TERM=xterm-256color -TMPDIR=/var/folders/68/4qxz0vzd2z1dt6bvj379jwl80000gp/T/ -DYLD_LIBRARY_PATH=/Library/Java/JavaVirtualMachines/amazon-corretto-17.jdk/Contents/Home/lib/server -DYLD_FALLBACK_LIBRARY_PATH=/Library/Frameworks/R.framework/Resources/lib:/Library/Java/JavaVirtualMachines/jdk-17.0.1+12/Contents/Home/lib/server:/var/folders/68/4qxz0vzd2z1dt6bvj379jwl80000gp/T/rstudio-fallback-library-path-1123487826 - -Signal Handlers: - SIGSEGV: crash_handler in libjvm.dylib, mask=11100110000111110111111111111111, flags=SA_RESTART|SA_SIGINFO - SIGBUS: crash_handler in libjvm.dylib, mask=11100110000111110111111111111111, flags=SA_RESTART|SA_SIGINFO - SIGFPE: crash_handler in libjvm.dylib, mask=11100110000111110111111111111111, flags=SA_RESTART|SA_SIGINFO - SIGPIPE: javaSignalHandler in libjvm.dylib, mask=11100110000111110111111111111111, flags=SA_RESTART|SA_SIGINFO - SIGXFSZ: javaSignalHandler in libjvm.dylib, mask=11100110000111110111111111111111, flags=SA_RESTART|SA_SIGINFO - SIGILL: crash_handler in libjvm.dylib, mask=11100110000111110111111111111111, flags=SA_RESTART|SA_SIGINFO - SIGUSR2: SIG_IGN, mask=00000000000000000000000000000000, flags=none - *** Handler was modified! - *** Expected: SR_handler in libjvm.dylib, mask=11000000000000000000000000000000, flags=SA_RESTART|SA_SIGINFO - SIGHUP: SIG_DFL, mask=00000000000000000000000000000000, flags=none - SIGINT: rstudio_boost::asio::detail::reactive_socket_accept_op_base, rstudio_boost::asio::ip::tcp>::do_perform+620944 in rsession-arm64, mask=00000000000000000000000000000000, flags=SA_RESTART - SIGTERM: SIG_DFL, mask=00000000000000000000000000000000, flags=none - SIGQUIT: SIG_DFL, mask=00000000000000000000000000000000, flags=none - SIGTRAP: crash_handler in libjvm.dylib, mask=11100110000111110111111111111111, flags=SA_RESTART|SA_SIGINFO - - ---------------- S Y S T E M --------------- - -OS: -uname: Darwin 23.5.0 Darwin Kernel Version 23.5.0: Wed May 1 20:12:58 PDT 2024; root:xnu-10063.121.3~5/RELEASE_ARM64_T6000 arm64 -OS uptime: 0 days 9:23 hours -rlimit (soft/hard): STACK 8176k/65520k , CORE 0k/infinity , NPROC 2666/4000 , NOFILE 12544/infinity , AS infinity/infinity , CPU infinity/infinity , DATA infinity/infinity , FSIZE infinity/infinity , MEMLOCK infinity/infinity , RSS infinity/infinity -load average: 2.40 2.95 4.51 - -CPU: total 8 (initial active 8) 0x61:0x0:0x1b588bb3:0, fp, simd, crc, lse - -Memory: 16k page, physical 16777216k(758240k free), swap 0k(0k free) - -vm_info: OpenJDK 64-Bit Server VM (17.0.5+8-LTS) for bsd-aarch64 JRE (17.0.5+8-LTS), built on Oct 13 2022 05:06:05 by "ec2user" with clang Apple LLVM 13.0.0 (clang-1300.0.29.30) - -END. From e9967998cf78de21dce76eca5e1404567a9ad3e0 Mon Sep 17 00:00:00 2001 From: Nathan Hall Date: Fri, 20 Sep 2024 08:07:51 -0400 Subject: [PATCH 8/8] fixing testing errors --- DESCRIPTION | 2 +- R/estimation-cohort-method-covariateBalance.R | 4 ++-- R/estimation-cohort-method-propensityModel.R | 2 +- R/estimation-cohort-method-systematicError.R | 2 +- tests/testthat/Rplots.pdf | Bin 0 -> 10146 bytes .../test-estimation-cohort-method-power.R | 4 ++-- 6 files changed, 7 insertions(+), 7 deletions(-) create mode 100644 tests/testthat/Rplots.pdf diff --git a/DESCRIPTION b/DESCRIPTION index 16e4363..74e2694 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -62,4 +62,4 @@ Suggests: Remotes: ohdsi/ReportGenerator, ohdsi/ResultModelManager -RoxygenNote: 7.3.1 +RoxygenNote: 7.3.2 diff --git a/R/estimation-cohort-method-covariateBalance.R b/R/estimation-cohort-method-covariateBalance.R index 52a5c9b..39656b2 100644 --- a/R/estimation-cohort-method-covariateBalance.R +++ b/R/estimation-cohort-method-covariateBalance.R @@ -456,7 +456,7 @@ plotCohortMethodCovariateBalanceScatterPlotNew <- function( beforeLabel = "Before propensity score adjustment", afterLabel = "After propensity score adjustment", textsearch = shiny::reactiveVal(NULL), - maxSdmStatistic + maxSdmStatistic = NULL ){ if(is.null(textsearch())){ @@ -498,7 +498,7 @@ plotCohortMethodCovariateBalanceScatterPlotNew <- function( ) %>% plotly::layout( #shapes = list(xyline(limits)), - title = paste0("Max SDM Statistic = ", maxSdmStatistic), + title = ~paste0("Max SDM Statistic = ", maxSdmStatistic), shapes = list(list( type = "line", x0 = 0, diff --git a/R/estimation-cohort-method-propensityModel.R b/R/estimation-cohort-method-propensityModel.R index 2084a96..070bf1c 100644 --- a/R/estimation-cohort-method-propensityModel.R +++ b/R/estimation-cohort-method-propensityModel.R @@ -67,7 +67,7 @@ cohortMethodPropensityModelServer <- function( databaseId = selectedRow()$databaseId, analysisId = selectedRow()$analysisId ) %>% - dplyr::mutate(absBeta = abs(coefficient)) + dplyr::mutate(absBeta = abs(.data$coefficient)) }) # ColorBrewer-inspired 3-color scale diff --git a/R/estimation-cohort-method-systematicError.R b/R/estimation-cohort-method-systematicError.R index d530322..b2fd49a 100644 --- a/R/estimation-cohort-method-systematicError.R +++ b/R/estimation-cohort-method-systematicError.R @@ -202,7 +202,7 @@ getCohortMethodControlResults <- function( } -plotCohortMethodScatter <- function(controlResults, ease) { +plotCohortMethodScatter <- function(controlResults, ease = NULL) { if(nrow(controlResults)==0){ return(NULL) diff --git a/tests/testthat/Rplots.pdf b/tests/testthat/Rplots.pdf new file mode 100644 index 0000000000000000000000000000000000000000..0caff5eaa592123cf01cc617f52d1a6b678b45a9 GIT binary patch literal 10146 zcma)C1z42Z)+Q7Lkq!xAL>gg&9J;%^r3M&U7`huNB?W0IL6GiLS~`_31tcY;!GF-> zIp-elz5ku(0cNjnt-aRXe9zkJefOeQk&t2ovvXq82P_Ay1Pld?88~5s0U&^bsWrBM z05(wE31)(TJJ?H@AYcF{2|fr2!U=*xKp?R%!rgClg02 zxS2CR*#+U~f<>mVhM8wa3B@b0Dl?q{AO^icdhLNvq$`)4itB=M<9pJ0Nx+wKsA`N zgNu_Haz4&~%y+HuYdaKR_Lc}M02s^-1^}htwg}`3fKs-|&5?kaIhez)<90?M_skC4 zJ#9co-eH9szhzUqe?%yuk0;NJsOt6&tAI%i&yRCKHmr?Urj*s`HS49jU+JUGS(BQ3 zYcNNs2XHK9d=Ij2%m(;NpX8jtPEZGVp9XP`e!u(Xa_CLyg0Xtj%=fb^jHGk1MR{Dr zERf^e)iqGC@p7uw<*WAI5|N`03EIwAkB1VVV|B1?gMVt5sEN)K!k9$d+zJJ!;e7MN ze)jo(eV_+Ov3v3JQ$jaWUpz5RhIV{7JVh0dVAc?LO2J@?ebBue=8^0f^`?R(o_&3= zW~dP+=o?sME@l81*kB23czY7oyX_i5i4iYcP*(ub-OB%(UO+<{=6Qy->PDt$8_N`= z-nV_Q3YrH8oSVEJEc*Jb^KAP)!@>g1#=T;)u+PuK2G;s4t)EvIU0gn{IPq!q@e~@T zDex%5=LsOdv9hDA=+KR(04E0uva4eUSiOB~_SrCT?#HE*-QpNJ^ z!GSLMVg^Dam9(Y|&O{TAV^DKf2FjN4K-n3kjGoX;GLax306k1Z!%*OcnrYx$m0E@8 z?QdP>$|3#OFPXYous4&Lp5#-!X4dRYqkq9?)ADTS(QZ|UDOJgesMWUe!#1|qB?>m0zJ=z zO=?BDL8ZNXZpZKKEHfje)jZ%sh9eh;;GV`~4mg$fJYMxRCE)m70jjr^-G@+itk%FLo zV8VaQy=CvbgT%jam7K4ZRp^vu&__A{qB}xm(ITwVqWWVA_0K*lw*KXe| zblZ=pC%>7B_s!1;b+)1d*Yc5h^pBMEM@EJInb3Y^)c=|w!Jz*yL;leCXNu(I3kvd1~Ia7JaOMe zYq__$MjgVKT@tH$doAZsNhdz95A(2#zbpJo){`d9ntp!4%}ma7hC4qrdO|ZWjyrPT z{b#ynlP06|3DhofxFMy=V@l)bc&%zwl3G-yn{aPR74V&p+&+dXaJX6RVlaPnT;e1G zonaPE+{8JDL*hnJ&lJ7Q`2ut&oWkCC#(@R#_F22EQCf2E2{A#D1gmhb+qV$-yW}31 z&iVM2D(z889YE}pszjFC`WmnHjq~u{S+F|4a#Fa-qve4Eac?5bTR8^9MjtBcO5Knj zRx4oXPDokfdEaA>*Hg`CY)H%XS|Gl*h)VTURT-&Qg{Bfqxi2x5-o0mDKo=nZo-746 zGpo71Jj*+>fNMeN;Qb|d*6XSliea}dB0tc zgfI0oeVi%cbw5muPYR^qD(wOEMV$dTzGOV_VRE8+4-wj-Nz|@*F~0gQ02XxP7agvM zTY6!gKF=Q41U-S2XQzE2KEuRl>u@~3LKPg*kghreybS1e2H1R{(tRRDIk3fO>xf$= z$64SE?w||XUEv-%de1sSMHrg$qy&r65 zzId{MS0o2U-x#6`k*%b;o0NmoUv>pB3#9L$+r&#WxO)=Pk+6EI&fjC{*}3|i*_^V` zl@ZKBg|Bb8RMuHFpujem64k2_08+PU;~QnJvmd7@zkg6lSzS{;5K3z*xK`F&r)JZ^ zdq70O%~6dJ^>tL^1E~6FS+3+-9>At*BB*ZDk)_Stl&tr_)wO~VIm)NHX_G&RwsNAb z;i75H_Elnn3n|SFRSagWmcrpFe5sr_iPqRlt?*-xj&Lh!Nh+iQ?|Zc9(s4cGH3lyY zYc^27#*uzuHI4H4^iwmet>%;B2Mfs`!@ZAlDbo!Eo23+PhVHIcx4lprl&bYf=9mhP zJvFsG)H7z^XKhZptLi|BR59Wy%=v)!{FUt?#pB|op+gFAqI-7Ehwv0%g;IhULd|HS z2N`l7rAi4NSf}r-a~lU$jMN)V>f&Cx7n+oO1I4g-fPar+CG zu?8!PD{`u>Y&GRl)b@To7o=BnqlpolHVRmC#*R0zmJ;XqOc1)@V^|x(zOk)4jnirZ zeSBqxUlf|~LO7td=dZecZXtlh}9 z2kfDj(tv#dp@ffwwh?Gpz=vRdFk5kzkS`7LehcV;UCmSPwOxG_#rZcEKA2g(GtsRM zC<1hRzC9K;Zm816G0tw;+?1X$U!9Ys{T(Y&#Z?wj5Z~Ti(nGk7eN8!qp2H^C1YHo(bZ)cf!B9!;^c=fQF*KeNHEdgz==qVq}z=MJcD1#>%P+9t+ zV3~mJa(iQjSz`Hs06NEx zJuQXipl(=G7$Vs8>5l5>db4)|3U#k5VHyl`RBxc9+A%M84-J%f@jvhIcgYazJse3S zc7rf-%iz5jHS4swKNwSX3-?ZuZA?Ya8`2wzuR1&MYJ1+i+r^DE-t6fcpshzJx$1sm zn%v?O#M!}TdQbI6PEb^%_SKk+;!_wa$W>Oj7Eh#Js_8k5qazk`)mvhs5cCVzy5WGZH$U`hQ zQFVH0A~djg}~4 zI8&PWm*5wiiAH?#jE9Djli-=*lOTJh6m}HKP$I=0_KKsjv#cRUo+sm5Ih5mgEEPK{ zX3DW4joA}uJk96Nb%eKT&+tO`?_2(Mo`e4aZ2#MVehsPA0RIK@fd2wr*uYijC4#FBU%@63S>`~@?dDD=OJ>m5Hiw z-Ckcr<*4izgdX?pg0gre@K+$ky8tbeY5DdZ&jw z$1Q#bJA}%UMd>W zJx5#T5BG=gDkr~YNZ&|sqL7pTy}!*#Jed4(b3Hhl_$!yL&sHw(&d`C}j>m-X4U%Rz zyqQ6KMP~jUKLk&Di&KenPRo?j8k-9V!SZla~s4VL^LWH0`Fy|$9yciI2GyQB1 zAx2OymW8{+7-D3O9eP&fmV*=o#)uWkW|O77!{2PLQojGj&|i=Y1!4sCa1YEIWhF0K zbsIZXb1x<$3P<(X=w3-Rb4$3zEzfz7{XSh?by&kE+CO}{ z4Aa^p(UrQnN+nIsJ;Rc{{5OxUQV9pzNWGtHcg5H=ggEH9vZ!L6=! zcF02LH!nO)^I&*vu!;rNDTd*rr*4(#kX=zfOvV3&FdKZIKZsLjgeh}vn#RLG$#b*_ z;dt*EsCvY9x+;TV>0Oa(77et9CrEXx%n;0O_R*x3)=s6}-yOVr)=jYUwN8*I4d4Of-XFjra@i*!W zFPg4ee6P@GJ^&wO+CRrsJuCg-q4Y(t03n>cMqN-?pIBP*?Vx?Guh(Gn3YF)%H^J{| z?V8y6i7NiLwDyy@`EP0MTH~KM1uf+*Wic*Y=pmUNA z2c?Sx`kqAhz#pLBJlo{=-g2tbE49)VF?kp=mGYD-j$@%;uZ{keyMJrL!c&@O2B4Xs ziX^Ptp&WBTj{VjrsZSsqPnwKYu}rW%N{W!1z~=2@A>!FGq-m%?ANxxSuKTa z>vqk(oH6psTA5Pz8ceSrquzdZq|~t8gwB_7S+zEs!oO{4c5ceC3w=tU*0p{Lth;5q z(^h^VbVoH|7E&St?JN!)pwwQ{GyD~E^nhUWRAp98x#zy|! zd>Xd`?uU)ne#}_BHw<=f=2XXYE1e<9JVJd;Fvh`VvHZ*sJNx^qIM-KR9Mi4lLsY8jc`ORW`}YYg=xPu@3k={6aNT(%N4=y1R}> z!W5v0bNLn!*&%{O?oEMHA#>+h4?>p~IgXTwYiEd)xuY?J1D2r$-`zRm-F-*$LEpcZ z6ouC4=)xT%NHmc{V$i1jV*Sl4B6Lvt&_`(AMdKJv`5TXZ-zHo?TT< zfA~u`h10+RwKRU+HJ){Bn(}uXjNSF|3B_a6K|<$=<>R|{Zs2%8L=GhtC!PQ@uwIfe z=Hi3Y#|O#7#oC&S1w8GY`$cRM_+VKOnvj)$VlRy6_!M}Va2y* zKit?+$72#VV-WYiXKNn&(p*g;+1`JL`TbsQo}I~LeZ1a_FI0?qhO<#^)FbQTIo}mF zX1}CYQQQ-h<_h2-H)LJ;^5U87WSE89BLa}gtf(OY=>Dv#^6B%h+gYV`k;BN}AD@?P zzbg17-{XqNbOJ6-R|twV(}6SXyfvbNAQ@2@uy#hwil?z)Qc(CRMIH3jt@reK{uI8OsY6YFqH@Iw8aCt!=wV2r4!c3Sqch#NUz?_5ZiCT z;bD}gjMiaEN!)dk`q=z-j!%58tX^Lwt%v#6SUWH`Rtc1z9TL72I;Fe4m05fv_34%8 zw;lEmTXRQPxX0g%9}_XP4Qzbq-oD)4dE6NEG&6JA@%yEP;ALiypRZ9ZlxxZ$!5K3^ zAk|qWO<{TGQHB3%>2F!{-zQCH08k!o?hMceT(je9fNKg!4M}7F{PUARH$*b)4lYQB z99iZm!pz|&Vh-*A{cG}v3&eT-WB50c{qLC+$>p1=!w>*{Ao4Z=nW|y#2t#b36p~;E z2nYbBAOJA;4?jq594P6IkXA=rUnU3$0D#i!U;y}MM9A+*#Xrb+=k(VC&$d?r386(}S~`v>1Tvm;1ji39d!gCxJdt zR$N@n#2ID|_z|SxuWN_v(XYct^qS|lzYZEG0ds|$!LBC-Dj}~Deig^akp4Z}b-iVO zUI?ToxoN0Rk%kR5^E9i(;YTD4+gPcg$=qp{iDhR2W8urSJwu`8me6pNP>s#M1z}qB z&k>I;r;P|fRW0AVK`t@=*pZkrN!GlCe4)u>cOZ3v=GfOJvw3LFa@S|F0p;06(9L%W zI#~WV**e5aYn|cIk(S1os5oCy&}~r`9V;uvNKd5DQqa6VM%ktioscy*-~vw1S;mB; z-lBZZOsLnT1*51WN3HFjOc{`q_3{d8r_t9c_a@hHDh`6=25EHzAzJay`w#WKk5XWG z&;v-Y0C}JD;4dPoa{Sr9@tRHVz{Q#rY}5;qD{+${U5 zv%0x0n^_zaB#>>z17%UB_tDo;pich~Q6FCCV80$aAzeW@IfH?EXmmVL9 zKM0p6`oS{zV+y%0)shp6#n6Q=v4yc}(5lZKT$*{Lqs1_3W&H zJZh#5GjM(PEECsH{E_#NTFcz-XA}2>c-}Y!Slo!m-oi6qqN8VU+3^%-H8bpl2J^~= znv~#zt|c6pASuz8uK-X;s@Crz3cr~m7AkU*`Qikx{VI2=KIzHy3BhoZ4qD!Q3K3sw z6ebn|0G5|I>+r76?JjBb(}Bp5l;rgDp};F2?K*|49#T5L7&B=JNFAZ-;MR)^Jv2@L zilhkoh6v?4I#Jt=nl^$u6ud=rG*PDT8;^~_i-E+?P$d9l#QxP;cM}3jj2T~HxMUG< z25~#yMFf~Fa`Ixb2lN@=m_=0s;b!!4D4U!6#7*Ljc5ks47Bqo>6{6zbQ_j zLX~ifUR+EDjYMQKOYId^QRqgt#k&4F6M~`v<&Jo5mZ}xu8Hp$60}xjJTfH&@+nbff z%DlH?g2~?YeuePTum{$*B|4&ewHa}z)2YnV7F>hvh3`e^b(25FC+NX4!m)<;k%53xIBSRI zqMjq8qqZYa9eESsJpOJJUgyErzCGB9lsBI5E#a8V`%FYpSZ{)5#8^z&vg3xOc;)Nl z-9_mLzlAGxIKK3+3)PVokPuL&qHm#Bm9e1XW)7gcZ+Cy2F`agfwiyuLD`k%7B%rG> zFJ{k>d4GYiRW*x6hvf#-S7I&JaV7+dfvS6cxHhN8p@uF_5lrVymP}?E!9~h2_4;v_ zaj6a64c2g(a8FJC@ACoZO%cdMbU;lClIWswPIpf!4 z(^S@M*X1eeRD3w^`4hM)!x&n{0@&k)aT&*MX^vxk>- zm-o(^&(tyaFz#dA#3;e2y|Wkku${QwF!VCCG&(BUG>ZGK3%MXfivt%l$YamdVk5@= zm`B%Q)Yxf&*z7$-kz>xza|(yMl1Co=8cYcZ8@ShhbG30GjBS`yiBv2SBa%{qa4bHh z-4+(3H_8^ocAKs7VWuv*PN%+I|mmAciK*}?0Q6t)jFT}RUf z`vwd3uh(3MeC#dlyK866+{QAjX-r$+wtTn>3d#xU$sRBn9ccrPluzzqM0R1D*;%B! ziSc_tOI-O@4=1PI>TY>|JS8K`mwzE2*_Y$db#QV(u@+swQSW51X_#k^Q!7#1Y_H~K z=oaG@bdHYagO?#4-yK{~Xj!x-I%H`yX+&F!Tl&G)@<{H8*`Z@*sIkLqIBc2dv--C4 zg7y&4RPBV@`=NPY>j1ulg5?bhjl2_=x6a-4vY=#S0t=lzc0A z-%-Z6=jd7E!JW0+Yi=Qd!~VnD*~jmq+LJyDO0*A^XxZha`vSWopi&ZujnlZW*%@Q|&IJh_P^@4wr7Tm7JB-<@?#Adf_$uVNHxa+B&@Q(GNLlKFYWoZ0XIE1As0-1Dzc)nlXGfl+`mJj!U*zW zB}qO0fPshaSSG_M1LR;_Keeye$GGov&}tN*_ttPkKTE%?#u$;e_Wn$BxG3+nr}kzk zyPjZ6m%~6nb#OJ@#*e9r{UOl1p54MwIaX`r#mn+B;0vvkw7j zW~eKgoiWX%dt;vSKi_InG0|47jVzO|kk=zOm@H*nTaFPl?X^`+f+$@fb@ zIJ(b3%)kKK3pQAZ-V=I7+`Avq>#P;a*kSoma5p)wg?0GbX6zZ1CBA3hUjImqeLL ztC?v+i7p#ozI+-pYnJ!iO?x8fTmo!z_-Z>mb+G0=l>X&-OW0%n+eP{9L9!SlbHlBM zPmYDoZN6D6nCCQn822#v!>Gah3r9HlD6)ot3QBI@=G;>N=D8)PBksZH_p9aZKsUd0B3_0T2}05aj!6{5FW+Y_^pv1w08R>2YA4Z_C(TV$o>|}gOL8mb5cZ2i(Pg8EK?iUac2|w4B z!QsVNY3id_tslRS?!a~t9}h3J$xAJao;RubIWMwp+I??Kb|d1b-!0!|6;AeDKfQan zw^It7>nxV@;oGyInT8z=#{ zuz(?ZUap&3^Z}e)Ks&g-i!;FRZ_PD7D)V1u?$7Ce)a^iZ7gNNKW}9mvve!k)#12{g zB5U~{PJimiz-(P%2)LOEvaJ6V(~o%n-i`C4y#K|y{IP&v7ywzVivqyxAQ0$p$l?bE z_-_UvcHVzA`0GCV&n^1PgP92c#17#C|83Dfki>uVfHe3K(%%jKBG~_v2M!SA?*@P8 z&wpF=kC2dS_?v;d6U+h|iDNjhk(=?y2f)q6#lZ!z0Q@Pt20hmwfc>8`FgFss{i}={ z1VzHAf5;%9-)y-#pugL4LXg1cUu{8<>+67j%Ami=z+4dI%lfZ+U~bTF^KtweJq~UV z5(fUOEhi5*5@r5FcHLF*4;d8v`@TRS*KhW}+Cn+Nzs(2b_Vi+