1
0
mirror of https://github.com/msberends/AMR.git synced 2025-07-08 23:21:56 +02:00

(v1.7.1.9054) mdro() update - fixes #49, first_isolate() speedup

This commit is contained in:
2021-11-28 23:01:26 +01:00
parent 9a2c431e16
commit 694cf5ba77
72 changed files with 780 additions and 669 deletions

3
R/ab.R
View File

@ -119,6 +119,8 @@ as.ab <- function(x, flag_multiple_results = TRUE, info = interactive(), ...) {
x <- iconv(x, from = "UTF-8", to = "ASCII//TRANSLIT")
x <- gsub('"', "", x, fixed = TRUE)
x <- gsub("(specimen|specimen date|specimen_date|spec_date|gender|^dates?$)", "", x, ignore.case = TRUE, perl = TRUE)
# penicillin is a special case: we call it so, but then mean benzylpenicillin
x[x %like_case% "^PENICILLIN" & x %unlike_case% "[ /+-]"] <- "benzylpenicillin"
x_bak_clean <- x
if (already_regex == FALSE) {
x_bak_clean <- generalise_antibiotic_name(x_bak_clean)
@ -227,6 +229,7 @@ as.ab <- function(x, flag_multiple_results = TRUE, info = interactive(), ...) {
}
x_spelling <- x[i]
if (already_regex == FALSE) {
x_spelling <- gsub("[IY]+", "[IY]+", x_spelling, perl = TRUE)
x_spelling <- gsub("(C|K|Q|QU|S|Z|X|KS)+", "(C|K|Q|QU|S|Z|X|KS)+", x_spelling, perl = TRUE)
x_spelling <- gsub("(PH|F|V)+", "(PH|F|V)+", x_spelling, perl = TRUE)

View File

@ -26,7 +26,7 @@
#' Define Custom EUCAST Rules
#'
#' Define custom EUCAST rules for your organisation or specific analysis and use the output of this function in [eucast_rules()].
#' @inheritSection lifecycle Maturing Lifecycle
#' @inheritSection lifecycle Stable Lifecycle
#' @param ... rules in formula notation, see *Examples*
#' @details
#' Some organisations have their own adoption of EUCAST rules. This function can be used to define custom EUCAST rules to be used in the [eucast_rules()] function.

View File

@ -119,6 +119,12 @@ all_valid_disks <- function(x) {
!any(is.na(x_disk)) && !all(is.na(x))
}
#' @rdname as.disk
#' @details `NA_disk_` is a missing value of the new `<disk>` class.
#' @export
NA_disk_ <- set_clean_class(as.integer(NA_real_),
new_class = c("disk", "integer"))
#' @rdname as.disk
#' @export
is.disk <- function(x) {

View File

@ -108,8 +108,8 @@ get_episode <- function(x, episode_days, ...) {
meet_criteria(x, allow_class = c("Date", "POSIXt"))
meet_criteria(episode_days, allow_class = c("numeric", "integer"), has_length = 1, is_positive = TRUE, is_finite = FALSE)
exec_episode(type = "sequential",
x = x,
exec_episode(x = x,
type = "sequential",
episode_days = episode_days,
... = ...)
}
@ -120,13 +120,13 @@ is_new_episode <- function(x, episode_days, ...) {
meet_criteria(x, allow_class = c("Date", "POSIXt"))
meet_criteria(episode_days, allow_class = c("numeric", "integer"), has_length = 1, is_positive = TRUE, is_finite = FALSE)
exec_episode(type = "logical",
x = x,
exec_episode(x = x,
type = "logical",
episode_days = episode_days,
... = ...)
}
exec_episode <- function(type, x, episode_days, ...) {
exec_episode <- function(x, type, episode_days, ...) {
x <- as.double(as.POSIXct(x)) # as.POSIXct() required for Date classes
# since x is now in seconds, get seconds from episode_days as well
episode_seconds <- episode_days * 60 * 60 * 24
@ -155,7 +155,7 @@ exec_episode <- function(type, x, episode_days, ...) {
# I asked on StackOverflow:
# https://stackoverflow.com/questions/42122245/filter-one-row-every-year
exec <- function(x, episode_seconds) {
run_episodes <- function(x, episode_seconds) {
indices <- integer()
start <- x[1]
ind <- 1
@ -181,11 +181,6 @@ exec_episode <- function(type, x, episode_days, ...) {
}
}
df <- data.frame(x = x,
y = seq_len(length(x))) %pm>%
pm_arrange(x)
df$new <- exec(df$x, episode_seconds)
df %pm>%
pm_arrange(y) %pm>%
pm_pull(new)
ord <- order(x)
run_episodes(x[ord], episode_seconds)[ord]
}

View File

@ -23,6 +23,10 @@
# how to conduct AMR data analysis: https://msberends.github.io/AMR/ #
# ==================================================================== #
# ====================================================== #
# || Change the EUCAST version numbers in R/globals.R || #
# ====================================================== #
format_eucast_version_nr <- function(version, markdown = TRUE) {
# for documentation - adds title, version number, year and url in markdown language
lst <- c(EUCAST_VERSION_BREAKPOINTS, EUCAST_VERSION_EXPERT_RULES)
@ -105,6 +109,7 @@ format_eucast_version_nr <- function(version, markdown = TRUE) {
#' Leclercq et al. **EUCAST expert rules in antimicrobial susceptibility testing.** *Clin Microbiol Infect.* 2013;19(2):141-60; \doi{https://doi.org/10.1111/j.1469-0691.2011.03703.x}
#' - EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes Tables. Version 3.1, 2016. [(link)](https://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Expert_Rules/Expert_rules_intrinsic_exceptional_V3.1.pdf)
#' - EUCAST Intrinsic Resistance and Unusual Phenotypes. Version 3.2, 2020. [(link)](https://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Expert_Rules/2020/Intrinsic_Resistance_and_Unusual_Phenotypes_Tables_v3.2_20200225.pdf)
#' - EUCAST Intrinsic Resistance and Unusual Phenotypes. Version 3.3, 2021. [(link)](https://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Expert_Rules/2021/Intrinsic_Resistance_and_Unusual_Phenotypes_Tables_v3.3_20211018.pdf)
#' - EUCAST Breakpoint tables for interpretation of MICs and zone diameters. Version 9.0, 2019. [(link)](https://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Breakpoint_tables/v_9.0_Breakpoint_Tables.xlsx)
#' - EUCAST Breakpoint tables for interpretation of MICs and zone diameters. Version 10.0, 2020. [(link)](https://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Breakpoint_tables/v_10.0_Breakpoint_Tables.xlsx)
#' - EUCAST Breakpoint tables for interpretation of MICs and zone diameters. Version 11.0, 2021. [(link)](https://www.eucast.org/fileadmin/src/media/PDFs/EUCAST_files/Breakpoint_tables/v_11.0_Breakpoint_Tables.xlsx)
@ -159,7 +164,7 @@ eucast_rules <- function(x,
rules = getOption("AMR_eucastrules", default = c("breakpoints", "expert")),
verbose = FALSE,
version_breakpoints = 11.0,
version_expertrules = 3.2,
version_expertrules = 3.3,
ampc_cephalosporin_resistance = NA,
only_rsi_columns = FALSE,
custom_rules = NULL,
@ -316,25 +321,6 @@ eucast_rules <- function(x,
}
# Some helper functions ---------------------------------------------------
get_antibiotic_columns <- function(x, cols_ab) {
x <- trimws(unique(toupper(unlist(strsplit(x, ",")))))
x_new <- character()
for (val in x) {
if (paste0("AB_", val) %in% ls(envir = asNamespace("AMR"))) {
# antibiotic group names, as defined in data-raw/_internals.R, such as `AB_CARBAPENEMS`
val <- eval(parse(text = paste0("AB_", val)), envir = asNamespace("AMR"))
} else if (val %in% AB_lookup$ab) {
# separate drugs, such as `AMX`
val <- as.ab(val)
} else {
stop_("unknown antimicrobial agent (group) in EUCAST rules file: ", val, call = FALSE)
}
x_new <- c(x_new, val)
}
x_new <- unique(x_new)
out <- cols_ab[match(x_new, names(cols_ab))]
out[!is.na(out)]
}
get_antibiotic_names <- function(x) {
x <- x %pm>%
strsplit(",") %pm>%
@ -580,6 +566,7 @@ eucast_rules <- function(x,
(reference.rule_group %like% "expert" & reference.version == version_expertrules))
}
# filter out AmpC de-repressed cephalosporin-resistant mutants ----
# no need to filter on version number here - the rules contain these version number, so are inherently filtered
# cefotaxime, ceftriaxone, ceftazidime
if (is.null(ampc_cephalosporin_resistance) || isFALSE(ampc_cephalosporin_resistance)) {
eucast_rules_df <- subset(eucast_rules_df,
@ -720,7 +707,7 @@ eucast_rules <- function(x,
rows <- tryCatch(which(x[, if_mo_property, drop = TRUE] %like% mo_value),
error = function(e) integer(0))
} else {
source_antibiotics <- get_antibiotic_columns(source_antibiotics, cols_ab)
source_antibiotics <- get_ab_from_namespace(source_antibiotics, cols_ab)
if (length(source_value) == 1 & length(source_antibiotics) > 1) {
source_value <- rep(source_value, length(source_antibiotics))
}
@ -748,7 +735,7 @@ eucast_rules <- function(x,
}
}
cols <- get_antibiotic_columns(target_antibiotics, cols_ab)
cols <- get_ab_from_namespace(target_antibiotics, cols_ab)
# Apply rule on data ------------------------------------------------------
# this will return the unique number of changes

View File

@ -238,7 +238,7 @@ first_isolate <- function(x = NULL,
meet_criteria(testcodes_exclude, allow_class = "character", allow_NULL = TRUE)
meet_criteria(icu_exclude, allow_class = "logical", has_length = 1)
meet_criteria(specimen_group, allow_class = "character", has_length = 1, allow_NULL = TRUE)
meet_criteria(type, allow_class = "character", has_length = 1)
meet_criteria(type, allow_class = "character", has_length = 1, is_in = c("points", "keyantimicrobials"))
meet_criteria(ignore_I, allow_class = "logical", has_length = 1)
meet_criteria(points_threshold, allow_class = c("numeric", "integer"), has_length = 1, is_positive = TRUE, is_finite = TRUE)
meet_criteria(info, allow_class = "logical", has_length = 1)
@ -250,7 +250,8 @@ first_isolate <- function(x = NULL,
any_col_contains_rsi <- any(vapply(FUN.VALUE = logical(1),
X = x,
FUN = function(x) any(as.character(x) %in% c("R", "S", "I"), na.rm = TRUE),
# check only first 10,000 rows
FUN = function(x) any(as.character(x[1:10000]) %in% c("R", "S", "I"), na.rm = TRUE),
USE.NAMES = FALSE))
if (method == "phenotype-based" & !any_col_contains_rsi) {
method <- "episode-based"
@ -443,17 +444,6 @@ first_isolate <- function(x = NULL,
!is.na(x$newvar_mo)), , drop = FALSE])
# Analysis of first isolate ----
x$other_pat_or_mo <- ifelse(x$newvar_patient_id == pm_lag(x$newvar_patient_id) &
x$newvar_genus_species == pm_lag(x$newvar_genus_species),
FALSE,
TRUE)
x$episode_group <- paste(x$newvar_patient_id, x$newvar_genus_species)
x$more_than_episode_ago <- unlist(lapply(split(x$newvar_date,
x$episode_group),
is_new_episode,
episode_days = episode_days),
use.names = FALSE)
if (!is.null(col_keyantimicrobials)) {
if (info == TRUE & message_not_thrown_before("first_isolate.type")) {
if (type == "keyantimicrobials") {
@ -470,23 +460,38 @@ first_isolate <- function(x = NULL,
as_note = FALSE)
}
}
type_param <- type
}
x$other_pat_or_mo <- ifelse(x$newvar_patient_id == pm_lag(x$newvar_patient_id) &
x$newvar_genus_species == pm_lag(x$newvar_genus_species),
FALSE,
TRUE)
x$episode_group <- paste(x$newvar_patient_id, x$newvar_genus_species)
x$more_than_episode_ago <- unlist(lapply(split(x$newvar_date,
x$episode_group),
exec_episode, # this will skip meet_criteria() in is_new_episode(), saving time
type = "logical",
episode_days = episode_days),
use.names = FALSE)
if (!is.null(col_keyantimicrobials)) {
# with key antibiotics
x$other_key_ab <- !antimicrobials_equal(y = x$newvar_key_ab,
z = pm_lag(x$newvar_key_ab),
type = type_param,
type = type,
ignore_I = ignore_I,
points_threshold = points_threshold)
# with key antibiotics
x$newvar_first_isolate <- pm_if_else(x$newvar_row_index_sorted >= row.start &
x$newvar_row_index_sorted <= row.end &
x$newvar_genus_species != "" &
(x$other_pat_or_mo | x$more_than_episode_ago | x$other_key_ab),
TRUE,
FALSE)
} else {
# no key antibiotics
x1 <<- x$other_pat_or_mo
x2 <<- x$more_than_episode_ago
x$newvar_first_isolate <- pm_if_else(x$newvar_row_index_sorted >= row.start &
x$newvar_row_index_sorted <= row.end &
x$newvar_genus_species != "" &
@ -566,7 +571,7 @@ first_isolate <- function(x = NULL,
}
# arrange back according to original sorting again
x <- x[order(x$newvar_row_index), ]
x <- x[order(x$newvar_row_index), , drop = FALSE]
rownames(x) <- NULL
if (info == TRUE) {

View File

@ -40,6 +40,10 @@ EUCAST_VERSION_EXPERT_RULES <- list("3.1" = list(version_txt = "v3.1",
"3.2" = list(version_txt = "v3.2",
year = 2020,
title = "'EUCAST Expert Rules' and 'EUCAST Intrinsic Resistance and Unusual Phenotypes'",
url = "https://www.eucast.org/expert_rules_and_intrinsic_resistance/"),
"3.3" = list(version_txt = "v3.3",
year = 2021,
title = "'EUCAST Expert Rules' and 'EUCAST Intrinsic Resistance and Unusual Phenotypes'",
url = "https://www.eucast.org/expert_rules_and_intrinsic_resistance/"))
SNOMED_VERSION <- list(title = "Public Health Information Network Vocabulary Access and Distribution System (PHIN VADS)",

View File

@ -293,6 +293,28 @@ get_column_abx <- function(x,
out
}
get_ab_from_namespace <- function(x, cols_ab) {
# cols_ab comes from get_column_abx()
x <- trimws(unique(toupper(unlist(strsplit(x, ",")))))
x_new <- character()
for (val in x) {
if (paste0("AB_", val) %in% ls(envir = asNamespace("AMR"))) {
# antibiotic group names, as defined in data-raw/_internals.R, such as `AB_CARBAPENEMS`
val <- eval(parse(text = paste0("AB_", val)), envir = asNamespace("AMR"))
} else if (val %in% AB_lookup$ab) {
# separate drugs, such as `AMX`
val <- as.ab(val)
} else {
stop_("unknown antimicrobial agent (group): ", val, call = FALSE)
}
x_new <- c(x_new, val)
}
x_new <- unique(x_new)
out <- cols_ab[match(x_new, names(cols_ab))]
out[!is.na(out)]
}
generate_warning_abs_missing <- function(missing, any = FALSE) {
missing <- paste0(missing, " (", ab_name(missing, tolower = TRUE, language = NULL), ")")
if (any == TRUE) {

View File

@ -26,7 +26,7 @@
#' Italicise Taxonomic Families, Genera, Species, Subspecies
#'
#' According to the binomial nomenclature, the lowest four taxonomic levels (family, genus, species, subspecies) should be printed in italic. This function finds taxonomic names within strings and makes them italic.
#' @inheritSection lifecycle Maturing Lifecycle
#' @inheritSection lifecycle Stable Lifecycle
#' @param string a [character] (vector)
#' @param type type of conversion of the taxonomic names, either "markdown" or "ansi", see *Details*
#' @details

View File

@ -250,16 +250,16 @@ generate_antimcrobials_string <- function(df) {
if (NROW(df) == 0) {
return(character(0))
}
out <- tryCatch(
tryCatch({
do.call(paste0,
lapply(as.list(df),
function(x) {
x <- toupper(as.character(x))
x[!x %in% c("R", "S", "I")] <- "."
paste(x)
})),
error = function(e) rep(strrep(".", NCOL(df)), NROW(df)))
out
}))
},
error = function(e) rep(strrep(".", NCOL(df)), NROW(df)))
}
#' @rdname key_antimicrobials
@ -279,10 +279,20 @@ antimicrobials_equal <- function(y,
stop_ifnot(length(y) == length(z), "length of `y` and `z` must be equal")
key2rsi <- function(val) {
as.double(as.rsi(gsub(".", NA_character_, unlist(strsplit(val, "")), fixed = TRUE)))
val <- strsplit(val, "")[[1L]]
val.int <- rep(NA_real_, length(val))
val.int[val == "S"] <- 1
val.int[val == "I"] <- 2
val.int[val == "R"] <- 3
val.int
}
y <- lapply(y, key2rsi)
z <- lapply(z, key2rsi)
# only run on uniques
uniq <- unique(c(y, z))
uniq_list <- lapply(uniq, key2rsi)
names(uniq_list) <- uniq
y <- uniq_list[match(y, names(uniq_list))]
z <- uniq_list[match(z, names(uniq_list))]
determine_equality <- function(a, b, type, points_threshold, ignore_I) {
if (length(a) != length(b)) {

View File

@ -536,6 +536,13 @@ mdro <- function(x = NULL,
only_rsi_columns = only_rsi_columns,
...)
}
if (!"AMP" %in% names(cols_ab) & "AMX" %in% names(cols_ab)) {
# ampicillin column is missing, but amoxicillin is available
if (info == TRUE) {
message_("Using column '", cols_ab[names(cols_ab) == "AMX"], "' as input for ampicillin since many EUCAST rules depend on it.")
}
cols_ab <- c(cols_ab, c(AMP = unname(cols_ab[names(cols_ab) == "AMX"])))
}
# nolint start
AMC <- cols_ab["AMC"]
@ -738,7 +745,8 @@ mdro <- function(x = NULL,
x[rows, "columns_nonsusceptible"] <<- vapply(FUN.VALUE = character(1),
rows,
function(row, group_vct = cols) {
cols_nonsus <- vapply(FUN.VALUE = logical(1), x[row, group_vct, drop = FALSE],
cols_nonsus <- vapply(FUN.VALUE = logical(1),
x[row, group_vct, drop = FALSE],
function(y) y %in% search_result)
paste(sort(c(unlist(strsplit(x[row, "columns_nonsusceptible", drop = TRUE], ", ")),
names(cols_nonsus)[cols_nonsus])),
@ -752,17 +760,20 @@ mdro <- function(x = NULL,
}
x_transposed <- as.list(as.data.frame(t(x[, cols, drop = FALSE]),
stringsAsFactors = FALSE))
row_filter <- vapply(FUN.VALUE = logical(1), x_transposed, function(y) search_function(y %in% search_result, na.rm = TRUE))
row_filter <- x[which(row_filter), "row_number", drop = TRUE]
rows <- rows[rows %in% row_filter]
x[rows, "MDRO"] <<- to
x[rows, "reason"] <<- paste0(any_all,
" of the required antibiotics ",
ifelse(any_all == "any", "is", "are"),
" R",
ifelse(!isTRUE(combine_SI), " or I", ""))
rows_affected <- vapply(FUN.VALUE = logical(1),
x_transposed,
function(y) search_function(y %in% search_result, na.rm = TRUE))
rows_affected <- x[which(rows_affected), "row_number", drop = TRUE]
rows_to_change <- rows[rows %in% rows_affected]
x[rows_to_change, "MDRO"] <<- to
x[rows_to_change, "reason"] <<- paste0(any_all,
" of the required antibiotics ",
ifelse(any_all == "any", "is", "are"),
" R",
ifelse(!isTRUE(combine_SI), " or I", ""))
}
}
trans_tbl2 <- function(txt, rows, lst) {
if (info == TRUE) {
message_(txt, "...", appendLF = FALSE, as_note = FALSE)
@ -1382,16 +1393,6 @@ mdro <- function(x = NULL,
x$reason <- "PDR/MDR/XDR criteria were met"
}
if (info.bak == TRUE) {
cat(group_msg)
if (sum(!is.na(x$MDRO)) == 0) {
cat(font_bold(paste0("=> Found 0 MDROs since no isolates are covered by the guideline")))
} else {
cat(font_bold(paste0("=> Found ", sum(x$MDRO %in% c(2:5), na.rm = TRUE), " ", guideline$type, " out of ", sum(!is.na(x$MDRO)),
" isolates (", trimws(percentage(sum(x$MDRO %in% c(2:5), na.rm = TRUE) / sum(!is.na(x$MDRO)))), ")\n")))
}
}
# some more info on negative results
if (verbose == TRUE) {
if (guideline$code == "cmi2012") {
@ -1406,6 +1407,31 @@ mdro <- function(x = NULL,
}
}
if (info.bak == TRUE) {
cat(group_msg)
if (sum(!is.na(x$MDRO)) == 0) {
cat(font_bold(paste0("=> Found 0 MDROs since no isolates are covered by the guideline")))
} else {
cat(font_bold(paste0("=> Found ", sum(x$MDRO %in% c(2:5), na.rm = TRUE), " ", guideline$type, " out of ", sum(!is.na(x$MDRO)),
" isolates (", trimws(percentage(sum(x$MDRO %in% c(2:5), na.rm = TRUE) / sum(!is.na(x$MDRO)))), ")")))
}
}
# Fill in blanks ----
# for rows that have no results
x_transposed <- as.list(as.data.frame(t(x[, cols_ab, drop = FALSE]),
stringsAsFactors = FALSE))
rows_empty <- which(vapply(FUN.VALUE = logical(1),
x_transposed,
function(y) all(is.na(y))))
if (length(rows_empty) > 0) {
cat(font_italic(paste0(" (", length(rows_empty), " isolates had no test results)\n")))
x[rows_empty, "MDRO"] <- NA
x[rows_empty, "reason"] <- "none of the antibiotics have test results"
} else {
cat("\n")
}
# Results ----
if (guideline$code == "cmi2012") {
if (any(x$MDRO == -1, na.rm = TRUE)) {

44
R/mic.R
View File

@ -23,9 +23,26 @@
# how to conduct AMR data analysis: https://msberends.github.io/AMR/ #
# ==================================================================== #
# these are allowed MIC values and will become [factor] levels
ops <- c("<", "<=", "", ">=", ">")
valid_mic_levels <- c(c(t(vapply(FUN.VALUE = character(9), ops,
function(x) paste0(x, "0.00", 1:9)))),
unique(c(t(vapply(FUN.VALUE = character(104), ops,
function(x) paste0(x, sort(as.double(paste0("0.0",
sort(c(1:99, 125, 128, 256, 512, 625)))))))))),
unique(c(t(vapply(FUN.VALUE = character(103), ops,
function(x) paste0(x, sort(as.double(paste0("0.",
c(1:99, 125, 128, 256, 512))))))))),
c(t(vapply(FUN.VALUE = character(10), ops,
function(x) paste0(x, sort(c(1:9, 1.5)))))),
c(t(vapply(FUN.VALUE = character(45), ops,
function(x) paste0(x, c(10:98)[9:98 %% 2 == TRUE])))),
c(t(vapply(FUN.VALUE = character(15), ops,
function(x) paste0(x, sort(c(2 ^ c(7:10), 80 * c(2:12))))))))
#' Transform Input to Minimum Inhibitory Concentrations (MIC)
#'
#' This ransforms vectors to a new class [`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.
#' This transforms vectors to a new class [`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.
#' @inheritSection lifecycle Stable Lifecycle
#' @rdname as.mic
#' @param x a [character] or [numeric] vector
@ -117,6 +134,8 @@ as.mic <- function(x, na.rm = FALSE) {
# transform Unicode for >= and <=
x <- gsub("\u2264", "<=", x, fixed = TRUE)
x <- gsub("\u2265", ">=", x, fixed = TRUE)
# remove other invalid characters
x <- gsub("[^a-zA-Z0-9.><= ]+", "", x, perl = TRUE)
# remove space between operator and number ("<= 0.002" -> "<=0.002")
x <- gsub("(<|=|>) +", "\\1", x, perl = TRUE)
# transform => to >= and =< to <=
@ -141,27 +160,14 @@ as.mic <- function(x, na.rm = FALSE) {
x[x %like% "[.]"] <- gsub("0+$", "", x[x %like% "[.]"])
# never end with dot
x <- gsub("[.]$", "", x, perl = TRUE)
# force to be character
x <- as.character(x)
# trim it
x <- trimws(x)
## previously unempty values now empty - should return a warning later on
x[x.bak != "" & x == ""] <- "invalid"
# these are allowed MIC values and will become [factor] levels
ops <- c("<", "<=", "", ">=", ">")
lvls <- c(c(t(vapply(FUN.VALUE = character(9), ops, function(x) paste0(x, "0.00", 1:9)))),
unique(c(t(vapply(FUN.VALUE = character(104), ops, function(x) paste0(x, sort(as.double(paste0("0.0",
sort(c(1:99, 125, 128, 256, 512, 625)))))))))),
unique(c(t(vapply(FUN.VALUE = character(103), ops, function(x) paste0(x, sort(as.double(paste0("0.",
c(1:99, 125, 128, 256, 512))))))))),
c(t(vapply(FUN.VALUE = character(10), ops, function(x) paste0(x, sort(c(1:9, 1.5)))))),
c(t(vapply(FUN.VALUE = character(45), ops, function(x) paste0(x, c(10:98)[9:98 %% 2 == TRUE])))),
c(t(vapply(FUN.VALUE = character(15), ops, function(x) paste0(x, sort(c(2 ^ c(7:10), 80 * c(2:12))))))))
na_before <- x[is.na(x) | x == ""] %pm>% length()
x[!x %in% lvls] <- NA
x[!x %in% valid_mic_levels] <- NA
na_after <- x[is.na(x) | x == ""] %pm>% length()
if (na_before != na_after) {
@ -175,7 +181,7 @@ as.mic <- function(x, na.rm = FALSE) {
list_missing, call = FALSE)
}
set_clean_class(factor(x, levels = lvls, ordered = TRUE),
set_clean_class(factor(x, levels = valid_mic_levels, ordered = TRUE),
new_class = c("mic", "ordered", "factor"))
}
}
@ -189,6 +195,12 @@ all_valid_mics <- function(x) {
!any(is.na(x_mic)) && !all(is.na(x))
}
#' @rdname as.mic
#' @details `NA_mic_` is a missing value of the new `<mic>` class.
#' @export
NA_mic_ <- set_clean_class(factor(NA, levels = valid_mic_levels, ordered = TRUE),
new_class = c("mic", "ordered", "factor"))
#' @rdname as.mic
#' @export
is.mic <- function(x) {

View File

@ -26,7 +26,7 @@
#' Plotting for Classes `rsi`, `mic` and `disk`
#'
#' Functions to plot classes `rsi`, `mic` and `disk`, with support for base \R and `ggplot2`.
#' @inheritSection lifecycle Maturing Lifecycle
#' @inheritSection lifecycle Stable Lifecycle
#' @inheritSection AMR Read more on Our Website!
#' @param x,object values created with [as.mic()], [as.disk()] or [as.rsi()] (or their `random_*` variants, such as [random_mic()])
#' @param mo any (vector of) text that can be coerced to a valid microorganism code with [as.mo()]

35
R/rsi.R
View File

@ -188,6 +188,12 @@ as.rsi <- function(x, ...) {
UseMethod("as.rsi")
}
#' @rdname as.rsi
#' @details `NA_rsi_` is a missing value of the new `<rsi>` class.
#' @export
NA_rsi_ <- set_clean_class(factor(NA, levels = c("S", "I", "R"), ordered = TRUE),
new_class = c("rsi", "ordered", "factor"))
#' @rdname as.rsi
#' @export
is.rsi <- function(x) {
@ -257,12 +263,12 @@ as.rsi.default <- function(x, ...) {
return(x)
}
if (inherits(x, c("integer", "numeric", "double")) && all(x %in% c(1:3, NA))) {
x.bak <- x
x <- as.character(x) # this is needed to prevent the vctrs pkg from throwing an error
x.bak <- x
x <- as.character(x) # this is needed to prevent the vctrs pkg from throwing an error
if (inherits(x.bak, c("integer", "numeric", "double")) && all(x %in% c(1:3, NA))) {
# support haven package for importing e.g., from SPSS - it adds the 'labels' attribute
lbls <- attributes(x)$labels
lbls <- attributes(x.bak)$labels
if (!is.null(lbls) && all(c("R", "S", "I") %in% names(lbls)) && all(c(1:3) %in% lbls)) {
x[x.bak == 1] <- names(lbls[lbls == 1])
x[x.bak == 2] <- names(lbls[lbls == 2])
@ -278,9 +284,9 @@ as.rsi.default <- function(x, ...) {
if (all(x %unlike% "(R|S|I)", na.rm = TRUE)) {
# check if they are actually MICs or disks
if (all_valid_mics(x)) {
warning_("The input seems to be MIC values. Transform them with `as.mic()` before running `as.rsi()` to interpret them.")
warning_("The input seems to contain MIC values. You can transform them with `as.mic()` before running `as.rsi()` to interpret them.", call = FALSE)
} else if (all_valid_disks(x)) {
warning_("The input seems to be disk diffusion values. Transform them with `as.disk()` before running `as.rsi()` to interpret them.")
warning_("The input seems to contain disk diffusion values. You can transform them with `as.disk()` before running `as.rsi()` to interpret them.", call = FALSE)
}
}
@ -303,26 +309,17 @@ as.rsi.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 all spaces
x <- gsub(" +", "", x)
# remove all MIC-like values: numbers, operators and periods
x <- gsub("[0-9.,;:<=>]+", "", x)
# remove everything between brackets, and 'high' and 'low'
x <- gsub("([(].*[)])", "", x)
x <- gsub("(high|low)", "", x, ignore.case = TRUE)
# remove other invalid characters
x <- gsub("[^rsiRSIHi]+", "", x, perl = TRUE)
# some labs now report "H" instead of "I" to not interfere with EUCAST prior to 2019
x <- gsub("H", "I", x, ignore.case = TRUE)
# disallow more than 3 characters
x[nchar(x) > 3] <- NA
# set to capitals
x <- toupper(x)
# remove all invalid characters
x <- gsub("[^RSI]+", "", x)
# 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
x[!x %in% c("S", "I", "R")] <- NA_character_
na_after <- length(x[is.na(x) | x == ""])
if (!isFALSE(list(...)$warn)) { # so as.rsi(..., warn = FALSE) will never throw a warning

View File

@ -344,6 +344,7 @@ rsi_calc_df <- function(type, # "proportion", "count" or "both"
}
rownames(out) <- NULL
class(out) <- c("rsi_df", class(out))
out
}

Binary file not shown.