1
0
mirror of https://github.com/msberends/AMR.git synced 2025-04-15 13:10:32 +02:00

(v2.1.1.9190) antibiotics deprecation in antibiogram()

This commit is contained in:
dr. M.S. (Matthijs) Berends 2025-03-09 10:41:11 +01:00
parent c7af397edf
commit a2c2be23c1
No known key found for this signature in database
26 changed files with 203 additions and 180 deletions

View File

@ -65,6 +65,7 @@ jobs:
# do not check these folders
rm -rf data-raw
rm -rf tests
rm -rf vignettes
- name: Lint
run: |
@ -76,7 +77,7 @@ jobs:
linters <- linters[!grepl("^(closed_curly|open_curly|paren_brace|semicolon_terminator|consecutive_stopifnot|no_tab|single_quotes|unnecessary_nested_if|unneeded_concatenation)_linter$", linters)]
linters <- linters[linters != "linter"]
# and the ones we find unnnecessary
linters <- linters[!grepl("^(extraction_operator|implicit_integer|line_length|object_length|object_name|object_usage|nonportable_path|is)_linter$", linters)]
linters <- linters[!grepl("^(commented_code|extraction_operator|implicit_integer|indentation|line_length|namespace|nonportable_path|object_length|object_name|object_usage|is)_linter$", linters)]
# put the functions in a list
linters_list <- lapply(linters, function(l) eval(parse(text = paste0("lintr::", l, "()")), envir = asNamespace("lintr")))
names(linters_list) <- linters

View File

@ -1,6 +1,6 @@
Package: AMR
Version: 2.1.1.9189
Date: 2025-03-07
Version: 2.1.1.9190
Date: 2025-03-09
Title: Antimicrobial Resistance Data Analysis
Description: Functions to simplify and standardise antimicrobial resistance (AMR)
data analysis and to work with microbial and antimicrobial properties by

View File

