mirror of
https://github.com/msberends/AMR.git
synced 2025-07-11 23:42:02 +02:00
new SDD and N for as.sir()
This commit is contained in:
@ -743,6 +743,10 @@ 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"))) {
|
||||
# class 'sir' should be sorted like this
|
||||
v <- c("S", "SDD", "I", "R", "N")
|
||||
}
|
||||
# oxford comma
|
||||
if (last_sep %in% c(" or ", " and ") && length(v) > 2) {
|
||||
last_sep <- paste0(",", last_sep)
|
||||
|
13
R/ab.R
13
R/ab.R
@ -140,10 +140,15 @@ as.ab <- function(x, flag_multiple_results = TRUE, info = interactive(), ...) {
|
||||
abnames <- abnames[!abnames %in% c("clavulanic acid", "avibactam", "tazobactam", "vaborbactam", "monobactam")]
|
||||
}
|
||||
if (length(abnames) > 1) {
|
||||
message_(
|
||||
"More than one result was found for item ", index, ": ",
|
||||
vector_and(abnames, quotes = FALSE)
|
||||
)
|
||||
if (toupper(paste(abnames, collapse = " ")) %in% AMR_env$AB_lookup$generalised_name) {
|
||||
# if the found values combined is a valid AB, return that
|
||||
found <- AMR_env$AB_lookup$ab[match(toupper(paste(abnames, collapse = " ")), AMR_env$AB_lookup$generalised_name)][1]
|
||||
} else {
|
||||
message_(
|
||||
"More than one result was found for item ", index, ": ",
|
||||
vector_and(abnames, quotes = FALSE)
|
||||
)
|
||||
}
|
||||
}
|
||||
}
|
||||
found[1L]
|
||||
|
@ -676,10 +676,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", "I", "R")]
|
||||
result <- cols_ab[toupper(cols_ab) %in% c("S", "SDD", "I", "R", "N")]
|
||||
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", "I", "R")
|
||||
result <- c("S", "SDD", "I", "R", "N")
|
||||
}
|
||||
cols_ab <- cols_ab[!cols_ab %in% result]
|
||||
df <- get_current_data(arg_name = NA, call = -3)
|
||||
@ -788,7 +788,7 @@ any.ab_selector_any_all <- function(..., na.rm = FALSE) {
|
||||
}
|
||||
}
|
||||
# this is `!=`, so turn around the values
|
||||
sir <- c("S", "I", "R")
|
||||
sir <- c("S", "SDD", "I", "R", "N")
|
||||
e2 <- sir[sir != e2]
|
||||
structure(all_any_ab_selector(type = type, e1, e2),
|
||||
class = c("ab_selector_any_all", "logical")
|
||||
|
@ -348,11 +348,11 @@ antibiogram <- function(x,
|
||||
} else {
|
||||
# determine whether this new column should contain S, I, R, or NA
|
||||
if (isTRUE(combine_SI)) {
|
||||
S_values <- c("S", "I")
|
||||
S_values <- c("S", "SDD", "I")
|
||||
} else {
|
||||
S_values <- "S"
|
||||
}
|
||||
other_values <- setdiff(c("S", "I", "R"), S_values)
|
||||
other_values <- setdiff(c("S", "SDD", "I", "R", "N"), 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))
|
||||
|
@ -42,7 +42,7 @@
|
||||
#' @details The function [format()] calculates the resistance per bug-drug combination and returns a table ready for reporting/publishing. Use `combine_SI = TRUE` (default) to test R vs. S+I and `combine_SI = FALSE` to test R+I vs. S. This table can also directly be used in R Markdown / Quarto without the need for e.g. [knitr::kable()].
|
||||
#' @export
|
||||
#' @rdname bug_drug_combinations
|
||||
#' @return The function [bug_drug_combinations()] returns a [data.frame] with columns "mo", "ab", "S", "I", "R" and "total".
|
||||
#' @return The function [bug_drug_combinations()] returns a [data.frame] with columns "mo", "ab", "S", "SDD", "I", "R", and "total".
|
||||
#' @examples
|
||||
#' # example_isolates is a data set available in the AMR package.
|
||||
#' # run ?example_isolates for more info.
|
||||
@ -105,6 +105,7 @@ bug_drug_combinations <- function(x,
|
||||
mo = character(0),
|
||||
ab = character(0),
|
||||
S = integer(0),
|
||||
SDD = integer(0),
|
||||
I = integer(0),
|
||||
R = integer(0),
|
||||
total = integer(0),
|
||||
@ -122,13 +123,14 @@ bug_drug_combinations <- function(x,
|
||||
# turn and merge everything
|
||||
pivot <- lapply(x_mo_filter, function(x) {
|
||||
m <- as.matrix(table(x))
|
||||
data.frame(S = m["S", ], I = m["I", ], R = m["R", ], stringsAsFactors = FALSE)
|
||||
data.frame(S = m["S", ], SDD = m["SDD", ], I = m["I", ], R = m["R", ], stringsAsFactors = FALSE)
|
||||
})
|
||||
merged <- do.call(rbind_AMR, pivot)
|
||||
out_group <- data.frame(
|
||||
mo = rep(unique_mo[i], NROW(merged)),
|
||||
ab = rownames(merged),
|
||||
S = merged$S,
|
||||
SDD = merged$SSD,
|
||||
I = merged$I,
|
||||
R = merged$R,
|
||||
total = merged$S + merged$I + merged$R,
|
||||
@ -203,10 +205,12 @@ format.bug_drug_combinations <- function(x,
|
||||
mo = gsub("(.*)%%(.*)", "\\1", names(idx)),
|
||||
ab = gsub("(.*)%%(.*)", "\\2", names(idx)),
|
||||
S = vapply(FUN.VALUE = double(1), idx, function(i) sum(x$S[i], na.rm = TRUE)),
|
||||
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)),
|
||||
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)
|
||||
}),
|
||||
@ -223,7 +227,7 @@ format.bug_drug_combinations <- function(x,
|
||||
if (combine_SI == TRUE) {
|
||||
x$isolates <- x$R
|
||||
} else {
|
||||
x$isolates <- x$R + x$I
|
||||
x$isolates <- x$R + x$I + x$SDD
|
||||
}
|
||||
|
||||
give_ab_name <- function(ab, format, language) {
|
||||
|
120
R/count.R
120
R/count.R
@ -143,66 +143,11 @@ count_susceptible <- function(..., only_all_tested = FALSE) {
|
||||
)
|
||||
}
|
||||
|
||||
#' @rdname count
|
||||
#' @export
|
||||
count_R <- function(..., only_all_tested = FALSE) {
|
||||
tryCatch(
|
||||
sir_calc(...,
|
||||
ab_result = "R",
|
||||
only_all_tested = only_all_tested,
|
||||
only_count = TRUE
|
||||
),
|
||||
error = function(e) stop_(gsub("in sir_calc(): ", "", e$message, fixed = TRUE), call = -5)
|
||||
)
|
||||
}
|
||||
|
||||
#' @rdname count
|
||||
#' @export
|
||||
count_IR <- function(..., only_all_tested = FALSE) {
|
||||
if (message_not_thrown_before("count_IR", entire_session = TRUE)) {
|
||||
message_("Using `count_IR()` is discouraged; use `count_resistant()` instead to not consider \"I\" being resistant. This note will be shown once for this session.", as_note = FALSE)
|
||||
}
|
||||
tryCatch(
|
||||
sir_calc(...,
|
||||
ab_result = c("I", "R"),
|
||||
only_all_tested = only_all_tested,
|
||||
only_count = TRUE
|
||||
),
|
||||
error = function(e) stop_(gsub("in sir_calc(): ", "", e$message, fixed = TRUE), call = -5)
|
||||
)
|
||||
}
|
||||
|
||||
#' @rdname count
|
||||
#' @export
|
||||
count_I <- function(..., only_all_tested = FALSE) {
|
||||
tryCatch(
|
||||
sir_calc(...,
|
||||
ab_result = "I",
|
||||
only_all_tested = only_all_tested,
|
||||
only_count = TRUE
|
||||
),
|
||||
error = function(e) stop_(gsub("in sir_calc(): ", "", e$message, fixed = TRUE), call = -5)
|
||||
)
|
||||
}
|
||||
|
||||
#' @rdname count
|
||||
#' @export
|
||||
count_SI <- function(..., only_all_tested = FALSE) {
|
||||
tryCatch(
|
||||
sir_calc(...,
|
||||
ab_result = c("S", "I"),
|
||||
only_all_tested = only_all_tested,
|
||||
only_count = TRUE
|
||||
),
|
||||
error = function(e) stop_(gsub("in sir_calc(): ", "", e$message, fixed = TRUE), call = -5)
|
||||
)
|
||||
}
|
||||
|
||||
#' @rdname count
|
||||
#' @export
|
||||
count_S <- function(..., only_all_tested = FALSE) {
|
||||
if (message_not_thrown_before("count_S", entire_session = TRUE)) {
|
||||
message_("Using `count_S()` is discouraged; use `count_susceptible()` instead to also consider \"I\" being susceptible. This note will be shown once for this session.", as_note = FALSE)
|
||||
message_("Using `count_S()` is discouraged; use `count_susceptible()` instead to also consider \"I\" and \"SDD\" being susceptible. This note will be shown once for this session.", as_note = FALSE)
|
||||
}
|
||||
tryCatch(
|
||||
sir_calc(...,
|
||||
@ -214,12 +159,73 @@ count_S <- function(..., only_all_tested = FALSE) {
|
||||
)
|
||||
}
|
||||
|
||||
#' @rdname count
|
||||
#' @export
|
||||
count_SI <- function(..., only_all_tested = FALSE) {
|
||||
if (message_not_thrown_before("count_SI", entire_session = TRUE)) {
|
||||
message_("Note that `count_SI()` will also count dose-dependent susceptibility, 'SDD'. This note will be shown once for this session.", as_note = FALSE)
|
||||
}
|
||||
tryCatch(
|
||||
sir_calc(...,
|
||||
ab_result = c("S", "SDD", "I"),
|
||||
only_all_tested = only_all_tested,
|
||||
only_count = TRUE
|
||||
),
|
||||
error = function(e) stop_(gsub("in sir_calc(): ", "", e$message, fixed = TRUE), call = -5)
|
||||
)
|
||||
}
|
||||
|
||||
#' @rdname count
|
||||
#' @export
|
||||
count_I <- function(..., only_all_tested = FALSE) {
|
||||
if (message_not_thrown_before("count_I", entire_session = TRUE)) {
|
||||
message_("Note that `count_I()` will also count dose-dependent susceptibility, 'SDD'. This note will be shown once for this session.", as_note = FALSE)
|
||||
}
|
||||
tryCatch(
|
||||
sir_calc(...,
|
||||
ab_result = c("I", "SDD"),
|
||||
only_all_tested = only_all_tested,
|
||||
only_count = TRUE
|
||||
),
|
||||
error = function(e) stop_(gsub("in sir_calc(): ", "", e$message, fixed = TRUE), call = -5)
|
||||
)
|
||||
}
|
||||
|
||||
#' @rdname count
|
||||
#' @export
|
||||
count_IR <- function(..., only_all_tested = FALSE) {
|
||||
if (message_not_thrown_before("count_IR", entire_session = TRUE)) {
|
||||
message_("Using `count_IR()` is discouraged; use `count_resistant()` instead to not consider \"I\" and \"SDD\" being resistant. This note will be shown once for this session.", as_note = FALSE)
|
||||
}
|
||||
tryCatch(
|
||||
sir_calc(...,
|
||||
ab_result = c("I", "SDD", "R"),
|
||||
only_all_tested = only_all_tested,
|
||||
only_count = TRUE
|
||||
),
|
||||
error = function(e) stop_(gsub("in sir_calc(): ", "", e$message, fixed = TRUE), call = -5)
|
||||
)
|
||||
}
|
||||
|
||||
#' @rdname count
|
||||
#' @export
|
||||
count_R <- function(..., only_all_tested = FALSE) {
|
||||
tryCatch(
|
||||
sir_calc(...,
|
||||
ab_result = "R",
|
||||
only_all_tested = only_all_tested,
|
||||
only_count = TRUE
|
||||
),
|
||||
error = function(e) stop_(gsub("in sir_calc(): ", "", e$message, fixed = TRUE), call = -5)
|
||||
)
|
||||
}
|
||||
|
||||
#' @rdname count
|
||||
#' @export
|
||||
count_all <- function(..., only_all_tested = FALSE) {
|
||||
tryCatch(
|
||||
sir_calc(...,
|
||||
ab_result = c("S", "I", "R"),
|
||||
ab_result = c("S", "SDD", "I", "R", "N"),
|
||||
only_all_tested = only_all_tested,
|
||||
only_count = TRUE
|
||||
),
|
||||
|
@ -181,8 +181,8 @@ custom_eucast_rules <- function(...) {
|
||||
result_value <- as.character(result)[[3]]
|
||||
result_value[result_value == "NA"] <- NA
|
||||
stop_ifnot(
|
||||
result_value %in% c("S", "I", "R", NA),
|
||||
"the resulting value of rule ", i, " must be either \"S\", \"I\", \"R\" or NA"
|
||||
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 <- as.sir(result_value)
|
||||
|
||||
|
2
R/data.R
2
R/data.R
@ -298,7 +298,7 @@
|
||||
#' ### Download
|
||||
#' Like all data sets in this package, this data set is publicly available for download in the following formats: R, MS Excel, Apache Feather, Apache Parquet, SPSS, SAS, and Stata. Please visit [our website for the download links](https://msberends.github.io/AMR/articles/datasets.html). The actual files are of course available on [our GitHub repository](https://github.com/msberends/AMR/tree/main/data-raw). They allow for machine reading EUCAST and CLSI guidelines, which is almost impossible with the MS Excel and PDF files distributed by EUCAST and CLSI, though initiatives have started to overcome these burdens.
|
||||
#'
|
||||
#' **NOTE:** this `AMR` package (and the WHONET software as well) contains internal methods to apply the guidelines, which is rather complex. For example, some breakpoints must be applied on certain species groups (which are in case of this package available through the [microorganisms.groups] data set). It is important that this is considered when using the breakpoints for own use.
|
||||
#' **NOTE:** this `AMR` package (and the WHONET software as well) contains rather complex internal methods to apply the guidelines. For example, some breakpoints must be applied on certain species groups (which are in case of this package available through the [microorganisms.groups] data set). It is important that this is considered when using the breakpoints for own use.
|
||||
#' @seealso [intrinsic_resistant]
|
||||
#' @examples
|
||||
#' clinical_breakpoints
|
||||
|
@ -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", "I", "R"), na.rm = TRUE),
|
||||
FUN = function(x) any(as.character(x[1:10000]) %in% c("S", "SDD", "I", "R", "N"), na.rm = TRUE),
|
||||
USE.NAMES = FALSE
|
||||
))
|
||||
if (method == "phenotype-based" && !any_col_contains_sir) {
|
||||
|
@ -282,6 +282,8 @@ generate_antimcrobials_string <- function(df) {
|
||||
as.list(df),
|
||||
function(x) {
|
||||
x <- toupper(as.character(x))
|
||||
x[x == "SDD"] <- "I"
|
||||
# ignore "N" here, no use for determining first isolates
|
||||
x[!x %in% c("S", "I", "R")] <- "."
|
||||
paste(x)
|
||||
}
|
||||
@ -312,7 +314,7 @@ antimicrobials_equal <- function(y,
|
||||
val <- strsplit(val, "", fixed = TRUE)[[1L]]
|
||||
val.int <- rep(NA_real_, length(val))
|
||||
val.int[val == "S"] <- 1
|
||||
val.int[val == "I"] <- 2
|
||||
val.int[val %in% c("I", "SDD")] <- 2
|
||||
val.int[val == "R"] <- 3
|
||||
val.int
|
||||
}
|
||||
|
2
R/mdro.R
2
R/mdro.R
@ -732,7 +732,7 @@ mdro <- function(x = NULL,
|
||||
sum(vapply(
|
||||
FUN.VALUE = logical(1),
|
||||
group_tbl,
|
||||
function(group) any(unlist(x[row, group[!is.na(group)], drop = TRUE]) %in% c("S", "I", "R"))
|
||||
function(group) any(unlist(x[row, group[!is.na(group)], drop = TRUE]) %in% c("S", "SDD", "I", "R"))
|
||||
))
|
||||
}
|
||||
)
|
||||
|
26
R/plot.R
26
R/plot.R
@ -363,6 +363,7 @@ autoplot.mic <- function(object,
|
||||
if (any(colours_SIR %in% cols_sub$cols)) {
|
||||
vals <- c(
|
||||
"(S) Susceptible" = colours_SIR[1],
|
||||
"(SDD) Susceptible dose-dependent" = colours_SIR[2],
|
||||
"(I) Susceptible, incr. exp." = colours_SIR[2],
|
||||
"(I) Intermediate" = colours_SIR[2],
|
||||
"(R) Resistant" = colours_SIR[3]
|
||||
@ -595,6 +596,7 @@ autoplot.disk <- function(object,
|
||||
if (any(colours_SIR %in% cols_sub$cols)) {
|
||||
vals <- c(
|
||||
"(S) Susceptible" = colours_SIR[1],
|
||||
"(SDD) Susceptible dose-dependent" = colours_SIR[2],
|
||||
"(I) Susceptible, incr. exp." = colours_SIR[2],
|
||||
"(I) Intermediate" = colours_SIR[2],
|
||||
"(R) Resistant" = colours_SIR[3]
|
||||
@ -648,14 +650,21 @@ plot.sir <- function(x,
|
||||
if (!"S" %in% data$x) {
|
||||
data <- rbind_AMR(data, data.frame(x = "S", n = 0, s = 0, stringsAsFactors = FALSE))
|
||||
}
|
||||
if (!"SDD" %in% data$x) {
|
||||
data <- rbind_AMR(data, data.frame(x = "SDD", n = 0, s = 0, stringsAsFactors = FALSE))
|
||||
}
|
||||
if (!"I" %in% data$x) {
|
||||
data <- rbind_AMR(data, data.frame(x = "I", n = 0, s = 0, stringsAsFactors = FALSE))
|
||||
}
|
||||
if (!"R" %in% data$x) {
|
||||
data <- rbind_AMR(data, data.frame(x = "R", n = 0, s = 0, stringsAsFactors = FALSE))
|
||||
}
|
||||
|
||||
data$x <- factor(data$x, levels = c("S", "I", "R"), ordered = TRUE)
|
||||
if (!"N" %in% data$x) {
|
||||
data <- rbind_AMR(data, data.frame(x = "N", 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)
|
||||
|
||||
ymax <- pm_if_else(max(data$s) > 95, 105, 100)
|
||||
|
||||
@ -704,10 +713,15 @@ barplot.sir <- function(height,
|
||||
if (length(colours_SIR) == 1) {
|
||||
colours_SIR <- rep(colours_SIR, 3)
|
||||
}
|
||||
# add SSD and N to colours
|
||||
colours_SIR <- c(colours_SIR[1:2], colours_SIR[2], colours_SIR[3], "#888888")
|
||||
main <- gsub(" +", " ", paste0(main, collapse = " "))
|
||||
|
||||
x <- table(height)
|
||||
x <- x[c(1, 2, 3)]
|
||||
# remove missing I, SSD, 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)]
|
||||
# plot it
|
||||
barplot(x,
|
||||
col = colours_SIR,
|
||||
xlab = xlab,
|
||||
@ -753,8 +767,10 @@ autoplot.sir <- function(object,
|
||||
ggplot2::scale_fill_manual(
|
||||
values = c(
|
||||
"S" = colours_SIR[1],
|
||||
"SDD" = colours_SIR[2],
|
||||
"I" = colours_SIR[2],
|
||||
"R" = colours_SIR[3]
|
||||
"R" = colours_SIR[3],
|
||||
"N" = "#888888"
|
||||
),
|
||||
limits = force
|
||||
) +
|
||||
@ -882,8 +898,10 @@ plot_colours_subtitle_guideline <- function(x, mo, ab, guideline, colours_SIR, f
|
||||
cols <- character(length = length(sir))
|
||||
cols[is.na(sir)] <- "#BEBEBE"
|
||||
cols[sir == "S"] <- colours_SIR[1]
|
||||
cols[sir == "SDD"] <- colours_SIR[2]
|
||||
cols[sir == "I"] <- colours_SIR[2]
|
||||
cols[sir == "R"] <- colours_SIR[3]
|
||||
cols[sir == "N"] <- "#888888"
|
||||
sub <- bquote(.(abname) ~ "-" ~ italic(.(moname)) ~ .(guideline_txt))
|
||||
} else {
|
||||
cols <- "#BEBEBE"
|
||||
|
@ -48,7 +48,7 @@
|
||||
#' @details
|
||||
#' **Remember that you should filter your data to let it contain only first isolates!** This is needed to exclude duplicates and to reduce selection bias. Use [first_isolate()] to determine them in your data set with one of the four available algorithms.
|
||||
#'
|
||||
#' The function [resistance()] is equal to the function [proportion_R()]. The function [susceptibility()] is equal to the function [proportion_SI()].
|
||||
#' The function [resistance()] is equal to the function [proportion_R()]. The function [susceptibility()] is equal to the function [proportion_SI()]. Since AMR v3.0, [proportion_SI()] and [proportion_I()] include dose-dependent susceptibility ('SDD').
|
||||
#'
|
||||
#' Use [sir_confidence_interval()] to calculate the confidence interval, which relies on [binom.test()], i.e., the Clopper-Pearson method. This function returns a vector of length 2 at default for antimicrobial *resistance*. Change the `side` argument to "left"/"min" or "right"/"max" to return a single value, and change the `ab_result` argument to e.g. `c("S", "I")` to test for antimicrobial *susceptibility*, see Examples.
|
||||
#'
|
||||
@ -247,7 +247,7 @@ susceptibility <- function(...,
|
||||
only_all_tested = FALSE) {
|
||||
tryCatch(
|
||||
sir_calc(...,
|
||||
ab_result = c("S", "I"),
|
||||
ab_result = c("S", "SDD", "I"),
|
||||
minimum = minimum,
|
||||
as_percent = as_percent,
|
||||
only_all_tested = only_all_tested,
|
||||
@ -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, 2, 3), is_in = c("S", "I", "R"))
|
||||
meet_criteria(ab_result, allow_class = c("character", "sir"), has_length = c(1:5), is_in = c("S", "SDD", "I", "R", "N"))
|
||||
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", "I", "R"),
|
||||
ab_result = c("S", "SDD", "I", "R", "N"),
|
||||
only_all_tested = only_all_tested,
|
||||
only_count = TRUE
|
||||
),
|
||||
@ -351,9 +351,12 @@ proportion_IR <- function(...,
|
||||
minimum = 30,
|
||||
as_percent = FALSE,
|
||||
only_all_tested = FALSE) {
|
||||
if (message_not_thrown_before("proportion_IR", entire_session = TRUE)) {
|
||||
message_("Note that `proportion_IR()` will also include dose-dependent susceptibility, 'SDD'. This note will be shown once for this session.", as_note = FALSE)
|
||||
}
|
||||
tryCatch(
|
||||
sir_calc(...,
|
||||
ab_result = c("I", "R"),
|
||||
ab_result = c("I", "SDD", "R"),
|
||||
minimum = minimum,
|
||||
as_percent = as_percent,
|
||||
only_all_tested = only_all_tested,
|
||||
@ -369,9 +372,12 @@ proportion_I <- function(...,
|
||||
minimum = 30,
|
||||
as_percent = FALSE,
|
||||
only_all_tested = FALSE) {
|
||||
if (message_not_thrown_before("proportion_I", entire_session = TRUE)) {
|
||||
message_("Note that `proportion_I()` will also include dose-dependent susceptibility, 'SDD'. This note will be shown once for this session.", as_note = FALSE)
|
||||
}
|
||||
tryCatch(
|
||||
sir_calc(...,
|
||||
ab_result = "I",
|
||||
ab_result = c("I", "SDD"),
|
||||
minimum = minimum,
|
||||
as_percent = as_percent,
|
||||
only_all_tested = only_all_tested,
|
||||
@ -387,9 +393,12 @@ proportion_SI <- function(...,
|
||||
minimum = 30,
|
||||
as_percent = FALSE,
|
||||
only_all_tested = FALSE) {
|
||||
if (message_not_thrown_before("proportion_SI", entire_session = TRUE)) {
|
||||
message_("Note that `proportion_SI()` will also include dose-dependent susceptibility, 'SDD'. This note will be shown once for this session.", as_note = FALSE)
|
||||
}
|
||||
tryCatch(
|
||||
sir_calc(...,
|
||||
ab_result = c("S", "I"),
|
||||
ab_result = c("S", "I", "SDD"),
|
||||
minimum = minimum,
|
||||
as_percent = as_percent,
|
||||
only_all_tested = only_all_tested,
|
||||
|
76
R/sir.R
76
R/sir.R
@ -31,12 +31,12 @@
|
||||
#'
|
||||
#' @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].
|
||||
#'
|
||||
#' Currently breakpoints are available:
|
||||
#' These breakpoints are currently available:
|
||||
#' - For **clinical microbiology** from EUCAST `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "EUCAST" & type == "human")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "EUCAST" & type == "human")$guideline)))` and CLSI `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI" & type == "human")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI" & type == "human")$guideline)))`;
|
||||
#' - For **veterinary microbiology** from EUCAST `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "EUCAST" & type == "animal")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "EUCAST" & type == "animal")$guideline)))` and CLSI `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI" & type == "animal")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI" & type == "animal")$guideline)))`;
|
||||
#' - ECOFFs (Epidemiological cut-off values) from EUCAST `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "EUCAST" & type == "ECOFF")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "EUCAST" & type == "ECOFF")$guideline)))` and CLSI `r min(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI" & type == "ECOFF")$guideline)))`-`r max(as.integer(gsub("[^0-9]", "", subset(AMR::clinical_breakpoints, guideline %like% "CLSI" & type == "ECOFF")$guideline)))`.
|
||||
#'
|
||||
#' All breakpoints used for interpretation are publicly available in the [clinical_breakpoints] data set.
|
||||
#' All breakpoints used for interpretation are available in our [clinical_breakpoints] data set.
|
||||
#' @rdname as.sir
|
||||
#' @param x vector of values (for class [`mic`]: MIC values in mg/L, for class [`disk`]: a disk diffusion radius in millimetres)
|
||||
#' @param mo any (vector of) text that can be coerced to valid microorganism codes with [as.mo()], can be left empty to determine it automatically
|
||||
@ -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 values S, I and R and will try its best to determine this 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 unclear.
|
||||
#' 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.
|
||||
#'
|
||||
#' 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:
|
||||
@ -120,7 +120,7 @@
|
||||
#'
|
||||
#' The function [is.sir()] detects if the input contains class `sir`. 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 columns contains at most 5% invalid antimicrobial interpretations (not S and/or I and/or R), 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 columns 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.
|
||||
#' @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>):
|
||||
#'
|
||||
@ -214,7 +214,7 @@
|
||||
#'
|
||||
#' # For CLEANING existing SIR values ------------------------------------
|
||||
#'
|
||||
#' as.sir(c("S", "I", "R", "A", "B", "C"))
|
||||
#' as.sir(c("S", "SDD", "I", "R", "N", "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)
|
||||
@ -242,13 +242,18 @@ as.sir <- function(x, ...) {
|
||||
UseMethod("as.sir")
|
||||
}
|
||||
|
||||
as_sir_structure <- function(x) {
|
||||
structure(factor(as.character(unlist(unname(x))),
|
||||
levels = c("S", "SDD", "I", "R", "N"),
|
||||
ordered = TRUE),
|
||||
class = c("sir", "ordered", "factor"))
|
||||
}
|
||||
|
||||
#' @rdname as.sir
|
||||
#' @details `NA_sir_` is a missing value of the new `sir` class, analogous to e.g. base \R's [`NA_character_`][base::NA].
|
||||
#' @format NULL
|
||||
#' @export
|
||||
NA_sir_ <- set_clean_class(factor(NA_character_, levels = c("S", "I", "R"), ordered = TRUE),
|
||||
new_class = c("sir", "ordered", "factor")
|
||||
)
|
||||
NA_sir_ <- as_sir_structure(NA_character_)
|
||||
|
||||
#' @rdname as.sir
|
||||
#' @export
|
||||
@ -286,9 +291,9 @@ is_sir_eligible <- function(x, threshold = 0.05) {
|
||||
%in% class(x))) {
|
||||
# no transformation needed
|
||||
return(FALSE)
|
||||
} else if (all(x %in% c("S", "I", "R", NA)) & !all(is.na(x))) {
|
||||
} else if (all(x %in% c("S", "SDD", "I", "R", "N", NA)) & !all(is.na(x))) {
|
||||
return(TRUE)
|
||||
} else if (!any(c("S", "I", "R") %in% x, na.rm = TRUE) & !all(is.na(x))) {
|
||||
} else if (!any(c("S", "SDD", "I", "R", "N") %in% x, na.rm = TRUE) & !all(is.na(x))) {
|
||||
return(FALSE)
|
||||
} else {
|
||||
x <- x[!is.na(x) & !is.null(x) & !x %in% c("", "-", "NULL")]
|
||||
@ -316,9 +321,11 @@ is_sir_eligible <- function(x, threshold = 0.05) {
|
||||
}
|
||||
}
|
||||
|
||||
#' @rdname as.sir
|
||||
#' @export
|
||||
#' @param S,I,R,N,SDD a case-indepdendent [regular expression][base::regex] to translate input to this result. This regular expression will be run *after* all non-letters are removed from the input.
|
||||
# extra param: warn (logical, to never throw a warning)
|
||||
as.sir.default <- function(x, ...) {
|
||||
as.sir.default <- function(x, S = "^(S|U)+$", I = "^(I|H)+$", R = "^(R)+$", N = "^(N|V)+$", SDD = "^(SDD|D)+$", ...) {
|
||||
if (inherits(x, "sir")) {
|
||||
return(x)
|
||||
}
|
||||
@ -338,11 +345,11 @@ as.sir.default <- function(x, ...) {
|
||||
x[x.bak == 2] <- "I"
|
||||
x[x.bak == 3] <- "R"
|
||||
}
|
||||
} else if (inherits(x.bak, "character") && all(x %in% c("1", "2", "3", "S", "I", "R", NA_character_))) {
|
||||
} else if (inherits(x.bak, "character") && all(x %in% c("1", "2", "3", c("S", "SDD", "I", "R", "N"), NA_character_))) {
|
||||
x[x.bak == "1"] <- "S"
|
||||
x[x.bak == "2"] <- "I"
|
||||
x[x.bak == "3"] <- "R"
|
||||
} else if (!all(is.na(x)) && !identical(levels(x), c("S", "I", "R")) && !all(x %in% c("S", "I", "R", NA))) {
|
||||
} 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))) {
|
||||
if (all(x %unlike% "(S|I|R)", na.rm = TRUE)) {
|
||||
# check if they are actually MICs or disks
|
||||
if (all_valid_mics(x)) {
|
||||
@ -379,23 +386,14 @@ as.sir.default <- function(x, ...) {
|
||||
x[x %like% "([^a-z]|^)res(is(tant)?)?"] <- "R"
|
||||
x[x %like% "([^a-z]|^)sus(cep(tible)?)?"] <- "S"
|
||||
x[x %like% "([^a-z]|^)int(er(mediate)?)?|incr.*exp"] <- "I"
|
||||
# remove other invalid characters
|
||||
# set to capitals
|
||||
x <- toupper(x)
|
||||
x <- gsub("[^A-Z]+", "", x, perl = TRUE)
|
||||
# CLSI uses SDD for "susceptible dose-dependent"
|
||||
x <- gsub("SDD", "I", x, fixed = TRUE)
|
||||
# some labs now report "H" instead of "I" to not interfere with EUCAST prior to 2019
|
||||
x <- gsub("H", "I", x, fixed = TRUE)
|
||||
# MIPS uses D for Dose-dependent (which is I, but it will throw a note)
|
||||
x <- gsub("D", "I", x, fixed = TRUE)
|
||||
# MIPS uses U for "susceptible urine"
|
||||
x <- gsub("U", "S", x, fixed = TRUE)
|
||||
# in cases of "S;S" keep S, but in case of "S;I" make it NA
|
||||
x <- gsub("^S+$", "S", x)
|
||||
x <- gsub("^I+$", "I", x)
|
||||
x <- gsub("^R+$", "R", x)
|
||||
x[!x %in% c("S", "I", "R")] <- NA_character_
|
||||
# apply regexes set by user
|
||||
x[x %like% S] <- "S"
|
||||
x[x %like% I] <- "I"
|
||||
x[x %like% R] <- "R"
|
||||
x[x %like% N] <- "N"
|
||||
x[x %like% SDD] <- "SDD"
|
||||
x[!x %in% c("S", "SDD", "I", "R", "N")] <- NA_character_
|
||||
na_after <- length(x[is.na(x) | x == ""])
|
||||
|
||||
if (!isFALSE(list(...)$warn)) { # so as.sir(..., warn = FALSE) will never throw a warning
|
||||
@ -415,24 +413,10 @@ as.sir.default <- function(x, ...) {
|
||||
call = FALSE
|
||||
)
|
||||
}
|
||||
if (any(toupper(x.bak[!is.na(x.bak)]) == "U") && message_not_thrown_before("as.sir", "U")) {
|
||||
warning_("in `as.sir()`: 'U' was interpreted as 'S', following some laboratory systems")
|
||||
}
|
||||
if (any(toupper(x.bak[!is.na(x.bak)]) == "D") && message_not_thrown_before("as.sir", "D")) {
|
||||
warning_("in `as.sir()`: 'D' (dose-dependent) was interpreted as 'I', following some laboratory systems")
|
||||
}
|
||||
if (any(toupper(x.bak[!is.na(x.bak)]) == "SDD") && message_not_thrown_before("as.sir", "SDD")) {
|
||||
warning_("in `as.sir()`: 'SDD' (susceptible dose-dependent, coined by CLSI) was interpreted as 'I' to comply with EUCAST's 'I'")
|
||||
}
|
||||
if (any(toupper(x.bak[!is.na(x.bak)]) == "H") && message_not_thrown_before("as.sir", "H")) {
|
||||
warning_("in `as.sir()`: 'H' was interpreted as 'I', following some laboratory systems")
|
||||
}
|
||||
}
|
||||
}
|
||||
|
||||
set_clean_class(factor(x, levels = c("S", "I", "R"), ordered = TRUE),
|
||||
new_class = c("sir", "ordered", "factor")
|
||||
)
|
||||
as_sir_structure(x)
|
||||
}
|
||||
|
||||
#' @rdname as.sir
|
||||
@ -693,7 +677,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", "I", "R", NA), na.rm = TRUE)) {
|
||||
if (!all(x[, ab_cols[i], drop = TRUE] %in% c("S", "SDD", "I", "R", "N", NA), na.rm = TRUE)) {
|
||||
show_message <- TRUE
|
||||
# only print message if values are not already clean
|
||||
message_("Cleaning values in column '", font_bold(ab), "' (",
|
||||
@ -1245,8 +1229,10 @@ 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 == "S"] <- font_green_bg(" S ")
|
||||
out[x == "I"] <- font_orange_bg(" I ")
|
||||
out[x == "SDD"] <- font_orange_bg(" SDD ")
|
||||
if (is_dark()) {
|
||||
out[x == "R"] <- font_red_bg(" R ")
|
||||
} else {
|
||||
|
16
R/sir_calc.R
16
R/sir_calc.R
@ -41,7 +41,7 @@ sir_calc <- function(...,
|
||||
as_percent = FALSE,
|
||||
only_all_tested = FALSE,
|
||||
only_count = FALSE) {
|
||||
meet_criteria(ab_result, allow_class = c("character", "numeric", "integer"), has_length = c(1, 2, 3))
|
||||
meet_criteria(ab_result, allow_class = c("character", "numeric", "integer"), has_length = c(1:5))
|
||||
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)
|
||||
@ -249,7 +249,13 @@ sir_calc_df <- function(type, # "proportion", "count" or "both"
|
||||
for (i in seq_len(ncol(data))) {
|
||||
if (is.sir(data[, i, drop = TRUE])) {
|
||||
data[, i] <- as.character(data[, i, drop = TRUE])
|
||||
data[, i] <- gsub("(I|S)", "SI", data[, i, drop = TRUE])
|
||||
if ("SDD" %in% data[, i, drop = TRUE]) {
|
||||
if (message_not_thrown_before("sir_calc_df", combine_SI, entire_session = TRUE)) {
|
||||
message_("Note that `sir_calc_df()` will also count dose-dependent susceptibility, 'SDD', as 'SI' when `combine_SI = TRUE`. This note will be shown once for this session.", as_note = FALSE)
|
||||
}
|
||||
|
||||
}
|
||||
data[, i] <- gsub("(I|S|SDD)", "SI", data[, i, drop = TRUE])
|
||||
}
|
||||
}
|
||||
}
|
||||
@ -272,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"), ordered = TRUE)
|
||||
values <- factor(values, levels = c("SI", "R", "N"), ordered = TRUE)
|
||||
} else {
|
||||
values <- factor(values, levels = c("S", "I", "R"), ordered = TRUE)
|
||||
values <- factor(values, levels = c("S", "SDD", "I", "R", "N"), ordered = TRUE)
|
||||
}
|
||||
col_results <- as.data.frame(as.matrix(table(values)), stringsAsFactors = FALSE)
|
||||
col_results$interpretation <- rownames(col_results)
|
||||
@ -351,7 +357,7 @@ sir_calc_df <- function(type, # "proportion", "count" or "both"
|
||||
} else {
|
||||
# don't use as.sir() here, as it would add the class 'sir' and we would like
|
||||
# the same data structure as output, regardless of input
|
||||
out$interpretation <- factor(out$interpretation, levels = c("S", "I", "R"), ordered = TRUE)
|
||||
out$interpretation <- factor(out$interpretation, levels = c("S", "SDD", "I", "R", "N"), ordered = TRUE)
|
||||
}
|
||||
|
||||
if (data_has_groups) {
|
||||
|
BIN
R/sysdata.rda
BIN
R/sysdata.rda
Binary file not shown.
Reference in New Issue
Block a user