diff --git a/.github/workflows/check.yaml b/.github/workflows/check.yaml index 3ae9834f..88dc2760 100644 --- a/.github/workflows/check.yaml +++ b/.github/workflows/check.yaml @@ -32,9 +32,9 @@ on: branches: - master schedule: - # run a schedule everyday at 3 AM. + # run a schedule everyday at 1 AM. # this is to check that all dependencies are still available (see R/zzz.R) - - cron: '0 3 * * *' + - cron: '0 1 * * *' name: R-code-check @@ -98,8 +98,7 @@ jobs: - name: Restore cached R packages # this step will add the step 'Post Restore cached R packages' on a succesful run - if: runner.os != 'Windows' - uses: actions/cache@v1 + uses: actions/cache@v2 with: path: ${{ env.R_LIBS_USER }} key: ${{ matrix.config.os }}-r-${{ matrix.config.r }}-v4 diff --git a/.github/workflows/codecovr.yaml b/.github/workflows/codecovr.yaml index 972bc332..ce3dcfdf 100644 --- a/.github/workflows/codecovr.yaml +++ b/.github/workflows/codecovr.yaml @@ -50,7 +50,7 @@ jobs: - name: Restore cached R packages # this step will add the step 'Post Restore cached R packages' on a succesful run - uses: actions/cache@v1 + uses: actions/cache@v2 with: path: ${{ env.R_LIBS_USER }} key: macOS-latest-r-release-v5-codecovr @@ -68,20 +68,6 @@ jobs: as.data.frame(utils::installed.packages())[, "Version", drop = FALSE] shell: Rscript {0} - # - name: Test coverage - # env: - # CODECOV_TOKEN: ${{ secrets.CODECOV_TOKEN }} - # run: | - # library(AMR) - # library(tinytest) - # library(covr) - # source_files <- list.files("R", pattern = ".R$", full.names = TRUE) - # test_files <- list.files("inst/tinytest", full.names = TRUE) - # cov <- file_coverage(source_files = source_files, test_files = test_files, parent_env = asNamespace("AMR"), line_exclusions = list("R/atc_online.R", "R/mo_source.R", "R/translate.R", "R/resistance_predict.R", "R/aa_helper_functions.R", "R/aa_helper_pm_functions.R", "R/zzz.R")) - # attr(cov, which = "package") <- list(path = ".") # until https://github.com/r-lib/covr/issues/478 is solved - # codecov(coverage = cov, quiet = FALSE) - # shell: Rscript {0} - - name: Test coverage env: CODECOV_TOKEN: ${{ secrets.CODECOV_TOKEN }} @@ -89,5 +75,6 @@ jobs: run: | library(AMR) library(tinytest) - covr::codecov(line_exclusions = list("R/atc_online.R", "R/mo_source.R", "R/translate.R", "R/resistance_predict.R", "R/aa_helper_functions.R", "R/aa_helper_pm_functions.R", "R/zzz.R")) + x <- covr::codecov(line_exclusions = list("R/atc_online.R", "R/mo_source.R", "R/translate.R", "R/resistance_predict.R", "R/aa_helper_functions.R", "R/aa_helper_pm_functions.R", "R/zzz.R")) + print(x) shell: Rscript {0} diff --git a/.github/workflows/lintr.yaml b/.github/workflows/lintr.yaml index 0cc16834..eb42cd50 100644 --- a/.github/workflows/lintr.yaml +++ b/.github/workflows/lintr.yaml @@ -52,7 +52,7 @@ jobs: shell: Rscript {0} - name: Cache R packages - uses: actions/cache@v1 + uses: actions/cache@v2 with: path: ${{ env.R_LIBS_USER }} key: ${{ runner.os }}-${{ hashFiles('.github/R-version') }}-1-${{ hashFiles('.github/depends.Rds') }} diff --git a/DESCRIPTION b/DESCRIPTION index 669cbbd8..ebe46a15 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: AMR -Version: 1.7.1 -Date: 2021-06-03 +Version: 1.7.1.9000 +Date: 2021-06-04 Title: Antimicrobial Resistance Data Analysis Authors@R: c( person(role = c("aut", "cre"), diff --git a/NAMESPACE b/NAMESPACE index 87cb42e8..9ccd455a 100755 --- a/NAMESPACE +++ b/NAMESPACE @@ -170,6 +170,7 @@ export(age) export(age_groups) export(all_antimicrobials) export(aminoglycosides) +export(aminopenicillins) export(anti_join_microorganisms) export(antimicrobials_equal) export(as.ab) @@ -255,6 +256,8 @@ export(kurtosis) export(labels_rsi_count) export(left_join_microorganisms) export(like) +export(lincosamides) +export(lipoglycopeptides) export(macrolides) export(mdr_cmi2012) export(mdr_tb) @@ -297,12 +300,14 @@ export(oxazolidinones) export(p_symbol) export(pca) export(penicillins) +export(polymyxins) export(proportion_I) export(proportion_IR) export(proportion_R) export(proportion_S) export(proportion_SI) export(proportion_df) +export(quinolones) export(random_disk) export(random_mic) export(random_rsi) @@ -316,9 +321,11 @@ export(scale_y_percent) export(semi_join_microorganisms) export(set_mo_source) export(skewness) +export(streptogramins) export(susceptibility) export(tetracyclines) export(theme_rsi) +export(ureidopenicillins) importFrom(graphics,arrows) importFrom(graphics,axis) importFrom(graphics,barplot) diff --git a/NEWS.md b/NEWS.md index 139173ea..5e421489 100755 --- a/NEWS.md +++ b/NEWS.md @@ -1,3 +1,10 @@ +# `AMR` 1.7.1.9000 +## Last updated: 4 June 2021 + +### Changed +* Added more antibiotic class selectors, such as `lincosamides()` and `lipoglycopeptides()` + + # `AMR` 1.7.1 ### Breaking change diff --git a/R/aa_helper_functions.R b/R/aa_helper_functions.R index 33dff254..2eaa3bdc 100755 --- a/R/aa_helper_functions.R +++ b/R/aa_helper_functions.R @@ -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"), ] diff --git a/R/ab.R b/R/ab.R index c8a4fdcf..c99de647 100755 --- a/R/ab.R +++ b/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]) } } diff --git a/R/ab_class_selectors.R b/R/ab_class_selectors.R index d897d022..4d912f3e 100644 --- a/R/ab_class_selectors.R +++ b/R/ab_class_selectors.R @@ -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 `` 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 , 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), diff --git a/R/eucast_rules.R b/R/eucast_rules.R index cfa3c3bd..38df612b 100755 --- a/R/eucast_rules.R +++ b/R/eucast_rules.R @@ -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 ---- diff --git a/R/ggplot_rsi.R b/R/ggplot_rsi.R index 2f5dfa95..b80dee75 100755 --- a/R/ggplot_rsi.R +++ b/R/ggplot_rsi.R @@ -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)) diff --git a/R/mo.R b/R/mo.R index 014d131f..0a870533 100755 --- a/R/mo.R +++ b/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))) { diff --git a/R/sysdata.rda b/R/sysdata.rda index d9cd9bdb..71dacfce 100644 Binary files a/R/sysdata.rda and b/R/sysdata.rda differ diff --git a/R/translate.R b/R/translate.R index 6bb8c884..bdec3aa8 100755 --- a/R/translate.R +++ b/R/translate.R @@ -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 diff --git a/data-raw/AMR_latest.tar.gz b/data-raw/AMR_latest.tar.gz index 7564a482..84bc2487 100644 Binary files a/data-raw/AMR_latest.tar.gz and b/data-raw/AMR_latest.tar.gz differ diff --git a/data-raw/_internals.R b/data-raw/_internals.R index 2bbed1bc..de4a93c2 100644 --- a/data-raw/_internals.R +++ b/data-raw/_internals.R @@ -34,7 +34,7 @@ old_globalenv <- ls(envir = globalenv()) # Save internal data to R/sysdata.rda ------------------------------------- # See 'data-raw/eucast_rules.tsv' for the EUCAST reference file -eucast_rules_file <- utils::read.delim(file = "data-raw/eucast_rules.tsv", +EUCAST_RULES_DF <- utils::read.delim(file = "data-raw/eucast_rules.tsv", skip = 10, sep = "\t", stringsAsFactors = FALSE, @@ -54,7 +54,7 @@ eucast_rules_file <- utils::read.delim(file = "data-raw/eucast_rules.tsv", select(-sorting_rule) # Translations -translations_file <- utils::read.delim(file = "data-raw/translations.tsv", +TRANSLATIONS <- utils::read.delim(file = "data-raw/translations.tsv", sep = "\t", stringsAsFactors = FALSE, header = TRUE, @@ -68,7 +68,7 @@ translations_file <- utils::read.delim(file = "data-raw/translations.tsv", quote = "") # for checking input in `language` argument in e.g. mo_*() and ab_*() functions -LANGUAGES_SUPPORTED <- sort(c("en", colnames(translations_file)[nchar(colnames(translations_file)) == 2])) +LANGUAGES_SUPPORTED <- sort(c("en", colnames(TRANSLATIONS)[nchar(colnames(TRANSLATIONS)) == 2])) # vectors of CoNS and CoPS, improves speed in as.mo() create_species_cons_cops <- function(type = c("CoNS", "CoPS")) { @@ -121,6 +121,8 @@ CEPHALOSPORINS <- antibiotics %>% filter(group %like% "cephalosporin") %>% pull( CEPHALOSPORINS_1ST <- antibiotics %>% filter(group %like% "cephalosporin.*1") %>% pull(ab) CEPHALOSPORINS_2ND <- antibiotics %>% filter(group %like% "cephalosporin.*2") %>% pull(ab) CEPHALOSPORINS_3RD <- antibiotics %>% filter(group %like% "cephalosporin.*3") %>% pull(ab) +CEPHALOSPORINS_4TH <- antibiotics %>% filter(group %like% "cephalosporin.*4") %>% pull(ab) +CEPHALOSPORINS_5TH <- antibiotics %>% filter(group %like% "cephalosporin.*5") %>% pull(ab) CEPHALOSPORINS_EXCEPT_CAZ <- CEPHALOSPORINS[CEPHALOSPORINS != "CAZ"] FLUOROQUINOLONES <- antibiotics %>% filter(atc_group2 %like% "fluoroquinolone") %>% pull(ab) LIPOGLYCOPEPTIDES <- as.ab(c("DAL", "ORI", "TLV")) # dalba/orita/tela @@ -131,6 +133,7 @@ MACROLIDES <- antibiotics %>% filter(atc_group2 %like% "macrolide") %>% pull(ab) OXAZOLIDINONES <- antibiotics %>% filter(group %like% "oxazolidinone") %>% pull(ab) PENICILLINS <- antibiotics %>% filter(group %like% "penicillin") %>% pull(ab) POLYMYXINS <- antibiotics %>% filter(group %like% "polymyxin") %>% pull(ab) +QUINOLONES <- antibiotics %>% filter(group %like% "quinolone") %>% pull(ab) STREPTOGRAMINS <- antibiotics %>% filter(atc_group2 %like% "streptogramin") %>% pull(ab) TETRACYCLINES <- antibiotics %>% filter(atc_group2 %like% "tetracycline") %>% pull(ab) TETRACYCLINES_EXCEPT_TGC <- TETRACYCLINES[TETRACYCLINES != "TGC"] @@ -141,8 +144,8 @@ DEFINED_AB_GROUPS <- ls(envir = globalenv()) DEFINED_AB_GROUPS <- DEFINED_AB_GROUPS[!DEFINED_AB_GROUPS %in% globalenv_before_ab] # Export to package as internal data ---- -usethis::use_data(eucast_rules_file, - translations_file, +usethis::use_data(EUCAST_RULES_DF, + TRANSLATIONS, LANGUAGES_SUPPORTED, MO_CONS, MO_COPS, @@ -153,6 +156,8 @@ usethis::use_data(eucast_rules_file, CEPHALOSPORINS_1ST, CEPHALOSPORINS_2ND, CEPHALOSPORINS_3RD, + CEPHALOSPORINS_4TH, + CEPHALOSPORINS_5TH, CEPHALOSPORINS_EXCEPT_CAZ, FLUOROQUINOLONES, LIPOGLYCOPEPTIDES, @@ -163,6 +168,7 @@ usethis::use_data(eucast_rules_file, OXAZOLIDINONES, PENICILLINS, POLYMYXINS, + QUINOLONES, STREPTOGRAMINS, TETRACYCLINES, TETRACYCLINES_EXCEPT_TGC, diff --git a/data-raw/reproduction_of_intrinsic_resistant.R b/data-raw/reproduction_of_intrinsic_resistant.R index bfc65beb..114e1b66 100644 --- a/data-raw/reproduction_of_intrinsic_resistant.R +++ b/data-raw/reproduction_of_intrinsic_resistant.R @@ -32,7 +32,7 @@ for (i in seq_len(nrow(antibiotics))) { } int_resis <- eucast_rules(int_resis, - eucast_rules_df = subset(AMR:::eucast_rules_file, + eucast_rules_df = subset(AMR:::EUCAST_RULES_DF, is.na(have_these_values) & reference.version == 3.2), info = FALSE) diff --git a/docs/404.html b/docs/404.html index e400ee9d..f4b7f40a 100644 --- a/docs/404.html +++ b/docs/404.html @@ -81,7 +81,7 @@ AMR (for R) - 1.7.1 + 1.7.1.9000 diff --git a/docs/LICENSE-text.html b/docs/LICENSE-text.html index ca124220..dc371719 100644 --- a/docs/LICENSE-text.html +++ b/docs/LICENSE-text.html @@ -81,7 +81,7 @@ AMR (for R) - 1.7.1 + 1.7.1.9000 diff --git a/docs/articles/datasets.html b/docs/articles/datasets.html index 1873e506..ee42f971 100644 --- a/docs/articles/datasets.html +++ b/docs/articles/datasets.html @@ -39,7 +39,7 @@ AMR (for R) - 1.7.1 + 1.7.1.9000 @@ -192,7 +192,7 @@ diff --git a/docs/authors.html b/docs/authors.html index 680fe639..594ed8e9 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -81,7 +81,7 @@ AMR (for R) - 1.7.1 + 1.7.1.9000 diff --git a/docs/index.html b/docs/index.html index 346b4a61..a43dbfde 100644 --- a/docs/index.html +++ b/docs/index.html @@ -42,7 +42,7 @@ AMR (for R) - 1.7.1 + 1.7.1.9000 @@ -400,7 +400,7 @@
 options(repos = c(getOption("repos"),
                   msberends = "https://msberends.r-universe.dev"))
-

After this, you can install and update this AMR package like any official release (using install.packages("AMR") or in RStudio via Tools > Check of Package Updates…).

+

After this, you can install and update this AMR package like any official release (e.g., using install.packages("AMR") or in RStudio via Tools > Check for Package Updates…).

You can also download the latest build from our repository: https://github.com/msberends/AMR/raw/master/data-raw/AMR_latest.tar.gz

diff --git a/docs/news/index.html b/docs/news/index.html index 20538bc8..b0ef4737 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -81,7 +81,7 @@ AMR (for R) - 1.7.1 + 1.7.1.9000 @@ -236,9 +236,26 @@ Source: NEWS.md +
+

+ Unreleased AMR 1.7.1.9000

+
+

+Last updated: 4 June 2021 +

+
+

+Changed

+ +
+
+

- Unreleased AMR 1.7.1

+ 2021-06-03 AMR 1.7.1

Breaking change

@@ -289,9 +306,9 @@
-
+

-Changed

+Changed
-
+

-Changed

+Changed
-
+

-Changed

+Changed
  • New argument ampc_cephalosporin_resistance in eucast_rules() to correct for AmpC de-repressed cephalosporin-resistant mutants

  • @@ -623,9 +640,9 @@
  • Support for skimming classes <rsi>, <mic>, <disk> and <mo> with the skimr package

-
+

-Changed

+Changed
  • Although advertised that this package should work under R 3.0.0, we still had a dependency on R 3.6.0. This is fixed, meaning that our package should now work under R 3.0.0.

  • @@ -728,9 +745,9 @@
  • Added argument conserve_capped_values to as.rsi() for interpreting MIC values - it makes sure that values starting with “<” (but not “<=”) will always return “S” and values starting with “>” (but not “>=”) will always return “R”. The default behaviour of as.rsi() has not changed, so you need to specifically do as.rsi(..., conserve_capped_values = TRUE).

-
+

-Changed

+Changed
-
+

-Changed

+Changed
  • Taxonomy:
      @@ -857,9 +874,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
    • Plotting biplots for principal component analysis using the new ggplot_pca() function
-
+

-Changed