@ -1,4 +1,4 @@
# AMR 2.1.1.9189
# AMR 2.1.1.9190
*(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://msberends.github.io/AMR/#latest-development-version).)*
@ -48,8 +48,9 @@ This package now supports not only tools for AMR data analysis in clinical setti
* To get quantitative values, `as.double()` on a `sir` object will return 1 for S, 2 for SDD/I, and 3 for R (NI will become `NA`). Other functions using `sir` classes (e.g., `summary()`) are updated to reflect the change to contain NI and SDD.
* Fix for `conserve_capped_values`, which now again works as expected: in MIC values, `<x` will always be S, `>x` will always be R
* `antibiogram()` function
* New argument `formatting_type` to set any of the 22 options for the formatting of all 'cells'. This defaults to `10` for non-WISCA and `14` for WISCA, changing the output of antibiograms to cells with more info.
* For this reason, `add_total_n` is now `FALSE` at default since the denominators are added to the cells
* Argument `antibiotics` has been renamed to `antimicrobials`. Using `antibiotics` will still work, but now returns a warning.
* Added argument `formatting_type` to set any of the 22 options for the formatting of all 'cells'. This defaults to `18` for non-WISCA and `14` for WISCA, changing the output of antibiograms to cells with more info.
* For this reason, `add_total_n` is now `FALSE` at default since the denominators are added to the cells for non-WISCA. For WISCA, the denominator is not useful anyway.
* The `ab_transform` argument now defaults to `"name"`, displaying antibiotic column names instead of codes
* Antimicrobial selectors (previously: *antibiotic selectors*)
* 'Antibiotic selectors' are now called 'antimicrobial selectors' since their scope is broader than just antibiotics. All documentation have been updated, and `ab_class()` and `ab_selector()` have been replaced with `amr_class()` and `amr_selector()`. The old functions are now deprecated and will be removed in a future version.

View File

@ -1,6 +1,6 @@
Metadata-Version: 2.2
Name: AMR
Version: 2.1.1.9189
Version: 2.1.1.9190
Summary: A Python wrapper for the AMR R package
Home-page: https://github.com/msberends/AMR
Author: Matthijs Berends

Binary file not shown.

Binary file not shown.

View File

@ -2,7 +2,7 @@ from setuptools import setup, find_packages
setup(
name='AMR',
version='2.1.1.9189',
version='2.1.1.9190',
packages=find_packages(),
install_requires=[
'rpy2',

View File

@ -34,7 +34,7 @@
#'
#' Adhering to previously described approaches (see *Source*) and especially the Bayesian WISCA model (Weighted-Incidence Syndromic Combination Antibiogram) by Bielicki *et al.*, these functions provide flexible output formats including plots and tables, ideal for integration with R Markdown and Quarto reports.
#' @param x a [data.frame] containing at least a column with microorganisms and columns with antimicrobial results (class 'sir', see [as.sir()])
#' @param antibiotics vector of any antimicrobial name or code (will be evaluated with [as.ab()], column name of `x`, or (any combinations of) [antimicrobial selectors][antimicrobial_selectors] such as [aminoglycosides()] or [carbapenems()]. For combination antibiograms, this can also be set to values separated with `"+"`, such as `"TZP+TOB"` or `"cipro + genta"`, given that columns resembling such antimicrobials exist in `x`. See *Examples*.
#' @param antimicrobials vector of any antimicrobial name or code (will be evaluated with [as.ab()], column name of `x`, or (any combinations of) [antimicrobial selectors][antimicrobial_selectors] such as [aminoglycosides()] or [carbapenems()]. For combination antibiograms, this can also be set to values separated with `"+"`, such as `"TZP+TOB"` or `"cipro + genta"`, given that columns resembling such antimicrobials exist in `x`. See *Examples*.
#' @param mo_transform a character to transform microorganism input - must be `"name"`, `"shortname"` (default), `"gramstain"`, or one of the column names of the [microorganisms] data set: `r vector_or(colnames(microorganisms), sort = FALSE, quotes = TRUE)`. Can also be `NULL` to not transform the input or `NA` to consider all microorganisms 'unknown'.
#' @param ab_transform a character to transform antimicrobial input - must be one of the column names of the [antimicrobials] data set (defaults to `"name"`): `r vector_or(colnames(antimicrobials), sort = FALSE, quotes = TRUE)`. Can also be `NULL` to not transform the input.
#' @param syndromic_group a column name of `x`, or values calculated to split rows of `x`, e.g. by using [ifelse()] or [`case_when()`][dplyr::case_when()]. See *Examples*.
@ -107,7 +107,7 @@
#'
#' ```r
#' antibiogram(your_data,
#' antibiotics = "TZP")
#' antimicrobials = "TZP")
#' ```
#'
#' 2. **Combination Antibiogram**
@ -118,7 +118,7 @@
#'
#' ```r
#' antibiogram(your_data,
#' antibiotics = c("TZP", "TZP+TOB", "TZP+GEN"))
#' antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"))
#' ```
#'
#' 3. **Syndromic Antibiogram**
@ -129,7 +129,7 @@
#'
#' ```r
#' antibiogram(your_data,
#' antibiotics = penicillins(),
#' antimicrobials = penicillins(),
#' syndromic_group = "ward")
#' ```
#'
@ -141,12 +141,12 @@
#'
#' ```r
#' antibiogram(your_data,
#' antibiotics = c("TZP", "TZP+TOB", "TZP+GEN"),
#' antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"),
#' wisca = TRUE)
#'
#' # this is equal to:
#' wisca(your_data,
#' antibiotics = c("TZP", "TZP+TOB", "TZP+GEN"))
#' antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"))
#' ```
#'
#' WISCA uses a sophisticated Bayesian decision model to combine both local and pooled antimicrobial resistance data. This approach not only evaluates local patterns but can also draw on multi-centre datasets to improve regimen accuracy, even in low-incidence infections like paediatric bloodstream infections (BSIs).
@ -161,7 +161,7 @@
#' library(dplyr)
#' your_data %>%
#' group_by(has_sepsis, is_neonate, sex) %>%
#' wisca(antibiotics = c("TZP", "TZP+TOB", "TZP+GEN"))
#' wisca(antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"))
#' ```
#'
#' ### Stepped Approach for Clinical Insight
@ -177,12 +177,12 @@
#'
#' ```r
#' antibiogram(your_data,
#' antibiotics = selected_regimens,
#' antimicrobials = selected_regimens,
#' mo_transform = NA) # all pathogens set to `NA`
#'
#' # preferred: use WISCA
#' wisca(your_data,
#' antibiotics = selected_regimens)
#' antimicrobials = selected_regimens)
#' ```
#'
#' 2. **Refinement with Gram Stain Results**
@ -194,7 +194,7 @@
#'
#' ```r
#' antibiogram(your_data,
#' antibiotics = selected_regimens,
#' antimicrobials = selected_regimens,
#' mo_transform = "gramstain") # all pathogens set to Gram-pos/Gram-neg
#' ```
#'
@ -207,7 +207,7 @@
#'
#' ```r
#' antibiogram(your_data,
#' antibiotics = selected_regimens,
#' antimicrobials = selected_regimens,
#' mo_transform = "shortname") # all pathogens set to 'G. species', e.g., E. coli
#' ```
#'
@ -301,17 +301,17 @@
#' # Traditional antibiogram ----------------------------------------------
#'
#' antibiogram(example_isolates,
#' antibiotics = c(aminoglycosides(), carbapenems())
#' antimicrobials = c(aminoglycosides(), carbapenems())
#' )
#'
#' antibiogram(example_isolates,
#' antibiotics = aminoglycosides(),
#' antimicrobials = aminoglycosides(),
#' ab_transform = "atc",
#' mo_transform = "gramstain"
#' )
#'
#' antibiogram(example_isolates,
#' antibiotics = carbapenems(),
#' antimicrobials = carbapenems(),
#' ab_transform = "name",
#' mo_transform = "name"
#' )
@ -319,15 +319,15 @@
#'
#' # Combined antibiogram -------------------------------------------------
#'
#' # combined antibiotics yield higher empiric coverage
#' # combined antimicrobials yield higher empiric coverage
#' antibiogram(example_isolates,
#' antibiotics = c("TZP", "TZP+TOB", "TZP+GEN"),
#' antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"),
#' mo_transform = "gramstain"
#' )
#'
#' # names of antibiotics do not need to resemble columns exactly:
#' # names of antimicrobials do not need to resemble columns exactly:
#' antibiogram(example_isolates,
#' antibiotics = c("Cipro", "cipro + genta"),
#' antimicrobials = c("Cipro", "cipro + genta"),
#' mo_transform = "gramstain",
#' ab_transform = "name",
#' sep = " & "
@ -338,7 +338,7 @@
#'
#' # the data set could contain a filter for e.g. respiratory specimens
#' antibiogram(example_isolates,
#' antibiotics = c(aminoglycosides(), carbapenems()),
#' antimicrobials = c(aminoglycosides(), carbapenems()),
#' syndromic_group = "ward"
#' )
#'
@ -348,7 +348,7 @@
#' # with a custom language, though this will be determined automatically
#' # (i.e., this table will be in Spanish on Spanish systems)
#' antibiogram(ex1,
#' antibiotics = aminoglycosides(),
#' antimicrobials = aminoglycosides(),
#' ab_transform = "name",
#' syndromic_group = ifelse(ex1$ward == "ICU",
#' "UCI", "No UCI"
@ -361,7 +361,7 @@
#'
#' # WISCA are not stratified by species, but rather on syndromes
#' antibiogram(example_isolates,
#' antibiotics = c("TZP", "TZP+TOB", "TZP+GEN"),
#' antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"),
#' syndromic_group = "ward",
#' wisca = TRUE
#' )
@ -370,7 +370,7 @@
#' # Print the output for R Markdown / Quarto -----------------------------
#'
#' ureido <- antibiogram(example_isolates,
#' antibiotics = ureidopenicillins(),
#' antimicrobials = ureidopenicillins(),
#' syndromic_group = "ward",
#' wisca = TRUE
#' )
@ -385,11 +385,11 @@
#' # Generate plots with ggplot2 or base R --------------------------------
#'
#' ab1 <- antibiogram(example_isolates,
#' antibiotics = c("AMC", "CIP", "TZP", "TZP+TOB"),
#' antimicrobials = c("AMC", "CIP", "TZP", "TZP+TOB"),
#' mo_transform = "gramstain"
#' )
#' ab2 <- antibiogram(example_isolates,
#' antibiotics = c("AMC", "CIP", "TZP", "TZP+TOB"),
#' antimicrobials = c("AMC", "CIP", "TZP", "TZP+TOB"),
#' mo_transform = "gramstain",
#' syndromic_group = "ward"
#' )
@ -405,7 +405,7 @@
#' plot(ab2)
#' }
antibiogram <- function(x,
antibiotics = where(is.sir),
antimicrobials = where(is.sir),
mo_transform = "shortname",
ab_transform = "name",
syndromic_group = NULL,
@ -422,14 +422,15 @@ antibiogram <- function(x,
simulations = 1000,
conf_interval = 0.95,
interval_side = "two-tailed",
info = interactive()) {
info = interactive(),
...) {
UseMethod("antibiogram")
}
#' @method antibiogram default
#' @export
antibiogram.default <- function(x,
antibiotics = where(is.sir),
antimicrobials = where(is.sir),
mo_transform = "shortname",
ab_transform = "name",
syndromic_group = NULL,
@ -446,7 +447,8 @@ antibiogram.default <- function(x,
simulations = 1000,
conf_interval = 0.95,
interval_side = "two-tailed",
info = interactive()) {
info = interactive(),
...) {
meet_criteria(x, allow_class = "data.frame")
x <- ascertain_sir_classes(x, "x")
meet_criteria(wisca, allow_class = "logical", has_length = 1)
@ -456,6 +458,10 @@ antibiogram.default <- function(x,
}
mo_transform <- function(x) suppressMessages(suppressWarnings(paste(mo_genus(x, keep_synonyms = TRUE, language = NULL), mo_species(x, keep_synonyms = TRUE, language = NULL))))
}
if ("antibiotics" %in% names(list(...))) {
deprecation_warning("antibiotics", "antimicrobials", fn = "antibiogram", is_argument = TRUE)
antimicrobials <- list(...)$antibiotics
}
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)
}
@ -514,17 +520,17 @@ antibiogram.default <- function(x,
has_syndromic_group <- FALSE
}
# get antibiotics
ab_trycatch <- tryCatch(colnames(suppressWarnings(x[, antibiotics, drop = FALSE])), error = function(e) NULL)
# get antimicrobials
ab_trycatch <- tryCatch(colnames(suppressWarnings(x[, antimicrobials, drop = FALSE])), error = function(e) NULL)
if (is.null(ab_trycatch)) {
stop_ifnot(is.character(suppressMessages(antibiotics)), "`antibiotics` must be an antimicrobial selector, or a character vector.")
antibiotics.bak <- antibiotics
# split antibiotics on separator and make it a list
antibiotics <- strsplit(gsub(" ", "", antibiotics), "+", fixed = TRUE)
# get available antibiotics in data set
stop_ifnot(is.character(suppressMessages(antimicrobials)), "`antimicrobials` must be an antimicrobial selector, or a character vector.")
antimicrobials.bak <- antimicrobials
# split antimicrobials on separator and make it a list
antimicrobials <- strsplit(gsub(" ", "", antimicrobials), "+", fixed = TRUE)
# get available antimicrobials in data set
df_ab <- get_column_abx(x, verbose = FALSE, info = FALSE)
# get antibiotics from user
user_ab <- suppressMessages(suppressWarnings(lapply(antibiotics, as.ab, flag_multiple_results = FALSE, info = FALSE)))
# get antimicrobials from user
user_ab <- suppressMessages(suppressWarnings(lapply(antimicrobials, as.ab, flag_multiple_results = FALSE, info = FALSE)))
non_existing <- character(0)
user_ab <- lapply(user_ab, function(x) {
out <- unname(df_ab[match(x, names(df_ab))])
@ -535,14 +541,14 @@ antibiogram.default <- function(x,
user_ab <- user_ab[unlist(lapply(user_ab, length)) > 0]
if (length(non_existing) > 0) {
warning_("The following antibiotics were not available and ignored: ", vector_and(ab_name(non_existing, language = NULL, tolower = TRUE), quotes = FALSE))
warning_("The following antimicrobials were not available and ignored: ", vector_and(ab_name(non_existing, language = NULL, tolower = TRUE), quotes = FALSE))
}
# make list unique
antibiotics <- unique(user_ab)
antimicrobials <- unique(user_ab)
# go through list to set AMR in combinations
for (i in seq_len(length(antibiotics))) {
abx <- antibiotics[[i]]
for (i in seq_len(length(antimicrobials))) {
abx <- antimicrobials[[i]]
for (ab in abx) {
# make sure they are SIR columns
x[, ab] <- as.sir(x[, ab, drop = TRUE])
@ -568,20 +574,20 @@ antibiogram.default <- function(x,
))
}
}
antibiotics[[i]] <- new_colname
antimicrobials[[i]] <- new_colname
}
antibiotics <- unlist(antibiotics)
antimicrobials <- unlist(antimicrobials)
} else {
antibiotics <- ab_trycatch
antimicrobials <- ab_trycatch
}
if (isTRUE(has_syndromic_group)) {
out <- x %pm>%
pm_select(.syndromic_group, .mo, antibiotics) %pm>%
pm_select(.syndromic_group, .mo, antimicrobials) %pm>%
pm_group_by(.syndromic_group)
} else {
out <- x %pm>%
pm_select(.mo, antibiotics)
pm_select(.mo, antimicrobials)
}
@ -613,8 +619,6 @@ antibiogram.default <- function(x,
if (isTRUE(info) && mins > 0) {
message_("NOTE: ", mins, " combinations had less than `minimum = ", minimum, "` results and were ignored", add_fn = font_red)
}
} else if (isTRUE(info)) {
warning_("Number of tested isolates per regimen should exceed ", minimum, " for each species. Coverage estimates might be inaccurate.", call = FALSE)
}
}
if (NROW(out) == 0) {
@ -678,6 +682,10 @@ antibiogram.default <- function(x,
n_susceptible = sum(n_susceptible, na.rm = TRUE)
)
if (any(out_wisca$n_tested < minimum, na.rm = TRUE) && message_not_thrown_before("antibiogram", wisca)) {
warning_("Number of tested isolates should exceed ", minimum, " for each regimen (and group). WISCA coverage estimates might be inaccurate.", call = FALSE)
}
out_wisca$p_susceptible <- out_wisca$n_susceptible / out_wisca$n_tested
if (isTRUE(has_syndromic_group)) {
@ -690,8 +698,8 @@ antibiogram.default <- function(x,
# create the WISCA parameters, including our priors/posteriors
out$gamma_posterior <- NA_real_
out$beta_posterior1 <- NA_real_
out$beta_posterior2 <- NA_real_
out$beta_posterior_1 <- NA_real_
out$beta_posterior_2 <- NA_real_
for (i in seq_len(NROW(out))) {
if (out$n_tested[i] == 0) {
@ -699,10 +707,22 @@ antibiogram.default <- function(x,
}
out_current <- out[i, , drop = FALSE]
priors <- calculate_priors(out_current, combine_SI = combine_SI)
out$gamma_posterior[i] <- priors$gamma_posterior
out$beta_posterior1[i] <- priors$beta_posterior_1
out$beta_posterior2[i] <- priors$beta_posterior_2
## calculate priors ----
# pathogen incidence (Dirichlet distribution)
gamma_prior <- rep(1, length(unique(out_current$mo))) # Dirichlet prior
gamma_posterior <- gamma_prior + out_current$n_total # Posterior parameters
# regimen susceptibility (Beta distribution)
beta_prior <- rep(1, length(unique(out_current$mo))) # Beta prior
r <- out_current$n_susceptible
n <- out_current$n_tested
beta_posterior_1 <- beta_prior + r # Posterior alpha
beta_posterior_2 <- beta_prior + (n - r) # Posterior beta
out$gamma_posterior[i] <- gamma_posterior
out$beta_posterior_1[i] <- beta_posterior_1
out$beta_posterior_2[i] <- beta_posterior_2
}
wisca_parameters <- out
@ -742,8 +762,8 @@ antibiogram.default <- function(x,
random_susceptibity <- stats::runif(1, min = 0, max = 1)
simulated_susceptibility <- stats::qbeta(
p = random_susceptibity,
shape1 = params_current$beta_posterior1,
shape2 = params_current$beta_posterior2
shape1 = params_current$beta_posterior_1,
shape2 = params_current$beta_posterior_2
)
sum(simulated_incidence * simulated_susceptibility, na.rm = TRUE)
})
@ -825,6 +845,9 @@ antibiogram.default <- function(x,
# 20. 5% (4-6%,15/300)
# 21. 5 (4-6,N=15/300)
# 22. 5% (4-6%,N=15/300)
if (wisca == TRUE && !formatting_type %in% c(1, 2, 13, 14) && info == TRUE && message_not_thrown_before("antibiogram", wisca, formatting_type)) {
message_("Using WISCA with a `formatting_type` that includes the denominator is not useful")
}
if (formatting_type == 1) out <- out %pm>% pm_summarise(out_value = round(coverage * 100, digits = digits))
if (formatting_type == 2) out <- out %pm>% pm_summarise(out_value = n_susceptible)
if (formatting_type == 3) out <- out %pm>% pm_summarise(out_value = n_tested)
@ -847,8 +870,9 @@ antibiogram.default <- function(x,
if (formatting_type == 20) out <- out %pm>% pm_summarise(out_value = paste0(round(coverage * 100, digits = digits), "% (", round(lower_ci * 100, digits = digits), "-", round(upper_ci * 100, digits = digits), "%,", n_susceptible, "/", n_tested, ")"))
if (formatting_type == 21) out <- out %pm>% pm_summarise(out_value = paste0(round(coverage * 100, digits = digits), " (", round(lower_ci * 100, digits = digits), "-", round(upper_ci * 100, digits = digits), ",N=", n_susceptible, "/", n_tested, ")"))
if (formatting_type == 22) out <- out %pm>% pm_summarise(out_value = paste0(round(coverage * 100, digits = digits), "% (", round(lower_ci * 100, digits = digits), "-", round(upper_ci * 100, digits = digits), "%,N=", n_susceptible, "/", n_tested, ")"))
out$out_value[out$out_value %like% "^NA"] <- NA_character_
# transform names of antibiotics
# transform names of antimicrobials
ab_naming_function <- function(x, t, l, s) {
x <- strsplit(x, s, fixed = TRUE)
out <- character(length = length(x))
@ -979,7 +1003,7 @@ antibiogram.default <- function(x,
#' @method antibiogram grouped_df
#' @export
antibiogram.grouped_df <- function(x,
antibiotics = where(is.sir),
antimicrobials = where(is.sir),
mo_transform = NULL,
ab_transform = "name",
syndromic_group = NULL,
@ -996,7 +1020,8 @@ antibiogram.grouped_df <- function(x,
simulations = 1000,
conf_interval = 0.95,
interval_side = "two-tailed",
info = interactive()) {
info = interactive(),
...) {
stop_ifnot(is.null(mo_transform), "`mo_transform` must not be set if creating an antibiogram using a grouped tibble. The groups will become the variables over which the antimicrobials are calculated, which could include the pathogen information (though not necessary). Nonetheless, this makes `mo_transform` redundant.", call = FALSE)
stop_ifnot(is.null(syndromic_group), "`syndromic_group` must not be set if creating an antibiogram using a grouped tibble. The groups will become the variables over which the antimicrobials are calculated, making `syndromic_groups` redundant.", call = FALSE)
groups <- attributes(x)$groups
@ -1020,7 +1045,7 @@ antibiogram.grouped_df <- function(x,
next
}
new_out <- antibiogram(as.data.frame(x)[rows, , drop = FALSE],
antibiotics = antibiotics,
antimicrobials = antimicrobials,
mo_transform = NULL,
ab_transform = ab_transform,
syndromic_group = NULL,
@ -1037,7 +1062,8 @@ antibiogram.grouped_df <- function(x,
simulations = simulations,
conf_interval = conf_interval,
interval_side = interval_side,
info = FALSE
info = FALSE,
...
)
new_wisca_parameters <- attributes(new_out)$wisca_parameters
new_long_numeric <- attributes(new_out)$long_numeric
@ -1098,7 +1124,7 @@ antibiogram.grouped_df <- function(x,
#' @export
#' @rdname antibiogram
wisca <- function(x,
antibiotics = where(is.sir),
antimicrobials = where(is.sir),
ab_transform = "name",
syndromic_group = NULL,
add_total_n = FALSE,
@ -1113,10 +1139,11 @@ wisca <- function(x,
simulations = 1000,
conf_interval = 0.95,
interval_side = "two-tailed",
info = interactive()) {
info = interactive(),
...) {
antibiogram(
x = x,
antibiotics = antibiotics,
antimicrobials = antimicrobials,
ab_transform = ab_transform,
mo_transform = NULL,
syndromic_group = syndromic_group,
@ -1133,7 +1160,8 @@ wisca <- function(x,
simulations = simulations,
conf_interval = conf_interval,
interval_side = interval_side,
info = info
info = info,
...
)
}
@ -1145,26 +1173,6 @@ retrieve_wisca_parameters <- function(wisca_model, ...) {
attributes(wisca_model)$wisca_parameters
}
calculate_priors <- function(data, combine_SI = TRUE) {
# Pathogen incidence (Dirichlet distribution)
gamma_prior <- rep(1, length(unique(data$mo))) # Dirichlet prior
gamma_posterior <- gamma_prior + data$n_total # Posterior parameters
# Regimen susceptibility (Beta distribution)
beta_prior <- rep(1, length(unique(data$mo))) # Beta prior
r <- data$n_susceptible # Number of pathogens tested susceptible
n <- data$n_tested # n_tested tested
beta_posterior_1 <- beta_prior + r # Posterior alpha
beta_posterior_2 <- beta_prior + (n - r) # Posterior beta
# Return parameters as a list
list(
gamma_posterior = gamma_posterior,
beta_posterior_1 = beta_posterior_1,
beta_posterior_2 = beta_posterior_2
)
}
# will be exported in R/zzz.R
tbl_sum.antibiogram <- function(x, ...) {
dims <- paste(format(NROW(x), big.mark = ","), AMR_env$cross_icon, format(NCOL(x), big.mark = ","))
@ -1185,7 +1193,7 @@ tbl_format_footer.antibiogram <- function(x, ...) {
return(footer)
}
c(footer, font_subtle(paste0(
"# Use `plot()` or `ggplot2::autoplot()` to create a plot of this antibiogram,\n",
"# Use `ggplot2::autoplot()` or base R `plot()` to create a plot of this antibiogram,\n",
"# or use it directly in R Markdown or ",
font_url("https://quarto.org", "Quarto"), ", see ", word_wrap("?antibiogram")
)))

View File

@ -58,7 +58,7 @@
#'
#' The function [proportion_df()] takes any variable from `data` that has an [`sir`] class (created with [as.sir()]) and calculates the proportions S, I, and R. It also supports grouped variables. The function [sir_df()] works exactly like [proportion_df()], but adds the number of isolates.
#' @section Combination Therapy:
#' When using more than one variable for `...` (= combination therapy), use `only_all_tested` to only count isolates that are tested for all antibiotics/variables that you test them for. See this example for two antimicrobials, Drug A and Drug B, about how [susceptibility()] works to calculate the %SI:
#' When using more than one variable for `...` (= combination therapy), use `only_all_tested` to only count isolates that are tested for all antimicrobials/variables that you test them for. See this example for two antimicrobials, Drug A and Drug B, about how [susceptibility()] works to calculate the %SI:
#'
#'
#' ```

View File

@ -235,7 +235,7 @@ sir_calc_df <- function(type, # "proportion", "count" or "both"
translate_ab <- get_translate_ab(translate_ab)
data.bak <- data
# select only groups and antibiotics
# select only groups and antimicrobials
if (is_null_or_grouped_tbl(data)) {
data_has_groups <- TRUE
groups <- get_group_names(data)

View File

@ -40,22 +40,25 @@ NULL
#' @export
"antibiotics"
# REMEMBER to also remove the deprecated `antibiotics` argument in `antibiogram()`
#' @rdname AMR-deprecated
#' @export
ab_class <- function(...) {
deprecation_warning("ab_class", "amr_class")
deprecation_warning("ab_class", "amr_class", is_function = TRUE)
amr_class(...)
}
#' @rdname AMR-deprecated
#' @export
ab_selector <- function(...) {
deprecation_warning("ab_selector", "amr_selector")
deprecation_warning("ab_selector", "amr_selector", is_function = TRUE)
amr_selector(...)
}
## Helper function ----
deprecation_warning <- function(old = NULL, new = NULL, extra_msg = NULL, is_function = TRUE, is_dataset = FALSE) {
deprecation_warning <- function(old = NULL, new = NULL, fn = NULL, extra_msg = NULL, is_function = FALSE, is_dataset = FALSE, is_argument = FALSE) {
if (is.null(old)) {
warning_(extra_msg)
} else {
@ -68,22 +71,30 @@ deprecation_warning <- function(old = NULL, new = NULL, extra_msg = NULL, is_fun
type <- "function"
} else if (isTRUE(is_dataset)) {
type <- "dataset"
} else {
} else if (isTRUE(is_argument)) {
type <- "argument"
if (is.null(fn)) {
stop("Set 'fn' in deprecation_warning()")
}
} else {
stop("Set either 'is_function', 'is_dataset', or 'is_argument' to TRUE in deprecation_warning()")
}
warning_(
ifelse(is.null(new),
paste0("The `", old, "` ", type, " is no longer in use"),
ifelse(type == "dataset",
paste0("The `", old, "` ", type, " has been renamed to `", new, "`"),
paste0("The `", old, "` ", type, " has been replaced with `", new, "` and will be removed in a future version")
ifelse(type == "argument",
paste0("The `", old, "` ", type, " in `", fn, "()` has been renamed to `", new, "`: `", fn, "(", new, " = ...)`"),
paste0("The `", old, "` ", type, " has been replaced with `", new, "`")
)
)
),
ifelse(type == "dataset",
". The old name will be removed in future version, so please update your code.",
ifelse(type == "argument",
". While the old argument still works, it will be removed in a future version, so please update your code.",
", see `?AMR-deprecated`."
" and will be removed in a future version, see `?AMR-deprecated`."
)
),
ifelse(!is.null(extra_msg),

View File

@ -204,14 +204,14 @@ AMR_env$cross_icon <- if (isTRUE(base::l10n_info()$`UTF-8`)) "\u00d7" else "x"
# reference data - they have additional data to improve algorithm speed
# they cannot be part of R/sysdata.rda since CRAN thinks it would make the package too large (+3 MB)
if (NROW(AB_LOOKUP) != NROW(AMR::antimicrobials)) {
# antibiotics data set was updated - run create_AB_AV_lookup() again
# antimicrobials data set was updated - run create_AB_AV_lookup() again
AB_LOOKUP <- create_AB_AV_lookup(AMR::antimicrobials)
}
# deprecated antibiotics data set
makeActiveBinding("antibiotics", function() {
if (interactive()) {
deprecation_warning(old = "antibiotics", new = "antimicrobials", is_function = FALSE, is_dataset = TRUE)
deprecation_warning(old = "antibiotics", new = "antimicrobials", is_dataset = TRUE)
}
AMR::antimicrobials
}, env = asNamespace(pkgname))

View File

@ -492,9 +492,11 @@ write_md5 <- function(object) {
close(conn)
}
changed_md5 <- function(object) {
path <- paste0("data-raw/", deparse(substitute(object)), ".md5")
if (!file.exists(path)) return(TRUE)
tryCatch(
{
conn <- file(paste0("data-raw/", deparse(substitute(object)), ".md5"))
conn <- file(path)
compared <- md5(object) != readLines(con = conn)
close(conn)
compared

View File

@ -1,6 +1,6 @@
This knowledge base contains all context you must know about the AMR package for R. You are a GPT trained to be an assistant for the AMR package in R. You are an incredible R specialist, especially trained in this package and in the tidyverse.
First and foremost, you are trained on version 2.1.1.9189. Remember this whenever someone asks which AMR package version youre at.
First and foremost, you are trained on version 2.1.1.9190. Remember this whenever someone asks which AMR package version youre at.
Below are the contents of the file, the file, and all the files (documentation) in the package. Every file content is split using 100 hypens.
----------------------------------------------------------------------------------------------------
@ -420,7 +420,7 @@ The `AMR` package is a [free and open-source](#copyright) R package with [zero d
This work was published in the Journal of Statistical Software (Volume 104(3); [DOI 10.18637/jss.v104.i03](https://doi.org/10.18637/jss.v104.i03)) and formed the basis of two PhD theses ([DOI 10.33612/diss.177417131](https://doi.org/10.33612/diss.177417131) and [DOI 10.33612/diss.192486375](https://doi.org/10.33612/diss.192486375)).
After installing this package, R knows [**~52,000 distinct microbial species**](./reference/microorganisms.html) (updated December 2022) and all [**~600 antimicrobial and antiviral drugs**](./reference/antibiotics.html) by name and code (including ATC, EARS-Net, ASIARS-Net, PubChem, LOINC and SNOMED CT), and knows all about valid SIR and MIC values. The integral clinical breakpoint guidelines from CLSI and EUCAST are included, even with epidemiological cut-off (ECOFF) values. It supports and can read any data format, including WHONET data. This package works on Windows, macOS and Linux with all versions of R since R-3.0 (April 2013). **It was designed to work in any setting, including those with very limited resources**. It was created for both routine data analysis and academic research at the Faculty of Medical Sciences of the [University of Groningen](https://www.rug.nl), in collaboration with non-profit organisations [Certe Medical Diagnostics and Advice Foundation](https://www.certe.nl) and [University Medical Center Groningen](https://www.umcg.nl).
After installing this package, R knows [**~52,000 distinct microbial species**](./reference/microorganisms.html) (updated December 2022) and all [**~600 antimicrobial and antiviral drugs**](./reference/antimicrobials.html) by name and code (including ATC, EARS-Net, ASIARS-Net, PubChem, LOINC and SNOMED CT), and knows all about valid SIR and MIC values. The integral clinical breakpoint guidelines from CLSI and EUCAST are included, even with epidemiological cut-off (ECOFF) values. It supports and can read any data format, including WHONET data. This package works on Windows, macOS and Linux with all versions of R since R-3.0 (April 2013). **It was designed to work in any setting, including those with very limited resources**. It was created for both routine data analysis and academic research at the Faculty of Medical Sciences of the [University of Groningen](https://www.rug.nl), in collaboration with non-profit organisations [Certe Medical Diagnostics and Advice Foundation](https://www.certe.nl) and [University Medical Center Groningen](https://www.umcg.nl).
##### Used in over 175 countries, available in 20 languages
@ -475,7 +475,7 @@ If used inside [R Markdown](https://rmarkdown.rstudio.com) or [Quarto](https://q
```r
antibiogram(example_isolates,
antibiotics = c(aminoglycosides(), carbapenems()),
antimicrobials = c(aminoglycosides(), carbapenems()),
formatting_type = 14)
```
@ -492,11 +492,11 @@ antibiogram(example_isolates,
| *S. hominis* | | 92% (84-97%) | | | | 85% (74-93%) |
| *S. pneumoniae* | 0% (0-3%) | 0% (0-3%) | | 0% (0-3%) | | 0% (0-3%) |
In combination antibiograms, it is clear that combined antibiotics yield higher empiric coverage:
In combination antibiograms, it is clear that combined antimicrobials yield higher empiric coverage:
```r
antibiogram(example_isolates,
antibiotics = c("TZP", "TZP+TOB", "TZP+GEN"),
antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"),
mo_transform = "gramstain",
formatting_type = 14)
```
@ -510,7 +510,7 @@ Like many other functions in this package, `antibiogram()` comes with support fo
```r
antibiogram(example_isolates,
antibiotics = c("cipro", "tobra", "genta"), # any arbitrary name or code will work
antimicrobials = c("cipro", "tobra", "genta"), # any arbitrary name or code will work
mo_transform = "gramstain",
ab_transform = "name",
formatting_type = 14,
@ -1670,23 +1670,23 @@ THE PART HEREAFTER CONTAINS CONTENTS FROM FILE 'man/antibiogram.Rd':
}
}
\usage{
antibiogram(x, antibiotics = where(is.sir), mo_transform = "shortname",
antibiogram(x, antimicrobials = where(is.sir), mo_transform = "shortname",
ab_transform = "name", syndromic_group = NULL, add_total_n = FALSE,
only_all_tested = FALSE, digits = ifelse(wisca, 1, 0),
formatting_type = getOption("AMR_antibiogram_formatting_type",
ifelse(wisca, 14, 18)), col_mo = NULL, language = get_AMR_locale(),
minimum = 30, combine_SI = TRUE, sep = " + ", wisca = FALSE,
simulations = 1000, conf_interval = 0.95, interval_side = "two-tailed",
info = interactive())
info = interactive(), ...)
wisca(x, antibiotics = where(is.sir), ab_transform = "name",
wisca(x, antimicrobials = where(is.sir), ab_transform = "name",
syndromic_group = NULL, add_total_n = FALSE, only_all_tested = FALSE,
digits = 1,
formatting_type = getOption("AMR_antibiogram_formatting_type", 14),
col_mo = NULL, language = get_AMR_locale(), minimum = 30,
combine_SI = TRUE, sep = " + ", simulations = 1000,
conf_interval = 0.95, interval_side = "two-tailed",
info = interactive())
info = interactive(), ...)
retrieve_wisca_parameters(wisca_model, ...)
@ -1700,7 +1700,7 @@ retrieve_wisca_parameters(wisca_model, ...)
\arguments{
\item{x}{a \link{data.frame} containing at least a column with microorganisms and columns with antimicrobial results (class 'sir', see \code{\link[=as.sir]{as.sir()}})}
\item{antibiotics}{vector of any antimicrobial name or code (will be evaluated with \code{\link[=as.ab]{as.ab()}}, column name of \code{x}, or (any combinations of) \link[=antimicrobial_selectors]{antimicrobial selectors} such as \code{\link[=aminoglycosides]{aminoglycosides()}} or \code{\link[=carbapenems]{carbapenems()}}. For combination antibiograms, this can also be set to values separated with \code{"+"}, such as \code{"TZP+TOB"} or \code{"cipro + genta"}, given that columns resembling such antimicrobials exist in \code{x}. See \emph{Examples}.}
\item{antimicrobials}{vector of any antimicrobial name or code (will be evaluated with \code{\link[=as.ab]{as.ab()}}, column name of \code{x}, or (any combinations of) \link[=antimicrobial_selectors]{antimicrobial selectors} such as \code{\link[=aminoglycosides]{aminoglycosides()}} or \code{\link[=carbapenems]{carbapenems()}}. For combination antibiograms, this can also be set to values separated with \code{"+"}, such as \code{"TZP+TOB"} or \code{"cipro + genta"}, given that columns resembling such antimicrobials exist in \code{x}. See \emph{Examples}.}
\item{mo_transform}{a character to transform microorganism input - must be \code{"name"}, \code{"shortname"} (default), \code{"gramstain"}, or one of the column names of the \link{microorganisms} data set: "mo", "fullname", "status", "kingdom", "phylum", "class", "order", "family", "genus", "species", "subspecies", "rank", "ref", "oxygen_tolerance", "source", "lpsn", "lpsn_parent", "lpsn_renamed_to", "mycobank", "mycobank_parent", "mycobank_renamed_to", "gbif", "gbif_parent", "gbif_renamed_to", "prevalence", or "snomed". Can also be \code{NULL} to not transform the input or \code{NA} to consider all microorganisms 'unknown'.}
@ -1736,10 +1736,10 @@ retrieve_wisca_parameters(wisca_model, ...)
\item{info}{a \link{logical} to indicate info should be printed - the default is \code{TRUE} only in interactive mode}
\item{wisca_model}{the outcome of \code{\link[=wisca]{wisca()}} or \code{\link[=antibiogram]{antibiogram(..., wisca = TRUE)}}}
\item{...}{when used in \link[knitr:kable]{R Markdown or Quarto}: arguments passed on to \code{\link[knitr:kable]{knitr::kable()}} (otherwise, has no use)}
\item{wisca_model}{the outcome of \code{\link[=wisca]{wisca()}} or \code{\link[=antibiogram]{antibiogram(..., wisca = TRUE)}}}
\item{object}{an \code{\link[=antibiogram]{antibiogram()}} object}
\item{italicise}{a \link{logical} to indicate whether the microorganism names in the \link[knitr:kable]{knitr} table should be made italic, using \code{\link[=italicise_taxonomy]{italicise_taxonomy()}}.}
@ -1805,7 +1805,7 @@ Case example: Susceptibility of \emph{Pseudomonas aeruginosa} to piperacillin/ta
Code example:
\if{html}{\out{<div class="sourceCode r">}}\preformatted{antibiogram(your_data,
antibiotics = "TZP")
antimicrobials = "TZP")
}\if{html}{\out{</div>}}
\item \strong{Combination Antibiogram}
@ -1814,7 +1814,7 @@ Case example: Additional susceptibility of \emph{Pseudomonas aeruginosa} to TZP
Code example:
\if{html}{\out{<div class="sourceCode r">}}\preformatted{antibiogram(your_data,
antibiotics = c("TZP", "TZP+TOB", "TZP+GEN"))
antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"))
}\if{html}{\out{</div>}}
\item \strong{Syndromic Antibiogram}
@ -1823,7 +1823,7 @@ Case example: Susceptibility of \emph{Pseudomonas aeruginosa} to TZP among respi
Code example:
\if{html}{\out{<div class="sourceCode r">}}\preformatted{antibiogram(your_data,
antibiotics = penicillins(),
antimicrobials = penicillins(),
syndromic_group = "ward")
}\if{html}{\out{</div>}}
\item \strong{Weighted-Incidence Syndromic Combination Antibiogram (WISCA)}
@ -1833,12 +1833,12 @@ WISCA can be applied to any antibiogram, see the section \emph{Explaining WISCA}
Code example:
\if{html}{\out{<div class="sourceCode r">}}\preformatted{antibiogram(your_data,
antibiotics = c("TZP", "TZP+TOB", "TZP+GEN"),
antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"),
wisca = TRUE)
# this is equal to:
wisca(your_data,
antibiotics = c("TZP", "TZP+TOB", "TZP+GEN"))
antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"))
}\if{html}{\out{</div>}}
WISCA uses a sophisticated Bayesian decision model to combine both local and pooled antimicrobial resistance data. This approach not only evaluates local patterns but can also draw on multi-centre datasets to improve regimen accuracy, even in low-incidence infections like paediatric bloodstream infections (BSIs).
@ -1854,7 +1854,7 @@ Code example:
\if{html}{\out{<div class="sourceCode r">}}\preformatted{library(dplyr)
your_data \%>\%
group_by(has_sepsis, is_neonate, sex) \%>\%
wisca(antibiotics = c("TZP", "TZP+TOB", "TZP+GEN"))
wisca(antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"))
}\if{html}{\out{</div>}}
}
@ -1870,12 +1870,12 @@ At admission, no pathogen information is available.
\item Code example:
\if{html}{\out{<div class="sourceCode r">}}\preformatted{antibiogram(your_data,
antibiotics = selected_regimens,
antimicrobials = selected_regimens,
mo_transform = NA) # all pathogens set to `NA`
# preferred: use WISCA
wisca(your_data,
antibiotics = selected_regimens)
antimicrobials = selected_regimens)
}\if{html}{\out{</div>}}
}
\item \strong{Refinement with Gram Stain Results}
@ -1886,7 +1886,7 @@ When a blood culture becomes positive, the Gram stain provides an initial and cr
\item Code example:
\if{html}{\out{<div class="sourceCode r">}}\preformatted{antibiogram(your_data,
antibiotics = selected_regimens,
antimicrobials = selected_regimens,
mo_transform = "gramstain") # all pathogens set to Gram-pos/Gram-neg
}\if{html}{\out{</div>}}
}
@ -1898,7 +1898,7 @@ After cultivation of the pathogen, full pathogen identification allows precise t
\item Code example:
\if{html}{\out{<div class="sourceCode r">}}\preformatted{antibiogram(your_data,
antibiotics = selected_regimens,
antimicrobials = selected_regimens,
mo_transform = "shortname") # all pathogens set to 'G. species', e.g., E. coli
}\if{html}{\out{</div>}}
}
@ -1989,17 +1989,17 @@ example_isolates
# Traditional antibiogram ----------------------------------------------
antibiogram(example_isolates,
antibiotics = c(aminoglycosides(), carbapenems())
antimicrobials = c(aminoglycosides(), carbapenems())
)
antibiogram(example_isolates,
antibiotics = aminoglycosides(),
antimicrobials = aminoglycosides(),
ab_transform = "atc",
mo_transform = "gramstain"
)
antibiogram(example_isolates,
antibiotics = carbapenems(),
antimicrobials = carbapenems(),
ab_transform = "name",
mo_transform = "name"
)
@ -2007,15 +2007,15 @@ antibiogram(example_isolates,
# Combined antibiogram -------------------------------------------------
# combined antibiotics yield higher empiric coverage
# combined antimicrobials yield higher empiric coverage
antibiogram(example_isolates,
antibiotics = c("TZP", "TZP+TOB", "TZP+GEN"),
antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"),
mo_transform = "gramstain"
)
# names of antibiotics do not need to resemble columns exactly:
# names of antimicrobials do not need to resemble columns exactly:
antibiogram(example_isolates,
antibiotics = c("Cipro", "cipro + genta"),
antimicrobials = c("Cipro", "cipro + genta"),
mo_transform = "gramstain",
ab_transform = "name",
sep = " & "
@ -2026,7 +2026,7 @@ antibiogram(example_isolates,
# the data set could contain a filter for e.g. respiratory specimens
antibiogram(example_isolates,
antibiotics = c(aminoglycosides(), carbapenems()),
antimicrobials = c(aminoglycosides(), carbapenems()),
syndromic_group = "ward"
)
@ -2036,7 +2036,7 @@ ex1 <- example_isolates[which(mo_genus() == "Escherichia"), ]
# with a custom language, though this will be determined automatically
# (i.e., this table will be in Spanish on Spanish systems)
antibiogram(ex1,
antibiotics = aminoglycosides(),
antimicrobials = aminoglycosides(),
ab_transform = "name",
syndromic_group = ifelse(ex1$ward == "ICU",
"UCI", "No UCI"
@ -2049,7 +2049,7 @@ antibiogram(ex1,
# WISCA are not stratified by species, but rather on syndromes
antibiogram(example_isolates,
antibiotics = c("TZP", "TZP+TOB", "TZP+GEN"),
antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"),
syndromic_group = "ward",
wisca = TRUE
)
@ -2058,7 +2058,7 @@ antibiogram(example_isolates,
# Print the output for R Markdown / Quarto -----------------------------
ureido <- antibiogram(example_isolates,
antibiotics = ureidopenicillins(),
antimicrobials = ureidopenicillins(),
syndromic_group = "ward",
wisca = TRUE
)
@ -2073,11 +2073,11 @@ if (requireNamespace("knitr")) {
# Generate plots with ggplot2 or base R --------------------------------
ab1 <- antibiogram(example_isolates,
antibiotics = c("AMC", "CIP", "TZP", "TZP+TOB"),
antimicrobials = c("AMC", "CIP", "TZP", "TZP+TOB"),
mo_transform = "gramstain"
)
ab2 <- antibiogram(example_isolates,
antibiotics = c("AMC", "CIP", "TZP", "TZP+TOB"),
antimicrobials = c("AMC", "CIP", "TZP", "TZP+TOB"),
mo_transform = "gramstain",
syndromic_group = "ward"
)
@ -4287,7 +4287,7 @@ This AMR package honours this insight. Use \code{\link[=susceptibility]{suscepti
\section{Combination Therapy}{
When using more than one variable for \code{...} (= combination therapy), use \code{only_all_tested} to only count isolates that are tested for all antibiotics/variables that you test them for. See this example for two antimicrobials, Drug A and Drug B, about how \code{\link[=susceptibility]{susceptibility()}} works to calculate the \%SI:
When using more than one variable for \code{...} (= combination therapy), use \code{only_all_tested} to only count isolates that are tested for all antimicrobials/variables that you test them for. See this example for two antimicrobials, Drug A and Drug B, about how \code{\link[=susceptibility]{susceptibility()}} works to calculate the \%SI:
\if{html}{\out{<div class="sourceCode">}}\preformatted{--------------------------------------------------------------------
only_all_tested = FALSE only_all_tested = TRUE
@ -7852,7 +7852,7 @@ The function \code{\link[=proportion_df]{proportion_df()}} takes any variable fr
}
\section{Combination Therapy}{
When using more than one variable for \code{...} (= combination therapy), use \code{only_all_tested} to only count isolates that are tested for all antibiotics/variables that you test them for. See this example for two antimicrobials, Drug A and Drug B, about how \code{\link[=susceptibility]{susceptibility()}} works to calculate the \%SI:
When using more than one variable for \code{...} (= combination therapy), use \code{only_all_tested} to only count isolates that are tested for all antimicrobials/variables that you test them for. See this example for two antimicrobials, Drug A and Drug B, about how \code{\link[=susceptibility]{susceptibility()}} works to calculate the \%SI:
\if{html}{\out{<div class="sourceCode">}}\preformatted{--------------------------------------------------------------------
only_all_tested = FALSE only_all_tested = TRUE

View File

@ -26,7 +26,7 @@ The `AMR` package is a [free and open-source](#copyright) R package with [zero d
This work was published in the Journal of Statistical Software (Volume 104(3); [DOI 10.18637/jss.v104.i03](https://doi.org/10.18637/jss.v104.i03)) and formed the basis of two PhD theses ([DOI 10.33612/diss.177417131](https://doi.org/10.33612/diss.177417131) and [DOI 10.33612/diss.192486375](https://doi.org/10.33612/diss.192486375)).
After installing this package, R knows [**~52,000 distinct microbial species**](./reference/microorganisms.html) (updated December 2022) and all [**~600 antimicrobial and antiviral drugs**](./reference/antibiotics.html) by name and code (including ATC, EARS-Net, ASIARS-Net, PubChem, LOINC and SNOMED CT), and knows all about valid SIR and MIC values. The integral clinical breakpoint guidelines from CLSI and EUCAST are included, even with epidemiological cut-off (ECOFF) values. It supports and can read any data format, including WHONET data. This package works on Windows, macOS and Linux with all versions of R since R-3.0 (April 2013). **It was designed to work in any setting, including those with very limited resources**. It was created for both routine data analysis and academic research at the Faculty of Medical Sciences of the [University of Groningen](https://www.rug.nl), in collaboration with non-profit organisations [Certe Medical Diagnostics and Advice Foundation](https://www.certe.nl) and [University Medical Center Groningen](https://www.umcg.nl).
After installing this package, R knows [**~52,000 distinct microbial species**](./reference/microorganisms.html) (updated December 2022) and all [**~600 antimicrobial and antiviral drugs**](./reference/antimicrobials.html) by name and code (including ATC, EARS-Net, ASIARS-Net, PubChem, LOINC and SNOMED CT), and knows all about valid SIR and MIC values. The integral clinical breakpoint guidelines from CLSI and EUCAST are included, even with epidemiological cut-off (ECOFF) values. It supports and can read any data format, including WHONET data. This package works on Windows, macOS and Linux with all versions of R since R-3.0 (April 2013). **It was designed to work in any setting, including those with very limited resources**. It was created for both routine data analysis and academic research at the Faculty of Medical Sciences of the [University of Groningen](https://www.rug.nl), in collaboration with non-profit organisations [Certe Medical Diagnostics and Advice Foundation](https://www.certe.nl) and [University Medical Center Groningen](https://www.umcg.nl).
##### Used in over 175 countries, available in 20 languages
@ -81,7 +81,7 @@ If used inside [R Markdown](https://rmarkdown.rstudio.com) or [Quarto](https://q
```r
antibiogram(example_isolates,
antibiotics = c(aminoglycosides(), carbapenems()),
antimicrobials = c(aminoglycosides(), carbapenems()),
formatting_type = 14)
```
@ -98,11 +98,11 @@ antibiogram(example_isolates,
| *S. hominis* | | 92% (84-97%) | | | | 85% (74-93%) |
| *S. pneumoniae* | 0% (0-3%) | 0% (0-3%) | | 0% (0-3%) | | 0% (0-3%) |
In combination antibiograms, it is clear that combined antibiotics yield higher empiric coverage:
In combination antibiograms, it is clear that combined antimicrobials yield higher empiric coverage:
```r
antibiogram(example_isolates,
antibiotics = c("TZP", "TZP+TOB", "TZP+GEN"),
antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"),
mo_transform = "gramstain",
formatting_type = 14)
```
@ -116,7 +116,7 @@ Like many other functions in this package, `antibiogram()` comes with support fo
```r
antibiogram(example_isolates,
antibiotics = c("cipro", "tobra", "genta"), # any arbitrary name or code will work
antimicrobials = c("cipro", "tobra", "genta"), # any arbitrary name or code will work
mo_transform = "gramstain",
ab_transform = "name",
formatting_type = 14,

View File

@ -18,23 +18,23 @@
}
}
\usage{
antibiogram(x, antibiotics = where(is.sir), mo_transform = "shortname",
antibiogram(x, antimicrobials = where(is.sir), mo_transform = "shortname",
ab_transform = "name", syndromic_group = NULL, add_total_n = FALSE,
only_all_tested = FALSE, digits = ifelse(wisca, 1, 0),
formatting_type = getOption("AMR_antibiogram_formatting_type",
ifelse(wisca, 14, 18)), col_mo = NULL, language = get_AMR_locale(),
minimum = 30, combine_SI = TRUE, sep = " + ", wisca = FALSE,
simulations = 1000, conf_interval = 0.95, interval_side = "two-tailed",
info = interactive())
info = interactive(), ...)
wisca(x, antibiotics = where(is.sir), ab_transform = "name",
wisca(x, antimicrobials = where(is.sir), ab_transform = "name",
syndromic_group = NULL, add_total_n = FALSE, only_all_tested = FALSE,
digits = 1,
formatting_type = getOption("AMR_antibiogram_formatting_type", 14),
col_mo = NULL, language = get_AMR_locale(), minimum = 30,
combine_SI = TRUE, sep = " + ", simulations = 1000,
conf_interval = 0.95, interval_side = "two-tailed",
info = interactive())
info = interactive(), ...)
retrieve_wisca_parameters(wisca_model, ...)
@ -48,7 +48,7 @@ retrieve_wisca_parameters(wisca_model, ...)
\arguments{
\item{x}{a \link{data.frame} containing at least a column with microorganisms and columns with antimicrobial results (class 'sir', see \code{\link[=as.sir]{as.sir()}})}
\item{antibiotics}{vector of any antimicrobial name or code (will be evaluated with \code{\link[=as.ab]{as.ab()}}, column name of \code{x}, or (any combinations of) \link[=antimicrobial_selectors]{antimicrobial selectors} such as \code{\link[=aminoglycosides]{aminoglycosides()}} or \code{\link[=carbapenems]{carbapenems()}}. For combination antibiograms, this can also be set to values separated with \code{"+"}, such as \code{"TZP+TOB"} or \code{"cipro + genta"}, given that columns resembling such antimicrobials exist in \code{x}. See \emph{Examples}.}
\item{antimicrobials}{vector of any antimicrobial name or code (will be evaluated with \code{\link[=as.ab]{as.ab()}}, column name of \code{x}, or (any combinations of) \link[=antimicrobial_selectors]{antimicrobial selectors} such as \code{\link[=aminoglycosides]{aminoglycosides()}} or \code{\link[=carbapenems]{carbapenems()}}. For combination antibiograms, this can also be set to values separated with \code{"+"}, such as \code{"TZP+TOB"} or \code{"cipro + genta"}, given that columns resembling such antimicrobials exist in \code{x}. See \emph{Examples}.}
\item{mo_transform}{a character to transform microorganism input - must be \code{"name"}, \code{"shortname"} (default), \code{"gramstain"}, or one of the column names of the \link{microorganisms} data set: "mo", "fullname", "status", "kingdom", "phylum", "class", "order", "family", "genus", "species", "subspecies", "rank", "ref", "oxygen_tolerance", "source", "lpsn", "lpsn_parent", "lpsn_renamed_to", "mycobank", "mycobank_parent", "mycobank_renamed_to", "gbif", "gbif_parent", "gbif_renamed_to", "prevalence", or "snomed". Can also be \code{NULL} to not transform the input or \code{NA} to consider all microorganisms 'unknown'.}
@ -84,10 +84,10 @@ retrieve_wisca_parameters(wisca_model, ...)
\item{info}{a \link{logical} to indicate info should be printed - the default is \code{TRUE} only in interactive mode}
\item{wisca_model}{the outcome of \code{\link[=wisca]{wisca()}} or \code{\link[=antibiogram]{antibiogram(..., wisca = TRUE)}}}
\item{...}{when used in \link[knitr:kable]{R Markdown or Quarto}: arguments passed on to \code{\link[knitr:kable]{knitr::kable()}} (otherwise, has no use)}
\item{wisca_model}{the outcome of \code{\link[=wisca]{wisca()}} or \code{\link[=antibiogram]{antibiogram(..., wisca = TRUE)}}}
\item{object}{an \code{\link[=antibiogram]{antibiogram()}} object}
\item{italicise}{a \link{logical} to indicate whether the microorganism names in the \link[knitr:kable]{knitr} table should be made italic, using \code{\link[=italicise_taxonomy]{italicise_taxonomy()}}.}
@ -153,7 +153,7 @@ Case example: Susceptibility of \emph{Pseudomonas aeruginosa} to piperacillin/ta
Code example:
\if{html}{\out{<div class="sourceCode r">}}\preformatted{antibiogram(your_data,
antibiotics = "TZP")
antimicrobials = "TZP")
}\if{html}{\out{</div>}}
\item \strong{Combination Antibiogram}
@ -162,7 +162,7 @@ Case example: Additional susceptibility of \emph{Pseudomonas aeruginosa} to TZP
Code example:
\if{html}{\out{<div class="sourceCode r">}}\preformatted{antibiogram(your_data,
antibiotics = c("TZP", "TZP+TOB", "TZP+GEN"))
antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"))
}\if{html}{\out{</div>}}
\item \strong{Syndromic Antibiogram}
@ -171,7 +171,7 @@ Case example: Susceptibility of \emph{Pseudomonas aeruginosa} to TZP among respi
Code example:
\if{html}{\out{<div class="sourceCode r">}}\preformatted{antibiogram(your_data,
antibiotics = penicillins(),
antimicrobials = penicillins(),
syndromic_group = "ward")
}\if{html}{\out{</div>}}
\item \strong{Weighted-Incidence Syndromic Combination Antibiogram (WISCA)}
@ -181,12 +181,12 @@ WISCA can be applied to any antibiogram, see the section \emph{Explaining WISCA}
Code example:
\if{html}{\out{<div class="sourceCode r">}}\preformatted{antibiogram(your_data,
antibiotics = c("TZP", "TZP+TOB", "TZP+GEN"),
antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"),
wisca = TRUE)
# this is equal to:
wisca(your_data,
antibiotics = c("TZP", "TZP+TOB", "TZP+GEN"))
antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"))
}\if{html}{\out{</div>}}
WISCA uses a sophisticated Bayesian decision model to combine both local and pooled antimicrobial resistance data. This approach not only evaluates local patterns but can also draw on multi-centre datasets to improve regimen accuracy, even in low-incidence infections like paediatric bloodstream infections (BSIs).
@ -202,7 +202,7 @@ Code example:
\if{html}{\out{<div class="sourceCode r">}}\preformatted{library(dplyr)
your_data \%>\%
group_by(has_sepsis, is_neonate, sex) \%>\%
wisca(antibiotics = c("TZP", "TZP+TOB", "TZP+GEN"))
wisca(antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"))
}\if{html}{\out{</div>}}
}
@ -218,12 +218,12 @@ At admission, no pathogen information is available.
\item Code example:
\if{html}{\out{<div class="sourceCode r">}}\preformatted{antibiogram(your_data,
antibiotics = selected_regimens,
antimicrobials = selected_regimens,
mo_transform = NA) # all pathogens set to `NA`
# preferred: use WISCA
wisca(your_data,
antibiotics = selected_regimens)
antimicrobials = selected_regimens)
}\if{html}{\out{</div>}}
}
\item \strong{Refinement with Gram Stain Results}
@ -234,7 +234,7 @@ When a blood culture becomes positive, the Gram stain provides an initial and cr
\item Code example:
\if{html}{\out{<div class="sourceCode r">}}\preformatted{antibiogram(your_data,
antibiotics = selected_regimens,
antimicrobials = selected_regimens,
mo_transform = "gramstain") # all pathogens set to Gram-pos/Gram-neg
}\if{html}{\out{</div>}}
}
@ -246,7 +246,7 @@ After cultivation of the pathogen, full pathogen identification allows precise t
\item Code example:
\if{html}{\out{<div class="sourceCode r">}}\preformatted{antibiogram(your_data,
antibiotics = selected_regimens,
antimicrobials = selected_regimens,
mo_transform = "shortname") # all pathogens set to 'G. species', e.g., E. coli
}\if{html}{\out{</div>}}
}
@ -337,17 +337,17 @@ example_isolates
# Traditional antibiogram ----------------------------------------------
antibiogram(example_isolates,
antibiotics = c(aminoglycosides(), carbapenems())
antimicrobials = c(aminoglycosides(), carbapenems())
)
antibiogram(example_isolates,
antibiotics = aminoglycosides(),
antimicrobials = aminoglycosides(),
ab_transform = "atc",
mo_transform = "gramstain"
)
antibiogram(example_isolates,
antibiotics = carbapenems(),
antimicrobials = carbapenems(),
ab_transform = "name",
mo_transform = "name"
)
@ -355,15 +355,15 @@ antibiogram(example_isolates,
# Combined antibiogram -------------------------------------------------
# combined antibiotics yield higher empiric coverage
# combined antimicrobials yield higher empiric coverage
antibiogram(example_isolates,
antibiotics = c("TZP", "TZP+TOB", "TZP+GEN"),
antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"),
mo_transform = "gramstain"
)
# names of antibiotics do not need to resemble columns exactly:
# names of antimicrobials do not need to resemble columns exactly:
antibiogram(example_isolates,
antibiotics = c("Cipro", "cipro + genta"),
antimicrobials = c("Cipro", "cipro + genta"),
mo_transform = "gramstain",
ab_transform = "name",
sep = " & "
@ -374,7 +374,7 @@ antibiogram(example_isolates,
# the data set could contain a filter for e.g. respiratory specimens
antibiogram(example_isolates,
antibiotics = c(aminoglycosides(), carbapenems()),
antimicrobials = c(aminoglycosides(), carbapenems()),
syndromic_group = "ward"
)
@ -384,7 +384,7 @@ ex1 <- example_isolates[which(mo_genus() == "Escherichia"), ]
# with a custom language, though this will be determined automatically
# (i.e., this table will be in Spanish on Spanish systems)
antibiogram(ex1,
antibiotics = aminoglycosides(),
antimicrobials = aminoglycosides(),
ab_transform = "name",
syndromic_group = ifelse(ex1$ward == "ICU",
"UCI", "No UCI"
@ -397,7 +397,7 @@ antibiogram(ex1,
# WISCA are not stratified by species, but rather on syndromes
antibiogram(example_isolates,
antibiotics = c("TZP", "TZP+TOB", "TZP+GEN"),
antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"),
syndromic_group = "ward",
wisca = TRUE
)
@ -406,7 +406,7 @@ antibiogram(example_isolates,
# Print the output for R Markdown / Quarto -----------------------------
ureido <- antibiogram(example_isolates,
antibiotics = ureidopenicillins(),
antimicrobials = ureidopenicillins(),
syndromic_group = "ward",
wisca = TRUE
)
@ -421,11 +421,11 @@ if (requireNamespace("knitr")) {
# Generate plots with ggplot2 or base R --------------------------------
ab1 <- antibiogram(example_isolates,
antibiotics = c("AMC", "CIP", "TZP", "TZP+TOB"),
antimicrobials = c("AMC", "CIP", "TZP", "TZP+TOB"),
mo_transform = "gramstain"
)
ab2 <- antibiogram(example_isolates,
antibiotics = c("AMC", "CIP", "TZP", "TZP+TOB"),
antimicrobials = c("AMC", "CIP", "TZP", "TZP+TOB"),
mo_transform = "gramstain",
syndromic_group = "ward"
)

View File

@ -85,7 +85,7 @@ This AMR package honours this insight. Use \code{\link[=susceptibility]{suscepti
\section{Combination Therapy}{
When using more than one variable for \code{...} (= combination therapy), use \code{only_all_tested} to only count isolates that are tested for all antibiotics/variables that you test them for. See this example for two antimicrobials, Drug A and Drug B, about how \code{\link[=susceptibility]{susceptibility()}} works to calculate the \%SI:
When using more than one variable for \code{...} (= combination therapy), use \code{only_all_tested} to only count isolates that are tested for all antimicrobials/variables that you test them for. See this example for two antimicrobials, Drug A and Drug B, about how \code{\link[=susceptibility]{susceptibility()}} works to calculate the \%SI:
\if{html}{\out{<div class="sourceCode">}}\preformatted{--------------------------------------------------------------------
only_all_tested = FALSE only_all_tested = TRUE

View File

@ -99,7 +99,7 @@ The function \code{\link[=proportion_df]{proportion_df()}} takes any variable fr
}
\section{Combination Therapy}{
When using more than one variable for \code{...} (= combination therapy), use \code{only_all_tested} to only count isolates that are tested for all antibiotics/variables that you test them for. See this example for two antimicrobials, Drug A and Drug B, about how \code{\link[=susceptibility]{susceptibility()}} works to calculate the \%SI:
When using more than one variable for \code{...} (= combination therapy), use \code{only_all_tested} to only count isolates that are tested for all antimicrobials/variables that you test them for. See this example for two antimicrobials, Drug A and Drug B, about how \code{\link[=susceptibility]{susceptibility()}} works to calculate the \%SI:
\if{html}{\out{<div class="sourceCode">}}\preformatted{--------------------------------------------------------------------
only_all_tested = FALSE only_all_tested = TRUE