diff --git a/DESCRIPTION b/DESCRIPTION index b187c2de..788d7664 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: AMR -Version: 1.5.0.9011 -Date: 2021-01-24 +Version: 1.5.0.9012 +Date: 2021-01-25 Title: Antimicrobial Resistance Analysis Authors@R: c( person(role = c("aut", "cre"), diff --git a/NEWS.md b/NEWS.md index 350e2da6..4ae399b0 100755 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,5 @@ -# AMR 1.5.0.9011 -## Last updated: 24 January 2021 +# AMR 1.5.0.9012 +## Last updated: 25 January 2021 ### New * Support for EUCAST Clinical Breakpoints v11.0 (2021), effective in the `eucast_rules()` function and in `as.rsi()` to interpret MIC and disk diffusion values. This is now the default guideline in this package. @@ -35,6 +35,7 @@ * Fix for verbose output of `mdro(..., verbose = TRUE)` for German guideline (3MGRN and 4MGRN) and Dutch guideline (BRMO, only *P. aeruginosa*) * `is.rsi.eligible()` now returns `FALSE` immediately if the input does not contain any of the values "R", "S" or "I". This drastically improves speed, also for a lot of other functions that rely on automatic determination of antibiotic columns. * Functions `get_episode()` and `is_new_episode()` now support less than a day as value for argument `episode_days` (e.g., to include one patient/test per hour) +* Argument `ampc_cephalosporin_resistance` in `eucast_rules()` now also applies to value "I" (not only "S") ### Other * Big documentation updates diff --git a/R/aa_helper_functions.R b/R/aa_helper_functions.R index b8961bb6..8b9ecb60 100755 --- a/R/aa_helper_functions.R +++ b/R/aa_helper_functions.R @@ -442,7 +442,7 @@ create_ab_documentation <- function(ab) { out } -vector_or <- function(v, quotes = TRUE, reverse = FALSE) { +vector_or <- function(v, quotes = TRUE, reverse = FALSE, last_sep = " or ") { # makes unique and sorts, and this also removed NAs v <- sort(unique(v)) if (length(v) == 1) { @@ -451,9 +451,18 @@ vector_or <- function(v, quotes = TRUE, reverse = FALSE) { if (reverse == TRUE) { v <- rev(v) } + if (identical(v, c("I", "R", "S"))) { + # class should be sorted like this + v <- c("R", "S", "I") + } + if (isTRUE(quotes)) { + quotes <- '"' + } else if (isFALSE(quotes)) { + quotes <- "" + } # all commas except for last item, so will become '"val1", "val2", "val3" or "val4"' - paste0(paste0(ifelse(quotes, '"', ""), v[seq_len(length(v) - 1)], ifelse(quotes, '"', ""), collapse = ", "), - " or ", paste0(ifelse(quotes, '"', ""), v[length(v)], ifelse(quotes, '"', ""))) + paste0(paste0(quotes, v[seq_len(length(v) - 1)], quotes, collapse = ", "), + last_sep, paste0(quotes, v[length(v)], quotes)) } format_class <- function(class, plural) { @@ -562,6 +571,7 @@ meet_criteria <- function(object, "` must be ", ifelse(!is.null(has_length) && length(has_length) == 1 && has_length == 1, "either ", ""), vector_or(is_in, quotes = !isTRUE(any(c("double", "numeric", "integer") %in% allow_class))), + ifelse(allow_NA == TRUE, ", or NA", ""), call = call_depth) } if (!is.null(is_positive)) { diff --git a/R/eucast_rules.R b/R/eucast_rules.R index 36f2d42f..935db54a 100755 --- a/R/eucast_rules.R +++ b/R/eucast_rules.R @@ -73,7 +73,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 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 susceptible (S) results of cefotaxime, ceftriaxone and ceftazidime should be reported with a note, or results should be suppressed (emptied) for these agents. A value of `NA` for this argument will remove results for these agents, while e.g. a value of `"R"` will make the results for these agents resistant. Use `NULL` to not alter the results for AmpC de-repressed cephalosporin-resistant mutants. \cr For *EUCAST Expert Rules* v3.2, this rule applies to: *`r gsub("[)(^]", "", gsub("|", ", ", eucast_rules_file[which(eucast_rules_file$reference.version == 3.2 & eucast_rules_file$reference.rule %like% "ampc"), "this_value"][1], fixed = TRUE))`*. +#' @param ampc_cephalosporin_resistance a character value that should be applied 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 agents. A value of `NA` for this argument will remove results for these agents, while e.g. a value of `"R"` will make the results for these agents resistant. Use `NULL` to not alter the results for AmpC de-repressed cephalosporin-resistant mutants. \cr For *EUCAST Expert Rules* v3.2, this rule applies to: `r vector_or(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 = "*", last_sep = " and ")`. #' @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)` @@ -173,7 +173,7 @@ eucast_rules <- function(x, meet_criteria(verbose, allow_class = "logical", has_length = 1) meet_criteria(version_breakpoints, allow_class = c("numeric", "integer"), has_length = 1, is_in = as.double(names(EUCAST_VERSION_BREAKPOINTS))) meet_criteria(version_expertrules, allow_class = c("numeric", "integer"), has_length = 1, is_in = as.double(names(EUCAST_VERSION_EXPERT_RULES))) - meet_criteria(ampc_cephalosporin_resistance, allow_class = c("rsi", "character"), has_length = 1, allow_NA = TRUE, allow_NULL = TRUE, is_in = c("R", "S", "I")) + meet_criteria(ampc_cephalosporin_resistance, has_length = 1, allow_NA = TRUE, allow_NULL = TRUE, is_in = c("R", "S", "I")) x_deparsed <- deparse(substitute(x)) if (length(x_deparsed) > 1 || !all(x_deparsed %like% "[a-z]+")) { @@ -1183,7 +1183,7 @@ edit_rsi <- function(x, #' @export eucast_dosage <- function(ab, administration = "iv", version_breakpoints = 11.0) { meet_criteria(ab, allow_class = c("character", "numeric", "integer", "factor")) - meet_criteria(administration, allow_class = "character", is_in = dosage$administration[!is.na(dosage$administration)]) + meet_criteria(administration, allow_class = "character", is_in = dosage$administration[!is.na(dosage$administration)], has_length = 1) meet_criteria(version_breakpoints, allow_class = c("numeric", "integer"), has_length = 1, is_in = as.double(names(EUCAST_VERSION_BREAKPOINTS))) # show used version_breakpoints number once per session (pkg_env will reload every session) @@ -1195,9 +1195,21 @@ eucast_dosage <- function(ab, administration = "iv", version_breakpoints = 11.0) } ab <- as.ab(ab) - df <- AMR::dosage[which(AMR::dosage$ab %in% ab & AMR::dosage$administration %in% administration), , drop = FALSE] - df <- df[which(df$ab == ab), colnames(df)[colnames(df) != "administration"], drop = FALSE] - rownames(df) <- NULL - df$ab <- ab - df + lst <- vector("list", length = length(ab)) + for (i in seq_len(length(ab))) { + df <- AMR::dosage[which(AMR::dosage$ab == ab[i] & AMR::dosage$administration == administration), , drop = FALSE] + lst[[i]] <- list(ab = "", + name = "", + standard_dosage = ifelse("standard_dosage" %in% df$type, + df[which(df$type == "standard_dosage"), ]$original_txt, + NA_character_), + high_dosage = ifelse("high_dosage" %in% df$type, + df[which(df$type == "high_dosage"), ]$original_txt, + NA_character_)) + } + out <- do.call("rbind", lapply(lst, as.data.frame, stringsAsFactors = FALSE)) + rownames(out) <- NULL + out$ab <- ab + out$name <- ab_name(ab, language = NULL) + out } diff --git a/R/mo.R b/R/mo.R index ad4a7faf..9b732809 100755 --- a/R/mo.R +++ b/R/mo.R @@ -2016,3 +2016,14 @@ repair_reference_df <- function(reference_df) { reference_df[, "mo"] <- as.mo(reference_df[, "mo", drop = TRUE]) reference_df } + +strip_words <- function(text, n, side = "right") { + out <- lapply(strsplit(x, " "), function(x) { + if (side %like% "^r" & length(x) > n) { + x[seq_len(length(x) - n)] + } else if (side %like% "^l" & length(x) > n) { + x[2:length(x)] + } + }) + vapply(FUN.VALUE = character(1), out, paste, collapse = " ") +} diff --git a/R/sysdata.rda b/R/sysdata.rda index d3d3c27a..229b38ad 100644 Binary files a/R/sysdata.rda and b/R/sysdata.rda differ diff --git a/data-raw/AMR_1.5.0.9011.tar.gz b/data-raw/AMR_1.5.0.9012.tar.gz similarity index 58% rename from data-raw/AMR_1.5.0.9011.tar.gz rename to data-raw/AMR_1.5.0.9012.tar.gz index 9fb90f62..0bbc2b90 100644 Binary files a/data-raw/AMR_1.5.0.9011.tar.gz and b/data-raw/AMR_1.5.0.9012.tar.gz differ diff --git a/data-raw/eucast_rules.tsv b/data-raw/eucast_rules.tsv index 9251dc55..b2706643 100644 --- a/data-raw/eucast_rules.tsv +++ b/data-raw/eucast_rules.tsv @@ -409,6 +409,9 @@ genus_species is Moraxella catarrhalis NAL S fluoroquinolones S Expert Rules on genus_species is Moraxella catarrhalis NAL R fluoroquinolones R Expert Rules on Moraxella catarrhalis Expert Rules 3.2 genus is Campylobacter ERY S CLR, AZM S Expert Rules on Campylobacter Expert Rules 3.2 genus_species is Campylobacter ERY R CLR, AZM R Expert Rules on Campylobacter Expert Rules 3.2 -fullname like ^(Enterobacter|Klebsiella aerogenes|Citrobacter (braakii|freundii|gillenii|murliniae|rodenticum|sedlakii|werkmanii|youngae)|Hafnia alvei|Serratia|Morganella morganii|Providencia) CTX S CTX, CRO, CAZ Expert Rules on Enterobacterales (AmpC de-repressed cephalosporins) Expert Rules 3.2 This is rule 3 and 4 of EUCAST Expert Rules v3.2 on Enterobacterales, result will be set with the 'ampc_derepressed_cephalosporins' argument -fullname like ^(Enterobacter|Klebsiella aerogenes|Citrobacter (braakii|freundii|gillenii|murliniae|rodenticum|sedlakii|werkmanii|youngae)|Hafnia alvei|Serratia|Morganella morganii|Providencia) CRO S CTX, CRO, CAZ Expert Rules on Enterobacterales (AmpC de-repressed cephalosporins) Expert Rules 3.2 This is rule 3 and 4 of EUCAST Expert Rules v3.2 on Enterobacterales, result will be set with the 'ampc_derepressed_cephalosporins' argument -fullname like ^(Enterobacter|Klebsiella aerogenes|Citrobacter (braakii|freundii|gillenii|murliniae|rodenticum|sedlakii|werkmanii|youngae)|Hafnia alvei|Serratia|Morganella morganii|Providencia) CAZ S CTX, CRO, CAZ Expert Rules on Enterobacterales (AmpC de-repressed cephalosporins) Expert Rules 3.2 This is rule 3 and 4 of EUCAST Expert Rules v3.2 on Enterobacterales, result will be set with the 'ampc_derepressed_cephalosporins' argument +fullname like ^(Enterobacter|Klebsiella aerogenes|Citrobacter braakii|Citrobacter freundii|Citrobacter gillenii|Citrobacter murliniae|Citrobacter rodenticum|Citrobacter sedlakii|Citrobacter werkmanii|Citrobacter youngae|Hafnia alvei|Serratia|Morganella morganii|Providencia) CTX S CTX, CRO, CAZ Expert Rules on Enterobacterales (AmpC de-repressed cephalosporins) Expert Rules 3.2 This is rule 3 and 4 of EUCAST Expert Rules v3.2 on Enterobacterales, result will be set with the 'ampc_derepressed_cephalosporins' argument +fullname like ^(Enterobacter|Klebsiella aerogenes|Citrobacter braakii|Citrobacter freundii|Citrobacter gillenii|Citrobacter murliniae|Citrobacter rodenticum|Citrobacter sedlakii|Citrobacter werkmanii|Citrobacter youngae|Hafnia alvei|Serratia|Morganella morganii|Providencia) CRO S CTX, CRO, CAZ Expert Rules on Enterobacterales (AmpC de-repressed cephalosporins) Expert Rules 3.2 This is rule 3 and 4 of EUCAST Expert Rules v3.2 on Enterobacterales, result will be set with the 'ampc_derepressed_cephalosporins' argument +fullname like ^(Enterobacter|Klebsiella aerogenes|Citrobacter braakii|Citrobacter freundii|Citrobacter gillenii|Citrobacter murliniae|Citrobacter rodenticum|Citrobacter sedlakii|Citrobacter werkmanii|Citrobacter youngae|Hafnia alvei|Serratia|Morganella morganii|Providencia) CAZ S CTX, CRO, CAZ Expert Rules on Enterobacterales (AmpC de-repressed cephalosporins) Expert Rules 3.2 This is rule 3 and 4 of EUCAST Expert Rules v3.2 on Enterobacterales, result will be set with the 'ampc_derepressed_cephalosporins' argument +fullname like ^(Enterobacter|Klebsiella aerogenes|Citrobacter braakii|Citrobacter freundii|Citrobacter gillenii|Citrobacter murliniae|Citrobacter rodenticum|Citrobacter sedlakii|Citrobacter werkmanii|Citrobacter youngae|Hafnia alvei|Serratia|Morganella morganii|Providencia) CTX I CTX, CRO, CAZ Expert Rules on Enterobacterales (AmpC de-repressed cephalosporins) Expert Rules 3.2 This is rule 3 and 4 of EUCAST Expert Rules v3.2 on Enterobacterales, result will be set with the 'ampc_derepressed_cephalosporins' argument +fullname like ^(Enterobacter|Klebsiella aerogenes|Citrobacter braakii|Citrobacter freundii|Citrobacter gillenii|Citrobacter murliniae|Citrobacter rodenticum|Citrobacter sedlakii|Citrobacter werkmanii|Citrobacter youngae|Hafnia alvei|Serratia|Morganella morganii|Providencia) CRO I CTX, CRO, CAZ Expert Rules on Enterobacterales (AmpC de-repressed cephalosporins) Expert Rules 3.2 This is rule 3 and 4 of EUCAST Expert Rules v3.2 on Enterobacterales, result will be set with the 'ampc_derepressed_cephalosporins' argument +fullname like ^(Enterobacter|Klebsiella aerogenes|Citrobacter braakii|Citrobacter freundii|Citrobacter gillenii|Citrobacter murliniae|Citrobacter rodenticum|Citrobacter sedlakii|Citrobacter werkmanii|Citrobacter youngae|Hafnia alvei|Serratia|Morganella morganii|Providencia) CAZ I CTX, CRO, CAZ Expert Rules on Enterobacterales (AmpC de-repressed cephalosporins) Expert Rules 3.2 This is rule 3 and 4 of EUCAST Expert Rules v3.2 on Enterobacterales, result will be set with the 'ampc_derepressed_cephalosporins' argument diff --git a/docs/404.html b/docs/404.html index b8dc635d..003f6c58 100644 --- a/docs/404.html +++ b/docs/404.html @@ -81,7 +81,7 @@ AMR (for R) - 1.5.0.9011 + 1.5.0.9012 diff --git a/docs/LICENSE-text.html b/docs/LICENSE-text.html index d9e7fab7..c85d7dbc 100644 --- a/docs/LICENSE-text.html +++ b/docs/LICENSE-text.html @@ -81,7 +81,7 @@ AMR (for R) - 1.5.0.9011 + 1.5.0.9012 diff --git a/docs/articles/index.html b/docs/articles/index.html index 2d02f57a..7507c279 100644 --- a/docs/articles/index.html +++ b/docs/articles/index.html @@ -81,7 +81,7 @@ AMR (for R) - 1.5.0.9011 + 1.5.0.9012 diff --git a/docs/authors.html b/docs/authors.html index 9c0477e2..72ab23bb 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -81,7 +81,7 @@ AMR (for R) - 1.5.0.9011 + 1.5.0.9012 diff --git a/docs/index.html b/docs/index.html index 46274b68..a589bb57 100644 --- a/docs/index.html +++ b/docs/index.html @@ -43,7 +43,7 @@ AMR (for R) - 1.5.0.9011 + 1.5.0.9012 diff --git a/docs/news/index.html b/docs/news/index.html index f94674a6..8cc42558 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -81,7 +81,7 @@ AMR (for R) - 1.5.0.9011 + 1.5.0.9012 @@ -236,13 +236,13 @@ Source: NEWS.md -
-

-AMR 1.5.0.9011 Unreleased +
+

+AMR 1.5.0.9012 Unreleased

-
+

-Last updated: 24 January 2021 +Last updated: 25 January 2021

@@ -289,6 +289,7 @@
  • is.rsi.eligible() now returns FALSE immediately if the input does not contain any of the values “R”, “S” or “I”. This drastically improves speed, also for a lot of other functions that rely on automatic determination of antibiotic columns.
  • Functions get_episode() and is_new_episode() now support less than a day as value for argument episode_days (e.g., to include one patient/test per hour)
  • +
  • Argument ampc_cephalosporin_resistance in eucast_rules() now also applies to value “I” (not only “S”)
  • diff --git a/docs/pkgdown.yml b/docs/pkgdown.yml index eef418d1..26c74b54 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-01-24T22:17Z +last_built: 2021-01-25T20:57Z urls: reference: https://msberends.github.io/AMR//reference article: https://msberends.github.io/AMR//articles diff --git a/docs/reference/eucast_rules.html b/docs/reference/eucast_rules.html index 12933c27..def06b52 100644 --- a/docs/reference/eucast_rules.html +++ b/docs/reference/eucast_rules.html @@ -83,7 +83,7 @@ To improve the interpretation of the antibiogram before EUCAST rules are applied AMR (for R) - 1.5.0.9008 + 1.5.0.9012
    @@ -291,7 +291,7 @@ To improve the interpretation of the antibiogram before EUCAST rules are applied ampc_cephalosporin_resistance -

    a character value that should be applied 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 susceptible (S) results of cefotaxime, ceftriaxone and ceftazidime should be reported with a note, or results should be suppressed (emptied) for these agents. A value of NA for this argument will remove results for these agents, while e.g. a value of "R" will make the results for these agents resistant. Use NULL to not alter the results for AmpC de-repressed cephalosporin-resistant mutants.
    For EUCAST Expert Rules v3.2, this rule applies to: Enterobacter, Klebsiella aerogenes, Citrobacter braakii, freundii, gillenii, murliniae, rodenticum, sedlakii, werkmanii, youngae, Hafnia alvei, Serratia, Morganella morganii, Providencia.

    +

    a character value that should be applied 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 agents. A value of NA for this argument will remove results for these agents, while e.g. a value of "R" will make the results for these agents resistant. Use NULL to not alter the results for AmpC de-repressed cephalosporin-resistant mutants.
    For EUCAST Expert Rules v3.2, this rule applies to: Citrobacter braakii, Citrobacter freundii, Citrobacter gillenii, Citrobacter murliniae, Citrobacter rodenticum, Citrobacter sedlakii, Citrobacter werkmanii, Citrobacter youngae, Enterobacter, Hafnia alvei, Klebsiella aerogenes, Morganella morganii, Providencia and Serratia.

    ... diff --git a/docs/reference/index.html b/docs/reference/index.html index 6d607671..07f38b09 100644 --- a/docs/reference/index.html +++ b/docs/reference/index.html @@ -81,7 +81,7 @@ AMR (for R) - 1.5.0.9011 + 1.5.0.9012
    diff --git a/docs/survey.html b/docs/survey.html index 447170ef..8ef1314a 100644 --- a/docs/survey.html +++ b/docs/survey.html @@ -81,7 +81,7 @@ AMR (for R) - 1.5.0.9011 + 1.5.0.9012
    diff --git a/man/eucast_rules.Rd b/man/eucast_rules.Rd index 1caf4494..162fcb05 100644 --- a/man/eucast_rules.Rd +++ b/man/eucast_rules.Rd @@ -46,7 +46,7 @@ eucast_dosage(ab, administration = "iv", version_breakpoints = 11) \item{version_expertrules}{the version number to use for the EUCAST Expert Rules and Intrinsic Resistance guideline. Can be either "3.2" or "3.1".} -\item{ampc_cephalosporin_resistance}{a character value that should be applied for AmpC de-repressed cephalosporin-resistant mutants, defaults to \code{NA}. Currently only works when \code{version_expertrules} is \code{3.2}; '\emph{EUCAST Expert Rules v3.2 on Enterobacterales}' states that susceptible (S) results of cefotaxime, ceftriaxone and ceftazidime should be reported with a note, or results should be suppressed (emptied) for these agents. A value of \code{NA} for this argument will remove results for these agents, while e.g. a value of \code{"R"} will make the results for these agents resistant. Use \code{NULL} to not alter the results for AmpC de-repressed cephalosporin-resistant mutants. \cr For \emph{EUCAST Expert Rules} v3.2, this rule applies to: \emph{Enterobacter, Klebsiella aerogenes, Citrobacter braakii, freundii, gillenii, murliniae, rodenticum, sedlakii, werkmanii, youngae, Hafnia alvei, Serratia, Morganella morganii, Providencia}.} +\item{ampc_cephalosporin_resistance}{a character value that should be applied for AmpC de-repressed cephalosporin-resistant mutants, defaults to \code{NA}. Currently only works when \code{version_expertrules} is \code{3.2}; '\emph{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 agents. A value of \code{NA} for this argument will remove results for these agents, while e.g. a value of \code{"R"} will make the results for these agents resistant. Use \code{NULL} to not alter the results for AmpC de-repressed cephalosporin-resistant mutants. \cr For \emph{EUCAST Expert Rules} v3.2, this rule applies to: \emph{Citrobacter braakii}, \emph{Citrobacter freundii}, \emph{Citrobacter gillenii}, \emph{Citrobacter murliniae}, \emph{Citrobacter rodenticum}, \emph{Citrobacter sedlakii}, \emph{Citrobacter werkmanii}, \emph{Citrobacter youngae}, \emph{Enterobacter}, \emph{Hafnia alvei}, \emph{Klebsiella aerogenes}, \emph{Morganella morganii}, \emph{Providencia} and \emph{Serratia}.} \item{...}{column name of an antibiotic, see section \emph{Antibiotics} below}