mirror of
https://github.com/msberends/AMR.git
synced 2025-05-03 15:03:49 +02:00
(v2.1.1.9268) WISCA vignette, antibiogram sorting, fix translations
This commit is contained in:
parent
5e6bbdf3d1
commit
2461631bce
@ -1,5 +1,5 @@
|
|||||||
Package: AMR
|
Package: AMR
|
||||||
Version: 2.1.1.9267
|
Version: 2.1.1.9268
|
||||||
Date: 2025-05-01
|
Date: 2025-05-01
|
||||||
Title: Antimicrobial Resistance Data Analysis
|
Title: Antimicrobial Resistance Data Analysis
|
||||||
Description: Functions to simplify and standardise antimicrobial resistance (AMR)
|
Description: Functions to simplify and standardise antimicrobial resistance (AMR)
|
||||||
|
2
NEWS.md
2
NEWS.md
@ -1,4 +1,4 @@
|
|||||||
# AMR 2.1.1.9267
|
# AMR 2.1.1.9268
|
||||||
|
|
||||||
*(this beta version will eventually become v3.0. We're happy to reach a new major milestone soon, which will be all about the new One Health support! Install this beta using [the instructions here](https://amr-for-r.org/#get-this-package).)*
|
*(this beta version will eventually become v3.0. We're happy to reach a new major milestone soon, which will be all about the new One Health support! Install this beta using [the instructions here](https://amr-for-r.org/#get-this-package).)*
|
||||||
|
|
||||||
|
@ -59,6 +59,7 @@
|
|||||||
#' @param minimum The minimum allowed number of available (tested) isolates. Any isolate count lower than `minimum` will return `NA` with a warning. The default number of `30` isolates is advised by the Clinical and Laboratory Standards Institute (CLSI) as best practice, see *Source*.
|
#' @param minimum The minimum allowed number of available (tested) isolates. Any isolate count lower than `minimum` will return `NA` with a warning. The default number of `30` isolates is advised by the Clinical and Laboratory Standards Institute (CLSI) as best practice, see *Source*.
|
||||||
#' @param combine_SI A [logical] to indicate whether all susceptibility should be determined by results of either S, SDD, or I, instead of only S (default is `TRUE`).
|
#' @param combine_SI A [logical] to indicate whether all susceptibility should be determined by results of either S, SDD, or I, instead of only S (default is `TRUE`).
|
||||||
#' @param sep A separating character for antimicrobial columns in combination antibiograms.
|
#' @param sep A separating character for antimicrobial columns in combination antibiograms.
|
||||||
|
#' @param sort_columns A [logical] to indicate whether the antimicrobial columns must be sorted on name.
|
||||||
#' @param wisca A [logical] to indicate whether a Weighted-Incidence Syndromic Combination Antibiogram (WISCA) must be generated (default is `FALSE`). This will use a Bayesian decision model to estimate regimen coverage probabilities using [Monte Carlo simulations](https://en.wikipedia.org/wiki/Monte_Carlo_method). Set `simulations`, `conf_interval`, and `interval_side` to adjust.
|
#' @param wisca A [logical] to indicate whether a Weighted-Incidence Syndromic Combination Antibiogram (WISCA) must be generated (default is `FALSE`). This will use a Bayesian decision model to estimate regimen coverage probabilities using [Monte Carlo simulations](https://en.wikipedia.org/wiki/Monte_Carlo_method). Set `simulations`, `conf_interval`, and `interval_side` to adjust.
|
||||||
#' @param simulations (for WISCA) a numerical value to set the number of Monte Carlo simulations.
|
#' @param simulations (for WISCA) a numerical value to set the number of Monte Carlo simulations.
|
||||||
#' @param conf_interval A numerical value to set confidence interval (default is `0.95`).
|
#' @param conf_interval A numerical value to set confidence interval (default is `0.95`).
|
||||||
@ -405,6 +406,7 @@ antibiogram <- function(x,
|
|||||||
minimum = 30,
|
minimum = 30,
|
||||||
combine_SI = TRUE,
|
combine_SI = TRUE,
|
||||||
sep = " + ",
|
sep = " + ",
|
||||||
|
sort_columns = TRUE,
|
||||||
wisca = FALSE,
|
wisca = FALSE,
|
||||||
simulations = 1000,
|
simulations = 1000,
|
||||||
conf_interval = 0.95,
|
conf_interval = 0.95,
|
||||||
@ -430,6 +432,7 @@ antibiogram.default <- function(x,
|
|||||||
minimum = 30,
|
minimum = 30,
|
||||||
combine_SI = TRUE,
|
combine_SI = TRUE,
|
||||||
sep = " + ",
|
sep = " + ",
|
||||||
|
sort_columns = TRUE,
|
||||||
wisca = FALSE,
|
wisca = FALSE,
|
||||||
simulations = 1000,
|
simulations = 1000,
|
||||||
conf_interval = 0.95,
|
conf_interval = 0.95,
|
||||||
@ -449,6 +452,7 @@ antibiogram.default <- function(x,
|
|||||||
deprecation_warning("antibiotics", "antimicrobials", fn = "antibiogram", is_argument = TRUE)
|
deprecation_warning("antibiotics", "antimicrobials", fn = "antibiogram", is_argument = TRUE)
|
||||||
antimicrobials <- list(...)$antibiotics
|
antimicrobials <- list(...)$antibiotics
|
||||||
}
|
}
|
||||||
|
meet_criteria(antimicrobials, allow_class = "character", allow_NA = FALSE, allow_NULL = FALSE)
|
||||||
if (!is.function(mo_transform)) {
|
if (!is.function(mo_transform)) {
|
||||||
meet_criteria(mo_transform, allow_class = "character", has_length = 1, is_in = c("name", "shortname", "gramstain", colnames(AMR::microorganisms)), allow_NULL = TRUE, allow_NA = TRUE)
|
meet_criteria(mo_transform, allow_class = "character", has_length = 1, is_in = c("name", "shortname", "gramstain", colnames(AMR::microorganisms)), allow_NULL = TRUE, allow_NA = TRUE)
|
||||||
}
|
}
|
||||||
@ -468,6 +472,7 @@ antibiogram.default <- function(x,
|
|||||||
meet_criteria(minimum, allow_class = c("numeric", "integer"), has_length = 1, is_positive_or_zero = TRUE, is_finite = TRUE)
|
meet_criteria(minimum, allow_class = c("numeric", "integer"), has_length = 1, is_positive_or_zero = TRUE, is_finite = TRUE)
|
||||||
meet_criteria(combine_SI, allow_class = "logical", has_length = 1)
|
meet_criteria(combine_SI, allow_class = "logical", has_length = 1)
|
||||||
meet_criteria(sep, allow_class = "character", has_length = 1)
|
meet_criteria(sep, allow_class = "character", has_length = 1)
|
||||||
|
meet_criteria(sort_columns, allow_class = "logical", has_length = 1)
|
||||||
meet_criteria(simulations, allow_class = c("numeric", "integer"), has_length = 1, is_finite = TRUE, is_positive = TRUE)
|
meet_criteria(simulations, allow_class = c("numeric", "integer"), has_length = 1, is_finite = TRUE, is_positive = TRUE)
|
||||||
meet_criteria(conf_interval, allow_class = c("numeric", "integer"), has_length = 1, is_finite = TRUE, is_positive = TRUE)
|
meet_criteria(conf_interval, allow_class = c("numeric", "integer"), has_length = 1, is_finite = TRUE, is_positive = TRUE)
|
||||||
meet_criteria(interval_side, allow_class = "character", has_length = 1, is_in = c("two-tailed", "left", "right"))
|
meet_criteria(interval_side, allow_class = "character", has_length = 1, is_in = c("two-tailed", "left", "right"))
|
||||||
@ -591,6 +596,8 @@ antibiogram.default <- function(x,
|
|||||||
)
|
)
|
||||||
colnames(out)[colnames(out) == "total"] <- "n_tested"
|
colnames(out)[colnames(out) == "total"] <- "n_tested"
|
||||||
colnames(out)[colnames(out) == "total_rows"] <- "n_total"
|
colnames(out)[colnames(out) == "total_rows"] <- "n_total"
|
||||||
|
out$ab <- factor(out$ab, levels = antimicrobials, ordered = TRUE)
|
||||||
|
out <- out[order(out$mo, out$ab), , drop = FALSE]
|
||||||
|
|
||||||
counts <- out
|
counts <- out
|
||||||
|
|
||||||
@ -824,7 +831,7 @@ antibiogram.default <- function(x,
|
|||||||
|
|
||||||
# transform names of antimicrobials
|
# transform names of antimicrobials
|
||||||
ab_naming_function <- function(x, t, l, s) {
|
ab_naming_function <- function(x, t, l, s) {
|
||||||
x <- strsplit(x, s, fixed = TRUE)
|
x <- strsplit(as.character(x), s, fixed = TRUE)
|
||||||
out <- character(length = length(x))
|
out <- character(length = length(x))
|
||||||
for (i in seq_along(x)) {
|
for (i in seq_along(x)) {
|
||||||
a <- x[[i]]
|
a <- x[[i]]
|
||||||
@ -869,6 +876,12 @@ antibiogram.default <- function(x,
|
|||||||
attr(out, "groups") <- NULL
|
attr(out, "groups") <- NULL
|
||||||
class(out) <- class(out)[!class(out) %in% c("grouped_df", "grouped_data")]
|
class(out) <- class(out)[!class(out) %in% c("grouped_df", "grouped_data")]
|
||||||
|
|
||||||
|
if (isTRUE(sort_columns)) {
|
||||||
|
sort_fn <- base::sort
|
||||||
|
} else {
|
||||||
|
sort_fn <- function(x) x
|
||||||
|
}
|
||||||
|
|
||||||
if (isTRUE(has_syndromic_group)) {
|
if (isTRUE(has_syndromic_group)) {
|
||||||
grps <- unique(out$syndromic_group)
|
grps <- unique(out$syndromic_group)
|
||||||
for (i in seq_along(grps)) {
|
for (i in seq_along(grps)) {
|
||||||
@ -886,25 +899,25 @@ antibiogram.default <- function(x,
|
|||||||
# sort rows
|
# sort rows
|
||||||
new_df <- new_df %pm>% pm_arrange(syndromic_group)
|
new_df <- new_df %pm>% pm_arrange(syndromic_group)
|
||||||
# sort columns
|
# sort columns
|
||||||
new_df <- new_df[, c("syndromic_group", sort(colnames(new_df)[colnames(new_df) != "syndromic_group"])), drop = FALSE]
|
new_df <- new_df[, c("syndromic_group", sort_fn(colnames(new_df)[colnames(new_df) != "syndromic_group"])), drop = FALSE]
|
||||||
colnames(new_df)[1] <- translate_AMR("Syndromic Group", language = language)
|
colnames(new_df)[1] <- translate_AMR("Syndromic Group", language = language)
|
||||||
} else {
|
} else {
|
||||||
# sort rows
|
# sort rows
|
||||||
new_df <- new_df %pm>% pm_arrange(mo, syndromic_group)
|
new_df <- new_df %pm>% pm_arrange(mo, syndromic_group)
|
||||||
# sort columns
|
# sort columns
|
||||||
new_df <- new_df[, c("syndromic_group", "mo", sort(colnames(new_df)[!colnames(new_df) %in% c("syndromic_group", "mo")])), drop = FALSE]
|
new_df <- new_df[, c("syndromic_group", "mo", sort_fn(colnames(new_df)[!colnames(new_df) %in% c("syndromic_group", "mo")])), drop = FALSE]
|
||||||
colnames(new_df)[1:2] <- translate_AMR(c("Syndromic Group", "Pathogen"), language = language)
|
colnames(new_df)[1:2] <- translate_AMR(c("Syndromic Group", "Pathogen"), language = language)
|
||||||
}
|
}
|
||||||
} else {
|
} else {
|
||||||
new_df <- long_to_wide(out)
|
new_df <- long_to_wide(out)
|
||||||
if (wisca == TRUE) {
|
if (wisca == TRUE) {
|
||||||
# sort columns
|
# sort columns
|
||||||
new_df <- new_df[, c(sort(colnames(new_df))), drop = FALSE]
|
new_df <- new_df[, c(sort_fn(colnames(new_df))), drop = FALSE]
|
||||||
} else {
|
} else {
|
||||||
# sort rows
|
# sort rows
|
||||||
new_df <- new_df %pm>% pm_arrange(mo)
|
new_df <- new_df %pm>% pm_arrange(mo)
|
||||||
# sort columns
|
# sort columns
|
||||||
new_df <- new_df[, c("mo", sort(colnames(new_df)[colnames(new_df) != "mo"])), drop = FALSE]
|
new_df <- new_df[, c("mo", sort_fn(colnames(new_df)[colnames(new_df) != "mo"])), drop = FALSE]
|
||||||
colnames(new_df)[1] <- translate_AMR("Pathogen", language = language)
|
colnames(new_df)[1] <- translate_AMR("Pathogen", language = language)
|
||||||
}
|
}
|
||||||
}
|
}
|
||||||
@ -966,6 +979,7 @@ antibiogram.grouped_df <- function(x,
|
|||||||
minimum = 30,
|
minimum = 30,
|
||||||
combine_SI = TRUE,
|
combine_SI = TRUE,
|
||||||
sep = " + ",
|
sep = " + ",
|
||||||
|
sort_columns = TRUE,
|
||||||
wisca = FALSE,
|
wisca = FALSE,
|
||||||
simulations = 1000,
|
simulations = 1000,
|
||||||
conf_interval = 0.95,
|
conf_interval = 0.95,
|
||||||
@ -1008,6 +1022,7 @@ antibiogram.grouped_df <- function(x,
|
|||||||
minimum = minimum,
|
minimum = minimum,
|
||||||
combine_SI = combine_SI,
|
combine_SI = combine_SI,
|
||||||
sep = sep,
|
sep = sep,
|
||||||
|
sort_columns = sort_columns,
|
||||||
wisca = wisca,
|
wisca = wisca,
|
||||||
simulations = simulations,
|
simulations = simulations,
|
||||||
conf_interval = conf_interval,
|
conf_interval = conf_interval,
|
||||||
@ -1084,6 +1099,7 @@ wisca <- function(x,
|
|||||||
language = get_AMR_locale(),
|
language = get_AMR_locale(),
|
||||||
combine_SI = TRUE,
|
combine_SI = TRUE,
|
||||||
sep = " + ",
|
sep = " + ",
|
||||||
|
sort_columns = TRUE,
|
||||||
simulations = 1000,
|
simulations = 1000,
|
||||||
conf_interval = 0.95,
|
conf_interval = 0.95,
|
||||||
interval_side = "two-tailed",
|
interval_side = "two-tailed",
|
||||||
@ -1103,6 +1119,7 @@ wisca <- function(x,
|
|||||||
language = language,
|
language = language,
|
||||||
combine_SI = combine_SI,
|
combine_SI = combine_SI,
|
||||||
sep = sep,
|
sep = sep,
|
||||||
|
sort_columns = sort_columns,
|
||||||
wisca = TRUE,
|
wisca = TRUE,
|
||||||
simulations = simulations,
|
simulations = simulations,
|
||||||
conf_interval = conf_interval,
|
conf_interval = conf_interval,
|
||||||
@ -1143,8 +1160,8 @@ simulate_coverage <- function(params) {
|
|||||||
n_pathogens <- length(params$gamma_posterior)
|
n_pathogens <- length(params$gamma_posterior)
|
||||||
|
|
||||||
# random draws per pathogen
|
# random draws per pathogen
|
||||||
random_incidence <- runif(n = n_pathogens)
|
random_incidence <- stats::runif(n = n_pathogens)
|
||||||
random_susceptibility <- runif(n = n_pathogens)
|
random_susceptibility <- stats::runif(n = n_pathogens)
|
||||||
|
|
||||||
simulated_incidence <- stats::qgamma(
|
simulated_incidence <- stats::qgamma(
|
||||||
p = random_incidence,
|
p = random_incidence,
|
||||||
|
@ -203,7 +203,25 @@ translate_into_language <- function(from,
|
|||||||
df_trans <- TRANSLATIONS # internal data file
|
df_trans <- TRANSLATIONS # internal data file
|
||||||
from.bak <- from
|
from.bak <- from
|
||||||
from_unique <- unique(from)
|
from_unique <- unique(from)
|
||||||
from_unique_translated <- from_unique
|
from_split_combined <- function(vec) {
|
||||||
|
sapply(vec, function(x) {
|
||||||
|
if (grepl("/", x, fixed = TRUE)) {
|
||||||
|
parts <- strsplit(x, "/", fixed = TRUE)[[1]]
|
||||||
|
# Translate each part separately
|
||||||
|
translated_parts <- translate_into_language(
|
||||||
|
parts,
|
||||||
|
language = lang,
|
||||||
|
only_unknown = only_unknown,
|
||||||
|
only_affect_ab_names = only_affect_ab_names,
|
||||||
|
only_affect_mo_names = only_affect_mo_names
|
||||||
|
)
|
||||||
|
paste(translated_parts, collapse = "/")
|
||||||
|
} else {
|
||||||
|
x
|
||||||
|
}
|
||||||
|
}, USE.NAMES = FALSE)
|
||||||
|
}
|
||||||
|
from_unique_translated <- from_split_combined(from_unique)
|
||||||
|
|
||||||
# only keep lines where translation is available for this language
|
# only keep lines where translation is available for this language
|
||||||
df_trans <- df_trans[which(!is.na(df_trans[, lang, drop = TRUE])), , drop = FALSE]
|
df_trans <- df_trans[which(!is.na(df_trans[, lang, drop = TRUE])), , drop = FALSE]
|
||||||
|
@ -23,16 +23,17 @@ antibiogram(x, antimicrobials = where(is.sir), mo_transform = "shortname",
|
|||||||
only_all_tested = FALSE, digits = ifelse(wisca, 1, 0),
|
only_all_tested = FALSE, digits = ifelse(wisca, 1, 0),
|
||||||
formatting_type = getOption("AMR_antibiogram_formatting_type",
|
formatting_type = getOption("AMR_antibiogram_formatting_type",
|
||||||
ifelse(wisca, 14, 18)), col_mo = NULL, language = get_AMR_locale(),
|
ifelse(wisca, 14, 18)), col_mo = NULL, language = get_AMR_locale(),
|
||||||
minimum = 30, combine_SI = TRUE, sep = " + ", wisca = FALSE,
|
minimum = 30, combine_SI = TRUE, sep = " + ", sort_columns = TRUE,
|
||||||
simulations = 1000, conf_interval = 0.95, interval_side = "two-tailed",
|
wisca = FALSE, simulations = 1000, conf_interval = 0.95,
|
||||||
info = interactive(), ...)
|
interval_side = "two-tailed", info = interactive(), ...)
|
||||||
|
|
||||||
wisca(x, antimicrobials = where(is.sir), ab_transform = "name",
|
wisca(x, antimicrobials = where(is.sir), ab_transform = "name",
|
||||||
syndromic_group = NULL, only_all_tested = FALSE, digits = 1,
|
syndromic_group = NULL, only_all_tested = FALSE, digits = 1,
|
||||||
formatting_type = getOption("AMR_antibiogram_formatting_type", 14),
|
formatting_type = getOption("AMR_antibiogram_formatting_type", 14),
|
||||||
col_mo = NULL, language = get_AMR_locale(), combine_SI = TRUE,
|
col_mo = NULL, language = get_AMR_locale(), combine_SI = TRUE,
|
||||||
sep = " + ", simulations = 1000, conf_interval = 0.95,
|
sep = " + ", sort_columns = TRUE, simulations = 1000,
|
||||||
interval_side = "two-tailed", info = interactive(), ...)
|
conf_interval = 0.95, interval_side = "two-tailed",
|
||||||
|
info = interactive(), ...)
|
||||||
|
|
||||||
retrieve_wisca_parameters(wisca_model, ...)
|
retrieve_wisca_parameters(wisca_model, ...)
|
||||||
|
|
||||||
@ -90,6 +91,8 @@ retrieve_wisca_parameters(wisca_model, ...)
|
|||||||
|
|
||||||
\item{sep}{A separating character for antimicrobial columns in combination antibiograms.}
|
\item{sep}{A separating character for antimicrobial columns in combination antibiograms.}
|
||||||
|
|
||||||
|
\item{sort_columns}{A \link{logical} to indicate whether the antimicrobial columns must be sorted on name.}
|
||||||
|
|
||||||
\item{wisca}{A \link{logical} to indicate whether a Weighted-Incidence Syndromic Combination Antibiogram (WISCA) must be generated (default is \code{FALSE}). This will use a Bayesian decision model to estimate regimen coverage probabilities using \href{https://en.wikipedia.org/wiki/Monte_Carlo_method}{Monte Carlo simulations}. Set \code{simulations}, \code{conf_interval}, and \code{interval_side} to adjust.}
|
\item{wisca}{A \link{logical} to indicate whether a Weighted-Incidence Syndromic Combination Antibiogram (WISCA) must be generated (default is \code{FALSE}). This will use a Bayesian decision model to estimate regimen coverage probabilities using \href{https://en.wikipedia.org/wiki/Monte_Carlo_method}{Monte Carlo simulations}. Set \code{simulations}, \code{conf_interval}, and \code{interval_side} to adjust.}
|
||||||
|
|
||||||
\item{simulations}{(for WISCA) a numerical value to set the number of Monte Carlo simulations.}
|
\item{simulations}{(for WISCA) a numerical value to set the number of Monte Carlo simulations.}
|
||||||
|
@ -33,7 +33,7 @@ test_that("test-ab_property.R", {
|
|||||||
ab_reset_session()
|
ab_reset_session()
|
||||||
|
|
||||||
expect_identical(ab_name("AMX", language = NULL), "Amoxicillin")
|
expect_identical(ab_name("AMX", language = NULL), "Amoxicillin")
|
||||||
expect_identical(ab_atc("AMX"), "J01CA04")
|
expect_identical(ab_atc("AMX"), c("J01CA04", "QG51AA03", "QJ01CA04"))
|
||||||
expect_identical(ab_cid("AMX"), as.integer(33613))
|
expect_identical(ab_cid("AMX"), as.integer(33613))
|
||||||
|
|
||||||
expect_inherits(ab_tradenames("AMX"), "character")
|
expect_inherits(ab_tradenames("AMX"), "character")
|
||||||
|
@ -35,8 +35,8 @@ test_that("test-atc_online.R", {
|
|||||||
AMR:::pkg_is_available("xml2") &&
|
AMR:::pkg_is_available("xml2") &&
|
||||||
tryCatch(curl::has_internet(), error = function(e) FALSE)) {
|
tryCatch(curl::has_internet(), error = function(e) FALSE)) {
|
||||||
expect_true(length(atc_online_groups(ab_atc("AMX"))) >= 1)
|
expect_true(length(atc_online_groups(ab_atc("AMX"))) >= 1)
|
||||||
expect_equal(atc_online_ddd(ab_atc("AMX"), administration = "O"), 1.5)
|
expect_equal(atc_online_ddd(ab_atc("AMX", only_first = TRUE), administration = "O"), 1.5)
|
||||||
expect_equal(atc_online_ddd(ab_atc("AMX"), administration = "P"), 3)
|
expect_equal(atc_online_ddd(ab_atc("AMX", only_first = TRUE), administration = "P"), 3)
|
||||||
expect_equal(atc_online_ddd_units("AMX", administration = "P"), "g")
|
expect_equal(atc_online_ddd_units("AMX", administration = "P"), "g")
|
||||||
}
|
}
|
||||||
})
|
})
|
||||||
|
@ -34,7 +34,6 @@ test_that("test-data.R", {
|
|||||||
expect_identical(nrow(microorganisms), length(unique(microorganisms$mo)))
|
expect_identical(nrow(microorganisms), length(unique(microorganisms$mo)))
|
||||||
expect_identical(class(microorganisms$mo), c("mo", "character"))
|
expect_identical(class(microorganisms$mo), c("mo", "character"))
|
||||||
expect_identical(nrow(antimicrobials), length(unique(AMR::antimicrobials$ab)))
|
expect_identical(nrow(antimicrobials), length(unique(AMR::antimicrobials$ab)))
|
||||||
expect_true(all(is.na(AMR::antimicrobials$atc[duplicated(AMR::antimicrobials$atc)])))
|
|
||||||
expect_identical(class(AMR::antimicrobials$ab), c("ab", "character"))
|
expect_identical(class(AMR::antimicrobials$ab), c("ab", "character"))
|
||||||
|
|
||||||
|
|
||||||
|
@ -1,11 +1,11 @@
|
|||||||
---
|
---
|
||||||
title: "How to conduct AMR data analysis"
|
title: "Conduct AMR data analysis"
|
||||||
output:
|
output:
|
||||||
rmarkdown::html_vignette:
|
rmarkdown::html_vignette:
|
||||||
toc: true
|
toc: true
|
||||||
toc_depth: 3
|
toc_depth: 3
|
||||||
vignette: >
|
vignette: >
|
||||||
%\VignetteIndexEntry{How to conduct AMR data analysis}
|
%\VignetteIndexEntry{Conduct AMR data analysis}
|
||||||
%\VignetteEncoding{UTF-8}
|
%\VignetteEncoding{UTF-8}
|
||||||
%\VignetteEngine{knitr::rmarkdown}
|
%\VignetteEngine{knitr::rmarkdown}
|
||||||
editor_options:
|
editor_options:
|
||||||
|
@ -22,7 +22,7 @@ knitr::opts_chunk$set(
|
|||||||
)
|
)
|
||||||
```
|
```
|
||||||
|
|
||||||
> This page was entirely written by our [AMR for R Assistant](https://chat.amr-for-r.org), a ChatGPT manually-trained model able to answer any question about the AMR package.
|
> This page was entirely written by our [AMR for R Assistant](https://chat.amr-for-r.org), a ChatGPT manually-trained model able to answer any question about the `AMR` package.
|
||||||
|
|
||||||
Antimicrobial resistance (AMR) is a global health crisis, and understanding resistance patterns is crucial for managing effective treatments. The `AMR` R package provides robust tools for analysing AMR data, including convenient antimicrobial selector functions like `aminoglycosides()` and `betalactams()`.
|
Antimicrobial resistance (AMR) is a global health crisis, and understanding resistance patterns is crucial for managing effective treatments. The `AMR` R package provides robust tools for analysing AMR data, including convenient antimicrobial selector functions like `aminoglycosides()` and `betalactams()`.
|
||||||
|
|
||||||
|
@ -1,11 +1,11 @@
|
|||||||
---
|
---
|
||||||
title: "How to apply EUCAST rules"
|
title: "Apply EUCAST rules"
|
||||||
output:
|
output:
|
||||||
rmarkdown::html_vignette:
|
rmarkdown::html_vignette:
|
||||||
toc: true
|
toc: true
|
||||||
toc_depth: 3
|
toc_depth: 3
|
||||||
vignette: >
|
vignette: >
|
||||||
%\VignetteIndexEntry{How to apply EUCAST rules}
|
%\VignetteIndexEntry{Apply EUCAST rules}
|
||||||
%\VignetteEncoding{UTF-8}
|
%\VignetteEncoding{UTF-8}
|
||||||
%\VignetteEngine{knitr::rmarkdown}
|
%\VignetteEngine{knitr::rmarkdown}
|
||||||
editor_options:
|
editor_options:
|
||||||
|
@ -1,10 +1,10 @@
|
|||||||
---
|
---
|
||||||
title: "How to determine multi-drug resistance (MDR)"
|
title: "Determine multi-drug resistance (MDR)"
|
||||||
output:
|
output:
|
||||||
rmarkdown::html_vignette:
|
rmarkdown::html_vignette:
|
||||||
toc: true
|
toc: true
|
||||||
vignette: >
|
vignette: >
|
||||||
%\VignetteIndexEntry{How to determine multi-drug resistance (MDR)}
|
%\VignetteIndexEntry{Determine multi-drug resistance (MDR)}
|
||||||
%\VignetteEncoding{UTF-8}
|
%\VignetteEncoding{UTF-8}
|
||||||
%\VignetteEngine{knitr::rmarkdown}
|
%\VignetteEngine{knitr::rmarkdown}
|
||||||
editor_options:
|
editor_options:
|
||||||
|
@ -1,11 +1,11 @@
|
|||||||
---
|
---
|
||||||
title: "How to conduct principal component analysis (PCA) for AMR"
|
title: "Conduct principal component analysis (PCA) for AMR"
|
||||||
output:
|
output:
|
||||||
rmarkdown::html_vignette:
|
rmarkdown::html_vignette:
|
||||||
toc: true
|
toc: true
|
||||||
toc_depth: 3
|
toc_depth: 3
|
||||||
vignette: >
|
vignette: >
|
||||||
%\VignetteIndexEntry{How to conduct principal component analysis (PCA) for AMR}
|
%\VignetteIndexEntry{Conduct principal component analysis (PCA) for AMR}
|
||||||
%\VignetteEncoding{UTF-8}
|
%\VignetteEncoding{UTF-8}
|
||||||
%\VignetteEngine{knitr::rmarkdown}
|
%\VignetteEngine{knitr::rmarkdown}
|
||||||
editor_options:
|
editor_options:
|
||||||
|
@ -1,11 +1,11 @@
|
|||||||
---
|
---
|
||||||
title: "How to work with WHONET data"
|
title: "Work with WHONET data"
|
||||||
output:
|
output:
|
||||||
rmarkdown::html_vignette:
|
rmarkdown::html_vignette:
|
||||||
toc: true
|
toc: true
|
||||||
toc_depth: 3
|
toc_depth: 3
|
||||||
vignette: >
|
vignette: >
|
||||||
%\VignetteIndexEntry{How to work with WHONET data}
|
%\VignetteIndexEntry{Work with WHONET data}
|
||||||
%\VignetteEncoding{UTF-8}
|
%\VignetteEncoding{UTF-8}
|
||||||
%\VignetteEngine{knitr::rmarkdown}
|
%\VignetteEngine{knitr::rmarkdown}
|
||||||
editor_options:
|
editor_options:
|
||||||
|
@ -22,202 +22,187 @@ knitr::opts_chunk$set(
|
|||||||
)
|
)
|
||||||
```
|
```
|
||||||
|
|
||||||
|
> This explainer was largely written by our [AMR for R Assistant](https://chat.amr-for-r.org), a ChatGPT manually-trained model able to answer any question about the `AMR` package.
|
||||||
|
|
||||||
## Introduction
|
## Introduction
|
||||||
|
|
||||||
Clinical guidelines for empirical antimicrobial therapy require *probabilistic reasoning*: what is the chance that a regimen will cover the likely infecting organisms, before culture results are available?
|
Clinical guidelines for empirical antimicrobial therapy require *probabilistic reasoning*: what is the chance that a regimen will cover the likely infecting organisms, before culture results are available?
|
||||||
|
|
||||||
This is the purpose of **WISCA**, or:
|
This is the purpose of **WISCA**, or **Weighted-Incidence Syndromic Combination Antibiogram**.
|
||||||
|
|
||||||
> **Weighted-Incidence Syndromic Combination Antibiogram**
|
|
||||||
|
|
||||||
WISCA is a Bayesian approach that integrates:
|
WISCA is a Bayesian approach that integrates:
|
||||||
|
|
||||||
- **Pathogen prevalence** (how often each species causes the syndrome),
|
- **Pathogen prevalence** (how often each species causes the syndrome),
|
||||||
- **Regimen susceptibility** (how often a regimen works *if* the pathogen is known),
|
- **Regimen susceptibility** (how often a regimen works *if* the pathogen is known),
|
||||||
|
|
||||||
to estimate the **overall empirical coverage** of antimicrobial regimens — with quantified uncertainty.
|
to estimate the **overall empirical coverage** of antimicrobial regimens, with quantified uncertainty.
|
||||||
|
|
||||||
This vignette explains how WISCA works, why it is useful, and how to apply it in **AMR**.
|
This vignette explains how WISCA works, why it is useful, and how to apply it using the `AMR` package.
|
||||||
|
|
||||||
---
|
|
||||||
|
|
||||||
## Why traditional antibiograms fall short
|
## Why traditional antibiograms fall short
|
||||||
|
|
||||||
A standard antibiogram gives you:
|
A standard antibiogram gives you:
|
||||||
|
|
||||||
``` Species → Antibiotic → Susceptibility %
|
```
|
||||||
|
Species → Antibiotic → Susceptibility %
|
||||||
|
```
|
||||||
|
|
||||||
But clinicians don’t know the species *a priori*. They need to choose a regimen that covers the **likely pathogens** — without knowing which one is present.
|
But clinicians don’t know the species *a priori*. They need to choose a regimen that covers the **likely pathogens**, without knowing which one is present.
|
||||||
|
|
||||||
|
Traditional antibiograms calculate the susceptibility % as just the number of resistant isolates divided by the total number of tested isolates. Therefore, traditional antibiograms:
|
||||||
|
|
||||||
Traditional antibiograms:
|
|
||||||
- Fragment information by organism,
|
- Fragment information by organism,
|
||||||
- Do not weight by real-world prevalence,
|
- Do not weight by real-world prevalence,
|
||||||
- Do not account for combination therapy or sample size,
|
- Do not account for combination therapy or sample size,
|
||||||
- Do not provide uncertainty.
|
- Do not provide uncertainty.
|
||||||
|
|
||||||
---
|
|
||||||
|
|
||||||
## The idea of WISCA
|
## The idea of WISCA
|
||||||
|
|
||||||
WISCA asks:
|
WISCA asks:
|
||||||
|
|
||||||
> “What is the **probability** that this regimen **will cover** the pathogen, given the syndrome?”
|
> "What is the **probability** that this regimen **will cover** the pathogen, given the syndrome?"
|
||||||
|
|
||||||
This means combining two things:
|
This means combining two things:
|
||||||
|
|
||||||
- **Incidence** of each pathogen in the syndrome,
|
- **Incidence** of each pathogen in the syndrome,
|
||||||
- **Susceptibility** of each pathogen to the regimen.
|
- **Susceptibility** of each pathogen to the regimen.
|
||||||
|
|
||||||
We can write this as:
|
We can write this as:
|
||||||
|
|
||||||
``` coverage = ∑ (pathogen incidence × susceptibility)
|
$$\text{Coverage} = \sum_i (\text{Incidence}_i \times \text{Susceptibility}_i)$$
|
||||||
|
|
||||||
For example, suppose:
|
For example, suppose:
|
||||||
- E. coli causes 60% of cases, and 90% of *E. coli* are susceptible to a drug.
|
|
||||||
- Klebsiella causes 40% of cases, and 70% of *Klebsiella* are susceptible.
|
- *E. coli* causes 60% of cases, and 90% of *E. coli* are susceptible to a drug.
|
||||||
|
- *Klebsiella* causes 40% of cases, and 70% of *Klebsiella* are susceptible.
|
||||||
|
|
||||||
Then:
|
Then:
|
||||||
|
|
||||||
``` coverage = (0.6 × 0.9) + (0.4 × 0.7) = 0.82
|
$$\text{Coverage} = (0.6 \times 0.9) + (0.4 \times 0.7) = 0.82$$
|
||||||
|
|
||||||
But in real data, incidence and susceptibility are **estimated from samples** — so they carry uncertainty. WISCA models this **probabilistically**, using conjugate Bayesian distributions.
|
But in real data, incidence and susceptibility are **estimated from samples**, so they carry uncertainty. WISCA models this **probabilistically**, using conjugate Bayesian distributions.
|
||||||
|
|
||||||
---
|
|
||||||
|
|
||||||
## The Bayesian engine behind WISCA
|
## The Bayesian engine behind WISCA
|
||||||
|
|
||||||
### Pathogen incidence
|
### Pathogen incidence
|
||||||
|
|
||||||
Let:
|
Let:
|
||||||
- K be the number of pathogens,
|
|
||||||
- ``` α = (1, 1, ..., 1) be a **Dirichlet** prior (uniform),
|
|
||||||
- ``` n = (n₁, ..., nₖ) be the observed counts per species.
|
|
||||||
|
|
||||||
Then the posterior incidence follows:
|
- $K$ be the number of pathogens,
|
||||||
|
- $\alpha = (1, 1, \ldots, 1)$ be a **Dirichlet** prior (uniform),
|
||||||
|
- $n = (n_1, \ldots, n_K)$ be the observed counts per species.
|
||||||
|
|
||||||
``` incidence ∼ Dirichlet(α + n)
|
Then the posterior incidence is:
|
||||||
|
|
||||||
In simulations, we draw from this posterior using:
|
$$p \sim \text{Dirichlet}(\alpha_1 + n_1, \ldots, \alpha_K + n_K)$$
|
||||||
|
|
||||||
``` xᵢ ∼ Gamma(αᵢ + nᵢ, 1)
|
To simulate from this, we use:
|
||||||
|
|
||||||
``` incidenceᵢ = xᵢ / ∑ xⱼ
|
$$x_i \sim \text{Gamma}(\alpha_i + n_i,\ 1), \quad p_i = \frac{x_i}{\sum_{j=1}^{K} x_j}$$
|
||||||
|
|
||||||
---
|
|
||||||
|
|
||||||
### Susceptibility
|
### Susceptibility
|
||||||
|
|
||||||
Each pathogen–regimen pair has:
|
Each pathogen–regimen pair has a prior and data:
|
||||||
- ``` prior: Beta(1, 1)
|
|
||||||
- ``` data: S susceptible out of N tested
|
|
||||||
|
|
||||||
Then:
|
- Prior: $\text{Beta}(\alpha_0, \beta_0)$, with default $\alpha_0 = \beta_0 = 1$
|
||||||
|
- Data: $S$ susceptible out of $N$ tested
|
||||||
|
|
||||||
``` susceptibility ∼ Beta(1 + S, 1 + (N - S))
|
The $S$ category could also include values SDD (susceptible, dose-dependent) and I (intermediate [CLSI], or susceptible, increased exposure [EUCAST]).
|
||||||
|
|
||||||
In each simulation, we draw random susceptibility per species from this Beta distribution.
|
Then the posterior is:
|
||||||
|
|
||||||
---
|
$$\theta \sim \text{Beta}(\alpha_0 + S,\ \beta_0 + N - S)$$
|
||||||
|
|
||||||
### Final coverage estimate
|
### Final coverage estimate
|
||||||
|
|
||||||
Putting it together:
|
Putting it together:
|
||||||
|
|
||||||
``` For each simulation:
|
1. Simulate pathogen incidence: $\boldsymbol{p} \sim \text{Dirichlet}$
|
||||||
- Draw incidence ∼ Dirichlet
|
2. Simulate susceptibility: $\theta_i \sim \text{Beta}(1 + S_i,\ 1 + R_i)$
|
||||||
- Draw susceptibility ∼ Beta
|
3. Combine:
|
||||||
- Multiply → coverage estimate
|
|
||||||
|
|
||||||
We repeat this (e.g. 1000×) and summarise:
|
$$\text{Coverage} = \sum_{i=1}^{K} p_i \cdot \theta_i$$
|
||||||
- **Mean**: expected coverage
|
|
||||||
- **Quantiles**: credible interval (default 95%)
|
|
||||||
|
|
||||||
---
|
Repeat this simulation (e.g. 1000×) and summarise:
|
||||||
|
|
||||||
## Practical use in AMR
|
- **Mean** = expected coverage
|
||||||
|
- **Quantiles** = credible interval
|
||||||
|
|
||||||
### Simulate a synthetic syndrome
|
## Practical use in the `AMR` package
|
||||||
|
|
||||||
|
### Prepare data and simulate synthetic syndrome
|
||||||
|
|
||||||
```{r}
|
```{r}
|
||||||
library(AMR)
|
library(AMR)
|
||||||
data <- example_isolates
|
data <- example_isolates
|
||||||
|
|
||||||
# Add a fake syndrome column for stratification
|
# Structure of our data
|
||||||
data$syndrome <- ifelse(data$mo %like% "coli", "UTI", "Other")
|
data
|
||||||
|
|
||||||
|
# Add a fake syndrome column
|
||||||
|
data$syndrome <- ifelse(data$mo %like% "coli", "UTI", "No UTI")
|
||||||
```
|
```
|
||||||
|
|
||||||
### Basic WISCA antibiogram
|
### Basic WISCA antibiogram
|
||||||
|
|
||||||
```{r}
|
```{r}
|
||||||
antibiogram(data,
|
wisca(data,
|
||||||
wisca = TRUE)
|
antimicrobials = c("AMC", "CIP", "GEN"))
|
||||||
|
```
|
||||||
|
|
||||||
|
### Use combination regimens
|
||||||
|
|
||||||
|
```{r}
|
||||||
|
wisca(data,
|
||||||
|
antimicrobials = c("AMC", "AMC + CIP", "AMC + GEN"))
|
||||||
```
|
```
|
||||||
|
|
||||||
### Stratify by syndrome
|
### Stratify by syndrome
|
||||||
|
|
||||||
```{r}
|
```{r}
|
||||||
antibiogram(data,
|
wisca(data,
|
||||||
syndromic_group = "syndrome",
|
antimicrobials = c("AMC", "AMC + CIP", "AMC + GEN"),
|
||||||
wisca = TRUE)
|
syndromic_group = "syndrome")
|
||||||
```
|
```
|
||||||
|
|
||||||
### Use combination regimens
|
The `AMR` package is available in `r length(AMR:::LANGUAGES_SUPPORTED)` languages, which can all be used for the `wisca()` function too:
|
||||||
|
|
||||||
The `antibiogram()` function supports combination regimens:
|
|
||||||
|
|
||||||
```{r}
|
```{r}
|
||||||
antibiogram(data,
|
wisca(data,
|
||||||
antimicrobials = c("AMC", "GEN", "AMC + GEN", "CIP"),
|
antimicrobials = c("AMC", "AMC + CIP", "AMC + GEN"),
|
||||||
wisca = TRUE)
|
syndromic_group = gsub("UTI", "UCI", data$syndrome),
|
||||||
|
language = "Spanish")
|
||||||
```
|
```
|
||||||
|
|
||||||
---
|
|
||||||
|
|
||||||
## Interpretation
|
## Sensible defaults, which can be customised
|
||||||
|
|
||||||
Suppose you get this output:
|
- `simulations = 1000`: number of Monte Carlo draws
|
||||||
|
- `conf_interval = 0.95`: coverage interval width
|
||||||
| Regimen | Coverage | Lower_CI | Upper_CI |
|
- `combine_SI = TRUE`: count "I" and "SDD" as susceptible
|
||||||
|-------------|----------|----------|----------|
|
|
||||||
| AMC | 0.72 | 0.65 | 0.78 |
|
|
||||||
| AMC + GEN | 0.88 | 0.83 | 0.93 |
|
|
||||||
|
|
||||||
Interpretation:
|
|
||||||
|
|
||||||
> *“AMC + GEN covers 88% of expected pathogens for this syndrome, with 95% certainty that the true coverage lies between 83% and 93%.”*
|
|
||||||
|
|
||||||
Regimens with few tested isolates will show **wider intervals**.
|
|
||||||
|
|
||||||
---
|
|
||||||
|
|
||||||
## Sensible defaults, but you can customise
|
|
||||||
|
|
||||||
- `minimum = 30`: exclude regimens with <30 isolates tested.
|
|
||||||
- `simulations = 1000`: number of Monte Carlo samples.
|
|
||||||
- `conf_interval = 0.95`: coverage interval width.
|
|
||||||
- `combine_SI = TRUE`: count “I”/“SDD” as susceptible.
|
|
||||||
|
|
||||||
---
|
|
||||||
|
|
||||||
## Limitations
|
## Limitations
|
||||||
|
|
||||||
- WISCA does not model time trends or temporal resistance shifts.
|
- It assumes your data are representative
|
||||||
- It assumes data are representative of current clinical practice.
|
- No adjustment for patient-level covariates, although these could be passed onto the `syndromic_group` argument
|
||||||
- It does not account for patient-level covariates (yet).
|
- WISCA does not model resistance over time, you might want to use `tidymodels` for that, for which we [wrote a basic introduction](https://amr-for-r.org/articles/AMR_with_tidymodels.html)
|
||||||
- Species-specific data are abstracted into syndrome-level estimates.
|
|
||||||
|
|
||||||
---
|
## Summary
|
||||||
|
|
||||||
|
WISCA enables:
|
||||||
|
|
||||||
|
- Empirical regimen comparison,
|
||||||
|
- Syndrome-specific coverage estimation,
|
||||||
|
- Fully probabilistic interpretation.
|
||||||
|
|
||||||
|
It is available in the `AMR` package via either:
|
||||||
|
|
||||||
|
```r
|
||||||
|
wisca(...)
|
||||||
|
|
||||||
|
antibiogram(..., wisca = TRUE)
|
||||||
|
```
|
||||||
|
|
||||||
## Reference
|
## Reference
|
||||||
|
|
||||||
Bielicki JA et al. (2016).
|
Bielicki, JA, et al. (2016). *Selecting appropriate empirical antibiotic regimens for paediatric bloodstream infections: application of a Bayesian decision model to local and pooled antimicrobial resistance surveillance data.* **J Antimicrob Chemother**. 71(3):794-802. https://doi.org/10.1093/jac/dkv397
|
||||||
*Weighted-incidence syndromic combination antibiograms to guide empiric treatment in pediatric bloodstream infections.*
|
|
||||||
**J Antimicrob Chemother**, 71(2):529–536. doi:10.1093/jac/dkv397
|
|
||||||
|
|
||||||
---
|
|
||||||
|
|
||||||
## Conclusion
|
|
||||||
|
|
||||||
WISCA shifts empirical therapy from simple percent susceptible toward **probabilistic, syndrome-based decision support**. It is a statistically principled, clinically intuitive method to guide regimen selection — and easy to use via the `antibiogram()` function in the **AMR** package.
|
|
||||||
|
|
||||||
For antimicrobial stewardship teams, it enables **disease-specific, reproducible, and data-driven guidance** — even in the face of sparse data.
|
|
||||||
|
|
||||||
|
@ -1,12 +1,12 @@
|
|||||||
---
|
---
|
||||||
title: "Data sets for download / own use"
|
title: "Download data sets for download / own use"
|
||||||
date: '`r format(Sys.Date(), "%d %B %Y")`'
|
date: '`r format(Sys.Date(), "%d %B %Y")`'
|
||||||
output:
|
output:
|
||||||
rmarkdown::html_vignette:
|
rmarkdown::html_vignette:
|
||||||
toc: true
|
toc: true
|
||||||
toc_depth: 1
|
toc_depth: 1
|
||||||
vignette: >
|
vignette: >
|
||||||
%\VignetteIndexEntry{Data sets for download / own use}
|
%\VignetteIndexEntry{Download data sets for download / own use}
|
||||||
%\VignetteEncoding{UTF-8}
|
%\VignetteEncoding{UTF-8}
|
||||||
%\VignetteEngine{knitr::rmarkdown}
|
%\VignetteEngine{knitr::rmarkdown}
|
||||||
editor_options:
|
editor_options:
|
||||||
|
Loading…
x
Reference in New Issue
Block a user