mirror of
https://github.com/msberends/AMR.git
synced 2025-06-07 19:14:01 +02:00
(v2.1.1.9276) mdro() fix
This commit is contained in:
parent
48a59ee31a
commit
4b171745de
@ -1,6 +1,6 @@
|
|||||||
Package: AMR
|
Package: AMR
|
||||||
Version: 2.1.1.9275
|
Version: 2.1.1.9276
|
||||||
Date: 2025-05-13
|
Date: 2025-05-15
|
||||||
Title: Antimicrobial Resistance Data Analysis
|
Title: Antimicrobial Resistance Data Analysis
|
||||||
Description: Functions to simplify and standardise antimicrobial resistance (AMR)
|
Description: Functions to simplify and standardise antimicrobial resistance (AMR)
|
||||||
data analysis and to work with microbial and antimicrobial properties by
|
data analysis and to work with microbial and antimicrobial properties by
|
||||||
|
3
NEWS.md
3
NEWS.md
@ -1,4 +1,4 @@
|
|||||||
# AMR 2.1.1.9275
|
# AMR 2.1.1.9276
|
||||||
|
|
||||||
*(this beta version will eventually become v3.0. We're happy to reach a new major milestone soon, which will be all about the new One Health support! Install this beta using [the instructions here](https://amr-for-r.org/#get-this-package).)*
|
*(this beta version will eventually become v3.0. We're happy to reach a new major milestone soon, which will be all about the new One Health support! Install this beta using [the instructions here](https://amr-for-r.org/#get-this-package).)*
|
||||||
|
|
||||||
@ -136,6 +136,7 @@ This package now supports not only tools for AMR data analysis in clinical setti
|
|||||||
* Updated all antimicrobial DDDs from WHOCC
|
* Updated all antimicrobial DDDs from WHOCC
|
||||||
* Fix for using a manual value for `mo_transform` in `antibiogram()`
|
* Fix for using a manual value for `mo_transform` in `antibiogram()`
|
||||||
* Fixed a bug for when `antibiogram()` returns an empty data set
|
* Fixed a bug for when `antibiogram()` returns an empty data set
|
||||||
|
* Argument `only_sir_columns` now defaults to `TRUE` if any column of a data set contains a class 'sir' (functions `eucast_rules()`, `key_antimicrobials()`, `mdro()`, etc.)
|
||||||
* Added Sensititre codes for animals, antimicrobials and microorganisms
|
* Added Sensititre codes for animals, antimicrobials and microorganisms
|
||||||
* Fix for mapping 'high level' antimicrobials in `as.ab()` (amphotericin B-high, gentamicin-high, kanamycin-high, streptomycin-high, tobramycin-high)
|
* Fix for mapping 'high level' antimicrobials in `as.ab()` (amphotericin B-high, gentamicin-high, kanamycin-high, streptomycin-high, tobramycin-high)
|
||||||
* Improved overall algorithm of `as.ab()` for better performance and accuracy, including the new function `as_reset_session()` to remove earlier coercions.
|
* Improved overall algorithm of `as.ab()` for better performance and accuracy, including the new function `as_reset_session()` to remove earlier coercions.
|
||||||
|
@ -711,40 +711,6 @@ format_included_data_number <- function(data) {
|
|||||||
paste0(ifelse(rounder == 0, "", "~"), format(round(n, rounder), decimal.mark = ".", big.mark = " "))
|
paste0(ifelse(rounder == 0, "", "~"), format(round(n, rounder), decimal.mark = ".", big.mark = " "))
|
||||||
}
|
}
|
||||||
|
|
||||||
# for eucast_rules() and mdro(), creates markdown output with URLs and names
|
|
||||||
create_eucast_ab_documentation <- function() {
|
|
||||||
x <- trimws(unique(toupper(unlist(strsplit(EUCAST_RULES_DF$then_change_these_antibiotics, ",", fixed = TRUE)))))
|
|
||||||
ab <- character()
|
|
||||||
for (val in x) {
|
|
||||||
if (paste0("AB_", val) %in% ls(envir = asNamespace("AMR"))) {
|
|
||||||
# antimicrobial group names, as defined in data-raw/_pre_commit_checks.R, such as `CARBAPENEMS`
|
|
||||||
val <- eval(parse(text = paste0("AB_", val)), envir = asNamespace("AMR"))
|
|
||||||
} else if (val %in% AMR_env$AB_lookup$ab) {
|
|
||||||
# separate drugs, such as `AMX`
|
|
||||||
val <- as.ab(val)
|
|
||||||
} else {
|
|
||||||
val <- as.sir(NA)
|
|
||||||
}
|
|
||||||
ab <- c(ab, val)
|
|
||||||
}
|
|
||||||
ab <- unique(ab)
|
|
||||||
atcs <- ab_atc(ab, only_first = TRUE)
|
|
||||||
# only keep ABx with an ATC code:
|
|
||||||
ab <- ab[!is.na(atcs)]
|
|
||||||
atcs <- atcs[!is.na(atcs)]
|
|
||||||
|
|
||||||
# sort all vectors on name:
|
|
||||||
ab_names <- ab_name(ab, language = NULL, tolower = TRUE)
|
|
||||||
ab <- ab[order(ab_names)]
|
|
||||||
atcs <- atcs[order(ab_names)]
|
|
||||||
ab_names <- ab_names[order(ab_names)]
|
|
||||||
# create the text:
|
|
||||||
atc_txt <- paste0("[", atcs, "](", ab_url(ab), ")")
|
|
||||||
out <- paste0(ab_names, " (`", ab, "`, ", atc_txt, ")", collapse = ", ")
|
|
||||||
substr(out, 1, 1) <- toupper(substr(out, 1, 1))
|
|
||||||
out
|
|
||||||
}
|
|
||||||
|
|
||||||
vector_or <- function(v, quotes = TRUE, reverse = FALSE, sort = TRUE, initial_captital = FALSE, last_sep = " or ") {
|
vector_or <- function(v, quotes = TRUE, reverse = FALSE, sort = TRUE, initial_captital = FALSE, last_sep = " or ") {
|
||||||
# makes unique and sorts, and this also removed NAs
|
# makes unique and sorts, and this also removed NAs
|
||||||
v <- unique(v)
|
v <- unique(v)
|
||||||
@ -983,7 +949,8 @@ ascertain_sir_classes <- function(x, obj_name) {
|
|||||||
warning_(
|
warning_(
|
||||||
"the data provided in argument `", obj_name,
|
"the data provided in argument `", obj_name,
|
||||||
"` should contain at least one column of class 'sir'. Eligible SIR column were now guessed. ",
|
"` should contain at least one column of class 'sir'. Eligible SIR column were now guessed. ",
|
||||||
"See `?as.sir`."
|
"See `?as.sir`.",
|
||||||
|
immediate = TRUE
|
||||||
)
|
)
|
||||||
sirs_eligible <- is_sir_eligible(x)
|
sirs_eligible <- is_sir_eligible(x)
|
||||||
for (col in colnames(x)[sirs_eligible]) {
|
for (col in colnames(x)[sirs_eligible]) {
|
||||||
|
@ -40,7 +40,7 @@
|
|||||||
#' ```
|
#' ```
|
||||||
#' @param amr_class An antimicrobial class or a part of it, such as `"carba"` and `"carbapenems"`. The columns `group`, `atc_group1` and `atc_group2` of the [antimicrobials] data set will be searched (case-insensitive) for this value.
|
#' @param amr_class An antimicrobial class or a part of it, such as `"carba"` and `"carbapenems"`. The columns `group`, `atc_group1` and `atc_group2` of the [antimicrobials] data set will be searched (case-insensitive) for this value.
|
||||||
#' @param filter An [expression] to be evaluated in the [antimicrobials] data set, such as `name %like% "trim"`.
|
#' @param filter An [expression] to be evaluated in the [antimicrobials] data set, such as `name %like% "trim"`.
|
||||||
#' @param only_sir_columns A [logical] to indicate whether only columns of class `sir` must be selected (default is `FALSE`), see [as.sir()].
|
#' @param only_sir_columns A [logical] to indicate whether only antimicrobial columns must be included that were transformed to class [sir][as.sir()] on beforehand. Defaults to `FALSE`.
|
||||||
#' @param only_treatable A [logical] to indicate whether antimicrobial drugs should be excluded that are only for laboratory tests (default is `TRUE`), such as gentamicin-high (`GEH`) and imipenem/EDTA (`IPE`).
|
#' @param only_treatable A [logical] to indicate whether antimicrobial drugs should be excluded that are only for laboratory tests (default is `TRUE`), such as gentamicin-high (`GEH`) and imipenem/EDTA (`IPE`).
|
||||||
#' @param return_all A [logical] to indicate whether all matched columns must be returned (default is `TRUE`). With `FALSE`, only the first of each unique antimicrobial will be returned, e.g. if both columns `"genta"` and `"gentamicin"` exist in the data, only the first hit for gentamicin will be returned.
|
#' @param return_all A [logical] to indicate whether all matched columns must be returned (default is `TRUE`). With `FALSE`, only the first of each unique antimicrobial will be returned, e.g. if both columns `"genta"` and `"gentamicin"` exist in the data, only the first hit for gentamicin will be returned.
|
||||||
#' @param ... Ignored, only in place to allow future extensions.
|
#' @param ... Ignored, only in place to allow future extensions.
|
||||||
|
@ -70,7 +70,7 @@ format_eucast_version_nr <- function(version, markdown = TRUE) {
|
|||||||
#' @param ... Column name of an antimicrobial, see section *Antimicrobials* below.
|
#' @param ... Column name of an antimicrobial, see section *Antimicrobials* below.
|
||||||
#' @param ab Any (vector of) text that can be coerced to a valid antimicrobial drug code with [as.ab()].
|
#' @param ab Any (vector of) text that can be coerced to a valid antimicrobial drug code with [as.ab()].
|
||||||
#' @param administration Route of administration, either `r vector_or(dosage$administration)`.
|
#' @param administration Route of administration, either `r vector_or(dosage$administration)`.
|
||||||
#' @param only_sir_columns A [logical] to indicate whether only antimicrobial columns must be detected that were transformed to class `sir` (see [as.sir()]) on beforehand (default is `FALSE`).
|
#' @param only_sir_columns A [logical] to indicate whether only antimicrobial columns must be included that were transformed to class [sir][as.sir()] on beforehand. Defaults to `FALSE` if no columns of `x` have a class [sir][as.sir()].
|
||||||
#' @param custom_rules Custom rules to apply, created with [custom_eucast_rules()].
|
#' @param custom_rules Custom rules to apply, created with [custom_eucast_rules()].
|
||||||
#' @param overwrite A [logical] indicating whether to overwrite existing SIR values (default: `FALSE`). When `FALSE`, only non-SIR values are modified (i.e., any value that is not already S, I or R). To ensure compliance with EUCAST guidelines, **this should remain** `FALSE`, as EUCAST notes often state that an organism "should be tested for susceptibility to individual agents or be reported resistant".
|
#' @param overwrite A [logical] indicating whether to overwrite existing SIR values (default: `FALSE`). When `FALSE`, only non-SIR values are modified (i.e., any value that is not already S, I or R). To ensure compliance with EUCAST guidelines, **this should remain** `FALSE`, as EUCAST notes often state that an organism "should be tested for susceptibility to individual agents or be reported resistant".
|
||||||
#' @inheritParams first_isolate
|
#' @inheritParams first_isolate
|
||||||
@ -102,11 +102,9 @@ format_eucast_version_nr <- function(version, markdown = TRUE) {
|
|||||||
#'
|
#'
|
||||||
#' Since these rules are not officially approved by EUCAST, they are not applied at default. To use these rules, include `"other"` to the `rules` argument, or use `eucast_rules(..., rules = "all")`. You can also set the package option [`AMR_eucastrules`][AMR-options], i.e. run `options(AMR_eucastrules = "all")`.
|
#' Since these rules are not officially approved by EUCAST, they are not applied at default. To use these rules, include `"other"` to the `rules` argument, or use `eucast_rules(..., rules = "all")`. You can also set the package option [`AMR_eucastrules`][AMR-options], i.e. run `options(AMR_eucastrules = "all")`.
|
||||||
#' @section Antimicrobials:
|
#' @section Antimicrobials:
|
||||||
#' To define antimicrobials column names, leave as it is to determine it automatically with [guess_ab_col()] or input a text (case-insensitive), or use `NULL` to skip a column (e.g. `TIC = NULL` to skip ticarcillin). Manually defined but non-existing columns will be skipped with a warning.
|
#' To let the function automatically detect antimicrobial column names, do not provide any named arguments. It will then use [guess_ab_col()] to find them.
|
||||||
#'
|
#'
|
||||||
#' The following antimicrobials are eligible for the functions [eucast_rules()] and [mdro()]. These are shown below in the format 'name (`antimicrobial ID`, [ATC code](https://atcddd.fhi.no/atc/structure_and_principles/))', sorted alphabetically:
|
#' To manually specify a column, provide its name (case-insensitive) as an argument, e.g. `AMX = "amoxicillin"`. To skip a specific antimicrobial, set it to `NULL`, e.g. `TIC = NULL` to exclude ticarcillin. If a manually defined column does not exist in the data, it will be skipped with a warning.
|
||||||
#'
|
|
||||||
#' `r create_eucast_ab_documentation()`
|
|
||||||
#' @aliases EUCAST
|
#' @aliases EUCAST
|
||||||
#' @rdname eucast_rules
|
#' @rdname eucast_rules
|
||||||
#' @export
|
#' @export
|
||||||
@ -171,7 +169,7 @@ eucast_rules <- function(x,
|
|||||||
version_expected_phenotypes = 1.2,
|
version_expected_phenotypes = 1.2,
|
||||||
version_expertrules = 3.3,
|
version_expertrules = 3.3,
|
||||||
ampc_cephalosporin_resistance = NA,
|
ampc_cephalosporin_resistance = NA,
|
||||||
only_sir_columns = FALSE,
|
only_sir_columns = any(is.sir(x)),
|
||||||
custom_rules = NULL,
|
custom_rules = NULL,
|
||||||
overwrite = FALSE,
|
overwrite = FALSE,
|
||||||
...) {
|
...) {
|
||||||
|
@ -33,7 +33,7 @@
|
|||||||
#' @param x A [data.frame].
|
#' @param x A [data.frame].
|
||||||
#' @param search_string A text to search `x` for, will be checked with [as.ab()] if this value is not a column in `x`.
|
#' @param search_string A text to search `x` for, will be checked with [as.ab()] if this value is not a column in `x`.
|
||||||
#' @param verbose A [logical] to indicate whether additional info should be printed.
|
#' @param verbose A [logical] to indicate whether additional info should be printed.
|
||||||
#' @param only_sir_columns A [logical] to indicate whether only antibiotic columns must be detected that were transformed to class `sir` (see [as.sir()]) on beforehand (default is `FALSE`).
|
#' @param only_sir_columns A [logical] to indicate whether only antimicrobial columns must be included that were transformed to class [sir][as.sir()] on beforehand. Defaults to `FALSE` if no columns of `x` have a class [sir][as.sir()].
|
||||||
#' @details You can look for an antibiotic (trade) name or abbreviation and it will search `x` and the [antimicrobials] data set for any column containing a name or code of that antibiotic.
|
#' @details You can look for an antibiotic (trade) name or abbreviation and it will search `x` and the [antimicrobials] data set for any column containing a name or code of that antibiotic.
|
||||||
#' @return A column name of `x`, or `NULL` when no result is found.
|
#' @return A column name of `x`, or `NULL` when no result is found.
|
||||||
#' @export
|
#' @export
|
||||||
@ -211,7 +211,7 @@ get_column_abx <- function(x,
|
|||||||
newnames <- suppressWarnings(as.ab(names(dots), info = FALSE))
|
newnames <- suppressWarnings(as.ab(names(dots), info = FALSE))
|
||||||
if (anyNA(newnames)) {
|
if (anyNA(newnames)) {
|
||||||
if (isTRUE(info)) {
|
if (isTRUE(info)) {
|
||||||
message_(" WARNING", add_fn = list(font_yellow, font_bold), as_note = FALSE)
|
message_(paste0(font_yellow(font_bold(" WARNING: ")), "some columns returned `NA` for `as.ab()`"), as_note = FALSE)
|
||||||
}
|
}
|
||||||
warning_("Invalid antibiotic reference(s): ", vector_and(names(dots)[is.na(newnames)], quotes = FALSE),
|
warning_("Invalid antibiotic reference(s): ", vector_and(names(dots)[is.na(newnames)], quotes = FALSE),
|
||||||
call = FALSE,
|
call = FALSE,
|
||||||
@ -254,7 +254,10 @@ get_column_abx <- function(x,
|
|||||||
out <- out[order(names(out), out)]
|
out <- out[order(names(out), out)]
|
||||||
}
|
}
|
||||||
|
|
||||||
|
dups <- FALSE
|
||||||
|
|
||||||
if (return_all == FALSE) {
|
if (return_all == FALSE) {
|
||||||
|
dups <- names(out)[names(out) %in% names(out)[duplicated(names(out))]]
|
||||||
# only keep the first hits, no duplicates
|
# only keep the first hits, no duplicates
|
||||||
duplicates <- c(out[duplicated(names(out))], out[duplicated(unname(out))])
|
duplicates <- c(out[duplicated(names(out))], out[duplicated(unname(out))])
|
||||||
if (length(duplicates) > 0) {
|
if (length(duplicates) > 0) {
|
||||||
@ -264,6 +267,8 @@ get_column_abx <- function(x,
|
|||||||
if (isTRUE(info)) {
|
if (isTRUE(info)) {
|
||||||
if (all_okay == TRUE) {
|
if (all_okay == TRUE) {
|
||||||
message_(" OK.", add_fn = list(font_green, font_bold), as_note = FALSE)
|
message_(" OK.", add_fn = list(font_green, font_bold), as_note = FALSE)
|
||||||
|
} else if (!isFALSE(dups)) {
|
||||||
|
message_(paste0(font_yellow(font_bold(" WARNING: ")), "some results from `as.ab()` are duplicated: ", vector_and(dups, quotes = "`")), as_note = FALSE)
|
||||||
} else {
|
} else {
|
||||||
message_(" WARNING.", add_fn = list(font_yellow, font_bold), as_note = FALSE)
|
message_(" WARNING.", add_fn = list(font_yellow, font_bold), as_note = FALSE)
|
||||||
}
|
}
|
||||||
|
@ -37,7 +37,7 @@
|
|||||||
#' @param gram_negative Names of antibiotic drugs for **Gram-positives**, case-insensitive. Set to `NULL` to ignore. See *Details* for the default antibiotic drugs.
|
#' @param gram_negative Names of antibiotic drugs for **Gram-positives**, case-insensitive. Set to `NULL` to ignore. See *Details* for the default antibiotic drugs.
|
||||||
#' @param gram_positive Names of antibiotic drugs for **Gram-negatives**, case-insensitive. Set to `NULL` to ignore. See *Details* for the default antibiotic drugs.
|
#' @param gram_positive Names of antibiotic drugs for **Gram-negatives**, case-insensitive. Set to `NULL` to ignore. See *Details* for the default antibiotic drugs.
|
||||||
#' @param antifungal Names of antifungal drugs for **fungi**, case-insensitive. Set to `NULL` to ignore. See *Details* for the default antifungal drugs.
|
#' @param antifungal Names of antifungal drugs for **fungi**, case-insensitive. Set to `NULL` to ignore. See *Details* for the default antifungal drugs.
|
||||||
#' @param only_sir_columns A [logical] to indicate whether only columns must be included that were transformed to class `sir` (see [as.sir()]) on beforehand (default is `FALSE`).
|
#' @param only_sir_columns A [logical] to indicate whether only antimicrobial columns must be included that were transformed to class [sir][as.sir()] on beforehand. Defaults to `FALSE` if no columns of `x` have a class [sir][as.sir()].
|
||||||
#' @param ... Ignored, only in place to allow future extensions.
|
#' @param ... Ignored, only in place to allow future extensions.
|
||||||
#' @details
|
#' @details
|
||||||
#' The [key_antimicrobials()] and [all_antimicrobials()] functions are context-aware. This means that the `x` argument can be left blank if used inside a [data.frame] call, see *Examples*.
|
#' The [key_antimicrobials()] and [all_antimicrobials()] functions are context-aware. This means that the `x` argument can be left blank if used inside a [data.frame] call, see *Examples*.
|
||||||
@ -134,7 +134,7 @@ key_antimicrobials <- function(x = NULL,
|
|||||||
"anidulafungin", "caspofungin", "fluconazole",
|
"anidulafungin", "caspofungin", "fluconazole",
|
||||||
"miconazole", "nystatin", "voriconazole"
|
"miconazole", "nystatin", "voriconazole"
|
||||||
),
|
),
|
||||||
only_sir_columns = FALSE,
|
only_sir_columns = any(is.sir(x)),
|
||||||
...) {
|
...) {
|
||||||
if (is_null_or_grouped_tbl(x)) {
|
if (is_null_or_grouped_tbl(x)) {
|
||||||
# when `x` is left blank, auto determine it (get_current_data() searches underlying data within call)
|
# when `x` is left blank, auto determine it (get_current_data() searches underlying data within call)
|
||||||
@ -246,7 +246,7 @@ key_antimicrobials <- function(x = NULL,
|
|||||||
#' @rdname key_antimicrobials
|
#' @rdname key_antimicrobials
|
||||||
#' @export
|
#' @export
|
||||||
all_antimicrobials <- function(x = NULL,
|
all_antimicrobials <- function(x = NULL,
|
||||||
only_sir_columns = FALSE,
|
only_sir_columns = any(is.sir(x)),
|
||||||
...) {
|
...) {
|
||||||
if (is_null_or_grouped_tbl(x)) {
|
if (is_null_or_grouped_tbl(x)) {
|
||||||
# when `x` is left blank, auto determine it (get_current_data() searches underlying data within call)
|
# when `x` is left blank, auto determine it (get_current_data() searches underlying data within call)
|
||||||
|
42
R/mdro.R
42
R/mdro.R
@ -195,13 +195,14 @@ mdro <- function(x = NULL,
|
|||||||
pct_required_classes = 0.5,
|
pct_required_classes = 0.5,
|
||||||
combine_SI = TRUE,
|
combine_SI = TRUE,
|
||||||
verbose = FALSE,
|
verbose = FALSE,
|
||||||
only_sir_columns = FALSE,
|
only_sir_columns = any(is.sir(x)),
|
||||||
...) {
|
...) {
|
||||||
if (is_null_or_grouped_tbl(x)) {
|
if (is_null_or_grouped_tbl(x)) {
|
||||||
# when `x` is left blank, auto determine it (get_current_data() searches underlying data within call)
|
# when `x` is left blank, auto determine it (get_current_data() searches underlying data within call)
|
||||||
# is also a fix for using a grouped df as input (i.e., a dot as first argument)
|
# is also a fix for using a grouped df as input (i.e., a dot as first argument)
|
||||||
x <- tryCatch(get_current_data(arg_name = "x", call = -2), error = function(e) x)
|
x <- tryCatch(get_current_data(arg_name = "x", call = -2), error = function(e) x)
|
||||||
}
|
}
|
||||||
|
|
||||||
meet_criteria(x, allow_class = "data.frame") # also checks dimensions to be >0
|
meet_criteria(x, allow_class = "data.frame") # also checks dimensions to be >0
|
||||||
meet_criteria(guideline, allow_class = c("list", "character"), allow_NULL = TRUE)
|
meet_criteria(guideline, allow_class = c("list", "character"), allow_NULL = TRUE)
|
||||||
if (!is.list(guideline)) meet_criteria(guideline, allow_class = "character", has_length = 1, allow_NULL = TRUE)
|
if (!is.list(guideline)) meet_criteria(guideline, allow_class = "character", has_length = 1, allow_NULL = TRUE)
|
||||||
@ -218,7 +219,8 @@ mdro <- function(x = NULL,
|
|||||||
meet_criteria(verbose, allow_class = "logical", has_length = 1)
|
meet_criteria(verbose, allow_class = "logical", has_length = 1)
|
||||||
meet_criteria(only_sir_columns, allow_class = "logical", has_length = 1)
|
meet_criteria(only_sir_columns, allow_class = "logical", has_length = 1)
|
||||||
|
|
||||||
if (!any(is_sir_eligible(x))) {
|
|
||||||
|
if (!isTRUE(only_sir_columns) && (!any(is.sir(x)) || !any(is_sir_eligible(x)))) {
|
||||||
stop_("There were no possible SIR columns found in the data set. Transform columns with `as.sir()` for valid antimicrobial interpretations.")
|
stop_("There were no possible SIR columns found in the data set. Transform columns with `as.sir()` for valid antimicrobial interpretations.")
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -600,6 +602,7 @@ mdro <- function(x = NULL,
|
|||||||
CTX <- cols_ab["CTX"]
|
CTX <- cols_ab["CTX"]
|
||||||
CTZ <- cols_ab["CTZ"]
|
CTZ <- cols_ab["CTZ"]
|
||||||
CXM <- cols_ab["CXM"]
|
CXM <- cols_ab["CXM"]
|
||||||
|
CZA <- cols_ab["CZA"]
|
||||||
CZD <- cols_ab["CZD"]
|
CZD <- cols_ab["CZD"]
|
||||||
CZO <- cols_ab["CZO"]
|
CZO <- cols_ab["CZO"]
|
||||||
CZX <- cols_ab["CZX"]
|
CZX <- cols_ab["CZX"]
|
||||||
@ -697,7 +700,6 @@ mdro <- function(x = NULL,
|
|||||||
abx_tb <- abx_tb[!is.na(abx_tb)]
|
abx_tb <- abx_tb[!is.na(abx_tb)]
|
||||||
stop_if(guideline$code == "tb" & length(abx_tb) == 0, "no antimycobacterials found in data set")
|
stop_if(guideline$code == "tb" & length(abx_tb) == 0, "no antimycobacterials found in data set")
|
||||||
# nolint end
|
# nolint end
|
||||||
|
|
||||||
if (isTRUE(combine_SI)) {
|
if (isTRUE(combine_SI)) {
|
||||||
search_result <- "R"
|
search_result <- "R"
|
||||||
} else {
|
} else {
|
||||||
@ -1618,28 +1620,24 @@ mdro <- function(x = NULL,
|
|||||||
)
|
)
|
||||||
|
|
||||||
# Pseudomonas aeruginosa
|
# Pseudomonas aeruginosa
|
||||||
if (ab_missing(PIP) && !ab_missing(TZP)) {
|
|
||||||
# take pip/tazo if just pip is not available - many labs only test for pip/tazo because of availability on a Vitek card
|
|
||||||
PIP <- TZP
|
|
||||||
}
|
|
||||||
x$psae <- 0
|
x$psae <- 0
|
||||||
x$psae <- x$psae + ifelse(NA_as_FALSE(col_values(x, TOB) == "R" | col_values(x, AMK) == "R"), 1, 0)
|
x$psae <- x$psae + ifelse(NA_as_FALSE(col_values(x, TOB) == "R") | NA_as_FALSE(col_values(x, AMK) == "R"), 1, 0)
|
||||||
x$psae <- x$psae + ifelse(NA_as_FALSE(col_values(x, IPM) == "R" | col_values(x, MEM) == "R"), 1, 0)
|
x$psae <- x$psae + ifelse(NA_as_FALSE(col_values(x, IPM) == "R") | NA_as_FALSE(col_values(x, MEM) == "R"), 1, 0)
|
||||||
x$psae <- x$psae + ifelse(NA_as_FALSE(col_values(x, PIP) == "R"), 1, 0)
|
x$psae <- x$psae + ifelse(NA_as_FALSE(col_values(x, PIP) == "R") | NA_as_FALSE(col_values(x, TZP) == "R"), 1, 0)
|
||||||
x$psae <- x$psae + ifelse(NA_as_FALSE(col_values(x, CAZ) == "R"), 1, 0)
|
x$psae <- x$psae + ifelse(NA_as_FALSE(col_values(x, CAZ) == "R") | NA_as_FALSE(col_values(x, CZA) == "R"), 1, 0)
|
||||||
x$psae <- x$psae + ifelse(NA_as_FALSE(col_values(x, CIP) == "R" | col_values(x, NOR) == "R" | col_values(x, LVX) == "R"), 1, 0)
|
x$psae <- x$psae + ifelse(NA_as_FALSE(col_values(x, CIP) == "R") | NA_as_FALSE(col_values(x, NOR) == "R") | NA_as_FALSE(col_values(x, LVX) == "R"), 1, 0)
|
||||||
trans_tbl(
|
trans_tbl(
|
||||||
3,
|
1,
|
||||||
rows = which(x$genus == "Pseudomonas" & x$species == "aeruginosa"),
|
rows = which(x$genus == "Pseudomonas" & x$species == "aeruginosa"),
|
||||||
cols = c(CAZ, CIP, GEN, IPM, MEM, TOB, PIP),
|
cols = "any",
|
||||||
any_all = "all", # this will set all negatives to "guideline criteria not met" instead of "not covered by guideline"
|
any_all = "all", # this will set all negatives to "guideline criteria not met" instead of "not covered by guideline"
|
||||||
reason = "P. aeruginosa: at least 3 classes contain R"
|
reason = "guideline criteria not met"
|
||||||
)
|
)
|
||||||
trans_tbl(
|
trans_tbl(
|
||||||
3,
|
3,
|
||||||
rows = which(x$genus == "Pseudomonas" & x$species == "aeruginosa" & x$psae >= 3),
|
rows = which(x$genus == "Pseudomonas" & x$species == "aeruginosa" & x$psae >= 3),
|
||||||
cols = c(CAZ, CIP, GEN, IPM, MEM, TOB, PIP),
|
cols = "any",
|
||||||
any_all = "any", # this is the actual one, changing the ones with x$psae >= 3
|
any_all = "any", # this is the actual one, overwriting the ones with x$psae >= 3
|
||||||
reason = "P. aeruginosa: at least 3 classes contain R"
|
reason = "P. aeruginosa: at least 3 classes contain R"
|
||||||
)
|
)
|
||||||
|
|
||||||
@ -2147,7 +2145,7 @@ run_custom_mdro_guideline <- function(df, guideline, info) {
|
|||||||
|
|
||||||
#' @rdname mdro
|
#' @rdname mdro
|
||||||
#' @export
|
#' @export
|
||||||
brmo <- function(x = NULL, only_sir_columns = FALSE, ...) {
|
brmo <- function(x = NULL, only_sir_columns = any(is.sir(x)), ...) {
|
||||||
meet_criteria(x, allow_class = "data.frame", allow_NULL = TRUE)
|
meet_criteria(x, allow_class = "data.frame", allow_NULL = TRUE)
|
||||||
meet_criteria(only_sir_columns, allow_class = "logical", has_length = 1)
|
meet_criteria(only_sir_columns, allow_class = "logical", has_length = 1)
|
||||||
stop_if(
|
stop_if(
|
||||||
@ -2160,7 +2158,7 @@ brmo <- function(x = NULL, only_sir_columns = FALSE, ...) {
|
|||||||
|
|
||||||
#' @rdname mdro
|
#' @rdname mdro
|
||||||
#' @export
|
#' @export
|
||||||
mrgn <- function(x = NULL, only_sir_columns = FALSE, verbose = FALSE, ...) {
|
mrgn <- function(x = NULL, only_sir_columns = any(is.sir(x)), verbose = FALSE, ...) {
|
||||||
meet_criteria(x, allow_class = "data.frame", allow_NULL = TRUE)
|
meet_criteria(x, allow_class = "data.frame", allow_NULL = TRUE)
|
||||||
meet_criteria(only_sir_columns, allow_class = "logical", has_length = 1)
|
meet_criteria(only_sir_columns, allow_class = "logical", has_length = 1)
|
||||||
stop_if(
|
stop_if(
|
||||||
@ -2172,7 +2170,7 @@ mrgn <- function(x = NULL, only_sir_columns = FALSE, verbose = FALSE, ...) {
|
|||||||
|
|
||||||
#' @rdname mdro
|
#' @rdname mdro
|
||||||
#' @export
|
#' @export
|
||||||
mdr_tb <- function(x = NULL, only_sir_columns = FALSE, verbose = FALSE, ...) {
|
mdr_tb <- function(x = NULL, only_sir_columns = any(is.sir(x)), verbose = FALSE, ...) {
|
||||||
meet_criteria(x, allow_class = "data.frame", allow_NULL = TRUE)
|
meet_criteria(x, allow_class = "data.frame", allow_NULL = TRUE)
|
||||||
meet_criteria(only_sir_columns, allow_class = "logical", has_length = 1)
|
meet_criteria(only_sir_columns, allow_class = "logical", has_length = 1)
|
||||||
stop_if(
|
stop_if(
|
||||||
@ -2184,7 +2182,7 @@ mdr_tb <- function(x = NULL, only_sir_columns = FALSE, verbose = FALSE, ...) {
|
|||||||
|
|
||||||
#' @rdname mdro
|
#' @rdname mdro
|
||||||
#' @export
|
#' @export
|
||||||
mdr_cmi2012 <- function(x = NULL, only_sir_columns = FALSE, verbose = FALSE, ...) {
|
mdr_cmi2012 <- function(x = NULL, only_sir_columns = any(is.sir(x)), verbose = FALSE, ...) {
|
||||||
meet_criteria(x, allow_class = "data.frame", allow_NULL = TRUE)
|
meet_criteria(x, allow_class = "data.frame", allow_NULL = TRUE)
|
||||||
meet_criteria(only_sir_columns, allow_class = "logical", has_length = 1)
|
meet_criteria(only_sir_columns, allow_class = "logical", has_length = 1)
|
||||||
stop_if(
|
stop_if(
|
||||||
@ -2196,7 +2194,7 @@ mdr_cmi2012 <- function(x = NULL, only_sir_columns = FALSE, verbose = FALSE, ...
|
|||||||
|
|
||||||
#' @rdname mdro
|
#' @rdname mdro
|
||||||
#' @export
|
#' @export
|
||||||
eucast_exceptional_phenotypes <- function(x = NULL, only_sir_columns = FALSE, verbose = FALSE, ...) {
|
eucast_exceptional_phenotypes <- function(x = NULL, only_sir_columns = any(is.sir(x)), verbose = FALSE, ...) {
|
||||||
meet_criteria(x, allow_class = "data.frame", allow_NULL = TRUE)
|
meet_criteria(x, allow_class = "data.frame", allow_NULL = TRUE)
|
||||||
meet_criteria(only_sir_columns, allow_class = "logical", has_length = 1)
|
meet_criteria(only_sir_columns, allow_class = "logical", has_length = 1)
|
||||||
stop_if(
|
stop_if(
|
||||||
|
@ -131,7 +131,7 @@ not_intrinsic_resistant(only_sir_columns = FALSE, col_mo = NULL,
|
|||||||
version_expected_phenotypes = 1.2, ...)
|
version_expected_phenotypes = 1.2, ...)
|
||||||
}
|
}
|
||||||
\arguments{
|
\arguments{
|
||||||
\item{only_sir_columns}{A \link{logical} to indicate whether only columns of class \code{sir} must be selected (default is \code{FALSE}), see \code{\link[=as.sir]{as.sir()}}.}
|
\item{only_sir_columns}{A \link{logical} to indicate whether only antimicrobial columns must be included that were transformed to class \link[=as.sir]{sir} on beforehand. Defaults to \code{FALSE}.}
|
||||||
|
|
||||||
\item{only_treatable}{A \link{logical} to indicate whether antimicrobial drugs should be excluded that are only for laboratory tests (default is \code{TRUE}), such as gentamicin-high (\code{GEH}) and imipenem/EDTA (\code{IPE}).}
|
\item{only_treatable}{A \link{logical} to indicate whether antimicrobial drugs should be excluded that are only for laboratory tests (default is \code{TRUE}), such as gentamicin-high (\code{GEH}) and imipenem/EDTA (\code{IPE}).}
|
||||||
|
|
||||||
|
File diff suppressed because one or more lines are too long
@ -14,7 +14,7 @@ guess_ab_col(x = NULL, search_string = NULL, verbose = FALSE,
|
|||||||
|
|
||||||
\item{verbose}{A \link{logical} to indicate whether additional info should be printed.}
|
\item{verbose}{A \link{logical} to indicate whether additional info should be printed.}
|
||||||
|
|
||||||
\item{only_sir_columns}{A \link{logical} to indicate whether only antibiotic columns must be detected that were transformed to class \code{sir} (see \code{\link[=as.sir]{as.sir()}}) on beforehand (default is \code{FALSE}).}
|
\item{only_sir_columns}{A \link{logical} to indicate whether only antimicrobial columns must be included that were transformed to class \link[=as.sir]{sir} on beforehand. Defaults to \code{FALSE} if no columns of \code{x} have a class \link[=as.sir]{sir}.}
|
||||||
}
|
}
|
||||||
\value{
|
\value{
|
||||||
A column name of \code{x}, or \code{NULL} when no result is found.
|
A column name of \code{x}, or \code{NULL} when no result is found.
|
||||||
|
@ -13,9 +13,9 @@ key_antimicrobials(x = NULL, col_mo = NULL, universal = c("ampicillin",
|
|||||||
"ceftazidime", "meropenem"), gram_positive = c("vancomycin", "teicoplanin",
|
"ceftazidime", "meropenem"), gram_positive = c("vancomycin", "teicoplanin",
|
||||||
"tetracycline", "erythromycin", "oxacillin", "rifampin"),
|
"tetracycline", "erythromycin", "oxacillin", "rifampin"),
|
||||||
antifungal = c("anidulafungin", "caspofungin", "fluconazole", "miconazole",
|
antifungal = c("anidulafungin", "caspofungin", "fluconazole", "miconazole",
|
||||||
"nystatin", "voriconazole"), only_sir_columns = FALSE, ...)
|
"nystatin", "voriconazole"), only_sir_columns = any(is.sir(x)), ...)
|
||||||
|
|
||||||
all_antimicrobials(x = NULL, only_sir_columns = FALSE, ...)
|
all_antimicrobials(x = NULL, only_sir_columns = any(is.sir(x)), ...)
|
||||||
|
|
||||||
antimicrobials_equal(y, z, type = c("points", "keyantimicrobials"),
|
antimicrobials_equal(y, z, type = c("points", "keyantimicrobials"),
|
||||||
ignore_I = TRUE, points_threshold = 2, ...)
|
ignore_I = TRUE, points_threshold = 2, ...)
|
||||||
@ -33,7 +33,7 @@ antimicrobials_equal(y, z, type = c("points", "keyantimicrobials"),
|
|||||||
|
|
||||||
\item{antifungal}{Names of antifungal drugs for \strong{fungi}, case-insensitive. Set to \code{NULL} to ignore. See \emph{Details} for the default antifungal drugs.}
|
\item{antifungal}{Names of antifungal drugs for \strong{fungi}, case-insensitive. Set to \code{NULL} to ignore. See \emph{Details} for the default antifungal drugs.}
|
||||||
|
|
||||||
\item{only_sir_columns}{A \link{logical} to indicate whether only columns must be included that were transformed to class \code{sir} (see \code{\link[=as.sir]{as.sir()}}) on beforehand (default is \code{FALSE}).}
|
\item{only_sir_columns}{A \link{logical} to indicate whether only antimicrobial columns must be included that were transformed to class \link[=as.sir]{sir} on beforehand. Defaults to \code{FALSE} if no columns of \code{x} have a class \link[=as.sir]{sir}.}
|
||||||
|
|
||||||
\item{...}{Ignored, only in place to allow future extensions.}
|
\item{...}{Ignored, only in place to allow future extensions.}
|
||||||
|
|
||||||
|
21
man/mdro.Rd
21
man/mdro.Rd
File diff suppressed because one or more lines are too long
@ -286,6 +286,10 @@ test_that("test-mdro.R", {
|
|||||||
colnames(suppressWarnings(mdro(example_isolates[1:10, ], verbose = TRUE, info = FALSE))),
|
colnames(suppressWarnings(mdro(example_isolates[1:10, ], verbose = TRUE, info = FALSE))),
|
||||||
c("row_number", "microorganism", "MDRO", "reason", "all_nonsusceptible_columns", "guideline")
|
c("row_number", "microorganism", "MDRO", "reason", "all_nonsusceptible_columns", "guideline")
|
||||||
)
|
)
|
||||||
|
expect_equal(
|
||||||
|
colnames(suppressWarnings(mdro(example_isolates[1:10, ], verbose = TRUE, info = FALSE, guideline = custom_mdro_guideline(AMX == "R" ~ "Positive")))),
|
||||||
|
c("row_number", "microorganism", "MDRO", "reason", "all_nonsusceptible_columns", "guideline")
|
||||||
|
)
|
||||||
|
|
||||||
# print groups
|
# print groups
|
||||||
if (AMR:::pkg_is_available("dplyr", min_version = "1.0.0", also_load = TRUE)) {
|
if (AMR:::pkg_is_available("dplyr", min_version = "1.0.0", also_load = TRUE)) {
|
||||||
|
Loading…
x
Reference in New Issue
Block a user