+Changed
  • Improvements for the algorithm used by as.mo() (and consequently all mo_* functions, that use as.mo() internally):
      @@ -890,9 +907,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/

      2020-02-23 AMR 1.0.1

      -
      +

      -Changed

      +Changed
      • Fixed important floating point error for some MIC comparisons in EUCAST 2020 guideline

      • @@ -1198,9 +1215,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
      -
      +

      -Changed

      +Changed
      • Many algorithm improvements for as.mo() (of which some led to additions to the microorganisms data set). Many thanks to all contributors that helped improving the algorithms.
          @@ -1310,9 +1327,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
        • Function mo_synonyms() to get all previously accepted taxonomic names of a microorganism

      -
      +

      -Changed

      +Changed
      • Column names of output count_df() and portion_df() are now lowercase
      • Fixed bug in translation of microorganism names
      • @@ -1358,9 +1375,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
      • Added guidelines of the WHO to determine multi-drug resistance (MDR) for TB (mdr_tb()) and added a new vignette about MDR. Read this tutorial here on our website.
      -
      +

      -Changed

      +Changed
      • Fixed a critical bug in first_isolate() where missing species would lead to incorrect FALSEs. This bug was not present in AMR v0.5.0, but was in v0.6.0 and v0.6.1.
      • Fixed a bug in eucast_rules() where antibiotics from WHONET software would not be recognised
      • @@ -1444,9 +1461,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/

        2019-03-29 AMR 0.6.1

        -
        +

        -Changed

        +Changed
        • Fixed a critical bug when using eucast_rules() with verbose = TRUE
        • @@ -1563,9 +1580,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
        • New vignettes about how to conduct AMR analysis, predict antimicrobial resistance, use the G-test and more. These are also available (and even easier readable) on our website: https://msberends.gitlab.io/AMR.

        -
        +

        -Changed

        +Changed
        • Function eucast_rules():
            @@ -1721,9 +1738,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
          • Functions mo_authors and mo_year to get specific values about the scientific reference of a taxonomic entry
        -
        +

        -Changed

        +Changed
        • Functions MDRO, BRMO, MRGN and EUCAST_exceptional_phenotypes were renamed to mdro, brmo, mrgn and eucast_exceptional_phenotypes

        • EUCAST_rules was renamed to eucast_rules, the old function still exists as a deprecated function

        • @@ -1911,9 +1928,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
        • Renamed septic_patients$sex to septic_patients$gender

        -
        +

        -Changed

        +Changed
        • Added three antimicrobial agents to the antibiotics data set: Terbinafine (D01BA02), Rifaximin (A07AA11) and Isoconazole (D01AC05)

        • @@ -2052,9 +2069,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
        -
        +

        -Changed

        +Changed
        • Improvements for forecasting with resistance_predict and added more examples
        • More antibiotics added as arguments for EUCAST rules
        • @@ -2137,9 +2154,9 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
        • New print format for tibbles and data.tables
        -
        +

        -Changed

        +Changed
        • Fixed rsi class for vectors that contain only invalid antimicrobial interpretations
        • Renamed dataset ablist to antibiotics diff --git a/docs/pkgdown.yml b/docs/pkgdown.yml index 6b7f70c8..98b5057d 100644 --- a/docs/pkgdown.yml +++ b/docs/pkgdown.yml @@ -12,7 +12,7 @@ articles: datasets: datasets.html resistance_predict: resistance_predict.html welcome_to_AMR: welcome_to_AMR.html -last_built: 2021-06-03T13:04Z +last_built: 2021-06-04T19:07Z urls: reference: https://msberends.github.io/AMR//reference article: https://msberends.github.io/AMR//articles diff --git a/docs/reference/antibiotic_class_selectors.html b/docs/reference/antibiotic_class_selectors.html index c4eb694f..2d6925b1 100644 --- a/docs/reference/antibiotic_class_selectors.html +++ b/docs/reference/antibiotic_class_selectors.html @@ -49,7 +49,7 @@ - @@ -83,7 +83,7 @@ AMR (for R) - 1.7.1 + 1.7.1.9000
        @@ -240,7 +240,7 @@
        -

        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. +

        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.

        @@ -248,6 +248,8 @@ aminoglycosides(only_rsi_columns = FALSE) +aminopenicillins(only_rsi_columns = FALSE) + betalactams(only_rsi_columns = FALSE) carbapenems(only_rsi_columns = FALSE) @@ -268,13 +270,25 @@ glycopeptides(only_rsi_columns = FALSE) +lincosamides(only_rsi_columns = FALSE) + +lipoglycopeptides(only_rsi_columns = FALSE) + macrolides(only_rsi_columns = FALSE) oxazolidinones(only_rsi_columns = FALSE) penicillins(only_rsi_columns = FALSE) -tetracyclines(only_rsi_columns = FALSE) +polymyxins(only_rsi_columns = FALSE) + +streptogramins(only_rsi_columns = FALSE) + +quinolones(only_rsi_columns = FALSE) + +tetracyclines(only_rsi_columns = FALSE) + +ureidopenicillins(only_rsi_columns = FALSE)

        Arguments

        @@ -294,8 +308,36 @@

        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(), filter() and 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.

        -

        The group of betalactams consists of all carbapenems, cephalosporins and penicillins.

        +

        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.

        +

        Full list of supported agents

        + + + +
          +
        • aminoglycosides() can select amikacin (AMK), amikacin/fosfomycin (AKF), amphotericin B-high (AMH), 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)

        • +
        • aminopenicillins() can select amoxicillin (AMX) and ampicillin (AMP)

        • +
        • betalactams() can select 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), bacampicillin (BAM), benzathine benzylpenicillin (BNB), benzathine phenoxymethylpenicillin (BNP), benzylpenicillin (PEN), biapenem (BIA), cadazolid (CDZ), carbenicillin (CRB), carindacillin (CRN), cefacetrile (CAC), cefaclor (CEC), cefadroxil (CFR), cefaloridine (RID), cefamandole (MAN), 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/tazobactam (FPT), cefetamet (CAT), cefetamet pivoxil (CPI), cefetecol (Cefcatacol) (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/enzyme inhibitor (CEI), ceftolozane/tazobactam (CZT), ceftriaxone (CRO), cefuroxime (CXM), cefuroxime axetil (CXA), cephalexin (LEX), cephalothin (CEP), cephapirin (HAP), 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 (Amdinocillin) (MEC), meropenem (MEM), meropenem/nacubactam (MNC), meropenem/vaborbactam (MEV), metampicillin (MTM), methicillin (MET), mezlocillin (MEZ), mezlocillin/sulbactam (MSU), nacubactam (NAC), nafcillin (NAF), oxacillin (OXA), panipenem (PAN), penamecillin (PNM), penicillin/novobiocin (PNO), penicillin/sulbactam (PSU), phenethicillin (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)

        • +
        • carbapenems() can select 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)

        • +
        • cephalosporins() can select cadazolid (CDZ), cefacetrile (CAC), cefaclor (CEC), cefadroxil (CFR), cefaloridine (RID), cefamandole (MAN), 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/tazobactam (FPT), cefetamet (CAT), cefetamet pivoxil (CPI), cefetecol (Cefcatacol) (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/enzyme inhibitor (CEI), ceftolozane/tazobactam (CZT), ceftriaxone (CRO), cefuroxime (CXM), cefuroxime axetil (CXA), cephalexin (LEX), cephalothin (CEP), cephapirin (HAP), cephradine (CED), latamoxef (LTM) and loracarbef (LOR)

        • +
        • cephalosporins_1st() can select cefacetrile (CAC), cefadroxil (CFR), cefaloridine (RID), cefatrizine (CTZ), cefazedone (CZD), cefazolin (CZO), cefroxadine (CRD), ceftezole (CTL), cephalexin (LEX), cephalothin (CEP), cephapirin (HAP) and cephradine (CED)

        • +
        • cephalosporins_2nd() can select cefaclor (CEC), cefamandole (MAN), cefmetazole (CMZ), cefonicid (CID), ceforanide (CND), cefotetan (CTT), cefotiam (CTF), cefoxitin (FOX), cefoxitin screening (FOX1), cefprozil (CPR), cefuroxime (CXM), cefuroxime axetil (CXA) and loracarbef (LOR)

        • +
        • cephalosporins_3rd() can select cadazolid (CDZ), cefcapene (CCP), cefcapene pivoxil (CCX), cefdinir (CDR), cefditoren (DIT), cefditoren pivoxil (DIX), cefetamet (CAT), cefetamet pivoxil (CPI), cefixime (CFM), cefmenoxime (CMX), cefodizime (DIZ), cefoperazone (CFP), cefoperazone/sulbactam (CSL), cefotaxime (CTX), cefotaxime/clavulanic acid (CTC), cefotaxime/sulbactam (CTS), cefotiam hexetil (CHE), cefovecin (FOV), cefpimizole (CFZ), cefpiramide (CPM), cefpodoxime (CPD), cefpodoxime proxetil (CPX), cefpodoxime/clavulanic acid (CDC), cefsulodin (CFS), ceftazidime (CAZ), ceftazidime/avibactam (CZA), ceftazidime/clavulanic acid (CCV), cefteram (CEM), cefteram pivoxil (CPL), ceftibuten (CTB), ceftiofur (TIO), ceftizoxime (CZX), ceftizoxime alapivoxil (CZP), ceftriaxone (CRO) and latamoxef (LTM)

        • +
        • cephalosporins_4th() can select cefepime (FEP), cefepime/clavulanic acid (CPC), cefepime/tazobactam (FPT), cefetecol (Cefcatacol) (CCL), cefoselis (CSE), cefozopran (ZOP), cefpirome (CPO) and cefquinome (CEQ)

        • +
        • cephalosporins_5th() can select ceftaroline (CPT), ceftaroline/avibactam (CPA), ceftobiprole (BPR), ceftobiprole medocaril (CFM1), ceftolozane/enzyme inhibitor (CEI) and ceftolozane/tazobactam (CZT)

        • +
        • fluoroquinolones() can select ciprofloxacin (CIP), enoxacin (ENX), fleroxacin (FLE), gatifloxacin (GAT), gemifloxacin (GEM), grepafloxacin (GRX), levofloxacin (LVX), lomefloxacin (LOM), moxifloxacin (MFX), norfloxacin (NOR), ofloxacin (OFX), pazufloxacin (PAZ), pefloxacin (PEF), prulifloxacin (PRU), rufloxacin (RFL), sparfloxacin (SPX), temafloxacin (TMX) and trovafloxacin (TVA)

        • +
        • glycopeptides() can select avoparcin (AVO), dalbavancin (DAL), norvancomycin (NVA), oritavancin (ORI), ramoplanin (RAM), teicoplanin (TEC), teicoplanin-macromethod (TCM), telavancin (TLV), vancomycin (VAN) and vancomycin-macromethod (VAM)

        • +
        • lincosamides() can select clindamycin (CLI), lincomycin (LIN) and pirlimycin (PRL)

        • +
        • lipoglycopeptides() can select dalbavancin (DAL), oritavancin (ORI) and telavancin (TLV)

        • +
        • macrolides() can select azithromycin (AZM), clarithromycin (CLR), dirithromycin (DIR), erythromycin (ERY), flurithromycin (FLR1), josamycin (JOS), midecamycin (MID), miocamycin (MCM), oleandomycin (OLE), rokitamycin (ROK), roxithromycin (RXT), spiramycin (SPI), telithromycin (TLT) and troleandomycin (TRL)

        • +
        • oxazolidinones() can select cycloserine (CYC), linezolid (LNZ), tedizolid (TZD) and thiacetazone (THA)

        • +
        • penicillins() can select 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), bacampicillin (BAM), benzathine benzylpenicillin (BNB), benzathine phenoxymethylpenicillin (BNP), benzylpenicillin (PEN), carbenicillin (CRB), carindacillin (CRN), ciclacillin (CIC), clometocillin (CLM), cloxacillin (CLO), dicloxacillin (DIC), epicillin (EPC), flucloxacillin (FLC), hetacillin (HET), lenampicillin (LEN), mecillinam (Amdinocillin) (MEC), metampicillin (MTM), methicillin (MET), mezlocillin (MEZ), mezlocillin/sulbactam (MSU), nacubactam (NAC), nafcillin (NAF), oxacillin (OXA), penamecillin (PNM), penicillin/novobiocin (PNO), penicillin/sulbactam (PSU), phenethicillin (PHE), phenoxymethylpenicillin (PHN), piperacillin (PIP), piperacillin/sulbactam (PIS), piperacillin/tazobactam (TZP), piridicillin (PRC), pivampicillin (PVM), pivmecillinam (PME), procaine benzylpenicillin (PRB), propicillin (PRP), sarmoxicillin (SRX), sulbactam (SUL), sulbenicillin (SBC), sultamicillin (SLT6), talampicillin (TAL), tazobactam (TAZ), temocillin (TEM), ticarcillin (TIC) and ticarcillin/clavulanic acid (TCC)

        • +
        • polymyxins() can select colistin (COL), polymyxin B (PLB) and polymyxin B/polysorbate 80 (POP)

        • +
        • streptogramins() can select pristinamycin (PRI) and quinupristin/dalfopristin (QDA)

        • +
        • quinolones() can select besifloxacin (BES), cinoxacin (CIN), ciprofloxacin (CIP), clinafloxacin (CLX), danofloxacin (DAN), delafloxacin (DFX), difloxacin (DIF), enoxacin (ENX), enrofloxacin (ENR), finafloxacin (FIN), fleroxacin (FLE), flumequine (FLM), garenoxacin (GRN), gatifloxacin (GAT), gemifloxacin (GEM), grepafloxacin (GRX), levofloxacin (LVX), levonadifloxacin (LND), lomefloxacin (LOM), marbofloxacin (MAR), metioxate (MXT), miloxacin (MIL), moxifloxacin (MFX), nadifloxacin (NAD), nalidixic acid (NAL), nifuroquine (NIF), nitroxoline (NTR), norfloxacin (NOR), ofloxacin (OFX), orbifloxacin (ORB), oxolinic acid (OXO), pazufloxacin (PAZ), pefloxacin (PEF), pipemidic acid (PPA), piromidic acid (PIR), pradofloxacin (PRA), premafloxacin (PRX), prulifloxacin (PRU), rosoxacin (ROS), rufloxacin (RFL), sarafloxacin (SAR), sitafloxacin (SIT), sparfloxacin (SPX), temafloxacin (TMX), tilbroquinol (TBQ), tioxacin (TXC), tosufloxacin (TFX) and trovafloxacin (TVA)

        • +
        • tetracyclines() can select chlortetracycline (CTE), clomocycline (CLM1), demeclocycline (DEM), doxycycline (DOX), eravacycline (ERV), lymecycline (LYM), metacycline (MTC), minocycline (MNO), oxytetracycline (OXY), penimepicycline (PNM1), rolitetracycline (RLT), tetracycline (TCY) and tigecycline (TGC)

        • +
        • ureidopenicillins() can select azlocillin (AZL), mezlocillin (MEZ), piperacillin (PIP) and piperacillin/tazobactam (TZP)

        • +
        +

        Stable Lifecycle

        @@ -315,1209 +357,31 @@ The lifecycle of this function is stableOn our website https://msberends.github.io/AMR/ you can find a comprehensive tutorial about how to conduct AMR data analysis, the complete documentation of all functions and an example analysis using WHONET data.

        Examples

        -
        # `example_isolates` is a data set available in the AMR package. +
        # `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()]
        -
        #> ℹ For `carbapenems()` using columns: 'IPM' (imipenem) and 'MEM' (meropenem)
        #> IPM MEM -#> 1 <NA> <NA> -#> 2 <NA> <NA> -#> 3 <NA> <NA> -#> 4 <NA> <NA> -#> 5 <NA> <NA> -#> 6 <NA> <NA> -#> 7 <NA> <NA> -#> 8 <NA> <NA> -#> 9 <NA> <NA> -#> 10 <NA> <NA> -#> 11 <NA> <NA> -#> 12 <NA> <NA> -#> 13 S <NA> -#> 14 S <NA> -#> 15 <NA> <NA> -#> 16 S <NA> -#> 17 S <NA> -#> 18 <NA> <NA> -#> 19 <NA> <NA> -#> 20 <NA> <NA> -#> 21 <NA> <NA> -#> 22 S <NA> -#> 23 S <NA> -#> 24 S <NA> -#> 25 <NA> <NA> -#> 26 <NA> <NA> -#> 27 <NA> <NA> -#> 28 <NA> <NA> -#> 29 <NA> <NA> -#> 30 <NA> <NA> -#> 31 <NA> <NA> -#> 32 <NA> <NA> -#> 33 S <NA> -#> 34 S <NA> -#> 35 S <NA> -#> 36 S <NA> -#> 37 <NA> <NA> -#> 38 S <NA> -#> 39 S <NA> -#> 40 <NA> <NA> -#> 41 <NA> <NA> -#> 42 <NA> <NA> -#> 43 <NA> <NA> -#> 44 <NA> <NA> -#> 45 S <NA> -#> 46 <NA> <NA> -#> 47 <NA> <NA> -#> 48 S S -#> 49 S <NA> -#> 50 S <NA> -#> 51 S <NA> -#> 52 <NA> <NA> -#> 53 <NA> <NA> -#> 54 <NA> <NA> -#> 55 <NA> <NA> -#> 56 <NA> <NA> -#> 57 <NA> <NA> -#> 58 <NA> <NA> -#> 59 <NA> <NA> -#> 60 <NA> <NA> -#> 61 <NA> <NA> -#> 62 <NA> <NA> -#> 63 <NA> <NA> -#> 64 <NA> <NA> -#> 65 S <NA> -#> 66 S <NA> -#> 67 S <NA> -#> 68 <NA> <NA> -#> 69 <NA> <NA> -#> 70 <NA> <NA> -#> 71 S <NA> -#> 72 S <NA> -#> 73 S <NA> -#> 74 S <NA> -#> 75 <NA> <NA> -#> 76 S <NA> -#> 77 <NA> <NA> -#> 78 S <NA> -#> 79 S <NA> -#> 80 <NA> <NA> -#> 81 <NA> <NA> -#> 82 <NA> <NA> -#> 83 <NA> <NA> -#> 84 S <NA> -#> 85 S <NA> -#> 86 S <NA> -#> 87 S <NA> -#> 88 S <NA> -#> 89 S <NA> -#> 90 <NA> <NA> -#> 91 <NA> <NA> -#> 92 <NA> <NA> -#> 93 <NA> <NA> -#> 94 <NA> <NA> -#> 95 <NA> <NA> -#> 96 <NA> <NA> -#> 97 <NA> <NA> -#> 98 <NA> <NA> -#> 99 <NA> <NA> -#> 100 <NA> <NA> -#> 101 S <NA> -#> 102 <NA> <NA> -#> 103 <NA> <NA> -#> 104 <NA> <NA> -#> 105 <NA> <NA> -#> 106 <NA> <NA> -#> 107 <NA> <NA> -#> 108 <NA> <NA> -#> 109 <NA> <NA> -#> 110 <NA> <NA> -#> 111 <NA> <NA> -#> 112 <NA> <NA> -#> 113 <NA> <NA> -#> 114 <NA> <NA> -#> 115 <NA> <NA> -#> 116 S <NA> -#> 117 <NA> <NA> -#> 118 S <NA> -#> 119 S <NA> -#> 120 S <NA> -#> 121 S <NA> -#> 122 S <NA> -#> 123 <NA> <NA> -#> 124 <NA> <NA> -#> 125 <NA> <NA> -#> 126 <NA> <NA> -#> 127 <NA> <NA> -#> 128 <NA> <NA> -#> 129 S <NA> -#> 130 S <NA> -#> 131 <NA> <NA> -#> 132 <NA> <NA> -#> 133 <NA> <NA> -#> 134 <NA> <NA> -#> 135 <NA> <NA> -#> 136 <NA> <NA> -#> 137 <NA> <NA> -#> 138 <NA> <NA> -#> 139 S <NA> -#> 140 <NA> <NA> -#> 141 <NA> <NA> -#> 142 <NA> <NA> -#> 143 S <NA> -#> 144 <NA> <NA> -#> 145 <NA> <NA> -#> 146 <NA> <NA> -#> 147 <NA> <NA> -#> 148 <NA> <NA> -#> 149 <NA> <NA> -#> 150 <NA> <NA> -#> 151 <NA> <NA> -#> 152 <NA> <NA> -#> 153 S S -#> 154 S S -#> 155 S S -#> 156 <NA> <NA> -#> 157 <NA> <NA> -#> 158 <NA> <NA> -#> 159 <NA> <NA> -#> 160 S <NA> -#> 161 <NA> <NA> -#> 162 S <NA> -#> 163 <NA> <NA> -#> 164 <NA> <NA> -#> 165 <NA> <NA> -#> 166 <NA> <NA> -#> 167 <NA> <NA> -#> 168 <NA> <NA> -#> 169 <NA> <NA> -#> 170 <NA> <NA> -#> 171 <NA> <NA> -#> 172 <NA> <NA> -#> 173 <NA> <NA> -#> 174 <NA> <NA> -#> 175 <NA> <NA> -#> 176 S <NA> -#> 177 <NA> <NA> -#> 178 <NA> <NA> -#> 179 <NA> <NA> -#> 180 <NA> <NA> -#> 181 <NA> <NA> -#> 182 <NA> <NA> -#> 183 S <NA> -#> 184 S <NA> -#> 185 <NA> <NA> -#> 186 <NA> <NA> -#> 187 <NA> <NA> -#> 188 <NA> <NA> -#> 189 <NA> <NA> -#> 190 <NA> <NA> -#> 191 <NA> <NA> -#> 192 <NA> <NA> -#> 193 <NA> <NA> -#> 194 S <NA> -#> 195 S <NA> -#> 196 <NA> <NA> -#> 197 <NA> <NA> -#> 198 <NA> <NA> -#> 199 S <NA> -#> 200 <NA> <NA> -#> 201 <NA> <NA> -#> 202 <NA> <NA> -#> 203 <NA> <NA> -#> 204 S <NA> -#> 205 S <NA> -#> 206 <NA> <NA> -#> 207 S S -#> 208 S <NA> -#> 209 S <NA> -#> 210 S <NA> -#> 211 S <NA> -#> 212 I <NA> -#> 213 S <NA> -#> 214 <NA> <NA> -#> 215 <NA> <NA> -#> 216 S <NA> -#> 217 <NA> <NA> -#> 218 <NA> <NA> -#> 219 <NA> <NA> -#> 220 <NA> <NA> -#> 221 <NA> <NA> -#> 222 <NA> <NA> -#> 223 <NA> <NA> -#> 224 S <NA> -#> 225 S <NA> -#> 226 S <NA> -#> 227 S <NA> -#> 228 S <NA> -#> 229 <NA> <NA> -#> 230 S <NA> -#> 231 S <NA> -#> 232 S <NA> -#> 233 <NA> <NA> -#> 234 <NA> <NA> -#> 235 <NA> <NA> -#> 236 <NA> <NA> -#> 237 S S -#> 238 S <NA> -#> 239 S <NA> -#> 240 S S -#> 241 S <NA> -#> 242 S S -#> 243 <NA> <NA> -#> 244 <NA> <NA> -#> 245 <NA> <NA> -#> 246 S S -#> 247 S S -#> 248 S S -#> 249 <NA> <NA> -#> 250 <NA> <NA> -#> 251 S S -#> 252 <NA> <NA> -#> 253 S <NA> -#> 254 S <NA> -#> 255 <NA> <NA> -#> 256 <NA> <NA> -#> 257 <NA> <NA> -#> 258 <NA> <NA> -#> 259 <NA> <NA> -#> 260 <NA> <NA> -#> 261 <NA> S -#> 262 <NA> <NA> -#> 263 <NA> <NA> -#> 264 S <NA> -#> 265 S <NA> -#> 266 <NA> <NA> -#> 267 <NA> <NA> -#> 268 <NA> <NA> -#> 269 <NA> <NA> -#> 270 <NA> <NA> -#> 271 <NA> <NA> -#> 272 <NA> <NA> -#> 273 <NA> <NA> -#> 274 <NA> <NA> -#> 275 <NA> <NA> -#> 276 <NA> <NA> -#> 277 <NA> <NA> -#> 278 S S -#> 279 S S -#> 280 S S -#> 281 <NA> <NA> -#> 282 <NA> <NA> -#> 283 <NA> S -#> 284 <NA> S -#> 285 <NA> S -#> 286 <NA> S -#> 287 <NA> <NA> -#> 288 <NA> <NA> -#> 289 <NA> <NA> -#> 290 <NA> <NA> -#> 291 <NA> <NA> -#> 292 <NA> <NA> -#> 293 <NA> <NA> -#> 294 <NA> S -#> 295 <NA> <NA> -#> 296 <NA> <NA> -#> 297 <NA> <NA> -#> 298 S S -#> 299 S S -#> 300 <NA> <NA> -#> 301 <NA> <NA> -#> 302 <NA> <NA> -#> 303 <NA> <NA> -#> 304 <NA> <NA> -#> 305 <NA> <NA> -#> 306 <NA> <NA> -#> 307 S <NA> -#> 308 <NA> <NA> -#> 309 S S -#> 310 <NA> <NA> -#> 311 <NA> <NA> -#> 312 <NA> S -#> 313 S S -#> 314 S S -#> 315 S S -#> 316 S S -#> 317 <NA> <NA> -#> 318 <NA> <NA> -#> 319 <NA> <NA> -#> 320 <NA> S -#> 321 <NA> S -#> 322 S S -#> 323 S S -#> 324 <NA> <NA> -#> 325 <NA> <NA> -#> 326 <NA> <NA> -#> 327 <NA> <NA> -#> 328 <NA> <NA> -#> 329 <NA> <NA> -#> 330 <NA> <NA> -#> 331 <NA> <NA> -#> 332 <NA> <NA> -#> 333 <NA> <NA> -#> 334 <NA> <NA> -#> 335 <NA> <NA> -#> 336 <NA> <NA> -#> 337 R <NA> -#> 338 R <NA> -#> 339 <NA> <NA> -#> 340 S S -#> 341 <NA> <NA> -#> 342 <NA> <NA> -#> 343 S S -#> 344 S <NA> -#> 345 <NA> <NA> -#> 346 <NA> <NA> -#> 347 <NA> <NA> -#> 348 <NA> <NA> -#> 349 <NA> <NA> -#> 350 <NA> S -#> 351 <NA> <NA> -#> 352 <NA> <NA> -#> 353 <NA> <NA> -#> 354 S S -#> 355 <NA> <NA> -#> 356 S S -#> 357 <NA> <NA> -#> 358 S S -#> 359 <NA> <NA> -#> 360 S S -#> 361 S S -#> 362 <NA> <NA> -#> 363 <NA> S -#> 364 <NA> S -#> 365 <NA> S -#> 366 <NA> <NA> -#> 367 <NA> <NA> -#> 368 S S -#> 369 S S -#> 370 S S -#> 371 S S -#> 372 <NA> <NA> -#> 373 <NA> <NA> -#> 374 <NA> <NA> -#> 375 <NA> <NA> -#> 376 <NA> <NA> -#> 377 <NA> <NA> -#> 378 <NA> <NA> -#> 379 <NA> <NA> -#> 380 <NA> <NA> -#> 381 R R -#> 382 <NA> <NA> -#> 383 <NA> <NA> -#> 384 <NA> <NA> -#> 385 S S -#> 386 <NA> <NA> -#> 387 <NA> <NA> -#> 388 <NA> <NA> -#> 389 S S -#> 390 S S -#> 391 S S -#> 392 S <NA> -#> 393 S S -#> 394 <NA> <NA> -#> 395 S S -#> 396 <NA> <NA> -#> 397 <NA> <NA> -#> 398 <NA> <NA> -#> 399 <NA> <NA> -#> 400 S S -#> 401 S S -#> 402 S S -#> 403 S S -#> 404 <NA> <NA> -#> 405 S S -#> 406 <NA> S -#> 407 <NA> S -#> 408 <NA> S -#> 409 S S -#> 410 S S -#> 411 <NA> S -#> 412 <NA> <NA> -#> 413 <NA> <NA> -#> 414 <NA> <NA> -#> 415 S S -#> 416 <NA> <NA> -#> 417 <NA> <NA> -#> 418 <NA> <NA> -#> 419 <NA> <NA> -#> 420 <NA> <NA> -#> 421 <NA> <NA> -#> 422 <NA> <NA> -#> 423 <NA> <NA> -#> 424 S S -#> 425 S S -#> 426 <NA> <NA> -#> 427 <NA> <NA> -#> 428 <NA> <NA> -#> 429 <NA> <NA> -#> 430 <NA> <NA> -#> 431 <NA> <NA> -#> 432 <NA> <NA> -#> 433 <NA> <NA> -#> 434 <NA> <NA> -#> 435 <NA> <NA> -#> 436 <NA> <NA> -#> 437 <NA> <NA> -#> 438 S S -#> 439 S S -#> 440 S S -#> 441 S S -#> 442 <NA> <NA> -#> 443 <NA> S -#> 444 <NA> S -#> 445 <NA> <NA> -#> 446 <NA> <NA> -#> 447 <NA> <NA> -#> 448 <NA> <NA> -#> 449 S S -#> 450 S S -#> 451 <NA> <NA> -#> 452 <NA> <NA> -#> 453 <NA> <NA> -#> 454 <NA> <NA> -#> 455 <NA> <NA> -#> 456 <NA> <NA> -#> 457 S S -#> 458 S S -#> 459 <NA> <NA> -#> 460 <NA> <NA> -#> 461 R R -#> 462 R R -#> 463 R R -#> 464 <NA> <NA> -#> 465 <NA> <NA> -#> 466 <NA> <NA> -#> 467 <NA> S -#> 468 <NA> S -#> 469 S <NA> -#> 470 <NA> <NA> -#> 471 <NA> S -#> 472 <NA> S -#> 473 <NA> S -#> 474 <NA> S -#> 475 <NA> <NA> -#> 476 <NA> <NA> -#> 477 <NA> <NA> -#> 478 S S -#> 479 <NA> <NA> -#> 480 S S -#> 481 S S -#> 482 <NA> S -#> 483 <NA> S -#> 484 <NA> <NA> -#> 485 S S -#> 486 S S -#> 487 <NA> <NA> -#> 488 <NA> S -#> 489 S S -#> 490 S S -#> 491 S S -#> 492 S S -#> 493 <NA> S -#> 494 <NA> S -#> 495 <NA> S -#> 496 <NA> S -#> 497 <NA> <NA> -#> 498 <NA> <NA> -#> 499 <NA> <NA> -#> 500 <NA> <NA> -#> [ reached 'max' / getOption("max.print") -- omitted 1500 rows ]
        + # select columns 'mo', 'AMK', 'GEN', 'KAN' and 'TOB' example_isolates[, c("mo", aminoglycosides())] -
        #> ℹ For `aminoglycosides()` using columns: 'AMK' (amikacin), 'GEN' -#> (gentamicin), 'KAN' (kanamycin) and 'TOB' (tobramycin)
        #> mo GEN TOB AMK KAN -#> 1 B_ESCHR_COLI <NA> <NA> <NA> <NA> -#> 2 B_ESCHR_COLI <NA> <NA> <NA> <NA> -#> 3 B_STPHY_EPDR <NA> <NA> <NA> <NA> -#> 4 B_STPHY_EPDR <NA> <NA> <NA> <NA> -#> 5 B_STPHY_EPDR <NA> <NA> <NA> <NA> -#> 6 B_STPHY_EPDR <NA> <NA> <NA> <NA> -#> 7 B_STPHY_AURS <NA> S <NA> <NA> -#> 8 B_STPHY_AURS <NA> S <NA> <NA> -#> 9 B_STPHY_EPDR <NA> <NA> <NA> <NA> -#> 10 B_STPHY_EPDR <NA> <NA> <NA> <NA> -#> 11 B_STPHY_EPDR <NA> <NA> <NA> <NA> -#> 12 B_STPHY_EPDR <NA> <NA> <NA> <NA> -#> 13 B_ESCHR_COLI <NA> S <NA> <NA> -#> 14 B_ESCHR_COLI <NA> S <NA> <NA> -#> 15 B_CTRBC_FRND <NA> <NA> <NA> <NA> -#> 16 B_PROTS_MRBL <NA> <NA> <NA> <NA> -#> 17 B_PROTS_MRBL <NA> <NA> <NA> <NA> -#> 18 B_STPHY_EPDR <NA> <NA> <NA> <NA> -#> 19 B_STPHY_EPDR <NA> <NA> <NA> <NA> -#> 20 B_STPHY_CONS <NA> <NA> <NA> <NA> -#> 21 B_STPHY_HMNS <NA> <NA> <NA> <NA> -#> 22 B_SERRT_MRCS <NA> <NA> <NA> <NA> -#> 23 B_SERRT_MRCS <NA> <NA> <NA> <NA> -#> 24 B_SERRT_MRCS <NA> <NA> <NA> <NA> -#> 25 B_STPHY_CONS <NA> <NA> <NA> <NA> -#> 26 B_STPHY_CONS <NA> S <NA> <NA> -#> 27 B_STPHY_EPDR <NA> <NA> <NA> <NA> -#> 28 B_ENTRC_FACM R R R R -#> 29 B_STPHY_CONS S <NA> <NA> <NA> -#> 30 B_STPHY_CONS S <NA> <NA> <NA> -#> 31 B_STPHY_HMNS S <NA> <NA> <NA> -#> 32 B_STPHY_EPDR S <NA> <NA> <NA> -#> 33 B_KLBSL_PNMN S S <NA> <NA> -#> 34 B_KLBSL_PNMN S S <NA> <NA> -#> 35 B_ESCHR_COLI S <NA> <NA> <NA> -#> 36 B_PSDMN_AERG I S <NA> R -#> 37 B_STPHY_CONS R R R R -#> 38 B_ESCHR_COLI S S <NA> <NA> -#> 39 B_ESCHR_COLI S S <NA> <NA> -#> 40 B_STRPT_SNGN R R R R -#> 41 B_STPHY_AURS S <NA> <NA> <NA> -#> 42 B_STPHY_AURS S <NA> <NA> <NA> -#> 43 B_STPHY_AURS S <NA> <NA> <NA> -#> 44 B_STPHY_AURS S <NA> <NA> <NA> -#> 45 B_ENTRC_FCLS R R R R -#> 46 B_STPHY_CONS S <NA> <NA> <NA> -#> 47 F_CANDD_GLBR <NA> <NA> <NA> <NA> -#> 48 B_STRPT_GRPB R R R R -#> 49 B_ESCHR_COLI S S <NA> <NA> -#> 50 B_ESCHR_COLI S S <NA> <NA> -#> 51 B_KLBSL_PNMN S S <NA> <NA> -#> 52 B_STPHY_AURS S <NA> <NA> <NA> -#> 53 B_STPHY_CONS R R R R -#> 54 B_STPHY_CONS R R R R -#> 55 B_STRPT_PNMN R R R R -#> 56 B_STRPT_PNMN R R R R -#> 57 B_STPHY_AURS S <NA> <NA> <NA> -#> 58 B_STRPT_ANGN R R R R -#> 59 B_STRPT_ANGN R R R R -#> 60 B_STPHY_AURS S <NA> <NA> <NA> -#> 61 B_STPHY_AURS S <NA> <NA> <NA> -#> 62 B_STPHY_EPDR R R R R -#> 63 B_STPHY_AURS S <NA> <NA> <NA> -#> 64 B_STRPT_PNMN R R R R -#> 65 B_ESCHR_COLI S S <NA> <NA> -#> 66 B_ESCHR_COLI S S <NA> <NA> -#> 67 B_ESCHR_COLI S S <NA> <NA> -#> 68 B_STPHY_CONS S <NA> <NA> <NA> -#> 69 B_CRYNB <NA> <NA> <NA> <NA> -#> 70 B_STPHY_HMNS S <NA> <NA> <NA> -#> 71 B_ESCHR_COLI S S <NA> <NA> -#> 72 B_ESCHR_COLI S S <NA> <NA> -#> 73 B_ENTRC_FCLS R R R R -#> 74 B_ENTRC_FCLS R R R R -#> 75 B_STPHY_HMNS I <NA> <NA> <NA> -#> 76 B_ESCHR_COLI S S <NA> <NA> -#> 77 B_STPHY_CONS S <NA> <NA> <NA> -#> 78 B_PSDMN_AERG I S <NA> R -#> 79 B_PSDMN_AERG I S <NA> R -#> 80 B_STPHY_AURS S <NA> <NA> <NA> -#> 81 B_STPHY_AURS S <NA> <NA> <NA> -#> 82 B_STPHY_AURS S <NA> <NA> <NA> -#> 83 B_STPHY_CONS S <NA> <NA> <NA> -#> 84 B_ESCHR_COLI S S <NA> <NA> -#> 85 B_ESCHR_COLI S S <NA> <NA> -#> 86 B_ESCHR_COLI S S <NA> <NA> -#> 87 B_ESCHR_COLI S S <NA> <NA> -#> 88 B_ESCHR_COLI S S <NA> <NA> -#> 89 B_ESCHR_COLI S S <NA> <NA> -#> 90 B_STRPT_SLVR R R R R -#> 91 B_STRPT_SLVR R R R R -#> 92 B_STPHY_AURS S <NA> <NA> <NA> -#> 93 B_STPHY_CONS S <NA> <NA> <NA> -#> 94 B_STPHY_AURS S <NA> <NA> <NA> -#> 95 B_STPHY_AURS S <NA> <NA> <NA> -#> 96 B_CMPYL_JEJN <NA> <NA> <NA> <NA> -#> 97 B_STPHY_EPDR S S <NA> <NA> -#> 98 B_MCRCCC S R <NA> <NA> -#> 99 B_STPHY_EPDR S <NA> <NA> <NA> -#> 100 B_STRPT_PNMN R R R R -#> 101 B_ACNTB S S <NA> <NA> -#> 102 B_STPHY_AURS S <NA> <NA> <NA> -#> 103 B_STPHY_AURS S <NA> <NA> <NA> -#> 104 B_STPHY_AURS S <NA> <NA> <NA> -#> 105 B_STPHY_AURS S <NA> <NA> <NA> -#> 106 B_STPHY_AURS S <NA> <NA> <NA> -#> 107 B_STPHY_AURS S <NA> <NA> <NA> -#> 108 B_STPHY_EPDR R R R R -#> 109 B_STRPT_PNMN R R R R -#> 110 B_STRPT_PNMN R R R R -#> 111 B_STPHY_CONS R R R R -#> 112 B_STPHY_CONS S <NA> <NA> <NA> -#> 113 B_STPHY_CONS S <NA> <NA> <NA> -#> 114 B_STPHY_CONS S <NA> <NA> <NA> -#> 115 B_STPHY_HMNS S <NA> <NA> <NA> -#> 116 B_PROTS_MRBL S S <NA> <NA> -#> 117 B_BCTRD_FRGL <NA> <NA> <NA> <NA> -#> 118 B_PROTS_MRBL S S <NA> <NA> -#> 119 B_ESCHR_COLI S S <NA> <NA> -#> 120 B_ESCHR_COLI S S <NA> <NA> -#> 121 B_ESCHR_COLI S S <NA> <NA> -#> 122 B_ESCHR_COLI S S <NA> <NA> -#> 123 B_STPHY_EPDR R R R R -#> 124 B_STPHY_EPDR R R R R -#> 125 B_STPHY_CONS R R R R -#> 126 B_STPHY_AURS S <NA> <NA> <NA> -#> 127 B_STPHY_CONS S <NA> <NA> <NA> -#> 128 B_STPHY_CONS S <NA> <NA> <NA> -#> 129 B_ESCHR_COLI S S <NA> <NA> -#> 130 B_ESCHR_COLI S S <NA> <NA> -#> 131 B_STPHY_AURS S <NA> <NA> <NA> -#> 132 B_STPHY_AURS S <NA> <NA> <NA> -#> 133 B_STPHY_CONS S <NA> <NA> <NA> -#> 134 B_STRPT_PNMN R R R R -#> 135 B_CRYNB <NA> <NA> <NA> <NA> -#> 136 B_STRPT_PNMN R R R R -#> 137 B_STPHY_CONS S <NA> <NA> <NA> -#> 138 B_STPHY_CONS S <NA> <NA> <NA> -#> 139 B_ESCHR_COLI S S <NA> <NA> -#> 140 B_STPHY_HMNS R R R R -#> 141 B_STPHY_CONS R R R R -#> 142 B_STPHY_EPDR S <NA> <NA> <NA> -#> 143 B_ESCHR_COLI S S <NA> <NA> -#> 144 B_STPHY_AURS S <NA> <NA> <NA> -#> 145 B_STPHY_CONS R R R R -#> 146 B_STPHY_CONS R R R R -#> 147 B_STRPT_PNMN R R R R -#> 148 B_STRPT_PNMN R R R R -#> 149 B_STRPT_PNMN R R R R -#> 150 B_STRPT_PNMN R R R R -#> 151 B_STPHY_AURS S <NA> <NA> <NA> -#> 152 B_STPHY_AURS S <NA> <NA> <NA> -#> 153 B_STRPT_PYGN R R R R -#> 154 B_STRPT_GRPA R R R R -#> 155 B_STRPT_GRPA R R R R -#> 156 B_STPHY_CONS S <NA> <NA> <NA> -#> 157 B_STPHY_CONS S <NA> <NA> <NA> -#> 158 B_STPHY_AURS S <NA> <NA> <NA> -#> 159 B_STPHY_AURS S <NA> <NA> <NA> -#> 160 B_ENTRC <NA> <NA> <NA> <NA> -#> 161 B_STPHY_CONS R R R R -#> 162 B_ENTRC <NA> <NA> <NA> <NA> -#> 163 B_STPHY_CONS R R R R -#> 164 B_STPHY_CONS I <NA> <NA> <NA> -#> 165 B_STPHY_CONS I <NA> <NA> <NA> -#> 166 B_STPHY_CONS R R R R -#> 167 B_CRYNB <NA> <NA> <NA> <NA> -#> 168 B_STPHY_EPDR R R R R -#> 169 B_STPHY_EPDR S <NA> <NA> <NA> -#> 170 B_STPHY_CONS S <NA> <NA> <NA> -#> 171 B_STPHY_HMNS S <NA> <NA> <NA> -#> 172 B_STPHY_CONS S <NA> <NA> <NA> -#> 173 B_HMPHL_PRNF <NA> <NA> <NA> <NA> -#> 174 B_STPHY_AURS S <NA> <NA> <NA> -#> 175 B_STPHY_AURS S <NA> <NA> <NA> -#> 176 B_ESCHR_COLI S S <NA> <NA> -#> 177 B_STRPT_PNMN R R R R -#> 178 B_STPHY_AURS S <NA> <NA> <NA> -#> 179 B_STRPT_MITS R R R R -#> 180 B_STRPT_MITS R R R R -#> 181 B_STPHY_CONS S <NA> <NA> <NA> -#> 182 B_STPHY_CONS S <NA> <NA> <NA> -#> 183 B_ESCHR_COLI S S <NA> <NA> -#> 184 B_ESCHR_COLI S S <NA> <NA> -#> 185 B_STPHY_EPDR S <NA> <NA> <NA> -#> 186 B_STPHY_CONS S <NA> <NA> <NA> -#> 187 B_STPHY_CONS R R R R -#> 188 B_STPHY_CONS S <NA> <NA> <NA> -#> 189 B_STPHY_EPDR S <NA> <NA> <NA> -#> 190 B_STPHY_EPDR R R R R -#> 191 B_STPHY_AURS S <NA> <NA> <NA> -#> 192 B_STPHY_CONS S <NA> <NA> <NA> -#> 193 B_STRPT_PNMN R R R R -#> 194 B_KLBSL_PNMN S S <NA> <NA> -#> 195 B_KLBSL_PNMN S S <NA> <NA> -#> 196 B_STPHY_CONS S <NA> <NA> <NA> -#> 197 B_STPHY_CONS S <NA> <NA> <NA> -#> 198 B_STPHY_CONS S <NA> <NA> <NA> -#> 199 B_ESCHR_COLI S S <NA> <NA> -#> 200 B_STPHY_AURS S <NA> <NA> <NA> -#> [ reached 'max' / getOption("max.print") -- omitted 1800 rows ]
        + # filter using any() or all() example_isolates[any(carbapenems() == "R"), ] -
        #> ℹ Assuming a filter on all 2 carbapenems. Wrap around `all()` or `any()` to -#> prevent this note.
        #> date hospital_id ward_icu ward_clinical ward_outpatient age gender -#> 381 2004-11-03 B TRUE FALSE FALSE 80 F -#> 461 2005-04-21 B TRUE FALSE FALSE 82 F -#> 462 2005-04-22 B TRUE FALSE FALSE 82 F -#> 463 2005-04-22 B TRUE FALSE FALSE 82 F -#> 698 2007-02-21 D FALSE TRUE FALSE 61 F -#> 799 2007-12-15 A FALSE TRUE FALSE 72 M -#> 918 2008-12-06 D FALSE TRUE FALSE 43 F -#> 1147 2011-03-16 B TRUE TRUE FALSE 83 M -#> 1149 2011-03-19 B TRUE TRUE FALSE 83 M -#> 1156 2011-04-06 D TRUE TRUE FALSE 74 M -#> 1157 2011-04-11 C FALSE TRUE FALSE 74 M -#> 1172 2011-05-09 D TRUE TRUE FALSE 82 F -#> 1210 2011-08-01 D FALSE TRUE FALSE 63 M -#> 1213 2011-08-18 B FALSE TRUE FALSE 75 F -#> 1217 2011-09-01 B FALSE TRUE FALSE 71 M -#> 1218 2011-09-01 B FALSE TRUE FALSE 71 M -#> 1242 2011-11-04 D FALSE TRUE FALSE 70 M -#> 1243 2011-11-07 D FALSE TRUE FALSE 70 M -#> 1246 2011-11-10 D FALSE TRUE FALSE 90 F -#> 1259 2012-02-06 D TRUE TRUE FALSE 80 M -#> patient_id mo PEN OXA FLC AMX AMC AMP TZP CZO FEP CXM -#> 381 D65308 B_STNTR_MLTP R <NA> <NA> R R R R R <NA> R -#> 461 452212 B_ENTRC <NA> <NA> <NA> <NA> <NA> <NA> R <NA> <NA> <NA> -#> 462 452212 B_ENTRC <NA> <NA> <NA> <NA> <NA> <NA> R <NA> <NA> <NA> -#> 463 452212 B_ENTRC_FACM <NA> <NA> <NA> <NA> <NA> <NA> R R R R -#> 698 8BBC46 B_ENTRC_FACM <NA> <NA> <NA> <NA> <NA> <NA> R R R R -#> 799 401043 B_ENTRC_FACM <NA> <NA> <NA> <NA> <NA> <NA> R R R R -#> 918 501361 B_STNTR_MLTP R <NA> <NA> R R R R R <NA> R -#> 1147 0D7D34 B_STPHY_EPDR R R R R R R R R R R -#> 1149 0D7D34 B_STPHY_EPDR R R R R R R R R R R -#> 1156 329273 B_STPHY_CONS R R R R R R R R R R -#> 1157 A26784 B_STPHY_CONS R R R R R R R R R R -#> 1172 207325 B_ENTRC_FACM <NA> <NA> <NA> <NA> <NA> <NA> R R R R -#> 1210 F8DB34 B_STPHY_CONS R R R R R R R R R R -#> 1213 A81782 B_STPHY_CONS R R R R R R R R R R -#> 1217 50C8DB B_STPHY_EPDR R R R R R R R R R R -#> 1218 50C8DB B_STPHY_CONS R R R R R R R R R R -#> 1242 443847 B_STPHY_CONS R R R R R R R R R R -#> 1243 116866 B_STPHY_CONS R R R R R R R R R R -#> 1246 F86227 B_STPHY_CONS R R R R R R R R R R -#> 1259 967247 B_STPHY_CONS R R R R R R R R R R -#> FOX CTX CAZ CRO GEN TOB AMK KAN TMP SXT NIT FOS LNZ CIP MFX -#> 381 R R R R R R R R R S <NA> R R <NA> <NA> -#> 461 <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> -#> 462 <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> -#> 463 R R R R R R R R R R <NA> <NA> <NA> <NA> <NA> -#> 698 R R R R R R R R R R <NA> <NA> <NA> <NA> <NA> -#> 799 R R R R R R R R R R <NA> <NA> <NA> R <NA> -#> 918 R R R R R R R R R S R R R S <NA> -#> 1147 R R R R I <NA> <NA> <NA> R <NA> <NA> <NA> <NA> S <NA> -#> 1149 R R R R I <NA> <NA> <NA> R <NA> <NA> <NA> <NA> S <NA> -#> 1156 R R R R S <NA> <NA> <NA> R R <NA> <NA> <NA> R <NA> -#> 1157 R R R R I <NA> <NA> <NA> R <NA> <NA> <NA> <NA> I <NA> -#> 1172 R R R R R R R R R R <NA> <NA> <NA> <NA> <NA> -#> 1210 R R R R S <NA> <NA> <NA> R R <NA> <NA> <NA> R <NA> -#> 1213 R R R R S <NA> <NA> <NA> R <NA> <NA> <NA> <NA> R <NA> -#> 1217 R R R R I <NA> <NA> <NA> R <NA> <NA> <NA> <NA> S <NA> -#> 1218 R R R R S <NA> <NA> <NA> S S <NA> <NA> <NA> S <NA> -#> 1242 R R R R S <NA> <NA> <NA> S S <NA> <NA> <NA> S <NA> -#> 1243 R R R R S <NA> <NA> <NA> R S <NA> <NA> <NA> R <NA> -#> 1246 R R R R S <NA> <NA> <NA> R R <NA> <NA> <NA> R <NA> -#> 1259 R R R R S <NA> <NA> <NA> R R <NA> <NA> <NA> R <NA> -#> VAN TEC TCY TGC DOX ERY CLI AZM IPM MEM MTR CHL COL MUP RIF -#> 381 R R R <NA> R R R R R R <NA> <NA> R <NA> R -#> 461 S <NA> R <NA> <NA> R <NA> R R R <NA> <NA> R <NA> <NA> -#> 462 S <NA> R <NA> <NA> R <NA> R R R <NA> <NA> R <NA> <NA> -#> 463 S <NA> R <NA> <NA> R R R R R <NA> <NA> R <NA> <NA> -#> 698 S <NA> S <NA> <NA> R R R R R <NA> <NA> R <NA> <NA> -#> 799 S <NA> S <NA> <NA> R R R R R <NA> <NA> R <NA> <NA> -#> 918 R R R <NA> R R R R R R <NA> <NA> R <NA> R -#> 1147 S <NA> <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> 1149 S <NA> <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> 1156 S <NA> <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> 1157 S <NA> <NA> <NA> S R S R R R <NA> <NA> R <NA> <NA> -#> 1172 S <NA> <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> 1210 S <NA> <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> 1213 S <NA> <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> 1217 S <NA> <NA> <NA> S S S S R R <NA> <NA> R <NA> S -#> 1218 S <NA> <NA> <NA> S R S R R R <NA> <NA> R <NA> S -#> 1242 S <NA> <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> 1243 S <NA> <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> 1246 S <NA> <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> 1259 S <NA> <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> [ reached 'max' / getOption("max.print") -- omitted 29 rows ]
        subset(example_isolates, any(carbapenems() == "R")) -
        #> ℹ Assuming a filter on all 2 carbapenems. Wrap around `all()` or `any()` to -#> prevent this note.
        #> date hospital_id ward_icu ward_clinical ward_outpatient age gender -#> 381 2004-11-03 B TRUE FALSE FALSE 80 F -#> 461 2005-04-21 B TRUE FALSE FALSE 82 F -#> 462 2005-04-22 B TRUE FALSE FALSE 82 F -#> 463 2005-04-22 B TRUE FALSE FALSE 82 F -#> 698 2007-02-21 D FALSE TRUE FALSE 61 F -#> 799 2007-12-15 A FALSE TRUE FALSE 72 M -#> 918 2008-12-06 D FALSE TRUE FALSE 43 F -#> 1147 2011-03-16 B TRUE TRUE FALSE 83 M -#> 1149 2011-03-19 B TRUE TRUE FALSE 83 M -#> 1156 2011-04-06 D TRUE TRUE FALSE 74 M -#> 1157 2011-04-11 C FALSE TRUE FALSE 74 M -#> 1172 2011-05-09 D TRUE TRUE FALSE 82 F -#> 1210 2011-08-01 D FALSE TRUE FALSE 63 M -#> 1213 2011-08-18 B FALSE TRUE FALSE 75 F -#> 1217 2011-09-01 B FALSE TRUE FALSE 71 M -#> 1218 2011-09-01 B FALSE TRUE FALSE 71 M -#> 1242 2011-11-04 D FALSE TRUE FALSE 70 M -#> 1243 2011-11-07 D FALSE TRUE FALSE 70 M -#> 1246 2011-11-10 D FALSE TRUE FALSE 90 F -#> 1259 2012-02-06 D TRUE TRUE FALSE 80 M -#> patient_id mo PEN OXA FLC AMX AMC AMP TZP CZO FEP CXM -#> 381 D65308 B_STNTR_MLTP R <NA> <NA> R R R R R <NA> R -#> 461 452212 B_ENTRC <NA> <NA> <NA> <NA> <NA> <NA> R <NA> <NA> <NA> -#> 462 452212 B_ENTRC <NA> <NA> <NA> <NA> <NA> <NA> R <NA> <NA> <NA> -#> 463 452212 B_ENTRC_FACM <NA> <NA> <NA> <NA> <NA> <NA> R R R R -#> 698 8BBC46 B_ENTRC_FACM <NA> <NA> <NA> <NA> <NA> <NA> R R R R -#> 799 401043 B_ENTRC_FACM <NA> <NA> <NA> <NA> <NA> <NA> R R R R -#> 918 501361 B_STNTR_MLTP R <NA> <NA> R R R R R <NA> R -#> 1147 0D7D34 B_STPHY_EPDR R R R R R R R R R R -#> 1149 0D7D34 B_STPHY_EPDR R R R R R R R R R R -#> 1156 329273 B_STPHY_CONS R R R R R R R R R R -#> 1157 A26784 B_STPHY_CONS R R R R R R R R R R -#> 1172 207325 B_ENTRC_FACM <NA> <NA> <NA> <NA> <NA> <NA> R R R R -#> 1210 F8DB34 B_STPHY_CONS R R R R R R R R R R -#> 1213 A81782 B_STPHY_CONS R R R R R R R R R R -#> 1217 50C8DB B_STPHY_EPDR R R R R R R R R R R -#> 1218 50C8DB B_STPHY_CONS R R R R R R R R R R -#> 1242 443847 B_STPHY_CONS R R R R R R R R R R -#> 1243 116866 B_STPHY_CONS R R R R R R R R R R -#> 1246 F86227 B_STPHY_CONS R R R R R R R R R R -#> 1259 967247 B_STPHY_CONS R R R R R R R R R R -#> FOX CTX CAZ CRO GEN TOB AMK KAN TMP SXT NIT FOS LNZ CIP MFX -#> 381 R R R R R R R R R S <NA> R R <NA> <NA> -#> 461 <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> -#> 462 <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> <NA> -#> 463 R R R R R R R R R R <NA> <NA> <NA> <NA> <NA> -#> 698 R R R R R R R R R R <NA> <NA> <NA> <NA> <NA> -#> 799 R R R R R R R R R R <NA> <NA> <NA> R <NA> -#> 918 R R R R R R R R R S R R R S <NA> -#> 1147 R R R R I <NA> <NA> <NA> R <NA> <NA> <NA> <NA> S <NA> -#> 1149 R R R R I <NA> <NA> <NA> R <NA> <NA> <NA> <NA> S <NA> -#> 1156 R R R R S <NA> <NA> <NA> R R <NA> <NA> <NA> R <NA> -#> 1157 R R R R I <NA> <NA> <NA> R <NA> <NA> <NA> <NA> I <NA> -#> 1172 R R R R R R R R R R <NA> <NA> <NA> <NA> <NA> -#> 1210 R R R R S <NA> <NA> <NA> R R <NA> <NA> <NA> R <NA> -#> 1213 R R R R S <NA> <NA> <NA> R <NA> <NA> <NA> <NA> R <NA> -#> 1217 R R R R I <NA> <NA> <NA> R <NA> <NA> <NA> <NA> S <NA> -#> 1218 R R R R S <NA> <NA> <NA> S S <NA> <NA> <NA> S <NA> -#> 1242 R R R R S <NA> <NA> <NA> S S <NA> <NA> <NA> S <NA> -#> 1243 R R R R S <NA> <NA> <NA> R S <NA> <NA> <NA> R <NA> -#> 1246 R R R R S <NA> <NA> <NA> R R <NA> <NA> <NA> R <NA> -#> 1259 R R R R S <NA> <NA> <NA> R R <NA> <NA> <NA> R <NA> -#> VAN TEC TCY TGC DOX ERY CLI AZM IPM MEM MTR CHL COL MUP RIF -#> 381 R R R <NA> R R R R R R <NA> <NA> R <NA> R -#> 461 S <NA> R <NA> <NA> R <NA> R R R <NA> <NA> R <NA> <NA> -#> 462 S <NA> R <NA> <NA> R <NA> R R R <NA> <NA> R <NA> <NA> -#> 463 S <NA> R <NA> <NA> R R R R R <NA> <NA> R <NA> <NA> -#> 698 S <NA> S <NA> <NA> R R R R R <NA> <NA> R <NA> <NA> -#> 799 S <NA> S <NA> <NA> R R R R R <NA> <NA> R <NA> <NA> -#> 918 R R R <NA> R R R R R R <NA> <NA> R <NA> R -#> 1147 S <NA> <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> 1149 S <NA> <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> 1156 S <NA> <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> 1157 S <NA> <NA> <NA> S R S R R R <NA> <NA> R <NA> <NA> -#> 1172 S <NA> <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> 1210 S <NA> <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> 1213 S <NA> <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> 1217 S <NA> <NA> <NA> S S S S R R <NA> <NA> R <NA> S -#> 1218 S <NA> <NA> <NA> S R S R R R <NA> <NA> R <NA> S -#> 1242 S <NA> <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> 1243 S <NA> <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> 1246 S <NA> <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> 1259 S <NA> <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> [ reached 'max' / getOption("max.print") -- omitted 29 rows ]
        +subset(example_isolates, any(carbapenems() == "R")) + # filter on any or all results in the carbapenem columns (i.e., IPM, MEM): example_isolates[any(carbapenems()), ] -
        #> ℹ Filtering any of columns 'IPM' and 'MEM' to contain value "R", "S" or "I"
        #> date hospital_id ward_icu ward_clinical ward_outpatient age gender -#> 13 2002-01-19 D FALSE TRUE FALSE 71 M -#> 14 2002-01-19 D FALSE TRUE FALSE 71 M -#> 16 2002-01-22 B TRUE FALSE FALSE 50 M -#> 17 2002-01-22 B TRUE FALSE FALSE 50 M -#> 22 2002-02-05 B TRUE FALSE FALSE 45 F -#> 23 2002-02-05 B TRUE FALSE FALSE 45 F -#> 24 2002-02-05 B TRUE FALSE FALSE 45 F -#> 33 2002-02-27 D FALSE TRUE FALSE 85 F -#> 34 2002-02-27 D FALSE TRUE FALSE 85 F -#> 35 2002-03-08 C FALSE TRUE FALSE 69 M -#> 36 2002-03-16 C FALSE TRUE FALSE 69 M -#> 38 2002-04-01 B TRUE FALSE FALSE 46 F -#> 39 2002-04-01 B TRUE FALSE FALSE 46 F -#> 45 2002-04-08 A TRUE TRUE FALSE 78 M -#> 48 2002-04-14 C FALSE FALSE TRUE 73 M -#> 49 2002-04-23 B TRUE FALSE FALSE 69 F -#> 50 2002-04-23 B TRUE FALSE FALSE 69 F -#> 51 2002-04-26 D FALSE TRUE FALSE 79 M -#> 65 2002-06-05 D FALSE TRUE FALSE 20 F -#> 66 2002-06-06 D FALSE TRUE FALSE 20 F -#> patient_id mo PEN OXA FLC AMX AMC AMP TZP CZO FEP CXM FOX -#> 13 738003 B_ESCHR_COLI R <NA> <NA> <NA> I <NA> <NA> <NA> <NA> S <NA> -#> 14 738003 B_ESCHR_COLI R <NA> <NA> <NA> I <NA> <NA> <NA> <NA> S <NA> -#> 16 F35553 B_PROTS_MRBL R <NA> <NA> <NA> I <NA> <NA> <NA> <NA> S <NA> -#> 17 F35553 B_PROTS_MRBL R <NA> <NA> <NA> I <NA> <NA> <NA> <NA> S <NA> -#> 22 067927 B_SERRT_MRCS R <NA> <NA> R R R <NA> R <NA> R R -#> 23 067927 B_SERRT_MRCS R <NA> <NA> R R R <NA> R <NA> R R -#> 24 067927 B_SERRT_MRCS R <NA> <NA> R R R <NA> R <NA> R R -#> 33 066895 B_KLBSL_PNMN R <NA> <NA> R I R <NA> <NA> <NA> S <NA> -#> 34 066895 B_KLBSL_PNMN R <NA> <NA> R I R <NA> <NA> <NA> S <NA> -#> 35 4FC193 B_ESCHR_COLI R <NA> <NA> R R R <NA> <NA> <NA> R <NA> -#> 36 4FC193 B_PSDMN_AERG R <NA> <NA> R R R <NA> R <NA> R R -#> 38 496896 B_ESCHR_COLI R <NA> <NA> <NA> I <NA> <NA> <NA> <NA> I <NA> -#> 39 496896 B_ESCHR_COLI R <NA> <NA> <NA> I <NA> <NA> <NA> <NA> I <NA> -#> 45 130252 B_ENTRC_FCLS <NA> <NA> <NA> <NA> S <NA> <NA> R R R R -#> 48 F30196 B_STRPT_GRPB S <NA> S S S S S S S S S -#> 49 EE2510 B_ESCHR_COLI R <NA> <NA> <NA> I <NA> R <NA> <NA> I <NA> -#> 50 EE2510 B_ESCHR_COLI R <NA> <NA> <NA> I <NA> R <NA> <NA> I <NA> -#> 51 D10443 B_KLBSL_PNMN R <NA> <NA> R S R <NA> <NA> <NA> S <NA> -#> 65 24D393 B_ESCHR_COLI R <NA> <NA> <NA> I <NA> <NA> <NA> <NA> S <NA> -#> 66 24D393 B_ESCHR_COLI R <NA> <NA> <NA> I <NA> <NA> <NA> <NA> S <NA> -#> CTX CAZ CRO GEN TOB AMK KAN TMP SXT NIT FOS LNZ CIP MFX VAN TEC -#> 13 S <NA> S <NA> S <NA> <NA> S S <NA> <NA> R <NA> <NA> R R -#> 14 S <NA> S <NA> S <NA> <NA> S S <NA> <NA> R <NA> <NA> R R -#> 16 S S S <NA> <NA> <NA> <NA> S S R <NA> R S <NA> R R -#> 17 S S S <NA> <NA> <NA> <NA> S S R <NA> R S <NA> R R -#> 22 <NA> <NA> <NA> <NA> <NA> <NA> <NA> S S R <NA> R S <NA> R R -#> 23 <NA> <NA> <NA> <NA> <NA> <NA> <NA> S S R <NA> R S <NA> R R -#> 24 <NA> <NA> <NA> <NA> <NA> <NA> <NA> S S R <NA> R S <NA> R R -#> 33 S S S S S <NA> <NA> S S S <NA> R S <NA> R R -#> 34 S S S S S <NA> <NA> S S S <NA> R S <NA> R R -#> 35 S S S S <NA> <NA> <NA> S S <NA> <NA> R S <NA> R R -#> 36 R R R I S <NA> R R R <NA> <NA> R I <NA> R R -#> 38 S S S S S <NA> <NA> S S S <NA> R S <NA> R R -#> 39 S S S S S <NA> <NA> S S S <NA> R S <NA> R R -#> 45 R R R R R R R R R <NA> <NA> <NA> <NA> <NA> S <NA> -#> 48 S R S R R R R S S <NA> <NA> <NA> <NA> <NA> S <NA> -#> 49 S S S S S <NA> <NA> R R R <NA> R R R R R -#> 50 S S S S S <NA> <NA> R R R <NA> R R R R R -#> 51 S S S S S <NA> <NA> S S S <NA> R S <NA> R R -#> 65 S S S S S <NA> <NA> S S S <NA> R S <NA> R R -#> 66 S S S S S <NA> <NA> S S S <NA> R S <NA> R R -#> TCY TGC DOX ERY CLI AZM IPM MEM MTR CHL COL MUP RIF -#> 13 <NA> <NA> <NA> R R R S <NA> <NA> <NA> <NA> <NA> R -#> 14 <NA> <NA> <NA> R R R S <NA> <NA> <NA> <NA> <NA> R -#> 16 R R R R R R S <NA> <NA> <NA> R <NA> R -#> 17 R R R R R R S <NA> <NA> <NA> R <NA> R -#> 22 R R R R R R S <NA> <NA> <NA> R <NA> R -#> 23 R R R R R R S <NA> <NA> <NA> R <NA> R -#> 24 R R R R R R S <NA> <NA> <NA> R <NA> R -#> 33 <NA> <NA> <NA> R R R S <NA> <NA> <NA> <NA> <NA> R -#> 34 <NA> <NA> <NA> R R R S <NA> <NA> <NA> <NA> <NA> R -#> 35 <NA> <NA> <NA> R R R S <NA> <NA> <NA> <NA> <NA> R -#> 36 R R R R R R S <NA> <NA> R <NA> <NA> R -#> 38 <NA> <NA> <NA> R R R S <NA> <NA> <NA> <NA> <NA> R -#> 39 <NA> <NA> <NA> R R R S <NA> <NA> <NA> <NA> <NA> R -#> 45 R <NA> <NA> R R R S <NA> <NA> <NA> R <NA> <NA> -#> 48 S <NA> S S <NA> S S S <NA> <NA> R <NA> <NA> -#> 49 <NA> <NA> <NA> R R R S <NA> <NA> <NA> <NA> <NA> R -#> 50 <NA> <NA> <NA> R R R S <NA> <NA> <NA> <NA> <NA> R -#> 51 <NA> <NA> <NA> R R R S <NA> <NA> <NA> <NA> <NA> R -#> 65 <NA> <NA> <NA> R R R S <NA> <NA> <NA> <NA> <NA> R -#> 66 <NA> <NA> <NA> R R R S <NA> <NA> <NA> <NA> <NA> R -#> [ reached 'max' / getOption("max.print") -- omitted 942 rows ]
        example_isolates[all(carbapenems()), ] -
        #> ℹ Filtering all of columns 'IPM' and 'MEM' to contain value "R", "S" or "I"
        #> date hospital_id ward_icu ward_clinical ward_outpatient age gender -#> 48 2002-04-14 C FALSE FALSE TRUE 73 M -#> 153 2003-04-08 B TRUE FALSE FALSE 74 M -#> 154 2003-04-08 B TRUE FALSE FALSE 74 M -#> 155 2003-04-08 B TRUE FALSE FALSE 74 M -#> 207 2003-08-14 D FALSE TRUE FALSE 0 F -#> 237 2003-10-16 B TRUE FALSE FALSE 63 F -#> 240 2003-10-20 B TRUE FALSE FALSE 52 M -#> 242 2003-10-20 B TRUE FALSE FALSE 52 M -#> 246 2003-11-04 B TRUE FALSE FALSE 87 F -#> 247 2003-11-04 B TRUE FALSE FALSE 87 F -#> 248 2003-11-04 B TRUE FALSE FALSE 87 F -#> 251 2003-11-21 B TRUE FALSE FALSE 77 F -#> 278 2004-02-10 B TRUE FALSE FALSE 71 F -#> 279 2004-02-10 B TRUE FALSE FALSE 71 F -#> 280 2004-02-10 B TRUE FALSE FALSE 71 F -#> 298 2004-03-03 D FALSE TRUE FALSE 74 M -#> 299 2004-03-03 D FALSE TRUE FALSE 74 M -#> 309 2004-04-07 C FALSE TRUE FALSE 86 F -#> 313 2004-04-15 B TRUE FALSE FALSE 87 F -#> 314 2004-04-15 B TRUE FALSE FALSE 87 F -#> patient_id mo PEN OXA FLC AMX AMC AMP TZP CZO FEP CXM FOX -#> 48 F30196 B_STRPT_GRPB S <NA> S S S S S S S S S -#> 153 114570 B_STRPT_PYGN S <NA> S S S S S S S S S -#> 154 114570 B_STRPT_GRPA S <NA> S S S S S S S S S -#> 155 114570 B_STRPT_GRPA S <NA> S S S S S S S S S -#> 207 F71508 B_STRPT_GRPB S <NA> S S S S S S S S S -#> 237 650870 B_ESCHR_COLI R <NA> <NA> R R R S <NA> S S S -#> 240 F35553 B_ENTRBC_CLOC R <NA> <NA> R R R S R S R R -#> 242 F35553 B_ENTRBC_CLOC R <NA> <NA> R R R S R S R R -#> 246 2FC253 B_ESCHR_COLI R <NA> <NA> <NA> S <NA> S <NA> S S S -#> 247 2FC253 B_ESCHR_COLI R <NA> <NA> <NA> S <NA> S <NA> S S S -#> 248 2FC253 B_ESCHR_COLI R <NA> <NA> <NA> S <NA> S <NA> S S S -#> 251 550406 B_ESCHR_COLI R <NA> <NA> R R R S <NA> S I R -#> 278 F24801 B_STRPT_GRPB S <NA> S S S S S S S S S -#> 279 F24801 B_STRPT_AGLC S <NA> S S S S S S S S S -#> 280 F24801 B_STRPT_GRPB S <NA> S S S S S S S S S -#> 298 1435C8 B_ESCHR_COLI R <NA> <NA> S S S S <NA> S S S -#> 299 1435C8 B_ESCHR_COLI R <NA> <NA> S S S S <NA> S S S -#> 309 765860 B_STRPT_GRPA S <NA> S S S S S S S S S -#> 313 386739 B_ESCHR_COLI R <NA> <NA> R I R S <NA> S S S -#> 314 386739 B_ESCHR_COLI R <NA> <NA> R I R S <NA> S S S -#> CTX CAZ CRO GEN TOB AMK KAN TMP SXT NIT FOS LNZ CIP MFX VAN TEC -#> 48 S R S R R R R S S <NA> <NA> <NA> <NA> <NA> S <NA> -#> 153 S R S R R R R S S <NA> <NA> <NA> <NA> <NA> S <NA> -#> 154 S R S R R R R S S <NA> <NA> <NA> <NA> <NA> S <NA> -#> 155 S R S R R R R S S <NA> <NA> <NA> <NA> <NA> S <NA> -#> 207 S R S R R R R S S <NA> <NA> <NA> <NA> <NA> S <NA> -#> 237 S S S S S S <NA> <NA> S S <NA> R S <NA> R R -#> 240 <NA> <NA> <NA> S S S <NA> <NA> S R <NA> R S <NA> R R -#> 242 <NA> <NA> <NA> S S S <NA> <NA> S R <NA> R S <NA> R R -#> 246 S S S S S S <NA> <NA> S S <NA> R S <NA> R R -#> 247 S S S S S S <NA> <NA> S S <NA> R S <NA> R R -#> 248 S S S S S S <NA> <NA> S S <NA> R S <NA> R R -#> 251 S S S S S S <NA> <NA> S S <NA> R S <NA> R R -#> 278 S R S R R R R R <NA> <NA> <NA> <NA> <NA> <NA> S <NA> -#> 279 S R S R R R R R <NA> <NA> <NA> <NA> <NA> <NA> S <NA> -#> 280 S R S R R R R R <NA> <NA> <NA> <NA> <NA> <NA> S <NA> -#> 298 S S S S S S <NA> <NA> S S <NA> R S <NA> R R -#> 299 S S S S S S <NA> <NA> S S <NA> R S <NA> R R -#> 309 S R S R R R R S S <NA> <NA> <NA> <NA> <NA> S <NA> -#> 313 S S S S S S <NA> <NA> S S <NA> R S <NA> R R -#> 314 S S S S S S <NA> <NA> S S <NA> R S <NA> R R -#> TCY TGC DOX ERY CLI AZM IPM MEM MTR CHL COL MUP RIF -#> 48 S <NA> S S <NA> S S S <NA> <NA> R <NA> <NA> -#> 153 S <NA> S S S S S S <NA> <NA> R <NA> <NA> -#> 154 S <NA> S S S S S S <NA> <NA> R <NA> <NA> -#> 155 S <NA> S S S S S S <NA> <NA> R <NA> <NA> -#> 207 R <NA> <NA> S <NA> S S S <NA> <NA> R <NA> <NA> -#> 237 <NA> <NA> <NA> R R R S S <NA> <NA> <NA> <NA> R -#> 240 <NA> <NA> <NA> R R R S S <NA> <NA> <NA> <NA> R -#> 242 <NA> <NA> <NA> R R R S S <NA> <NA> <NA> <NA> R -#> 246 <NA> <NA> <NA> R R R S S <NA> <NA> <NA> <NA> R -#> 247 <NA> <NA> <NA> R R R S S <NA> <NA> <NA> <NA> R -#> 248 <NA> <NA> <NA> R R R S S <NA> <NA> <NA> <NA> R -#> 251 <NA> <NA> <NA> R R R S S <NA> <NA> <NA> <NA> R -#> 278 R <NA> <NA> S <NA> S S S <NA> <NA> R <NA> <NA> -#> 279 R <NA> <NA> S <NA> S S S <NA> <NA> R <NA> <NA> -#> 280 R <NA> <NA> S <NA> S S S <NA> <NA> R <NA> <NA> -#> 298 <NA> <NA> <NA> R R R S S <NA> <NA> <NA> <NA> R -#> 299 <NA> <NA> <NA> R R R S S <NA> <NA> <NA> <NA> R -#> 309 R <NA> <NA> S S S S S <NA> <NA> R <NA> <NA> -#> 313 <NA> <NA> <NA> R R R S S <NA> <NA> <NA> <NA> R -#> 314 <NA> <NA> <NA> R R R S S <NA> <NA> <NA> <NA> R -#> [ reached 'max' / getOption("max.print") -- omitted 736 rows ]
        +example_isolates[all(carbapenems()), ] + # filter with multiple antibiotic selectors using c() example_isolates[all(c(carbapenems(), aminoglycosides()) == "R"), ] -
        #> ℹ Assuming a filter on all 6 carbapenems, aminoglycosides. Wrap around -#> `all()` or `any()` to prevent this note.
        #> date hospital_id ward_icu ward_clinical ward_outpatient age gender -#> 381 2004-11-03 B TRUE FALSE FALSE 80 F -#> 463 2005-04-22 B TRUE FALSE FALSE 82 F -#> 698 2007-02-21 D FALSE TRUE FALSE 61 F -#> 799 2007-12-15 A FALSE TRUE FALSE 72 M -#> 918 2008-12-06 D FALSE TRUE FALSE 43 F -#> 1172 2011-05-09 D TRUE TRUE FALSE 82 F -#> 1262 2012-03-12 B TRUE TRUE FALSE 80 M -#> 1281 2012-05-19 A FALSE FALSE TRUE 89 F -#> 1302 2012-07-17 D TRUE TRUE FALSE 83 M -#> 1307 2012-07-20 D FALSE TRUE FALSE 66 F -#> 1308 2012-07-20 D FALSE TRUE FALSE 66 F -#> 1324 2012-09-18 D FALSE TRUE FALSE 62 M -#> 1328 2012-10-04 D FALSE TRUE FALSE 62 M -#> 1334 2012-10-18 D TRUE TRUE FALSE 65 F -#> 1449 2014-01-14 B FALSE TRUE FALSE 81 M -#> 1450 2014-01-14 B FALSE TRUE FALSE 81 M -#> 1624 2015-10-06 B TRUE TRUE FALSE 79 F -#> 1625 2015-10-07 B TRUE TRUE FALSE 79 F -#> 1626 2015-10-07 B TRUE TRUE FALSE 79 F -#> 1690 2016-03-27 D FALSE TRUE FALSE 47 M -#> patient_id mo PEN OXA FLC AMX AMC AMP TZP CZO FEP CXM FOX -#> 381 D65308 B_STNTR_MLTP R <NA> <NA> R R R R R <NA> R R -#> 463 452212 B_ENTRC_FACM <NA> <NA> <NA> <NA> <NA> <NA> R R R R R -#> 698 8BBC46 B_ENTRC_FACM <NA> <NA> <NA> <NA> <NA> <NA> R R R R R -#> 799 401043 B_ENTRC_FACM <NA> <NA> <NA> <NA> <NA> <NA> R R R R R -#> 918 501361 B_STNTR_MLTP R <NA> <NA> R R R R R <NA> R R -#> 1172 207325 B_ENTRC_FACM <NA> <NA> <NA> <NA> <NA> <NA> R R R R R -#> 1262 582258 B_STPHY_CONS R R R R R R R R R R R -#> 1281 C25552 B_STPHY_CONS R R R R R R R R R R R -#> 1302 F05015 B_STPHY_CONS R R R R R R R R R R R -#> 1307 404299 B_STPHY_CONS R R R R R R R R R R R -#> 1308 404299 B_STPHY_CONS R R R R R R R R R R R -#> 1324 431647 B_STPHY_CONS R R R R R R R R R R R -#> 1328 431647 B_STPHY_CONS R R R R R R R R R R R -#> 1334 E4F322 B_ENTRC_FACM R R R R R R R R R R R -#> 1449 8F77B2 B_ENTRC_FACM R R R R R R R R R R R -#> 1450 8F77B2 B_ENTRC_FACM R R R R R R R R R R R -#> 1624 A76045 B_ENTRC_FACM R R R R R R R R R R R -#> 1625 A76045 B_ENTRC_FACM R R R R R R R R R R R -#> 1626 A76045 B_ENTRC_FACM R R R R R R R R R R R -#> 1690 960787 B_ENTRC_FACM R R R R R R R R R R R -#> CTX CAZ CRO GEN TOB AMK KAN TMP SXT NIT FOS LNZ CIP MFX VAN TEC -#> 381 R R R R R R R R S <NA> R R <NA> <NA> R R -#> 463 R R R R R R R R R <NA> <NA> <NA> <NA> <NA> S <NA> -#> 698 R R R R R R R R R <NA> <NA> <NA> <NA> <NA> S <NA> -#> 799 R R R R R R R R R <NA> <NA> <NA> R <NA> S <NA> -#> 918 R R R R R R R R S R R R S <NA> R R -#> 1172 R R R R R R R R R <NA> <NA> <NA> <NA> <NA> S <NA> -#> 1262 R R R R R R R R <NA> <NA> <NA> <NA> S <NA> S <NA> -#> 1281 R R R R R R R R R <NA> <NA> <NA> R <NA> S <NA> -#> 1302 R R R R R R R S S <NA> <NA> <NA> S <NA> S <NA> -#> 1307 R R R R R R R R S <NA> <NA> <NA> S <NA> <NA> <NA> -#> 1308 R R R R R R R R R <NA> <NA> <NA> R <NA> S <NA> -#> 1324 R R R R R R R R R <NA> <NA> <NA> R <NA> S <NA> -#> 1328 R R R R R R R R R S <NA> <NA> R <NA> <NA> <NA> -#> 1334 R R R R R R R R R S <NA> S <NA> <NA> S <NA> -#> 1449 R R R R R R R R R S <NA> S <NA> <NA> S S -#> 1450 R R R R R R R R R S <NA> S <NA> <NA> S S -#> 1624 R R R R R R R R R S <NA> S <NA> <NA> S S -#> 1625 R R R R R R R R R S <NA> S <NA> <NA> S S -#> 1626 R R R R R R R R R S <NA> S <NA> <NA> S S -#> 1690 R R R R R R R R R S <NA> S <NA> <NA> S S -#> TCY TGC DOX ERY CLI AZM IPM MEM MTR CHL COL MUP RIF -#> 381 R <NA> R R R R R R <NA> <NA> R <NA> R -#> 463 R <NA> <NA> R R R R R <NA> <NA> R <NA> <NA> -#> 698 S <NA> <NA> R R R R R <NA> <NA> R <NA> <NA> -#> 799 S <NA> <NA> R R R R R <NA> <NA> R <NA> <NA> -#> 918 R <NA> R R R R R R <NA> <NA> R <NA> R -#> 1172 <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> 1262 <NA> <NA> S R R R R R <NA> <NA> R <NA> <NA> -#> 1281 <NA> <NA> <NA> R R R R R <NA> <NA> R <NA> <NA> -#> 1302 <NA> <NA> R R R R R R <NA> <NA> R <NA> <NA> -#> 1307 <NA> <NA> R R R R R R <NA> <NA> R <NA> <NA> -#> 1308 <NA> <NA> S R S R R R <NA> <NA> R <NA> <NA> -#> 1324 <NA> <NA> R R S R R R <NA> <NA> R <NA> <NA> -#> 1328 R <NA> R R R R R R <NA> <NA> R S S -#> 1334 <NA> <NA> <NA> R R R R R <NA> <NA> R <NA> <NA> -#> 1449 <NA> S <NA> R R R R R <NA> <NA> R <NA> <NA> -#> 1450 <NA> S <NA> R R R R R <NA> <NA> R <NA> <NA> -#> 1624 <NA> S <NA> R R R R R <NA> <NA> R <NA> <NA> -#> 1625 <NA> S <NA> R R R R R <NA> <NA> R <NA> <NA> -#> 1626 <NA> S <NA> R R R R R <NA> <NA> R <NA> <NA> -#> 1690 <NA> S <NA> R R R R R <NA> <NA> R <NA> <NA> -#> [ reached 'max' / getOption("max.print") -- omitted 6 rows ]
        + # filter + select in one go: get penicillins in carbapenems-resistant strains example_isolates[any(carbapenems() == "R"), penicillins()] -
        #> ℹ For `penicillins()` using columns: 'AMC' (amoxicillin/clavulanic acid), -#> 'AMP' (ampicillin), 'AMX' (amoxicillin), 'FLC' (flucloxacillin), 'OXA' -#> (oxacillin), 'PEN' (benzylpenicillin) and 'TZP' (piperacillin/tazobactam)
        #> ℹ Assuming a filter on all 2 carbapenems. Wrap around `all()` or `any()` to -#> prevent this note.
        #> PEN OXA FLC AMX AMC AMP TZP -#> 381 R <NA> <NA> R R R R -#> 461 <NA> <NA> <NA> <NA> <NA> <NA> R -#> 462 <NA> <NA> <NA> <NA> <NA> <NA> R -#> 463 <NA> <NA> <NA> <NA> <NA> <NA> R -#> 698 <NA> <NA> <NA> <NA> <NA> <NA> R -#> 799 <NA> <NA> <NA> <NA> <NA> <NA> R -#> 918 R <NA> <NA> R R R R -#> 1147 R R R R R R R -#> 1149 R R R R R R R -#> 1156 R R R R R R R -#> 1157 R R R R R R R -#> 1172 <NA> <NA> <NA> <NA> <NA> <NA> R -#> 1210 R R R R R R R -#> 1213 R R R R R R R -#> 1217 R R R R R R R -#> 1218 R R R R R R R -#> 1242 R R R R R R R -#> 1243 R R R R R R R -#> 1246 R R R R R R R -#> 1259 R R R R R R R -#> 1260 R R R R R R R -#> 1262 R R R R R R R -#> 1268 R R R R R R R -#> 1269 R R R R R R R -#> 1281 R R R R R R R -#> 1302 R R R R R R R -#> 1307 R R R R R R R -#> 1308 R R R R R R R -#> 1311 R R R R R R R -#> 1315 R R R R R R R -#> 1321 R R R R R R R -#> 1324 R R R R R R R -#> 1326 R R R R R R R -#> 1328 R R R R R R R -#> 1334 R R R R R R R -#> 1346 <NA> <NA> <NA> R R R R -#> 1449 R R R R R R R -#> 1450 R R R R R R R -#> 1624 R R R R R R R -#> 1625 R R R R R R R -#> 1626 R R R R R R R -#> 1690 R R R R R R R -#> 1693 R R R R R R R -#> 1696 R R R R R R R -#> 1723 R R R R R R R -#> 1906 R R R R R R R -#> 1908 R R R R R R R -#> 1929 R R R R R R R -#> 1945 R R R R R R R
        + # dplyr ------------------------------------------------------------------- # \donttest{ @@ -1554,7 +418,6 @@ The lifecycle of this function is stableexample_isolates %>% select(mo, ab_class("mycobact")) - # get bug/drug combinations for only macrolides in Gram-positives: example_isolates %>% filter(mo_is_gram_positive()) %>% @@ -1562,20 +425,18 @@ The lifecycle of this function is stablebug_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")) } -
        #> Error:
        # } -
        +# } + @@ -321,6 +321,8 @@
      • cephalosporins_1st
        (cefacetrile, cefadroxil, cefaloridine, cefatrizine, cefazedone, cefazolin, cefroxadine, ceftezole, cephalexin, cephalothin, cephapirin, cephradine)

      • cephalosporins_2nd
        (cefaclor, cefamandole, cefmetazole, cefonicid, ceforanide, cefotetan, cefotiam, cefoxitin, cefoxitin screening, cefprozil, cefuroxime, cefuroxime axetil, loracarbef)

      • cephalosporins_3rd
        (cadazolid, cefcapene, cefcapene pivoxil, cefdinir, cefditoren, cefditoren pivoxil, cefetamet, cefetamet pivoxil, cefixime, cefmenoxime, cefodizime, cefoperazone, cefoperazone/sulbactam, cefotaxime, cefotaxime/clavulanic acid, cefotaxime/sulbactam, cefotiam hexetil, cefovecin, cefpimizole, cefpiramide, cefpodoxime, cefpodoxime proxetil, cefpodoxime/clavulanic acid, cefsulodin, ceftazidime, ceftazidime/avibactam, ceftazidime/clavulanic acid, cefteram, cefteram pivoxil, ceftibuten, ceftiofur, ceftizoxime, ceftizoxime alapivoxil, ceftriaxone, latamoxef)

      • +
      • cephalosporins_4th
        (cefepime, cefepime/clavulanic acid, cefepime/tazobactam, cefetecol (Cefcatacol), cefoselis, cefozopran, cefpirome, cefquinome)

      • +
      • cephalosporins_5th
        (ceftaroline, ceftaroline/avibactam, ceftobiprole, ceftobiprole medocaril, ceftolozane/enzyme inhibitor, ceftolozane/tazobactam)

      • cephalosporins_except_caz
        (cadazolid, cefacetrile, cefaclor, cefadroxil, cefaloridine, cefamandole, cefatrizine, cefazedone, cefazolin, cefcapene, cefcapene pivoxil, cefdinir, cefditoren, cefditoren pivoxil, cefepime, cefepime/clavulanic acid, cefepime/tazobactam, cefetamet, cefetamet pivoxil, cefetecol (Cefcatacol), 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/avibactam, ceftazidime/clavulanic acid, cefteram, cefteram pivoxil, ceftezole, ceftibuten, ceftiofur, ceftizoxime, ceftizoxime alapivoxil, ceftobiprole, ceftobiprole medocaril, ceftolozane/enzyme inhibitor, ceftolozane/tazobactam, ceftriaxone, cefuroxime, cefuroxime axetil, cephalexin, cephalothin, cephapirin, cephradine, latamoxef, loracarbef)

      • fluoroquinolones
        (ciprofloxacin, enoxacin, fleroxacin, gatifloxacin, gemifloxacin, grepafloxacin, levofloxacin, lomefloxacin, moxifloxacin, norfloxacin, ofloxacin, pazufloxacin, pefloxacin, prulifloxacin, rufloxacin, sparfloxacin, temafloxacin, trovafloxacin)

      • glycopeptides
        (avoparcin, dalbavancin, norvancomycin, oritavancin, ramoplanin, teicoplanin, teicoplanin-macromethod, telavancin, vancomycin, vancomycin-macromethod)

      • @@ -331,6 +333,7 @@
      • oxazolidinones
        (cycloserine, linezolid, tedizolid, thiacetazone)

      • penicillins
        (amoxicillin, amoxicillin/clavulanic acid, amoxicillin/sulbactam, ampicillin, ampicillin/sulbactam, apalcillin, aspoxicillin, avibactam, azidocillin, azlocillin, aztreonam, aztreonam/avibactam, bacampicillin, benzathine benzylpenicillin, benzathine phenoxymethylpenicillin, benzylpenicillin, carbenicillin, carindacillin, ciclacillin, clometocillin, cloxacillin, dicloxacillin, epicillin, flucloxacillin, hetacillin, lenampicillin, mecillinam (Amdinocillin), metampicillin, methicillin, mezlocillin, mezlocillin/sulbactam, nacubactam, nafcillin, oxacillin, penamecillin, penicillin/novobiocin, penicillin/sulbactam, phenethicillin, phenoxymethylpenicillin, piperacillin, piperacillin/sulbactam, piperacillin/tazobactam, piridicillin, pivampicillin, pivmecillinam, procaine benzylpenicillin, propicillin, sarmoxicillin, sulbactam, sulbenicillin, sultamicillin, talampicillin, tazobactam, temocillin, ticarcillin, ticarcillin/clavulanic acid)

      • polymyxins
        (colistin, polymyxin B, polymyxin B/polysorbate 80)

      • +
      • quinolones
        (besifloxacin, cinoxacin, ciprofloxacin, clinafloxacin, danofloxacin, delafloxacin, difloxacin, enoxacin, enrofloxacin, finafloxacin, fleroxacin, flumequine, garenoxacin, gatifloxacin, gemifloxacin, grepafloxacin, levofloxacin, levonadifloxacin, lomefloxacin, marbofloxacin, metioxate, miloxacin, moxifloxacin, nadifloxacin, nalidixic acid, nifuroquine, nitroxoline, norfloxacin, ofloxacin, orbifloxacin, oxolinic acid, pazufloxacin, pefloxacin, pipemidic acid, piromidic acid, pradofloxacin, premafloxacin, prulifloxacin, rosoxacin, rufloxacin, sarafloxacin, sitafloxacin, sparfloxacin, temafloxacin, tilbroquinol, tioxacin, tosufloxacin, trovafloxacin)

      • streptogramins
        (pristinamycin, quinupristin/dalfopristin)

      • tetracyclines
        (chlortetracycline, clomocycline, demeclocycline, doxycycline, eravacycline, lymecycline, metacycline, minocycline, oxytetracycline, penimepicycline, rolitetracycline, tetracycline, tigecycline)

      • tetracyclines_except_tgc
        (chlortetracycline, clomocycline, demeclocycline, doxycycline, eravacycline, lymecycline, metacycline, minocycline, oxytetracycline, penimepicycline, rolitetracycline, tetracycline)

      • diff --git a/docs/reference/index.html b/docs/reference/index.html index 3a840f2c..6685715c 100644 --- a/docs/reference/index.html +++ b/docs/reference/index.html @@ -81,7 +81,7 @@ AMR (for R) - 1.7.1 + 1.7.1.9000 @@ -526,7 +526,7 @@
        diff --git a/docs/survey.html b/docs/survey.html index 2b2e9284..7dbfb806 100644 --- a/docs/survey.html +++ b/docs/survey.html @@ -81,7 +81,7 @@ AMR (for R) - 1.7.1 + 1.7.1.9000 diff --git a/inst/tinytest/test-ab_class_selectors.R b/inst/tinytest/test-ab_class_selectors.R index 594807bd..e4167be2 100644 --- a/inst/tinytest/test-ab_class_selectors.R +++ b/inst/tinytest/test-ab_class_selectors.R @@ -23,9 +23,14 @@ # how to conduct AMR data analysis: https://msberends.github.io/AMR/ # # ==================================================================== # +if (getRversion() < "3.2") { + expect_warning(example_isolates[, aminoglycosides(), drop = FALSE]) +} if (getRversion() >= "3.2") { # antibiotic class selectors require at least R-3.2 + expect_true(ncol(example_isolates[, ab_class("antimyco"), drop = FALSE]) < ncol(example_isolates)) expect_true(ncol(example_isolates[, aminoglycosides(), drop = FALSE]) < ncol(example_isolates)) + expect_true(ncol(example_isolates[, aminopenicillins(), drop = FALSE]) < ncol(example_isolates)) expect_true(ncol(example_isolates[, betalactams(), drop = FALSE]) < ncol(example_isolates)) expect_true(ncol(example_isolates[, carbapenems(), drop = FALSE]) < ncol(example_isolates)) expect_true(ncol(example_isolates[, cephalosporins(), drop = FALSE]) < ncol(example_isolates)) @@ -36,10 +41,16 @@ if (getRversion() >= "3.2") { expect_true(ncol(example_isolates[, cephalosporins_5th(), drop = FALSE]) < ncol(example_isolates)) expect_true(ncol(example_isolates[, fluoroquinolones(), drop = FALSE]) < ncol(example_isolates)) expect_true(ncol(example_isolates[, glycopeptides(), drop = FALSE]) < ncol(example_isolates)) + expect_true(ncol(example_isolates[, lincosamides(), drop = FALSE]) < ncol(example_isolates)) + expect_true(ncol(example_isolates[, lipoglycopeptides(), drop = FALSE]) < ncol(example_isolates)) expect_true(ncol(example_isolates[, macrolides(), drop = FALSE]) < ncol(example_isolates)) expect_true(ncol(example_isolates[, oxazolidinones(), drop = FALSE]) < ncol(example_isolates)) expect_true(ncol(example_isolates[, penicillins(), drop = FALSE]) < ncol(example_isolates)) + expect_true(ncol(example_isolates[, polymyxins(), drop = FALSE]) < ncol(example_isolates)) + expect_true(ncol(example_isolates[, streptogramins(), drop = FALSE]) < ncol(example_isolates)) + expect_true(ncol(example_isolates[, quinolones(), drop = FALSE]) < ncol(example_isolates)) expect_true(ncol(example_isolates[, tetracyclines(), drop = FALSE]) < ncol(example_isolates)) + expect_true(ncol(example_isolates[, ureidopenicillins(), drop = FALSE]) < ncol(example_isolates)) # Examples: diff --git a/inst/tinytest/test-bug_drug_combinations.R b/inst/tinytest/test-bug_drug_combinations.R index f79d81f8..769961a4 100644 --- a/inst/tinytest/test-bug_drug_combinations.R +++ b/inst/tinytest/test-bug_drug_combinations.R @@ -28,3 +28,9 @@ expect_inherits(b, "bug_drug_combinations") expect_stdout(suppressMessages(print(b))) expect_true(is.data.frame(format(b))) expect_true(is.data.frame(format(b, combine_IR = TRUE, add_ab_group = FALSE))) +if (AMR:::pkg_is_available("dplyr")) { + expect_true(example_isolates %>% + group_by(hospital_id) %>% + bug_drug_combinations(FUN = mo_gramstain) %>% + is.data.frame()) +} diff --git a/inst/tinytest/test-eucast_rules.R b/inst/tinytest/test-eucast_rules.R index b2e0d607..087f51e2 100755 --- a/inst/tinytest/test-eucast_rules.R +++ b/inst/tinytest/test-eucast_rules.R @@ -24,14 +24,14 @@ # ==================================================================== # # thoroughly check input table -expect_equal(colnames(AMR:::eucast_rules_file), +expect_equal(colnames(AMR:::EUCAST_RULES_DF), c("if_mo_property", "like.is.one_of", "this_value", "and_these_antibiotics", "have_these_values", "then_change_these_antibiotics", "to_value", "reference.rule", "reference.rule_group", "reference.version", "note")) -MOs_mentioned <- unique(AMR:::eucast_rules_file$this_value) +MOs_mentioned <- unique(AMR:::EUCAST_RULES_DF$this_value) MOs_mentioned <- sort(AMR:::trimws(unlist(strsplit(MOs_mentioned[!AMR:::is_valid_regex(MOs_mentioned)], ",", fixed = TRUE)))) MOs_test <- suppressWarnings(suppressMessages(mo_name(MOs_mentioned))) expect_true(length(MOs_mentioned[MOs_test != MOs_mentioned]) == 0) diff --git a/man/antibiotic_class_selectors.Rd b/man/antibiotic_class_selectors.Rd index 083bb579..1d5c4408 100644 --- a/man/antibiotic_class_selectors.Rd +++ b/man/antibiotic_class_selectors.Rd @@ -4,6 +4,7 @@ \alias{antibiotic_class_selectors} \alias{ab_class} \alias{aminoglycosides} +\alias{aminopenicillins} \alias{betalactams} \alias{carbapenems} \alias{cephalosporins} @@ -14,16 +15,24 @@ \alias{cephalosporins_5th} \alias{fluoroquinolones} \alias{glycopeptides} +\alias{lincosamides} +\alias{lipoglycopeptides} \alias{macrolides} \alias{oxazolidinones} \alias{penicillins} +\alias{polymyxins} +\alias{streptogramins} +\alias{quinolones} \alias{tetracyclines} +\alias{ureidopenicillins} \title{Antibiotic Class Selectors} \usage{ ab_class(ab_class, only_rsi_columns = FALSE) aminoglycosides(only_rsi_columns = FALSE) +aminopenicillins(only_rsi_columns = FALSE) + betalactams(only_rsi_columns = FALSE) carbapenems(only_rsi_columns = FALSE) @@ -44,13 +53,25 @@ fluoroquinolones(only_rsi_columns = FALSE) glycopeptides(only_rsi_columns = FALSE) +lincosamides(only_rsi_columns = FALSE) + +lipoglycopeptides(only_rsi_columns = FALSE) + macrolides(only_rsi_columns = FALSE) oxazolidinones(only_rsi_columns = FALSE) penicillins(only_rsi_columns = FALSE) +polymyxins(only_rsi_columns = FALSE) + +streptogramins(only_rsi_columns = FALSE) + +quinolones(only_rsi_columns = FALSE) + tetracyclines(only_rsi_columns = FALSE) + +ureidopenicillins(only_rsi_columns = FALSE) } \arguments{ \item{ab_class}{an antimicrobial class, such as \code{"carbapenems"}. The columns \code{group}, \code{atc_group1} and \code{atc_group2} of the \link{antibiotics} data set will be searched (case-insensitive) for this value.} @@ -58,17 +79,43 @@ tetracyclines(only_rsi_columns = FALSE) \item{only_rsi_columns}{a \link{logical} to indicate whether only columns of class \verb{} must be selected (defaults to \code{FALSE}), see \code{\link[=as.rsi]{as.rsi()}}} } \description{ -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, "."), "")}} } \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 \emph{Examples}. They support base R, but work more convenient in dplyr functions such as \code{\link[dplyr:select]{select()}}, \code{\link[dplyr:filter]{filter()}} and \code{\link[dplyr:summarise]{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 \link{antibiotics} data set. This means that a selector like e.g. \code{\link[=aminoglycosides]{aminoglycosides()}} will pick up column names like 'gen', 'genta', 'J01GB03', 'tobra', 'Tobracin', etc. - -The group of betalactams consists of all carbapenems, cephalosporins and penicillins. +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 \link{antibiotics} data set. This means that a selector such as \code{\link[=aminoglycosides]{aminoglycosides()}} will pick up column names like 'gen', 'genta', 'J01GB03', 'tobra', 'Tobracin', etc. Use the \code{\link[=ab_class]{ab_class()}} function to filter/select on a manually defined antibiotic class. } +\section{Full list of supported agents}{ + +\itemize{ +\item \code{aminoglycosides()} can select amikacin (AMK), amikacin/fosfomycin (AKF), amphotericin B-high (AMH), 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{aminopenicillins()} can select amoxicillin (AMX) and ampicillin (AMP) +\item \code{betalactams()} can select 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), bacampicillin (BAM), benzathine benzylpenicillin (BNB), benzathine phenoxymethylpenicillin (BNP), benzylpenicillin (PEN), biapenem (BIA), cadazolid (CDZ), carbenicillin (CRB), carindacillin (CRN), cefacetrile (CAC), cefaclor (CEC), cefadroxil (CFR), cefaloridine (RID), cefamandole (MAN), 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/tazobactam (FPT), cefetamet (CAT), cefetamet pivoxil (CPI), cefetecol (Cefcatacol) (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/enzyme inhibitor (CEI), ceftolozane/tazobactam (CZT), ceftriaxone (CRO), cefuroxime (CXM), cefuroxime axetil (CXA), cephalexin (LEX), cephalothin (CEP), cephapirin (HAP), 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 (Amdinocillin) (MEC), meropenem (MEM), meropenem/nacubactam (MNC), meropenem/vaborbactam (MEV), metampicillin (MTM), methicillin (MET), mezlocillin (MEZ), mezlocillin/sulbactam (MSU), nacubactam (NAC), nafcillin (NAF), oxacillin (OXA), panipenem (PAN), penamecillin (PNM), penicillin/novobiocin (PNO), penicillin/sulbactam (PSU), phenethicillin (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{carbapenems()} can select 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) +\item \code{cephalosporins()} can select cadazolid (CDZ), cefacetrile (CAC), cefaclor (CEC), cefadroxil (CFR), cefaloridine (RID), cefamandole (MAN), 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/tazobactam (FPT), cefetamet (CAT), cefetamet pivoxil (CPI), cefetecol (Cefcatacol) (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/enzyme inhibitor (CEI), ceftolozane/tazobactam (CZT), ceftriaxone (CRO), cefuroxime (CXM), cefuroxime axetil (CXA), cephalexin (LEX), cephalothin (CEP), cephapirin (HAP), cephradine (CED), latamoxef (LTM) and loracarbef (LOR) +\item \code{cephalosporins_1st()} can select cefacetrile (CAC), cefadroxil (CFR), cefaloridine (RID), cefatrizine (CTZ), cefazedone (CZD), cefazolin (CZO), cefroxadine (CRD), ceftezole (CTL), cephalexin (LEX), cephalothin (CEP), cephapirin (HAP) and cephradine (CED) +\item \code{cephalosporins_2nd()} can select cefaclor (CEC), cefamandole (MAN), cefmetazole (CMZ), cefonicid (CID), ceforanide (CND), cefotetan (CTT), cefotiam (CTF), cefoxitin (FOX), cefoxitin screening (FOX1), cefprozil (CPR), cefuroxime (CXM), cefuroxime axetil (CXA) and loracarbef (LOR) +\item \code{cephalosporins_3rd()} can select cadazolid (CDZ), cefcapene (CCP), cefcapene pivoxil (CCX), cefdinir (CDR), cefditoren (DIT), cefditoren pivoxil (DIX), cefetamet (CAT), cefetamet pivoxil (CPI), cefixime (CFM), cefmenoxime (CMX), cefodizime (DIZ), cefoperazone (CFP), cefoperazone/sulbactam (CSL), cefotaxime (CTX), cefotaxime/clavulanic acid (CTC), cefotaxime/sulbactam (CTS), cefotiam hexetil (CHE), cefovecin (FOV), cefpimizole (CFZ), cefpiramide (CPM), cefpodoxime (CPD), cefpodoxime proxetil (CPX), cefpodoxime/clavulanic acid (CDC), cefsulodin (CFS), ceftazidime (CAZ), ceftazidime/avibactam (CZA), ceftazidime/clavulanic acid (CCV), cefteram (CEM), cefteram pivoxil (CPL), ceftibuten (CTB), ceftiofur (TIO), ceftizoxime (CZX), ceftizoxime alapivoxil (CZP), ceftriaxone (CRO) and latamoxef (LTM) +\item \code{cephalosporins_4th()} can select cefepime (FEP), cefepime/clavulanic acid (CPC), cefepime/tazobactam (FPT), cefetecol (Cefcatacol) (CCL), cefoselis (CSE), cefozopran (ZOP), cefpirome (CPO) and cefquinome (CEQ) +\item \code{cephalosporins_5th()} can select ceftaroline (CPT), ceftaroline/avibactam (CPA), ceftobiprole (BPR), ceftobiprole medocaril (CFM1), ceftolozane/enzyme inhibitor (CEI) and ceftolozane/tazobactam (CZT) +\item \code{fluoroquinolones()} can select ciprofloxacin (CIP), enoxacin (ENX), fleroxacin (FLE), gatifloxacin (GAT), gemifloxacin (GEM), grepafloxacin (GRX), levofloxacin (LVX), lomefloxacin (LOM), moxifloxacin (MFX), norfloxacin (NOR), ofloxacin (OFX), pazufloxacin (PAZ), pefloxacin (PEF), prulifloxacin (PRU), rufloxacin (RFL), sparfloxacin (SPX), temafloxacin (TMX) and trovafloxacin (TVA) +\item \code{glycopeptides()} can select avoparcin (AVO), dalbavancin (DAL), norvancomycin (NVA), oritavancin (ORI), ramoplanin (RAM), teicoplanin (TEC), teicoplanin-macromethod (TCM), telavancin (TLV), vancomycin (VAN) and vancomycin-macromethod (VAM) +\item \code{lincosamides()} can select clindamycin (CLI), lincomycin (LIN) and pirlimycin (PRL) +\item \code{lipoglycopeptides()} can select dalbavancin (DAL), oritavancin (ORI) and telavancin (TLV) +\item \code{macrolides()} can select azithromycin (AZM), clarithromycin (CLR), dirithromycin (DIR), erythromycin (ERY), flurithromycin (FLR1), josamycin (JOS), midecamycin (MID), miocamycin (MCM), oleandomycin (OLE), rokitamycin (ROK), roxithromycin (RXT), spiramycin (SPI), telithromycin (TLT) and troleandomycin (TRL) +\item \code{oxazolidinones()} can select cycloserine (CYC), linezolid (LNZ), tedizolid (TZD) and thiacetazone (THA) +\item \code{penicillins()} can select 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), bacampicillin (BAM), benzathine benzylpenicillin (BNB), benzathine phenoxymethylpenicillin (BNP), benzylpenicillin (PEN), carbenicillin (CRB), carindacillin (CRN), ciclacillin (CIC), clometocillin (CLM), cloxacillin (CLO), dicloxacillin (DIC), epicillin (EPC), flucloxacillin (FLC), hetacillin (HET), lenampicillin (LEN), mecillinam (Amdinocillin) (MEC), metampicillin (MTM), methicillin (MET), mezlocillin (MEZ), mezlocillin/sulbactam (MSU), nacubactam (NAC), nafcillin (NAF), oxacillin (OXA), penamecillin (PNM), penicillin/novobiocin (PNO), penicillin/sulbactam (PSU), phenethicillin (PHE), phenoxymethylpenicillin (PHN), piperacillin (PIP), piperacillin/sulbactam (PIS), piperacillin/tazobactam (TZP), piridicillin (PRC), pivampicillin (PVM), pivmecillinam (PME), procaine benzylpenicillin (PRB), propicillin (PRP), sarmoxicillin (SRX), sulbactam (SUL), sulbenicillin (SBC), sultamicillin (SLT6), talampicillin (TAL), tazobactam (TAZ), temocillin (TEM), ticarcillin (TIC) and ticarcillin/clavulanic acid (TCC) +\item \code{polymyxins()} can select colistin (COL), polymyxin B (PLB) and polymyxin B/polysorbate 80 (POP) +\item \code{streptogramins()} can select pristinamycin (PRI) and quinupristin/dalfopristin (QDA) +\item \code{quinolones()} can select besifloxacin (BES), cinoxacin (CIN), ciprofloxacin (CIP), clinafloxacin (CLX), danofloxacin (DAN), delafloxacin (DFX), difloxacin (DIF), enoxacin (ENX), enrofloxacin (ENR), finafloxacin (FIN), fleroxacin (FLE), flumequine (FLM), garenoxacin (GRN), gatifloxacin (GAT), gemifloxacin (GEM), grepafloxacin (GRX), levofloxacin (LVX), levonadifloxacin (LND), lomefloxacin (LOM), marbofloxacin (MAR), metioxate (MXT), miloxacin (MIL), moxifloxacin (MFX), nadifloxacin (NAD), nalidixic acid (NAL), nifuroquine (NIF), nitroxoline (NTR), norfloxacin (NOR), ofloxacin (OFX), orbifloxacin (ORB), oxolinic acid (OXO), pazufloxacin (PAZ), pefloxacin (PEF), pipemidic acid (PPA), piromidic acid (PIR), pradofloxacin (PRA), premafloxacin (PRX), prulifloxacin (PRU), rosoxacin (ROS), rufloxacin (RFL), sarafloxacin (SAR), sitafloxacin (SIT), sparfloxacin (SPX), temafloxacin (TMX), tilbroquinol (TBQ), tioxacin (TXC), tosufloxacin (TFX) and trovafloxacin (TVA) +\item \code{tetracyclines()} can select chlortetracycline (CTE), clomocycline (CLM1), demeclocycline (DEM), doxycycline (DOX), eravacycline (ERV), lymecycline (LYM), metacycline (MTC), minocycline (MNO), oxytetracycline (OXY), penimepicycline (PNM1), rolitetracycline (RLT), tetracycline (TCY) and tigecycline (TGC) +\item \code{ureidopenicillins()} can select azlocillin (AZL), mezlocillin (MEZ), piperacillin (PIP) and piperacillin/tazobactam (TZP) +} +} + \section{Stable Lifecycle}{ \if{html}{\figure{lifecycle_stable.svg}{options: style=margin-bottom:5px} \cr} @@ -91,7 +138,7 @@ On our website \url{https://msberends.github.io/AMR/} you can find \href{https:/ # `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()] @@ -149,7 +196,6 @@ if (require("dplyr")) { example_isolates \%>\% select(mo, ab_class("mycobact")) - # get bug/drug combinations for only macrolides in Gram-positives: example_isolates \%>\% filter(mo_is_gram_positive()) \%>\% @@ -157,14 +203,12 @@ if (require("dplyr")) { 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")) diff --git a/man/custom_eucast_rules.Rd b/man/custom_eucast_rules.Rd index 72574cc0..ee9662c5 100644 --- a/man/custom_eucast_rules.Rd +++ b/man/custom_eucast_rules.Rd @@ -76,6 +76,8 @@ It is possible to define antibiotic groups instead of single antibiotics for the \item \code{cephalosporins_1st}\cr(cefacetrile, cefadroxil, cefaloridine, cefatrizine, cefazedone, cefazolin, cefroxadine, ceftezole, cephalexin, cephalothin, cephapirin, cephradine) \item \code{cephalosporins_2nd}\cr(cefaclor, cefamandole, cefmetazole, cefonicid, ceforanide, cefotetan, cefotiam, cefoxitin, cefoxitin screening, cefprozil, cefuroxime, cefuroxime axetil, loracarbef) \item \code{cephalosporins_3rd}\cr(cadazolid, cefcapene, cefcapene pivoxil, cefdinir, cefditoren, cefditoren pivoxil, cefetamet, cefetamet pivoxil, cefixime, cefmenoxime, cefodizime, cefoperazone, cefoperazone/sulbactam, cefotaxime, cefotaxime/clavulanic acid, cefotaxime/sulbactam, cefotiam hexetil, cefovecin, cefpimizole, cefpiramide, cefpodoxime, cefpodoxime proxetil, cefpodoxime/clavulanic acid, cefsulodin, ceftazidime, ceftazidime/avibactam, ceftazidime/clavulanic acid, cefteram, cefteram pivoxil, ceftibuten, ceftiofur, ceftizoxime, ceftizoxime alapivoxil, ceftriaxone, latamoxef) +\item \code{cephalosporins_4th}\cr(cefepime, cefepime/clavulanic acid, cefepime/tazobactam, cefetecol (Cefcatacol), cefoselis, cefozopran, cefpirome, cefquinome) +\item \code{cephalosporins_5th}\cr(ceftaroline, ceftaroline/avibactam, ceftobiprole, ceftobiprole medocaril, ceftolozane/enzyme inhibitor, ceftolozane/tazobactam) \item \code{cephalosporins_except_caz}\cr(cadazolid, cefacetrile, cefaclor, cefadroxil, cefaloridine, cefamandole, cefatrizine, cefazedone, cefazolin, cefcapene, cefcapene pivoxil, cefdinir, cefditoren, cefditoren pivoxil, cefepime, cefepime/clavulanic acid, cefepime/tazobactam, cefetamet, cefetamet pivoxil, cefetecol (Cefcatacol), 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/avibactam, ceftazidime/clavulanic acid, cefteram, cefteram pivoxil, ceftezole, ceftibuten, ceftiofur, ceftizoxime, ceftizoxime alapivoxil, ceftobiprole, ceftobiprole medocaril, ceftolozane/enzyme inhibitor, ceftolozane/tazobactam, ceftriaxone, cefuroxime, cefuroxime axetil, cephalexin, cephalothin, cephapirin, cephradine, latamoxef, loracarbef) \item \code{fluoroquinolones}\cr(ciprofloxacin, enoxacin, fleroxacin, gatifloxacin, gemifloxacin, grepafloxacin, levofloxacin, lomefloxacin, moxifloxacin, norfloxacin, ofloxacin, pazufloxacin, pefloxacin, prulifloxacin, rufloxacin, sparfloxacin, temafloxacin, trovafloxacin) \item \code{glycopeptides}\cr(avoparcin, dalbavancin, norvancomycin, oritavancin, ramoplanin, teicoplanin, teicoplanin-macromethod, telavancin, vancomycin, vancomycin-macromethod) @@ -86,6 +88,7 @@ It is possible to define antibiotic groups instead of single antibiotics for the \item \code{oxazolidinones}\cr(cycloserine, linezolid, tedizolid, thiacetazone) \item \code{penicillins}\cr(amoxicillin, amoxicillin/clavulanic acid, amoxicillin/sulbactam, ampicillin, ampicillin/sulbactam, apalcillin, aspoxicillin, avibactam, azidocillin, azlocillin, aztreonam, aztreonam/avibactam, bacampicillin, benzathine benzylpenicillin, benzathine phenoxymethylpenicillin, benzylpenicillin, carbenicillin, carindacillin, ciclacillin, clometocillin, cloxacillin, dicloxacillin, epicillin, flucloxacillin, hetacillin, lenampicillin, mecillinam (Amdinocillin), metampicillin, methicillin, mezlocillin, mezlocillin/sulbactam, nacubactam, nafcillin, oxacillin, penamecillin, penicillin/novobiocin, penicillin/sulbactam, phenethicillin, phenoxymethylpenicillin, piperacillin, piperacillin/sulbactam, piperacillin/tazobactam, piridicillin, pivampicillin, pivmecillinam, procaine benzylpenicillin, propicillin, sarmoxicillin, sulbactam, sulbenicillin, sultamicillin, talampicillin, tazobactam, temocillin, ticarcillin, ticarcillin/clavulanic acid) \item \code{polymyxins}\cr(colistin, polymyxin B, polymyxin B/polysorbate 80) +\item \code{quinolones}\cr(besifloxacin, cinoxacin, ciprofloxacin, clinafloxacin, danofloxacin, delafloxacin, difloxacin, enoxacin, enrofloxacin, finafloxacin, fleroxacin, flumequine, garenoxacin, gatifloxacin, gemifloxacin, grepafloxacin, levofloxacin, levonadifloxacin, lomefloxacin, marbofloxacin, metioxate, miloxacin, moxifloxacin, nadifloxacin, nalidixic acid, nifuroquine, nitroxoline, norfloxacin, ofloxacin, orbifloxacin, oxolinic acid, pazufloxacin, pefloxacin, pipemidic acid, piromidic acid, pradofloxacin, premafloxacin, prulifloxacin, rosoxacin, rufloxacin, sarafloxacin, sitafloxacin, sparfloxacin, temafloxacin, tilbroquinol, tioxacin, tosufloxacin, trovafloxacin) \item \code{streptogramins}\cr(pristinamycin, quinupristin/dalfopristin) \item \code{tetracyclines}\cr(chlortetracycline, clomocycline, demeclocycline, doxycycline, eravacycline, lymecycline, metacycline, minocycline, oxytetracycline, penimepicycline, rolitetracycline, tetracycline, tigecycline) \item \code{tetracyclines_except_tgc}\cr(chlortetracycline, clomocycline, demeclocycline, doxycycline, eravacycline, lymecycline, metacycline, minocycline, oxytetracycline, penimepicycline, rolitetracycline, tetracycline)
        -

        ab_class() aminoglycosides() betalactams() carbapenems() cephalosporins() cephalosporins_1st() cephalosporins_2nd() cephalosporins_3rd() cephalosporins_4th() cephalosporins_5th() fluoroquinolones() glycopeptides() macrolides() oxazolidinones() penicillins() tetracyclines()

        +

        ab_class() 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()

        Antibiotic Class Selectors