mirror of
https://github.com/msberends/AMR.git
synced 2025-07-08 20:41:58 +02:00
(v1.7.1.9000) ab_class update, unit tests
This commit is contained in:
@ -506,7 +506,7 @@ dataset_UTF8_to_ASCII <- function(df) {
|
||||
|
||||
# for eucast_rules() and mdro(), creates markdown output with URLs and names
|
||||
create_eucast_ab_documentation <- function() {
|
||||
x <- trimws(unique(toupper(unlist(strsplit(eucast_rules_file$then_change_these_antibiotics, ",")))))
|
||||
x <- trimws(unique(toupper(unlist(strsplit(EUCAST_RULES_DF$then_change_these_antibiotics, ",")))))
|
||||
ab <- character()
|
||||
for (val in x) {
|
||||
if (val %in% ls(envir = asNamespace("AMR"))) {
|
||||
@ -713,9 +713,10 @@ meet_criteria <- function(object,
|
||||
return(invisible())
|
||||
}
|
||||
|
||||
get_current_data <- function(arg_name, call) {
|
||||
# check if retrieved before, then get it from package environment
|
||||
if (identical(unique_call_id(entire_session = FALSE), pkg_env$get_current_data.call)) {
|
||||
get_current_data <- function(arg_name, call, reuse_equal_call = TRUE) {
|
||||
# check if retrieved before, then get it from package environment to improve speed
|
||||
if (reuse_equal_call == TRUE &&
|
||||
identical(unique_call_id(entire_session = FALSE), pkg_env$get_current_data.call)) {
|
||||
return(pkg_env$get_current_data.out)
|
||||
}
|
||||
|
||||
@ -735,9 +736,10 @@ get_current_data <- function(arg_name, call) {
|
||||
|
||||
if (getRversion() < "3.2") {
|
||||
# R-3.0 and R-3.1 do not have an `x` element in the call stack, rendering this function useless
|
||||
# R-3.2 was released in April 2015
|
||||
if (is.na(arg_name)) {
|
||||
# like in carbapenems() etc.
|
||||
warning_("this function can only be used in R >= 3.2", call = call)
|
||||
# such as for carbapenems() etc.
|
||||
warning_("this function requires R version 3.2 or later - you have ", R.version.string, call = call)
|
||||
return(data.frame())
|
||||
} else {
|
||||
# mimic a default R error, e.g. for example_isolates[which(mo_name() %like% "^ent"), ]
|
||||
|
6
R/ab.R
6
R/ab.R
@ -325,9 +325,9 @@ as.ab <- function(x, flag_multiple_results = TRUE, info = interactive(), ...) {
|
||||
function(y) {
|
||||
for (i in seq_len(length(y))) {
|
||||
for (lang in LANGUAGES_SUPPORTED[LANGUAGES_SUPPORTED != "en"]) {
|
||||
y[i] <- ifelse(tolower(y[i]) %in% tolower(translations_file[, lang, drop = TRUE]),
|
||||
translations_file[which(tolower(translations_file[, lang, drop = TRUE]) == tolower(y[i]) &
|
||||
!isFALSE(translations_file$fixed)), "pattern"],
|
||||
y[i] <- ifelse(tolower(y[i]) %in% tolower(TRANSLATIONS[, lang, drop = TRUE]),
|
||||
TRANSLATIONS[which(tolower(TRANSLATIONS[, lang, drop = TRUE]) == tolower(y[i]) &
|
||||
!isFALSE(TRANSLATIONS$fixed)), "pattern"],
|
||||
y[i])
|
||||
}
|
||||
}
|
||||
|
@ -25,18 +25,19 @@
|
||||
|
||||
#' Antibiotic Class Selectors
|
||||
#'
|
||||
#' These functions help to filter and select columns with antibiotic test results that are of a specific antibiotic class, without the need to define the columns or antibiotic abbreviations. \strong{\Sexpr{ifelse(getRversion() < "3.2", paste0("NOTE: THESE FUNCTIONS DO NOT WORK ON YOUR CURRENT R VERSION. These functions require R version 3.2 or later - you have ", R.version.string, "."), "")}}
|
||||
#' These functions allow for filtering rows and selecting columns based on antibiotic test results that are of a specific antibiotic class, without the need to define the columns or antibiotic abbreviations. \strong{\Sexpr{ifelse(getRversion() < "3.2", paste0("NOTE: THESE FUNCTIONS DO NOT WORK ON YOUR CURRENT R VERSION. These functions require R version 3.2 or later - you have ", R.version.string, "."), "")}}
|
||||
#' @inheritSection lifecycle Stable Lifecycle
|
||||
#' @param ab_class an antimicrobial class, such as `"carbapenems"`. The columns `group`, `atc_group1` and `atc_group2` of the [antibiotics] data set will be searched (case-insensitive) for this value.
|
||||
#' @param only_rsi_columns a [logical] to indicate whether only columns of class `<rsi>` must be selected (defaults to `FALSE`), see [as.rsi()]
|
||||
#' @details \strong{\Sexpr{ifelse(getRversion() < "3.2", paste0("NOTE: THESE FUNCTIONS DO NOT WORK ON YOUR CURRENT R VERSION. These functions require R version 3.2 or later - you have ", R.version.string, "."), "")}}
|
||||
#'
|
||||
#'
|
||||
#' These functions can be used in data set calls for selecting columns and filtering rows, see *Examples*. They support base R, but work more convenient in dplyr functions such as [`select()`][dplyr::select()], [`filter()`][dplyr::filter()] and [`summarise()`][dplyr::summarise()].
|
||||
#'
|
||||
#' All columns in the data in which these functions are called will be searched for known antibiotic names, abbreviations, brand names, and codes (ATC, EARS-Net, WHO, etc.) in the [antibiotics] data set. This means that a selector like e.g. [aminoglycosides()] will pick up column names like 'gen', 'genta', 'J01GB03', 'tobra', 'Tobracin', etc.
|
||||
#' All columns in the data in which these functions are called will be searched for known antibiotic names, abbreviations, brand names, and codes (ATC, EARS-Net, WHO, etc.) in the [antibiotics] data set. This means that a selector such as [aminoglycosides()] will pick up column names like 'gen', 'genta', 'J01GB03', 'tobra', 'Tobracin', etc. Use the [ab_class()] function to filter/select on a manually defined antibiotic class.
|
||||
#'
|
||||
#' The group of betalactams consists of all carbapenems, cephalosporins and penicillins.
|
||||
#' @section Full list of supported agents:
|
||||
#'
|
||||
#' `r paste0("* ", sapply(c("AMINOGLYCOSIDES", "AMINOPENICILLINS", "BETALACTAMS", "CARBAPENEMS", "CEPHALOSPORINS", "CEPHALOSPORINS_1ST", "CEPHALOSPORINS_2ND", "CEPHALOSPORINS_3RD", "CEPHALOSPORINS_4TH", "CEPHALOSPORINS_5TH", "FLUOROQUINOLONES", "GLYCOPEPTIDES", "LINCOSAMIDES", "LIPOGLYCOPEPTIDES", "MACROLIDES", "OXAZOLIDINONES", "PENICILLINS", "POLYMYXINS", "STREPTOGRAMINS", "QUINOLONES", "TETRACYCLINES", "UREIDOPENICILLINS"), function(x) paste0("``", tolower(x), "()`` can select ", vector_and(paste0(ab_name(eval(parse(text = x), envir = asNamespace("AMR")), language = NULL, tolower = TRUE), " (", eval(parse(text = x), envir = asNamespace("AMR")), ")"), quotes = FALSE))), "\n", collapse = "")`
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @name antibiotic_class_selectors
|
||||
#' @export
|
||||
@ -46,7 +47,7 @@
|
||||
#' # `example_isolates` is a data set available in the AMR package.
|
||||
#' # See ?example_isolates.
|
||||
#'
|
||||
#' # Base R ------------------------------------------------------------------
|
||||
#' # base R ------------------------------------------------------------------
|
||||
#'
|
||||
#' # select columns 'IPM' (imipenem) and 'MEM' (meropenem)
|
||||
#' example_isolates[, carbapenems()]
|
||||
@ -104,7 +105,6 @@
|
||||
#' example_isolates %>%
|
||||
#' select(mo, ab_class("mycobact"))
|
||||
#'
|
||||
#'
|
||||
#' # get bug/drug combinations for only macrolides in Gram-positives:
|
||||
#' example_isolates %>%
|
||||
#' filter(mo_is_gram_positive()) %>%
|
||||
@ -112,14 +112,12 @@
|
||||
#' bug_drug_combinations() %>%
|
||||
#' format()
|
||||
#'
|
||||
#'
|
||||
#' data.frame(some_column = "some_value",
|
||||
#' J01CA01 = "S") %>% # ATC code of ampicillin
|
||||
#' select(penicillins()) # only the 'J01CA01' column will be selected
|
||||
#'
|
||||
#'
|
||||
#' # with dplyr 1.0.0 and higher (that adds 'across()'), this is all equal:
|
||||
#' # (though the row names on the first are more correct)
|
||||
#' example_isolates[carbapenems() == "R", ]
|
||||
#' example_isolates %>% filter(carbapenems() == "R")
|
||||
#' example_isolates %>% filter(across(carbapenems(), ~.x == "R"))
|
||||
@ -127,138 +125,193 @@
|
||||
#' }
|
||||
ab_class <- function(ab_class,
|
||||
only_rsi_columns = FALSE) {
|
||||
ab_selector(ab_class, function_name = "ab_class", only_rsi_columns = only_rsi_columns)
|
||||
meet_criteria(ab_class, allow_class = "character", has_length = 1)
|
||||
ab_selector(NULL, only_rsi_columns = only_rsi_columns, ab_class = ab_class)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
aminoglycosides <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("aminoglycoside", function_name = "aminoglycosides", only_rsi_columns = only_rsi_columns)
|
||||
ab_selector("aminoglycosides", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
aminopenicillins <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("aminopenicillins", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
betalactams <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("carbapenem|cephalosporin|penicillin", function_name = "betalactams", only_rsi_columns = only_rsi_columns)
|
||||
ab_selector("betalactams", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
carbapenems <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("carbapenem", function_name = "carbapenems", only_rsi_columns = only_rsi_columns)
|
||||
ab_selector("carbapenems", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
cephalosporins <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("cephalosporin", function_name = "cephalosporins", only_rsi_columns = only_rsi_columns)
|
||||
ab_selector("cephalosporins", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
cephalosporins_1st <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("cephalosporins.*1", function_name = "cephalosporins_1st", only_rsi_columns = only_rsi_columns)
|
||||
ab_selector("cephalosporins_1st", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
cephalosporins_2nd <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("cephalosporins.*2", function_name = "cephalosporins_2nd", only_rsi_columns = only_rsi_columns)
|
||||
ab_selector("cephalosporins_2nd", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
cephalosporins_3rd <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("cephalosporins.*3", function_name = "cephalosporins_3rd", only_rsi_columns = only_rsi_columns)
|
||||
ab_selector("cephalosporins_3rd", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
cephalosporins_4th <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("cephalosporins.*4", function_name = "cephalosporins_4th", only_rsi_columns = only_rsi_columns)
|
||||
ab_selector("cephalosporins_4th", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
cephalosporins_5th <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("cephalosporins.*5", function_name = "cephalosporins_5th", only_rsi_columns = only_rsi_columns)
|
||||
ab_selector("cephalosporins_5th", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
fluoroquinolones <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("fluoroquinolone", function_name = "fluoroquinolones", only_rsi_columns = only_rsi_columns)
|
||||
ab_selector("fluoroquinolones", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
glycopeptides <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("glycopeptide", function_name = "glycopeptides", only_rsi_columns = only_rsi_columns)
|
||||
ab_selector("glycopeptides", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
lincosamides <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("lincosamides", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
lipoglycopeptides <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("lipoglycopeptides", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
macrolides <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("macrolide", function_name = "macrolides", only_rsi_columns = only_rsi_columns)
|
||||
ab_selector("macrolides", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
oxazolidinones <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("oxazolidinone", function_name = "oxazolidinones", only_rsi_columns = only_rsi_columns)
|
||||
ab_selector("oxazolidinones", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
penicillins <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("penicillin", function_name = "penicillins", only_rsi_columns = only_rsi_columns)
|
||||
ab_selector("penicillins", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
polymyxins <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("polymyxins", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
streptogramins <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("streptogramins", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
quinolones <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("quinolones", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
tetracyclines <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("tetracycline", function_name = "tetracyclines", only_rsi_columns = only_rsi_columns)
|
||||
ab_selector("tetracyclines", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
ab_selector <- function(ab_class,
|
||||
function_name,
|
||||
only_rsi_columns) {
|
||||
meet_criteria(ab_class, allow_class = "character", has_length = 1, .call_depth = 1)
|
||||
meet_criteria(function_name, allow_class = "character", has_length = 1, .call_depth = 1)
|
||||
#' @rdname antibiotic_class_selectors
|
||||
#' @export
|
||||
ureidopenicillins <- function(only_rsi_columns = FALSE) {
|
||||
ab_selector("ureidopenicillins", only_rsi_columns = only_rsi_columns)
|
||||
}
|
||||
|
||||
ab_selector <- function(function_name,
|
||||
only_rsi_columns,
|
||||
ab_class = NULL) {
|
||||
meet_criteria(function_name, allow_class = "character", has_length = 1, allow_NULL = TRUE, .call_depth = 1)
|
||||
meet_criteria(only_rsi_columns, allow_class = "logical", has_length = 1, .call_depth = 1)
|
||||
meet_criteria(ab_class, allow_class = "character", has_length = 1, allow_NULL = TRUE, .call_depth = 1)
|
||||
|
||||
if (getRversion() < "3.2") {
|
||||
# get_current_data() does not work on R 3.0 and R 3.1.
|
||||
# R 3.2 was released in April 2015.
|
||||
warning_("antibiotic class selectors such as ", function_name,
|
||||
"() require R version 3.2 or later - you have ", R.version.string,
|
||||
call = FALSE)
|
||||
return(NULL)
|
||||
}
|
||||
|
||||
# to improve speed, get_current_data() and get_column_abx() only run once when e.g. in a select or group call
|
||||
vars_df <- get_current_data(arg_name = NA, call = -3)
|
||||
# get_current_data() has to run each time, for cases where e.g., filter() and select() are used in same call
|
||||
vars_df <- get_current_data(arg_name = NA, call = -3, reuse_equal_call = FALSE)
|
||||
# to improve speed, get_column_abx() will only run once when e.g. in a select or group call
|
||||
ab_in_data <- get_column_abx(vars_df, info = FALSE, only_rsi_columns = only_rsi_columns, sort = FALSE)
|
||||
|
||||
if (length(ab_in_data) == 0) {
|
||||
message_("No antimicrobial agents found.")
|
||||
message_("No antimicrobial agents found in the data.")
|
||||
return(NULL)
|
||||
}
|
||||
|
||||
ab_reference <- subset(antibiotics,
|
||||
group %like% ab_class |
|
||||
atc_group1 %like% ab_class |
|
||||
atc_group2 %like% ab_class)
|
||||
ab_group <- find_ab_group(ab_class)
|
||||
if (ab_group == "") {
|
||||
ab_group <- paste0("'", ab_class, "'")
|
||||
examples <- ""
|
||||
if (is.null(ab_class)) {
|
||||
# their upper case equivalent are vectors with class <ab>, created in data-raw/_internals.R
|
||||
abx <- get(toupper(function_name), envir = asNamespace("AMR"))
|
||||
ab_group <- function_name
|
||||
examples <- paste0(" (such as ", vector_or(ab_name(sample(abx, size = min(2, length(abx)), replace = FALSE),
|
||||
tolower = TRUE,
|
||||
language = NULL),
|
||||
quotes = FALSE), ")")
|
||||
} else {
|
||||
# this for the 'manual' ab_class() function
|
||||
abx <- subset(AB_lookup,
|
||||
group %like% ab_class |
|
||||
atc_group1 %like% ab_class |
|
||||
atc_group2 %like% ab_class)$ab
|
||||
ab_group <- find_ab_group(ab_class)
|
||||
function_name <- "ab_class"
|
||||
examples <- paste0(" (such as ", find_ab_names(ab_class, 2), ")")
|
||||
}
|
||||
|
||||
# get the columns with a group names in the chosen ab class
|
||||
agents <- ab_in_data[names(ab_in_data) %in% ab_reference$ab]
|
||||
agents <- ab_in_data[names(ab_in_data) %in% abx]
|
||||
|
||||
if (message_not_thrown_before(function_name)) {
|
||||
if (length(agents) == 0) {
|
||||
message_("No antimicrobial agents of class ", ab_group, " found", examples, ".")
|
||||
message_("No antimicrobial agents of class '", ab_group, "' found", examples, ".")
|
||||
} else {
|
||||
agents_formatted <- paste0("'", font_bold(agents, collapse = NULL), "'")
|
||||
agents_names <- ab_name(names(agents), tolower = TRUE, language = NULL)
|
||||
@ -423,28 +476,16 @@ is_all <- function(el1) {
|
||||
|
||||
|
||||
find_ab_group <- function(ab_class) {
|
||||
ab_class[ab_class == "carbapenem|cephalosporin|penicillin"] <- "betalactam"
|
||||
ab_class <- gsub("[^a-zA-Z0-9]", ".*", ab_class)
|
||||
ifelse(ab_class %in% c("aminoglycoside",
|
||||
"betalactam",
|
||||
"carbapenem",
|
||||
"cephalosporin",
|
||||
"fluoroquinolone",
|
||||
"glycopeptide",
|
||||
"macrolide",
|
||||
"oxazolidinone",
|
||||
"tetracycline"),
|
||||
paste0(ab_class, "s"),
|
||||
antibiotics %pm>%
|
||||
subset(group %like% ab_class |
|
||||
atc_group1 %like% ab_class |
|
||||
atc_group2 %like% ab_class) %pm>%
|
||||
pm_pull(group) %pm>%
|
||||
unique() %pm>%
|
||||
tolower() %pm>%
|
||||
sort() %pm>%
|
||||
paste(collapse = "/")
|
||||
)
|
||||
AB_lookup %pm>%
|
||||
subset(group %like% ab_class |
|
||||
atc_group1 %like% ab_class |
|
||||
atc_group2 %like% ab_class) %pm>%
|
||||
pm_pull(group) %pm>%
|
||||
unique() %pm>%
|
||||
tolower() %pm>%
|
||||
sort() %pm>%
|
||||
paste(collapse = "/")
|
||||
}
|
||||
|
||||
find_ab_names <- function(ab_group, n = 3) {
|
||||
@ -462,6 +503,9 @@ find_ab_names <- function(ab_group, n = 3) {
|
||||
antibiotics$atc_group2 %like% ab_group) &
|
||||
antibiotics$ab %unlike% "[0-9]$"), ]$name
|
||||
}
|
||||
if (length(drugs) == 0) {
|
||||
return("??")
|
||||
}
|
||||
vector_or(ab_name(sample(drugs, size = min(n, length(drugs)), replace = FALSE),
|
||||
tolower = TRUE,
|
||||
language = NULL),
|
||||
|
@ -55,7 +55,7 @@ format_eucast_version_nr <- function(version, markdown = TRUE) {
|
||||
#' @param verbose a [logical] to turn Verbose mode on and off (default is off). In Verbose mode, the function does not apply rules to the data, but instead returns a data set in logbook form with extensive info about which rows and columns would be effected and in which way. Using Verbose mode takes a lot more time.
|
||||
#' @param version_breakpoints the version number to use for the EUCAST Clinical Breakpoints guideline. Can be either `r vector_or(names(EUCAST_VERSION_BREAKPOINTS), reverse = TRUE)`.
|
||||
#' @param version_expertrules the version number to use for the EUCAST Expert Rules and Intrinsic Resistance guideline. Can be either `r vector_or(names(EUCAST_VERSION_EXPERT_RULES), reverse = TRUE)`.
|
||||
#' @param ampc_cephalosporin_resistance a [character] value that should be applied to cefotaxime, ceftriaxone and ceftazidime for AmpC de-repressed cephalosporin-resistant mutants, defaults to `NA`. Currently only works when `version_expertrules` is `3.2`; '*EUCAST Expert Rules v3.2 on Enterobacterales*' states that results of cefotaxime, ceftriaxone and ceftazidime should be reported with a note, or results should be suppressed (emptied) for these three agents. A value of `NA` (the default) for this argument will remove results for these three agents, while e.g. a value of `"R"` will make the results for these agents resistant. Use `NULL` or `FALSE` to not alter results for these three agents of AmpC de-repressed cephalosporin-resistant mutants. Using `TRUE` is equal to using `"R"`. \cr For *EUCAST Expert Rules* v3.2, this rule applies to: `r vector_and(gsub("[^a-zA-Z ]+", "", unlist(strsplit(eucast_rules_file[which(eucast_rules_file$reference.version == 3.2 & eucast_rules_file$reference.rule %like% "ampc"), "this_value"][1], "|", fixed = TRUE))), quotes = "*")`.
|
||||
#' @param ampc_cephalosporin_resistance a [character] value that should be applied to cefotaxime, ceftriaxone and ceftazidime for AmpC de-repressed cephalosporin-resistant mutants, defaults to `NA`. Currently only works when `version_expertrules` is `3.2`; '*EUCAST Expert Rules v3.2 on Enterobacterales*' states that results of cefotaxime, ceftriaxone and ceftazidime should be reported with a note, or results should be suppressed (emptied) for these three agents. A value of `NA` (the default) for this argument will remove results for these three agents, while e.g. a value of `"R"` will make the results for these agents resistant. Use `NULL` or `FALSE` to not alter results for these three agents of AmpC de-repressed cephalosporin-resistant mutants. Using `TRUE` is equal to using `"R"`. \cr For *EUCAST Expert Rules* v3.2, this rule applies to: `r vector_and(gsub("[^a-zA-Z ]+", "", unlist(strsplit(EUCAST_RULES_DF[which(EUCAST_RULES_DF$reference.version == 3.2 & EUCAST_RULES_DF$reference.rule %like% "ampc"), "this_value"][1], "|", fixed = TRUE))), quotes = "*")`.
|
||||
#' @param ... column name of an antibiotic, see section *Antibiotics* below
|
||||
#' @param ab any (vector of) text that can be coerced to a valid antibiotic code with [as.ab()]
|
||||
#' @param administration route of administration, either `r vector_or(dosage$administration)`
|
||||
@ -561,11 +561,11 @@ eucast_rules <- function(x,
|
||||
# Official EUCAST rules ---------------------------------------------------
|
||||
eucast_notification_shown <- FALSE
|
||||
if (!is.null(list(...)$eucast_rules_df)) {
|
||||
# this allows: eucast_rules(x, eucast_rules_df = AMR:::eucast_rules_file %>% filter(is.na(have_these_values)))
|
||||
# this allows: eucast_rules(x, eucast_rules_df = AMR:::EUCAST_RULES_DF %>% filter(is.na(have_these_values)))
|
||||
eucast_rules_df <- list(...)$eucast_rules_df
|
||||
} else {
|
||||
# otherwise internal data file, created in data-raw/_internals.R
|
||||
eucast_rules_df <- eucast_rules_file
|
||||
eucast_rules_df <- EUCAST_RULES_DF
|
||||
}
|
||||
|
||||
# filter on user-set guideline versions ----
|
||||
|
@ -386,15 +386,15 @@ scale_rsi_colours <- function(...,
|
||||
}
|
||||
|
||||
names_susceptible <- c("S", "SI", "IS", "S+I", "I+S", "susceptible", "Susceptible",
|
||||
unique(translations_file[which(translations_file$pattern == "Susceptible"),
|
||||
unique(TRANSLATIONS[which(TRANSLATIONS$pattern == "Susceptible"),
|
||||
"replacement", drop = TRUE]))
|
||||
names_incr_exposure <- c("I", "intermediate", "increased exposure", "incr. exposure", "Increased exposure", "Incr. exposure",
|
||||
unique(translations_file[which(translations_file$pattern == "Intermediate"),
|
||||
unique(TRANSLATIONS[which(TRANSLATIONS$pattern == "Intermediate"),
|
||||
"replacement", drop = TRUE]),
|
||||
unique(translations_file[which(translations_file$pattern == "Incr. exposure"),
|
||||
unique(TRANSLATIONS[which(TRANSLATIONS$pattern == "Incr. exposure"),
|
||||
"replacement", drop = TRUE]))
|
||||
names_resistant <- c("R", "IR", "RI", "R+I", "I+R", "resistant", "Resistant",
|
||||
unique(translations_file[which(translations_file$pattern == "Resistant"),
|
||||
unique(TRANSLATIONS[which(TRANSLATIONS$pattern == "Resistant"),
|
||||
"replacement", drop = TRUE]))
|
||||
|
||||
susceptible <- rep("#3CAEA3", length(names_susceptible))
|
||||
|
2
R/mo.R
2
R/mo.R
@ -469,7 +469,7 @@ exec_as.mo <- function(x,
|
||||
x <- strip_whitespace(x, dyslexia_mode)
|
||||
# translate 'unknown' names back to English
|
||||
if (any(x %like% "unbekannt|onbekend|desconocid|sconosciut|iconnu|desconhecid", na.rm = TRUE)) {
|
||||
trns <- subset(translations_file, pattern %like% "unknown" | affect_mo_name == TRUE)
|
||||
trns <- subset(TRANSLATIONS, pattern %like% "unknown" | affect_mo_name == TRUE)
|
||||
langs <- LANGUAGES_SUPPORTED[LANGUAGES_SUPPORTED != "en"]
|
||||
for (l in langs) {
|
||||
for (i in seq_len(nrow(trns))) {
|
||||
|
BIN
R/sysdata.rda
BIN
R/sysdata.rda
Binary file not shown.
@ -136,7 +136,7 @@ translate_AMR <- function(from,
|
||||
return(from)
|
||||
}
|
||||
|
||||
df_trans <- translations_file # internal data file
|
||||
df_trans <- TRANSLATIONS # internal data file
|
||||
from.bak <- from
|
||||
from_unique <- unique(from)
|
||||
from_unique_translated <- from_unique
|
||||
|
Reference in New Issue
Block a user