mirror of https://github.com/msberends/AMR.git
(v2.1.1.9049) new 2024 breakpoints, add `AMO`, set NI instead of N
This commit is contained in:
parent
de17de1be9
commit
9bf7584d58
|
@ -1,6 +1,6 @@
|
|||
Package: AMR
|
||||
Version: 2.1.1.9048
|
||||
Date: 2024-06-13
|
||||
Version: 2.1.1.9049
|
||||
Date: 2024-06-14
|
||||
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
|
||||
|
|
10
NEWS.md
10
NEWS.md
|
@ -1,4 +1,4 @@
|
|||
# AMR 2.1.1.9048
|
||||
# AMR 2.1.1.9049
|
||||
|
||||
*(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!)*
|
||||
|
||||
|
@ -15,15 +15,18 @@ This package now supports not only tools for AMR data analysis in clinical setti
|
|||
* The `antibiotics` data set contains all veterinary antibiotics, such as pradofloxacin and enrofloxacin. All WHOCC codes for veterinary use have been added as well.
|
||||
* `ab_atc()` now supports ATC codes of veterinary antibiotics (that all start with "Q")
|
||||
* `ab_url()` now supports retrieving the WHOCC url of their ATCvet pages
|
||||
* `as.sir()` now brings additional factor levels: "N" for non-interpretable and "SDD" for susceptible dose-dependent. Users can now set their own criteria (using regular expressions) as to what should be considered S, I, R, SDD, and N. Also, to get quantitative values, `as.double()` or a `sir` object will return 1 for S, 2 for SDD/I, and 3 for R (N will become `NA`). Other functions using `sir` classes (e.g., `summary()`) are updated to reflect the change to contain N and SDD.
|
||||
* `as.sir()` now brings additional factor levels: "NI" for non-interpretable and "SDD" for susceptible dose-dependent. Users can now set their own criteria (using regular expressions) as to what should be considered S, I, R, SDD, and NI. Also, to get quantitative values, `as.double()` or a `sir` object will return 1 for S, 2 for SDD/I, and 3 for R (NI will become `NA`). Other functions using `sir` classes (e.g., `summary()`) are updated to reflect the change to contain NI and SDD.
|
||||
* The function group `scale_*_mic()`, namely: `scale_x_mic()`, `scale_y_mic()`, `scale_colour_mic()` and `scale_fill_mic()`. They are advanced ggplot2 extensions to allow easy plotting of MIC values. They allow for manual range definition and plotting missing intermediate log2 levels.
|
||||
* Function `rescale_mic()`, which allows to rescale MIC values to a manually set range. This is the powerhouse behind the `scale_*_mic()` functions, but it can be used by users directly to e.g. compare equality in MIC distributions by rescaling them to the same range first.
|
||||
* Function `mo_group_members()` to retrieve the member microorganisms of a microorganism group. For example, `mo_group_members("Strep group C")` returns a vector of all microorganisms that are in that group.
|
||||
* Clinical breakpoints and intrinsic resistance of EUCAST 2024 and CLSI 2024 have been added to the `clinical_breakpoints` data set for usage in `as.sir()`. EUCAST 2024 (v14.0) is now the new default guideline for all MIC and disks diffusion interpretations.
|
||||
|
||||
## Changed
|
||||
* For SIR interpretation, it is now possible to use column names for argument `ab`, `mo`, and `uti`: `as.sir(..., ab = "column1", mo = "column2", uti = "column3")`. This greatly improves the flexibility for users.
|
||||
* Extended the antibiotic selectors with `nitrofurans()` and `rifamycins()`
|
||||
* Added "clindamycin inducible screening" as `CLI1` to the `antibiotics` data set. Since clindamycin is a lincosamide, the antibiotic selector `lincosamides()` now contains the argument `only_treatable = TRUE` (similar to other antibiotic selectors that contain non-treatable drugs)
|
||||
* `antibiotics` data set:
|
||||
* Added "clindamycin inducible screening" as `CLI1`. Since clindamycin is a lincosamide, the antibiotic selector `lincosamides()` now contains the argument `only_treatable = TRUE` (similar to other antibiotic selectors that contain non-treatable drugs)
|
||||
* Added Amorolfine (`AMO`, D01AE16), which is now also part of the `antifungals()` selector
|
||||
* For MICs:
|
||||
* Added as valid levels: 4096, 6 powers of 0.0625, and 5 powers of 192 (192, 384, 576, 768, 960)
|
||||
* Added new argument `keep_operators` to `as.mic()`. This can be `"all"` (default), `"none"`, or `"edges"`. This argument is also available in the new `rescale_mic()` and `scale_*_mic()` functions.
|
||||
|
@ -38,6 +41,7 @@ This package now supports not only tools for AMR data analysis in clinical setti
|
|||
* Fix for using a manual value for `mo_transform` in `antibiogram()`
|
||||
* Fix for mapping 'high level' antibiotics 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
|
||||
* Improved overall algorithm of `as.mo()` for better performance and accuracy. Specifically, more weight is given to genus and species combinations in cases where the subspecies is miswritten, so that the result will be the correct genus and species.
|
||||
* When using antibiotic selectors such as `aminoglycosides()` that exclude non-treatable drugs like gentamicin-high, the function now always returns a warning that these can be included using `only_treatable = FALSE`
|
||||
* Intermediate log2 levels used for MIC plotting are now more common values instead of following a strict dilution range
|
||||
|
||||
|
|
|
@ -743,9 +743,9 @@ vector_or <- function(v, quotes = TRUE, reverse = FALSE, sort = TRUE, initial_ca
|
|||
# class 'sir' should be sorted like this
|
||||
v <- c("S", "I", "R")
|
||||
}
|
||||
if (identical(v, c("I", "N", "R", "S", "SDD"))) {
|
||||
if (identical(v, c("I", "NI", "R", "S", "SDD"))) {
|
||||
# class 'sir' should be sorted like this
|
||||
v <- c("S", "SDD", "I", "R", "N")
|
||||
v <- c("S", "SDD", "I", "R", "NI")
|
||||
}
|
||||
# oxford comma
|
||||
if (last_sep %in% c(" or ", " and ") && length(v) > 2) {
|
||||
|
@ -1342,6 +1342,10 @@ progress_ticker <- function(n = 1, n_min = 0, print = TRUE, clear = TRUE, title
|
|||
if (!is.null(progress_bar)) {
|
||||
# so we use progress::progress_bar
|
||||
# a close()-method was also added, see below for that
|
||||
title <- trimws2(title)
|
||||
if (title != "") {
|
||||
title <- paste0(title, " ")
|
||||
}
|
||||
pb <- progress_bar$new(
|
||||
format = paste0(title,
|
||||
ifelse(only_bar_percent == TRUE, "[:bar] :percent", "[:bar] :percent (:current/:total,:eta)")),
|
||||
|
@ -1538,14 +1542,14 @@ add_MO_lookup_to_AMR_env <- function() {
|
|||
MO_lookup[which(is.na(MO_lookup$kingdom_index)), "kingdom_index"] <- 3
|
||||
|
||||
# the fullname lowercase, important for the internal algorithms in as.mo()
|
||||
MO_lookup$fullname_lower <- tolower(trimws(paste(
|
||||
MO_lookup$fullname_lower <- tolower(trimws2(paste(
|
||||
MO_lookup$genus,
|
||||
MO_lookup$species,
|
||||
MO_lookup$subspecies
|
||||
)))
|
||||
ind <- MO_lookup$genus == "" | grepl("^[(]unknown ", MO_lookup$fullname, perl = TRUE)
|
||||
MO_lookup[ind, "fullname_lower"] <- tolower(MO_lookup[ind, "fullname", drop = TRUE])
|
||||
MO_lookup$fullname_lower <- trimws(gsub("[^.a-z0-9/ \\-]+", "", MO_lookup$fullname_lower, perl = TRUE))
|
||||
MO_lookup$fullname_lower <- trimws2(gsub("[^.a-z0-9/ \\-]+", "", MO_lookup$fullname_lower, perl = TRUE))
|
||||
# special for Salmonella - they have cities as subspecies but not the species (enterica) in the fullname:
|
||||
MO_lookup$fullname_lower[which(MO_lookup$subspecies %like_case% "^[A-Z]")] <- gsub(" enterica ", " ", MO_lookup$fullname_lower[which(MO_lookup$subspecies %like_case% "^[A-Z]")], fixed = TRUE)
|
||||
|
||||
|
|
1
R/ab.R
1
R/ab.R
|
@ -525,6 +525,7 @@ as.ab <- function(x, flag_multiple_results = TRUE, info = interactive(), ...) {
|
|||
x_unknown,
|
||||
AMR_env$ab_previously_coerced$x_bak[which(AMR_env$ab_previously_coerced$x %in% x & is.na(AMR_env$ab_previously_coerced$ab))]
|
||||
)
|
||||
x_unknown <- x_unknown[!x_unknown %in% c("", NA)]
|
||||
if (length(x_unknown) > 0 && fast_mode == FALSE) {
|
||||
warning_(
|
||||
"in `as.ab()`: these values could not be coerced to a valid antimicrobial ID: ",
|
||||
|
|
|
@ -690,10 +690,10 @@ c.ab_selector <- function(...) {
|
|||
|
||||
all_any_ab_selector <- function(type, ..., na.rm = TRUE) {
|
||||
cols_ab <- c(...)
|
||||
result <- cols_ab[toupper(cols_ab) %in% c("S", "SDD", "I", "R", "N")]
|
||||
result <- cols_ab[toupper(cols_ab) %in% c("S", "SDD", "I", "R", "NI")]
|
||||
if (length(result) == 0) {
|
||||
message_("Filtering ", type, " of columns ", vector_and(font_bold(cols_ab, collapse = NULL), quotes = "'"), ' to contain value "S", "I" or "R"')
|
||||
result <- c("S", "SDD", "I", "R", "N")
|
||||
result <- c("S", "SDD", "I", "R", "NI")
|
||||
}
|
||||
cols_ab <- cols_ab[!cols_ab %in% result]
|
||||
df <- get_current_data(arg_name = NA, call = -3)
|
||||
|
@ -802,7 +802,7 @@ any.ab_selector_any_all <- function(..., na.rm = FALSE) {
|
|||
}
|
||||
}
|
||||
# this is `!=`, so turn around the values
|
||||
sir <- c("S", "SDD", "I", "R", "N")
|
||||
sir <- c("S", "SDD", "I", "R", "NI")
|
||||
e2 <- sir[sir != e2]
|
||||
structure(all_any_ab_selector(type = type, e1, e2),
|
||||
class = c("ab_selector_any_all", "logical")
|
||||
|
|
|
@ -352,7 +352,7 @@ antibiogram <- function(x,
|
|||
} else {
|
||||
S_values <- "S"
|
||||
}
|
||||
other_values <- setdiff(c("S", "SDD", "I", "R", "N"), S_values)
|
||||
other_values <- setdiff(c("S", "SDD", "I", "R", "NI"), S_values)
|
||||
x_transposed <- as.list(as.data.frame(t(x[, abx, drop = FALSE]), stringsAsFactors = FALSE))
|
||||
if (isTRUE(only_all_tested)) {
|
||||
x[new_colname] <- as.sir(vapply(FUN.VALUE = character(1), x_transposed, function(x) ifelse(anyNA(x), NA_character_, ifelse(any(x %in% S_values), "S", "R")), USE.NAMES = FALSE))
|
||||
|
|
|
@ -124,7 +124,7 @@ bug_drug_combinations <- function(x,
|
|||
# turn and merge everything
|
||||
pivot <- lapply(x_mo_filter, function(x) {
|
||||
m <- as.matrix(table(as.sir(x)))
|
||||
data.frame(S = m["S", ], SDD = m["SDD", ], I = m["I", ], R = m["R", ], N = m["N", ], stringsAsFactors = FALSE)
|
||||
data.frame(S = m["S", ], SDD = m["SDD", ], I = m["I", ], R = m["R", ], NI = m["NI", ], stringsAsFactors = FALSE)
|
||||
})
|
||||
merged <- do.call(rbind_AMR, pivot)
|
||||
out_group <- data.frame(
|
||||
|
@ -134,8 +134,8 @@ bug_drug_combinations <- function(x,
|
|||
SDD = merged$SDD,
|
||||
I = merged$I,
|
||||
R = merged$R,
|
||||
N = merged$N,
|
||||
total = merged$S + merged$SDD + merged$I + merged$R + merged$N,
|
||||
NI = merged$NI,
|
||||
total = merged$S + merged$SDD + merged$I + merged$R + merged$NI,
|
||||
stringsAsFactors = FALSE
|
||||
)
|
||||
if (data_has_groups) {
|
||||
|
@ -210,13 +210,13 @@ format.bug_drug_combinations <- function(x,
|
|||
SDD = vapply(FUN.VALUE = double(1), idx, function(i) sum(x$SDD[i], na.rm = TRUE)),
|
||||
I = vapply(FUN.VALUE = double(1), idx, function(i) sum(x$I[i], na.rm = TRUE)),
|
||||
R = vapply(FUN.VALUE = double(1), idx, function(i) sum(x$R[i], na.rm = TRUE)),
|
||||
N = vapply(FUN.VALUE = double(1), idx, function(i) sum(x$R[i], na.rm = TRUE)),
|
||||
NI = vapply(FUN.VALUE = double(1), idx, function(i) sum(x$NI[i], na.rm = TRUE)),
|
||||
total = vapply(FUN.VALUE = double(1), idx, function(i) {
|
||||
sum(x$S[i], na.rm = TRUE) +
|
||||
sum(x$SDD[i], na.rm = TRUE) +
|
||||
sum(x$I[i], na.rm = TRUE) +
|
||||
sum(x$R[i], na.rm = TRUE) +
|
||||
sum(x$N[i], na.rm = TRUE)
|
||||
sum(x$NI[i], na.rm = TRUE)
|
||||
}),
|
||||
stringsAsFactors = FALSE
|
||||
)
|
||||
|
|
|
@ -225,7 +225,7 @@ count_R <- function(..., only_all_tested = FALSE) {
|
|||
count_all <- function(..., only_all_tested = FALSE) {
|
||||
tryCatch(
|
||||
sir_calc(...,
|
||||
ab_result = c("S", "SDD", "I", "R", "N"),
|
||||
ab_result = c("S", "SDD", "I", "R", "NI"),
|
||||
only_all_tested = only_all_tested,
|
||||
only_count = TRUE
|
||||
),
|
||||
|
|
|
@ -204,8 +204,8 @@ custom_eucast_rules <- function(...) {
|
|||
result_value <- as.character(result)[[3]]
|
||||
result_value[result_value == "NA"] <- NA
|
||||
stop_ifnot(
|
||||
result_value %in% c("S", "SDD", "I", "R", "N", NA),
|
||||
"the resulting value of rule ", i, " must be either \"S\", \"SDD\", \"I\", \"R\", \"N\" or NA"
|
||||
result_value %in% c("S", "SDD", "I", "R", "NI", NA),
|
||||
"the resulting value of rule ", i, " must be either \"S\", \"SDD\", \"I\", \"R\", \"NI\" or NA"
|
||||
)
|
||||
result_value <- as.sir(result_value)
|
||||
|
||||
|
|
|
@ -236,7 +236,7 @@ first_isolate <- function(x = NULL,
|
|||
FUN.VALUE = logical(1),
|
||||
X = x,
|
||||
# check only first 10,000 rows
|
||||
FUN = function(x) any(as.character(x[1:10000]) %in% c("S", "SDD", "I", "R", "N"), na.rm = TRUE),
|
||||
FUN = function(x) any(as.character(x[1:10000]) %in% c("S", "SDD", "I", "R", "NI"), na.rm = TRUE),
|
||||
USE.NAMES = FALSE
|
||||
))
|
||||
if (method == "phenotype-based" && !any_col_contains_sir) {
|
||||
|
|
|
@ -283,7 +283,7 @@ generate_antimcrobials_string <- function(df) {
|
|||
function(x) {
|
||||
x <- toupper(as.character(x))
|
||||
x[x == "SDD"] <- "I"
|
||||
# ignore "N" here, no use for determining first isolates
|
||||
# ignore "NI" here, no use for determining first isolates
|
||||
x[!x %in% c("S", "I", "R")] <- "."
|
||||
paste(x)
|
||||
}
|
||||
|
|
4
R/mo.R
4
R/mo.R
|
@ -285,7 +285,9 @@ as.mo <- function(x,
|
|||
# do a pre-match on first character (and if it contains a space, first chars of first two terms)
|
||||
if (length(x_parts) %in% c(2, 3)) {
|
||||
# for genus + species + subspecies
|
||||
if (nchar(gsub("[^a-z]", "", x_parts[1], perl = TRUE)) <= 3) {
|
||||
if (paste(x_parts[1:2], collapse = " ") %in% AMR_env$MO_lookup$fullname_lower) {
|
||||
filtr <- which(AMR_env$MO_lookup$fullname_lower %like% paste(x_parts[1:2], collapse = " "))
|
||||
} else if (nchar(gsub("[^a-z]", "", x_parts[1], perl = TRUE)) <= 3) {
|
||||
filtr <- which(AMR_env$MO_lookup$full_first == substr(x_parts[1], 1, 1) &
|
||||
(AMR_env$MO_lookup$species_first == substr(x_parts[2], 1, 1) |
|
||||
AMR_env$MO_lookup$subspecies_first == substr(x_parts[2], 1, 1) |
|
||||
|
|
18
R/plot.R
18
R/plot.R
|
@ -659,12 +659,12 @@ plot.sir <- function(x,
|
|||
if (!"R" %in% data$x) {
|
||||
data <- rbind_AMR(data, data.frame(x = "R", n = 0, s = 0, stringsAsFactors = FALSE))
|
||||
}
|
||||
if (!"N" %in% data$x) {
|
||||
data <- rbind_AMR(data, data.frame(x = "N", n = 0, s = 0, stringsAsFactors = FALSE))
|
||||
if (!"NI" %in% data$x) {
|
||||
data <- rbind_AMR(data, data.frame(x = "NI", n = 0, s = 0, stringsAsFactors = FALSE))
|
||||
}
|
||||
|
||||
data <- data[!(data$n == 0 & data$x %in% c("SDD", "I", "N")), , drop = FALSE]
|
||||
data$x <- factor(data$x, levels = intersect(unique(data$x), c("S", "SDD", "I", "R", "N")), ordered = TRUE)
|
||||
data <- data[!(data$n == 0 & data$x %in% c("SDD", "I", "NI")), , drop = FALSE]
|
||||
data$x <- factor(data$x, levels = intersect(unique(data$x), c("S", "SDD", "I", "R", "NI")), ordered = TRUE)
|
||||
|
||||
ymax <- pm_if_else(max(data$s) > 95, 105, 100)
|
||||
|
||||
|
@ -719,8 +719,8 @@ barplot.sir <- function(height,
|
|||
|
||||
x <- table(height)
|
||||
# remove missing I, SDD, and N
|
||||
colours_SIR <- colours_SIR[!(names(x) %in% c("SDD", "I", "N") & x == 0)]
|
||||
x <- x[!(names(x) %in% c("SDD", "I", "N") & x == 0)]
|
||||
colours_SIR <- colours_SIR[!(names(x) %in% c("SDD", "I", "NI") & x == 0)]
|
||||
x <- x[!(names(x) %in% c("SDD", "I", "NI") & x == 0)]
|
||||
# plot it
|
||||
barplot(x,
|
||||
col = colours_SIR,
|
||||
|
@ -761,7 +761,7 @@ autoplot.sir <- function(object,
|
|||
|
||||
df <- as.data.frame(table(object), stringsAsFactors = TRUE)
|
||||
colnames(df) <- c("x", "n")
|
||||
df <- df[!(df$n == 0 & df$x %in% c("SDD", "I", "N")), , drop = FALSE]
|
||||
df <- df[!(df$n == 0 & df$x %in% c("SDD", "I", "NI")), , drop = FALSE]
|
||||
ggplot2::ggplot(df) +
|
||||
ggplot2::geom_col(ggplot2::aes(x = x, y = n, fill = x)) +
|
||||
# limits = force is needed because of a ggplot2 >= 3.3.4 bug (#4511)
|
||||
|
@ -771,7 +771,7 @@ autoplot.sir <- function(object,
|
|||
"SDD" = colours_SIR[2],
|
||||
"I" = colours_SIR[2],
|
||||
"R" = colours_SIR[3],
|
||||
"N" = "#888888"
|
||||
"NI" = "#888888"
|
||||
),
|
||||
limits = force
|
||||
) +
|
||||
|
@ -891,7 +891,7 @@ plot_colours_subtitle_guideline <- function(x, mo, ab, guideline, colours_SIR, f
|
|||
cols[sir == "SDD"] <- colours_SIR[2]
|
||||
cols[sir == "I"] <- colours_SIR[2]
|
||||
cols[sir == "R"] <- colours_SIR[3]
|
||||
cols[sir == "N"] <- "#888888"
|
||||
cols[sir == "NI"] <- "#888888"
|
||||
sub <- bquote(.(abname) ~ "-" ~ italic(.(moname)) ~ .(guideline_txt))
|
||||
} else {
|
||||
cols <- "#BEBEBE"
|
||||
|
|
|
@ -267,7 +267,7 @@ sir_confidence_interval <- function(...,
|
|||
confidence_level = 0.95,
|
||||
side = "both",
|
||||
collapse = FALSE) {
|
||||
meet_criteria(ab_result, allow_class = c("character", "sir"), has_length = c(1:5), is_in = c("S", "SDD", "I", "R", "N"))
|
||||
meet_criteria(ab_result, allow_class = c("character", "sir"), has_length = c(1:5), is_in = c("S", "SDD", "I", "R", "NI"))
|
||||
meet_criteria(minimum, allow_class = c("numeric", "integer"), has_length = 1, is_positive_or_zero = TRUE, is_finite = TRUE)
|
||||
meet_criteria(as_percent, allow_class = "logical", has_length = 1)
|
||||
meet_criteria(only_all_tested, allow_class = "logical", has_length = 1)
|
||||
|
@ -285,7 +285,7 @@ sir_confidence_interval <- function(...,
|
|||
)
|
||||
n <- tryCatch(
|
||||
sir_calc(...,
|
||||
ab_result = c("S", "SDD", "I", "R", "N"),
|
||||
ab_result = c("S", "SDD", "I", "R", "NI"),
|
||||
only_all_tested = only_all_tested,
|
||||
only_count = TRUE
|
||||
),
|
||||
|
|
42
R/sir.R
42
R/sir.R
|
@ -29,7 +29,7 @@
|
|||
|
||||
#' Translate MIC and Disk Diffusion to 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`, `N`.
|
||||
#' @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`.
|
||||
#'
|
||||
#' These breakpoints are currently implemented:
|
||||
#' - 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)))`;
|
||||
|
@ -60,7 +60,7 @@
|
|||
#'
|
||||
#' 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, **N** 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.
|
||||
#' 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.
|
||||
#' * Using `dplyr`, SIR interpretation can be done very easily with either:
|
||||
|
@ -126,7 +126,7 @@
|
|||
#'
|
||||
#' 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 N 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.
|
||||
#' 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 as shown below (<https://www.eucast.org/newsiandr>):
|
||||
#'
|
||||
|
@ -220,7 +220,7 @@
|
|||
#'
|
||||
#' # For CLEANING existing SIR values ------------------------------------
|
||||
#'
|
||||
#' as.sir(c("S", "SDD", "I", "R", "N", "A", "B", "C"))
|
||||
#' 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)
|
||||
|
@ -228,9 +228,9 @@
|
|||
#' 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", "N", NA)))
|
||||
#' 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", "N", NA)))
|
||||
#' as.double(as.sir(c("S", "SDD", "I", "R", "NI", NA)))
|
||||
#'
|
||||
#' # the dplyr way
|
||||
#' if (require("dplyr")) {
|
||||
|
@ -255,7 +255,7 @@ as.sir <- function(x, ...) {
|
|||
|
||||
as_sir_structure <- function(x) {
|
||||
structure(factor(as.character(unlist(unname(x))),
|
||||
levels = c("S", "SDD", "I", "R", "N"),
|
||||
levels = c("S", "SDD", "I", "R", "NI"),
|
||||
ordered = TRUE),
|
||||
class = c("sir", "ordered", "factor"))
|
||||
}
|
||||
|
@ -302,9 +302,9 @@ is_sir_eligible <- function(x, threshold = 0.05) {
|
|||
%in% class(x))) {
|
||||
# no transformation needed
|
||||
return(FALSE)
|
||||
} else if (all(x %in% c("S", "SDD", "I", "R", "N", NA)) & !all(is.na(x))) {
|
||||
} 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", "N") %in% x, na.rm = TRUE) & !all(is.na(x))) {
|
||||
} 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")]
|
||||
|
@ -334,13 +334,13 @@ is_sir_eligible <- function(x, threshold = 0.05) {
|
|||
|
||||
#' @rdname as.sir
|
||||
#' @export
|
||||
#' @param S,I,R,N,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 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.
|
||||
# extra param: warn (logical, to never throw a warning)
|
||||
as.sir.default <- function(x,
|
||||
S = "^(S|U)+$",
|
||||
I = "^(I)+$",
|
||||
R = "^(R)+$",
|
||||
N = "^(N|V)+$",
|
||||
NI = "^(N|NI|V)+$",
|
||||
SDD = "^(SDD|D|H)+$",
|
||||
...) {
|
||||
if (inherits(x, "sir")) {
|
||||
|
@ -366,13 +366,13 @@ as.sir.default <- function(x,
|
|||
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", "N", NA_character_))) {
|
||||
} 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"] <- "N"
|
||||
} else if (!all(is.na(x)) && !identical(levels(x), c("S", "SDD", "I", "R", "N")) && !all(x %in% c("S", "SDD", "I", "R", "N", NA))) {
|
||||
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)) {
|
||||
|
@ -408,7 +408,7 @@ as.sir.default <- function(x,
|
|||
# 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"] <- "N"
|
||||
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)
|
||||
|
@ -416,9 +416,9 @@ as.sir.default <- function(x,
|
|||
x[x %like% S] <- "S"
|
||||
x[x %like% I] <- "I"
|
||||
x[x %like% R] <- "R"
|
||||
x[x %like% N] <- "N"
|
||||
x[x %like% NI] <- "NI"
|
||||
x[x %like% SDD] <- "SDD"
|
||||
x[!x %in% c("S", "SDD", "I", "R", "N")] <- NA_character_
|
||||
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
|
||||
|
@ -711,7 +711,7 @@ as.sir.data.frame <- function(x,
|
|||
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", "N", NA), na.rm = TRUE)) {
|
||||
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
|
||||
message_("Cleaning values in column '", font_bold(ab), "' (",
|
||||
|
@ -1313,7 +1313,7 @@ pillar_shaft.sir <- function(x, ...) {
|
|||
# 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 == "N"] <- font_grey_bg(" N ")
|
||||
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 ")
|
||||
|
@ -1445,7 +1445,7 @@ summary.sir <- function(object, ...) {
|
|||
SDD <- sum(x == "SDD", na.rm = TRUE)
|
||||
I <- sum(x == "I", na.rm = TRUE)
|
||||
R <- sum(x == "R", na.rm = TRUE)
|
||||
N <- sum(x == "N", na.rm = TRUE)
|
||||
NI <- sum(x == "NI", na.rm = TRUE)
|
||||
pad <- function(x) {
|
||||
if (is.na(x)) {
|
||||
return("??")
|
||||
|
@ -1464,7 +1464,7 @@ summary.sir <- function(object, ...) {
|
|||
"%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, ")"),
|
||||
"%N" = paste0(pad(percentage(N / n, digits = 1)), " (n=", N, ")")
|
||||
"%NI" = paste0(pad(percentage(NI / n, digits = 1)), " (n=", NI, ")")
|
||||
)
|
||||
class(value) <- c("summaryDefault", "table")
|
||||
value
|
||||
|
|
|
@ -278,9 +278,9 @@ sir_calc_df <- function(type, # "proportion", "count" or "both"
|
|||
for (i in seq_len(ncol(.data))) {
|
||||
values <- .data[, i, drop = TRUE]
|
||||
if (isTRUE(combine_SI)) {
|
||||
values <- factor(values, levels = c("SI", "R", "N"), ordered = TRUE)
|
||||
values <- factor(values, levels = c("SI", "R", "NI"), ordered = TRUE)
|
||||
} else {
|
||||
values <- factor(values, levels = c("S", "SDD", "I", "R", "N"), ordered = TRUE)
|
||||
values <- factor(values, levels = c("S", "SDD", "I", "R", "NI"), ordered = TRUE)
|
||||
}
|
||||
col_results <- as.data.frame(as.matrix(table(values)), stringsAsFactors = FALSE)
|
||||
col_results$interpretation <- rownames(col_results)
|
||||
|
|
BIN
R/sysdata.rda
BIN
R/sysdata.rda
Binary file not shown.
|
@ -1 +1 @@
|
|||
4e536434d1301bedaec0e856c74cded8
|
||||
92d3e2f8deac335c92841d2ded974dee
|
||||
|
|
Binary file not shown.
Binary file not shown.
Binary file not shown.
Binary file not shown.
|
@ -5,6 +5,7 @@
|
|||
"ALS" 8954 "Aldesulfone sodium" "Other antibacterials" "J04BA03" "Drugs for treatment of lepra" "Drugs for treatment of lepra" "" "adesulfone sodium,aldapsone,aldesulfona sodica,aldesulfone,aldesulfone sodique,aldesulfone sodium,aldesulphone sodium,diamidin,diasone,diasone sodium,diazon,novotrone,sodium aldesulphone,sodium sulfoxone,sulfoxone sodium" 0.33 "g" ""
|
||||
"AMK" 37768 "Amikacin" "Aminoglycosides" "D06AX12,J01GB06,S01AA21" "Aminoglycoside antibacterials" "Other aminoglycosides" "ak,ami,amik,amk,an" "amicacin,amikacillin,amikacin,amikacin base,amikacin dihydrate,amikacin free base,amikacin sulfate,amikacina,amikacine,amikacinum,amikavet,amikin,amiklin,amikozit,amukin,arikace,arikayce liposomal,briclin,kaminax,lukadin,mikavir,pierami,potentox" 1 "g" "101493-5,11-7,12-5,13-3,13546-7,14-1,15098-7,17798-0,18860-7,20373-7,23624-0,25174-4,25175-1,25176-9,25177-7,25178-5,25179-3,31097-9,31098-7,31099-5,3319-1,3320-9,3321-7,35669-1,42642-9,48169-7,50802-8,50803-6,56628-1,59378-0,60564-2,60565-9,6975-7,80972-3,89484-0"
|
||||
"AKF" "Amikacin/fosfomycin" "Aminoglycosides" "NA" "" "" ""
|
||||
"AMO" 54260 "Amorolfine" "Antifungals/antimycotics" "D01AE16" "Antifungals for topical use" "Other antifungals for topical use" "amor" "amorolfina,amorolfine,amorolfinum,loceryl" ""
|
||||
"AMX" 33613 "Amoxicillin" "Beta-lactams/penicillins" "J01CA04" "Beta-lactam antibacterials, penicillins" "Penicillins with extended spectrum" "ac,amox,amx" "actimoxi,amoclen,amolin,amopen,amopenixin,amoxibiotic,amoxicaps,amoxicilina,amoxicillin,amoxicillin hydrate,amoxicilline,amoxicillinum,amoxiden,amoxil,amoxivet,amoxy,amoxycillin,amoxyke,anemolin,aspenil,atoksilin,biomox,bristamox,cemoxin,clamoxyl,damoxy,delacillin,demoksil,dispermox,efpenix,flemoxin,hiconcil,histocillin,hydroxyampicillin,ibiamox,imacillin,lamoxy,largopen,metafarma capsules,metifarma capsules,moksilin,moxacin,moxatag,ospamox,pamoxicillin,piramox,promoxil,remoxil,robamox,sawamox pm,tolodina,topramoxin,unicillin,utimox,vetramox" 1.5 "g" 3 "g" "101498-4,15-8,16-6,16365-9,17-4,18-2,18861-5,18862-3,19-0,20-8,21-6,22-4,25274-2,25310-4,3344-9,55614-2,55615-9,55616-7,6976-5,6977-3,80133-2"
|
||||
"AMC" 23665637 "Amoxicillin/clavulanic acid" "Beta-lactams/penicillins" "J01CR02" "Beta-lactam antibacterials, penicillins" "Combinations of penicillins, incl. beta-lactamase inhibitors" "a/c,amcl,aml,aug,xl" "amocla,amoclan,amoclav,amoksiclav,amoxsiklav,amoxyclav,augmentan,augmentin,augmentin xr,augmentine,auspilic,clamentin,clamobit,clavamox,clavinex,clavoxilin plus,clavulin,clavumox,coamoxiclav,eumetinex,kmoxilin,spectramox,spektramox,synulox,viaclav,xiclav" 1.5 "g" 3 "g" ""
|
||||
"AXS" 465441 "Amoxicillin/sulbactam" "Beta-lactams/penicillins" "NA" "" "" "55614-2,55615-9,55616-7"
|
||||
|
@ -144,7 +145,7 @@
|
|||
"CLA1" 5280980 "Clavulanic acid" "Other antibacterials" "NA" "" "acide clavulanique,acido clavulanico,acidum clavulanicum,clavulanate,clavulanate acid,clavulanate lithium,clavulanateacid,clavulanic acid,clavulansaeure,clavulansaure,clavulinic acid,clavulox,serdaxin,sodium clavulanate" ""
|
||||
"CLX" 60063 "Clinafloxacin" "Quinolones" "NA" "" "clinafloxacin" "32376-6,33284-1,35785-5,35786-3,7004-5"
|
||||
"CLI" 446598 "Clindamycin" "Macrolides/lincosamides" "D10AF01,G01AA10,J01FF01" "Macrolides, lincosamides and streptogramins" "Lincosamides" "cc,cd,cli,clin,cm,da" "antirobe,chlolincocin,clindaderm,clindamicina,clindamycin,clindamycine,clindamycinum,clinimycin,dalacin c,dalacine,klimicin,sobelin" 1.2 "g" 1.8 "g" "16621-5,16622-3,18908-4,192-5,193-3,194-1,195-8,25249-4,3486-8,42720-3,55657-1,55658-9,55659-7,55660-5,61188-9,7005-2"
|
||||
"CLI1" "Clindamycin inducible screening" "Macrolides/lincosamides" "NA" "clindamycin inducible,clinda inducible,clin inducible" "" ""
|
||||
"CLI1" "Clindamycin inducible screening" "Macrolides/lincosamides" "NA" "clin inducible,clinda inducible,clindamycin inducible" "" ""
|
||||
"CLF" 2794 "Clofazimine" "Antimycobacterials" "J04BA01" "Drugs for treatment of lepra" "Drugs for treatment of lepra" "clof" "chlofazimine,clofazimin,clofazimina,clofazimine,clofaziminum,colfazimine,lampren,lamprene,riminophenazine" 0.1 "g" "16623-1,20376-0,23620-8,23627-3,43986-9,43988-5,43989-3,55661-3,55662-1,96108-6"
|
||||
"CLF1" 2799 "Clofoctol" "Other antibacterials" "J01XX03" "Other antibacterials" "Other antibacterials" "" "clofoctol,clofoctolo,clofoctolum,gramplus,octofene" ""
|
||||
"CLM" 71807 "Clometocillin" "Beta-lactams/penicillins" "J01CE07" "Beta-lactam antibacterials, penicillins" "Beta-lactamase sensitive penicillins" "" "chlomethocillin,clometacillin,clometocilina,clometocillin,clometocilline,clometocillinum,rixapen" 1 "g" ""
|
||||
|
|
Binary file not shown.
Binary file not shown.
|
@ -1 +1 @@
|
|||
25f9e2b995124710eb121cc4e62eba16
|
||||
5d90ad7fe89682bfc58700682c562207
|
||||
|
|
Binary file not shown.
Binary file not shown.
Binary file not shown.
Binary file not shown.
Binary file not shown.
File diff suppressed because it is too large
Load Diff
Binary file not shown.
Binary file not shown.
Binary file not shown.
Binary file not shown.
|
@ -1 +1 @@
|
|||
0a874ae6f76e12fabd57b997cb13ebc1
|
||||
89e85bfa66228cfba526e375dad7ff37
|
||||
|
|
Binary file not shown.
Binary file not shown.
|
@ -558,6 +558,7 @@
|
|||
"ACESPP" "B_ACTBCT"
|
||||
"ACF" "F_ABSID"
|
||||
"ACFSPP" "F_ABSID"
|
||||
"ACG" "B_ACNTB_GULL"
|
||||
"ACH" "B_ACHRMB"
|
||||
"ACHCDC" "B_ACHRMB"
|
||||
"ACHDEN" "B_ACHRMB_DNTR"
|
||||
|
@ -633,6 +634,7 @@
|
|||
"ACX" "B_ACDVR"
|
||||
"ACXSPP" "B_ACDVR"
|
||||
"ACY" "B_ARCBC_CRYR"
|
||||
"ACZ" "B_ACNTB_BRZN"
|
||||
"ADE" "B_ACHRMB_DNTR"
|
||||
"ADF" "B_ACDVR_DLFL"
|
||||
"ADH" "B_AERMN_DHKN"
|
||||
|
@ -676,7 +678,7 @@
|
|||
"AERURI" "B_AERCC_URIN"
|
||||
"AERVER" "B_AERMN_VERN"
|
||||
"AERVIR" "B_AERCC_VRDN"
|
||||
"AES" "B_AERCC"
|
||||
"AES" "B_AERCC_SNGN"
|
||||
"AESSAN" "B_AERCC_SNGN"
|
||||
"AESSPP" "B_AERCC"
|
||||
"AESURI" "B_AERCC_URIN"
|
||||
|
@ -782,6 +784,7 @@
|
|||
"ANISPP" "AN_ANSKS"
|
||||
"ANK" "AN_ANSKS"
|
||||
"ANKSPP" "AN_ANSKS"
|
||||
"ANL" "B_ACNTB_LCTC"
|
||||
"ANNEST" "B_GRAMN"
|
||||
"ANO" "B_ACNTB_NSCM"
|
||||
"ANP" "B_ANRBS"
|
||||
|
@ -856,6 +859,7 @@
|
|||
"ARHSPP" "B_ANRRH"
|
||||
"ARI" "B_SLMNL_ENTR_ARZN"
|
||||
"ARM" "B_ATPBM_RIMA"
|
||||
"ARN" "B_CRNBCT"
|
||||
"ARO" "B_ACNTB_RDRS"
|
||||
"AROSPP" "B_ACNTB"
|
||||
"ARS" "F_ASPRG_RSTR"
|
||||
|
@ -863,12 +867,13 @@
|
|||
"ARTCUM" "B_ARTHR_CMMN"
|
||||
"ARTSPP" "B_ARTHR"
|
||||
"ASA" "B_AERMN_SLMN"
|
||||
"ASB" "B_AERMN_SLMN_MSCD"
|
||||
"ASB" "B_AERMN_VERN"
|
||||
"ASC" "B_ACRCM"
|
||||
"ASCSPP" "B_ACRCM"
|
||||
"ASD" "B_ACNTB_SCHN"
|
||||
"ASE" "B_ACNTB_SFRT"
|
||||
"ASH" "B_AERMN_SCHB"
|
||||
"ASK" "B_ARCBC_SKRR"
|
||||
"ASN" "B_ANRBS_SCCN"
|
||||
"ASO" "B_AERMN_SOBR"
|
||||
"ASP" "F_ASPRG"
|
||||
|
@ -1274,7 +1279,7 @@
|
|||
"BVI" "B_BRTNL_VNSN"
|
||||
"BVT" "B_BRKHL_VTNM"
|
||||
"BVTSPP" "B_BRKHL"
|
||||
"BVU" "B_BCTRD_VLGT"
|
||||
"BVU" "B_PHCCL_VLGT"
|
||||
"BWA" "B_BLPHL_WDSW"
|
||||
"BXX" "B_SHGLL_BOYD"
|
||||
"BYP" "B_BSPRA_PLSC"
|
||||
|
@ -1390,6 +1395,7 @@
|
|||
"CBE" "B_CTRDM_BJRN"
|
||||
"CBI" "B_CTRDM_BFRM"
|
||||
"CBK" "B_CTRBC_BRAK"
|
||||
"CBM" "B_CRNBCT_MLTR"
|
||||
"CBN" "F_CLDPH_BNTN"
|
||||
"CBO" "B_CTRDM_BTLN"
|
||||
"CBP" "F_CLDPH_BOPP"
|
||||
|
@ -2117,6 +2123,7 @@
|
|||
"ENMPOL" "P_ENTMB_PLCK"
|
||||
"ENO" "B_EBCTRM_NDTM"
|
||||
"ENP" "B_ENTRBC_NMPR"
|
||||
"ENQ" "B_ENTRC_AQMR"
|
||||
"ENR" "P_ENTRMN"
|
||||
"ENT" "B_ENTRC"
|
||||
"ENTAER" "B_ENTRBC_AERG"
|
||||
|
@ -2147,6 +2154,7 @@
|
|||
"ENTSPP" "B_ENTRBC"
|
||||
"ENTTAY" "B_ENTRBC_TYLR"
|
||||
"ENTVER" "AN_ENTRB_VRMC"
|
||||
"ENU" "B_ENTRC_THLN"
|
||||
"ENX" "B_ENTRBC_XNGF"
|
||||
"ENZ" "P_EYTZN"
|
||||
"EO2" "B_PRCCC_YEEI"
|
||||
|
@ -2550,7 +2558,7 @@
|
|||
"GVA" "B_GRDNR_VGNL"
|
||||
"GVB" "UNKNOWN"
|
||||
"GVC" "UNKNOWN"
|
||||
"GVR" "B_MYCBC_LLRE_YNGN"
|
||||
"GVR" "UNKNOWN"
|
||||
"HA-" "B_HMPHL"
|
||||
"HAA" "B_HLLLL"
|
||||
"HAASPP" "B_HLLLL"
|
||||
|
@ -3555,6 +3563,7 @@
|
|||
"PAV" "B_AVBCT_AVIM"
|
||||
"PBC" "B_PRVTL_BCCL"
|
||||
"PBE" "B_PSTRL_BTTY"
|
||||
"PBI" "B_PRBCT"
|
||||
"PBL" "B_PNBCL_LARV"
|
||||
"PBO" "F_PSDLL_BOYD"
|
||||
"PBR" "B_PRBCT"
|
||||
|
@ -3647,6 +3656,7 @@
|
|||
"PHE" "B_PRVDN_HMBC"
|
||||
"PHI" "F_CLDPH"
|
||||
"PHISPP" "F_CLDPH"
|
||||
"PHL" "B_PHCCL"
|
||||
"PHM" "F_PHOMA"
|
||||
"PHMSPP" "F_PHOMA"
|
||||
"PHO" "F_PHOMA"
|
||||
|
@ -3883,6 +3893,7 @@
|
|||
"PSP" "B_PSTRL_MLTC_SPTC"
|
||||
"PSPPRO" "B_PSDPRP_PNCM"
|
||||
"PSPSPP" "B_PSDPRP"
|
||||
"PSR" "B_PSDMN_GSSR"
|
||||
"PSS" "B_PSDSC"
|
||||
"PSSSPP" "B_PSDSC"
|
||||
"PSSVUL" "B_PSDSC_VLNR"
|
||||
|
@ -4093,7 +4104,7 @@
|
|||
"SBO" "B_STRPT_BOVS"
|
||||
"SBR" "B_SLMNL_BRND"
|
||||
"SBT" "B_SLMNL_SBTR"
|
||||
"SBV" "B_STRPT_ORLS_DNTS"
|
||||
"SBV" "B_STRPT_BOVS"
|
||||
"SBY" "F_STCHY"
|
||||
"SC+" "B_STPHY_COPS"
|
||||
"SC0BRE" "F_SCPLR_VCLS"
|
||||
|
@ -4177,7 +4188,7 @@
|
|||
"SGM" "B_MYCBC_SGM"
|
||||
"SGMSPP" "B_STRPT"
|
||||
"SGO" "B_STRPT_GRDN"
|
||||
"SGP" "B_SLMNL_CHLR_CHLR"
|
||||
"SGP" "B_SLMNL_GNRM"
|
||||
"SGR" "B_SERRT_GRMS"
|
||||
"SGS" "B_SMYCS_GRISS"
|
||||
"SGU" "B_STRPT_PRSN"
|
||||
|
@ -4370,6 +4381,7 @@
|
|||
"SRC" "B_STRPT_CRST"
|
||||
"SRE" "B_SLMNL_ENTR_ENTR"
|
||||
"SRG" "B_STPHY_GNTS"
|
||||
"SRH" "B_STRPT_PHOC"
|
||||
"SRI" "B_SLMNL_ENTR_ENTR"
|
||||
"SRM" "B_SPRLLM"
|
||||
"SRMSPP" "B_SPRLLM"
|
||||
|
@ -4377,7 +4389,7 @@
|
|||
"SRP" "AN_SRCPT"
|
||||
"SRT" "B_STRPT_RATT"
|
||||
"SRU" "B_SERRT_RUBD"
|
||||
"SS1" "B_STRPT_SNGN"
|
||||
"SS1" "B_STRPT_GRPI"
|
||||
"SS2" "B_STRPT_SNGN"
|
||||
"SS3" "B_STRPT_SNGN"
|
||||
"SSA" "B_STRPT_SLVR"
|
||||
|
@ -4845,6 +4857,8 @@
|
|||
"VEL" "B_VIBRI_CHLR"
|
||||
"VFL" "B_VIBRI_FLVL"
|
||||
"VFU" "B_VIBRI_FRNS"
|
||||
"VGC" "B_VGCCC"
|
||||
"VGS" "B_VGCCC_SLMN"
|
||||
"VHI" "B_VIBRI_CHLR"
|
||||
"VHO" "B_GRMNT_HLLS"
|
||||
"VI-" "B_VIBRI"
|
||||
|
|
Binary file not shown.
Binary file not shown.
|
@ -134,6 +134,7 @@ organisms <- organisms %>%
|
|||
distinct()
|
||||
|
||||
# 2023-07-08 SGM is also Strep gamma in WHONET, must only be Slowly-growing Mycobacterium
|
||||
# 2024-06-14 still the case
|
||||
organisms <- organisms %>%
|
||||
filter(!(code == "SGM" & name %like% "Streptococcus"))
|
||||
# this must be empty:
|
||||
|
@ -159,6 +160,7 @@ mo_name(microorganisms.codes2$mo[which(!microorganisms.codes2$code %in% microorg
|
|||
microorganisms.codes <- microorganisms.codes2
|
||||
|
||||
# Run this part to update ASIARS-Net:
|
||||
# 2024-06-14: file not available anymore
|
||||
# # start
|
||||
# asiarsnet <- read_tsv("data-raw/WHONET/Codes/ASIARS_Net_Organisms_ForwardLookup.txt")
|
||||
# asiarsnet <- asiarsnet %>%
|
||||
|
@ -198,6 +200,13 @@ whonet_breakpoints %>%
|
|||
count(GUIDELINES, BREAKPOINT_TYPE) %>%
|
||||
pivot_wider(names_from = BREAKPOINT_TYPE, values_from = n) %>%
|
||||
janitor::adorn_totals(where = c("row", "col"))
|
||||
# compared to current
|
||||
AMR::clinical_breakpoints |>
|
||||
count(GUIDELINES = gsub("[^a-zA-Z]", "", guideline), type) |>
|
||||
arrange(tolower(type)) |>
|
||||
pivot_wider(names_from = type, values_from = n) %>%
|
||||
as.data.frame() |>
|
||||
janitor::adorn_totals(where = c("row", "col"))
|
||||
|
||||
breakpoints <- whonet_breakpoints %>%
|
||||
mutate(code = toupper(ORGANISM_CODE)) %>%
|
||||
|
@ -213,10 +222,7 @@ unknown <- breakpoints %>%
|
|||
breakpoints %>%
|
||||
filter(code %in% unknown) %>%
|
||||
count(GUIDELINES, YEAR, ORGANISM_CODE, BREAKPOINT_TYPE, sort = TRUE)
|
||||
# 2024-02-22: clu and kma are know (see below), fix the PBI one
|
||||
breakpoints$mo[breakpoints$ORGANISM_CODE == "PBI"] <- as.mo("Parabacteroides")
|
||||
breakpoints$ORGANISM_CODE[breakpoints$ORGANISM_CODE == "PBI"] <- "Parabacteroides"
|
||||
# 2023-07-08: these codes are currently: clu, kma. No clue (are not in MO list of WHONET), so remove them:
|
||||
# 2024-06-14: these codes are currently: clu, kma, fso, tyi. No clue (are not in MO list of WHONET), and they are only ECOFFs, so remove them:
|
||||
breakpoints <- breakpoints %>%
|
||||
filter(!is.na(mo))
|
||||
|
||||
|
@ -272,7 +278,8 @@ breakpoints_new <- breakpoints %>%
|
|||
# check the strange duplicates
|
||||
breakpoints_new %>%
|
||||
mutate(id = paste(guideline, type, host, ab, mo, method, site)) %>%
|
||||
filter(id %in% .$id[which(duplicated(id))])
|
||||
filter(id %in% .$id[which(duplicated(id))]) |>
|
||||
arrange(desc(guideline))
|
||||
# remove duplicates
|
||||
breakpoints_new <- breakpoints_new %>%
|
||||
distinct(guideline, type, host, ab, mo, method, site, .keep_all = TRUE)
|
||||
|
@ -289,6 +296,9 @@ breakpoints_new[which(breakpoints_new$method == "DISK"), "breakpoint_S"] <- as.d
|
|||
breakpoints_new[which(breakpoints_new$method == "DISK"), "breakpoint_R"] <- as.double(as.disk(breakpoints_new[which(breakpoints_new$method == "DISK"), "breakpoint_R", drop = TRUE]))
|
||||
|
||||
# regarding animal breakpoints, CLSI has adults and foals for horses, but only for amikacin - remove them
|
||||
breakpoints_new |>
|
||||
filter(host %like% "foal") |>
|
||||
View()
|
||||
breakpoints_new <- breakpoints_new |>
|
||||
filter(host %unlike% "foal") |>
|
||||
mutate(host = ifelse(host %like% "horse", "horse", host))
|
||||
|
@ -328,7 +338,6 @@ breakpoints_new <- breakpoints_new %>% filter(!(mo == as.mo("Streptococcus virid
|
|||
breakpoints_new$mo[breakpoints_new$mo == "B_STPHY" & breakpoints_new$ab == "NIT" & breakpoints_new$guideline %like% "EUCAST"] <- as.mo("B_STPHY_SPRP")
|
||||
# WHONET sets the 2023 breakpoints for SAM to MIC of 16/32 for Enterobacterales, should be MIC 8/32 like AMC (see issue #123 on github.com/msberends/AMR)
|
||||
# UPDATE 2024-02-22: fixed now
|
||||
# breakpoints_new$breakpoint_S[breakpoints_new$mo == "B_[ORD]_ENTRBCTR" & breakpoints_new$ab == "SAM" & breakpoints_new$guideline %like% "CLSI 2023" & breakpoints_new$method == "MIC"] <- 8
|
||||
|
||||
# determine rank again now that some changes were made on taxonomic level (genus -> species)
|
||||
breakpoints_new <- breakpoints_new %>%
|
||||
|
@ -344,10 +353,10 @@ breakpoints_new <- breakpoints_new %>%
|
|||
))
|
||||
|
||||
# WHONET adds one log2 level to the R breakpoint for their software, e.g. in AMC in Enterobacterales:
|
||||
# EUCAST 2022 guideline: S <= 8 and R > 8
|
||||
# EUCAST 2023 guideline: S <= 8 and R > 8
|
||||
# WHONET file: S <= 8 and R >= 16
|
||||
breakpoints_new %>% filter(guideline == "EUCAST 2023", ab == "AMC", mo == "B_[ORD]_ENTRBCTR", method == "MIC")
|
||||
# this will make an MIC of 12 I, which should be R according to EUCAST, so:
|
||||
# but this will make an MIC of 12 I, which should be R according to EUCAST, so:
|
||||
breakpoints_new <- breakpoints_new %>%
|
||||
mutate(breakpoint_R = ifelse(guideline %like% "EUCAST" & method == "MIC" & log2(breakpoint_R) - log2(breakpoint_S) != 0,
|
||||
pmax(breakpoint_S, breakpoint_R / 2),
|
||||
|
@ -363,13 +372,16 @@ breakpoints_new <- breakpoints_new %>%
|
|||
# fill missing R breakpoint where there is an S breakpoint
|
||||
breakpoints_new[which(is.na(breakpoints_new$breakpoint_R)), "breakpoint_R"] <- breakpoints_new[which(is.na(breakpoints_new$breakpoint_R)), "breakpoint_S"]
|
||||
|
||||
# keep distinct rows
|
||||
breakpoints_new <- breakpoints_new |>
|
||||
distinct()
|
||||
|
||||
# CHECKS AND SAVE TO PACKAGE ----
|
||||
|
||||
# check again
|
||||
breakpoints_new %>% filter(guideline == "EUCAST 2023", ab == "AMC", mo == "B_[ORD]_ENTRBCTR", method == "MIC")
|
||||
breakpoints_new %>% filter(guideline == "EUCAST 2024", ab == "AMC", mo == "B_[ORD]_ENTRBCTR", method == "MIC")
|
||||
# compare with current version
|
||||
clinical_breakpoints %>% filter(guideline == "EUCAST 2022", ab == "AMC", mo == "B_[ORD]_ENTRBCTR", method == "MIC")
|
||||
clinical_breakpoints %>% filter(guideline == "EUCAST 2023", ab == "AMC", mo == "B_[ORD]_ENTRBCTR", method == "MIC")
|
||||
|
||||
# must have "human" and "ECOFF"
|
||||
breakpoints_new %>% filter(mo == "B_STRPT_PNMN", ab == "AMP", guideline == "EUCAST 2020", method == "MIC")
|
||||
|
|
Binary file not shown.
Binary file not shown.
Binary file not shown.
|
@ -45,12 +45,12 @@ expect_inherits(x[[1]], "sir")
|
|||
expect_inherits(c(x[1], x[9]), "sir")
|
||||
expect_inherits(unique(x[1], x[9]), "sir")
|
||||
pdf(NULL) # prevent Rplots.pdf being created
|
||||
expect_silent(barplot(as.sir(c("S", "SDD", "I", "R", "N"))))
|
||||
expect_silent(plot(as.sir(c("S", "SDD", "I", "R", "N"))))
|
||||
expect_silent(barplot(as.sir(c("S", "SDD", "I", "R", "NI"))))
|
||||
expect_silent(plot(as.sir(c("S", "SDD", "I", "R", "NI"))))
|
||||
if (AMR:::pkg_is_available("ggplot2")) {
|
||||
expect_inherits(ggplot2::autoplot(as.sir(c("S", "SDD", "I", "R", "N"))), "gg")
|
||||
expect_inherits(ggplot2::autoplot(as.sir(c("S", "SDD", "I", "R", "NI"))), "gg")
|
||||
}
|
||||
expect_stdout(print(as.sir(c("S", "SDD", "I", "R", "N"))))
|
||||
expect_stdout(print(as.sir(c("S", "SDD", "I", "R", "NI"))))
|
||||
expect_equal(as.character(as.sir(c(1:3))), c("S", "I", "R"))
|
||||
expect_equal(as.character(as.sir(c(1:3))), c("S", "I", "R"))
|
||||
expect_equal(suppressWarnings(as.logical(as.sir("INVALID VALUE"))), NA)
|
||||
|
@ -62,7 +62,7 @@ expect_equal(
|
|||
"%SDD" = " 0.0% (n=0)",
|
||||
"%I" = " 0.0% (n=0)",
|
||||
"%R" = "50.0% (n=1)",
|
||||
"%N" = " 0.0% (n=0)"
|
||||
"%NI" = " 0.0% (n=0)"
|
||||
), class = c("summaryDefault", "table"))
|
||||
)
|
||||
expect_identical(
|
||||
|
@ -276,7 +276,7 @@ expect_inherits(
|
|||
expect_inherits(
|
||||
suppressWarnings(as.sir(data.frame(
|
||||
mo = "Escherichia coli",
|
||||
amoxi = c("S", "SDD", "I", "R", "N", "invalid")
|
||||
amoxi = c("S", "SDD", "I", "R", "NI", "invalid")
|
||||
))$amoxi),
|
||||
"sir"
|
||||
)
|
||||
|
|
|
@ -14,7 +14,7 @@ This is an overview of all the package-specific \code{\link[=options]{options()}
|
|||
\item \code{AMR_custom_ab} \cr A file location to an RDS file, to use custom antimicrobial drugs with this package. This is explained in \code{\link[=add_custom_antimicrobials]{add_custom_antimicrobials()}}.
|
||||
\item \code{AMR_custom_mo} \cr A file location to an RDS file, to use custom microorganisms with this package. This is explained in \code{\link[=add_custom_microorganisms]{add_custom_microorganisms()}}.
|
||||
\item \code{AMR_eucastrules} \cr A \link{character} to set the default types of rules for \code{\link[=eucast_rules]{eucast_rules()}} function, must be one or more of: \code{"breakpoints"}, \code{"expert"}, \code{"other"}, \code{"custom"}, \code{"all"}, and defaults to \code{c("breakpoints", "expert")}.
|
||||
\item \code{AMR_guideline} \cr A \link{character} to set the default guideline for interpreting MIC values and disk diffusion diameters with \code{\link[=as.sir]{as.sir()}}. Can be only the guideline name (e.g., \code{"CLSI"}) or the name with a year (e.g. \code{"CLSI 2019"}). The default to the latest implemented EUCAST guideline, currently \code{"EUCAST 2023"}. Supported guideline are currently EUCAST (2011-2023) and CLSI (2011-2023).
|
||||
\item \code{AMR_guideline} \cr A \link{character} to set the default guideline for interpreting MIC values and disk diffusion diameters with \code{\link[=as.sir]{as.sir()}}. Can be only the guideline name (e.g., \code{"CLSI"}) or the name with a year (e.g. \code{"CLSI 2019"}). The default to the latest implemented EUCAST guideline, currently \code{"EUCAST 2024"}. Supported guideline are currently EUCAST (2011-2024) and CLSI (2011-2024).
|
||||
\item \code{AMR_ignore_pattern} \cr A \link[base:regex]{regular expression} to ignore (i.e., make \code{NA}) any match given in \code{\link[=as.mo]{as.mo()}} and all \code{\link[=mo_property]{mo_*}} functions.
|
||||
\item \code{AMR_include_PKPD} \cr A \link{logical} to use in \code{\link[=as.sir]{as.sir()}}, to indicate that PK/PD clinical breakpoints must be applied as a last resort - the default is \code{TRUE}.
|
||||
\item \code{AMR_include_screening} \cr A \link{logical} to use in \code{\link[=as.sir]{as.sir()}}, to indicate that clinical breakpoints for screening are allowed - the default is \code{FALSE}.
|
||||
|
|
|
@ -146,7 +146,7 @@ The \code{\link[=not_intrinsic_resistant]{not_intrinsic_resistant()}} function c
|
|||
\itemize{
|
||||
\item \code{\link[=aminoglycosides]{aminoglycosides()}} can select: \cr amikacin (AMK), amikacin/fosfomycin (AKF), apramycin (APR), arbekacin (ARB), astromicin (AST), bekanamycin (BEK), dibekacin (DKB), framycetin (FRM), gentamicin (GEN), gentamicin-high (GEH), habekacin (HAB), hygromycin (HYG), isepamicin (ISE), kanamycin (KAN), kanamycin-high (KAH), kanamycin/cephalexin (KAC), micronomicin (MCR), neomycin (NEO), netilmicin (NET), pentisomicin (PIM), plazomicin (PLZ), propikacin (PKA), ribostamycin (RST), sisomicin (SIS), streptoduocin (STR), streptomycin (STR1), streptomycin-high (STH), tobramycin (TOB), and tobramycin-high (TOH)
|
||||
\item \code{\link[=aminopenicillins]{aminopenicillins()}} can select: \cr amoxicillin (AMX) and ampicillin (AMP)
|
||||
\item \code{\link[=antifungals]{antifungals()}} can select: \cr amphotericin B (AMB), amphotericin B-high (AMH), anidulafungin (ANI), butoconazole (BUT), caspofungin (CAS), ciclopirox (CIX), clotrimazole (CTR), econazole (ECO), fluconazole (FLU), flucytosine (FCT), fosfluconazole (FFL), griseofulvin (GRI), hachimycin (HCH), ibrexafungerp (IBX), isavuconazole (ISV), isoconazole (ISO), itraconazole (ITR), ketoconazole (KET), manogepix (MGX), micafungin (MIF), miconazole (MCZ), nystatin (NYS), oteseconazole (OTE), pimaricin (PMR), posaconazole (POS), rezafungin (RZF), ribociclib (RBC), sulconazole (SUC), terbinafine (TRB), terconazole (TRC), and voriconazole (VOR)
|
||||
\item \code{\link[=antifungals]{antifungals()}} can select: \cr amorolfine (AMO), amphotericin B (AMB), amphotericin B-high (AMH), anidulafungin (ANI), butoconazole (BUT), caspofungin (CAS), ciclopirox (CIX), clotrimazole (CTR), econazole (ECO), fluconazole (FLU), flucytosine (FCT), fosfluconazole (FFL), griseofulvin (GRI), hachimycin (HCH), ibrexafungerp (IBX), isavuconazole (ISV), isoconazole (ISO), itraconazole (ITR), ketoconazole (KET), manogepix (MGX), micafungin (MIF), miconazole (MCZ), nystatin (NYS), oteseconazole (OTE), pimaricin (PMR), posaconazole (POS), rezafungin (RZF), ribociclib (RBC), sulconazole (SUC), terbinafine (TRB), terconazole (TRC), and voriconazole (VOR)
|
||||
\item \code{\link[=antimycobacterials]{antimycobacterials()}} can select: \cr 4-aminosalicylic acid (AMA), calcium aminosalicylate (CLA), capreomycin (CAP), clofazimine (CLF), delamanid (DLM), enviomycin (ENV), ethambutol (ETH), ethambutol/isoniazid (ETI), ethionamide (ETI1), isoniazid (INH), isoniazid/sulfamethoxazole/trimethoprim/pyridoxine (IST), morinamide (MRN), p-aminosalicylic acid (PAS), pretomanid (PMD), protionamide (PTH), pyrazinamide (PZA), rifabutin (RIB), rifampicin (RIF), rifampicin/ethambutol/isoniazid (REI), rifampicin/isoniazid (RFI), rifampicin/pyrazinamide/ethambutol/isoniazid (RPEI), rifampicin/pyrazinamide/isoniazid (RPI), rifamycin (RFM), rifapentine (RFP), simvastatin/fenofibrate (SMF), sodium aminosalicylate (SDA), streptomycin/isoniazid (STI), terizidone (TRZ), thioacetazone (TAT), thioacetazone/isoniazid (THI1), tiocarlide (TCR), and viomycin (VIO)
|
||||
\item \code{\link[=betalactams]{betalactams()}} can select: \cr amoxicillin (AMX), amoxicillin/clavulanic acid (AMC), amoxicillin/sulbactam (AXS), ampicillin (AMP), ampicillin/sulbactam (SAM), apalcillin (APL), aspoxicillin (APX), avibactam (AVB), azidocillin (AZD), azlocillin (AZL), aztreonam (ATM), aztreonam/avibactam (AZA), aztreonam/nacubactam (ANC), bacampicillin (BAM), benzathine benzylpenicillin (BNB), benzathine phenoxymethylpenicillin (BNP), benzylpenicillin (PEN), biapenem (BIA), carbenicillin (CRB), carindacillin (CRN), cefacetrile (CAC), cefaclor (CEC), cefadroxil (CFR), cefalexin (LEX), cefaloridine (RID), cefalotin (CEP), cefamandole (MAN), cefapirin (HAP), cefatrizine (CTZ), cefazedone (CZD), cefazolin (CZO), cefcapene (CCP), cefcapene pivoxil (CCX), cefdinir (CDR), cefditoren (DIT), cefditoren pivoxil (DIX), cefepime (FEP), cefepime/clavulanic acid (CPC), cefepime/nacubactam (FNC), cefepime/tazobactam (FPT), cefetamet (CAT), cefetamet pivoxil (CPI), cefetecol (CCL), cefetrizole (CZL), cefixime (CFM), cefmenoxime (CMX), cefmetazole (CMZ), cefodizime (DIZ), cefonicid (CID), cefoperazone (CFP), cefoperazone/sulbactam (CSL), ceforanide (CND), cefoselis (CSE), cefotaxime (CTX), cefotaxime/clavulanic acid (CTC), cefotaxime/sulbactam (CTS), cefotetan (CTT), cefotiam (CTF), cefotiam hexetil (CHE), cefovecin (FOV), cefoxitin (FOX), cefoxitin screening (FOX1), cefozopran (ZOP), cefpimizole (CFZ), cefpiramide (CPM), cefpirome (CPO), cefpodoxime (CPD), cefpodoxime proxetil (CPX), cefpodoxime/clavulanic acid (CDC), cefprozil (CPR), cefquinome (CEQ), cefroxadine (CRD), cefsulodin (CFS), cefsumide (CSU), ceftaroline (CPT), ceftaroline/avibactam (CPA), ceftazidime (CAZ), ceftazidime/avibactam (CZA), ceftazidime/clavulanic acid (CCV), cefteram (CEM), cefteram pivoxil (CPL), ceftezole (CTL), ceftibuten (CTB), ceftiofur (TIO), ceftizoxime (CZX), ceftizoxime alapivoxil (CZP), ceftobiprole (BPR), ceftobiprole medocaril (CFM1), ceftolozane/tazobactam (CZT), ceftriaxone (CRO), ceftriaxone/beta-lactamase inhibitor (CEB), cefuroxime (CXM), cefuroxime axetil (CXA), cephradine (CED), ciclacillin (CIC), clometocillin (CLM), cloxacillin (CLO), dicloxacillin (DIC), doripenem (DOR), epicillin (EPC), ertapenem (ETP), flucloxacillin (FLC), hetacillin (HET), imipenem (IPM), imipenem/EDTA (IPE), imipenem/relebactam (IMR), latamoxef (LTM), lenampicillin (LEN), loracarbef (LOR), mecillinam (MEC), meropenem (MEM), meropenem/nacubactam (MNC), meropenem/vaborbactam (MEV), metampicillin (MTM), meticillin (MET), mezlocillin (MEZ), mezlocillin/sulbactam (MSU), nacubactam (NAC), nafcillin (NAF), oxacillin (OXA), panipenem (PAN), penamecillin (PNM), penicillin/novobiocin (PNO), penicillin/sulbactam (PSU), pheneticillin (PHE), phenoxymethylpenicillin (PHN), piperacillin (PIP), piperacillin/sulbactam (PIS), piperacillin/tazobactam (TZP), piridicillin (PRC), pivampicillin (PVM), pivmecillinam (PME), procaine benzylpenicillin (PRB), propicillin (PRP), razupenem (RZM), ritipenem (RIT), ritipenem acoxil (RIA), sarmoxicillin (SRX), sulbactam (SUL), sulbenicillin (SBC), sultamicillin (SLT6), talampicillin (TAL), tazobactam (TAZ), tebipenem (TBP), temocillin (TEM), ticarcillin (TIC), and ticarcillin/clavulanic acid (TCC)
|
||||
\item \code{\link[=carbapenems]{carbapenems()}} can select: \cr biapenem (BIA), doripenem (DOR), ertapenem (ETP), imipenem (IPM), imipenem/EDTA (IPE), imipenem/relebactam (IMR), meropenem (MEM), meropenem/nacubactam (MNC), meropenem/vaborbactam (MEV), panipenem (PAN), razupenem (RZM), ritipenem (RIT), ritipenem acoxil (RIA), and tebipenem (TBP)
|
||||
|
|
|
@ -4,9 +4,9 @@
|
|||
\name{antibiotics}
|
||||
\alias{antibiotics}
|
||||
\alias{antivirals}
|
||||
\title{Data Sets with 604 Antimicrobial Drugs}
|
||||
\title{Data Sets with 605 Antimicrobial Drugs}
|
||||
\format{
|
||||
\subsection{For the \link{antibiotics} data set: a \link[tibble:tibble]{tibble} with 484 observations and 14 variables:}{
|
||||
\subsection{For the \link{antibiotics} data set: a \link[tibble:tibble]{tibble} with 485 observations and 14 variables:}{
|
||||
\itemize{
|
||||
\item \code{ab}\cr Antibiotic ID as used in this package (such as \code{AMC}), using the official EARS-Net (European Antimicrobial Resistance Surveillance Network) codes where available. \emph{This is a unique identifier.}
|
||||
\item \code{cid}\cr Compound ID as found in PubChem. \emph{This is a unique identifier.}
|
||||
|
|
|
@ -40,7 +40,7 @@ Ordered \link{factor} with additional class \code{\link{mic}}, that in mathemati
|
|||
This transforms vectors to a new class \code{\link{mic}}, which treats the input as decimal numbers, while maintaining operators (such as ">=") and only allowing valid MIC values known to the field of (medical) microbiology.
|
||||
}
|
||||
\details{
|
||||
To interpret MIC values as SIR values, use \code{\link[=as.sir]{as.sir()}} on MIC values. It supports guidelines from EUCAST (2011-2023) and CLSI (2011-2023).
|
||||
To interpret MIC values as SIR values, use \code{\link[=as.sir]{as.sir()}} on MIC values. It supports guidelines from EUCAST (2011-2024) and CLSI (2011-2024).
|
||||
|
||||
This class for MIC values is a quite a special data type: formally it is an ordered \link{factor} with valid MIC values as \link{factor} levels (to make sure only valid MIC values are retained), but for any mathematical operation it acts as decimal numbers:
|
||||
|
||||
|
|
|
@ -16,10 +16,10 @@
|
|||
\source{
|
||||
For interpretations of minimum inhibitory concentration (MIC) values and disk diffusion diameters:
|
||||
\itemize{
|
||||
\item \strong{CLSI M39: Analysis and Presentation of Cumulative Antimicrobial Susceptibility Test Data}, 2011-2023, \emph{Clinical and Laboratory Standards Institute} (CLSI). \url{https://clsi.org/standards/products/microbiology/documents/m39/}.
|
||||
\item \strong{CLSI M100: Performance Standard for Antimicrobial Susceptibility Testing}, 2011-2023, \emph{Clinical and Laboratory Standards Institute} (CLSI). \url{https://clsi.org/standards/products/microbiology/documents/m100/}.
|
||||
\item \strong{CLSI VET01: Performance Standards for Antimicrobial Disk and Dilution Susceptibility Tests for Bacteria Isolated From Animals}, 2019-2023, \emph{Clinical and Laboratory Standards Institute} (CLSI). \url{https://clsi.org/standards/products/veterinary-medicine/documents/vet01//}.
|
||||
\item \strong{EUCAST Breakpoint tables for interpretation of MICs and zone diameters}, 2011-2023, \emph{European Committee on Antimicrobial Susceptibility Testing} (EUCAST). \url{https://www.eucast.org/clinical_breakpoints}.
|
||||
\item \strong{CLSI M39: Analysis and Presentation of Cumulative Antimicrobial Susceptibility Test Data}, 2011-2024, \emph{Clinical and Laboratory Standards Institute} (CLSI). \url{https://clsi.org/standards/products/microbiology/documents/m39/}.
|
||||
\item \strong{CLSI M100: Performance Standard for Antimicrobial Susceptibility Testing}, 2011-2024, \emph{Clinical and Laboratory Standards Institute} (CLSI). \url{https://clsi.org/standards/products/microbiology/documents/m100/}.
|
||||
\item \strong{CLSI VET01: Performance Standards for Antimicrobial Disk and Dilution Susceptibility Tests for Bacteria Isolated From Animals}, 2019-2024, \emph{Clinical and Laboratory Standards Institute} (CLSI). \url{https://clsi.org/standards/products/veterinary-medicine/documents/vet01//}.
|
||||
\item \strong{EUCAST Breakpoint tables for interpretation of MICs and zone diameters}, 2011-2024, \emph{European Committee on Antimicrobial Susceptibility Testing} (EUCAST). \url{https://www.eucast.org/clinical_breakpoints}.
|
||||
}
|
||||
}
|
||||
\usage{
|
||||
|
@ -36,7 +36,7 @@ is_sir_eligible(x, threshold = 0.05)
|
|||
S = "^(S|U)+$",
|
||||
I = "^(I)+$",
|
||||
R = "^(R)+$",
|
||||
N = "^(N|V)+$",
|
||||
NI = "^(N|NI|V)+$",
|
||||
SDD = "^(SDD|D|H)+$",
|
||||
...
|
||||
)
|
||||
|
@ -96,13 +96,13 @@ sir_interpretation_history(clean = FALSE)
|
|||
|
||||
\item{threshold}{maximum fraction of invalid antimicrobial interpretations of \code{x}, see \emph{Examples}}
|
||||
|
||||
\item{S, I, R, N, SDD}{a case-independent \link[base:regex]{regular expression} to translate input to this result. This regular expression will be run \emph{after} all non-letters and whitespaces are removed from the input.}
|
||||
\item{S, I, R, NI, SDD}{a case-independent \link[base:regex]{regular expression} to translate input to this result. This regular expression will be run \emph{after} all non-letters and whitespaces are removed from the input.}
|
||||
|
||||
\item{mo}{a vector (or column name) with \link{character}s that can be coerced to valid microorganism codes with \code{\link[=as.mo]{as.mo()}}, can be left empty to determine it automatically}
|
||||
|
||||
\item{ab}{a vector (or column name) with \link{character}s that can be coerced to a valid antimicrobial drug code with \code{\link[=as.ab]{as.ab()}}}
|
||||
|
||||
\item{guideline}{defaults to EUCAST 2023 (the latest implemented EUCAST guideline in the \link{clinical_breakpoints} data set), but can be set with the \link[=AMR-options]{package option} \code{\link[=AMR-options]{AMR_guideline}}. Currently supports EUCAST (2011-2023) and CLSI (2011-2023), see \emph{Details}.}
|
||||
\item{guideline}{defaults to EUCAST 2024 (the latest implemented EUCAST guideline in the \link{clinical_breakpoints} data set), but can be set with the \link[=AMR-options]{package option} \code{\link[=AMR-options]{AMR_guideline}}. Currently supports EUCAST (2011-2024) and CLSI (2011-2024), see \emph{Details}.}
|
||||
|
||||
\item{uti}{(Urinary Tract Infection) a vector (or column name) with \link{logical}s (\code{TRUE} or \code{FALSE}) to specify whether a UTI specific interpretation from the guideline should be chosen. For using \code{\link[=as.sir]{as.sir()}} on a \link{data.frame}, this can also be a column containing \link{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 \emph{Examples}.}
|
||||
|
||||
|
@ -128,13 +128,13 @@ sir_interpretation_history(clean = FALSE)
|
|||
Ordered \link{factor} with new class \code{sir}
|
||||
}
|
||||
\description{
|
||||
Clean up existing SIR values, or interpret minimum inhibitory concentration (MIC) values and disk diffusion diameters according to EUCAST or CLSI. \code{\link[=as.sir]{as.sir()}} transforms the input to a new class \code{\link{sir}}, which is an ordered \link{factor} containing the levels \code{S}, \code{SDD}, \code{I}, \code{R}, \code{N}.
|
||||
Clean up existing SIR values, or interpret minimum inhibitory concentration (MIC) values and disk diffusion diameters according to EUCAST or CLSI. \code{\link[=as.sir]{as.sir()}} transforms the input to a new class \code{\link{sir}}, which is an ordered \link{factor} containing the levels \code{S}, \code{SDD}, \code{I}, \code{R}, \code{NI}.
|
||||
|
||||
These breakpoints are currently implemented:
|
||||
\itemize{
|
||||
\item For \strong{clinical microbiology}: EUCAST 2011-2023 and CLSI 2011-2023;
|
||||
\item For \strong{veterinary microbiology}: EUCAST 2021-2023 and CLSI 2019-2023;
|
||||
\item ECOFFs (Epidemiological cut-off values): EUCAST 2020-2023 and CLSI 2022-2023.
|
||||
\item For \strong{clinical microbiology}: EUCAST 2011-2024 and CLSI 2011-2024;
|
||||
\item For \strong{veterinary microbiology}: EUCAST 2021-2024 and CLSI 2019-2024;
|
||||
\item ECOFFs (Epidemiological cut-off values): EUCAST 2020-2024 and CLSI 2022-2024.
|
||||
}
|
||||
|
||||
All breakpoints used for interpretation are available in our \link{clinical_breakpoints} data set.
|
||||
|
@ -145,7 +145,7 @@ All breakpoints used for interpretation are available in our \link{clinical_brea
|
|||
|
||||
The \code{\link[=as.sir]{as.sir()}} function can work in four ways:
|
||||
\enumerate{
|
||||
\item For \strong{cleaning raw / untransformed data}. The data will be cleaned to only contain valid values, namely: \strong{S} for susceptible, \strong{I} for intermediate or 'susceptible, increased exposure', \strong{R} for resistant, \strong{N} for non-interpretable, and \strong{SDD} for susceptible dose-dependent. Each of these can be set using a \link[base:regex]{regular expression}. Furthermore, \code{\link[=as.sir]{as.sir()}} will try its best to clean with some intelligence. For example, mixed values with SIR interpretations and MIC values such as \code{"<0.25; S"} will be coerced to \code{"S"}. Combined interpretations for multiple test methods (as seen in laboratory records) such as \code{"S; S"} will be coerced to \code{"S"}, but a value like \code{"S; I"} will return \code{NA} with a warning that the input is invalid.
|
||||
\item For \strong{cleaning raw / untransformed data}. The data will be cleaned to only contain valid values, namely: \strong{S} for susceptible, \strong{I} for intermediate or 'susceptible, increased exposure', \strong{R} for resistant, \strong{NI} for non-interpretable, and \strong{SDD} for susceptible dose-dependent. Each of these can be set using a \link[base:regex]{regular expression}. Furthermore, \code{\link[=as.sir]{as.sir()}} will try its best to clean with some intelligence. For example, mixed values with SIR interpretations and MIC values such as \code{"<0.25; S"} will be coerced to \code{"S"}. Combined interpretations for multiple test methods (as seen in laboratory records) such as \code{"S; S"} will be coerced to \code{"S"}, but a value like \code{"S; I"} will return \code{NA} with a warning that the input is invalid.
|
||||
\item For \strong{interpreting minimum inhibitory concentration (MIC) values} according to EUCAST or CLSI. You must clean your MIC values first using \code{\link[=as.mic]{as.mic()}}, that also gives your columns the new data class \code{\link{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 \code{mo} argument.
|
||||
\itemize{
|
||||
\item Using \code{dplyr}, SIR interpretation can be done very easily with either:
|
||||
|
@ -181,9 +181,9 @@ your_data \%>\% mutate_if(is.disk, as.sir, host = "column_with_animal_hosts", gu
|
|||
|
||||
\subsection{Supported Guidelines}{
|
||||
|
||||
For interpreting MIC values as well as disk diffusion diameters, currently implemented guidelines are for \strong{clinical microbiology}: EUCAST 2011-2023 and CLSI 2011-2023, and for \strong{veterinary microbiology}: EUCAST 2021-2023 and CLSI 2019-2023.
|
||||
For interpreting MIC values as well as disk diffusion diameters, currently implemented guidelines are for \strong{clinical microbiology}: EUCAST 2011-2024 and CLSI 2011-2024, and for \strong{veterinary microbiology}: EUCAST 2021-2024 and CLSI 2019-2024.
|
||||
|
||||
Thus, the \code{guideline} argument must be set to e.g., \code{"EUCAST 2023"} or \code{"CLSI 2023"}. By simply using \code{"EUCAST"} (the default) or \code{"CLSI"} as input, the latest included version of that guideline will automatically be selected. You can set your own data set using the \code{reference_data} argument. The \code{guideline} argument will then be ignored.
|
||||
Thus, the \code{guideline} argument must be set to e.g., \code{"EUCAST 2024"} or \code{"CLSI 2024"}. By simply using \code{"EUCAST"} (the default) or \code{"CLSI"} as input, the latest included version of that guideline will automatically be selected. You can set your own data set using the \code{reference_data} argument. The \code{guideline} argument will then be ignored.
|
||||
|
||||
You can set the default guideline with the \link[=AMR-options]{package option} \code{\link[=AMR-options]{AMR_guideline}} (e.g. in your \code{.Rprofile} file), such as:
|
||||
|
||||
|
@ -208,7 +208,7 @@ After using \code{\link[=as.sir]{as.sir()}}, you can use the \code{\link[=eucast
|
|||
|
||||
\subsection{Machine-Readable Clinical Breakpoints}{
|
||||
|
||||
The repository of this package \href{https://github.com/msberends/AMR/blob/main/data-raw/clinical_breakpoints.txt}{contains a machine-readable version} of all guidelines. This is a CSV file consisting of 29 883 rows and 13 columns. This file is machine-readable, since it contains one row for every unique combination of the test method (MIC or disk diffusion), the antimicrobial drug and the microorganism. \strong{This allows for easy implementation of these rules in laboratory information systems (LIS)}. Note that it only contains interpretation guidelines for humans - interpretation guidelines from CLSI for animals were removed.
|
||||
The repository of this package \href{https://github.com/msberends/AMR/blob/main/data-raw/clinical_breakpoints.txt}{contains a machine-readable version} of all guidelines. This is a CSV file consisting of 34 085 rows and 13 columns. This file is machine-readable, since it contains one row for every unique combination of the test method (MIC or disk diffusion), the antimicrobial drug and the microorganism. \strong{This allows for easy implementation of these rules in laboratory information systems (LIS)}. Note that it only contains interpretation guidelines for humans - interpretation guidelines from CLSI for animals were removed.
|
||||
}
|
||||
|
||||
\subsection{Other}{
|
||||
|
@ -217,7 +217,7 @@ The function \code{\link[=is.sir]{is.sir()}} detects if the input contains class
|
|||
|
||||
The base R function \code{\link[=as.double]{as.double()}} can be used to retrieve quantitative values from a \code{sir} object: \code{"S"} = 1, \code{"I"}/\code{"SDD"} = 2, \code{"R"} = 3. All other values are rendered \code{NA} . \strong{Note:} Do not use \code{as.integer()}, since that (because of how R works internally) will return the factor level indices, and not these aforementioned quantitative values.
|
||||
|
||||
The function \code{\link[=is_sir_eligible]{is_sir_eligible()}} returns \code{TRUE} when a column contains at most 5\% invalid antimicrobial interpretations (not S and/or I and/or R and/or N and/or SDD), and \code{FALSE} otherwise. The threshold of 5\% can be set with the \code{threshold} argument. If the input is a \link{data.frame}, it iterates over all columns and returns a \link{logical} vector.
|
||||
The function \code{\link[=is_sir_eligible]{is_sir_eligible()}} returns \code{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 \code{FALSE} otherwise. The threshold of 5\% can be set with the \code{threshold} argument. If the input is a \link{data.frame}, it iterates over all columns and returns a \link{logical} vector.
|
||||
}
|
||||
|
||||
\code{NA_sir_} is a missing value of the new \code{sir} class, analogous to e.g. base \R's \code{\link[base:NA]{NA_character_}}.
|
||||
|
@ -313,7 +313,7 @@ if (require("dplyr")) {
|
|||
|
||||
# For CLEANING existing SIR values ------------------------------------
|
||||
|
||||
as.sir(c("S", "SDD", "I", "R", "N", "A", "B", "C"))
|
||||
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)
|
||||
|
@ -321,9 +321,9 @@ 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", "N", NA)))
|
||||
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", "N", NA)))
|
||||
as.double(as.sir(c("S", "SDD", "I", "R", "NI", NA)))
|
||||
|
||||
# the dplyr way
|
||||
if (require("dplyr")) {
|
||||
|
|
|
@ -5,7 +5,7 @@
|
|||
\alias{clinical_breakpoints}
|
||||
\title{Data Set with Clinical Breakpoints for SIR Interpretation}
|
||||
\format{
|
||||
A \link[tibble:tibble]{tibble} with 29 883 observations and 13 variables:
|
||||
A \link[tibble:tibble]{tibble} with 34 085 observations and 13 variables:
|
||||
\itemize{
|
||||
\item \code{guideline}\cr Name of the guideline
|
||||
\item \code{type}\cr Breakpoint type, either "ECOFF", "animal", or "human"
|
||||
|
@ -28,9 +28,9 @@ clinical_breakpoints
|
|||
\description{
|
||||
Data set containing clinical breakpoints to interpret MIC and disk diffusion to SIR values, according to international guidelines. This dataset contain breakpoints for humans, 7 different animal groups, and ECOFFs.
|
||||
|
||||
Currently available breakpoint guidelines for \strong{clinical microbiology} are EUCAST 2011-2023 and CLSI 2011-2023.
|
||||
Currently available breakpoint guidelines for \strong{clinical microbiology} are EUCAST 2011-2024 and CLSI 2011-2024.
|
||||
|
||||
Currently available breakpoint guidelines for \strong{veterinary microbiology} are EUCAST 2021-2023 and CLSI 2019-2023.
|
||||
Currently available breakpoint guidelines for \strong{veterinary microbiology} are EUCAST 2021-2024 and CLSI 2019-2024.
|
||||
|
||||
Use \code{\link[=as.sir]{as.sir()}} to transform MICs or disks measurements to SIR values.
|
||||
}
|
||||
|
|
|
@ -90,7 +90,7 @@ These 30 antibiotic groups are allowed in the rules (case-insensitive) and can b
|
|||
\itemize{
|
||||
\item aminoglycosides\cr(amikacin, amikacin/fosfomycin, apramycin, arbekacin, astromicin, bekanamycin, dibekacin, framycetin, gentamicin, gentamicin-high, habekacin, hygromycin, isepamicin, kanamycin, kanamycin-high, kanamycin/cephalexin, micronomicin, neomycin, netilmicin, pentisomicin, plazomicin, propikacin, ribostamycin, sisomicin, streptoduocin, streptomycin, streptomycin-high, tobramycin, and tobramycin-high)
|
||||
\item aminopenicillins\cr(amoxicillin and ampicillin)
|
||||
\item antifungals\cr(amphotericin B, amphotericin B-high, anidulafungin, butoconazole, caspofungin, ciclopirox, clotrimazole, econazole, fluconazole, flucytosine, fosfluconazole, griseofulvin, hachimycin, ibrexafungerp, isavuconazole, isoconazole, itraconazole, ketoconazole, manogepix, micafungin, miconazole, nystatin, oteseconazole, pimaricin, posaconazole, rezafungin, ribociclib, sulconazole, terbinafine, terconazole, and voriconazole)
|
||||
\item antifungals\cr(amorolfine, amphotericin B, amphotericin B-high, anidulafungin, butoconazole, caspofungin, ciclopirox, clotrimazole, econazole, fluconazole, flucytosine, fosfluconazole, griseofulvin, hachimycin, ibrexafungerp, isavuconazole, isoconazole, itraconazole, ketoconazole, manogepix, micafungin, miconazole, nystatin, oteseconazole, pimaricin, posaconazole, rezafungin, ribociclib, sulconazole, terbinafine, terconazole, and voriconazole)
|
||||
\item antimycobacterials\cr(4-aminosalicylic acid, calcium aminosalicylate, capreomycin, clofazimine, delamanid, enviomycin, ethambutol, ethambutol/isoniazid, ethionamide, isoniazid, isoniazid/sulfamethoxazole/trimethoprim/pyridoxine, morinamide, p-aminosalicylic acid, pretomanid, protionamide, pyrazinamide, rifabutin, rifampicin, rifampicin/ethambutol/isoniazid, rifampicin/isoniazid, rifampicin/pyrazinamide/ethambutol/isoniazid, rifampicin/pyrazinamide/isoniazid, rifamycin, rifapentine, simvastatin/fenofibrate, sodium aminosalicylate, streptomycin/isoniazid, terizidone, thioacetazone, thioacetazone/isoniazid, tiocarlide, and viomycin)
|
||||
\item betalactams\cr(amoxicillin, amoxicillin/clavulanic acid, amoxicillin/sulbactam, ampicillin, ampicillin/sulbactam, apalcillin, aspoxicillin, avibactam, azidocillin, azlocillin, aztreonam, aztreonam/avibactam, aztreonam/nacubactam, bacampicillin, benzathine benzylpenicillin, benzathine phenoxymethylpenicillin, benzylpenicillin, biapenem, carbenicillin, carindacillin, cefacetrile, cefaclor, cefadroxil, cefalexin, cefaloridine, cefalotin, cefamandole, cefapirin, cefatrizine, cefazedone, cefazolin, cefcapene, cefcapene pivoxil, cefdinir, cefditoren, cefditoren pivoxil, cefepime, cefepime/clavulanic acid, cefepime/nacubactam, cefepime/tazobactam, cefetamet, cefetamet pivoxil, cefetecol, cefetrizole, cefixime, cefmenoxime, cefmetazole, cefodizime, cefonicid, cefoperazone, cefoperazone/sulbactam, ceforanide, cefoselis, cefotaxime, cefotaxime/clavulanic acid, cefotaxime/sulbactam, cefotetan, cefotiam, cefotiam hexetil, cefovecin, cefoxitin, cefoxitin screening, cefozopran, cefpimizole, cefpiramide, cefpirome, cefpodoxime, cefpodoxime proxetil, cefpodoxime/clavulanic acid, cefprozil, cefquinome, cefroxadine, cefsulodin, cefsumide, ceftaroline, ceftaroline/avibactam, ceftazidime, ceftazidime/avibactam, ceftazidime/clavulanic acid, cefteram, cefteram pivoxil, ceftezole, ceftibuten, ceftiofur, ceftizoxime, ceftizoxime alapivoxil, ceftobiprole, ceftobiprole medocaril, ceftolozane/tazobactam, ceftriaxone, ceftriaxone/beta-lactamase inhibitor, cefuroxime, cefuroxime axetil, cephradine, ciclacillin, clometocillin, cloxacillin, dicloxacillin, doripenem, epicillin, ertapenem, flucloxacillin, hetacillin, imipenem, imipenem/EDTA, imipenem/relebactam, latamoxef, lenampicillin, loracarbef, mecillinam, meropenem, meropenem/nacubactam, meropenem/vaborbactam, metampicillin, meticillin, mezlocillin, mezlocillin/sulbactam, nacubactam, nafcillin, oxacillin, panipenem, penamecillin, penicillin/novobiocin, penicillin/sulbactam, pheneticillin, phenoxymethylpenicillin, piperacillin, piperacillin/sulbactam, piperacillin/tazobactam, piridicillin, pivampicillin, pivmecillinam, procaine benzylpenicillin, propicillin, razupenem, ritipenem, ritipenem acoxil, sarmoxicillin, sulbactam, sulbenicillin, sultamicillin, talampicillin, tazobactam, tebipenem, temocillin, ticarcillin, and ticarcillin/clavulanic acid)
|
||||
\item carbapenems\cr(biapenem, doripenem, ertapenem, imipenem, imipenem/EDTA, imipenem/relebactam, meropenem, meropenem/nacubactam, meropenem/vaborbactam, panipenem, razupenem, ritipenem, ritipenem acoxil, and tebipenem)
|
||||
|
|
|
@ -3,9 +3,9 @@
|
|||
\docType{data}
|
||||
\name{microorganisms.codes}
|
||||
\alias{microorganisms.codes}
|
||||
\title{Data Set with 4 958 Common Microorganism Codes}
|
||||
\title{Data Set with 4 972 Common Microorganism Codes}
|
||||
\format{
|
||||
A \link[tibble:tibble]{tibble} with 4 958 observations and 2 variables:
|
||||
A \link[tibble:tibble]{tibble} with 4 972 observations and 2 variables:
|
||||
\itemize{
|
||||
\item \code{code}\cr Commonly used code of a microorganism. \emph{This is a unique identifier.}
|
||||
\item \code{mo}\cr ID of the microorganism in the \link{microorganisms} data set
|
||||
|
|
|
@ -158,7 +158,7 @@ Especially the \verb{scale_*_mic()} functions are relevant wrappers to plot MIC
|
|||
\details{
|
||||
The interpretation of "I" will be named "Increased exposure" for all EUCAST guidelines since 2019, and will be named "Intermediate" in all other cases.
|
||||
|
||||
For interpreting MIC values as well as disk diffusion diameters, supported guidelines to be used as input for the \code{guideline} argument are: "EUCAST 2023", "EUCAST 2022", "EUCAST 2021", "EUCAST 2020", "EUCAST 2019", "EUCAST 2018", "EUCAST 2017", "EUCAST 2016", "EUCAST 2015", "EUCAST 2014", "EUCAST 2013", "EUCAST 2012", "EUCAST 2011", "CLSI 2023", "CLSI 2022", "CLSI 2021", "CLSI 2020", "CLSI 2019", "CLSI 2018", "CLSI 2017", "CLSI 2016", "CLSI 2015", "CLSI 2014", "CLSI 2013", "CLSI 2012", and "CLSI 2011".
|
||||
For interpreting MIC values as well as disk diffusion diameters, supported guidelines to be used as input for the \code{guideline} argument are: "EUCAST 2024", "EUCAST 2023", "EUCAST 2022", "EUCAST 2021", "EUCAST 2020", "EUCAST 2019", "EUCAST 2018", "EUCAST 2017", "EUCAST 2016", "EUCAST 2015", "EUCAST 2014", "EUCAST 2013", "EUCAST 2012", "EUCAST 2011", "CLSI 2024", "CLSI 2023", "CLSI 2022", "CLSI 2021", "CLSI 2020", "CLSI 2019", "CLSI 2018", "CLSI 2017", "CLSI 2016", "CLSI 2015", "CLSI 2014", "CLSI 2013", "CLSI 2012", and "CLSI 2011".
|
||||
|
||||
Simply using \code{"CLSI"} or \code{"EUCAST"} as input will automatically select the latest version of that guideline.
|
||||
}
|
||||
|
|
|
@ -33,7 +33,7 @@ These functions can be used for generating random MIC values and disk diffusion
|
|||
\details{
|
||||
The base \R function \code{\link[=sample]{sample()}} is used for generating values.
|
||||
|
||||
Generated values are based on the EUCAST 2023 guideline as implemented in the \link{clinical_breakpoints} data set. To create specific generated values per bug or drug, set the \code{mo} and/or \code{ab} argument.
|
||||
Generated values are based on the EUCAST 2024 guideline as implemented in the \link{clinical_breakpoints} data set. To create specific generated values per bug or drug, set the \code{mo} and/or \code{ab} argument.
|
||||
}
|
||||
\examples{
|
||||
random_mic(25)
|
||||
|
|
Loading…
Reference in New Issue