From faa9ae0d85283804870c8bbc8e762cd90bd9947d Mon Sep 17 00:00:00 2001 From: Matthijs Berends Date: Tue, 29 Apr 2025 16:15:18 +0200 Subject: [PATCH] (v2.1.1.9260) fix antibiogram --- DESCRIPTION | 4 +- NEWS.md | 2 +- R/aa_amr-package.R | 6 +- R/aa_helper_functions.R | 6 +- R/antibiogram.R | 139 +- R/sir.R | 54 +- data-raw/parallel_test_sir.R | 2128 ------------------------------- data-raw/wisca_reprex.R | 23 + index.md | 18 +- man/AMR.Rd | 6 +- man/WHONET.Rd | 2 +- man/ab_property.Rd | 2 +- man/antimicrobial_selectors.Rd | 2 +- man/antimicrobials.Rd | 2 +- man/as.ab.Rd | 2 +- man/as.av.Rd | 2 +- man/as.mo.Rd | 2 +- man/as.sir.Rd | 2 +- man/av_property.Rd | 2 +- man/clinical_breakpoints.Rd | 2 +- man/dosage.Rd | 2 +- man/eucast_rules.Rd | 2 +- man/example_isolates.Rd | 2 +- man/example_isolates_unclean.Rd | 2 +- man/intrinsic_resistant.Rd | 2 +- man/microorganisms.Rd | 2 +- man/microorganisms.codes.Rd | 2 +- man/microorganisms.groups.Rd | 2 +- man/mo_matching_score.Rd | 2 +- man/mo_property.Rd | 2 +- vignettes/welcome_to_AMR.Rmd | 52 +- 31 files changed, 195 insertions(+), 2283 deletions(-) delete mode 100644 data-raw/parallel_test_sir.R create mode 100644 data-raw/wisca_reprex.R diff --git a/DESCRIPTION b/DESCRIPTION index adc5fda52..3fda2c1fb 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: AMR -Version: 2.1.1.9259 -Date: 2025-04-27 +Version: 2.1.1.9260 +Date: 2025-04-29 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 diff --git a/NEWS.md b/NEWS.md index dc23e31dc..8e77716bc 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,4 +1,4 @@ -# AMR 2.1.1.9259 +# AMR 2.1.1.9260 *(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).)* diff --git a/R/aa_amr-package.R b/R/aa_amr-package.R index 98dd21290..cbbe2b540 100755 --- a/R/aa_amr-package.R +++ b/R/aa_amr-package.R @@ -32,11 +32,11 @@ #' @description #' Welcome to the `AMR` package. #' -#' The `AMR` package is a peer-reviewed, [free and open-source](https://amr-for-r.org/#copyright) R package with [zero dependencies](https://en.wikipedia.org/wiki/Dependency_hell) to simplify the analysis and prediction of Antimicrobial Resistance (AMR) and to work with microbial and antimicrobial data and properties, by using evidence-based methods. **Our aim is to provide a standard** for clean and reproducible AMR data analysis, that can therefore empower epidemiological analyses to continuously enable surveillance and treatment evaluation in any setting. [Many different researchers](https://amr-for-r.org/authors.html) from around the globe are continually helping us to make this a successful and durable project! +#' The `AMR` package is a peer-reviewed, [free and open-source](https://amr-for-r.org/#copyright) R package with [zero dependencies](https://en.wikipedia.org/wiki/Dependency_hell) to simplify the analysis and prediction of Antimicrobial Resistance (AMR) and to work with microbial and antimicrobial data and properties, by using evidence-based methods. **Our aim is to provide a standard** for clean and reproducible AMR data analysis, that can therefore empower epidemiological analyses to continuously enable surveillance and treatment evaluation in any setting. We are a team of [many different researchers](https://amr-for-r.org/authors.html) from around the globe to make this a successful and durable project! #' #' This work was published in the Journal of Statistical Software (Volume 104(3); \doi{10.18637/jss.v104.i03}) and formed the basis of two PhD theses (\doi{10.33612/diss.177417131} and \doi{10.33612/diss.192486375}). #' -#' After installing this package, R knows [**`r format_included_data_number(AMR::microorganisms)` microorganisms**](https://amr-for-r.org/reference/microorganisms.html) (updated `r format(TAXONOMY_VERSION$GBIF$accessed_date, "%B %Y")`) and all [**`r format_included_data_number(nrow(AMR::antimicrobials) + nrow(AMR::antivirals))` antibiotic, antimycotic and antiviral drugs**](https://amr-for-r.org/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 public [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 [**`r AMR:::format_included_data_number(AMR::microorganisms)` distinct microbial species**](https://amr-for-r.org/reference/microorganisms.html) (updated June 2024) and all [**`r AMR:::format_included_data_number(NROW(AMR::antimicrobials) + NROW(AMR::antivirals))` antimicrobial and antiviral drugs**](https://amr-for-r.org/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 `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, grepl("CLSI", guideline))$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, grepl("CLSI", guideline))$guideline)))` and EUCAST `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, grepl("EUCAST", guideline))$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, grepl("EUCAST", guideline))$guideline)))` 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) and the [University Medical Center Groningen](https://www.umcg.nl). #' #' The `AMR` package is available in `r vector_and(vapply(FUN.VALUE = character(1), LANGUAGES_SUPPORTED_NAMES, function(x) x$exonym), quotes = FALSE, sort = FALSE)`. Antimicrobial drug (group) names and colloquial microorganism names are provided in these languages. #' @section Download Our Reference Data: @@ -44,7 +44,7 @@ #' #' For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. #' -#' Visit [our website for direct download links](https://amr-for-r.org/articles/datasets.html), or explore the actual files in [our GitHub repository](https://github.com/msberends/AMR/tree/main/data-raw). +#' Visit [our website for direct download links](https://amr-for-r.org/articles/datasets.html), or explore the actual files in [our GitHub repository](https://github.com/msberends/AMR/tree/main/data-raw/datasets). #' @source #' To cite AMR in publications use: #' diff --git a/R/aa_helper_functions.R b/R/aa_helper_functions.R index df2c31502..f168a3244 100644 --- a/R/aa_helper_functions.R +++ b/R/aa_helper_functions.R @@ -538,9 +538,9 @@ word_wrap <- function(..., txt = parts[parts %in% c("antimicrobials", "microorganisms", "microorganisms.codes", "microorganisms.groups")] ) # text starting with `?` must also lead to the help page - parts[parts %like% "^[?]"] <- font_url( - url = paste0("ide:help:AMR::", gsub("?", "", parts[parts %like% "^[?]"], fixed = TRUE)), - txt = parts[parts %like% "^[?]"] + parts[parts %like% "^[?].+"] <- font_url( + url = paste0("ide:help:AMR::", gsub("?", "", parts[parts %like% "^[?].+"], fixed = TRUE)), + txt = parts[parts %like% "^[?].+"] ) msg <- paste0(parts, collapse = "`") } diff --git a/R/antibiogram.R b/R/antibiogram.R index 127d5004d..6c9f24cd6 100755 --- a/R/antibiogram.R +++ b/R/antibiogram.R @@ -682,9 +682,8 @@ antibiogram.default <- function(x, wisca_parameters <- data.frame() + # WISCA START if (wisca == TRUE) { - # WISCA ---- - if (isTRUE(has_syndromic_group)) { colnames(out)[1] <- "syndromic_group" out_wisca <- out %pm>% @@ -708,9 +707,6 @@ antibiogram.default <- function(x, 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 - out_wisca$p_susceptible[is.nan(out_wisca$p_susceptible)] <- 0 - if (isTRUE(has_syndromic_group)) { out$group <- paste(out$syndromic_group, out$ab) out_wisca$group <- paste(out_wisca$syndromic_group, out_wisca$ab) @@ -719,31 +715,6 @@ antibiogram.default <- function(x, out_wisca$group <- out_wisca$ab } - # create the WISCA parameters, including our priors/posteriors - out$gamma_posterior <- NA_real_ - out$beta_posterior_1 <- NA_real_ - out$beta_posterior_2 <- NA_real_ - - for (i in seq_len(NROW(out))) { - out_current <- out[i, , drop = FALSE] - - ## 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 progress <- progress_ticker( @@ -754,42 +725,28 @@ antibiogram.default <- function(x, ) on.exit(close(progress)) - # run WISCA + # run WISCA per group for (group in unique(wisca_parameters$group)) { - params_current <- wisca_parameters[which(wisca_parameters$group == group), , drop = FALSE] + params_current <- wisca_parameters[wisca_parameters$group == group, , drop = FALSE] if (sum(params_current$n_tested, na.rm = TRUE) == 0) { next } - # Monte Carlo simulation - coverage_simulations <- replicate(simulations, { - progress$tick() + # prepare priors + priors_current <- create_wisca_priors(params_current) - # simulate pathogen incidence - # = Dirichlet (Gamma) parameters - random_incidence <- stats::runif(n = 1, min = 0, max = 1) - simulated_incidence <- stats::qgamma( - p = random_incidence, - shape = params_current$gamma_posterior, - scale = 1 - ) + # Monte Carlo simulations + coverage_simulations <- vapply( + FUN.VALUE = double(1), + seq_len(simulations), function(i) { + progress$tick() + simulate_coverage(priors_current) + } + ) - # normalise - simulated_incidence <- simulated_incidence / sum(simulated_incidence, na.rm = TRUE) - - # simulate susceptibility - # = Beta parameters - random_susceptibity <- stats::runif(n = 1, min = 0, max = 1) - simulated_susceptibility <- stats::qbeta( - p = random_susceptibity, - shape1 = params_current$beta_posterior_1, - shape2 = params_current$beta_posterior_2 - ) - sum(simulated_incidence * simulated_susceptibility, na.rm = TRUE) - }) - - # calculate coverage statistics + # summarise results coverage_mean <- mean(coverage_simulations) + if (interval_side == "two-tailed") { probs <- c((1 - conf_interval) / 2, 1 - (1 - conf_interval) / 2) } else if (interval_side == "left") { @@ -797,17 +754,20 @@ antibiogram.default <- function(x, } else if (interval_side == "right") { probs <- c(1 - conf_interval, 1) } + coverage_ci <- unname(stats::quantile(coverage_simulations, probs = probs)) - out_wisca$coverage[which(out_wisca$group == group)] <- coverage_mean - out_wisca$lower_ci[which(out_wisca$group == group)] <- coverage_ci[1] - out_wisca$upper_ci[which(out_wisca$group == group)] <- coverage_ci[2] + out_wisca$coverage[out_wisca$group == group] <- coverage_mean + out_wisca$lower_ci[out_wisca$group == group] <- coverage_ci[1] + out_wisca$upper_ci[out_wisca$group == group] <- coverage_ci[2] } - # remove progress bar from console + close(progress) - # prepare for definitive output + + # final output preparation out <- out_wisca wisca_parameters <- wisca_parameters[, colnames(wisca_parameters)[!colnames(wisca_parameters) %in% c(levels(NA_sir_), "lower_ci", "upper_ci", "group")], drop = FALSE] + if (isTRUE(has_syndromic_group)) { long_numeric <- out_wisca %pm>% pm_ungroup() %pm>% @@ -1346,3 +1306,56 @@ knit_print.antibiogram <- function(x, italicise = TRUE, na = getOption("knitr.ka out <- paste(c("", "", knitr::kable(x, ..., output = FALSE)), collapse = "\n") knitr::asis_output(out) } + +create_wisca_priors <- function(data) { + pathogens <- unique(data$mo) + n_pathogens <- length(pathogens) + + # Dirichlet prior (gamma parameters) + gamma_prior <- rep(1, times = n_pathogens) + multinomial_obs <- data$n_total + gamma_posterior <- gamma_prior + multinomial_obs + + # beta priors + beta_prior_alpha <- rep(1, times = n_pathogens) + beta_prior_beta <- rep(1, times = n_pathogens) + + r <- data$n_susceptible + n <- data$n_tested + diff_nr <- n - r + + beta_posterior_1 <- beta_prior_alpha + r + beta_posterior_2 <- beta_prior_beta + diff_nr + + list( + gamma_posterior = gamma_posterior, + beta_posterior_1 = beta_posterior_1, + beta_posterior_2 = beta_posterior_2 + ) +} + +simulate_coverage <- function(params) { + n_pathogens <- length(params$gamma_posterior) + + # random draws per pathogen + random_incidence <- runif(n = n_pathogens) + random_susceptibility <- runif(n = n_pathogens) + + simulated_incidence <- stats::qgamma( + p = random_incidence, + shape = params$gamma_posterior, + scale = 1 + ) + + # normalise incidence + simulated_incidence <- simulated_incidence / sum(simulated_incidence, na.rm = TRUE) + + simulated_susceptibility <- stats::qbeta( + p = random_susceptibility, + shape1 = params$beta_posterior_1, + shape2 = params$beta_posterior_2 + ) + + # weighted coverage + sum(simulated_incidence * simulated_susceptibility, na.rm = TRUE) +} diff --git a/R/sir.R b/R/sir.R index 4becfdbb2..352651dfa 100755 --- a/R/sir.R +++ b/R/sir.R @@ -729,7 +729,7 @@ as.sir.data.frame <- function(x, # -- MO col_mo.bak <- col_mo if (is.null(col_mo)) { - col_mo <- search_type_in_df(x = x, type = "mo", info = FALSE) + col_mo <- search_type_in_df(x = x, type = "mo", info = info) } # -- host @@ -742,7 +742,7 @@ as.sir.data.frame <- function(x, } if (breakpoint_type == "animal") { if (is.null(host)) { - host <- search_type_in_df(x = x, type = "host", add_col_prefix = FALSE) + host <- search_type_in_df(x = x, type = "host", add_col_prefix = FALSE, info = info) } else if (length(host) == 1 && as.character(host) %in% colnames(x)) { host <- x[[as.character(host)]] } @@ -753,7 +753,7 @@ as.sir.data.frame <- function(x, # -- UTIs col_uti <- uti if (is.null(col_uti)) { - col_uti <- search_type_in_df(x = x, type = "uti", add_col_prefix = FALSE) + col_uti <- search_type_in_df(x = x, type = "uti", add_col_prefix = FALSE, info = info) } if (!is.null(col_uti)) { if (is.logical(col_uti)) { @@ -773,7 +773,7 @@ as.sir.data.frame <- function(x, } } else { # col_uti is still NULL - look for specimen column and make logicals of the urines - col_specimen <- suppressMessages(search_type_in_df(x = x, type = "specimen")) + col_specimen <- suppressMessages(search_type_in_df(x = x, type = "specimen", info = info)) if (!is.null(col_specimen)) { uti <- x[, col_specimen, drop = TRUE] %like% "urin" values <- sort(unique(x[uti, col_specimen, drop = TRUE])) @@ -846,7 +846,7 @@ as.sir.data.frame <- function(x, stop_if(is.null(col_mo), "`col_mo` must be set") # if not null, we already found it, now find again so a message will show if (is.null(col_mo.bak)) { - col_mo <- search_type_in_df(x = x, type = "mo") + col_mo <- search_type_in_df(x = x, type = "mo", info = info) } x_mo <- as.mo(x[, col_mo, drop = TRUE], info = info) } @@ -854,10 +854,17 @@ as.sir.data.frame <- function(x, # set up parallel computing n_cores <- get_n_cores(max_cores = max_cores) n_cores <- min(n_cores, length(ab_cols)) # never more cores than variables required - if (isTRUE(parallel) && .Platform$OS.type != "windows" && getRversion() < "4.0.0") { - n_cores <- 1 - if (isTRUE(info)) { - warning("Parallel computing is not available on unix in R < 4.0", call. = FALSE) + if (isTRUE(parallel) && (.Platform$OS.type == "windows" || getRversion() < "4.0.0")) { + cl <- tryCatch(parallel::makeCluster(n_cores, type = "PSOCK"), + error = function(e) { + if (isTRUE(info)) { + message_("Could not create parallel cluster, using single-core computation. Error message: ", e$message, add_fn = font_red) + } + return(NULL) + } + ) + if (is.null(cl)) { + n_cores <- 1 } } @@ -959,10 +966,10 @@ as.sir.data.frame <- function(x, if (isTRUE(parallel) && n_cores > 1 && length(ab_cols) > 1) { if (isTRUE(info)) { message() - message_("Running in parallel mode using ", n_cores, " out of ", get_n_cores(Inf), " cores, on columns ", vector_and(font_bold(ab_cols, collapse = NULL), quotes = "'", sort = FALSE), "...", as_note = FALSE, appendLF = FALSE, add_fn = font_red) + message_("Running in parallel mode using ", n_cores, " out of ", get_n_cores(Inf), " cores, on columns ", vector_and(font_bold(ab_cols, collapse = NULL), quotes = "'", sort = FALSE), "...", as_note = FALSE, appendLF = FALSE) } if (.Platform$OS.type == "windows" || getRversion() < "4.0.0") { - cl <- parallel::makeCluster(n_cores, type = "PSOCK") + # `cl` has been created in the part above before the `run_as_sir_column` function on.exit(parallel::stopCluster(cl), add = TRUE) parallel::clusterExport(cl, varlist = c( "x", "x.bak", "x_mo", "ab_cols", "types", @@ -974,12 +981,13 @@ as.sir.data.frame <- function(x, ), envir = environment()) result_list <- parallel::parLapply(cl, seq_along(ab_cols), run_as_sir_column) } else { + # R>=4.0 on unix result_list <- parallel::mclapply(seq_along(ab_cols), run_as_sir_column, mc.cores = n_cores) } if (isTRUE(info)) { - message_(" Done.", appendLF = TRUE, as_note = FALSE, add_fn = font_red) + message_(font_green_bg(" DONE "), as_note = FALSE) message() - message_("Run `sir_interpretation_history()` to retrieve a logbook with all the details of the breakpoint interpretations.", add_fn = font_green) + message_("Run `sir_interpretation_history()` to retrieve a logbook with all details of the breakpoint interpretations.", add_fn = font_green) } } else { # sequential mode (non-parallel) @@ -1116,7 +1124,7 @@ as_sir_method <- function(method_short, if (isTRUE(info) && message_not_thrown_before("as.sir", "sir_interpretation_history")) { message() - message_("Run `sir_interpretation_history()` afterwards to retrieve a logbook with all the details of the breakpoint interpretations.\n\n", add_fn = font_green) + message_("Run `sir_interpretation_history()` afterwards to retrieve a logbook with all details of the breakpoint interpretations.\n\n", add_fn = font_green) } current_df <- tryCatch(get_current_data(NA, 0), error = function(e) NULL) @@ -1200,7 +1208,7 @@ as_sir_method <- function(method_short, mo <- NULL try( { - mo <- suppressMessages(search_type_in_df(df, "mo", add_col_prefix = FALSE)) + mo <- suppressMessages(search_type_in_df(df, "mo", add_col_prefix = FALSE, info = info)) }, silent = TRUE ) @@ -1236,7 +1244,7 @@ as_sir_method <- function(method_short, uti <- NULL try( { - uti <- suppressMessages(search_type_in_df(df, "uti", add_col_prefix = FALSE)) + uti <- suppressMessages(search_type_in_df(df, "uti", add_col_prefix = FALSE, info = info)) }, silent = TRUE ) @@ -1441,14 +1449,7 @@ as_sir_method <- function(method_short, if (nrow(breakpoints) == 0) { # apparently no breakpoints found if (isTRUE(info)) { - message( - paste0(font_rose_bg(" WARNING "), "\n"), - font_black(paste0( - " ", AMR_env$bullet_icon, " No ", method_coerced, " breakpoints available for ", - suppressMessages(suppressWarnings(ab_name(unique(ab_coerced), language = NULL, tolower = TRUE, info = info))), - " (", unique(ab_coerced), ")." - ), collapse = "\n") - ) + message(font_grey_bg(font_black(" NO BREAKPOINTS "))) } load_mo_uncertainties(metadata_mo) @@ -1829,12 +1830,13 @@ as_sir_method <- function(method_short, message(font_yellow_bg(" NOTE ")) } notes <- unique(notes) - if (isTRUE(verbose) || length(notes) == 1 || NROW(AMR_env$sir_interpretation_history) == 0) { + # if (isTRUE(verbose) || length(notes) == 1 || NROW(AMR_env$sir_interpretation_history) == 0) { + if (isTRUE(verbose)) { for (i in seq_along(notes)) { message(word_wrap(" ", AMR_env$bullet_icon, " ", notes[i], add_fn = font_black)) } } else { - message(word_wrap(" ", AMR_env$bullet_icon, " There were multiple notes. Print or View `sir_interpretation_history()` to examine them, or use `as.sir(..., verbose = TRUE)` next time to directly print them here.", add_fn = font_black)) + # message(word_wrap(" ", AMR_env$bullet_icon, " There were multiple notes. Print or View `sir_interpretation_history()` to examine them, or use `as.sir(..., verbose = TRUE)` next time to directly print them here.", add_fn = font_black)) } } else { message(font_green_bg(" OK ")) diff --git a/data-raw/parallel_test_sir.R b/data-raw/parallel_test_sir.R deleted file mode 100644 index 82ec2ad4d..000000000 --- a/data-raw/parallel_test_sir.R +++ /dev/null @@ -1,2128 +0,0 @@ -# ==================================================================== # -# TITLE: # -# AMR: An R Package for Working with Antimicrobial Resistance Data # -# # -# SOURCE CODE: # -# https://github.com/msberends/AMR # -# # -# PLEASE CITE THIS SOFTWARE AS: # -# Berends MS, Luz CF, Friedrich AW, et al. (2022). # -# AMR: An R Package for Working with Antimicrobial Resistance Data. # -# Journal of Statistical Software, 104(3), 1-31. # -# https://doi.org/10.18637/jss.v104.i03 # -# # -# Developed at the University of Groningen and the University Medical # -# Center Groningen in The Netherlands, in collaboration with many # -# colleagues from around the world, see our website. # -# # -# This R package is free software; you can freely use and distribute # -# it for both personal and commercial purposes under the terms of the # -# GNU General Public License version 2.0 (GNU GPL-2), as published by # -# the Free Software Foundation. # -# We created this package for both routine data analysis and academic # -# research and it was publicly released in the hope that it will be # -# useful, but it comes WITHOUT ANY WARRANTY OR LIABILITY. # -# # -# Visit our website for the full manual and a complete tutorial about # -# how to conduct AMR data analysis: https://amr-for-r.org # -# ==================================================================== # - -#' Interpret MIC and Disk Diffusion as SIR, or Clean Existing SIR Data -#' -#' @description Clean up existing SIR values, or interpret minimum inhibitory concentration (MIC) values and disk diffusion diameters according to EUCAST or CLSI. [as.sir()] transforms the input to a new class [`sir`], which is an ordered [factor] containing the levels `S`, `SDD`, `I`, `R`, `NI`. -#' -#' Breakpoints are currently implemented from EUCAST `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "EUCAST")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "EUCAST")$guideline)))` and CLSI `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI")$guideline)))`, see *Details*. All breakpoints used for interpretation are available in our [clinical_breakpoints] data set. -#' @rdname as.sir -#' @param x Vector of values (for class [`mic`]: MIC values in mg/L, for class [`disk`]: a disk diffusion radius in millimetres). -#' @param mo A vector (or column name) with [character]s that can be coerced to valid microorganism codes with [as.mo()], can be left empty to determine it automatically. -#' @param ab A vector (or column name) with [character]s that can be coerced to a valid antimicrobial drug code with [as.ab()]. -#' @param uti (Urinary Tract Infection) a vector (or column name) with [logical]s (`TRUE` or `FALSE`) to specify whether a UTI specific interpretation from the guideline should be chosen. For using [as.sir()] on a [data.frame], this can also be a column containing [logical]s or when left blank, the data set will be searched for a column 'specimen', and rows within this column containing 'urin' (such as 'urine', 'urina') will be regarded isolates from a UTI. See *Examples*. -#' @inheritParams first_isolate -#' @param guideline A guideline name (or column name) to use for SIR interpretation. Defaults to `r AMR::clinical_breakpoints$guideline[1]` (the latest implemented EUCAST guideline in the [AMR::clinical_breakpoints] data set), but can be set with the package option [`AMR_guideline`][AMR-options]. Currently supports EUCAST (`r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "EUCAST")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "EUCAST")$guideline)))`) and CLSI (`r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI")$guideline)))`), see *Details*. Using a column name allows for straightforward interpretation of historical data, which must be analysed in the context of, for example, different years. -#' @param capped_mic_handling A [character] string that controls how MIC values with a cap (i.e., starting with `<`, `<=`, `>`, or `>=`) are interpreted. Supports the following options: -#' -#' `"none"` -#' * `<=` and `>=` are treated as-is. -#' * `<` and `>` are treated as-is. -#' -#' `"conservative"` -#' * `<=` and `>=` return `"NI"` (non-interpretable) if the MIC is within the breakpoint guideline range. -#' * `<` always returns `"S"`, and `>` always returns `"R"`. -#' -#' `"standard"` (default) -#' * `<=` and `>=` return `"NI"` (non-interpretable) if the MIC is within the breakpoint guideline range. -#' * `<` and `>` are treated as-is. -#' -#' `"inverse"` -#' * `<=` and `>=` are treated as-is. -#' * `<` always returns `"S"`, and `>` always returns `"R"`. -#' -#' The default `"standard"` setting ensures cautious handling of uncertain values while preserving interpretability. This option can also be set with the package option [`AMR_capped_mic_handling`][AMR-options]. -#' @param add_intrinsic_resistance *(only useful when using a EUCAST guideline)* a [logical] to indicate whether intrinsic antibiotic resistance must also be considered for applicable bug-drug combinations, meaning that e.g. ampicillin will always return "R" in *Klebsiella* species. Determination is based on the [intrinsic_resistant] data set, that itself is based on `r format_eucast_version_nr(3.3)`. -#' @param substitute_missing_r_breakpoint A [logical] to indicate that a missing clinical breakpoints for R (resistant) must be substituted with R - the default is `FALSE`. Some (especially CLSI) breakpoints only have a breakpoint for S, meaning the outcome can only be `"S"` or `NA`. Setting this to `TRUE` will convert the `NA`s to `"R"` only if the R breakpoint is missing. Can also be set with the package option [`AMR_substitute_missing_r_breakpoint`][AMR-options]. -#' @param include_screening A [logical] to indicate that clinical breakpoints for screening are allowed - the default is `FALSE`. Can also be set with the package option [`AMR_include_screening`][AMR-options]. -#' @param include_PKPD A [logical] to indicate that PK/PD clinical breakpoints must be applied as a last resort - the default is `TRUE`. Can also be set with the package option [`AMR_include_PKPD`][AMR-options]. -#' @param breakpoint_type The type of breakpoints to use, either `r vector_or(clinical_breakpoints$type)`. ECOFF stands for Epidemiological Cut-Off values. The default is `"human"`, which can also be set with the package option [`AMR_breakpoint_type`][AMR-options]. If `host` is set to values of veterinary species, this will automatically be set to `"animal"`. -#' @param host A vector (or column name) with [character]s to indicate the host. Only useful for veterinary breakpoints, as it requires `breakpoint_type = "animal"`. The values can be any text resembling the animal species, even in any of the `r length(LANGUAGES_SUPPORTED)` supported languages of this package. For foreign languages, be sure to set the language with [set_AMR_locale()] (though it will be automatically guessed based on the system language). -#' @param verbose A [logical] to indicate that all notes should be printed during interpretation of MIC values or disk diffusion values. -#' @param reference_data A [data.frame] to be used for interpretation, which defaults to the [clinical_breakpoints] data set. Changing this argument allows for using own interpretation guidelines. This argument must contain a data set that is equal in structure to the [clinical_breakpoints] data set (same column names and column types). Please note that the `guideline` argument will be ignored when `reference_data` is manually set. -#' @param threshold Maximum fraction of invalid antimicrobial interpretations of `x`, see *Examples*. -#' @param conserve_capped_values Deprecated, use `capped_mic_handling` instead. -#' @param parallel A [logical] to indicate if parallel computing must be used, defaults to `TRUE`. -#' @param max_cores Maximum number of cores to use if `parallel = TRUE`. Use a negative value to subtract that number from the available number of cores, e.g. a value of `-2` on an 8-core machine means that 6 cores will be used. Defaults to `-1`. The available number of cores are detected using [parallelly::availableCores()] if that package is installed, and base \R's [parallel::detectCores()] otherwise. -#' @param ... For using on a [data.frame]: names of columns to apply [as.sir()] on (supports tidy selection such as `column1:column4`). Otherwise: arguments passed on to methods. -#' @details -#' *Note: The clinical breakpoints in this package were validated through, and imported from, [WHONET](https://whonet.org). The public use of this `AMR` package has been endorsed by both CLSI and EUCAST. See [clinical_breakpoints] for more information.* -#' -#' ### How it Works -#' -#' The [as.sir()] function can work in four ways: -#' -#' 1. For **cleaning raw / untransformed data**. The data will be cleaned to only contain valid values, namely: **S** for susceptible, **I** for intermediate or 'susceptible, increased exposure', **R** for resistant, **NI** for non-interpretable, and **SDD** for susceptible dose-dependent. Each of these can be set using a [regular expression][base::regex]. Furthermore, [as.sir()] will try its best to clean with some intelligence. For example, mixed values with SIR interpretations and MIC values such as `"<0.25; S"` will be coerced to `"S"`. Combined interpretations for multiple test methods (as seen in laboratory records) such as `"S; S"` will be coerced to `"S"`, but a value like `"S; I"` will return `NA` with a warning that the input is invalid. -#' -#' 2. For **interpreting minimum inhibitory concentration (MIC) values** according to EUCAST or CLSI. You must clean your MIC values first using [as.mic()], that also gives your columns the new data class [`mic`]. Also, be sure to have a column with microorganism names or codes. It will be found automatically, but can be set manually using the `mo` argument. -#' * Example to apply using `dplyr`: -#' ```r -#' your_data %>% mutate_if(is.mic, as.sir) -#' your_data %>% mutate(across(where(is.mic), as.sir)) -#' your_data %>% mutate_if(is.mic, as.sir, ab = "column_with_antibiotics", mo = "column_with_microorganisms") -#' your_data %>% mutate_if(is.mic, as.sir, ab = c("cipro", "ampicillin", ...), mo = c("E. coli", "K. pneumoniae", ...)) -#' -#' # for veterinary breakpoints, also set `host`: -#' your_data %>% mutate_if(is.mic, as.sir, host = "column_with_animal_species", guideline = "CLSI") -#' ``` -#' * Operators like "<=" will be stripped before interpretation. When using `capped_mic_handling = "conservative"`, an MIC value of e.g. ">2" will always return "R", even if the breakpoint according to the chosen guideline is ">=4". This is to prevent that capped values from raw laboratory data would not be treated conservatively. The default behaviour (`capped_mic_handling = "standard"`) considers ">2" to be lower than ">=4" and might in this case return "S" or "I". -#' * **Note:** When using CLSI as the guideline, MIC values must be log2-based doubling dilutions. Values not in this format, will be automatically rounded up to the nearest log2 level as CLSI instructs, and a warning will be thrown. -#' -#' 3. For **interpreting disk diffusion diameters** according to EUCAST or CLSI. You must clean your disk zones first using [as.disk()], that also gives your columns the new data class [`disk`]. Also, be sure to have a column with microorganism names or codes. It will be found automatically, but can be set manually using the `mo` argument. -#' * Example to apply using `dplyr`: -#' ```r -#' your_data %>% mutate_if(is.disk, as.sir) -#' your_data %>% mutate(across(where(is.disk), as.sir)) -#' your_data %>% mutate_if(is.disk, as.sir, ab = "column_with_antibiotics", mo = "column_with_microorganisms") -#' your_data %>% mutate_if(is.disk, as.sir, ab = c("cipro", "ampicillin", ...), mo = c("E. coli", "K. pneumoniae", ...)) -#' -#' # for veterinary breakpoints, also set `host`: -#' your_data %>% mutate_if(is.disk, as.sir, host = "column_with_animal_species", guideline = "CLSI") -#' ``` -#' -#' 4. For **interpreting a complete data set**, with automatic determination of MIC values, disk diffusion diameters, microorganism names or codes, and antimicrobial test results. This is done very simply by running `as.sir(your_data)`. -#' -#' **For points 2, 3 and 4: Use [sir_interpretation_history()]** to retrieve a [data.frame] with all results of all previous [as.sir()] calls. It also contains notes about interpretation, and the exact input and output values. -#' -#' ### Supported Guidelines -#' -#' For interpreting MIC values as well as disk diffusion diameters, currently implemented guidelines are: -#' - For **clinical microbiology**: EUCAST `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "EUCAST" & type == "human")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "EUCAST" & type == "human")$guideline)))` and CLSI `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI" & type == "human")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI" & type == "human")$guideline)))`; -#' - For **veterinary microbiology**: EUCAST `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "EUCAST" & type == "animal")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "EUCAST" & type == "animal")$guideline)))` and CLSI `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI" & type == "animal")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI" & type == "animal")$guideline)))`; -#' - For **ECOFFs** (Epidemiological Cut-off Values): EUCAST `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "EUCAST" & type == "ECOFF")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "EUCAST" & type == "ECOFF")$guideline)))` and CLSI `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI" & type == "ECOFF")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI" & type == "ECOFF")$guideline)))`. -#' -#' The `guideline` argument must be set to e.g., ``r paste0('"', subset(AMR::clinical_breakpoints, guideline %like% "EUCAST")$guideline[1], '"')`` or ``r paste0('"', subset(AMR::clinical_breakpoints, guideline %like% "CLSI")$guideline[1], '"')``. By simply using `"EUCAST"` (the default) or `"CLSI"` as input, the latest included version of that guideline will automatically be selected. Importantly, using a column name of your data instead, allows for straightforward interpretation of historical data that must be analysed in the context of, for example, different years. -#' -#' You can set your own data set using the `reference_data` argument. The `guideline` argument will then be ignored. -#' -#' It is also possible to set the default guideline with the package option [`AMR_guideline`][AMR-options] (e.g. in your `.Rprofile` file), such as: -#' -#' ``` -#' options(AMR_guideline = "CLSI") -#' options(AMR_guideline = "CLSI 2018") -#' options(AMR_guideline = "EUCAST 2020") -#' # or to reset: -#' options(AMR_guideline = NULL) -#' ``` -#' -#' For veterinary guidelines, these might be the best options: -#' -#' ``` -#' options(AMR_guideline = "CLSI") -#' options(AMR_breakpoint_type = "animal") -#' ``` -#' -###### TODO #187 When applying veterinary breakpoints (by setting `host` or by setting `breakpoint_type = "animal"`), the [CLSI VET09 guideline](https://clsi.org/standards/products/veterinary-medicine/documents/vet09/) will be applied to cope with missing animal species-specific breakpoints. -#' -#' ### After Interpretation -#' -#' After using [as.sir()], you can use the [eucast_rules()] defined by EUCAST to (1) apply inferred susceptibility and resistance based on results of other antimicrobials and (2) apply intrinsic resistance based on taxonomic properties of a microorganism. -#' -#' To determine which isolates are multi-drug resistant, be sure to run [mdro()] (which applies the MDR/PDR/XDR guideline from 2012 at default) on a data set that contains S/I/R values. Read more about [interpreting multidrug-resistant organisms here][mdro()]. -#' -#' ### Other -#' -#' The function [is.sir()] detects if the input contains class `sir`. If the input is a [data.frame] or [list], it iterates over all columns/items and returns a [logical] vector. -#' -#' The base R function [as.double()] can be used to retrieve quantitative values from a `sir` object: `"S"` = 1, `"I"`/`"SDD"` = 2, `"R"` = 3. All other values are rendered `NA` . **Note:** Do not use `as.integer()`, since that (because of how R works internally) will return the factor level indices, and not these aforementioned quantitative values. -#' -#' The function [is_sir_eligible()] returns `TRUE` when a column contains at most 5% invalid antimicrobial interpretations (not S and/or I and/or R and/or NI and/or SDD), and `FALSE` otherwise. The threshold of 5% can be set with the `threshold` argument. If the input is a [data.frame], it iterates over all columns and returns a [logical] vector. -#' @section Interpretation of SIR: -#' In 2019, the European Committee on Antimicrobial Susceptibility Testing (EUCAST) has decided to change the definitions of susceptibility testing categories S, I, and R (). -#' -#' This AMR package follows insight; use [susceptibility()] (equal to [proportion_SI()]) to determine antimicrobial susceptibility and [count_susceptible()] (equal to [count_SI()]) to count susceptible isolates. -#' @return Ordered [factor] with new class `sir` -#' @aliases sir -#' @export -#' @seealso [as.mic()], [as.disk()], [as.mo()] -#' @source -#' For interpretations of minimum inhibitory concentration (MIC) values and disk diffusion diameters: -#' -#' - **CLSI M39: Analysis and Presentation of Cumulative Antimicrobial Susceptibility Test Data**, `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI")$guideline)))`, *Clinical and Laboratory Standards Institute* (CLSI). . -#' - **CLSI M100: Performance Standard for Antimicrobial Susceptibility Testing**, `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI" & type != "animal")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI" & type != "animal")$guideline)))`, *Clinical and Laboratory Standards Institute* (CLSI). . -#' - **CLSI VET01: Performance Standards for Antimicrobial Disk and Dilution Susceptibility Tests for Bacteria Isolated From Animals**, `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI" & type == "animal")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI" & type == "animal")$guideline)))`, *Clinical and Laboratory Standards Institute* (CLSI). . -###### TODO - **CLSI VET09: Understanding Susceptibility Test Data as a Component of Antimicrobial Stewardship in Veterinary Settings**, `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI" & type == "animal")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI" & type == "animal")$guideline)))`, *Clinical and Laboratory Standards Institute* (CLSI). . -#' - **EUCAST Breakpoint tables for interpretation of MICs and zone diameters**, `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "EUCAST")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "EUCAST")$guideline)))`, *European Committee on Antimicrobial Susceptibility Testing* (EUCAST). . -#' - **WHONET** as a source for machine-reading the clinical breakpoints ([read more here](https://amr-for-r.org/reference/clinical_breakpoints.html#imported-from-whonet)), 1989-`r max(as.integer(gsub("[^0-9]", "", AMR::clinical_breakpoints$guideline)))`, *WHO Collaborating Centre for Surveillance of Antimicrobial Resistance*. . -#' -#' @inheritSection AMR Download Our Reference Data -#' @examples -#' example_isolates -#' summary(example_isolates) # see all SIR results at a glance -#' -#' # For INTERPRETING disk diffusion and MIC values ----------------------- -#' -#' # example data sets, with combined MIC values and disk zones -#' df_wide <- data.frame( -#' microorganism = "Escherichia coli", -#' amoxicillin = as.mic(8), -#' cipro = as.mic(0.256), -#' tobra = as.disk(16), -#' genta = as.disk(18), -#' ERY = "R" -#' ) -#' df_long <- data.frame( -#' bacteria = rep("Escherichia coli", 4), -#' antibiotic = c("amoxicillin", "cipro", "tobra", "genta"), -#' mics = as.mic(c(0.01, 1, 4, 8)), -#' disks = as.disk(c(6, 10, 14, 18)), -#' guideline = c("EUCAST 2021", "EUCAST 2022", "EUCAST 2023", "EUCAST 2024") -#' ) -#' -#' \donttest{ -#' ## Using dplyr ------------------------------------------------- -#' if (require("dplyr")) { -#' # approaches that all work without additional arguments: -#' df_wide %>% mutate_if(is.mic, as.sir) -#' df_wide %>% mutate_if(function(x) is.mic(x) | is.disk(x), as.sir) -#' df_wide %>% mutate(across(where(is.mic), as.sir)) -#' df_wide %>% mutate_at(vars(amoxicillin:tobra), as.sir) -#' df_wide %>% mutate(across(amoxicillin:tobra, as.sir)) -#' -#' # approaches that all work with additional arguments: -#' df_long %>% -#' # given a certain data type, e.g. MIC values -#' mutate_if(is.mic, as.sir, -#' mo = "bacteria", -#' ab = "antibiotic", -#' guideline = "guideline" -#' ) -#' df_long %>% -#' mutate(across( -#' where(is.mic), -#' function(x) { -#' as.sir(x, -#' mo = "bacteria", -#' ab = "antibiotic", -#' guideline = "CLSI" -#' ) -#' } -#' )) -#' df_wide %>% -#' # given certain columns, e.g. from 'cipro' to 'genta' -#' mutate_at(vars(cipro:genta), as.sir, -#' mo = "bacteria", -#' guideline = "CLSI" -#' ) -#' df_wide %>% -#' mutate(across( -#' cipro:genta, -#' function(x) { -#' as.sir(x, -#' mo = "bacteria", -#' guideline = "CLSI" -#' ) -#' } -#' )) -#' -#' # for veterinary breakpoints, add 'host': -#' df_long$animal_species <- c("cats", "dogs", "horses", "cattle") -#' df_long %>% -#' # given a certain data type, e.g. MIC values -#' mutate_if(is.mic, as.sir, -#' mo = "bacteria", -#' ab = "antibiotic", -#' host = "animal_species", -#' guideline = "CLSI" -#' ) -#' df_long %>% -#' mutate(across( -#' where(is.mic), -#' function(x) { -#' as.sir(x, -#' mo = "bacteria", -#' ab = "antibiotic", -#' host = "animal_species", -#' guideline = "CLSI" -#' ) -#' } -#' )) -#' df_wide %>% -#' mutate_at(vars(cipro:genta), as.sir, -#' mo = "bacteria", -#' ab = "antibiotic", -#' host = "animal_species", -#' guideline = "CLSI" -#' ) -#' df_wide %>% -#' mutate(across( -#' cipro:genta, -#' function(x) { -#' as.sir(x, -#' mo = "bacteria", -#' host = "animal_species", -#' guideline = "CLSI" -#' ) -#' } -#' )) -#' -#' # to include information about urinary tract infections (UTI) -#' data.frame( -#' mo = "E. coli", -#' nitrofuratoin = c("<= 2", 32), -#' from_the_bladder = c(TRUE, FALSE) -#' ) %>% -#' as.sir(uti = "from_the_bladder") -#' -#' data.frame( -#' mo = "E. coli", -#' nitrofuratoin = c("<= 2", 32), -#' specimen = c("urine", "blood") -#' ) %>% -#' as.sir() # automatically determines urine isolates -#' -#' df_wide %>% -#' mutate_at(vars(cipro:genta), as.sir, mo = "E. coli", uti = TRUE) -#' } -#' -#' -#' ## Using base R ------------------------------------------------ -#' -#' as.sir(df_wide) -#' -#' # return a 'logbook' about the results: -#' sir_interpretation_history() -#' -#' # for single values -#' as.sir( -#' x = as.mic(2), -#' mo = as.mo("S. pneumoniae"), -#' ab = "AMP", -#' guideline = "EUCAST" -#' ) -#' -#' as.sir( -#' x = as.disk(18), -#' mo = "Strep pneu", # `mo` will be coerced with as.mo() -#' ab = "ampicillin", # and `ab` with as.ab() -#' guideline = "EUCAST" -#' ) -#' -#' -#' # For CLEANING existing SIR values ------------------------------------- -#' -#' as.sir(c("S", "SDD", "I", "R", "NI", "A", "B", "C")) -#' as.sir("<= 0.002; S") # will return "S" -#' sir_data <- as.sir(c(rep("S", 474), rep("I", 36), rep("R", 370))) -#' is.sir(sir_data) -#' plot(sir_data) # for percentages -#' barplot(sir_data) # for frequencies -#' -#' # as common in R, you can use as.integer() to return factor indices: -#' as.integer(as.sir(c("S", "SDD", "I", "R", "NI", NA))) -#' # but for computational use, as.double() will return 1 for S, 2 for I/SDD, and 3 for R: -#' as.double(as.sir(c("S", "SDD", "I", "R", "NI", NA))) -#' -#' # the dplyr way -#' if (require("dplyr")) { -#' example_isolates %>% -#' mutate_at(vars(PEN:RIF), as.sir) -#' # same: -#' example_isolates %>% -#' as.sir(PEN:RIF) -#' -#' # fastest way to transform all columns with already valid AMR results to class `sir`: -#' example_isolates %>% -#' mutate_if(is_sir_eligible, as.sir) -#' -#' # since dplyr 1.0.0, this can also be: -#' # example_isolates %>% -#' # mutate(across(where(is_sir_eligible), as.sir)) -#' } -#' } -as.sir <- function(x, ...) { - UseMethod("as.sir") -} - -as_sir_structure <- function(x, - guideline = NULL, - mo = NULL, - ab = NULL, - method = NULL, - ref_tbl = NULL, - ref_breakpoints = NULL) { - out <- structure( - factor(as.character(unlist(unname(x))), - levels = c("S", "SDD", "I", "R", "NI"), - ordered = TRUE - ), - # TODO for #170 - # guideline = guideline, - # mo = mo, - # ab = ab, - # method = method, - # ref_tbl = ref_tbl, - # ref_breakpoints = ref_breakpoints, - class = c("sir", "ordered", "factor") - ) -} - -#' @rdname as.sir -#' @details `NA_sir_` is a missing value of the new `sir` class, analogous to e.g. base \R's [`NA_character_`][base::NA]. -#' @format NULL -#' @export -NA_sir_ <- as_sir_structure(NA_character_) - -#' @rdname as.sir -#' @export -is.sir <- function(x) { - if (identical(typeof(x), "list")) { - unname(vapply(FUN.VALUE = logical(1), x, is.sir)) - } else { - isTRUE(inherits(x, "sir")) - } -} - -#' @rdname as.sir -#' @export -is_sir_eligible <- function(x, threshold = 0.05) { - meet_criteria(threshold, allow_class = "numeric", has_length = 1) - - if (identical(typeof(x), "list")) { - # iterate this function over all columns - return(unname(vapply(FUN.VALUE = logical(1), x, is_sir_eligible))) - } - - stop_if(NCOL(x) > 1, "`x` must be a one-dimensional vector.") - if (any(c( - "numeric", - "integer", - "mo", - "ab", - "Date", - "POSIXt", - "raw", - "hms", - "mic", - "disk" - ) - %in% class(x))) { - # no transformation needed - return(FALSE) - } else if (all(x %in% c("S", "SDD", "I", "R", "NI", NA)) & !all(is.na(x))) { - return(TRUE) - } else if (!any(c("S", "SDD", "I", "R", "NI") %in% x, na.rm = TRUE) & !all(is.na(x))) { - return(FALSE) - } else { - x <- x[!is.na(x) & !is.null(x) & !x %in% c("", "-", "NULL")] - if (length(x) == 0) { - # no other values than empty - cur_col <- get_current_column() - if (!is.null(cur_col)) { - ab <- suppressWarnings(as.ab(cur_col, fast_mode = TRUE, info = FALSE)) - if (!is.na(ab)) { - # this is a valid antibiotic drug code - message_( - "Column '", font_bold(cur_col), "' is SIR eligible (despite only having empty values), since it seems to be ", - ab_name(ab, language = NULL, tolower = TRUE), " (", ab, ")" - ) - return(TRUE) - } - } - # all values empty and no antibiotic col name - return FALSE - return(FALSE) - } - # transform all values and see if it meets the set threshold - checked <- suppressWarnings(as.sir(x)) - outcome <- sum(is.na(checked)) / length(x) - outcome <= threshold - } -} - -#' @rdname as.sir -#' @export -#' @param S,I,R,NI,SDD A case-independent [regular expression][base::regex] to translate input to this result. This regular expression will be run *after* all non-letters and whitespaces are removed from the input. -#' @param info A [logical] to print information about the process. -# extra param: warn (logical, to never throw a warning) -as.sir.default <- function(x, - S = "^(S|U)+$", - I = "^(I)+$", - R = "^(R)+$", - NI = "^(N|NI|V)+$", - SDD = "^(SDD|D|H)+$", - info = TRUE, - ...) { - meet_criteria(S, allow_class = "character", has_length = 1) - meet_criteria(I, allow_class = "character", has_length = 1) - meet_criteria(R, allow_class = "character", has_length = 1) - meet_criteria(NI, allow_class = "character", has_length = 1) - meet_criteria(SDD, allow_class = "character", has_length = 1) - meet_criteria(info, allow_class = "logical", has_length = 1) - if (inherits(x, "sir")) { - return(as_sir_structure(x)) - } - - x.bak <- x - x <- as.character(x) # this is needed to prevent the vctrs pkg from throwing an error - - if (inherits(x.bak, c("numeric", "integer")) && all(x %in% c(1:3, NA))) { - # support haven package for importing e.g., from SPSS - it adds the 'labels' attribute - lbls <- attributes(x.bak)$labels - if (!is.null(lbls) && all(c("S", "I", "R") %in% names(lbls)) && all(c(1:3) %in% lbls)) { - x[x.bak == 1] <- names(lbls[lbls == 1]) - x[x.bak == 2] <- names(lbls[lbls == 2]) - x[x.bak == 3] <- names(lbls[lbls == 3]) - } else { - x[x.bak == 1] <- "S" - x[x.bak == 2] <- "I" - x[x.bak == 3] <- "R" - } - } else if (inherits(x.bak, "character") && all(x %in% c("1", "2", "3", "S", "I", "R", NA_character_))) { - x[x.bak == "1"] <- "S" - x[x.bak == "2"] <- "I" - x[x.bak == "3"] <- "R" - } else if (inherits(x.bak, "character") && all(x %in% c("1", "2", "3", "4", "5", "S", "SDD", "I", "R", "NI", NA_character_))) { - x[x.bak == "1"] <- "S" - x[x.bak == "2"] <- "SDD" - x[x.bak == "3"] <- "I" - x[x.bak == "4"] <- "R" - x[x.bak == "5"] <- "NI" - } else if (!all(is.na(x)) && !identical(levels(x), c("S", "SDD", "I", "R", "NI")) && !all(x %in% c("S", "SDD", "I", "R", "NI", NA))) { - if (all(x %unlike% "(S|I|R)", na.rm = TRUE)) { - # check if they are actually MICs or disks - if (all_valid_mics(x)) { - warning_("in `as.sir()`: input values were guessed to be MIC values - preferably transform them with `as.mic()` before running `as.sir()`.") - return(as.sir(as.mic(x), ...)) - } else if (all_valid_disks(x)) { - warning_("in `as.sir()`: input values were guessed to be disk diffusion values - preferably transform them with `as.disk()` before running `as.sir()`.") - return(as.sir(as.disk(x), ...)) - } - } - - # trim leading and trailing spaces, new lines, etc. - x <- trimws2(as.character(unlist(x))) - x[x %in% c(NA, "", "-", "NULL")] <- NA_character_ - x.bak <- x - - na_before <- length(x[is.na(x)]) - - # correct for translations - trans_R <- unlist(TRANSLATIONS[ - which(TRANSLATIONS$pattern == "Resistant"), - LANGUAGES_SUPPORTED[LANGUAGES_SUPPORTED %in% colnames(TRANSLATIONS)] - ]) - trans_S <- unlist(TRANSLATIONS[ - which(TRANSLATIONS$pattern == "Susceptible"), - LANGUAGES_SUPPORTED[LANGUAGES_SUPPORTED %in% colnames(TRANSLATIONS)] - ]) - trans_I <- unlist(TRANSLATIONS[ - which(TRANSLATIONS$pattern %in% c("Incr. exposure", "Susceptible, incr. exp.", "Intermediate")), - LANGUAGES_SUPPORTED[LANGUAGES_SUPPORTED %in% colnames(TRANSLATIONS)] - ]) - x <- gsub(paste0(unique(trans_R[!is.na(trans_R)]), collapse = "|"), "R", x, ignore.case = TRUE) - x <- gsub(paste0(unique(trans_S[!is.na(trans_S)]), collapse = "|"), "S", x, ignore.case = TRUE) - x <- gsub(paste0(unique(trans_I[!is.na(trans_I)]), collapse = "|"), "I", x, ignore.case = TRUE) - # replace all English textual input - x[x %like% "([^a-z]|^)res(is(tant)?)?"] <- "R" - x[x %like% "([^a-z]|^)sus(cep(tible)?)?"] <- "S" - x[x %like% "not|non"] <- "NI" - x[x %like% "([^a-z]|^)int(er(mediate)?)?|incr.*exp"] <- "I" - x[x %like% "dose"] <- "SDD" - x <- gsub("[^A-Z]+", "", x, perl = TRUE) - # apply regexes set by user - x[x %like% S] <- "S" - x[x %like% I] <- "I" - x[x %like% R] <- "R" - x[x %like% NI] <- "NI" - x[x %like% SDD] <- "SDD" - x[!x %in% c("S", "SDD", "I", "R", "NI")] <- NA_character_ - na_after <- length(x[is.na(x) | x == ""]) - - if (!isFALSE(list(...)$warn)) { # so as.sir(..., warn = FALSE) will never throw a warning - if (na_before != na_after) { - list_missing <- x.bak[is.na(x) & !is.na(x.bak) & x.bak != ""] %pm>% - unique() %pm>% - sort() %pm>% - vector_and(quotes = TRUE) - cur_col <- get_current_column() - warning_("in `as.sir()`: ", na_after - na_before, " result", - ifelse(na_after - na_before > 1, "s", ""), - ifelse(is.null(cur_col), "", paste0(" in index '", cur_col, "'")), - " truncated (", - round(((na_after - na_before) / length(x)) * 100), - "%) that were invalid antimicrobial interpretations: ", - list_missing, - call = FALSE - ) - } - } - } - - as_sir_structure(x) -} - -#' @rdname as.sir -#' @export -as.sir.mic <- function(x, - mo = NULL, - ab = deparse(substitute(x)), - guideline = getOption("AMR_guideline", "EUCAST"), - uti = NULL, - capped_mic_handling = getOption("AMR_capped_mic_handling", "standard"), - add_intrinsic_resistance = FALSE, - reference_data = AMR::clinical_breakpoints, - substitute_missing_r_breakpoint = getOption("AMR_substitute_missing_r_breakpoint", FALSE), - include_screening = getOption("AMR_include_screening", FALSE), - include_PKPD = getOption("AMR_include_PKPD", TRUE), - breakpoint_type = getOption("AMR_breakpoint_type", "human"), - host = NULL, - verbose = FALSE, - info = TRUE, - parallel = TRUE, - max_cores = -1, - conserve_capped_values = NULL, - ...) { - as_sir_method( - method_short = "mic", - method_long = "MIC values", - x = x, - mo = mo, - ab = ab, - guideline = guideline, - uti = uti, - capped_mic_handling = capped_mic_handling, - add_intrinsic_resistance = add_intrinsic_resistance, - reference_data = reference_data, - substitute_missing_r_breakpoint = substitute_missing_r_breakpoint, - include_screening = include_screening, - include_PKPD = include_PKPD, - breakpoint_type = breakpoint_type, - host = host, - verbose = verbose, - info = info, - parallel = parallel, - max_cores = max_cores, - conserve_capped_values = conserve_capped_values, - ... - ) -} - -#' @rdname as.sir -#' @export -as.sir.disk <- function(x, - mo = NULL, - ab = deparse(substitute(x)), - guideline = getOption("AMR_guideline", "EUCAST"), - uti = NULL, - add_intrinsic_resistance = FALSE, - reference_data = AMR::clinical_breakpoints, - substitute_missing_r_breakpoint = getOption("AMR_substitute_missing_r_breakpoint", FALSE), - include_screening = getOption("AMR_include_screening", FALSE), - include_PKPD = getOption("AMR_include_PKPD", TRUE), - breakpoint_type = getOption("AMR_breakpoint_type", "human"), - host = NULL, - verbose = FALSE, - info = TRUE, - parallel = TRUE, - max_cores = -1, - ...) { - as_sir_method( - method_short = "disk", - method_long = "disk diffusion zones", - x = x, - mo = mo, - ab = ab, - guideline = guideline, - uti = uti, - capped_mic_handling = "standard", # will be ignored for non-MIC anyway - add_intrinsic_resistance = add_intrinsic_resistance, - reference_data = reference_data, - substitute_missing_r_breakpoint = substitute_missing_r_breakpoint, - include_screening = include_screening, - include_PKPD = include_PKPD, - breakpoint_type = breakpoint_type, - host = host, - verbose = verbose, - parallel = parallel, - max_cores = max_cores, - info = info, - ... - ) -} - -#' @rdname as.sir -#' @export -as.sir.data.frame <- function(x, - ..., - col_mo = NULL, - guideline = getOption("AMR_guideline", "EUCAST"), - uti = NULL, - capped_mic_handling = getOption("AMR_capped_mic_handling", "standard"), - add_intrinsic_resistance = FALSE, - reference_data = AMR::clinical_breakpoints, - substitute_missing_r_breakpoint = getOption("AMR_substitute_missing_r_breakpoint", FALSE), - include_screening = getOption("AMR_include_screening", FALSE), - include_PKPD = getOption("AMR_include_PKPD", TRUE), - breakpoint_type = getOption("AMR_breakpoint_type", "human"), - host = NULL, - verbose = FALSE, - info = TRUE, - parallel = TRUE, - max_cores = -1, - conserve_capped_values = NULL) { - meet_criteria(x, allow_class = "data.frame") # will also check for dimensions > 0 - meet_criteria(col_mo, allow_class = "character", is_in = colnames(x), allow_NULL = TRUE) - meet_criteria(guideline, allow_class = "character") - meet_criteria(uti, allow_class = c("logical", "character"), allow_NULL = TRUE, allow_NA = TRUE) - meet_criteria(capped_mic_handling, allow_class = "character", has_length = 1, is_in = c("standard", "conservative", "none", "inverse")) - meet_criteria(add_intrinsic_resistance, allow_class = "logical", has_length = 1) - meet_criteria(reference_data, allow_class = "data.frame") - meet_criteria(substitute_missing_r_breakpoint, allow_class = "logical", has_length = 1) - meet_criteria(include_screening, allow_class = "logical", has_length = 1) - meet_criteria(include_PKPD, allow_class = "logical", has_length = 1) - meet_criteria(breakpoint_type, allow_class = "character", is_in = reference_data$type, has_length = 1) - meet_criteria(host, allow_class = c("character", "factor"), allow_NULL = TRUE, allow_NA = TRUE) - meet_criteria(verbose, allow_class = "logical", has_length = 1) - meet_criteria(info, allow_class = "logical", has_length = 1) - meet_criteria(parallel, allow_class = "logical", has_length = 1) - meet_criteria(max_cores, allow_class = c("numeric", "integer"), has_length = 1) - x.bak <- x - for (i in seq_len(ncol(x))) { - # don't keep factors, overwriting them is hard - if (is.factor(x[, i, drop = TRUE])) { - x[, i] <- as.character(x[, i, drop = TRUE]) - } - } - - # -- MO - col_mo.bak <- col_mo - if (is.null(col_mo)) { - col_mo <- search_type_in_df(x = x, type = "mo", info = FALSE) - } - - # -- host - if (missing(breakpoint_type) && any(host %in% clinical_breakpoints$host[!clinical_breakpoints$host %in% c("human", "ECOFF")], na.rm = TRUE)) { - if (isTRUE(info)) message_("Assuming `breakpoint_type = \"animal\"` since `host` contains animal species.") - breakpoint_type <- "animal" - } else if (any(!suppressMessages(convert_host(host)) %in% c("human", "ECOFF"), na.rm = TRUE)) { - if (isTRUE(info)) message_("Assuming `breakpoint_type = \"animal\"`.") - breakpoint_type <- "animal" - } - if (breakpoint_type == "animal") { - if (is.null(host)) { - host <- search_type_in_df(x = x, type = "host", add_col_prefix = FALSE) - } else if (length(host) == 1 && as.character(host) %in% colnames(x)) { - host <- x[[as.character(host)]] - } - } else { - host <- breakpoint_type - } - - # -- UTIs - col_uti <- uti - if (is.null(col_uti)) { - col_uti <- search_type_in_df(x = x, type = "uti", add_col_prefix = FALSE) - } - if (!is.null(col_uti)) { - if (is.logical(col_uti)) { - # already a logical vector as input - if (length(col_uti) == 1) { - uti <- rep(col_uti, NROW(x)) - } else { - uti <- col_uti - } - } else { - # column found, transform to logical - stop_if( - length(col_uti) != 1 | !col_uti %in% colnames(x), - "argument `uti` must be a [logical] vector, of must be a single column name of `x`" - ) - uti <- as.logical(x[, col_uti, drop = TRUE]) - } - } else { - # col_uti is still NULL - look for specimen column and make logicals of the urines - col_specimen <- suppressMessages(search_type_in_df(x = x, type = "specimen")) - if (!is.null(col_specimen)) { - uti <- x[, col_specimen, drop = TRUE] %like% "urin" - values <- sort(unique(x[uti, col_specimen, drop = TRUE])) - if (length(values) > 1) { - plural <- c("s", "", "") - } else { - plural <- c("", "s", "a ") - } - if (isTRUE(info)) { - message_( - "Assuming value", plural[1], " ", - vector_and(values, quotes = TRUE), - " in column '", font_bold(col_specimen), - "' reflect", plural[2], " ", plural[3], "urinary tract infection", plural[1], - ".\n Use `as.sir(uti = FALSE)` to prevent this." - ) - } - } else { - # no data about UTI's found - uti <- NULL - } - } - - i <- 0 - if (tryCatch(length(list(...)) > 0, error = function(e) TRUE)) { - sel <- colnames(pm_select(x, ...)) - } else { - sel <- colnames(x) - } - if (!is.null(col_mo)) { - sel <- sel[sel != col_mo] - } - - ab_cols <- colnames(x)[vapply(FUN.VALUE = logical(1), x, function(y) { - i <<- i + 1 - check <- is.mic(y) | is.disk(y) - ab <- colnames(x)[i] - if (!is.null(col_mo) && ab == col_mo) { - return(FALSE) - } - if (!is.null(col_uti) && ab == col_uti) { - return(FALSE) - } - if (length(sel) == 0 || (length(sel) > 0 && ab %in% sel)) { - ab_coerced <- suppressWarnings(as.ab(ab)) - if (is.na(ab_coerced) || (length(sel) > 0 & !ab %in% sel)) { - # not even a valid AB code - return(FALSE) - } else { - return(TRUE) - } - } else { - return(FALSE) - } - })] - - stop_if( - length(ab_cols) == 0, - "no columns with MIC values, disk zones or antibiotic column names found in this data set. Use as.mic() or as.disk() to transform antimicrobial columns." - ) - # set type per column - types <- character(length(ab_cols)) - types[vapply(FUN.VALUE = logical(1), x.bak[, ab_cols, drop = FALSE], is.disk)] <- "disk" - types[vapply(FUN.VALUE = logical(1), x.bak[, ab_cols, drop = FALSE], is.mic)] <- "mic" - types[types == "" & vapply(FUN.VALUE = logical(1), x[, ab_cols, drop = FALSE], all_valid_disks)] <- "disk" - types[types == "" & vapply(FUN.VALUE = logical(1), x[, ab_cols, drop = FALSE], all_valid_mics)] <- "mic" - types[types == "" & !vapply(FUN.VALUE = logical(1), x.bak[, ab_cols, drop = FALSE], is.sir)] <- "sir" - if (any(types %in% c("mic", "disk"), na.rm = TRUE)) { - # now we need an mo column - stop_if(is.null(col_mo), "`col_mo` must be set") - # if not null, we already found it, now find again so a message will show - if (is.null(col_mo.bak)) { - col_mo <- search_type_in_df(x = x, type = "mo") - } - x_mo <- as.mo(x[, col_mo, drop = TRUE]) - } - - for (i in seq_along(ab_cols)) { - if (types[i] == "mic") { - x[, ab_cols[i]] <- x %pm>% - pm_pull(ab_cols[i]) %pm>% - as.character() %pm>% - as.mic() %pm>% - as.sir( - mo = x_mo, - mo.bak = x[, col_mo, drop = TRUE], - ab = ab_cols[i], - guideline = guideline, - uti = uti, - capped_mic_handling = capped_mic_handling, - add_intrinsic_resistance = add_intrinsic_resistance, - reference_data = reference_data, - substitute_missing_r_breakpoint = substitute_missing_r_breakpoint, - include_screening = include_screening, - include_PKPD = include_PKPD, - breakpoint_type = breakpoint_type, - host = host, - verbose = verbose, - info = info, - parallel = parallel, - max_cores = max_cores, - conserve_capped_values = conserve_capped_values, - is_data.frame = TRUE - ) - } else if (types[i] == "disk") { - x[, ab_cols[i]] <- x %pm>% - pm_pull(ab_cols[i]) %pm>% - as.character() %pm>% - as.disk() %pm>% - as.sir( - mo = x_mo, - mo.bak = x[, col_mo, drop = TRUE], - ab = ab_cols[i], - guideline = guideline, - uti = uti, - add_intrinsic_resistance = add_intrinsic_resistance, - reference_data = reference_data, - substitute_missing_r_breakpoint = substitute_missing_r_breakpoint, - include_screening = include_screening, - include_PKPD = include_PKPD, - breakpoint_type = breakpoint_type, - host = host, - verbose = verbose, - info = info, - parallel = parallel, - max_cores = max_cores, - is_data.frame = TRUE - ) - } else if (types[i] == "sir") { - show_message <- FALSE - ab <- ab_cols[i] - ab_coerced <- suppressWarnings(as.ab(ab)) - if (!all(x[, ab_cols[i], drop = TRUE] %in% c("S", "SDD", "I", "R", "NI", NA), na.rm = TRUE)) { - show_message <- TRUE - # only print message if values are not already clean - if (isTRUE(info)) { - message_("Cleaning values in column '", font_bold(ab), "' (", - ifelse(ab_coerced != toupper(ab), paste0(ab_coerced, ", "), ""), - ab_name(ab_coerced, tolower = TRUE), ")... ", - appendLF = FALSE, - as_note = FALSE - ) - } - } else if (!is.sir(x.bak[, ab_cols[i], drop = TRUE])) { - show_message <- TRUE - # only print message if class not already set - if (isTRUE(info)) { - message_("Assigning class 'sir' to already clean column '", font_bold(ab), "' (", - ifelse(ab_coerced != toupper(ab), paste0(ab_coerced, ", "), ""), - ab_name(ab_coerced, tolower = TRUE, language = NULL), ")... ", - appendLF = FALSE, - as_note = FALSE - ) - } - } - x[, ab_cols[i]] <- as.sir.default(x = as.character(x[, ab_cols[i], drop = TRUE])) - if (show_message == TRUE && isTRUE(info)) { - message(font_green_bg(" OK ")) - } - } - } - - x -} - -get_guideline <- function(guideline, reference_data) { - if (!identical(reference_data, AMR::clinical_breakpoints)) { - return(guideline) - } - guideline_param <- trimws2(toupper(guideline)) - latest_clsi <- rev(sort(subset(reference_data, guideline %like% "CLSI")$guideline))[1L] - latest_eucast <- rev(sort(subset(reference_data, guideline %like% "EUCAST")$guideline))[1L] - guideline_param[guideline_param == "CLSI"] <- latest_clsi - guideline_param[guideline_param == "EUCAST"] <- latest_eucast - # like 'EUCAST2020', should be 'EUCAST 2020' - guideline_param[guideline_param %unlike% " "] <- gsub("([a-z]+)([0-9]+)", "\\1 \\2", guideline_param[guideline_param %unlike% " "], ignore.case = TRUE) - - stop_ifnot(guideline_param %in% reference_data$guideline, - "invalid guideline: '", guideline, - "'.\nValid guidelines are: ", vector_and(reference_data$guideline, quotes = TRUE, reverse = TRUE), - call = FALSE - ) - - guideline_param -} - -convert_host <- function(x, lang = get_AMR_locale()) { - x <- gsub("[^a-zA-Z ]", "", trimws2(tolower(as.character(x))), perl = TRUE) - x_out <- rep(NA_character_, length(x)) - x_out[trimws2(tolower(x)) == "human"] <- "human" - x_out[trimws2(tolower(x)) == "ecoff"] <- "ecoff" - # this order is based on: clinical_breakpoints |> filter(type == "animal") |> count(host, sort = TRUE) - x_out[is.na(x_out) & (x %like% "dog|canine|Canis lupus" | x %like% translate_AMR("dog|dogs|canine", lang))] <- "dogs" - x_out[is.na(x_out) & (x %like% "cattle|bovine|Bos taurus" | x %like% translate_AMR("cattle|bovine", lang))] <- "cattle" - x_out[is.na(x_out) & (x %like% "swine|suida(e)?|Sus scrofa" | x %like% translate_AMR("swine|swines", lang))] <- "swine" - x_out[is.na(x_out) & (x %like% "aqua|fish|Pisces" | x %like% translate_AMR("aquatic|fish", lang))] <- "aquatic" - x_out[is.na(x_out) & (x %like% "cat|feline|Felis catus" | x %like% translate_AMR("cat|cats|feline", lang))] <- "cats" - x_out[is.na(x_out) & (x %like% "horse|equine|Equus ferus" | x %like% translate_AMR("horse|horses|equine", lang))] <- "horse" - x_out[is.na(x_out) & (x %like% "bird|chicken|poultry|avia|Gallus gallus" | x %like% translate_AMR("bird|birds|poultry", lang))] <- "poultry" - - # additional animals, not necessarily currently in breakpoint guidelines: - x_out[is.na(x_out) & (x %like% "camel|camelid|Camelus dromedarius" | x %like% translate_AMR("camel|camels|camelid", lang))] <- "camels" - x_out[is.na(x_out) & (x %like% "deer|cervine|Cervidae" | x %like% translate_AMR("deer|deers|cervine", lang))] <- "deer" - x_out[is.na(x_out) & (x %like% "donkey|asinine|Equus africanus" | x %like% translate_AMR("donkey|donkeys|asinine", lang))] <- "donkeys" - x_out[is.na(x_out) & (x %like% "ferret|musteline|Mustela putorius" | x %like% translate_AMR("ferret|ferrets|musteline", lang))] <- "ferrets" - x_out[is.na(x_out) & (x %like% "goat|caprine|Capra aegagrus" | x %like% translate_AMR("goat|goats|caprine", lang))] <- "goats" - x_out[is.na(x_out) & (x %like% "guinea pig|caviine|Cavia porcellus" | x %like% translate_AMR("guinea pig|guinea pigs|caviine", lang))] <- "guinea pigs" - x_out[is.na(x_out) & (x %like% "hamster|cricetine|Cricetinae" | x %like% translate_AMR("hamster|hamsters|cricetine", lang))] <- "hamsters" - x_out[is.na(x_out) & (x %like% "monkey|simian|Simia" | x %like% translate_AMR("monkey|monkeys|simian", lang))] <- "monkeys" - x_out[is.na(x_out) & (x %like% "mouse|murine|Mus musculus" | x %like% translate_AMR("mouse|mice|murine", lang))] <- "mice" - x_out[is.na(x_out) & (x %like% "pig|porcine|Sus scrofa" | x %like% translate_AMR("pig|pigs|porcine", lang))] <- "pigs" - x_out[is.na(x_out) & (x %like% "rabbit|leporine|Oryctolagus cuniculus" | x %like% translate_AMR("rabbit|rabbits|leporine", lang))] <- "rabbits" - x_out[is.na(x_out) & (x %like% "rat|ratine|Rattus" | x %like% translate_AMR("rat|rats|ratine", lang))] <- "rats" - x_out[is.na(x_out) & (x %like% "sheep|ovine|Ovis aries" | x %like% translate_AMR("sheep|sheeps|ovine", lang))] <- "sheep" - x_out[is.na(x_out) & (x %like% "snake|serpentine|Serpentes" | x %like% translate_AMR("snake|snakes|serpentine", lang))] <- "snakes" - x_out[is.na(x_out) & (x %like% "turkey|meleagrine|Meleagris gallopavo" | x %like% translate_AMR("turkey|turkeys|meleagrine", lang))] <- "turkey" - - - x_out[x_out == "ecoff"] <- "ECOFF" - x_out -} - -as_sir_method <- function(method_short, - method_long, - x, - mo, - ab, - guideline, - uti, - capped_mic_handling, - add_intrinsic_resistance, - reference_data, - substitute_missing_r_breakpoint, - include_screening, - include_PKPD, - breakpoint_type, - host, - verbose, - info, - parallel, - max_cores, - conserve_capped_values = NULL, - ...) { - if (isTRUE(conserve_capped_values)) { - deprecation_warning(old = "conserve_capped_values", new = "capped_mic_handling", fn = "as.sir", is_argument = TRUE) - capped_mic_handling <- "conservative" - } - meet_criteria(x, allow_NA = TRUE, .call_depth = -2) - meet_criteria(mo, allow_class = c("mo", "character"), has_length = c(1, length(x)), allow_NULL = TRUE, .call_depth = -2) - meet_criteria(ab, allow_class = c("ab", "character"), has_length = c(1, length(x)), .call_depth = -2) - meet_criteria(guideline, allow_class = "character", has_length = c(1, length(x)), .call_depth = -2) - meet_criteria(uti, allow_class = c("logical", "character"), has_length = c(1, length(x)), allow_NULL = TRUE, allow_NA = TRUE, .call_depth = -2) - meet_criteria(capped_mic_handling, allow_class = "character", has_length = 1, is_in = c("standard", "conservative", "none", "inverse"), .call_depth = -2) - meet_criteria(add_intrinsic_resistance, allow_class = "logical", has_length = 1, .call_depth = -2) - meet_criteria(reference_data, allow_class = "data.frame", .call_depth = -2) - meet_criteria(substitute_missing_r_breakpoint, allow_class = "logical", has_length = 1, .call_depth = -2) - meet_criteria(include_screening, allow_class = "logical", has_length = 1, .call_depth = -2) - meet_criteria(include_PKPD, allow_class = "logical", has_length = 1, .call_depth = -2) - check_reference_data(reference_data, .call_depth = -2) - meet_criteria(breakpoint_type, allow_class = "character", is_in = reference_data$type, has_length = 1, .call_depth = -2) - meet_criteria(host, allow_class = c("character", "factor"), allow_NULL = TRUE, allow_NA = TRUE, .call_depth = -2) - meet_criteria(verbose, allow_class = "logical", has_length = 1, .call_depth = -2) - meet_criteria(info, allow_class = "logical", has_length = 1, .call_depth = -2) - meet_criteria(parallel, allow_class = "logical", has_length = 1, .call_depth = -2) - meet_criteria(max_cores, allow_class = c("numeric", "integer"), has_length = 1, .call_depth = -2) - - # backward compatibilty - dots <- list(...) - dots <- dots[which(!names(dots) %in% c("warn", "mo.bak", "is_data.frame"))] - if (length(dots) != 0) { - warning_("These arguments in `as.sir()` are no longer used: ", vector_and(names(dots), quotes = "`"), ".", call = FALSE) - } - - current_sir_interpretation_history <- NROW(AMR_env$sir_interpretation_history) - - if (isTRUE(info) && message_not_thrown_before("as.sir", "sir_interpretation_history")) { - message() - message_("Run `sir_interpretation_history()` afterwards to retrieve a logbook with all the details of the breakpoint interpretations.\n\n", add_fn = font_green) - } - - current_df <- tryCatch(get_current_data(NA, 0), error = function(e) NULL) - - # get guideline - if (!is.null(current_df) && length(guideline) == 1 && guideline %in% colnames(current_df) && any(current_df[[guideline]] %like% "CLSI|EUCAST", na.rm = TRUE)) { - guideline <- current_df[[guideline]] - } - guideline_coerced <- get_guideline(guideline, reference_data) - - # get host - if (breakpoint_type == "animal") { - if (is.null(host)) { - host <- "dogs" - if (isTRUE(info) && message_not_thrown_before("as.sir", "host_missing")) { - message_("Animal hosts not set in `host`, assuming `host = \"dogs\"`, since these have the highest breakpoint availability.\n\n") - } - } - } else { - if (!is.null(host) && !all(toupper(as.character(host)) %in% c("HUMAN", "ECOFF"))) { - if (isTRUE(info) && message_not_thrown_before("as.sir", "assumed_breakpoint_animal")) { - message_("Assuming `breakpoint_type = \"animal\"`, since `host` is set.", ifelse(guideline_coerced %like% "EUCAST", " Do you also need to set `guideline = \"CLSI\"`?", ""), "\n\n") - } - breakpoint_type <- "animal" - } else { - host <- breakpoint_type - } - } - - if (!is.null(host) && !all(toupper(as.character(host)) %in% c("HUMAN", "ECOFF"))) { - if (!is.null(current_df) && length(host) == 1 && host %in% colnames(current_df) && any(current_df[[host]] %like% "[A-Z]", na.rm = TRUE)) { - host <- current_df[[host]] - } else if (length(host) != length(x)) { - # for dplyr's across() - cur_column_dplyr <- import_fn("cur_column", "dplyr", error_on_fail = FALSE) - if (!is.null(cur_column_dplyr) && is.data.frame(current_df)) { - # try to get current column, which will only be available when in across() - host <- tryCatch(cur_column_dplyr(), - error = function(e) host - ) - } - } - } - host.bak <- host - host <- convert_host(host) - if (any(is.na(host) & !is.na(host.bak)) && isTRUE(info) && message_not_thrown_before("as.sir", "missing_hosts")) { - warning_("The following animal host(s) could not be coerced: ", vector_and(host.bak[is.na(host) & !is.na(host.bak)]), immediate = TRUE) - message() # new line - } - # TODO add a switch to turn this off? In interactive sessions perhaps ask the user. Default should be On. - # if (breakpoint_type == "animal" && isTRUE(info) && message_not_thrown_before("as.sir", "host_missing_breakpoints")) { - # if (guideline_coerced %like% "CLSI") { - # message_("Please note that in the absence of specific veterinary breakpoints for certain animal hosts, the CLSI guideline VET09 will be applied where possible.\n\n") - # } - # } - - # get ab - if (!is.null(current_df) && length(ab) == 1 && ab %in% colnames(current_df) && any(current_df[[ab]] %like% "[A-Z]", na.rm = TRUE)) { - ab <- current_df[[ab]] - } else if (length(ab) != length(x)) { - # for dplyr's across() - cur_column_dplyr <- import_fn("cur_column", "dplyr", error_on_fail = FALSE) - if (!is.null(cur_column_dplyr) && is.data.frame(current_df)) { - # try to get current column, which will only be available when in across() - ab <- tryCatch(cur_column_dplyr(), - error = function(e) ab - ) - } - } - - # get mo - if (!is.null(current_df) && length(mo) == 1 && mo %in% colnames(current_df)) { - mo_var_found <- paste0(" based on column '", font_bold(mo), "'") - mo <- current_df[[mo]] - } else if (length(mo) != length(x)) { - mo_var_found <- "" - if (is.null(mo)) { - tryCatch( - { - df <- get_current_data(arg_name = "mo", call = -3) # will return an error if not found - mo <- NULL - try( - { - mo <- suppressMessages(search_type_in_df(df, "mo", add_col_prefix = FALSE)) - }, - silent = TRUE - ) - if (!is.null(df) && !is.null(mo) && is.data.frame(df)) { - mo_var_found <- paste0(" based on column '", font_bold(mo), "'") - mo <- df[, mo, drop = TRUE] - } - }, - error = function(e) { - mo <- NULL - } - ) - } - } else { - mo_var_found <- "" - } - if (is.null(mo)) { - stop_("No information was supplied about the microorganisms (missing argument `mo` and no column of class 'mo' found). See ?as.sir.\n\n", - "To transform certain columns with e.g. mutate(), use `data %>% mutate(across(..., as.sir, mo = x))`, where x is your column with microorganisms.\n", - "To transform all ", method_long, " in a data set, use `data %>% as.sir()` or `data %>% mutate_if(is.", method_short, ", as.sir)`.", - call = FALSE - ) - } - - # get uti - if (!is.null(current_df) && length(uti) == 1 && uti %in% colnames(current_df)) { - uti <- current_df[[uti]] - } else if (length(uti) != length(x)) { - if (is.null(uti)) { - tryCatch( - { - df <- get_current_data(arg_name = "uti", call = -3) # will return an error if not found - uti <- NULL - try( - { - uti <- suppressMessages(search_type_in_df(df, "uti", add_col_prefix = FALSE)) - }, - silent = TRUE - ) - if (!is.null(df) && !is.null(uti) && is.data.frame(df)) { - uti <- df[, uti, drop = TRUE] - } - }, - error = function(e) { - uti <- NULL - } - ) - } - } - # TODO set uti to specimen column here - - - if (length(ab) == 1 && ab %like% paste0("as.", method_short)) { - stop_("No unambiguous name was supplied about the antibiotic (argument `ab`). See ?as.sir.", call = FALSE) - } - - ab.bak <- trimws2(ab) - ab <- suppressWarnings(as.ab(ab)) - if (!is.null(list(...)$mo.bak)) { - mo.bak <- list(...)$mo.bak - } else { - mo.bak <- mo - } - mo.bak <- trimws2(mo.bak) - # be sure to take current taxonomy, as the 'clinical_breakpoints' data set only contains current taxonomy - mo <- suppressWarnings(suppressMessages(as.mo(mo, keep_synonyms = FALSE, info = FALSE))) - if (all(is.na(ab))) { - if (isTRUE(info)) { - message_("Returning NAs for unknown antibiotic: ", vector_and(ab.bak, sort = FALSE, quotes = TRUE), - ". Rename this column to a valid name or code, and check the output with `as.ab()`.", - add_fn = font_red, - as_note = FALSE - ) - } - return(as.sir(rep(NA, length(x)))) - } - if (length(mo) == 1) { - mo <- rep(mo, length(x)) - } - if (length(ab) == 1) { - ab <- rep(ab, length(x)) - ab.bak <- rep(ab.bak, length(ab)) - } - if (length(host) == 1) { - host <- rep(host, length(x)) - } - if (is.null(uti)) { - uti <- NA - } - if (length(uti) == 1) { - uti <- rep(uti, length(x)) - } - if (isTRUE(add_intrinsic_resistance) && guideline_coerced %unlike% "EUCAST") { - if (isTRUE(info) && message_not_thrown_before("as.sir", "intrinsic")) { - message_("in `as.sir()`: using 'add_intrinsic_resistance' is only useful when using EUCAST guidelines, since the rules for intrinsic resistance are based on EUCAST.", - add_fn = font_red - ) - } - } - - # format agents ---- - agent_formatted <- paste0("'", font_bold(ab.bak, collapse = NULL), "'") - agent_name <- ab_name(ab, tolower = TRUE, language = NULL) - same_ab <- generalise_antibiotic_name(ab) == generalise_antibiotic_name(agent_name) - same_ab.bak <- generalise_antibiotic_name(ab.bak) == generalise_antibiotic_name(agent_name) - agent_formatted[same_ab.bak] <- paste0(agent_formatted[same_ab.bak], " (", ab[same_ab.bak], ")") - agent_formatted[!same_ab.bak & !same_ab] <- paste0( - agent_formatted[!same_ab.bak & !same_ab], - " (", ifelse(ab.bak[!same_ab.bak & !same_ab] == ab[!same_ab.bak & !same_ab], - "", - paste0(ab[!same_ab.bak & !same_ab], ", ") - ), - agent_name[!same_ab.bak & !same_ab], - ")" - ) - # this intro text will also be printed in the progress bar if the `progress` package is installed - intro_txt <- paste0( - "Interpreting ", method_long, ": ", ifelse(isTRUE(list(...)$is_data.frame), "column ", ""), - ifelse(length(unique(agent_formatted)) == 1, unique(agent_formatted), paste0(vector_and(agent_formatted, quotes = FALSE, sort = FALSE))), - mo_var_found, - ifelse(identical(reference_data, AMR::clinical_breakpoints), - paste0(", ", vector_and(font_bold(guideline_coerced, collapse = NULL), quotes = FALSE)), - "" - ), - "... " - ) - - # prepare used arguments ---- - method <- method_short - - metadata_mo <- get_mo_uncertainties() - - rise_warning <- FALSE - rise_notes <- FALSE - method_coerced <- toupper(method) - ab_coerced <- as.ab(ab) - - if (identical(reference_data, AMR::clinical_breakpoints)) { - breakpoints <- reference_data %pm>% - subset(guideline %in% guideline_coerced & method == method_coerced & ab %in% ab_coerced) - if (any(ab_coerced == "AMX") && nrow(breakpoints[breakpoints$ab == "AMX", , drop = FALSE]) == 0) { - ab_coerced[ab_coerced == "AMX"] <- "AMP" - breakpoints <- reference_data %pm>% - subset(guideline %in% guideline_coerced & method == method_coerced & ab %in% ab_coerced) - } - } else { - breakpoints <- reference_data %pm>% - subset(method == method_coerced & ab %in% ab_coerced) - } - - - # create the unique data frame to be filled to save time - df <- data.frame( - values = x, - values_bak = x, - guideline = guideline_coerced, - mo = mo, - ab = ab, - result = NA_sir_, - uti = uti, - host = host, - stringsAsFactors = FALSE - ) - if (method == "mic") { - if (any(guideline_coerced %like% "CLSI")) { - # CLSI in log 2 ---- - # CLSI says: if MIC is not a log2 value it must be rounded up to the nearest log2 value - log2_levels <- as.double(VALID_MIC_LEVELS[which(VALID_MIC_LEVELS %in% 2^c(-20:20))]) - test_values <- df$values[which(df$guideline %like% "CLSI")] - test_values_dbl <- as.double(test_values) - test_values_dbl[test_values %like% "^>[0-9]"] <- test_values_dbl[test_values %like% "^>[0-9]"] + 0.0000001 - test_values_dbl[test_values %like% "^<[0-9]"] <- test_values_dbl[test_values %like% "^>[0-9]"] - 0.0000001 - test_outcome <- vapply( - FUN.VALUE = double(1), - test_values_dbl, - function(mic_val) { - if (is.na(mic_val)) { - return(NA_real_) - } else { - # find the smallest log2 level that is >= mic_val - log2_val <- log2_levels[which(log2_levels >= as.double(mic_val))][1] - if (!is.na(log2_val) && as.double(mic_val) != log2_val) { - if (message_not_thrown_before("as.sir", "CLSI", "MICupscaling")) { - warning_("Some MICs were converted to the nearest higher log2 level, following the CLSI interpretation guideline.") - } - return(as.double(log2_val)) # will be MIC later - } else { - return(as.double(mic_val)) - } - } - } - ) - df$values[which(df$guideline %like% "CLSI" & test_values != test_outcome)] <- test_outcome[which(test_values != test_outcome)] - } - df$values <- as.mic(df$values) - } else if (method == "disk") { - # when as.sir.disk is called directly - df$values <- as.disk(df$values) - } - - df_unique <- unique(df[, c("guideline", "mo", "ab", "uti", "host"), drop = FALSE]) - mo_grams <- suppressWarnings(suppressMessages(mo_gramstain(df_unique$mo, language = NULL, keep_synonyms = FALSE))) - - # get all breakpoints, use humans as backup for animals - breakpoint_type_lookup <- breakpoint_type - if (breakpoint_type == "animal") { - breakpoint_type_lookup <- c(breakpoint_type, "human") - } - breakpoints <- breakpoints %pm>% - subset(type %in% breakpoint_type_lookup) - - if (isFALSE(include_screening)) { - # remove screening rules from the breakpoints table - breakpoints <- breakpoints %pm>% - subset(site %unlike% "screen" & ref_tbl %unlike% "screen") - } - if (isFALSE(include_PKPD)) { - # remove PKPD rules from the breakpoints table - breakpoints <- breakpoints %pm>% - subset(mo != "UNKNOWN" & ref_tbl %unlike% "PK.*PD") - } - - notes <- character(0) - - if (any(guideline_coerced %like% "EUCAST")) { - any_is_intrinsic_resistant <- FALSE - add_intrinsic_resistance_to_AMR_env() - } - - if (isTRUE(info) && nrow(df_unique) < 10 || nrow(breakpoints) == 0) { - # only print intro under 10 items, otherwise progressbar will print this and then it will be printed double - message_(intro_txt, appendLF = FALSE, as_note = FALSE) - } - p <- progress_ticker(n = nrow(df_unique), n_min = 10, title = font_blue(intro_txt), only_bar_percent = TRUE) - has_progress_bar <- !is.null(import_fn("progress_bar", "progress", error_on_fail = FALSE)) && nrow(df_unique) >= 10 - on.exit(close(p)) - - if (nrow(breakpoints) == 0) { - # apparently no breakpoints found - if (isTRUE(info)) { - message( - paste0(font_rose_bg(" WARNING "), "\n"), - font_black(paste0( - " ", AMR_env$bullet_icon, " No ", method_coerced, " breakpoints available for ", - suppressMessages(suppressWarnings(ab_name(unique(ab_coerced), language = NULL, tolower = TRUE))), - " (", unique(ab_coerced), ")." - ), collapse = "\n") - ) - } - - load_mo_uncertainties(metadata_mo) - return(rep(NA_sir_, nrow(df))) - } - - vectorise_log_entry <- function(x, len) { - if (length(x) == 1 && len > 1) { - rep(x, len) - } else { - x - } - } - - # set up parallel computing - n_cores <- get_n_cores(max_cores = max_cores) - - - # run the rules (df_unique is a row combination per mo/ab/uti/host) ---- - # for (i in seq_len(nrow(df_unique))) { - # p$tick() - run_sir_interpretation <- function(i) { - guideline_current <- df_unique[i, "guideline", drop = TRUE] - mo_current <- df_unique[i, "mo", drop = TRUE] - mo_gram_current <- mo_grams[i] - ab_current <- df_unique[i, "ab", drop = TRUE] - host_current <- df_unique[i, "host", drop = TRUE] - uti_current <- df_unique[i, "uti", drop = TRUE] - notes_current <- character(0) - rows <- which(as.character(df$mo) == mo_current & df$ab == ab_current & df$host == host_current & df$guideline == guideline_current) - if (!is.na(uti_current)) { - # also filter on UTIs - rows <- rows[df$uti[rows] == uti_current] - } - - if (length(rows) == 0) { - # this can happen if a host is unavailable, just continue with the next one, since a note about hosts having NA are already given at this point - # next - return(list( - rows = rows, - new_sir = NA_sir_[0], - sir_log = data.frame(), - notes_current = c(notes, notes_current) - )) - } - values <- df[rows, "values", drop = TRUE] - values_bak <- df[rows, "values_bak", drop = TRUE] - notes_current <- rep("", length(rows)) - new_sir <- rep(NA_sir_, length(rows)) - - # find different mo properties, as fast as possible - # TODO in case of VET09, we need to keep E. coli, also when users have Proteus in their data set - # TODO look up which species, at least E. coli - also Staph or Strep? - mo_current_genus <- AMR_env$MO_lookup$mo[match(AMR_env$MO_lookup$genus[match(mo_current, AMR_env$MO_lookup$mo)], AMR_env$MO_lookup$fullname)] - mo_current_family <- AMR_env$MO_lookup$mo[match(AMR_env$MO_lookup$family[match(mo_current, AMR_env$MO_lookup$mo)], AMR_env$MO_lookup$fullname)] - mo_current_order <- AMR_env$MO_lookup$mo[match(AMR_env$MO_lookup$order[match(mo_current, AMR_env$MO_lookup$mo)], AMR_env$MO_lookup$fullname)] - mo_current_class <- AMR_env$MO_lookup$mo[match(AMR_env$MO_lookup$class[match(mo_current, AMR_env$MO_lookup$mo)], AMR_env$MO_lookup$fullname)] - mo_current_rank <- AMR_env$MO_lookup$rank[match(mo_current, AMR_env$MO_lookup$mo)] - mo_current_name <- AMR_env$MO_lookup$fullname[match(mo_current, AMR_env$MO_lookup$mo)] - mo_current_oxygen_tolerance <- AMR_env$MO_lookup$oxygen_tolerance[match(mo_current, AMR_env$MO_lookup$mo)] - if (mo_current %in% AMR::microorganisms.groups$mo) { - # get the species group (might be more than 1 entry) - mo_current_species_group <- AMR::microorganisms.groups$mo_group[which(AMR::microorganisms.groups$mo == mo_current)] - } else { - mo_current_species_group <- NULL - } - mo_current_gram <- structure(character(0), class = c("mo", "character")) - if (identical(mo_gram_current, "Gram-negative")) { - mo_current_gram <- c(mo_current_gram, "B_GRAMN") - if (identical(mo_current_oxygen_tolerance, "anaerobe")) { - mo_current_gram <- c(mo_current_gram, "B_ANAER", "B_ANAER-NEG") - } - } else if (identical(mo_gram_current, "Gram-positive")) { - mo_current_gram <- c(mo_current_gram, "B_GRAMP") - if (identical(mo_current_oxygen_tolerance, "anaerobe")) { - mo_current_gram <- c(mo_current_gram, "B_ANAER", "B_ANAER-POS") - } - } - mo_current_other <- structure("UNKNOWN", class = c("mo", "character")) - # formatted for notes - mo_formatted <- mo_current_name - if (!mo_current_rank %in% c("kingdom", "phylum", "class", "order")) { - mo_formatted <- font_italic(mo_formatted, collapse = NULL) - } - ab_formatted <- paste0( - suppressMessages(suppressWarnings(ab_name(ab_current, language = NULL, tolower = TRUE))), - " (", ab_current, ")" - ) - - # gather all available breakpoints for current MO - # TODO for VET09 do not filter out E. coli and such - breakpoints_current <- breakpoints %pm>% - subset(ab == ab_current & guideline == guideline_current) %pm>% - subset(mo %in% c( - mo_current, mo_current_genus, mo_current_family, - mo_current_order, mo_current_class, - mo_current_species_group, - mo_current_gram, - mo_current_other - )) - - if (breakpoint_type == "animal") { - # 2025-03-13 for now, only strictly follow guideline for current host, no extrapolation - breakpoints_current <- breakpoints_current[which(breakpoints_current$host == host_current), , drop = FALSE] - } - - ## fall-back methods for veterinary guidelines ---- - ## TODO actually implement this well - if (FALSE) { - # if (breakpoint_type == "animal" && !host_current %in% breakpoints_current$host) { - if (guideline_coerced %like% "CLSI") { - # VET09 says that staph/strep/enterococcus BP can be extrapolated to all Gr+ cocci except for intrinsic resistance, so take all Gr+ cocci: - gram_plus_cocci_vet09 <- microorganisms$mo[microorganisms$genus %in% c("Staphylococcus", "Streptococcus", "Peptostreptococcus", "Aerococcus", "Micrococcus") & microorganisms$rank == "genus"] # TODO should probably include genera that were either of these before - - # HUMAN SUBSTITUTES - if (ab_current == "AZM" && mo_current_genus %in% gram_plus_cocci_vet09 && host_current %in% c("dogs", "cats", "horse")) { - # azithro can take human breakpoints for these agents - breakpoints_current <- breakpoints_current %pm>% subset(host == "human") - notes_current <- c(notes_current, paste0("Using ", font_bold("human"), " breakpoints for ", ab_formatted, " in Gram-positive cocci based on CLSI VET09.")) - } else if (ab_current == "CTX" && mo_current_order == "B_[ORD]_ENTRBCTR" && host_current %in% c("dogs", "cats", "horse")) { - # cefotax can take human breakpoints for these agents - breakpoints_current <- breakpoints_current %pm>% subset(host == "human") - notes_current <- c(notes_current, paste0("Using ", font_bold("human"), " breakpoints for ", ab_formatted, " in Enterobacterales based on CLSI VET09.")) - } else if (ab_current == "CAZ" && (mo_current_order == "B_[ORD]_ENTRBCTR" | mo_current == "B_PSDMN_AERG") && host_current %in% c("dogs", "cats", "horse")) { - # cefta can take human breakpoints for these agents - breakpoints_current <- breakpoints_current %pm>% subset(host == "human") - notes_current <- c(notes_current, paste0("Using ", font_bold("human"), " breakpoints for ", ab_formatted, " in Enterobacterales and ", font_italic("P. aeruginosa"), " based on CLSI VET09.")) - } else if (ab_current == "ERY" && mo_current_genus %in% gram_plus_cocci_vet09 && host_current %in% c("dogs", "cats", "horse")) { - # erythro can take human breakpoints for these agents - breakpoints_current <- breakpoints_current %pm>% subset(host == "human") - notes_current <- c(notes_current, paste0("Using ", font_bold("human"), " breakpoints for ", ab_formatted, " in Gram-positive cocci based on CLSI VET09.")) - } else if (ab_current == "IPM" && (mo_current_order == "B_[ORD]_ENTRBCTR" | mo_current == "B_PSDMN_AERG") && host_current %in% c("dogs", "cats", "horse")) { - # imipenem can take human breakpoints for these agents - breakpoints_current <- breakpoints_current %pm>% subset(host == "human") - notes_current <- c(notes_current, paste0("Using ", font_bold("human"), " breakpoints for ", ab_formatted, " in Enterobacterales and ", font_italic("P. aeruginosa"), " based on CLSI VET09.")) - } else if (ab_current == "LNZ" && mo_current_genus %in% gram_plus_cocci_vet09 && host_current %in% c("dogs", "cats")) { - # linezolid can take human breakpoints for these agents - breakpoints_current <- breakpoints_current %pm>% subset(host == "human") - notes_current <- c(notes_current, paste0("Using ", font_bold("human"), " breakpoints for ", ab_formatted, " in staphylococci/enterococci based on CLSI VET09.")) - } else if (ab_current == "NIT" && host_current %in% c("dogs", "cats")) { - # nitro can take human breakpoints for these agents - breakpoints_current <- breakpoints_current %pm>% subset(host == "human") - notes_current <- c(notes_current, paste0("Using ", font_bold("human"), " breakpoints for ", ab_formatted, " based on CLSI VET09.")) - } else if (ab_current == "PEN" && mo_current_genus %in% gram_plus_cocci_vet09 && host_current %in% c("dogs", "cats")) { - # penicillin can take human breakpoints for these agents - breakpoints_current <- breakpoints_current %pm>% subset(host == "human") - notes_current <- c(notes_current, paste0("Using ", font_bold("human"), " breakpoints for ", ab_formatted, " in Gram-positive cocci based on CLSI VET09.")) - } else if (ab_current == "RIF" && mo_current_genus %in% gram_plus_cocci_vet09 && host_current %in% c("dogs", "cats")) { - # rifampicin can take human breakpoints for staphylococci - breakpoints_current <- breakpoints_current %pm>% subset(host == "human") - notes_current <- c(notes_current, paste0("Using ", font_bold("human"), " breakpoints for ", ab_formatted, " in staphylococci based on CLSI VET09.")) - } else if (ab_current == "SXT" && host_current %in% c("dogs", "cats", "horse")) { - # trimethoprim-sulfamethoxazole (TMS) can take human breakpoints for these agents - breakpoints_current <- breakpoints_current %pm>% subset(host == "human") - notes_current <- c(notes_current, paste0("Using ", font_bold("human"), " breakpoints for ", ab_formatted, " based on CLSI VET09.")) - } else if (ab_current == "VAN" && host_current %in% c("dogs", "cats", "horse")) { - # vancomycin can take human breakpoints in these hosts - breakpoints_current <- breakpoints_current %pm>% subset(host == "human") - notes_current <- c(notes_current, paste0("Using ", font_bold("human"), " breakpoints for ", ab_formatted, " based on CLSI VET09.")) - } else if (host_current %in% c("dogs", "cats") && (mo_current_genus %in% c("B_AMYCS", "B_NOCRD", "B_CMPYL", "B_CRYNB", "B_ENTRC", "B_MYCBC", "B_PSDMN", "B_AERMN") | mo_current_class == "B_[CLS]_BTPRTBCT" | mo_current == "B_LISTR_MNCY")) { - # dog breakpoints if no canine/feline - # TODO do we still have dogs breakpoints at this point??? - breakpoints_current <- breakpoints_current %pm>% subset(host == "human") # WRONG - notes_current <- c(notes_current, paste0("Using ", font_bold("human"), " breakpoints for ", mo_formatted, " based on CLSI VET09.")) - } else { - # no specific CLSI solution for this, so only filter on current host (if no breakpoints available -> too bad) - breakpoints_current <- breakpoints_current %pm>% - subset(host == host_current) - } - } - } - - if (NROW(breakpoints_current) == 0) { - out <- data.frame( - # recycling 1 to 2 rows does not always seem to work, which is why vectorise_log_entry() was added - datetime = vectorise_log_entry(Sys.time(), length(rows)), - index = rows, - method = vectorise_log_entry(method_coerced, length(rows)), - ab_given = vectorise_log_entry(ab.bak[match(ab_current, df$ab)][1], length(rows)), - mo_given = vectorise_log_entry(mo.bak[match(mo_current, df$mo)][1], length(rows)), - host_given = vectorise_log_entry(host.bak[match(host_current, df$host)][1], length(rows)), - input_given = vectorise_log_entry(as.character(values_bak), length(rows)), - ab = vectorise_log_entry(ab_current, length(rows)), - mo = vectorise_log_entry(mo_current, length(rows)), - host = vectorise_log_entry(host_current, length(rows)), - input = vectorise_log_entry(as.character(values), length(rows)), - outcome = vectorise_log_entry(NA_sir_, length(rows)), - notes = vectorise_log_entry("No breakpoint available", length(rows)), - guideline = vectorise_log_entry(guideline_current, length(rows)), - ref_table = vectorise_log_entry(NA_character_, length(rows)), - uti = vectorise_log_entry(uti_current, length(rows)), - breakpoint_S_R = vectorise_log_entry(NA_character_, length(rows)), - site = vectorise_log_entry(NA_character_, length(rows)), - stringsAsFactors = FALSE - ) - out <- subset(out, !is.na(input_given)) - # AMR_env$sir_interpretation_history <- rbind_AMR(AMR_env$sir_interpretation_history, out) - # notes <- c(notes, notes_current) - # next - return(list( - rows = rows, - new_sir = new_sir, - sir_log = out, - notes_current = notes_current - )) - } - - # sort on host and taxonomic rank - # (this will e.g. prefer 'species' breakpoints over 'order' breakpoints) - if (is.na(uti_current)) { - breakpoints_current <- breakpoints_current %pm>% - # `uti` is a column in the data set - # this will put UTI = FALSE first, then UTI = NA, then UTI = TRUE - pm_mutate(uti_index = ifelse(!is.na(uti) & uti == FALSE, 1, - ifelse(is.na(uti), 2, - 3 - ) - )) %pm>% - # be as specific as possible (i.e. prefer species over genus): - pm_arrange(rank_index, uti_index) - } else if (uti_current == TRUE) { - breakpoints_current <- breakpoints_current %pm>% - subset(uti == TRUE) %pm>% - # be as specific as possible (i.e. prefer species over genus): - pm_arrange(rank_index) - } - - # throw messages for different body sites - site <- breakpoints_current[1L, "site", drop = FALSE] # this is the one we'll take - if (is.na(site)) { - site <- paste0("an unspecified body site") - } else { - site <- paste0("body site '", site, "'") - } - if (nrow(breakpoints_current) == 1 && all(breakpoints_current$uti == TRUE) && is.na(uti_current) && message_not_thrown_before("as.sir", "uti", ab_current)) { - # only UTI breakpoints available - notes_current <- paste0( - notes_current, "\n", - paste0("Breakpoints for ", font_bold(ab_formatted), " in ", mo_formatted, " are only available for (uncomplicated) urinary tract infections (UTI); assuming `uti = TRUE`.") - ) - } else if (nrow(breakpoints_current) > 1 && length(unique(breakpoints_current$site)) > 1 && any(is.na(uti_current)) && all(c(TRUE, FALSE) %in% breakpoints_current$uti, na.rm = TRUE) && message_not_thrown_before("as.sir", "siteUTI", mo_current, ab_current)) { - # both UTI and Non-UTI breakpoints available - breakpoints_current <- breakpoints_current %pm>% - pm_filter(uti == FALSE) - notes_current <- paste0( - notes_current, "\n", - paste0("Breakpoints for UTI ", font_bold("and"), " non-UTI available for ", ab_formatted, " in ", mo_formatted, " - assuming ", site, ". Use argument `uti` to set which isolates are from urine. See `?as.sir`.") - ) - } else if (nrow(breakpoints_current) > 1 && length(unique(breakpoints_current$site)) > 1 && all(breakpoints_current$uti == FALSE, na.rm = TRUE) && message_not_thrown_before("as.sir", "siteOther", mo_current, ab_current)) { - # breakpoints for multiple body sites available - notes_current <- paste0( - notes_current, "\n", - paste0("Multiple breakpoints available for ", font_bold(ab_formatted), " in ", mo_formatted, " - assuming ", site, ".") - ) - } - - # first check if mo is intrinsic resistant - if (isTRUE(add_intrinsic_resistance) && guideline_current %like% "EUCAST" && paste(mo_current, ab_current) %in% AMR_env$intrinsic_resistant) { - new_sir <- rep(as.sir("R"), length(rows)) - notes_current <- paste0( - notes_current, "\n", - paste0("Intrinsic resistance applied for ", ab_formatted, " in ", mo_formatted, "") - ) - out <- data.frame() - return(list( - rows = rows, - new_sir = new_sir, - sir_log = out, - notes_current = notes_current - )) - } else if (nrow(breakpoints_current) == 0) { - # no rules available - new_sir <- rep(NA_sir_, length(rows)) - return(list( - rows = rows, - new_sir = new_sir, - sir_log = data.frame(), - notes_current = notes_current - )) - } else { - # then run the rules - breakpoints_current <- breakpoints_current[1L, , drop = FALSE] - - notes_current <- paste0( - notes_current, "\n", - ifelse(breakpoints_current$mo == "UNKNOWN" | breakpoints_current$ref_tbl %like% "PK.*PD", - "Some PK/PD breakpoints were applied - use `include_PKPD = FALSE` to prevent this", - "" - ), - "\n", - ifelse(breakpoints_current$site %like% "screen" | breakpoints_current$ref_tbl %like% "screen", - "Some screening breakpoints were applied - use `include_screening = FALSE` to prevent this", - "" - ), - "\n", - ifelse(method == "mic" & capped_mic_handling %in% c("conservative", "inverse") & as.character(values_bak) %like% "^[<][0-9]", - paste0("MIC values with the operator '<' are all considered 'S' since capped_mic_handling = \"", capped_mic_handling, "\""), - "" - ), - "\n", - ifelse(method == "mic" & capped_mic_handling %in% c("conservative", "inverse") & as.character(values_bak) %like% "^[>][0-9]", - paste0("MIC values with the operator '>' are all considered 'R' since capped_mic_handling = \"", capped_mic_handling, "\""), - "" - ), - "\n", - ifelse(method == "mic" & capped_mic_handling %in% c("conservative", "standard") & as.character(values_bak) %like% "^[><]=[0-9]" & as.double(values) > breakpoints_current$breakpoint_S & as.double(values) < breakpoints_current$breakpoint_R, - paste0("MIC values within the breakpoint guideline range with the operator '<=' or '>=' are considered 'NI' (non-interpretable) since capped_mic_handling = \"", capped_mic_handling, "\""), - "" - ), - "\n", - ifelse(method == "mic" & capped_mic_handling %in% c("conservative", "standard") & as.character(values_bak) %like% "^<=[0-9]" & as.double(values) == breakpoints_current$breakpoint_R, - paste0("MIC values at the R breakpoint with the operator '<=' are considered 'NI' (non-interpretable) since capped_mic_handling = \"", capped_mic_handling, "\""), - "" - ), - "\n", - ifelse(method == "mic" & capped_mic_handling %in% c("conservative", "standard") & as.character(values_bak) %like% "^>=[0-9]" & as.double(values) == breakpoints_current$breakpoint_S, - paste0("MIC values at the S breakpoint with the operator '>=' are considered 'NI' (non-interpretable) since capped_mic_handling = \"", capped_mic_handling, "\""), - "" - ) - ) - if (isTRUE(substitute_missing_r_breakpoint) && !is.na(breakpoints_current$breakpoint_S) && is.na(breakpoints_current$breakpoint_R)) { - # breakpoints_current only has 1 row at this moment - breakpoints_current$breakpoint_R <- breakpoints_current$breakpoint_S - notes_current <- paste0( - notes_current, "\n", - ifelse(!is.na(breakpoints_current$breakpoint_S) & is.na(breakpoints_current$breakpoint_R), - "NAs because of missing R breakpoints were substituted with R since substitute_missing_r_breakpoint = TRUE", - "" - ) - ) - } - - ## actual interpretation ---- - if (method == "mic") { - new_sir <- case_when_AMR( - is.na(values) ~ NA_sir_, - capped_mic_handling %in% c("conservative", "inverse") & as.character(values_bak) %like% "^[<][0-9]" ~ as.sir("S"), - capped_mic_handling %in% c("conservative", "inverse") & as.character(values_bak) %like% "^[>][0-9]" ~ as.sir("R"), - capped_mic_handling %in% c("conservative", "standard") & as.character(values_bak) %like% "^[><]=[0-9]" & as.double(values) > breakpoints_current$breakpoint_S & as.double(values) < breakpoints_current$breakpoint_R ~ as.sir("NI"), - capped_mic_handling %in% c("conservative", "standard") & as.character(values_bak) %like% "^<=[0-9]" & as.double(values) == breakpoints_current$breakpoint_R ~ as.sir("NI"), - capped_mic_handling %in% c("conservative", "standard") & as.character(values_bak) %like% "^>=[0-9]" & as.double(values) == breakpoints_current$breakpoint_S ~ as.sir("NI"), - values <= breakpoints_current$breakpoint_S ~ as.sir("S"), - guideline_current %like% "EUCAST" & values > breakpoints_current$breakpoint_R ~ as.sir("R"), - guideline_current %like% "CLSI" & values >= breakpoints_current$breakpoint_R ~ as.sir("R"), - # return "I" or "SDD" when breakpoints are in the middle - !is.na(breakpoints_current$breakpoint_S) & !is.na(breakpoints_current$breakpoint_R) & breakpoints_current$is_SDD == TRUE ~ as.sir("SDD"), - !is.na(breakpoints_current$breakpoint_S) & !is.na(breakpoints_current$breakpoint_R) & breakpoints_current$is_SDD == FALSE ~ as.sir("I"), - # and NA otherwise - TRUE ~ NA_sir_ - ) - } else if (method == "disk") { - new_sir <- case_when_AMR( - is.na(values) ~ NA_sir_, - as.double(values) >= as.double(breakpoints_current$breakpoint_S) ~ as.sir("S"), - guideline_current %like% "EUCAST" & as.double(values) < as.double(breakpoints_current$breakpoint_R) ~ as.sir("R"), - guideline_current %like% "CLSI" & as.double(values) <= as.double(breakpoints_current$breakpoint_R) ~ as.sir("R"), - # return "I" or "SDD" when breakpoints are in the middle - !is.na(breakpoints_current$breakpoint_S) & !is.na(breakpoints_current$breakpoint_R) & breakpoints_current$is_SDD == TRUE ~ as.sir("SDD"), - !is.na(breakpoints_current$breakpoint_S) & !is.na(breakpoints_current$breakpoint_R) & breakpoints_current$is_SDD == FALSE ~ as.sir("I"), - # and NA otherwise - TRUE ~ NA_sir_ - ) - } - - # write to verbose output - notes_current <- trimws2(notes_current) - notes_current[notes_current == ""] <- NA_character_ - out <- data.frame( - # recycling 1 to 2 rows does not always seem to work, which is why vectorise_log_entry() was added - datetime = vectorise_log_entry(Sys.time(), length(rows)), - index = rows, - method = vectorise_log_entry(method_coerced, length(rows)), - ab_given = vectorise_log_entry(ab.bak[match(ab_current, df$ab)][1], length(rows)), - mo_given = vectorise_log_entry(mo.bak[match(mo_current, df$mo)][1], length(rows)), - host_given = vectorise_log_entry(host.bak[match(host_current, df$host)][1], length(rows)), - input_given = vectorise_log_entry(as.character(values_bak), length(rows)), - ab = vectorise_log_entry(breakpoints_current[, "ab", drop = TRUE], length(rows)), - mo = vectorise_log_entry(breakpoints_current[, "mo", drop = TRUE], length(rows)), - host = vectorise_log_entry(breakpoints_current[, "host", drop = TRUE], length(rows)), - input = vectorise_log_entry(as.character(values), length(rows)), - outcome = vectorise_log_entry(as.sir(new_sir), length(rows)), - notes = font_stripstyle(notes_current), # vectorise_log_entry(paste0(font_stripstyle(notes_current), collapse = "\n"), length(rows)), - guideline = vectorise_log_entry(guideline_current, length(rows)), - ref_table = vectorise_log_entry(breakpoints_current[, "ref_tbl", drop = TRUE], length(rows)), - uti = vectorise_log_entry(breakpoints_current[, "uti", drop = TRUE], length(rows)), - breakpoint_S_R = vectorise_log_entry(paste0(breakpoints_current[, "breakpoint_S", drop = TRUE], "-", breakpoints_current[, "breakpoint_R", drop = TRUE]), length(rows)), - site = vectorise_log_entry(breakpoints_current[, "site", drop = TRUE], length(rows)), - stringsAsFactors = FALSE - ) - out <- subset(out, !is.na(input_given)) - AMR_env$sir_interpretation_history <- rbind_AMR(AMR_env$sir_interpretation_history, out) - } - - return(list( - rows = rows, - new_sir = new_sir, - sir_log = out, - notes_current = c(notes, notes_current) - )) - - # notes <- c(notes, notes_current) - # df[rows, "result"] <- new_sir - } - - close(p) - - if (isTRUE(parallel)) { - # message_("Running in parallel mode using ", font_bold(n_cores), " core", ifelse(n_cores == 1, "", "s"), ".\n\n") - if (.Platform$OS.type == "windows") { - cl <- parallel::makeCluster(n_cores, type = "PSOCK") - on.exit(parallel::stopCluster(cl), add = TRUE) - parallel::clusterExport(cl, varlist = c( - "df", "df_unique", "mo_grams", - "ab.bak", "mo.bak", "host.bak", - "breakpoints", "breakpoint_type", "guideline_coerced", - "metadata_mo", "AMR_env", - "method", "method_coerced", "intro_txt", - "capped_mic_handling", "add_intrinsic_resistance", - "substitute_missing_r_breakpoint", "include_screening", "include_PKPD", - "verbose", "info", "current_df", - "reference_data", "conserve_capped_values" - ), envir = environment()) - results <- parallel::parLapply(cl, seq_len(nrow(df_unique)), run_sir_interpretation) - } else { - results <- parallel::mclapply(seq_len(nrow(df_unique)), run_sir_interpretation, mc.cores = n_cores) - } - } else { - results <- lapply(seq_len(nrow(df_unique)), run_sir_interpretation) - } - - # clean results - results <- Filter(Negate(is.null), results) - rr <<- results - - # bind results back - if (length(results) > 0) { - for (res in results) { - df[res$rows, "result"] <- res$new_sir - } - sir_logs_all <- do.call(rbind, lapply(results, function(x) x$sir_log)) - AMR_env$sir_interpretation_history <- rbind_AMR(AMR_env$sir_interpretation_history, sir_logs_all) - notes <- unlist(lapply(results, function(x) x$notes_current)) - } - - - # printing messages - if (isTRUE(info)) { - if (has_progress_bar == TRUE) { - # the progress bar has overwritten the intro text, so: - message_(intro_txt, appendLF = FALSE, as_note = FALSE) - } - notes <- notes[!trimws2(notes) %in% c("", NA_character_)] - if (length(notes) > 0) { - if (isTRUE(rise_warning)) { - message(font_rose_bg(" WARNING ")) - } else { - message(font_yellow_bg(" NOTE ")) - } - notes <- unique(notes) - if (isTRUE(verbose) || length(notes) == 1 || NROW(AMR_env$sir_interpretation_history) == 0) { - for (i in seq_along(notes)) { - message(word_wrap(" ", AMR_env$bullet_icon, " ", notes[i], add_fn = font_black)) - } - } else { - message(word_wrap(" ", AMR_env$bullet_icon, " There were multiple notes. Print or View `sir_interpretation_history()` to examine them, or use `as.sir(..., verbose = TRUE)` next time to directly print them here.", add_fn = font_black)) - } - } else { - message(font_green_bg(" OK ")) - } - } - - load_mo_uncertainties(metadata_mo) - - # reorder AMR_env$sir_interpretation_history to get a clean ordering on index - old_part <- AMR_env$sir_interpretation_history[seq_len(current_sir_interpretation_history), , drop = FALSE] - new_part <- AMR_env$sir_interpretation_history[c((current_sir_interpretation_history + 1):NROW(AMR_env$sir_interpretation_history)), , drop = FALSE] - new_part <- new_part[order(new_part$index), , drop = FALSE] - AMR_env$sir_interpretation_history <- rbind_AMR(old_part, new_part) - - df$result -} - -#' @rdname as.sir -#' @param clean A [logical] to indicate whether previously stored results should be forgotten after returning the 'logbook' with results. -#' @export -sir_interpretation_history <- function(clean = FALSE) { - meet_criteria(clean, allow_class = "logical", has_length = 1) - out <- AMR_env$sir_interpretation_history - out$outcome <- as.sir(out$outcome) - if (isTRUE(clean)) { - AMR_env$sir_interpretation_history <- AMR_env$sir_interpretation_history[0, , drop = FALSE] - } - if (pkg_is_available("tibble")) { - out <- import_fn("as_tibble", "tibble")(out) - } - as_original_data_class(out, class(out), extra_class = "sir_log") -} - -#' @method print sir_log -#' @export -#' @noRd -print.sir_log <- function(x, ...) { - if (NROW(x) == 0) { - message_("No results to print. Run `as.sir()` on MIC values or disk diffusion zones first to print a 'logbook' data set here.") - return(invisible(NULL)) - } - class(x) <- class(x)[class(x) != "sir_log"] - print(x, ...) -} - -# will be exported using s3_register() in R/zzz.R -pillar_shaft.sir <- function(x, ...) { - out <- trimws(format(x)) - if (has_colour()) { - # colours will anyway not work when has_colour() == FALSE, - # but then the indentation should also not be applied - out[is.na(x)] <- font_grey(" NA") - out[x == "NI"] <- font_grey_bg(" NI ") - out[x == "S"] <- font_green_bg(" S ") - out[x == "I"] <- font_orange_bg(" I ") - out[x == "SDD"] <- font_orange_bg(" SDD ") - out[x == "R"] <- font_rose_bg(" R ") - } - create_pillar_column(out, align = "left", width = 5) -} - -# will be exported using s3_register() in R/zzz.R -type_sum.sir <- function(x, ...) { - "sir" -} - -# will be exported using s3_register() in R/zzz.R -freq.sir <- function(x, ...) { - x_name <- deparse(substitute(x)) - x_name <- gsub(".*[$]", "", x_name) - if (x_name %in% c("x", ".")) { - # try again going through system calls - x_name <- stats::na.omit(vapply( - FUN.VALUE = character(1), - sys.calls(), - function(call) { - call_txt <- as.character(call) - ifelse(call_txt[1] %like% "freq$", call_txt[length(call_txt)], character(0)) - } - ))[1L] - } - ab <- suppressMessages(suppressWarnings(as.ab(x_name))) - digits <- list(...)$digits - if (is.null(digits)) { - digits <- 2 - } - if (!is.na(ab)) { - cleaner::freq.default( - x = x, ..., - .add_header = list( - Drug = paste0(ab_name(ab, language = NULL), " (", ab, ", ", paste(ab_atc(ab), collapse = "/"), ")"), - `Drug group` = ab_group(ab, language = NULL), - `%SI` = trimws(percentage(susceptibility(x, minimum = 0, as_percent = FALSE), - digits = digits - )) - ) - ) - } else { - cleaner::freq.default( - x = x, ..., - .add_header = list( - `%SI` = trimws(percentage(susceptibility(x, minimum = 0, as_percent = FALSE), - digits = digits - )) - ) - ) - } -} - - -# will be exported using s3_register() in R/zzz.R -get_skimmers.sir <- function(column) { - # get the variable name 'skim_variable' - name_call <- function(.data) { - calls <- sys.calls() - frms <- sys.frames() - calls_txt <- vapply(calls, function(x) paste(deparse(x), collapse = ""), FUN.VALUE = character(1)) - if (any(calls_txt %like% "skim_variable", na.rm = TRUE)) { - ind <- which(calls_txt %like% "skim_variable")[1L] - vars <- tryCatch(eval(parse(text = ".data$skim_variable$sir"), envir = frms[[ind]]), - error = function(e) NULL - ) - tryCatch(ab_name(as.character(calls[[length(calls)]][[2]]), language = NULL), - error = function(e) NA_character_ - ) - } else { - NA_character_ - } - } - - skimr::sfl( - skim_type = "sir", - ab_name = name_call, - count_R = count_R, - count_S = count_susceptible, - count_I = count_I, - prop_R = ~ proportion_R(., minimum = 0), - prop_S = ~ susceptibility(., minimum = 0), - prop_I = ~ proportion_I(., minimum = 0) - ) -} - -#' @method print sir -#' @export -#' @noRd -print.sir <- function(x, ...) { - x_name <- deparse(substitute(x)) - cat("Class 'sir'\n") - # TODO for #170 - # if (!is.null(attributes(x)$guideline) && !all(is.na(attributes(x)$guideline))) { - # cat(font_blue(word_wrap("These values were interpreted using ", - # font_bold(vector_and(attributes(x)$guideline, quotes = FALSE)), - # " based on ", - # vector_and(attributes(x)$method, quotes = FALSE), - # " values. ", - # "Use `sir_interpretation_history(", x_name, ")` to return a full logbook."))) - # cat("\n") - # } - print(as.character(x), quote = FALSE) -} - - -#' @method as.double sir -#' @export -as.double.sir <- function(x, ...) { - dbls <- rep(NA_real_, length(x)) - dbls[x == "S"] <- 1 - dbls[x %in% c("SDD", "I")] <- 2 - dbls[x == "R"] <- 3 - dbls -} - -#' @method droplevels sir -#' @export -#' @noRd -droplevels.sir <- function(x, exclude = if (any(is.na(levels(x)))) NULL else NA, ...) { - x <- droplevels.factor(x, exclude = exclude, ...) - class(x) <- c("sir", "ordered", "factor") - x -} - -#' @method summary sir -#' @export -#' @noRd -summary.sir <- function(object, ...) { - x <- object - n <- sum(!is.na(x)) - S <- sum(x == "S", na.rm = TRUE) - SDD <- sum(x == "SDD", na.rm = TRUE) - I <- sum(x == "I", na.rm = TRUE) - R <- sum(x == "R", na.rm = TRUE) - NI <- sum(x == "NI", na.rm = TRUE) - pad <- function(x) { - if (is.na(x)) { - return("??") - } - if (x == "0%") { - x <- " 0.0%" - } - if (nchar(x) < 5) { - x <- paste0(rep(" ", 5 - nchar(x)), x) - } - x - } - value <- c( - "Class" = "sir", - "%S" = paste0(pad(percentage(S / n, digits = 1)), " (n=", S, ")"), - "%SDD" = paste0(pad(percentage(SDD / n, digits = 1)), " (n=", SDD, ")"), - "%I" = paste0(pad(percentage(I / n, digits = 1)), " (n=", I, ")"), - "%R" = paste0(pad(percentage(R / n, digits = 1)), " (n=", R, ")"), - "%NI" = paste0(pad(percentage(NI / n, digits = 1)), " (n=", NI, ")") - ) - class(value) <- c("summaryDefault", "table") - value -} - -#' @method [<- sir -#' @export -#' @noRd -"[<-.sir" <- function(i, j, ..., value) { - value <- as.sir(value) - y <- NextMethod() - attributes(y) <- attributes(i) - y -} -#' @method [[<- sir -#' @export -#' @noRd -"[[<-.sir" <- function(i, j, ..., value) { - value <- as.sir(value) - y <- NextMethod() - attributes(y) <- attributes(i) - y -} -#' @method c sir -#' @export -#' @noRd -c.sir <- function(...) { - lst <- list(...) - - # TODO for #170 - # guideline <- vapply(FUN.VALUE = character(1), lst, function(x) attributes(x)$guideline %or% NA_character_) - # mo <- vapply(FUN.VALUE = character(1), lst, function(x) attributes(x)$mo %or% NA_character_) - # ab <- vapply(FUN.VALUE = character(1), lst, function(x) attributes(x)$ab %or% NA_character_) - # method <- vapply(FUN.VALUE = character(1), lst, function(x) attributes(x)$method %or% NA_character_) - # ref_tbl <- vapply(FUN.VALUE = character(1), lst, function(x) attributes(x)$ref_tbl %or% NA_character_) - # ref_breakpoints <- vapply(FUN.VALUE = character(1), lst, function(x) attributes(x)$ref_breakpoints %or% NA_character_) - - out <- as.sir(unlist(lapply(list(...), as.character))) - - # TODO for #170 - # if (!all(is.na(guideline))) { - # attributes(out)$guideline <- guideline - # attributes(out)$mo <- mo - # attributes(out)$ab <- ab - # attributes(out)$method <- method - # attributes(out)$ref_tbl <- ref_tbl - # attributes(out)$ref_breakpoints <- ref_breakpoints - # } - - out -} - -#' @method unique sir -#' @export -#' @noRd -unique.sir <- function(x, incomparables = FALSE, ...) { - y <- NextMethod() - attributes(y) <- attributes(x) - y -} - -#' @method rep sir -#' @export -#' @noRd -rep.sir <- function(x, ...) { - y <- NextMethod() - attributes(y) <- attributes(x) - y -} - -check_reference_data <- function(reference_data, .call_depth) { - if (!identical(reference_data, AMR::clinical_breakpoints)) { - class_sir <- vapply(FUN.VALUE = character(1), AMR::clinical_breakpoints, function(x) paste0("<", class(x), ">", collapse = " and ")) - class_ref <- vapply(FUN.VALUE = character(1), reference_data, function(x) paste0("<", class(x), ">", collapse = " and ")) - if (!all(names(class_sir) == names(class_ref))) { - stop_("`reference_data` must have the same column names as the 'clinical_breakpoints' data set.", call = .call_depth) - } - if (!all(class_sir == class_ref)) { - stop_("`reference_data` must be the same structure as the 'clinical_breakpoints' data set. Column '", names(class_ref[class_sir != class_ref][1]), "' is of class ", class_ref[class_sir != class_ref][1], ", but should be of class ", class_sir[class_sir != class_ref][1], ".", call = .call_depth) - } - } -} diff --git a/data-raw/wisca_reprex.R b/data-raw/wisca_reprex.R new file mode 100644 index 000000000..bed01caca --- /dev/null +++ b/data-raw/wisca_reprex.R @@ -0,0 +1,23 @@ +df <- example_isolates |> + filter_first_isolate(method = "e", episode_days = 14) |> + mutate(mo = ifelse(mo_genus(mo) == "Klebsiella", as.mo("Klebsiella"), mo)) |> + top_n_microorganisms(10) + +out_new <- df |> antibiogram(c("TZP","TZP+GEN","TZP+TOB"), wisca = TRUE, syndromic_group = "ward") +out_nonwisca <- df |> antibiogram(c("TZP","TZP+GEN","TZP+TOB"), + syndromic_group = "ward", + mo_transform = function(x) "", + digits = 1, + minimum = 10, + formatting_type = 14) |> + as_tibble() |> + select(-Pathogen) + +# parameters_amr.R#L110: no filter on ward, so pts are only in 1 ward, depending on order of data +# parameters_amr.R: number of first isolates are determined on the whole data set, while Klebsiella is aggregated afterwards (=duplicates on genus level) + +source("~/Downloads/estimate_definition_amr.R") + + + + diff --git a/index.md b/index.md index cdb26f45b..2e9f40a5e 100644 --- a/index.md +++ b/index.md @@ -155,8 +155,10 @@ example_isolates %>% #> ℹ Using column 'mo' as input for mo_fullname() #> ℹ Using column 'mo' as input for mo_is_gram_negative() #> ℹ Using column 'mo' as input for mo_is_intrinsic_resistant() -#> ℹ Determining intrinsic resistance based on 'EUCAST Expected Resistant Phenotypes' v1.2 (2023). This note will be shown once per session. -#> ℹ For aminoglycosides() using columns 'GEN' (gentamicin), 'TOB' (tobramycin), 'AMK' (amikacin), and 'KAN' (kanamycin) +#> ℹ Determining intrinsic resistance based on 'EUCAST Expected Resistant +#> Phenotypes' v1.2 (2023). This note will be shown once per session. +#> ℹ For aminoglycosides() using columns 'GEN' (gentamicin), 'TOB' +#> (tobramycin), 'AMK' (amikacin), and 'KAN' (kanamycin) #> ℹ For carbapenems() using columns 'IPM' (imipenem) and 'MEM' (meropenem) #> # A tibble: 35 × 7 #> bacteria GEN TOB AMK KAN IPM MEM @@ -194,9 +196,9 @@ output format automatically (such as markdown, LaTeX, HTML, etc.). ``` r antibiogram(example_isolates, antimicrobials = c(aminoglycosides(), carbapenems())) -#> ℹ For aminoglycosides() using columns 'GEN' (gentamicin), 'TOB' (tobramycin), 'AMK' (amikacin), and 'KAN' (kanamycin) +#> ℹ For aminoglycosides() using columns 'GEN' (gentamicin), 'TOB' +#> (tobramycin), 'AMK' (amikacin), and 'KAN' (kanamycin) #> ℹ For carbapenems() using columns 'IPM' (imipenem) and 'MEM' (meropenem) -#> ℹ 502 combinations had less than minimum = 30 results and were ignored ``` | Pathogen | Amikacin | Gentamicin | Imipenem | Kanamycin | Meropenem | Tobramycin | @@ -219,7 +221,6 @@ yield higher empiric coverage: antibiogram(example_isolates, antimicrobials = c("TZP", "TZP+TOB", "TZP+GEN"), mo_transform = "gramstain") -#> ℹ 3 combinations had less than minimum = 30 results and were ignored ``` | Pathogen | Piperacillin/tazobactam | Piperacillin/tazobactam + Gentamicin | Piperacillin/tazobactam + Tobramycin | @@ -237,7 +238,6 @@ antibiogram(example_isolates, mo_transform = "gramstain", ab_transform = "name", language = "uk") # Ukrainian -#> ℹ 3 combinations had less than minimum = 30 results and were ignored ``` | Збудник | Гентаміцин | Тобраміцин | Ципрофлоксацин | @@ -321,13 +321,15 @@ out <- example_isolates %>% # calculate AMR using resistance(), over all aminoglycosides and polymyxins: summarise(across(c(aminoglycosides(), polymyxins()), resistance)) -#> ℹ For aminoglycosides() using columns 'GEN' (gentamicin), 'TOB' (tobramycin), 'AMK' (amikacin), and 'KAN' (kanamycin) +#> ℹ For aminoglycosides() using columns 'GEN' (gentamicin), 'TOB' +#> (tobramycin), 'AMK' (amikacin), and 'KAN' (kanamycin) #> ℹ For polymyxins() using column 'COL' (colistin) #> Warning: There was 1 warning in `summarise()`. #> ℹ In argument: `across(c(aminoglycosides(), polymyxins()), resistance)`. #> ℹ In group 3: `ward = "Outpatient"`. #> Caused by warning: -#> ! Introducing NA: only 23 results available for KAN in group: ward = "Outpatient" (minimum = 30). +#> ! Introducing NA: only 23 results available for KAN in group: ward = +#> "Outpatient" (minimum = 30). out #> # A tibble: 3 × 6 #> ward GEN TOB AMK KAN COL diff --git a/man/AMR.Rd b/man/AMR.Rd index 1540b0d40..81bb22396 100644 --- a/man/AMR.Rd +++ b/man/AMR.Rd @@ -28,11 +28,11 @@ A BibTeX entry for LaTeX users is: \description{ Welcome to the \code{AMR} package. -The \code{AMR} package is a peer-reviewed, \href{https://amr-for-r.org/#copyright}{free and open-source} R package with \href{https://en.wikipedia.org/wiki/Dependency_hell}{zero dependencies} to simplify the analysis and prediction of Antimicrobial Resistance (AMR) and to work with microbial and antimicrobial data and properties, by using evidence-based methods. \strong{Our aim is to provide a standard} for clean and reproducible AMR data analysis, that can therefore empower epidemiological analyses to continuously enable surveillance and treatment evaluation in any setting. \href{https://amr-for-r.org/authors.html}{Many different researchers} from around the globe are continually helping us to make this a successful and durable project! +The \code{AMR} package is a peer-reviewed, \href{https://amr-for-r.org/#copyright}{free and open-source} R package with \href{https://en.wikipedia.org/wiki/Dependency_hell}{zero dependencies} to simplify the analysis and prediction of Antimicrobial Resistance (AMR) and to work with microbial and antimicrobial data and properties, by using evidence-based methods. \strong{Our aim is to provide a standard} for clean and reproducible AMR data analysis, that can therefore empower epidemiological analyses to continuously enable surveillance and treatment evaluation in any setting. We are a team of \href{https://amr-for-r.org/authors.html}{many different researchers} from around the globe to make this a successful and durable project! This work was published in the Journal of Statistical Software (Volume 104(3); \doi{10.18637/jss.v104.i03}) and formed the basis of two PhD theses (\doi{10.33612/diss.177417131} and \doi{10.33612/diss.192486375}). -After installing this package, R knows \href{https://amr-for-r.org/reference/microorganisms.html}{\strong{~79 000 microorganisms}} (updated June 2024) and all \href{https://amr-for-r.org/reference/antimicrobials.html}{\strong{~620 antibiotic, antimycotic and antiviral drugs}} 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). \strong{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 public \href{https://www.rug.nl}{University of Groningen}, in collaboration with non-profit organisations \href{https://www.certe.nl}{Certe Medical Diagnostics and Advice Foundation} and \href{https://www.umcg.nl}{University Medical Center Groningen}. +After installing this package, R knows \href{https://amr-for-r.org/reference/microorganisms.html}{\strong{~79 000 distinct microbial species}} (updated June 2024) and all \href{https://amr-for-r.org/reference/antimicrobials.html}{\strong{~620 antimicrobial and antiviral drugs}} 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 2011-2025 and EUCAST 2011-2025 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). \strong{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 \href{https://www.rug.nl}{University of Groningen} and the \href{https://www.umcg.nl}{University Medical Center Groningen}. The \code{AMR} package is available in English, Chinese, Czech, Danish, Dutch, Finnish, French, German, Greek, Italian, Japanese, Norwegian, Polish, Portuguese, Romanian, Russian, Spanish, Swedish, Turkish, and Ukrainian. Antimicrobial drug (group) names and colloquial microorganism names are provided in these languages. } @@ -42,7 +42,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \seealso{ diff --git a/man/WHONET.Rd b/man/WHONET.Rd index 8ebfcd480..580b09dbc 100644 --- a/man/WHONET.Rd +++ b/man/WHONET.Rd @@ -47,7 +47,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \examples{ diff --git a/man/ab_property.Rd b/man/ab_property.Rd index ad79afee7..61ede52d7 100644 --- a/man/ab_property.Rd +++ b/man/ab_property.Rd @@ -103,7 +103,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \examples{ diff --git a/man/antimicrobial_selectors.Rd b/man/antimicrobial_selectors.Rd index ed8b80a2f..6750a8a87 100644 --- a/man/antimicrobial_selectors.Rd +++ b/man/antimicrobial_selectors.Rd @@ -219,7 +219,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \examples{ diff --git a/man/antimicrobials.Rd b/man/antimicrobials.Rd index 56691721c..f54fd9046 100644 --- a/man/antimicrobials.Rd +++ b/man/antimicrobials.Rd @@ -69,7 +69,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \section{WHOCC}{ diff --git a/man/as.ab.Rd b/man/as.ab.Rd index d7d2d3b95..8492cbe8a 100644 --- a/man/as.ab.Rd +++ b/man/as.ab.Rd @@ -72,7 +72,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \examples{ diff --git a/man/as.av.Rd b/man/as.av.Rd index 99d8f2fcf..89cc11945 100644 --- a/man/as.av.Rd +++ b/man/as.av.Rd @@ -64,7 +64,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \examples{ diff --git a/man/as.mo.Rd b/man/as.mo.Rd index 01eb17ab9..dbcaaefde 100644 --- a/man/as.mo.Rd +++ b/man/as.mo.Rd @@ -208,7 +208,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \examples{ diff --git a/man/as.sir.Rd b/man/as.sir.Rd index 00d0b3b78..c2c206ed1 100644 --- a/man/as.sir.Rd +++ b/man/as.sir.Rd @@ -264,7 +264,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \examples{ diff --git a/man/av_property.Rd b/man/av_property.Rd index 6d09acff8..ff4a15880 100644 --- a/man/av_property.Rd +++ b/man/av_property.Rd @@ -83,7 +83,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \examples{ diff --git a/man/clinical_breakpoints.Rd b/man/clinical_breakpoints.Rd index f62e33684..ac281e683 100644 --- a/man/clinical_breakpoints.Rd +++ b/man/clinical_breakpoints.Rd @@ -69,7 +69,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \examples{ diff --git a/man/dosage.Rd b/man/dosage.Rd index 466b8410b..863d98a81 100644 --- a/man/dosage.Rd +++ b/man/dosage.Rd @@ -30,7 +30,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \examples{ diff --git a/man/eucast_rules.Rd b/man/eucast_rules.Rd index f65f5577b..c3aa44361 100644 --- a/man/eucast_rules.Rd +++ b/man/eucast_rules.Rd @@ -111,7 +111,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \examples{ diff --git a/man/example_isolates.Rd b/man/example_isolates.Rd index f025cc0e1..c77a4cee8 100644 --- a/man/example_isolates.Rd +++ b/man/example_isolates.Rd @@ -28,7 +28,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \examples{ diff --git a/man/example_isolates_unclean.Rd b/man/example_isolates_unclean.Rd index bd4f9c85d..7d10326e0 100644 --- a/man/example_isolates_unclean.Rd +++ b/man/example_isolates_unclean.Rd @@ -26,7 +26,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \examples{ diff --git a/man/intrinsic_resistant.Rd b/man/intrinsic_resistant.Rd index 54dacfa0e..15a701a5e 100644 --- a/man/intrinsic_resistant.Rd +++ b/man/intrinsic_resistant.Rd @@ -32,7 +32,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \examples{ diff --git a/man/microorganisms.Rd b/man/microorganisms.Rd index 46b4a2fb9..85a5e89ff 100644 --- a/man/microorganisms.Rd +++ b/man/microorganisms.Rd @@ -96,7 +96,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \examples{ diff --git a/man/microorganisms.codes.Rd b/man/microorganisms.codes.Rd index 3b0f05239..d8f0dffcb 100644 --- a/man/microorganisms.codes.Rd +++ b/man/microorganisms.codes.Rd @@ -23,7 +23,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \examples{ diff --git a/man/microorganisms.groups.Rd b/man/microorganisms.groups.Rd index f1aae9fa8..8e7132928 100644 --- a/man/microorganisms.groups.Rd +++ b/man/microorganisms.groups.Rd @@ -25,7 +25,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \examples{ diff --git a/man/mo_matching_score.Rd b/man/mo_matching_score.Rd index 0ac347e13..737dad82d 100644 --- a/man/mo_matching_score.Rd +++ b/man/mo_matching_score.Rd @@ -62,7 +62,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \examples{ diff --git a/man/mo_property.Rd b/man/mo_property.Rd index 0f2738503..8be166b42 100644 --- a/man/mo_property.Rd +++ b/man/mo_property.Rd @@ -233,7 +233,7 @@ All reference data sets in the AMR package - including information on microorgan For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. -Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw}{our GitHub repository}. +Visit \href{https://amr-for-r.org/articles/datasets.html}{our website for direct download links}, or explore the actual files in \href{https://github.com/msberends/AMR/tree/main/data-raw/datasets}{our GitHub repository}. } \examples{ diff --git a/vignettes/welcome_to_AMR.Rmd b/vignettes/welcome_to_AMR.Rmd index 5461a00d2..f36e113a7 100644 --- a/vignettes/welcome_to_AMR.Rmd +++ b/vignettes/welcome_to_AMR.Rmd @@ -22,42 +22,42 @@ knitr::opts_chunk$set( ) ``` -Note: to keep the package size as small as possible, we only include this vignette on CRAN. You can read more vignettes on our website about how to conduct AMR data analysis, determine MDROs, find explanation of EUCAST and CLSI breakpoints, and much more: . +Note: to keep the package size as small as possible, we only include this vignette on CRAN. You can read more vignettes on our website about how to conduct AMR data analysis, determine MDROs, find explanation of EUCAST and CLSI breakpoints, and much more: . ---- -The `AMR` package is a [free and open-source](https://amr-for-r.org/) R package with [zero dependencies](https://en.wikipedia.org/wiki/Dependency_hell) to simplify the analysis and prediction of Antimicrobial Resistance (AMR) and to work with microbial and antimicrobial data and properties, by using evidence-based methods. **Our aim is to provide a standard** for clean and reproducible AMR data analysis, that can therefore empower epidemiological analyses to continuously enable surveillance and treatment evaluation in any setting. [Many different researchers](https://amr-for-r.org/authors.html) from around the globe are continually helping us to make this a successful and durable project! +The `AMR` package is a peer-reviewed, [free and open-source](https://amr-for-r.org/#copyright) R package with [zero dependencies](https://en.wikipedia.org/wiki/Dependency_hell) to simplify the analysis and prediction of Antimicrobial Resistance (AMR) and to work with microbial and antimicrobial data and properties, by using evidence-based methods. **Our aim is to provide a standard** for clean and reproducible AMR data analysis, that can therefore empower epidemiological analyses to continuously enable surveillance and treatment evaluation in any setting. We are a team of [many different researchers](https://amr-for-r.org/authors.html) from around the globe to make this a successful and durable project! -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)). +This work was published in the Journal of Statistical Software (Volume 104(3); \doi{10.18637/jss.v104.i03}) and formed the basis of two PhD theses (\doi{10.33612/diss.177417131} and \doi{10.33612/diss.192486375}). -After installing this package, R knows `r AMR:::format_included_data_number(AMR::microorganisms)` distinct microbial species and all `r AMR:::format_included_data_number(rbind(AMR::antimicrobials[, "atc", drop = FALSE], AMR::antivirals[, "atc", drop = FALSE]))` antibiotic, antimycotic and antiviral drugs 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 breakpoint guidelines from CLSI and EUCAST are included from the last 10 years. It supports and can read any data format, including WHONET data. +After installing this package, R knows [**`r AMR:::format_included_data_number(AMR::microorganisms)` distinct microbial species**](https://amr-for-r.org/reference/microorganisms.html) (updated June 2024) and all [**`r AMR:::format_included_data_number(NROW(AMR::antimicrobials) + NROW(AMR::antivirals))` antimicrobial and antiviral drugs**](https://amr-for-r.org/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 `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, grepl("CLSI", guideline))$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, grepl("CLSI", guideline))$guideline)))` and EUCAST `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, grepl("EUCAST", guideline))$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, grepl("EUCAST", guideline))$guideline)))` 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) and the [University Medical Center Groningen](https://www.umcg.nl). -With the help of contributors from all corners of the world, the `AMR` package is available in English, Czech, Chinese, Danish, Dutch, Finnish, French, German, Greek, Italian, Japanese, Norwegian, Polish, Portuguese, Romanian, Russian, Spanish, Swedish, Turkish, and Ukrainian. Antimicrobial drug (group) names and colloquial microorganism names are provided in these languages. +The `AMR` package is available in `r vector_and(vapply(FUN.VALUE = character(1), LANGUAGES_SUPPORTED_NAMES, function(x) x$exonym), quotes = FALSE, sort = FALSE)`. Antimicrobial drug (group) names and colloquial microorganism names are provided in these languages. -This package is fully independent of any other R package and 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**. Since its first public release in early 2018, this package has been downloaded from more than 175 countries. +This package was intended as a comprehensive toolbox for integrated AMR data analysis. This package can be used for: -This package can be used for: - - * Reference for the taxonomy of microorganisms, since the package contains all microbial (sub)species from the List of Prokaryotic names with Standing in Nomenclature (LPSN) and the Global Biodiversity Information Facility (GBIF) - * Interpreting raw MIC and disk diffusion values, based on the latest CLSI or EUCAST guidelines - * Retrieving antimicrobial drug names, doses and forms of administration from clinical health care records - * Determining first isolates to be used for AMR data analysis - * Calculating antimicrobial resistance - * Determining multi-drug resistance (MDR) / multi-drug resistant organisms (MDRO) - * Calculating (empirical) susceptibility of both mono therapy and combination therapies - * Predicting future antimicrobial resistance using regression models - * Getting properties for any microorganism (like Gram stain, species, genus or family) - * Getting properties for any antibiotic (like name, code of EARS-Net/ATC/LOINC/PubChem, defined daily dose or trade name) - * Plotting antimicrobial resistance - * Applying EUCAST expert rules - * Getting SNOMED codes of a microorganism, or getting properties of a microorganism based on a SNOMED code - * Getting LOINC codes of an antibiotic, or getting properties of an antibiotic based on a LOINC code - * Machine reading the EUCAST and CLSI guidelines from 2011-2020 to translate MIC values and disk diffusion diameters to SIR - * Principal component analysis for AMR + * Reference for the taxonomy of microorganisms, since the package contains all microbial (sub)species from the List of Prokaryotic names with Standing in Nomenclature ([LPSN]((https://lpsn.dsmz.de))) and the Global Biodiversity Information Facility ([GBIF](https://www.gbif.org)) ([manual](https://amr-for-r.org/reference/mo_property.html)) + * Interpreting raw MIC and disk diffusion values, based on any CLSI or EUCAST guideline ([manual](https://amr-for-r.org/reference/as.sir.html)) + * Retrieving antimicrobial drug names, doses and forms of administration from clinical health care records ([manual](https://amr-for-r.org/reference/ab_from_text.html)) + * Determining first isolates to be used for AMR data analysis ([manual](https://amr-for-r.org/reference/first_isolate.html)) + * Calculating antimicrobial resistance ([tutorial](https://amr-for-r.org/articles/AMR.html)) + * Determining multi-drug resistance (MDR) / multi-drug resistant organisms (MDRO) ([tutorial](https://amr-for-r.org/articles/MDR.html)) + * Calculating (empirical) susceptibility of both mono therapy and combination therapies ([tutorial](https://amr-for-r.org/articles/AMR.html)) + * Apply AMR function in predictive modelling ([tutorial](https://amr-for-r.org/articles/AMR_with_tidymodels.html)) + * Getting properties for any microorganism (like Gram stain, species, genus or family) ([manual](https://amr-for-r.org/reference/mo_property.html)) + * Getting properties for any antimicrobial (like name, code of EARS-Net/ATC/LOINC/PubChem, defined daily dose or trade name) ([manual](https://amr-for-r.org/reference/ab_property.html)) + * Plotting antimicrobial resistance ([tutorial](https://amr-for-r.org/articles/AMR.html)) + * Applying EUCAST expert rules ([manual](https://amr-for-r.org/reference/eucast_rules.html)) + * Getting SNOMED codes of a microorganism, or getting properties of a microorganism based on a SNOMED code ([manual](https://amr-for-r.org/reference/mo_property.html)) + * Getting LOINC codes of an antibiotic, or getting properties of an antibiotic based on a LOINC code ([manual](https://amr-for-r.org/reference/ab_property.html)) + * Machine reading the EUCAST and CLSI guidelines from 2011-2021 to translate MIC values and disk diffusion diameters to SIR ([link](https://amr-for-r.org/articles/datasets.html)) + * Principal component analysis for AMR ([tutorial](https://amr-for-r.org/articles/PCA.html)) -All reference data sets (about microorganisms, antimicrobials, SIR interpretation, EUCAST rules, etc.) in this `AMR` package are publicly and freely available. We continually export our data sets to formats for use in R, SPSS, Stata and Excel. We also supply flat files that are machine-readable and suitable for input in any software program, such as laboratory information systems. Please find [all download links on our website](https://amr-for-r.org/articles/datasets.html), which is automatically updated with every code change. +All reference data sets in the AMR package - including information on microorganisms, antimicrobials, and clinical breakpoints - are freely available for download in multiple formats: R, MS Excel, Apache Feather, Apache Parquet, SPSS, and Stata. -This R package 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), and is being [actively and durably maintained](https://amr-for-r.org/news/) by two public healthcare organisations in the Netherlands. +For maximum compatibility, we also provide machine-readable, tab-separated plain text files suitable for use in any software, including laboratory information systems. + +Visit [our website for direct download links](https://amr-for-r.org/articles/datasets.html), or explore the actual files in [our GitHub repository](https://github.com/msberends/AMR/tree/main/data-raw/datasets). ----