(v1.7.1.9063) not_intrinsic_resistant

This commit is contained in:
dr. M.S. (Matthijs) Berends 2021-12-09 10:48:25 +01:00
parent e63defe324
commit e18c49ed93
32 changed files with 275 additions and 185 deletions

View File

@ -1,6 +1,6 @@
Package: AMR
Version: 1.7.1.9062
Date: 2021-12-06
Version: 1.7.1.9063
Date: 2021-12-09
Title: Antimicrobial Resistance Data Analysis
Description: Functions to simplify and standardise antimicrobial resistance (AMR)
data analysis and to work with microbial and antimicrobial properties by

View File

@ -273,6 +273,7 @@ export(mo_is_gram_positive)
export(mo_is_intrinsic_resistant)
export(mo_is_yeast)
export(mo_kingdom)
export(mo_lpsn)
export(mo_matching_score)
export(mo_name)
export(mo_order)
@ -293,6 +294,7 @@ export(mo_url)
export(mo_year)
export(mrgn)
export(n_rsi)
export(not_intrinsic_resistant)
export(oxazolidinones)
export(pca)
export(penicillins)

View File

@ -1,5 +1,5 @@
# `AMR` 1.7.1.9062
## <small>Last updated: 6 December 2021</small>
# `AMR` 1.7.1.9063
## <small>Last updated: 9 December 2021</small>
### Breaking changes
* Removed `p_symbol()` and all `filter_*()` functions (except for `filter_first_isolate()`), which were all deprecated in a previous package version
@ -8,12 +8,13 @@
### New
* Support for EUCAST Intrinsic Resistance and Unusual Phenotypes v3.3 (October 2021), effective in the `eucast_rules()` function. This is now the default guideline (all other guidelines are still available).
* Support for Danish, and also added missing translations of all antimicrobial drugs in Italian, French and Portuguese
* Function `set_ab_names()` to rename data set columns that resemble antimicrobial drugs. This allows for quickly renaming columns to official names, ATC codes, etc. Its second argument can be a tidyverse way of selecting:
```r
example_isolates %>% set_ab_names(where(is.rsi))
example_isolates %>% set_ab_names(AMC:GEN, property = "atc")
```
* Support for Danish, and also added missing translations of all antimicrobial drugs in Italian, French and Portuguese
* Function `mo_lpsn()` to retrieve the [LPSN](https://lpsn.dsmz.de) record ID
### Changed
* Updated the bacterial taxonomy to 5 October 2021 (according to [LPSN](https://lpsn.dsmz.de)), including all 11 new staphylococcal species named since 1 January last year
@ -36,7 +37,9 @@
example_isolates[, ab_selector(oral_ddd > 1 & oral_units == "g")] # base R
example_isolates %>% select(ab_selector(oral_ddd > 1 & oral_units == "g")) # dplyr
```
* Added the selector `not_intrinsic_resistant()`, which only keeps antibiotic columns that are not intrinsic resistant for all microorganisms in a data set, based on the latest EUCAST guideline on intrinsic resistance. For example, if a data set contains only microorganism codes or names of *E. coli* and *K. pneumoniae* and contains a column "vancomycin", this column will be removed (or rather, unselected) using this function.
* Fix for using selectors multiple times in one call (e.g., using them in `dplyr::filter()` and immediately after in `dplyr::select()`)
* Fix for using having multiple columns that are coerced to the same antibiotic agent
* Added argument `only_treatable`, which defaults to `TRUE` and will exclude drugs that are only for laboratory tests and not for treating patients (such as imipenem/EDTA and gentamicin-high)
* Fixed the Gram stain (`mo_gramstain()`) determination of the taxonomic class Negativicutes within the phylum of Firmicutes - they were considered Gram-positives because of their phylum but are actually Gram-negative. This impacts 137 taxonomic species, genera and families, such as *Negativicoccus* and *Veillonella*.
* Dramatic speed improvement for `first_isolate()`

View File

@ -194,7 +194,7 @@ check_dataset_integrity <- function() {
data_in_globalenv <- ls(envir = globalenv())
overwritten <- data_in_pkg[data_in_pkg %in% data_in_globalenv]
# exception for example_isolates
overwritten <- overwritten[overwritten != "example_isolates"]
overwritten <- overwritten[overwritten %unlike% "example_isolates"]
if (length(overwritten) > 0) {
if (length(overwritten) > 1) {
plural <- c("s are", "", "s")

View File

@ -38,11 +38,6 @@
#' 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.) according to the [antibiotics] data set. This means that a selector such as [aminoglycosides()] will pick up column names like 'gen', 'genta', 'J01GB03', 'tobra', 'Tobracin', etc.
#'
#' The [ab_class()] function can be used to filter/select on a manually defined antibiotic class. It searches for results in the [antibiotics] data set within the columns `group`, `atc_group1` and `atc_group2`.
#'
#' The [ab_selector()] function can be used to internally filter the [antibiotics] data set on any results, see *Examples*. It allows for filtering on a (part of) a certain name, and/or a group name or even a minimum of DDDs for oral treatment. This function yields the highest flexibility, but is also the least user-friendly, since it requires a hard-coded filter to set.
#'
#' The [administrable_per_os()] and [administrable_iv()] functions also rely on the [antibiotics] data set - antibiotic columns will be matched where a DDD (defined daily dose) for resp. oral and IV treatment is available in the [antibiotics] data set.
#'
#' @section Full list of supported (antibiotic) classes:
#'
#' `r paste0(" * ", na.omit(sapply(DEFINED_AB_GROUPS, function(ab) ifelse(tolower(gsub("^AB_", "", ab)) %in% ls(envir = asNamespace("AMR")), paste0("[", tolower(gsub("^AB_", "", ab)), "()] can select: \\cr ", vector_and(paste0(ab_name(eval(parse(text = ab), envir = asNamespace("AMR")), language = NULL, tolower = TRUE), " (", eval(parse(text = ab), envir = asNamespace("AMR")), ")"), quotes = FALSE, sort = TRUE)), character(0)), USE.NAMES = FALSE)), "\n", collapse = "")`
@ -105,6 +100,12 @@
#' # You can combine selectors with '&' to be more specific:
#' example_isolates %>%
#' select(penicillins() & administrable_per_os())
#'
#' # get AMR for only drugs that matter - no intrinsic resistance:
#' example_isolates %>%
#' filter(mo_genus() %in% c("Escherichia", "Klebsiella")) %>%
#' group_by(hospital_id) %>%
#' summarise(across(not_intrinsic_resistant(), resistance))
#'
#' # get susceptibility for antibiotics whose name contains "trim":
#' example_isolates %>%
@ -167,6 +168,7 @@ ab_class <- function(ab_class,
}
#' @rdname antibiotic_class_selectors
#' @details The [ab_selector()] function can be used to internally filter the [antibiotics] data set on any results, see *Examples*. It allows for filtering on a (part of) a certain name, and/or a group name or even a minimum of DDDs for oral treatment. This function yields the highest flexibility, but is also the least user-friendly, since it requires a hard-coded filter to set.
#' @export
ab_selector <- function(filter,
only_rsi_columns = FALSE,
@ -193,90 +195,6 @@ ab_selector <- function(filter,
class = c("ab_selector", "character"))
}
#' @rdname antibiotic_class_selectors
#' @export
administrable_per_os <- function(only_rsi_columns = FALSE, ...) {
meet_criteria(only_rsi_columns, allow_class = "logical", has_length = 1)
# get_current_data() has to run each time, for cases where e.g., filter() and select() are used in same call
# but it only takes a couple of milliseconds
vars_df <- get_current_data(arg_name = NA, call = -2)
# 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)
agents_all <- antibiotics[which(!is.na(antibiotics$oral_ddd)), "ab", drop = TRUE]
agents <- antibiotics[which(antibiotics$ab %in% ab_in_data & !is.na(antibiotics$oral_ddd)), "ab", drop = TRUE]
agents <- ab_in_data[ab_in_data %in% agents]
message_agent_names(function_name = "administrable_per_os",
agents = agents,
ab_group = "administrable_per_os",
examples = paste0(" (such as ",
vector_or(ab_name(sample(agents_all,
size = min(5, length(agents_all)),
replace = FALSE),
tolower = TRUE,
language = NULL),
quotes = FALSE),
")"))
structure(unname(agents),
class = c("ab_selector", "character"))
}
#' @rdname antibiotic_class_selectors
#' @export
administrable_iv <- function(only_rsi_columns = FALSE, ...) {
meet_criteria(only_rsi_columns, allow_class = "logical", has_length = 1)
# get_current_data() has to run each time, for cases where e.g., filter() and select() are used in same call
# but it only takes a couple of milliseconds
vars_df <- get_current_data(arg_name = NA, call = -2)
# 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)
agents_all <- antibiotics[which(!is.na(antibiotics$iv_ddd)), "ab", drop = TRUE]
agents <- antibiotics[which(antibiotics$ab %in% ab_in_data & !is.na(antibiotics$iv_ddd)), "ab", drop = TRUE]
agents <- ab_in_data[ab_in_data %in% agents]
message_agent_names(function_name = "administrable_iv",
agents = agents,
ab_group = "administrable_iv",
examples = "")
structure(unname(agents),
class = c("ab_selector", "character"))
}
# nolint start
# #' @rdname antibiotic_class_selectors
# #' @export
# not_intrinsic_resistant <- function(mo, ..., only_rsi_columns = FALSE, ...) {
# meet_criteria(mo, allow_class = c("mo", "data.frame", "list", "character", "numeric", "integer", "factor"), has_length = 1, allow_NA = FALSE)
# meet_criteria(only_rsi_columns, allow_class = "logical", has_length = 1)
#
# x <- as.mo(mo, ...)
# wont_work <- intrinsic_resistant[which(intrinsic_resistant$microorganism == mo_name(x, language = NULL)),
# "antibiotic",
# drop = TRUE]
#
# # get_current_data() has to run each time, for cases where e.g., filter() and select() are used in same call
# # but it only takes a couple of milliseconds
# vars_df <- get_current_data(arg_name = NA, call = -2)
# # 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)
#
# agents <- ab_in_data[!names(ab_in_data) %in% as.character(as.ab(wont_work))]
#
# # show used version number once per session (pkg_env will reload every session)
# if (message_not_thrown_before("intrinsic_resistant_version.ab", entire_session = TRUE)) {
# message_("Determining intrinsic resistance based on ",
# format_eucast_version_nr(3.2, markdown = FALSE), ". ",
# font_red("This note will be shown once per session."))
# }
#
# message_agent_names(function_name = "not_intrinsic_resistant",
# agents = ab_in_data,
# ab_group = NULL,
# examples = "",
# call = mo_name(x, language = NULL))
#
# agents
# }
# nolint end
#' @rdname antibiotic_class_selectors
#' @export
aminoglycosides <- function(only_rsi_columns = FALSE, only_treatable = TRUE, ...) {
@ -456,6 +374,94 @@ ureidopenicillins <- function(only_rsi_columns = FALSE, ...) {
ab_select_exec("ureidopenicillins", only_rsi_columns = only_rsi_columns)
}
#' @rdname antibiotic_class_selectors
#' @details The [administrable_per_os()] and [administrable_iv()] functions also rely on the [antibiotics] data set - antibiotic columns will be matched where a DDD (defined daily dose) for resp. oral and IV treatment is available in the [antibiotics] data set.
#' @export
administrable_per_os <- function(only_rsi_columns = FALSE, ...) {
meet_criteria(only_rsi_columns, allow_class = "logical", has_length = 1)
# get_current_data() has to run each time, for cases where e.g., filter() and select() are used in same call
# but it only takes a couple of milliseconds
vars_df <- get_current_data(arg_name = NA, call = -2)
# 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)
agents_all <- antibiotics[which(!is.na(antibiotics$oral_ddd)), "ab", drop = TRUE]
agents <- antibiotics[which(antibiotics$ab %in% ab_in_data & !is.na(antibiotics$oral_ddd)), "ab", drop = TRUE]
agents <- ab_in_data[ab_in_data %in% agents]
message_agent_names(function_name = "administrable_per_os",
agents = agents,
ab_group = "administrable_per_os",
examples = paste0(" (such as ",
vector_or(ab_name(sample(agents_all,
size = min(5, length(agents_all)),
replace = FALSE),
tolower = TRUE,
language = NULL),
quotes = FALSE),
")"))
structure(unname(agents),
class = c("ab_selector", "character"))
}
#' @rdname antibiotic_class_selectors
#' @export
administrable_iv <- function(only_rsi_columns = FALSE, ...) {
meet_criteria(only_rsi_columns, allow_class = "logical", has_length = 1)
# get_current_data() has to run each time, for cases where e.g., filter() and select() are used in same call
# but it only takes a couple of milliseconds
vars_df <- get_current_data(arg_name = NA, call = -2)
# 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)
agents_all <- antibiotics[which(!is.na(antibiotics$iv_ddd)), "ab", drop = TRUE]
agents <- antibiotics[which(antibiotics$ab %in% ab_in_data & !is.na(antibiotics$iv_ddd)), "ab", drop = TRUE]
agents <- ab_in_data[ab_in_data %in% agents]
message_agent_names(function_name = "administrable_iv",
agents = agents,
ab_group = "administrable_iv",
examples = "")
structure(unname(agents),
class = c("ab_selector", "character"))
}
#' @rdname antibiotic_class_selectors
#' @inheritParams eucast_rules
#' @details The [not_intrinsic_resistant()] function can be used to only select antibiotic columns that pose no intrinsic resistance for the microorganisms in the data set. For example, if a data set contains only microorganism codes or names of *E. coli* and *K. pneumoniae* and contains a column "vancomycin", this column will be removed (or rather, unselected) using this function. It currently applies `r format_eucast_version_nr(names(EUCAST_VERSION_EXPERT_RULES[length(EUCAST_VERSION_EXPERT_RULES)]))` to determine intrinsic resistance, using the [eucast_rules()] function internally. Because of this determination, this function is quite slow in terms of performance.
#' @export
not_intrinsic_resistant <- function(only_rsi_columns = FALSE, col_mo = NULL, version_expertrules = 3.3, ...) {
meet_criteria(only_rsi_columns, allow_class = "logical", has_length = 1)
# get_current_data() has to run each time, for cases where e.g., filter() and select() are used in same call
# but it only takes a couple of milliseconds
vars_df <- get_current_data(arg_name = NA, call = -2)
# 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)
# intrinsic vars
vars_df_R <- tryCatch(sapply(eucast_rules(vars_df,
col_mo = col_mo,
version_expertrules = version_expertrules,
rules = "expert",
info = FALSE),
function(col) tryCatch(!any(is.na(col)) && all(col == "R"),
error = function(e) FALSE)),
error = function(e) stop_("in not_intrinsic_resistant(): ", e$message, call = FALSE))
agents <- ab_in_data[ab_in_data %in% names(vars_df_R[which(vars_df_R)])]
if (length(agents) > 0 &&
message_not_thrown_before(paste0("not_intrinsic_resistant.", paste(sort(agents), collapse = "|")))) {
agents_formatted <- paste0("'", font_bold(agents, collapse = NULL), "'")
agents_names <- ab_name(names(agents), tolower = TRUE, language = NULL)
need_name <- generalise_antibiotic_name(agents) != generalise_antibiotic_name(agents_names)
agents_formatted[need_name] <- paste0(agents_formatted[need_name], " (", agents_names[need_name], ")")
message_("For `not_intrinsic_resistant()` removing ",
ifelse(length(agents) == 1, "column ", "columns "),
vector_and(agents_formatted, quotes = FALSE, sort = FALSE))
}
vars_df_R <- names(vars_df_R)[which(!vars_df_R)]
# find columns that are abx, but also intrinsic R
out <- unname(intersect(ab_in_data, vars_df_R))
structure(out,
class = c("ab_selector", "character"))
}
ab_select_exec <- function(function_name,
only_rsi_columns = FALSE,
only_treatable = FALSE,
@ -465,7 +471,6 @@ ab_select_exec <- function(function_name,
vars_df <- get_current_data(arg_name = NA, call = -3)
# 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)
# untreatable drugs
untreatable <- antibiotics[which(antibiotics$name %like% "-high|EDTA|polysorbate"), "ab", drop = TRUE]
if (only_treatable == TRUE & any(untreatable %in% names(ab_in_data))) {

View File

@ -59,7 +59,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_DF[which(EUCAST_RULES_DF$reference.version == 3.2 & EUCAST_RULES_DF$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` and higher; these version of '*EUCAST Expert Rules on Enterobacterales*' state 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 %in% c(3.2, 3.3) & 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)`

View File

@ -238,9 +238,10 @@ get_column_abx <- function(x,
if (sort == TRUE) {
out <- out[order(names(out), out)]
}
duplicates <- c(out[duplicated(out)], out[duplicated(names(out))])
duplicates <- duplicates[unique(names(duplicates))]
out <- c(out[!names(out) %in% names(duplicates)], duplicates)
# only keep the first hits, no duplicates
duplicates <- c(out[duplicated(names(out))], out[duplicated(unname(out))])
out <- out[!duplicated(names(out))]
out <- out[!duplicated(unname(out))]
if (sort == TRUE) {
out <- out[order(names(out), out)]
}

View File

@ -27,7 +27,7 @@
#'
#' This algorithm is used by [as.mo()] and all the [`mo_*`][mo_property()] functions to determine the most probable match of taxonomic records based on user input.
#' @inheritSection lifecycle Stable Lifecycle
#' @author Matthijs S. Berends
#' @author Dr. Matthijs Berends
#' @param x Any user input value(s)
#' @param n A full taxonomic name, that exists in [`microorganisms$fullname`][microorganisms]
#' @section Matching Score for Microorganisms:

View File

@ -96,6 +96,7 @@
#' mo_ref("E. coli") # "Castellani et al., 1919"
#' mo_authors("E. coli") # "Castellani et al."
#' mo_year("E. coli") # 1919
#' mo_lpsn("E. coli") # 776057 (LPSN record ID)
#'
#' # abbreviations known in the field -----------------------------------------
#' mo_genus("MRSA") # "Staphylococcus"
@ -538,6 +539,19 @@ mo_year <- function(x, language = get_locale(), ...) {
suppressWarnings(as.integer(x))
}
#' @rdname mo_property
#' @export
mo_lpsn <- function(x, language = get_locale(), ...) {
if (missing(x)) {
# this tries to find the data and an <mo> column
x <- find_mo_col(fn = "mo_rank")
}
meet_criteria(x, allow_NA = TRUE)
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
mo_validate(x = x, property = "species_id", language = language, ...)
}
#' @rdname mo_property
#' @export
mo_rank <- function(x, language = get_locale(), ...) {
@ -724,6 +738,8 @@ mo_validate <- function(x, property, language, ...) {
if (property == "mo") {
return(set_clean_class(x, new_class = c("mo", "character")))
} else if (property == "species_id") {
return(as.double(x))
} else if (property == "snomed") {
return(as.double(eval(parse(text = x))))
} else {

Binary file not shown.

View File

@ -43,7 +43,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="https://msberends.github.io/AMR/index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9062</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9063</span>
</span>
</div>

View File

@ -17,7 +17,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9062</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9063</span>
</span>
</div>

View File

@ -44,7 +44,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9062</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9063</span>
</span>
</div>
@ -190,7 +190,7 @@
<div class="page-header toc-ignore">
<h1 data-toc-skip>Data sets for download / own use</h1>
<h4 data-toc-skip class="date">06 December 2021</h4>
<h4 data-toc-skip class="date">09 December 2021</h4>
<small class="dont-index">Source: <a href="https://github.com/msberends/AMR/blob/HEAD/vignettes/datasets.Rmd" class="external-link"><code>vignettes/datasets.Rmd</code></a></small>
<div class="hidden name"><code>datasets.Rmd</code></div>

View File

@ -17,7 +17,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9062</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9063</span>
</span>
</div>

View File

@ -97,20 +97,20 @@ $(document).ready(function() {
x = x.replace(/Author, contributor/g, "Maintainer");
x = x.replace(/Author, thesis advisor/g, "Doctoral advisor");
x = x.replace(/Thesis advisor/g, "Doctoral advisor");
x = x.replace("Matthijs", "Dr. Matthijs");
x = x.replace("Christian", "Dr. Christian");
x = x.replace("Matthijs", "Dr Matthijs");
x = x.replace("Christian", "Dr Christian");
x = x.replace("Alex", "Prof. Alex");
x = x.replace("Bhanu", "Prof. Bhanu");
x = x.replace("Casper", "Prof. Casper");
x = x.replace("Corinna", "Dr. Corinna");
x = x.replace("Corinna", "Dr Corinna");
// others
x = x.replace("Bart", "Dr. Bart");
x = x.replace("Sofia", "Dr. Sofia");
x = x.replace("Dennis", "Dr. Dennis");
x = x.replace("Judith", "Dr. Judith");
x = x.replace("Gwen", "Dr. Gwen");
x = x.replace("Anthony", "Dr. Anthony");
x = x.replace("Rogier", "Dr. Rogier");
x = x.replace("Bart", "Dr Bart");
x = x.replace("Sofia", "Dr Sofia");
x = x.replace("Dennis", "Dr Dennis");
x = x.replace("Judith", "Dr Judith");
x = x.replace("Gwen", "Dr Gwen");
x = x.replace("Anthony", "Dr Anthony");
x = x.replace("Rogier", "Dr Rogier");
}
return(x);
}

View File

@ -47,7 +47,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9062</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9063</span>
</span>
</div>
@ -195,7 +195,7 @@
<code>AMR</code> (for R) <img src="./logo.png" align="right" height="120px"><a class="anchor" aria-label="anchor" href="#amr-for-r-"></a>
</h1></div>
<blockquote>
<p>Update: The latest EUCAST guideline for intrinsic resistance (v3.3, October 2021) is now supported, and our taxonomy tables has been updated as well (LPSN, 5 October 2021).</p>
<p>Update: The latest <a href="https://www.eucast.org/expert_rules_and_intrinsic_resistance/" class="external-link">EUCAST guideline for intrinsic resistance</a> (v3.3, October 2021) is now supported, and our taxonomy tables has been updated as well (LPSN, 5 October 2021). <strong>A new version will be released after the <a href="https://www.eucast.org/clinical_breakpoints/" class="external-link">EUCAST guideline for clinical breakpoints</a> (v12.0, likely January 2022) are implemented, to be expected shortly after the official guideline release.</strong></p>
</blockquote>
<div class="section level3">
<h3 id="what-is-amr-for-r">What is <code>AMR</code> (for R)?<a class="anchor" aria-label="anchor" href="#what-is-amr-for-r"></a>

View File

@ -17,7 +17,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9062</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9063</span>
</span>
</div>
@ -157,20 +157,21 @@
</div>
<div class="section level2">
<h2 class="page-header" data-toc-text="1.7.1.9062" id="amr-1719062">
<code>AMR</code> 1.7.1.9062<a class="anchor" aria-label="anchor" href="#amr-1719062"></a></h2>
<h2 class="page-header" data-toc-text="1.7.1.9063" id="amr-1719063">
<code>AMR</code> 1.7.1.9063<a class="anchor" aria-label="anchor" href="#amr-1719063"></a></h2>
<div class="section level3">
<h3 id="last-updated-december-1-7-1-9062"><small>Last updated: 6 December 2021</small><a class="anchor" aria-label="anchor" href="#last-updated-december-1-7-1-9062"></a></h3>
<h3 id="last-updated-december-1-7-1-9063"><small>Last updated: 9 December 2021</small><a class="anchor" aria-label="anchor" href="#last-updated-december-1-7-1-9063"></a></h3>
<div class="section level4">
<h4 id="breaking-changes-1-7-1-9062">Breaking changes<a class="anchor" aria-label="anchor" href="#breaking-changes-1-7-1-9062"></a></h4>
<h4 id="breaking-changes-1-7-1-9063">Breaking changes<a class="anchor" aria-label="anchor" href="#breaking-changes-1-7-1-9063"></a></h4>
<ul><li>Removed <code>p_symbol()</code> and all <code>filter_*()</code> functions (except for <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code>), which were all deprecated in a previous package version</li>
<li>Removed the <code>key_antibiotics()</code> and <code>key_antibiotics_equal()</code> functions, which were deprecated and superseded by <code><a href="../reference/key_antimicrobials.html">key_antimicrobials()</a></code> and <code><a href="../reference/key_antimicrobials.html">antimicrobials_equal()</a></code>
</li>
<li>Removed all previously implemented <code><a href="https://ggplot2.tidyverse.org/reference/ggplot.html" class="external-link">ggplot2::ggplot()</a></code> generics for classes <code>&lt;mic&gt;</code>, <code>&lt;disk&gt;</code>, <code>&lt;rsi&gt;</code> and <code>&lt;resistance_predict&gt;</code> as they did not follow the <code>ggplot2</code> logic. They were replaced with <code><a href="https://ggplot2.tidyverse.org/reference/autoplot.html" class="external-link">ggplot2::autoplot()</a></code> generics.</li>
</ul></div>
<div class="section level4">
<h4 id="new-1-7-1-9062">New<a class="anchor" aria-label="anchor" href="#new-1-7-1-9062"></a></h4>
<h4 id="new-1-7-1-9063">New<a class="anchor" aria-label="anchor" href="#new-1-7-1-9063"></a></h4>
<ul><li><p>Support for EUCAST Intrinsic Resistance and Unusual Phenotypes v3.3 (October 2021), effective in the <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code> function. This is now the default guideline (all other guidelines are still available).</p></li>
<li><p>Support for Danish, and also added missing translations of all antimicrobial drugs in Italian, French and Portuguese</p></li>
<li>
<p>Function <code><a href="../reference/ab_property.html">set_ab_names()</a></code> to rename data set columns that resemble antimicrobial drugs. This allows for quickly renaming columns to official names, ATC codes, etc. Its second argument can be a tidyverse way of selecting:</p>
<div class="sourceCode" id="cb1"><pre class="downlit sourceCode r">
@ -178,10 +179,10 @@
<span class="va">example_isolates</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span> <span class="fu"><a href="../reference/ab_property.html">set_ab_names</a></span><span class="op">(</span><span class="fu">where</span><span class="op">(</span><span class="va">is.rsi</span><span class="op">)</span><span class="op">)</span>
<span class="va">example_isolates</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span> <span class="fu"><a href="../reference/ab_property.html">set_ab_names</a></span><span class="op">(</span><span class="va">AMC</span><span class="op">:</span><span class="va">GEN</span>, property <span class="op">=</span> <span class="st">"atc"</span><span class="op">)</span></code></pre></div>
</li>
<li><p>Support for Danish, and also added missing translations of all antimicrobial drugs in Italian, French and Portuguese</p></li>
<li><p>Function <code><a href="../reference/mo_property.html">mo_lpsn()</a></code> to retrieve the <a href="https://lpsn.dsmz.de" class="external-link">LPSN</a> record ID</p></li>
</ul></div>
<div class="section level4">
<h4 id="changed-1-7-1-9062">Changed<a class="anchor" aria-label="anchor" href="#changed-1-7-1-9062"></a></h4>
<h4 id="changed-1-7-1-9063">Changed<a class="anchor" aria-label="anchor" href="#changed-1-7-1-9063"></a></h4>
<ul><li>Updated the bacterial taxonomy to 5 October 2021 (according to <a href="https://lpsn.dsmz.de" class="external-link">LPSN</a>), including all 11 new staphylococcal species named since 1 January last year</li>
<li>The <code>antibiotics</code> data set now contains <strong>all ATC codes</strong> that are available through the <a href="https://www.whocc.no" class="external-link">WHOCC website</a>, regardless of drugs being present in more than one ATC group. This means that:
<ul><li>Some drugs now contain multiple ATC codes (e.g., metronidazole contains 5)</li>
@ -210,7 +211,9 @@
<span class="va">example_isolates</span><span class="op">[</span>, <span class="fu"><a href="../reference/antibiotic_class_selectors.html">ab_selector</a></span><span class="op">(</span><span class="va">oral_ddd</span> <span class="op">&gt;</span> <span class="fl">1</span> <span class="op">&amp;</span> <span class="va">oral_units</span> <span class="op">==</span> <span class="st">"g"</span><span class="op">)</span><span class="op">]</span> <span class="co"># base R</span>
<span class="va">example_isolates</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span> <span class="fu"><a href="https://dplyr.tidyverse.org/reference/select.html" class="external-link">select</a></span><span class="op">(</span><span class="fu"><a href="../reference/antibiotic_class_selectors.html">ab_selector</a></span><span class="op">(</span><span class="va">oral_ddd</span> <span class="op">&gt;</span> <span class="fl">1</span> <span class="op">&amp;</span> <span class="va">oral_units</span> <span class="op">==</span> <span class="st">"g"</span><span class="op">)</span><span class="op">)</span> <span class="co"># dplyr</span></code></pre></div>
</li>
<li><p>Added the selector <code><a href="../reference/antibiotic_class_selectors.html">not_intrinsic_resistant()</a></code>, which only keeps antibiotic columns that are not intrinsic resistant for all microorganisms in a data set, based on the latest EUCAST guideline on intrinsic resistance. For example, if a data set contains only microorganism codes or names of <em>E. coli</em> and <em>K. pneumoniae</em> and contains a column “vancomycin”, this column will be removed (or rather, unselected) using this function.</p></li>
<li><p>Fix for using selectors multiple times in one call (e.g., using them in <code><a href="https://dplyr.tidyverse.org/reference/filter.html" class="external-link">dplyr::filter()</a></code> and immediately after in <code><a href="https://dplyr.tidyverse.org/reference/select.html" class="external-link">dplyr::select()</a></code>)</p></li>
<li><p>Fix for using having multiple columns that are coerced to the same antibiotic agent</p></li>
<li><p>Added argument <code>only_treatable</code>, which defaults to <code>TRUE</code> and will exclude drugs that are only for laboratory tests and not for treating patients (such as imipenem/EDTA and gentamicin-high)</p></li>
</ul></li>
<li>Fixed the Gram stain (<code><a href="../reference/mo_property.html">mo_gramstain()</a></code>) determination of the taxonomic class Negativicutes within the phylum of Firmicutes - they were considered Gram-positives because of their phylum but are actually Gram-negative. This impacts 137 taxonomic species, genera and families, such as <em>Negativicoccus</em> and <em>Veillonella</em>.</li>
@ -235,7 +238,7 @@
</li>
<li>Improved plot legends for MICs and disk diffusion values</li>
<li>Improved speed of <code><a href="../reference/as.ab.html">as.ab()</a></code> and all <code>ab_*()</code> functions</li>
<li>Added <code><a href="https://ggplot2.tidyverse.org/reference/fortify.html" class="external-link">fortify()</a></code> extensions for plotting methods</li>
<li>Added <code>fortify()</code> extensions for plotting methods</li>
<li>
<code>NA</code> values of the classes <code>&lt;mic&gt;</code>, <code>&lt;disk&gt;</code> and <code>&lt;rsi&gt;</code> are now exported objects of this package, e.g. <code>NA_mic_</code> is an <code>NA</code> of class <code>mic</code> (just like the base R <code>NA_character_</code> is an <code>NA</code> of class <code>character</code>)</li>
<li>The <code><a href="../reference/proportion.html">proportion_df()</a></code>, <code><a href="../reference/count.html">count_df()</a></code> and <code><a href="../reference/proportion.html">rsi_df()</a></code> functions now return with the additional S3 class rsi_df so they can be extended by other packages</li>
@ -247,7 +250,7 @@
<code><a href="../reference/get_episode.html">get_episode()</a></code> and <code><a href="../reference/get_episode.html">is_new_episode()</a></code> can now cope with <code>NA</code>s</li>
</ul></div>
<div class="section level4">
<h4 id="other-1-7-1-9062">Other<a class="anchor" aria-label="anchor" href="#other-1-7-1-9062"></a></h4>
<h4 id="other-1-7-1-9063">Other<a class="anchor" aria-label="anchor" href="#other-1-7-1-9063"></a></h4>
<ul><li>This package is now being maintained by two epidemiologists and a data scientist from two different non-profit healthcare organisations. All functions in this package are now all considered to be stable. Updates to the AMR interpretation rules (such as by EUCAST and CLSI), the microbial taxonomy, and the antibiotic dosages will all be updated every 6 to 12 months from now on.</li>
</ul></div>
</div>
@ -293,7 +296,7 @@
<li>The documentation of the <code><a href="../reference/first_isolate.html">first_isolate()</a></code> and <code><a href="../reference/key_antimicrobials.html">key_antimicrobials()</a></code> functions has been completely rewritten.</li>
</ul></li>
<li>Function <code><a href="../reference/antibiotic_class_selectors.html">betalactams()</a></code> as additional antbiotic column selector and function <code>filter_betalactams()</code> as additional antbiotic column filter. The group of betalactams consists of all carbapenems, cephalosporins and penicillins.</li>
<li>A <code><a href="https://ggplot2.tidyverse.org/reference/ggplot.html" class="external-link">ggplot()</a></code> method for <code><a href="../reference/resistance_predict.html">resistance_predict()</a></code>
<li>A <code>ggplot()</code> method for <code><a href="../reference/resistance_predict.html">resistance_predict()</a></code>
</li>
</ul></div>
<div class="section level4">
@ -376,7 +379,7 @@
<span class="co">#&gt; Filtering on oxazolidinones: value in column `LNZ` (linezolid) is either "R", "S" or "I"</span></code></pre></div>
</li>
<li><p>Support for custom MDRO guidelines, using the new <code><a href="../reference/mdro.html">custom_mdro_guideline()</a></code> function, please see <code><a href="../reference/mdro.html">mdro()</a></code> for additional info</p></li>
<li><p><code><a href="https://ggplot2.tidyverse.org/reference/ggplot.html" class="external-link">ggplot()</a></code> generics for classes <code>&lt;mic&gt;</code> and <code>&lt;disk&gt;</code></p></li>
<li><p><code>ggplot()</code> generics for classes <code>&lt;mic&gt;</code> and <code>&lt;disk&gt;</code></p></li>
<li>
<p>Function <code><a href="../reference/mo_property.html">mo_is_yeast()</a></code>, which determines whether a microorganism is a member of the taxonomic class Saccharomycetes or the taxonomic order Saccharomycetales:</p>
<div class="sourceCode" id="cb7"><pre class="downlit sourceCode r">
@ -427,7 +430,7 @@
<ul><li>Plotting of MIC and disk diffusion values now support interpretation colouring if you supply the microorganism and antimicrobial agent</li>
<li>All colours were updated to colour-blind friendly versions for values R, S and I for all plot methods (also applies to tibble printing)</li>
<li>Interpretation of MIC and disk diffusion values to R/SI will now be translated if the system language is German, Dutch or Spanish (see <code>translate</code>)</li>
<li>Plotting is now possible with base R using <code><a href="../reference/plot.html">plot()</a></code> and with ggplot2 using <code><a href="https://ggplot2.tidyverse.org/reference/ggplot.html" class="external-link">ggplot()</a></code> on any vector of MIC and disk diffusion values</li>
<li>Plotting is now possible with base R using <code><a href="../reference/plot.html">plot()</a></code> and with ggplot2 using <code>ggplot()</code> on any vector of MIC and disk diffusion values</li>
</ul></li>
<li>Updated SNOMED codes to US Edition of SNOMED CT from 1 September 2020 and added the source to the help page of the <code>microorganisms</code> data set</li>
<li>
@ -443,7 +446,7 @@
<code><a href="../reference/as.rsi.html">is.rsi.eligible()</a></code> now detects if the column name resembles an antibiotic name or code and now returns <code>TRUE</code> immediately if the input contains 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.</li>
<li>Functions <code><a href="../reference/get_episode.html">get_episode()</a></code> and <code><a href="../reference/get_episode.html">is_new_episode()</a></code> now support less than a day as value for argument <code>episode_days</code> (e.g., to include one patient/test per hour)</li>
<li>Argument <code>ampc_cephalosporin_resistance</code> in <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code> now also applies to value “I” (not only “S”)</li>
<li>Functions <code><a href="https://docs.ropensci.org/skimr/reference/print.html" class="external-link">print()</a></code> and <code><a href="https://rdrr.io/r/base/summary.html" class="external-link">summary()</a></code> on a Principal Components Analysis object (<code><a href="../reference/pca.html">pca()</a></code>) now print additional group info if the original data was grouped using <code><a href="https://dplyr.tidyverse.org/reference/group_by.html" class="external-link">dplyr::group_by()</a></code>
<li>Functions <code><a href="https://rdrr.io/r/base/print.html" class="external-link">print()</a></code> and <code><a href="https://rdrr.io/r/base/summary.html" class="external-link">summary()</a></code> on a Principal Components Analysis object (<code><a href="../reference/pca.html">pca()</a></code>) now print additional group info if the original data was grouped using <code><a href="https://dplyr.tidyverse.org/reference/group_by.html" class="external-link">dplyr::group_by()</a></code>
</li>
<li>Improved speed and reliability of <code><a href="../reference/guess_ab_col.html">guess_ab_col()</a></code>. As this also internally improves the reliability of <code><a href="../reference/first_isolate.html">first_isolate()</a></code> and <code><a href="../reference/mdro.html">mdro()</a></code>, this might have a slight impact on the results of those functions.</li>
<li>Fix for <code><a href="../reference/mo_property.html">mo_name()</a></code> when used in other languages than English</li>
@ -722,7 +725,7 @@
<p>Removed code dependency on all other R packages, making this package fully independent of the development process of others. This is a major code change, but will probably not be noticeable by most users.</p>
<p>Making this package independent of especially the tidyverse (e.g. packages <code>dplyr</code> and <code>tidyr</code>) tremendously increases sustainability on the long term, since tidyverse functions change quite often. Good for users, but hard for package maintainers. Most of our functions are replaced with versions that only rely on base R, which keeps this package fully functional for many years to come, without requiring a lot of maintenance to keep up with other packages anymore. Another upside it that this package can now be used with all versions of R since R-3.0.0 (April 2013). Our package is being used in settings where the resources are very limited. Fewer dependencies on newer software is helpful for such settings.</p>
<p>Negative effects of this change are:</p>
<ul><li>Function <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">freq()</a></code> that was borrowed from the <code>cleaner</code> package was removed. Use <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">cleaner::freq()</a></code>, or run <code><a href="https://github.com/msberends/cleaner" class="external-link">library("cleaner")</a></code> before you use <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">freq()</a></code>.</li>
<ul><li>Function <code>freq()</code> that was borrowed from the <code>cleaner</code> package was removed. Use <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">cleaner::freq()</a></code>, or run <code><a href="https://github.com/msberends/cleaner" class="external-link">library("cleaner")</a></code> before you use <code>freq()</code>.</li>
<li><del>Printing values of class <code>mo</code> or <code>rsi</code> in a tibble will no longer be in colour and printing <code>rsi</code> in a tibble will show the class <code>&lt;ord&gt;</code>, not <code>&lt;rsi&gt;</code> anymore. This is purely a visual effect.</del></li>
<li><del>All functions from the <code>mo_*</code> family (like <code><a href="../reference/mo_property.html">mo_name()</a></code> and <code><a href="../reference/mo_property.html">mo_gramstain()</a></code>) are noticeably slower when running on hundreds of thousands of rows.</del></li>
<li>For developers: classes <code>mo</code> and <code>ab</code> now both also inherit class <code>character</code>, to support any data transformation. This change invalidates code that checks for class length == 1.</li>
@ -985,7 +988,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<span class="co">#&gt; invalid microorganism code, NA generated</span></code></pre></div>
<p>This is important, because a value like <code>"testvalue"</code> could never be understood by e.g. <code><a href="../reference/mo_property.html">mo_name()</a></code>, although the class would suggest a valid microbial code.</p>
</li>
<li><p>Function <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">freq()</a></code> has moved to a new package, <a href="https://github.com/msberends/clean" class="external-link"><code>clean</code></a> (<a href="https://cran.r-project.org/package=clean" class="external-link">CRAN link</a>), since creating frequency tables actually does not fit the scope of this package. The <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">freq()</a></code> function still works, since it is re-exported from the <code>clean</code> package (which will be installed automatically upon updating this <code>AMR</code> package).</p></li>
<li><p>Function <code>freq()</code> has moved to a new package, <a href="https://github.com/msberends/clean" class="external-link"><code>clean</code></a> (<a href="https://cran.r-project.org/package=clean" class="external-link">CRAN link</a>), since creating frequency tables actually does not fit the scope of this package. The <code>freq()</code> function still works, since it is re-exported from the <code>clean</code> package (which will be installed automatically upon updating this <code>AMR</code> package).</p></li>
<li><p>Renamed data set <code>septic_patients</code> to <code>example_isolates</code></p></li>
</ul></div>
<div class="section level4">
@ -1214,7 +1217,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<li>The <code><a href="../reference/age.html">age()</a></code> function gained a new argument <code>exact</code> to determine ages with decimals</li>
<li>Removed deprecated functions <code>guess_mo()</code>, <code>guess_atc()</code>, <code>EUCAST_rules()</code>, <code>interpretive_reading()</code>, <code><a href="../reference/as.rsi.html">rsi()</a></code>
</li>
<li>Frequency tables (<code><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">freq()</a></code>):
<li>Frequency tables (<code>freq()</code>):
<ul><li><p>speed improvement for microbial IDs</p></li>
<li><p>fixed factor level names for R Markdown</p></li>
<li><p>when all values are unique it now shows a message instead of a warning</p></li>
@ -1223,12 +1226,12 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<div class="sourceCode" id="cb32"><pre class="downlit sourceCode r">
<code class="sourceCode R">
<span class="va">septic_patients</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">freq</a></span><span class="op">(</span><span class="va">age</span><span class="op">)</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu">freq</span><span class="op">(</span><span class="va">age</span><span class="op">)</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu"><a href="https://rdrr.io/r/graphics/boxplot.html" class="external-link">boxplot</a></span><span class="op">(</span><span class="op">)</span>
<span class="co"># grouped boxplots:</span>
<span class="va">septic_patients</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu"><a href="https://dplyr.tidyverse.org/reference/group_by.html" class="external-link">group_by</a></span><span class="op">(</span><span class="va">hospital_id</span><span class="op">)</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">freq</a></span><span class="op">(</span><span class="va">age</span><span class="op">)</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu">freq</span><span class="op">(</span><span class="va">age</span><span class="op">)</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu"><a href="https://rdrr.io/r/graphics/boxplot.html" class="external-link">boxplot</a></span><span class="op">(</span><span class="op">)</span></code></pre></div>
</li>
</ul></li>
@ -1237,7 +1240,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<li>Added ceftazidim intrinsic resistance to <em>Streptococci</em>
</li>
<li>Changed default settings for <code><a href="../reference/age_groups.html">age_groups()</a></code>, to let groups of fives and tens end with 100+ instead of 120+</li>
<li>Fix for <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">freq()</a></code> for when all values are <code>NA</code>
<li>Fix for <code>freq()</code> for when all values are <code>NA</code>
</li>
<li>Fix for <code><a href="../reference/first_isolate.html">first_isolate()</a></code> for when dates are missing</li>
<li>Improved speed of <code><a href="../reference/guess_ab_col.html">guess_ab_col()</a></code>
@ -1448,7 +1451,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<li>Now accepts high and low resistance: <code>"HIGH S"</code> will return <code>S</code>
</li>
</ul></li>
<li>Frequency tables (<code><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">freq()</a></code> function):
<li>Frequency tables (<code>freq()</code> function):
<ul><li>
<p>Support for tidyverse quasiquotation! Now you can create frequency tables of function outcomes:</p>
<div class="sourceCode" id="cb42"><pre class="downlit sourceCode r">
@ -1457,15 +1460,15 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<span class="co"># OLD WAY</span>
<span class="va">septic_patients</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu"><a href="https://dplyr.tidyverse.org/reference/mutate.html" class="external-link">mutate</a></span><span class="op">(</span>genus <span class="op">=</span> <span class="fu"><a href="../reference/mo_property.html">mo_genus</a></span><span class="op">(</span><span class="va">mo</span><span class="op">)</span><span class="op">)</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">freq</a></span><span class="op">(</span><span class="va">genus</span><span class="op">)</span>
<span class="fu">freq</span><span class="op">(</span><span class="va">genus</span><span class="op">)</span>
<span class="co"># NEW WAY</span>
<span class="va">septic_patients</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">freq</a></span><span class="op">(</span><span class="fu"><a href="../reference/mo_property.html">mo_genus</a></span><span class="op">(</span><span class="va">mo</span><span class="op">)</span><span class="op">)</span>
<span class="fu">freq</span><span class="op">(</span><span class="fu"><a href="../reference/mo_property.html">mo_genus</a></span><span class="op">(</span><span class="va">mo</span><span class="op">)</span><span class="op">)</span>
<span class="co"># Even supports grouping variables:</span>
<span class="va">septic_patients</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu"><a href="https://dplyr.tidyverse.org/reference/group_by.html" class="external-link">group_by</a></span><span class="op">(</span><span class="va">gender</span><span class="op">)</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">freq</a></span><span class="op">(</span><span class="fu"><a href="../reference/mo_property.html">mo_genus</a></span><span class="op">(</span><span class="va">mo</span><span class="op">)</span><span class="op">)</span></code></pre></div>
<span class="fu">freq</span><span class="op">(</span><span class="fu"><a href="../reference/mo_property.html">mo_genus</a></span><span class="op">(</span><span class="va">mo</span><span class="op">)</span><span class="op">)</span></code></pre></div>
</li>
<li><p>Header info is now available as a list, with the <code>header</code> function</p></li>
<li><p>The argument <code>header</code> is now set to <code>TRUE</code> at default, even for markdown</p></li>
@ -1534,21 +1537,21 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<li><p>Using <code>portion_*</code> functions now throws a warning when total available isolate is below argument <code>minimum</code></p></li>
<li><p>Functions <code>as.mo</code>, <code>as.rsi</code>, <code>as.mic</code>, <code>as.atc</code> and <code>freq</code> will not set package name as attribute anymore</p></li>
<li>
<p>Frequency tables - <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">freq()</a></code>:</p>
<p>Frequency tables - <code>freq()</code>:</p>
<ul><li>
<p>Support for grouping variables, test with:</p>
<div class="sourceCode" id="cb44"><pre class="downlit sourceCode r">
<code class="sourceCode R">
<span class="va">septic_patients</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu"><a href="https://dplyr.tidyverse.org/reference/group_by.html" class="external-link">group_by</a></span><span class="op">(</span><span class="va">hospital_id</span><span class="op">)</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">freq</a></span><span class="op">(</span><span class="va">gender</span><span class="op">)</span></code></pre></div>
<span class="fu">freq</span><span class="op">(</span><span class="va">gender</span><span class="op">)</span></code></pre></div>
</li>
<li>
<p>Support for (un)selecting columns:</p>
<div class="sourceCode" id="cb45"><pre class="downlit sourceCode r">
<code class="sourceCode R">
<span class="va">septic_patients</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">freq</a></span><span class="op">(</span><span class="va">hospital_id</span><span class="op">)</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu">freq</span><span class="op">(</span><span class="va">hospital_id</span><span class="op">)</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu"><a href="https://dplyr.tidyverse.org/reference/select.html" class="external-link">select</a></span><span class="op">(</span><span class="op">-</span><span class="va">count</span>, <span class="op">-</span><span class="va">cum_count</span><span class="op">)</span> <span class="co"># only get item, percent, cum_percent</span></code></pre></div>
</li>
<li><p>Check for <code><a href="https://hms.tidyverse.org/reference/Deprecated.html" class="external-link">hms::is.hms</a></code></p></li>
@ -1565,7 +1568,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<li><p>Removed diacritics from all authors (columns <code>microorganisms$ref</code> and <code>microorganisms.old$ref</code>) to comply with CRAN policy to only allow ASCII characters</p></li>
<li><p>Fix for <code>mo_property</code> not working properly</p></li>
<li><p>Fix for <code>eucast_rules</code> where some Streptococci would become ceftazidime R in EUCAST rule 4.5</p></li>
<li><p>Support for named vectors of class <code>mo</code>, useful for <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">top_freq()</a></code></p></li>
<li><p>Support for named vectors of class <code>mo</code>, useful for <code>top_freq()</code></p></li>
<li><p><code>ggplot_rsi</code> and <code>scale_y_percent</code> have <code>breaks</code> argument</p></li>
<li>
<p>AI improvements for <code>as.mo</code>:</p>
@ -1714,13 +1717,13 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<div class="sourceCode" id="cb52"><pre class="downlit sourceCode r">
<code class="sourceCode R">
<span class="va">my_matrix</span> <span class="op">=</span> <span class="fu"><a href="https://rdrr.io/r/base/with.html" class="external-link">with</a></span><span class="op">(</span><span class="va">septic_patients</span>, <span class="fu"><a href="https://rdrr.io/r/base/matrix.html" class="external-link">matrix</a></span><span class="op">(</span><span class="fu"><a href="https://rdrr.io/r/base/c.html" class="external-link">c</a></span><span class="op">(</span><span class="va">age</span>, <span class="va">gender</span><span class="op">)</span>, ncol <span class="op">=</span> <span class="fl">2</span><span class="op">)</span><span class="op">)</span>
<span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">freq</a></span><span class="op">(</span><span class="va">my_matrix</span><span class="op">)</span></code></pre></div>
<span class="fu">freq</span><span class="op">(</span><span class="va">my_matrix</span><span class="op">)</span></code></pre></div>
<p>For lists, subsetting is possible:</p>
<div class="sourceCode" id="cb53"><pre class="downlit sourceCode r">
<code class="sourceCode R">
<span class="va">my_list</span> <span class="op">=</span> <span class="fu"><a href="https://rdrr.io/r/base/list.html" class="external-link">list</a></span><span class="op">(</span>age <span class="op">=</span> <span class="va">septic_patients</span><span class="op">$</span><span class="va">age</span>, gender <span class="op">=</span> <span class="va">septic_patients</span><span class="op">$</span><span class="va">gender</span><span class="op">)</span>
<span class="va">my_list</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span> <span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">freq</a></span><span class="op">(</span><span class="va">age</span><span class="op">)</span>
<span class="va">my_list</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span> <span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html" class="external-link">freq</a></span><span class="op">(</span><span class="va">gender</span><span class="op">)</span></code></pre></div>
<span class="va">my_list</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span> <span class="fu">freq</span><span class="op">(</span><span class="va">age</span><span class="op">)</span>
<span class="va">my_list</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span> <span class="fu">freq</span><span class="op">(</span><span class="va">gender</span><span class="op">)</span></code></pre></div>
</li>
</ul></div>
<div class="section level5">

View File

@ -17,7 +17,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9062</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9063</span>
</span>
</div>
@ -153,7 +153,7 @@
<div class="col-md-9 contents">
<div class="page-header">
<h1>Antibiotic Selectors</h1>
<small class="dont-index">Source: <a href="https://github.com/msberends/AMR/blob/HEAD/R/ab_class_selectors.R" class="external-link"><code>R/ab_class_selectors.R</code></a></small>
<small class="dont-index">Source: <a href="https://github.com/msberends/AMR/blob/HEAD/R/ab_selectors.R" class="external-link"><code>R/ab_selectors.R</code></a></small>
<div class="hidden name"><code>antibiotic_class_selectors.Rd</code></div>
</div>
@ -165,10 +165,6 @@
<span class="fu">ab_selector</span><span class="op">(</span><span class="va">filter</span>, only_rsi_columns <span class="op">=</span> <span class="cn">FALSE</span>, only_treatable <span class="op">=</span> <span class="cn">TRUE</span>, <span class="va">...</span><span class="op">)</span>
<span class="fu">administrable_per_os</span><span class="op">(</span>only_rsi_columns <span class="op">=</span> <span class="cn">FALSE</span>, <span class="va">...</span><span class="op">)</span>
<span class="fu">administrable_iv</span><span class="op">(</span>only_rsi_columns <span class="op">=</span> <span class="cn">FALSE</span>, <span class="va">...</span><span class="op">)</span>
<span class="fu">aminoglycosides</span><span class="op">(</span>only_rsi_columns <span class="op">=</span> <span class="cn">FALSE</span>, only_treatable <span class="op">=</span> <span class="cn">TRUE</span>, <span class="va">...</span><span class="op">)</span>
<span class="fu">aminopenicillins</span><span class="op">(</span>only_rsi_columns <span class="op">=</span> <span class="cn">FALSE</span>, <span class="va">...</span><span class="op">)</span>
@ -217,7 +213,18 @@
<span class="fu">trimethoprims</span><span class="op">(</span>only_rsi_columns <span class="op">=</span> <span class="cn">FALSE</span>, <span class="va">...</span><span class="op">)</span>
<span class="fu">ureidopenicillins</span><span class="op">(</span>only_rsi_columns <span class="op">=</span> <span class="cn">FALSE</span>, <span class="va">...</span><span class="op">)</span></code></pre></div></div>
<span class="fu">ureidopenicillins</span><span class="op">(</span>only_rsi_columns <span class="op">=</span> <span class="cn">FALSE</span>, <span class="va">...</span><span class="op">)</span>
<span class="fu">administrable_per_os</span><span class="op">(</span>only_rsi_columns <span class="op">=</span> <span class="cn">FALSE</span>, <span class="va">...</span><span class="op">)</span>
<span class="fu">administrable_iv</span><span class="op">(</span>only_rsi_columns <span class="op">=</span> <span class="cn">FALSE</span>, <span class="va">...</span><span class="op">)</span>
<span class="fu">not_intrinsic_resistant</span><span class="op">(</span>
only_rsi_columns <span class="op">=</span> <span class="cn">FALSE</span>,
col_mo <span class="op">=</span> <span class="cn">NULL</span>,
version_expertrules <span class="op">=</span> <span class="fl">3.3</span>,
<span class="va">...</span>
<span class="op">)</span></code></pre></div></div>
<div id="arguments">
<h2>Arguments</h2>
@ -231,6 +238,10 @@
<dd><p>ignored, only in place to allow future extensions</p></dd>
<dt>filter</dt>
<dd><p>an <a href="https://rdrr.io/r/base/expression.html" class="external-link">expression</a> to be evaluated in the <a href="antibiotics.html">antibiotics</a> data set, such as <code>name %like% "trim"</code></p></dd>
<dt>col_mo</dt>
<dd><p>column name of the IDs of the microorganisms (see <code><a href="as.mo.html">as.mo()</a></code>), defaults to the first column of class <code><a href="as.mo.html">mo</a></code>. Values will be coerced using <code><a href="as.mo.html">as.mo()</a></code>.</p></dd>
<dt>version_expertrules</dt>
<dd><p>the version number to use for the EUCAST Expert Rules and Intrinsic Resistance guideline. Can be either "3.3", "3.2" or "3.1".</p></dd>
</dl></div>
<div id="value">
<h2>Value</h2>
@ -243,6 +254,7 @@
<p>The <code>ab_class()</code> function can be used to filter/select on a manually defined antibiotic class. It searches for results in the <a href="antibiotics.html">antibiotics</a> data set within the columns <code>group</code>, <code>atc_group1</code> and <code>atc_group2</code>.</p>
<p>The <code>ab_selector()</code> function can be used to internally filter the <a href="antibiotics.html">antibiotics</a> data set on any results, see <em>Examples</em>. It allows for filtering on a (part of) a certain name, and/or a group name or even a minimum of DDDs for oral treatment. This function yields the highest flexibility, but is also the least user-friendly, since it requires a hard-coded filter to set.</p>
<p>The <code>administrable_per_os()</code> and <code>administrable_iv()</code> functions also rely on the <a href="antibiotics.html">antibiotics</a> data set - antibiotic columns will be matched where a DDD (defined daily dose) for resp. oral and IV treatment is available in the <a href="antibiotics.html">antibiotics</a> data set.</p>
<p>The <code>not_intrinsic_resistant()</code> function can be used to only select antibiotic columns that pose no intrinsic resistance for the microorganisms in the data set. For example, if a data set contains only microorganism codes or names of <em>E. coli</em> and <em>K. pneumoniae</em> and contains a column "vancomycin", this column will be removed (or rather, unselected) using this function. It currently applies <a href="https://www.eucast.org/expert_rules_and_intrinsic_resistance/" class="external-link">'EUCAST Expert Rules' and 'EUCAST Intrinsic Resistance and Unusual Phenotypes' v3.3</a> (2021) to determine intrinsic resistance, using the <code><a href="eucast_rules.html">eucast_rules()</a></code> function internally. Because of this determination, this function is quite slow in terms of performance.</p>
</div>
<div id="full-list-of-supported-antibiotic-classes">
<h2>Full list of supported (antibiotic) classes</h2>
@ -349,6 +361,12 @@ The <a href="lifecycle.html">lifecycle</a> of this function is <strong>stable</s
<span class="co"># You can combine selectors with '&amp;' to be more specific:</span>
<span class="va">example_isolates</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu"><a href="https://dplyr.tidyverse.org/reference/select.html" class="external-link">select</a></span><span class="op">(</span><span class="fu">penicillins</span><span class="op">(</span><span class="op">)</span> <span class="op">&amp;</span> <span class="fu">administrable_per_os</span><span class="op">(</span><span class="op">)</span><span class="op">)</span>
<span class="co"># get AMR for only drugs that matter - no intrinsic resistance:</span>
<span class="va">example_isolates</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu"><a href="https://dplyr.tidyverse.org/reference/filter.html" class="external-link">filter</a></span><span class="op">(</span><span class="fu"><a href="mo_property.html">mo_genus</a></span><span class="op">(</span><span class="op">)</span> <span class="op"><a href="https://rdrr.io/r/base/match.html" class="external-link">%in%</a></span> <span class="fu"><a href="https://rdrr.io/r/base/c.html" class="external-link">c</a></span><span class="op">(</span><span class="st">"Escherichia"</span>, <span class="st">"Klebsiella"</span><span class="op">)</span><span class="op">)</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu"><a href="https://dplyr.tidyverse.org/reference/group_by.html" class="external-link">group_by</a></span><span class="op">(</span><span class="va">hospital_id</span><span class="op">)</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>
<span class="fu"><a href="https://dplyr.tidyverse.org/reference/summarise.html" class="external-link">summarise</a></span><span class="op">(</span><span class="fu"><a href="https://dplyr.tidyverse.org/reference/across.html" class="external-link">across</a></span><span class="op">(</span><span class="fu">not_intrinsic_resistant</span><span class="op">(</span><span class="op">)</span>, <span class="va">resistance</span><span class="op">)</span><span class="op">)</span>
<span class="co"># get susceptibility for antibiotics whose name contains "trim":</span>
<span class="va">example_isolates</span> <span class="op"><a href="https://magrittr.tidyverse.org/reference/pipe.html" class="external-link">%&gt;%</a></span>

View File

@ -18,7 +18,7 @@ To improve the interpretation of the antibiogram before EUCAST rules are applied
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9062</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9063</span>
</span>
</div>
@ -208,7 +208,7 @@ Leclercq et al. <strong>EUCAST expert rules in antimicrobial susceptibility test
<dt>version_expertrules</dt>
<dd><p>the version number to use for the EUCAST Expert Rules and Intrinsic Resistance guideline. Can be either "3.3", "3.2" or "3.1".</p></dd>
<dt>ampc_cephalosporin_resistance</dt>
<dd><p>a <a href="https://rdrr.io/r/base/character.html" class="external-link">character</a> value that should be applied to cefotaxime, ceftriaxone and ceftazidime for AmpC de-repressed cephalosporin-resistant mutants, defaults to <code>NA</code>. Currently only works when <code>version_expertrules</code> is <code>3.2</code>; '<em>EUCAST Expert Rules v3.2 on Enterobacterales</em>' 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 <code>NA</code> (the default) for this argument will remove results for these three agents, while e.g. a value of <code>"R"</code> will make the results for these agents resistant. Use <code>NULL</code> or <code>FALSE</code> to not alter results for these three agents of AmpC de-repressed cephalosporin-resistant mutants. Using <code>TRUE</code> is equal to using <code>"R"</code>. <br> For <em>EUCAST Expert Rules</em> v3.2, this rule applies to: <em>Citrobacter braakii</em>, <em>Citrobacter freundii</em>, <em>Citrobacter gillenii</em>, <em>Citrobacter murliniae</em>, <em>Citrobacter rodenticum</em>, <em>Citrobacter sedlakii</em>, <em>Citrobacter werkmanii</em>, <em>Citrobacter youngae</em>, <em>Enterobacter</em>, <em>Hafnia alvei</em>, <em>Klebsiella aerogenes</em>, <em>Morganella morganii</em>, <em>Providencia</em> and <em>Serratia</em>.</p></dd>
<dd><p>a <a href="https://rdrr.io/r/base/character.html" class="external-link">character</a> value that should be applied to cefotaxime, ceftriaxone and ceftazidime for AmpC de-repressed cephalosporin-resistant mutants, defaults to <code>NA</code>. Currently only works when <code>version_expertrules</code> is <code>3.2</code> and higher; these version of '<em>EUCAST Expert Rules on Enterobacterales</em>' state 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 <code>NA</code> (the default) for this argument will remove results for these three agents, while e.g. a value of <code>"R"</code> will make the results for these agents resistant. Use <code>NULL</code> or <code>FALSE</code> to not alter results for these three agents of AmpC de-repressed cephalosporin-resistant mutants. Using <code>TRUE</code> is equal to using <code>"R"</code>. <br> For <em>EUCAST Expert Rules</em> v3.2, this rule applies to: <em>Citrobacter braakii</em>, <em>Citrobacter freundii</em>, <em>Citrobacter gillenii</em>, <em>Citrobacter murliniae</em>, <em>Citrobacter rodenticum</em>, <em>Citrobacter sedlakii</em>, <em>Citrobacter werkmanii</em>, <em>Citrobacter youngae</em>, <em>Enterobacter</em>, <em>Hafnia alvei</em>, <em>Klebsiella aerogenes</em>, <em>Morganella morganii</em>, <em>Providencia</em> and <em>Serratia</em>.</p></dd>
<dt>only_rsi_columns</dt>
<dd><p>a <a href="https://rdrr.io/r/base/logical.html" class="external-link">logical</a> to indicate whether only antibiotic columns must be detected that were transformed to class <code>&lt;rsi&gt;</code> (see <code><a href="as.rsi.html">as.rsi()</a></code>) on beforehand (defaults to <code>FALSE</code>)</p></dd>
<dt>custom_rules</dt>

View File

@ -17,7 +17,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9062</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9063</span>
</span>
</div>
@ -164,7 +164,7 @@
</td>
<td><p>Transform Input to a Microorganism Code</p></td>
</tr><tr><td>
<p><code><a href="mo_property.html">mo_name()</a></code> <code><a href="mo_property.html">mo_fullname()</a></code> <code><a href="mo_property.html">mo_shortname()</a></code> <code><a href="mo_property.html">mo_subspecies()</a></code> <code><a href="mo_property.html">mo_species()</a></code> <code><a href="mo_property.html">mo_genus()</a></code> <code><a href="mo_property.html">mo_family()</a></code> <code><a href="mo_property.html">mo_order()</a></code> <code><a href="mo_property.html">mo_class()</a></code> <code><a href="mo_property.html">mo_phylum()</a></code> <code><a href="mo_property.html">mo_kingdom()</a></code> <code><a href="mo_property.html">mo_domain()</a></code> <code><a href="mo_property.html">mo_type()</a></code> <code><a href="mo_property.html">mo_gramstain()</a></code> <code><a href="mo_property.html">mo_is_gram_negative()</a></code> <code><a href="mo_property.html">mo_is_gram_positive()</a></code> <code><a href="mo_property.html">mo_is_yeast()</a></code> <code><a href="mo_property.html">mo_is_intrinsic_resistant()</a></code> <code><a href="mo_property.html">mo_snomed()</a></code> <code><a href="mo_property.html">mo_ref()</a></code> <code><a href="mo_property.html">mo_authors()</a></code> <code><a href="mo_property.html">mo_year()</a></code> <code><a href="mo_property.html">mo_rank()</a></code> <code><a href="mo_property.html">mo_taxonomy()</a></code> <code><a href="mo_property.html">mo_synonyms()</a></code> <code><a href="mo_property.html">mo_info()</a></code> <code><a href="mo_property.html">mo_url()</a></code> <code><a href="mo_property.html">mo_property()</a></code> </p>
<p><code><a href="mo_property.html">mo_name()</a></code> <code><a href="mo_property.html">mo_fullname()</a></code> <code><a href="mo_property.html">mo_shortname()</a></code> <code><a href="mo_property.html">mo_subspecies()</a></code> <code><a href="mo_property.html">mo_species()</a></code> <code><a href="mo_property.html">mo_genus()</a></code> <code><a href="mo_property.html">mo_family()</a></code> <code><a href="mo_property.html">mo_order()</a></code> <code><a href="mo_property.html">mo_class()</a></code> <code><a href="mo_property.html">mo_phylum()</a></code> <code><a href="mo_property.html">mo_kingdom()</a></code> <code><a href="mo_property.html">mo_domain()</a></code> <code><a href="mo_property.html">mo_type()</a></code> <code><a href="mo_property.html">mo_gramstain()</a></code> <code><a href="mo_property.html">mo_is_gram_negative()</a></code> <code><a href="mo_property.html">mo_is_gram_positive()</a></code> <code><a href="mo_property.html">mo_is_yeast()</a></code> <code><a href="mo_property.html">mo_is_intrinsic_resistant()</a></code> <code><a href="mo_property.html">mo_snomed()</a></code> <code><a href="mo_property.html">mo_ref()</a></code> <code><a href="mo_property.html">mo_authors()</a></code> <code><a href="mo_property.html">mo_year()</a></code> <code><a href="mo_property.html">mo_lpsn()</a></code> <code><a href="mo_property.html">mo_rank()</a></code> <code><a href="mo_property.html">mo_taxonomy()</a></code> <code><a href="mo_property.html">mo_synonyms()</a></code> <code><a href="mo_property.html">mo_info()</a></code> <code><a href="mo_property.html">mo_url()</a></code> <code><a href="mo_property.html">mo_property()</a></code> </p>
</td>
<td><p>Get Properties of a Microorganism</p></td>
</tr><tr><td>
@ -256,7 +256,7 @@
</td>
<td><p>Determine Bug-Drug Combinations</p></td>
</tr><tr><td>
<p><code><a href="antibiotic_class_selectors.html">ab_class()</a></code> <code><a href="antibiotic_class_selectors.html">ab_selector()</a></code> <code><a href="antibiotic_class_selectors.html">administrable_per_os()</a></code> <code><a href="antibiotic_class_selectors.html">administrable_iv()</a></code> <code><a href="antibiotic_class_selectors.html">aminoglycosides()</a></code> <code><a href="antibiotic_class_selectors.html">aminopenicillins()</a></code> <code><a href="antibiotic_class_selectors.html">antifungals()</a></code> <code><a href="antibiotic_class_selectors.html">antimycobacterials()</a></code> <code><a href="antibiotic_class_selectors.html">betalactams()</a></code> <code><a href="antibiotic_class_selectors.html">carbapenems()</a></code> <code><a href="antibiotic_class_selectors.html">cephalosporins()</a></code> <code><a href="antibiotic_class_selectors.html">cephalosporins_1st()</a></code> <code><a href="antibiotic_class_selectors.html">cephalosporins_2nd()</a></code> <code><a href="antibiotic_class_selectors.html">cephalosporins_3rd()</a></code> <code><a href="antibiotic_class_selectors.html">cephalosporins_4th()</a></code> <code><a href="antibiotic_class_selectors.html">cephalosporins_5th()</a></code> <code><a href="antibiotic_class_selectors.html">fluoroquinolones()</a></code> <code><a href="antibiotic_class_selectors.html">glycopeptides()</a></code> <code><a href="antibiotic_class_selectors.html">lincosamides()</a></code> <code><a href="antibiotic_class_selectors.html">lipoglycopeptides()</a></code> <code><a href="antibiotic_class_selectors.html">macrolides()</a></code> <code><a href="antibiotic_class_selectors.html">oxazolidinones()</a></code> <code><a href="antibiotic_class_selectors.html">penicillins()</a></code> <code><a href="antibiotic_class_selectors.html">polymyxins()</a></code> <code><a href="antibiotic_class_selectors.html">streptogramins()</a></code> <code><a href="antibiotic_class_selectors.html">quinolones()</a></code> <code><a href="antibiotic_class_selectors.html">tetracyclines()</a></code> <code><a href="antibiotic_class_selectors.html">trimethoprims()</a></code> <code><a href="antibiotic_class_selectors.html">ureidopenicillins()</a></code> </p>
<p><code><a href="antibiotic_class_selectors.html">ab_class()</a></code> <code><a href="antibiotic_class_selectors.html">ab_selector()</a></code> <code><a href="antibiotic_class_selectors.html">aminoglycosides()</a></code> <code><a href="antibiotic_class_selectors.html">aminopenicillins()</a></code> <code><a href="antibiotic_class_selectors.html">antifungals()</a></code> <code><a href="antibiotic_class_selectors.html">antimycobacterials()</a></code> <code><a href="antibiotic_class_selectors.html">betalactams()</a></code> <code><a href="antibiotic_class_selectors.html">carbapenems()</a></code> <code><a href="antibiotic_class_selectors.html">cephalosporins()</a></code> <code><a href="antibiotic_class_selectors.html">cephalosporins_1st()</a></code> <code><a href="antibiotic_class_selectors.html">cephalosporins_2nd()</a></code> <code><a href="antibiotic_class_selectors.html">cephalosporins_3rd()</a></code> <code><a href="antibiotic_class_selectors.html">cephalosporins_4th()</a></code> <code><a href="antibiotic_class_selectors.html">cephalosporins_5th()</a></code> <code><a href="antibiotic_class_selectors.html">fluoroquinolones()</a></code> <code><a href="antibiotic_class_selectors.html">glycopeptides()</a></code> <code><a href="antibiotic_class_selectors.html">lincosamides()</a></code> <code><a href="antibiotic_class_selectors.html">lipoglycopeptides()</a></code> <code><a href="antibiotic_class_selectors.html">macrolides()</a></code> <code><a href="antibiotic_class_selectors.html">oxazolidinones()</a></code> <code><a href="antibiotic_class_selectors.html">penicillins()</a></code> <code><a href="antibiotic_class_selectors.html">polymyxins()</a></code> <code><a href="antibiotic_class_selectors.html">streptogramins()</a></code> <code><a href="antibiotic_class_selectors.html">quinolones()</a></code> <code><a href="antibiotic_class_selectors.html">tetracyclines()</a></code> <code><a href="antibiotic_class_selectors.html">trimethoprims()</a></code> <code><a href="antibiotic_class_selectors.html">ureidopenicillins()</a></code> <code><a href="antibiotic_class_selectors.html">administrable_per_os()</a></code> <code><a href="antibiotic_class_selectors.html">administrable_iv()</a></code> <code><a href="antibiotic_class_selectors.html">not_intrinsic_resistant()</a></code> </p>
</td>
<td><p>Antibiotic Selectors</p></td>
</tr><tr><td>

View File

@ -17,7 +17,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9062</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9063</span>
</span>
</div>
@ -208,7 +208,7 @@ The <a href="lifecycle.html">lifecycle</a> of this function is <strong>stable</s
</div>
<div id="author">
<h2>Author</h2>
<p>Matthijs S. Berends</p>
<p>Dr. Matthijs Berends</p>
</div>
<div id="ref-examples">

View File

@ -17,7 +17,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9062</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9063</span>
</span>
</div>
@ -205,6 +205,8 @@
<span class="fu">mo_year</span><span class="op">(</span><span class="va">x</span>, language <span class="op">=</span> <span class="fu"><a href="translate.html">get_locale</a></span><span class="op">(</span><span class="op">)</span>, <span class="va">...</span><span class="op">)</span>
<span class="fu">mo_lpsn</span><span class="op">(</span><span class="va">x</span>, language <span class="op">=</span> <span class="fu"><a href="translate.html">get_locale</a></span><span class="op">(</span><span class="op">)</span>, <span class="va">...</span><span class="op">)</span>
<span class="fu">mo_rank</span><span class="op">(</span><span class="va">x</span>, language <span class="op">=</span> <span class="fu"><a href="translate.html">get_locale</a></span><span class="op">(</span><span class="op">)</span>, <span class="va">...</span><span class="op">)</span>
<span class="fu">mo_taxonomy</span><span class="op">(</span><span class="va">x</span>, language <span class="op">=</span> <span class="fu"><a href="translate.html">get_locale</a></span><span class="op">(</span><span class="op">)</span>, <span class="va">...</span><span class="op">)</span>
@ -344,6 +346,7 @@ This package contains the complete taxonomic tree of almost all microorganisms (
<span class="fu">mo_ref</span><span class="op">(</span><span class="st">"E. coli"</span><span class="op">)</span> <span class="co"># "Castellani et al., 1919"</span>
<span class="fu">mo_authors</span><span class="op">(</span><span class="st">"E. coli"</span><span class="op">)</span> <span class="co"># "Castellani et al."</span>
<span class="fu">mo_year</span><span class="op">(</span><span class="st">"E. coli"</span><span class="op">)</span> <span class="co"># 1919</span>
<span class="fu">mo_lpsn</span><span class="op">(</span><span class="st">"E. coli"</span><span class="op">)</span> <span class="co"># 776057 (LPSN record ID)</span>
<span class="co"># abbreviations known in the field -----------------------------------------</span>
<span class="fu">mo_genus</span><span class="op">(</span><span class="st">"MRSA"</span><span class="op">)</span> <span class="co"># "Staphylococcus"</span>

View File

@ -17,7 +17,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9062</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">1.7.1.9063</span>
</span>
</div>

View File

@ -1,6 +1,7 @@
# `AMR` (for R) <img src="./logo.png" align="right" height="120px" />
> Update: The latest EUCAST guideline for intrinsic resistance (v3.3, October 2021) is now supported, and our taxonomy tables has been updated as well (LPSN, 5 October 2021).
> Update: The latest [EUCAST guideline for intrinsic resistance](https://www.eucast.org/expert_rules_and_intrinsic_resistance/) (v3.3, October 2021) is now supported, and our taxonomy tables has been updated as well (LPSN, 5 October 2021).
> **A new version will be released after the [EUCAST guideline for clinical breakpoints](https://www.eucast.org/clinical_breakpoints/) (v12.0, likely January 2022) are implemented, to be expected shortly after the official guideline release.**
### What is `AMR` (for R)?

View File

@ -69,6 +69,7 @@ expect_identical(colnames(set_ab_names(example_isolates[, 20:25], language = "nl
c("Cefoxitine", "Cefotaxim", "Ceftazidim", "Ceftriaxon", "Gentamicine", "Tobramycine"))
expect_identical(colnames(set_ab_names(example_isolates[, 20:25], property = "atc")),
c("J01DC01", "J01DD01", "J01DD02", "J01DD04", "J01GB03", "J01GB01"))
if (AMR:::pkg_is_available("dplyr", min_version = "1.0.0")) {
expect_identical(example_isolates %>% set_ab_names(),
example_isolates %>% rename_with(set_ab_names))

View File

@ -76,6 +76,17 @@ expect_equal(nrow(example_isolates[all(c(carbapenems(), aminoglycosides()) == "R
expect_equal(nrow(example_isolates[any(carbapenems() == "R"), penicillins()]), 55, tolerance = 0.5)
expect_equal(ncol(example_isolates[any(carbapenems() == "R"), penicillins()]), 7, tolerance = 0.5)
x <- data.frame(x = 0,
mo = 0,
gen = "S",
genta = "S",
J01GB03 = "S",
tobra = "S",
Tobracin = "S")
# should have the first hits
expect_identical(colnames(x[, aminoglycosides()]),
c("gen", "tobra"))
if (AMR:::pkg_is_available("dplyr", min_version = "1.0.0")) {
expect_equal(example_isolates %>% select(administrable_per_os() & penicillins()) %>% ncol(), 5, tolerance = 0.5)
expect_equal(example_isolates %>% select(administrable_iv() & penicillins()) %>% ncol(), 7, tolerance = 0.5)

View File

@ -92,6 +92,8 @@ expect_identical(mo_property("Escherichia coli", property = "genus"),
mo_genus("Escherichia coli"))
expect_identical(mo_property("Escherichia coli", property = "species"),
mo_species("Escherichia coli"))
expect_identical(mo_property("Escherichia coli", property = "species_id"),
mo_lpsn("Escherichia coli"))
expect_identical(suppressWarnings(mo_ref("Chlamydia psittaci")), "Page, 1968")
expect_identical(mo_ref("Chlamydophila psittaci"), "Everett et al., 1999")

View File

@ -1,11 +1,9 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/ab_class_selectors.R
% Please edit documentation in R/ab_selectors.R
\name{antibiotic_class_selectors}
\alias{antibiotic_class_selectors}
\alias{ab_class}
\alias{ab_selector}
\alias{administrable_per_os}
\alias{administrable_iv}
\alias{aminoglycosides}
\alias{aminopenicillins}
\alias{antifungals}
@ -31,16 +29,15 @@
\alias{tetracyclines}
\alias{trimethoprims}
\alias{ureidopenicillins}
\alias{administrable_per_os}
\alias{administrable_iv}
\alias{not_intrinsic_resistant}
\title{Antibiotic Selectors}
\usage{
ab_class(ab_class, only_rsi_columns = FALSE, only_treatable = TRUE, ...)
ab_selector(filter, only_rsi_columns = FALSE, only_treatable = TRUE, ...)
administrable_per_os(only_rsi_columns = FALSE, ...)
administrable_iv(only_rsi_columns = FALSE, ...)
aminoglycosides(only_rsi_columns = FALSE, only_treatable = TRUE, ...)
aminopenicillins(only_rsi_columns = FALSE, ...)
@ -90,6 +87,17 @@ tetracyclines(only_rsi_columns = FALSE, ...)
trimethoprims(only_rsi_columns = FALSE, ...)
ureidopenicillins(only_rsi_columns = FALSE, ...)
administrable_per_os(only_rsi_columns = FALSE, ...)
administrable_iv(only_rsi_columns = FALSE, ...)
not_intrinsic_resistant(
only_rsi_columns = FALSE,
col_mo = NULL,
version_expertrules = 3.3,
...
)
}
\arguments{
\item{ab_class}{an antimicrobial class or a part of it, such as \code{"carba"} and \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.}
@ -101,6 +109,10 @@ ureidopenicillins(only_rsi_columns = FALSE, ...)
\item{...}{ignored, only in place to allow future extensions}
\item{filter}{an \link{expression} to be evaluated in the \link{antibiotics} data set, such as \code{name \%like\% "trim"}}
\item{col_mo}{column name of the IDs of the microorganisms (see \code{\link[=as.mo]{as.mo()}}), defaults to the first column of class \code{\link{mo}}. Values will be coerced using \code{\link[=as.mo]{as.mo()}}.}
\item{version_expertrules}{the version number to use for the EUCAST Expert Rules and Intrinsic Resistance guideline. Can be either "3.3", "3.2" or "3.1".}
}
\value{
(internally) a \link{character} vector of column names, with additional class \code{"ab_selector"}
@ -118,6 +130,8 @@ The \code{\link[=ab_class]{ab_class()}} function can be used to filter/select on
The \code{\link[=ab_selector]{ab_selector()}} function can be used to internally filter the \link{antibiotics} data set on any results, see \emph{Examples}. It allows for filtering on a (part of) a certain name, and/or a group name or even a minimum of DDDs for oral treatment. This function yields the highest flexibility, but is also the least user-friendly, since it requires a hard-coded filter to set.
The \code{\link[=administrable_per_os]{administrable_per_os()}} and \code{\link[=administrable_iv]{administrable_iv()}} functions also rely on the \link{antibiotics} data set - antibiotic columns will be matched where a DDD (defined daily dose) for resp. oral and IV treatment is available in the \link{antibiotics} data set.
The \code{\link[=not_intrinsic_resistant]{not_intrinsic_resistant()}} function can be used to only select antibiotic columns that pose no intrinsic resistance for the microorganisms in the data set. For example, if a data set contains only microorganism codes or names of \emph{E. coli} and \emph{K. pneumoniae} and contains a column "vancomycin", this column will be removed (or rather, unselected) using this function. It currently applies \href{https://www.eucast.org/expert_rules_and_intrinsic_resistance/}{'EUCAST Expert Rules' and 'EUCAST Intrinsic Resistance and Unusual Phenotypes' v3.3} (2021) to determine intrinsic resistance, using the \code{\link[=eucast_rules]{eucast_rules()}} function internally. Because of this determination, this function is quite slow in terms of performance.
}
\section{Full list of supported (antibiotic) classes}{
@ -221,6 +235,12 @@ if (require("dplyr")) {
# You can combine selectors with '&' to be more specific:
example_isolates \%>\%
select(penicillins() & administrable_per_os())
# get AMR for only drugs that matter - no intrinsic resistance:
example_isolates \%>\%
filter(mo_genus() \%in\% c("Escherichia", "Klebsiella")) \%>\%
group_by(hospital_id) \%>\%
summarise(across(not_intrinsic_resistant(), resistance))
# get susceptibility for antibiotics whose name contains "trim":
example_isolates \%>\%

View File

@ -49,7 +49,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.3", "3.2" or "3.1".}
\item{ampc_cephalosporin_resistance}{a \link{character} value that should be applied to cefotaxime, ceftriaxone and ceftazidime 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 three agents. A value of \code{NA} (the default) for this argument will remove results for these three agents, while e.g. a value of \code{"R"} will make the results for these agents resistant. Use \code{NULL} or \code{FALSE} to not alter results for these three agents of AmpC de-repressed cephalosporin-resistant mutants. Using \code{TRUE} is equal to using \code{"R"}. \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{ampc_cephalosporin_resistance}{a \link{character} value that should be applied to cefotaxime, ceftriaxone and ceftazidime for AmpC de-repressed cephalosporin-resistant mutants, defaults to \code{NA}. Currently only works when \code{version_expertrules} is \code{3.2} and higher; these version of '\emph{EUCAST Expert Rules on Enterobacterales}' state 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 \code{NA} (the default) for this argument will remove results for these three agents, while e.g. a value of \code{"R"} will make the results for these agents resistant. Use \code{NULL} or \code{FALSE} to not alter results for these three agents of AmpC de-repressed cephalosporin-resistant mutants. Using \code{TRUE} is equal to using \code{"R"}. \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{only_rsi_columns}{a \link{logical} to indicate whether only antibiotic columns must be detected that were transformed to class \verb{<rsi>} (see \code{\link[=as.rsi]{as.rsi()}}) on beforehand (defaults to \code{FALSE})}

View File

@ -63,5 +63,5 @@ mo_matching_score(x = "E. coli",
n = c("Escherichia coli", "Entamoeba coli"))
}
\author{
Matthijs S. Berends
Dr. Matthijs Berends
}

View File

@ -24,6 +24,7 @@
\alias{mo_ref}
\alias{mo_authors}
\alias{mo_year}
\alias{mo_lpsn}
\alias{mo_rank}
\alias{mo_taxonomy}
\alias{mo_synonyms}
@ -75,6 +76,8 @@ mo_authors(x, language = get_locale(), ...)
mo_year(x, language = get_locale(), ...)
mo_lpsn(x, language = get_locale(), ...)
mo_rank(x, language = get_locale(), ...)
mo_taxonomy(x, language = get_locale(), ...)
@ -226,6 +229,7 @@ mo_synonyms("E. coli") # get previously accepted taxonomic names
mo_ref("E. coli") # "Castellani et al., 1919"
mo_authors("E. coli") # "Castellani et al."
mo_year("E. coli") # 1919
mo_lpsn("E. coli") # 776057 (LPSN record ID)
# abbreviations known in the field -----------------------------------------
mo_genus("MRSA") # "Staphylococcus"

View File

@ -97,20 +97,20 @@ $(document).ready(function() {
x = x.replace(/Author, contributor/g, "Maintainer");
x = x.replace(/Author, thesis advisor/g, "Doctoral advisor");
x = x.replace(/Thesis advisor/g, "Doctoral advisor");
x = x.replace("Matthijs", "Dr. Matthijs");
x = x.replace("Christian", "Dr. Christian");
x = x.replace("Matthijs", "Dr Matthijs");
x = x.replace("Christian", "Dr Christian");
x = x.replace("Alex", "Prof. Alex");
x = x.replace("Bhanu", "Prof. Bhanu");
x = x.replace("Casper", "Prof. Casper");
x = x.replace("Corinna", "Dr. Corinna");
x = x.replace("Corinna", "Dr Corinna");
// others
x = x.replace("Bart", "Dr. Bart");
x = x.replace("Sofia", "Dr. Sofia");
x = x.replace("Dennis", "Dr. Dennis");
x = x.replace("Judith", "Dr. Judith");
x = x.replace("Gwen", "Dr. Gwen");
x = x.replace("Anthony", "Dr. Anthony");
x = x.replace("Rogier", "Dr. Rogier");
x = x.replace("Bart", "Dr Bart");
x = x.replace("Sofia", "Dr Sofia");
x = x.replace("Dennis", "Dr Dennis");
x = x.replace("Judith", "Dr Judith");
x = x.replace("Gwen", "Dr Gwen");
x = x.replace("Anthony", "Dr Anthony");
x = x.replace("Rogier", "Dr Rogier");
}
return(x);
}