(v1.6.0.9007) documentation custom eucast rules, progress bar as.mo

This commit is contained in:
dr. M.S. (Matthijs) Berends 2021-04-20 10:46:17 +02:00
parent de66eccf43
commit c6289c3fc3
44 changed files with 338 additions and 128 deletions

View File

@ -1,6 +1,6 @@
Package: AMR
Version: 1.6.0.9006
Date: 2021-04-16
Version: 1.6.0.9007
Date: 2021-04-20
Title: Antimicrobial Resistance Data Analysis
Authors@R: c(
person(role = c("aut", "cre"),

View File

@ -1,5 +1,5 @@
# AMR 1.6.0.9006
## <small>Last updated: 16 April 2021</small>
# AMR 1.6.0.9007
## <small>Last updated: 20 April 2021</small>
### New
* Function `custom_eucast_rules()` that brings support for custom AMR rules in `eucast_rules()`
@ -15,6 +15,7 @@
* `first_isolate()` can now take a vector of values for `col_keyantibiotics` and can have an episode length of `Inf`
* `like()` (and `%like%`) now checks if `pattern` is a *valid* regular expression
* Fixed an installation error on R-3.0
* Added `info` argument to `as.mo()` to turn on/off the progress bar
# AMR 1.6.0

View File

@ -932,8 +932,8 @@ font_stripstyle <- function(x) {
gsub("(?:(?:\\x{001b}\\[)|\\x{009b})(?:(?:[0-9]{1,3})?(?:(?:;[0-9]{0,3})*)?[A-M|f-m])|\\x{001b}[A-M]", "", x, perl = TRUE)
}
progress_ticker <- function(n = 1, n_min = 0, ...) {
if (!interactive() || n < n_min) {
progress_ticker <- function(n = 1, n_min = 0, print = TRUE, ...) {
if (print == FALSE || n < n_min) {
pb <- list()
pb$tick <- function() {
invisible()

7
R/ab.R
View File

@ -29,7 +29,7 @@
#' @inheritSection lifecycle Stable Lifecycle
#' @param x character vector to determine to antibiotic ID
#' @param flag_multiple_results logical to indicate whether a note should be printed to the console that probably more than one antibiotic code or name can be retrieved from a single input value.
#' @param info logical to indicate whether a progress bar should be printed
#' @param info a [logical] to indicate whether a progress bar should be printed, defaults to `TRUE` only in interactive mode
#' @param ... arguments passed on to internal functions
#' @rdname as.ab
#' @inheritSection WHOCC WHOCC
@ -90,7 +90,7 @@
#' rename_with(as.ab, where(is.rsi))
#'
#' }
as.ab <- function(x, flag_multiple_results = TRUE, info = TRUE, ...) {
as.ab <- function(x, flag_multiple_results = TRUE, info = interactive(), ...) {
meet_criteria(x, allow_class = c("character", "numeric", "integer", "factor"), allow_NA = TRUE)
meet_criteria(flag_multiple_results, allow_class = "logical", has_length = 1)
meet_criteria(info, allow_class = "logical", has_length = 1)
@ -155,8 +155,7 @@ as.ab <- function(x, flag_multiple_results = TRUE, info = TRUE, ...) {
}
if (initial_search == TRUE) {
progress <- progress_ticker(n = length(x),
n_min = ifelse(isTRUE(info) & isFALSE(fast_mode), 25, length(x) + 1)) # start if n >= 25
progress <- progress_ticker(n = length(x), n_min = 25, print = info) # start if n >= 25
on.exit(close(progress))
}

View File

@ -32,6 +32,7 @@
#' @param collapse character to pass on to `paste(, collapse = ...)` to only return one character per element of `text`, see *Examples*
#' @param translate_ab if `type = "drug"`: a column name of the [antibiotics] data set to translate the antibiotic abbreviations to, using [ab_property()]. Defaults to `FALSE`. Using `TRUE` is equal to using "name".
#' @param thorough_search logical to indicate whether the input must be extensively searched for misspelling and other faulty input values. Setting this to `TRUE` will take considerably more time than when using `FALSE`. At default, it will turn `TRUE` when all input elements contain a maximum of three words.
#' @param info logical to indicate whether a progress bar should be printed, defaults to `TRUE` only in interactive mode
#' @param ... arguments passed on to [as.ab()]
#' @details This function is also internally used by [as.ab()], although it then only searches for the first drug name and will throw a note if more drug names could have been returned. Note: the [as.ab()] function may use very long regular expression to match brand names of antimicrobial agents. This may fail on some systems.
#'
@ -92,6 +93,7 @@ ab_from_text <- function(text,
collapse = NULL,
translate_ab = FALSE,
thorough_search = NULL,
info = interactive(),
...) {
if (missing(type)) {
type <- type[1L]
@ -102,12 +104,13 @@ ab_from_text <- function(text,
meet_criteria(collapse, has_length = 1, allow_NULL = TRUE)
meet_criteria(translate_ab, allow_NULL = FALSE) # get_translate_ab() will be more informative about what's allowed
meet_criteria(thorough_search, allow_class = "logical", has_length = 1, allow_NULL = TRUE)
meet_criteria(info, allow_class = "logical", has_length = 1)
type <- tolower(trimws(type))
text <- tolower(as.character(text))
text_split_all <- strsplit(text, "[ ;.,:\\|]")
progress <- progress_ticker(n = length(text_split_all), n_min = 5)
progress <- progress_ticker(n = length(text_split_all), n_min = 5, print = info)
on.exit(close(progress))
if (type %like% "(drug|ab|anti)") {

View File

@ -23,17 +23,76 @@
# how to conduct AMR data analysis: https://msberends.github.io/AMR/ #
# ==================================================================== #
#' Create Custom EUCAST Rules
#' Define Custom EUCAST Rules
#'
#' @inheritSection lifecycle Experimental Lifecycle
#' Define custom EUCAST rules for your organisation or specific analysis and use the output of this function in [eucast_rules()].
#' @inheritSection lifecycle Maturing Lifecycle
#' @param ... rules in formula notation, see *Examples*
#' @details
#' This documentation page will be updated shortly. **This function is experimental.**
#' Some organisations have their own adoption of EUCAST rules. This function can be used to define custom EUCAST rules to be used in the [eucast_rules()] function.
#'
#' @section How it works:
#' ..
#'
#' It is also possible to define antibiotic groups instead of single antibiotics. The following groups are allowed (case-insensitive): `r vector_and(tolower(DEFINED_AB_GROUPS), quote = "``")`.
#' ### Basics
#'
#' If you are familiar with the [`case_when()`][dplyr::case_when()] function of the `dplyr` package, you will recognise the input method to set your own rules. Rules must be set using what \R considers to be the 'formula notation'. The rule itself is written *before* the tilde (`~`) and the consequence of the rule is written *after* the tilde:
#'
#' ```
#' x <- custom_eucast_rules(TZP == "S" ~ aminopenicillins == "S",
#' TZP == "R" ~ aminopenicillins == "R")
#' ```
#'
#' These are two custom EUCAST rules: if TZP (piperacillin/tazobactam) is "S", all aminopenicillins (ampicillin and amoxicillin) must be made "S", and if TZP is "R", aminopenicillins must be made "R". These rules can also be printed to the console, so it is immediately clear how they work:
#'
#' ```
#' x
#' #> A set of custom EUCAST rules:
#' #>
#' #> 1. If TZP is S then set to S:
#' #> amoxicillin (AMX), ampicillin (AMP)
#' #>
#' #> 2. If TZP is R then set to R:
#' #> amoxicillin (AMX), ampicillin (AMP)
#' ```
#'
#' The rules (the part *before* the tilde, in above example `TZP == "S"` and `TZP == "R"`) must be evaluable in your data set: it should be able to run as a filter in your data set without errors. This means for the above example that the column `TZP` must exist. We will create a sample data set and test the rules set:
#'
#' ```
#' df <- data.frame(mo = c("E. coli", "K. pneumoniae"),
#' TZP = "R",
#' amox = "",
#' AMP = "")
#' df
#' #> mo TZP amox AMP
#' #> 1 E. coli R
#' #> 2 K. pneumoniae R
#'
#' eucast_rules(df, rules = "custom", custom_rules = x)
#' #> mo TZP amox AMP
#' #> 1 E. coli R R R
#' #> 2 K. pneumoniae R R R
#' ```
#'
#' ### Using taxonomic properties in rules
#'
#' There is one exception in variables used for the rules: all column names of the [microorganisms] data set can also be used, but do not have to exist in the data set. These column names are: `r vector_and(colnames(microorganisms), quote = "``", sort = FALSE)`. Thus, this next example will work as well, despite the fact that the `df` data set does not contain a column `genus`:
#'
#' ```
#' y <- custom_eucast_rules(TZP == "S" & genus == "Klebsiella" ~ aminopenicillins == "S",
#' TZP == "R" & genus == "Klebsiella" ~ aminopenicillins == "R")
#'
#' eucast_rules(df, rules = "custom", custom_rules = y)
#' #> mo TZP amox AMP
#' #> 1 E. coli R
#' #> 2 K. pneumoniae R R R
#' ```
#'
#' ### Usage of antibiotic group names
#'
#' It is possible to define antibiotic groups instead of single antibiotics for the rule consequence, the part *after* the tilde. In above examples, the antibiotic group `aminopenicillins` is used to include ampicillin and amoxicillin. The following groups are allowed (case-insensitive). Within parentheses are the antibiotic agents that will be matched when running the rule.
#'
#' `r paste0(" * ", sapply(DEFINED_AB_GROUPS, function(x) paste0("``", tolower(x), "``\\cr(", paste0(sort(ab_name(eval(parse(text = x), envir = asNamespace("AMR")), language = NULL, tolower = TRUE)), collapse = ", "), ")"), USE.NAMES = FALSE), "\n", collapse = "")`
#' @returns A [list] containing the custom rules
#' @export
#' @examples
#' x <- custom_eucast_rules(AMC == "R" & genus == "Klebsiella" ~ aminopenicillins == "R",

View File

@ -98,7 +98,7 @@
#' @details
#' Please note that entries are only based on the Catalogue of Life and the LPSN (see below). Since these sources incorporate entries based on (recent) publications in the International Journal of Systematic and Evolutionary Microbiology (IJSEM), it can happen that the year of publication is sometimes later than one might expect.
#'
#' For example, *Staphylococcus pettenkoferi* was described for the first time in Diagnostic Microbiology and Infectious Disease in 2002 (\doi{10.1016/s0732-8893(02)00399-1}), but it was not before 2007 that a publication in IJSEM followed (\doi{10.1099/ijs.0.64381-0}). Consequently, the AMR package returns 2007 for `mo_year("S. pettenkoferi")`.
#' For example, *Staphylococcus pettenkoferi* was described for the first time in Diagnostic Microbiology and Infectious Disease in 2002 (\doi{10.1016/s0732-8893(02)00399-1}), but it was not before 2007 that a publication in IJSEM followed (\doi{10.1099/ijs.0.64381-0}). Consequently, the `AMR` package returns 2007 for `mo_year("S. pettenkoferi")`.
#'
#' ## Manual additions
#' For convenience, some entries were added manually:

View File

@ -42,7 +42,7 @@
#' @param type type to determine weighed isolates; can be `"keyantibiotics"` or `"points"`, see *Details*
#' @param ignore_I logical to indicate whether antibiotic interpretations with `"I"` will be ignored when `type = "keyantibiotics"`, see *Details*
#' @param points_threshold points until the comparison of key antibiotics will lead to inclusion of an isolate when `type = "points"`, see *Details*
#' @param info print progress
#' @param info a [logical] to indicate whether a progress bar should be printed, defaults to `TRUE` only in interactive mode
#' @param include_unknown logical to indicate whether 'unknown' microorganisms should be included too, i.e. microbial code `"UNKNOWN"`, which defaults to `FALSE`. For WHONET users, this means that all records with organism code `"con"` (*contamination*) will be excluded at default. Isolates with a microbial ID of `NA` will always be excluded as first isolate.
#' @param include_untested_rsi logical to indicate whether also rows without antibiotic results are still eligible for becoming a first isolate. Use `include_untested_rsi = FALSE` to always return `FALSE` for such rows. This checks the data set for columns of class `<rsi>` and consequently requires transforming columns with antibiotic results using [as.rsi()] first.
#' @param ... arguments passed on to [first_isolate()] when using [filter_first_isolate()], or arguments passed on to [key_antibiotics()] when using [filter_first_weighted_isolate()]

View File

@ -314,10 +314,8 @@ key_antibiotics_equal <- function(y,
result <- logical(length(x))
if (info_needed == TRUE) {
p <- progress_ticker(length(x))
on.exit(close(p))
}
p <- progress_ticker(length(x), print = info_needed)
on.exit(close(p))
for (i in seq_len(length(x))) {
@ -375,8 +373,8 @@ key_antibiotics_equal <- function(y,
}
}
}
if (info_needed == TRUE) {
close(p)
}
close(p)
result
}

View File

@ -35,18 +35,17 @@
#' @rdname like
#' @export
#' @details
#' This `%like%` function:
#' * Is case-insensitive (use `%like_case%` for case-sensitive matching)
#' * Supports multiple patterns
#' * Checks if `pattern` is a valid regular expression and sets `fixed = TRUE` if not, to greatly improve speed (vectorised over `pattern`)
#' * Always uses compatibility with Perl unless `fixed = TRUE`, to greatly improve speed
#' These [like()] and `%like%` functions:
#' * Are case-insensitive (use `%like_case%` for case-sensitive matching)
#' * Support multiple patterns
#' * Check if `pattern` is a valid regular expression and sets `fixed = TRUE` if not, to greatly improve speed (vectorised over `pattern`)
#' * Always use compatibility with Perl unless `fixed = TRUE`, to greatly improve speed
#'
#' Using RStudio? The text `%like%` can also be directly inserted in your code from the Addins menu and can have its own Keyboard Shortcut like `Ctrl+Shift+L` or `Cmd+Shift+L` (see `Tools` > `Modify Keyboard Shortcuts...`).
#' @source Idea from the [`like` function from the `data.table` package](https://github.com/Rdatatable/data.table/blob/ec1259af1bf13fc0c96a1d3f9e84d55d8106a9a4/R/like.R), although altered as explained in *Details*.
#' @seealso [grepl()]
#' @inheritSection AMR Read more on Our Website!
#' @examples
#' # simple test
#' a <- "This is a test"
#' b <- "TEST"
#' a %like% b
@ -65,12 +64,12 @@
#' #> TRUE FALSE FALSE
#'
#' # get isolates whose name start with 'Ent' or 'ent'
#' \donttest{
#' example_isolates[which(mo_name() %like% "^ent"), ]
#'
#' if (require("dplyr")) {
#' example_isolates %>%
#' filter(mo_name() %like% "^ent")
#' }
#' }
like <- function(x, pattern, ignore.case = TRUE) {
meet_criteria(x, allow_NA = TRUE)
meet_criteria(pattern, allow_NA = FALSE)

View File

@ -78,7 +78,7 @@
#'
#' Custom guidelines can be set with the [custom_mdro_guideline()] function. This is of great importance if you have custom rules to determine MDROs in your hospital, e.g., rules that are dependent on ward, state of contact isolation or other variables in your data.
#'
#' If you are familiar with `case_when()` of the `dplyr` package, you will recognise the input method to set your own rules. Rules must be set using what \R considers to be the 'formula notation':
#' If you are familiar with the [`case_when()`][dplyr::case_when()] function of the `dplyr` package, you will recognise the input method to set your own rules. Rules must be set using what \R considers to be the 'formula notation'. The rule is written *before* the tilde (`~`) and the consequence of the rule is written *after* the tilde:
#'
#' ```
#' custom <- custom_mdro_guideline(CIP == "R" & age > 60 ~ "Elderly Type A",

9
R/mo.R
View File

@ -38,6 +38,7 @@
#' @param reference_df a [data.frame] to be used for extra reference when translating `x` to a valid [`mo`]. See [set_mo_source()] and [get_mo_source()] to automate the usage of your own codes (e.g. used in your analysis or organisation).
#' @param ignore_pattern a regular expression (case-insensitive) of which all matches in `x` must return `NA`. This can be convenient to exclude known non-relevant input and can also be set with the option `AMR_ignore_pattern`, e.g. `options(AMR_ignore_pattern = "(not reported|contaminated flora)")`.
#' @param language language to translate text like "no growth", which defaults to the system language (see [get_locale()])
#' @param info a [logical] to indicate if a progress bar should be printed if more than 25 items are to be coerced, defaults to `TRUE` only in interactive mode
#' @param ... other arguments passed on to functions
#' @rdname as.mo
#' @aliases mo
@ -161,6 +162,7 @@ as.mo <- function(x,
reference_df = get_mo_source(),
ignore_pattern = getOption("AMR_ignore_pattern"),
language = get_locale(),
info = interactive(),
...) {
meet_criteria(x, allow_class = c("mo", "data.frame", "list", "character", "numeric", "integer", "factor"), allow_NA = TRUE)
meet_criteria(Becker, allow_class = c("logical", "character"), has_length = 1)
@ -169,7 +171,8 @@ as.mo <- function(x,
meet_criteria(reference_df, allow_class = "data.frame", allow_NULL = TRUE)
meet_criteria(ignore_pattern, allow_class = "character", has_length = 1, allow_NULL = TRUE)
meet_criteria(language, has_length = 1, is_in = c(LANGUAGES_SUPPORTED, ""), allow_NULL = TRUE, allow_NA = TRUE)
meet_criteria(info, allow_class = "logical", has_length = 1)
check_dataset_integrity()
if (tryCatch(all(x[!is.na(x)] %in% MO_lookup$mo)
@ -227,6 +230,7 @@ as.mo <- function(x,
reference_df = reference_df,
ignore_pattern = ignore_pattern,
language = language,
info = info,
...)
}
@ -253,6 +257,7 @@ exec_as.mo <- function(x,
Lancefield = FALSE,
allow_uncertain = TRUE,
reference_df = get_mo_source(),
info = interactive(),
property = "mo",
initial_search = TRUE,
dyslexia_mode = FALSE,
@ -600,7 +605,7 @@ exec_as.mo <- function(x,
}
if (initial_search == TRUE) {
progress <- progress_ticker(n = length(x[!already_known]), n_min = 25) # start if n >= 25
progress <- progress_ticker(n = length(x[!already_known]), n_min = 25, print = info) # start if n >= 25
on.exit(close(progress))
}

17
R/zzz.R
View File

@ -61,20 +61,3 @@ pkg_env$mo_failed <- character(0)
}
}, silent = TRUE)
}
.onAttach <- function(...) {
# show notice in 10% of cases in interactive session
if (!interactive() || stats::runif(1) > 0.1 || isTRUE(as.logical(getOption("AMR_silentstart", FALSE)))) {
return()
}
packageStartupMessage(word_wrap("Thank you for using the AMR package! ",
"If you have a minute, please anonymously fill in this short questionnaire to improve the package and its functionalities: ",
font_blue("https://msberends.github.io/AMR/survey.html\n"),
"[prevent his notice with ",
font_bold("suppressPackageStartupMessages(library(AMR))"),
" or use ",
font_bold("options(AMR_silentstart = TRUE)"), "]"))
}

Binary file not shown.

View File

@ -81,7 +81,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="Latest development version">1.6.0.9006</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.6.0.9007</span>
</span>
</div>

View File

@ -81,7 +81,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="Latest development version">1.6.0.9006</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.6.0.9007</span>
</span>
</div>

View File

@ -81,7 +81,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="Latest development version">1.6.0.9006</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.6.0.9007</span>
</span>
</div>

View File

@ -81,7 +81,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="Latest development version">1.6.0.9006</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.6.0.9007</span>
</span>
</div>

View File

@ -42,7 +42,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="Latest development version">1.6.0.9006</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.6.0.9007</span>
</span>
</div>

View File

@ -81,7 +81,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="Latest development version">1.6.0.9006</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.6.0.9007</span>
</span>
</div>
@ -236,13 +236,13 @@
<small>Source: <a href='https://github.com/msberends/AMR/blob/master/NEWS.md'><code>NEWS.md</code></a></small>
</div>
<div id="amr-1609006" class="section level1">
<h1 class="page-header" data-toc-text="1.6.0.9006">
<a href="#amr-1609006" class="anchor"></a>AMR 1.6.0.9006<small> Unreleased </small>
<div id="amr-1609007" class="section level1">
<h1 class="page-header" data-toc-text="1.6.0.9007">
<a href="#amr-1609007" class="anchor"></a>AMR 1.6.0.9007<small> Unreleased </small>
</h1>
<div id="last-updated-16-april-2021" class="section level2">
<div id="last-updated-20-april-2021" class="section level2">
<h2 class="hasAnchor">
<a href="#last-updated-16-april-2021" class="anchor"></a><small>Last updated: 16 April 2021</small>
<a href="#last-updated-20-april-2021" class="anchor"></a><small>Last updated: 20 April 2021</small>
</h2>
<div id="new" class="section level3">
<h3 class="hasAnchor">
@ -273,6 +273,7 @@
<li>
<code><a href="../reference/like.html">like()</a></code> (and <code><a href="../reference/like.html">%like%</a></code>) now checks if <code>pattern</code> is a <em>valid</em> regular expression</li>
<li>Fixed an installation error on R-3.0</li>
<li>Added <code>info</code> argument to <code><a href="../reference/as.mo.html">as.mo()</a></code> to turn on/off the progress bar</li>
</ul>
</div>
</div>

View File

@ -12,7 +12,7 @@ articles:
datasets: datasets.html
resistance_predict: resistance_predict.html
welcome_to_AMR: welcome_to_AMR.html
last_built: 2021-04-16T12:59Z
last_built: 2021-04-20T08:46Z
urls:
reference: https://msberends.github.io/AMR//reference
article: https://msberends.github.io/AMR//articles

View File

@ -82,7 +82,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="Latest development version">1.5.0.9040</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.6.0.9007</span>
</span>
</div>
@ -248,6 +248,7 @@
collapse <span class='op'>=</span> <span class='cn'>NULL</span>,
translate_ab <span class='op'>=</span> <span class='cn'>FALSE</span>,
thorough_search <span class='op'>=</span> <span class='cn'>NULL</span>,
info <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/interactive.html'>interactive</a></span><span class='op'>(</span><span class='op'>)</span>,
<span class='va'>...</span>
<span class='op'>)</span></pre>
@ -274,6 +275,10 @@
<th>thorough_search</th>
<td><p>logical to indicate whether the input must be extensively searched for misspelling and other faulty input values. Setting this to <code>TRUE</code> will take considerably more time than when using <code>FALSE</code>. At default, it will turn <code>TRUE</code> when all input elements contain a maximum of three words.</p></td>
</tr>
<tr>
<th>info</th>
<td><p>logical to indicate whether a progress bar should be printed, defaults to <code>TRUE</code> only in interactive mode</p></td>
</tr>
<tr>
<th>...</th>
<td><p>arguments passed on to <code><a href='as.ab.html'>as.ab()</a></code></p></td>

View File

@ -82,7 +82,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="Latest development version">1.5.0.9016</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.6.0.9007</span>
</span>
</div>
@ -242,7 +242,7 @@
<p>Use this function to determine the antibiotic code of one or more antibiotics. The data set <a href='antibiotics.html'>antibiotics</a> will be searched for abbreviations, official names and synonyms (brand names).</p>
</div>
<pre class="usage"><span class='fu'>as.ab</span><span class='op'>(</span><span class='va'>x</span>, flag_multiple_results <span class='op'>=</span> <span class='cn'>TRUE</span>, info <span class='op'>=</span> <span class='cn'>TRUE</span>, <span class='va'>...</span><span class='op'>)</span>
<pre class="usage"><span class='fu'>as.ab</span><span class='op'>(</span><span class='va'>x</span>, flag_multiple_results <span class='op'>=</span> <span class='cn'>TRUE</span>, info <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/interactive.html'>interactive</a></span><span class='op'>(</span><span class='op'>)</span>, <span class='va'>...</span><span class='op'>)</span>
<span class='fu'>is.ab</span><span class='op'>(</span><span class='va'>x</span><span class='op'>)</span></pre>
@ -259,7 +259,7 @@
</tr>
<tr>
<th>info</th>
<td><p>logical to indicate whether a progress bar should be printed</p></td>
<td><p>a <a href='https://rdrr.io/r/base/logical.html'>logical</a> to indicate whether a progress bar should be printed, defaults to <code>TRUE</code> only in interactive mode</p></td>
</tr>
<tr>
<th>...</th>

View File

@ -82,7 +82,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="Latest development version">1.6.0.9003</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.6.0.9007</span>
</span>
</div>
@ -250,6 +250,7 @@
reference_df <span class='op'>=</span> <span class='fu'><a href='mo_source.html'>get_mo_source</a></span><span class='op'>(</span><span class='op'>)</span>,
ignore_pattern <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/options.html'>getOption</a></span><span class='op'>(</span><span class='st'>"AMR_ignore_pattern"</span><span class='op'>)</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>,
info <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/interactive.html'>interactive</a></span><span class='op'>(</span><span class='op'>)</span>,
<span class='va'>...</span>
<span class='op'>)</span>
@ -294,6 +295,10 @@
<th>language</th>
<td><p>language to translate text like "no growth", which defaults to the system language (see <code><a href='translate.html'>get_locale()</a></code>)</p></td>
</tr>
<tr>
<th>info</th>
<td><p>a <a href='https://rdrr.io/r/base/logical.html'>logical</a> to indicate if a progress bar should be printed if more than 25 items are to be coerced, defaults to <code>TRUE</code> only in interactive mode</p></td>
</tr>
<tr>
<th>...</th>
<td><p>other arguments passed on to functions</p></td>

View File

@ -6,7 +6,7 @@
<meta http-equiv="X-UA-Compatible" content="IE=edge">
<meta name="viewport" content="width=device-width, initial-scale=1.0">
<title>Create Custom EUCAST Rules — custom_eucast_rules • AMR (for R)</title>
<title>Define Custom EUCAST Rules — custom_eucast_rules • AMR (for R)</title>
<!-- favicons -->
<link rel="icon" type="image/png" sizes="16x16" href="../favicon-16x16.png">
@ -48,8 +48,8 @@
<link href="../extra.css" rel="stylesheet">
<script src="../extra.js"></script>
<meta property="og:title" content="Create Custom EUCAST Rules — custom_eucast_rules" />
<meta property="og:description" content="Create Custom EUCAST Rules" />
<meta property="og:title" content="Define Custom EUCAST Rules — custom_eucast_rules" />
<meta property="og:description" content="Define custom EUCAST rules for your organisation or specific analysis and use the output of this function in eucast_rules()." />
<meta property="og:image" content="https://msberends.github.io/AMR/logo.png" />
@ -82,7 +82,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="Latest development version">1.6.0.9001</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.6.0.9007</span>
</span>
</div>
@ -233,13 +233,13 @@
<div class="row">
<div class="col-md-9 contents">
<div class="page-header">
<h1>Create Custom EUCAST Rules</h1>
<h1>Define Custom EUCAST Rules</h1>
<small class="dont-index">Source: <a href='https://github.com/msberends/AMR/blob/master/R/custom_eucast_rules.R'><code>R/custom_eucast_rules.R</code></a></small>
<div class="hidden name"><code>custom_eucast_rules.Rd</code></div>
</div>
<div class="ref-description">
<p>Create Custom EUCAST Rules</p>
<p>Define custom EUCAST rules for your organisation or specific analysis and use the output of this function in <code><a href='eucast_rules.html'>eucast_rules()</a></code>.</p>
</div>
<pre class="usage"><span class='fu'>custom_eucast_rules</span><span class='op'>(</span><span class='va'>...</span><span class='op'>)</span></pre>
@ -253,21 +253,97 @@
</tr>
</table>
<h2 class="hasAnchor" id="value"><a class="anchor" href="#value"></a>Value</h2>
<p>A <a href='https://rdrr.io/r/base/list.html'>list</a> containing the custom rules</p>
<h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2>
<p>This documentation page will be updated shortly. <strong>This function is experimental.</strong></p>
<p>Some organisations have their own adoption of EUCAST rules. This function can be used to define custom EUCAST rules to be used in the <code><a href='eucast_rules.html'>eucast_rules()</a></code> function.</p>
<h2 class="hasAnchor" id="how-it-works"><a class="anchor" href="#how-it-works"></a>How it works</h2>
<p>..</p>
<p>It is also possible to define antibiotic groups instead of single antibiotics. The following groups are allowed (case-insensitive): <code>aminoglycosides</code>, <code>aminopenicillins</code>, <code>betalactams</code>, <code>carbapenems</code>, <code>cephalosporins</code>, <code>cephalosporins_1st</code>, <code>cephalosporins_2nd</code>, <code>cephalosporins_3rd</code>, <code>cephalosporins_except_caz</code>, <code>fluoroquinolones</code>, <code>glycopeptides</code>, <code>glycopeptides_except_lipo</code>, <code>lincosamides</code>, <code>lipoglycopeptides</code>, <code>macrolides</code>, <code>oxazolidinones</code>, <code>penicillins</code>, <code>polymyxins</code>, <code>streptogramins</code>, <code>tetracyclines</code>, <code>tetracyclines_except_tgc</code> and <code>ureidopenicillins</code>.</p>
<h2 class="hasAnchor" id="experimental-lifecycle"><a class="anchor" href="#experimental-lifecycle"></a>Experimental Lifecycle</h2>
<h3 class='hasAnchor' id='arguments'><a class='anchor' href='#arguments'></a>Basics</h3>
<p>If you are familiar with the <code><a href='https://dplyr.tidyverse.org/reference/case_when.html'>case_when()</a></code> function of the <code>dplyr</code> package, you will recognise the input method to set your own rules. Rules must be set using what <span style="R">R</span> considers to be the 'formula notation'. The rule itself is written <em>before</em> the tilde (<code><a href='https://rdrr.io/r/base/tilde.html'>~</a></code>) and the consequence of the rule is written <em>after</em> the tilde:</p><pre><span class='va'>x</span> <span class='op'>&lt;-</span> <span class='fu'>custom_eucast_rules</span><span class='op'>(</span><span class='va'>TZP</span> <span class='op'>==</span> <span class='st'>"S"</span> <span class='op'>~</span> <span class='va'>aminopenicillins</span> <span class='op'>==</span> <span class='st'>"S"</span>,
<span class='va'>TZP</span> <span class='op'>==</span> <span class='st'>"R"</span> <span class='op'>~</span> <span class='va'>aminopenicillins</span> <span class='op'>==</span> <span class='st'>"R"</span><span class='op'>)</span>
</pre>
<p>These are two custom EUCAST rules: if TZP (piperacillin/tazobactam) is "S", all aminopenicillins (ampicillin and amoxicillin) must be made "S", and if TZP is "R", aminopenicillins must be made "R". These rules can also be printed to the console, so it is immediately clear how they work:</p><pre><span class='va'>x</span>
<span class='co'>#&gt; A set of custom EUCAST rules:</span>
<span class='co'>#&gt; </span>
<span class='co'>#&gt; 1. If TZP is S then set to S:</span>
<span class='co'>#&gt; amoxicillin (AMX), ampicillin (AMP)</span>
<span class='co'>#&gt; </span>
<span class='co'>#&gt; 2. If TZP is R then set to R:</span>
<span class='co'>#&gt; amoxicillin (AMX), ampicillin (AMP)</span>
</pre>
<p>The rules (the part <em>before</em> the tilde, in above example <code>TZP == "S"</code> and <code>TZP == "R"</code>) must be evaluable in your data set: it should be able to run as a filter in your data set without errors. This means for the above example that the column <code>TZP</code> must exist. We will create a sample data set and test the rules set:</p><pre><span class='va'>df</span> <span class='op'>&lt;-</span> <span class='fu'><a href='https://rdrr.io/r/base/data.frame.html'>data.frame</a></span><span class='op'>(</span>mo <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span><span class='st'>"E. coli"</span>, <span class='st'>"K. pneumoniae"</span><span class='op'>)</span>,
TZP <span class='op'>=</span> <span class='st'>"R"</span>,
amox <span class='op'>=</span> <span class='st'>""</span>,
AMP <span class='op'>=</span> <span class='st'>""</span><span class='op'>)</span>
<span class='va'>df</span>
<span class='co'>#&gt; mo TZP amox AMP</span>
<span class='co'>#&gt; 1 E. coli R </span>
<span class='co'>#&gt; 2 K. pneumoniae R </span>
<span class='fu'><a href='eucast_rules.html'>eucast_rules</a></span><span class='op'>(</span><span class='va'>df</span>, rules <span class='op'>=</span> <span class='st'>"custom"</span>, custom_rules <span class='op'>=</span> <span class='va'>x</span><span class='op'>)</span>
<span class='co'>#&gt; mo TZP amox AMP</span>
<span class='co'>#&gt; 1 E. coli R R R </span>
<span class='co'>#&gt; 2 K. pneumoniae R R R </span>
</pre>
<h3 class='hasAnchor' id='arguments'><a class='anchor' href='#arguments'></a>Using taxonomic properties in rules</h3>
<p>There is one exception in variables used for the rules: all column names of the <a href='microorganisms.html'>microorganisms</a> data set can also be used, but do not have to exist in the data set. These column names are: <code>mo</code>, <code>fullname</code>, <code>kingdom</code>, <code>phylum</code>, <code>class</code>, <code>order</code>, <code>family</code>, <code>genus</code>, <code>species</code>, <code>subspecies</code>, <code>rank</code>, <code>ref</code>, <code>species_id</code>, <code>source</code>, <code>prevalence</code> and <code>snomed</code>. Thus, this next example will work as well, despite the fact that the <code>df</code> data set does not contain a column <code>genus</code>:</p><pre><span class='va'>y</span> <span class='op'>&lt;-</span> <span class='fu'>custom_eucast_rules</span><span class='op'>(</span><span class='va'>TZP</span> <span class='op'>==</span> <span class='st'>"S"</span> <span class='op'>&amp;</span> <span class='va'>genus</span> <span class='op'>==</span> <span class='st'>"Klebsiella"</span> <span class='op'>~</span> <span class='va'>aminopenicillins</span> <span class='op'>==</span> <span class='st'>"S"</span>,
<span class='va'>TZP</span> <span class='op'>==</span> <span class='st'>"R"</span> <span class='op'>&amp;</span> <span class='va'>genus</span> <span class='op'>==</span> <span class='st'>"Klebsiella"</span> <span class='op'>~</span> <span class='va'>aminopenicillins</span> <span class='op'>==</span> <span class='st'>"R"</span><span class='op'>)</span>
<span class='fu'><a href='eucast_rules.html'>eucast_rules</a></span><span class='op'>(</span><span class='va'>df</span>, rules <span class='op'>=</span> <span class='st'>"custom"</span>, custom_rules <span class='op'>=</span> <span class='va'>y</span><span class='op'>)</span>
<span class='co'>#&gt; mo TZP amox AMP</span>
<span class='co'>#&gt; 1 E. coli R </span>
<span class='co'>#&gt; 2 K. pneumoniae R R R</span>
</pre>
<h3 class='hasAnchor' id='arguments'><a class='anchor' href='#arguments'></a>Usage of antibiotic group names</h3>
<p>It is possible to define antibiotic groups instead of single antibiotics for the rule consequence, the part <em>after</em> the tilde. In above examples, the antibiotic group <code>aminopenicillins</code> is used to include ampicillin and amoxicillin. The following groups are allowed (case-insensitive). Within parentheses are the antibiotic agents that will be matched when running the rule.</p><ul>
<li><p><code>aminoglycosides</code><br />(amikacin, amikacin/fosfomycin, amphotericin B-high, apramycin, arbekacin, astromicin, bekanamycin, dibekacin, framycetin, gentamicin, gentamicin-high, habekacin, hygromycin, isepamicin, kanamycin, kanamycin-high, kanamycin/cephalexin, micronomicin, neomycin, netilmicin, pentisomicin, plazomicin, propikacin, ribostamycin, sisomicin, streptoduocin, streptomycin, streptomycin-high, tobramycin, tobramycin-high)</p></li>
<li><p><code>aminopenicillins</code><br />(amoxicillin, ampicillin)</p></li>
<li><p><code>betalactams</code><br />(amoxicillin, amoxicillin/clavulanic acid, amoxicillin/sulbactam, ampicillin, ampicillin/sulbactam, apalcillin, aspoxicillin, avibactam, azidocillin, azlocillin, aztreonam, aztreonam/avibactam, bacampicillin, benzathine benzylpenicillin, benzathine phenoxymethylpenicillin, benzylpenicillin, biapenem, cadazolid, carbenicillin, carindacillin, cefacetrile, cefaclor, cefadroxil, cefaloridine, cefamandole, cefatrizine, cefazedone, cefazolin, cefcapene, cefcapene pivoxil, cefdinir, cefditoren, cefditoren pivoxil, cefepime, cefepime/clavulanic acid, cefepime/tazobactam, cefetamet, cefetamet pivoxil, cefetecol (Cefcatacol), cefetrizole, cefixime, cefmenoxime, cefmetazole, cefodizime, cefonicid, cefoperazone, cefoperazone/sulbactam, ceforanide, cefoselis, cefotaxime, cefotaxime/clavulanic acid, cefotaxime/sulbactam, cefotetan, cefotiam, cefotiam hexetil, cefovecin, cefoxitin, cefoxitin screening, cefozopran, cefpimizole, cefpiramide, cefpirome, cefpodoxime, cefpodoxime proxetil, cefpodoxime/clavulanic acid, cefprozil, cefquinome, cefroxadine, cefsulodin, cefsumide, ceftaroline, ceftaroline/avibactam, ceftazidime, ceftazidime/avibactam, ceftazidime/clavulanic acid, cefteram, cefteram pivoxil, ceftezole, ceftibuten, ceftiofur, ceftizoxime, ceftizoxime alapivoxil, ceftobiprole, ceftobiprole medocaril, ceftolozane/enzyme inhibitor, ceftolozane/tazobactam, ceftriaxone, cefuroxime, cefuroxime axetil, cephalexin, cephalothin, cephapirin, cephradine, ciclacillin, clometocillin, cloxacillin, dicloxacillin, doripenem, epicillin, ertapenem, flucloxacillin, hetacillin, imipenem, imipenem/EDTA, imipenem/relebactam, latamoxef, lenampicillin, loracarbef, mecillinam (Amdinocillin), meropenem, meropenem/nacubactam, meropenem/vaborbactam, metampicillin, methicillin, mezlocillin, mezlocillin/sulbactam, nacubactam, nafcillin, oxacillin, panipenem, penamecillin, penicillin/novobiocin, penicillin/sulbactam, phenethicillin, phenoxymethylpenicillin, piperacillin, piperacillin/sulbactam, piperacillin/tazobactam, piridicillin, pivampicillin, pivmecillinam, procaine benzylpenicillin, propicillin, razupenem, ritipenem, ritipenem acoxil, sarmoxicillin, sulbactam, sulbenicillin, sultamicillin, talampicillin, tazobactam, tebipenem, temocillin, ticarcillin, ticarcillin/clavulanic acid)</p></li>
<li><p><code>carbapenems</code><br />(biapenem, doripenem, ertapenem, imipenem, imipenem/EDTA, imipenem/relebactam, meropenem, meropenem/nacubactam, meropenem/vaborbactam, panipenem, razupenem, ritipenem, ritipenem acoxil, tebipenem)</p></li>
<li><p><code>cephalosporins</code><br />(cadazolid, cefacetrile, cefaclor, cefadroxil, cefaloridine, cefamandole, cefatrizine, cefazedone, cefazolin, cefcapene, cefcapene pivoxil, cefdinir, cefditoren, cefditoren pivoxil, cefepime, cefepime/clavulanic acid, cefepime/tazobactam, cefetamet, cefetamet pivoxil, cefetecol (Cefcatacol), cefetrizole, cefixime, cefmenoxime, cefmetazole, cefodizime, cefonicid, cefoperazone, cefoperazone/sulbactam, ceforanide, cefoselis, cefotaxime, cefotaxime/clavulanic acid, cefotaxime/sulbactam, cefotetan, cefotiam, cefotiam hexetil, cefovecin, cefoxitin, cefoxitin screening, cefozopran, cefpimizole, cefpiramide, cefpirome, cefpodoxime, cefpodoxime proxetil, cefpodoxime/clavulanic acid, cefprozil, cefquinome, cefroxadine, cefsulodin, cefsumide, ceftaroline, ceftaroline/avibactam, ceftazidime, ceftazidime/avibactam, ceftazidime/clavulanic acid, cefteram, cefteram pivoxil, ceftezole, ceftibuten, ceftiofur, ceftizoxime, ceftizoxime alapivoxil, ceftobiprole, ceftobiprole medocaril, ceftolozane/enzyme inhibitor, ceftolozane/tazobactam, ceftriaxone, cefuroxime, cefuroxime axetil, cephalexin, cephalothin, cephapirin, cephradine, latamoxef, loracarbef)</p></li>
<li><p><code>cephalosporins_1st</code><br />(cefacetrile, cefadroxil, cefaloridine, cefatrizine, cefazedone, cefazolin, cefroxadine, ceftezole, cephalexin, cephalothin, cephapirin, cephradine)</p></li>
<li><p><code>cephalosporins_2nd</code><br />(cefaclor, cefamandole, cefmetazole, cefonicid, ceforanide, cefotetan, cefotiam, cefoxitin, cefoxitin screening, cefprozil, cefuroxime, cefuroxime axetil, loracarbef)</p></li>
<li><p><code>cephalosporins_3rd</code><br />(cadazolid, cefcapene, cefcapene pivoxil, cefdinir, cefditoren, cefditoren pivoxil, cefetamet, cefetamet pivoxil, cefixime, cefmenoxime, cefodizime, cefoperazone, cefoperazone/sulbactam, cefotaxime, cefotaxime/clavulanic acid, cefotaxime/sulbactam, cefotiam hexetil, cefovecin, cefpimizole, cefpiramide, cefpodoxime, cefpodoxime proxetil, cefpodoxime/clavulanic acid, cefsulodin, ceftazidime, ceftazidime/avibactam, ceftazidime/clavulanic acid, cefteram, cefteram pivoxil, ceftibuten, ceftiofur, ceftizoxime, ceftizoxime alapivoxil, ceftriaxone, latamoxef)</p></li>
<li><p><code>cephalosporins_except_caz</code><br />(cadazolid, cefacetrile, cefaclor, cefadroxil, cefaloridine, cefamandole, cefatrizine, cefazedone, cefazolin, cefcapene, cefcapene pivoxil, cefdinir, cefditoren, cefditoren pivoxil, cefepime, cefepime/clavulanic acid, cefepime/tazobactam, cefetamet, cefetamet pivoxil, cefetecol (Cefcatacol), cefetrizole, cefixime, cefmenoxime, cefmetazole, cefodizime, cefonicid, cefoperazone, cefoperazone/sulbactam, ceforanide, cefoselis, cefotaxime, cefotaxime/clavulanic acid, cefotaxime/sulbactam, cefotetan, cefotiam, cefotiam hexetil, cefovecin, cefoxitin, cefoxitin screening, cefozopran, cefpimizole, cefpiramide, cefpirome, cefpodoxime, cefpodoxime proxetil, cefpodoxime/clavulanic acid, cefprozil, cefquinome, cefroxadine, cefsulodin, cefsumide, ceftaroline, ceftaroline/avibactam, ceftazidime/avibactam, ceftazidime/clavulanic acid, cefteram, cefteram pivoxil, ceftezole, ceftibuten, ceftiofur, ceftizoxime, ceftizoxime alapivoxil, ceftobiprole, ceftobiprole medocaril, ceftolozane/enzyme inhibitor, ceftolozane/tazobactam, ceftriaxone, cefuroxime, cefuroxime axetil, cephalexin, cephalothin, cephapirin, cephradine, latamoxef, loracarbef)</p></li>
<li><p><code>fluoroquinolones</code><br />(ciprofloxacin, enoxacin, fleroxacin, gatifloxacin, gemifloxacin, grepafloxacin, levofloxacin, lomefloxacin, moxifloxacin, norfloxacin, ofloxacin, pazufloxacin, pefloxacin, prulifloxacin, rufloxacin, sparfloxacin, temafloxacin, trovafloxacin)</p></li>
<li><p><code>glycopeptides</code><br />(avoparcin, dalbavancin, norvancomycin, oritavancin, ramoplanin, teicoplanin, teicoplanin-macromethod, telavancin, vancomycin, vancomycin-macromethod)</p></li>
<li><p><code>glycopeptides_except_lipo</code><br />(avoparcin, norvancomycin, ramoplanin, teicoplanin, teicoplanin-macromethod, vancomycin, vancomycin-macromethod)</p></li>
<li><p><code>lincosamides</code><br />(clindamycin, lincomycin, pirlimycin)</p></li>
<li><p><code>lipoglycopeptides</code><br />(dalbavancin, oritavancin, telavancin)</p></li>
<li><p><code>macrolides</code><br />(azithromycin, clarithromycin, dirithromycin, erythromycin, flurithromycin, josamycin, midecamycin, miocamycin, oleandomycin, rokitamycin, roxithromycin, spiramycin, telithromycin, troleandomycin)</p></li>
<li><p><code>oxazolidinones</code><br />(cycloserine, linezolid, tedizolid, thiacetazone)</p></li>
<li><p><code>penicillins</code><br />(amoxicillin, amoxicillin/clavulanic acid, amoxicillin/sulbactam, ampicillin, ampicillin/sulbactam, apalcillin, aspoxicillin, avibactam, azidocillin, azlocillin, aztreonam, aztreonam/avibactam, bacampicillin, benzathine benzylpenicillin, benzathine phenoxymethylpenicillin, benzylpenicillin, carbenicillin, carindacillin, ciclacillin, clometocillin, cloxacillin, dicloxacillin, epicillin, flucloxacillin, hetacillin, lenampicillin, mecillinam (Amdinocillin), metampicillin, methicillin, mezlocillin, mezlocillin/sulbactam, nacubactam, nafcillin, oxacillin, penamecillin, penicillin/novobiocin, penicillin/sulbactam, phenethicillin, phenoxymethylpenicillin, piperacillin, piperacillin/sulbactam, piperacillin/tazobactam, piridicillin, pivampicillin, pivmecillinam, procaine benzylpenicillin, propicillin, sarmoxicillin, sulbactam, sulbenicillin, sultamicillin, talampicillin, tazobactam, temocillin, ticarcillin, ticarcillin/clavulanic acid)</p></li>
<li><p><code>polymyxins</code><br />(colistin, polymyxin B, polymyxin B/polysorbate 80)</p></li>
<li><p><code>streptogramins</code><br />(pristinamycin, quinupristin/dalfopristin)</p></li>
<li><p><code>tetracyclines</code><br />(chlortetracycline, clomocycline, demeclocycline, doxycycline, eravacycline, lymecycline, metacycline, minocycline, oxytetracycline, penimepicycline, rolitetracycline, tetracycline, tigecycline)</p></li>
<li><p><code>tetracyclines_except_tgc</code><br />(chlortetracycline, clomocycline, demeclocycline, doxycycline, eravacycline, lymecycline, metacycline, minocycline, oxytetracycline, penimepicycline, rolitetracycline, tetracycline)</p></li>
<li><p><code>ureidopenicillins</code><br />(azlocillin, mezlocillin, piperacillin, piperacillin/tazobactam)</p></li>
</ul>
<h2 class="hasAnchor" id="maturing-lifecycle"><a class="anchor" href="#maturing-lifecycle"></a>Maturing Lifecycle</h2>
<p><img src='figures/lifecycle_experimental.svg' style=margin-bottom:5px /> <br />
The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>experimental</strong>. An experimental function is in early stages of development. The unlying code might be changing frequently. Experimental functions might be removed without deprecation, so you are generally best off waiting until a function is more mature before you use it in production code. Experimental functions are only available in development versions of this <code>AMR</code> package and will thus not be included in releases that are submitted to CRAN, since such functions have not yet matured enough.</p>
<p><img src='figures/lifecycle_maturing.svg' style=margin-bottom:5px /> <br />
The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>maturing</strong>. The unlying code of a maturing function has been roughed out, but finer details might still change. Since this function needs wider usage and more extensive testing, you are very welcome <a href='https://github.com/msberends/AMR/issues'>to suggest changes at our repository</a> or <a href='AMR.html'>write us an email (see section 'Contact Us')</a>.</p>
<h2 class="hasAnchor" id="examples"><a class="anchor" href="#examples"></a>Examples</h2>
<pre class="examples"><span class='va'>x</span> <span class='op'>&lt;-</span> <span class='fu'>custom_eucast_rules</span><span class='op'>(</span><span class='va'>AMC</span> <span class='op'>==</span> <span class='st'>"R"</span> <span class='op'>&amp;</span> <span class='va'>genus</span> <span class='op'>==</span> <span class='st'>"Klebsiella"</span> <span class='op'>~</span> <span class='va'>aminopenicillins</span> <span class='op'>==</span> <span class='st'>"R"</span>,

View File

@ -83,7 +83,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="Latest development version">1.6.0.9006</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.6.0.9007</span>
</span>
</div>

View File

@ -82,7 +82,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="Latest development version">1.6.0.9003</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.6.0.9007</span>
</span>
</div>
@ -346,7 +346,7 @@
</tr>
<tr>
<th>info</th>
<td><p>print progress</p></td>
<td><p>a <a href='https://rdrr.io/r/base/logical.html'>logical</a> to indicate whether a progress bar should be printed, defaults to <code>TRUE</code> only in interactive mode</p></td>
</tr>
<tr>
<th>include_unknown</th>

View File

@ -81,7 +81,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="Latest development version">1.6.0.9006</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.6.0.9007</span>
</span>
</div>
@ -455,7 +455,7 @@
<td>
<p><code><a href="custom_eucast_rules.html">custom_eucast_rules()</a></code> </p>
</td>
<td><p>Create Custom EUCAST Rules</p></td>
<td><p>Define Custom EUCAST Rules</p></td>
</tr>
</tbody><tbody>
<tr>

View File

@ -82,7 +82,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="Latest development version">1.5.0.9040</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.6.0.9007</span>
</span>
</div>
@ -325,7 +325,7 @@
</tr>
<tr>
<th>info</th>
<td><p>print progress</p></td>
<td><p>a <a href='https://rdrr.io/r/base/logical.html'>logical</a> to indicate whether a progress bar should be printed, defaults to <code>TRUE</code> only in interactive mode</p></td>
</tr>
</table>

View File

@ -82,7 +82,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="Latest development version">1.6.0.9003</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.6.0.9007</span>
</span>
</div>
@ -273,11 +273,11 @@
<p>A <a href='https://rdrr.io/r/base/logical.html'>logical</a> vector</p>
<h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2>
<p>This <code>%like%</code> function:</p><ul>
<li><p>Is case-insensitive (use <code>%like_case%</code> for case-sensitive matching)</p></li>
<li><p>Supports multiple patterns</p></li>
<li><p>Checks if <code>pattern</code> is a valid regular expression and sets <code>fixed = TRUE</code> if not, to greatly improve speed (vectorised over <code>pattern</code>)</p></li>
<li><p>Always uses compatibility with Perl unless <code>fixed = TRUE</code>, to greatly improve speed</p></li>
<p>These <code>like()</code> and <code>%like%</code> functions:</p><ul>
<li><p>Are case-insensitive (use <code>%like_case%</code> for case-sensitive matching)</p></li>
<li><p>Support multiple patterns</p></li>
<li><p>Check if <code>pattern</code> is a valid regular expression and sets <code>fixed = TRUE</code> if not, to greatly improve speed (vectorised over <code>pattern</code>)</p></li>
<li><p>Always use compatibility with Perl unless <code>fixed = TRUE</code>, to greatly improve speed</p></li>
</ul>
<p>Using RStudio? The text <code>%like%</code> can also be directly inserted in your code from the Addins menu and can have its own Keyboard Shortcut like <code>Ctrl+Shift+L</code> or <code>Cmd+Shift+L</code> (see <code>Tools</code> &gt; <code>Modify Keyboard Shortcuts...</code>).</p>
@ -298,8 +298,7 @@ The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>stable</s
<div class='dont-index'><p><code><a href='https://rdrr.io/r/base/grep.html'>grepl()</a></code></p></div>
<h2 class="hasAnchor" id="examples"><a class="anchor" href="#examples"></a>Examples</h2>
<pre class="examples"><span class='co'># simple test</span>
<span class='va'>a</span> <span class='op'>&lt;-</span> <span class='st'>"This is a test"</span>
<pre class="examples"><span class='va'>a</span> <span class='op'>&lt;-</span> <span class='st'>"This is a test"</span>
<span class='va'>b</span> <span class='op'>&lt;-</span> <span class='st'>"TEST"</span>
<span class='va'>a</span> <span class='op'>%like%</span> <span class='va'>b</span>
<span class='co'>#&gt; TRUE</span>
@ -317,12 +316,12 @@ The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>stable</s
<span class='co'>#&gt; TRUE FALSE FALSE</span>
<span class='co'># get isolates whose name start with 'Ent' or 'ent'</span>
<span class='co'># \donttest{</span>
<span class='va'>example_isolates</span><span class='op'>[</span><span class='fu'><a href='https://rdrr.io/r/base/which.html'>which</a></span><span class='op'>(</span><span class='fu'><a href='mo_property.html'>mo_name</a></span><span class='op'>(</span><span class='op'>)</span> <span class='op'>%like%</span> <span class='st'>"^ent"</span><span class='op'>)</span>, <span class='op'>]</span>
<span class='kw'>if</span> <span class='op'>(</span><span class='kw'><a href='https://rdrr.io/r/base/library.html'>require</a></span><span class='op'>(</span><span class='st'><a href='https://dplyr.tidyverse.org'>"dplyr"</a></span><span class='op'>)</span><span class='op'>)</span> <span class='op'>{</span>
<span class='va'>example_isolates</span> <span class='op'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/filter.html'>filter</a></span><span class='op'>(</span><span class='fu'><a href='mo_property.html'>mo_name</a></span><span class='op'>(</span><span class='op'>)</span> <span class='op'>%like%</span> <span class='st'>"^ent"</span><span class='op'>)</span>
<span class='op'>}</span>
<span class='co'># }</span>
</pre>
</div>
<div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar">

View File

@ -82,7 +82,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="Latest development version">1.6.0.9001</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.6.0.9007</span>
</span>
</div>
@ -360,7 +360,7 @@ Ordered <a href='https://rdrr.io/r/base/factor.html'>factor</a> with levels <cod
<p>Custom guidelines can be set with the <code>custom_mdro_guideline()</code> function. This is of great importance if you have custom rules to determine MDROs in your hospital, e.g., rules that are dependent on ward, state of contact isolation or other variables in your data.</p>
<p>If you are familiar with <code><a href='https://dplyr.tidyverse.org/reference/case_when.html'>case_when()</a></code> of the <code>dplyr</code> package, you will recognise the input method to set your own rules. Rules must be set using what <span style="R">R</span> considers to be the 'formula notation':</p><pre><span class='va'>custom</span> <span class='op'>&lt;-</span> <span class='fu'>custom_mdro_guideline</span><span class='op'>(</span><span class='va'>CIP</span> <span class='op'>==</span> <span class='st'>"R"</span> <span class='op'>&amp;</span> <span class='va'>age</span> <span class='op'>&gt;</span> <span class='fl'>60</span> <span class='op'>~</span> <span class='st'>"Elderly Type A"</span>,
<p>If you are familiar with the <code><a href='https://dplyr.tidyverse.org/reference/case_when.html'>case_when()</a></code> function of the <code>dplyr</code> package, you will recognise the input method to set your own rules. Rules must be set using what <span style="R">R</span> considers to be the 'formula notation'. The rule is written <em>before</em> the tilde (<code><a href='https://rdrr.io/r/base/tilde.html'>~</a></code>) and the consequence of the rule is written <em>after</em> the tilde:</p><pre><span class='va'>custom</span> <span class='op'>&lt;-</span> <span class='fu'>custom_mdro_guideline</span><span class='op'>(</span><span class='va'>CIP</span> <span class='op'>==</span> <span class='st'>"R"</span> <span class='op'>&amp;</span> <span class='va'>age</span> <span class='op'>&gt;</span> <span class='fl'>60</span> <span class='op'>~</span> <span class='st'>"Elderly Type A"</span>,
<span class='va'>ERY</span> <span class='op'>==</span> <span class='st'>"R"</span> <span class='op'>&amp;</span> <span class='va'>age</span> <span class='op'>&gt;</span> <span class='fl'>60</span> <span class='op'>~</span> <span class='st'>"Elderly Type B"</span><span class='op'>)</span>
</pre>

View File

@ -82,7 +82,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="Latest development version">1.6.0</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.6.0.9007</span>
</span>
</div>
@ -281,7 +281,7 @@
<p>Please note that entries are only based on the Catalogue of Life and the LPSN (see below). Since these sources incorporate entries based on (recent) publications in the International Journal of Systematic and Evolutionary Microbiology (IJSEM), it can happen that the year of publication is sometimes later than one might expect.</p>
<p>For example, <em>Staphylococcus pettenkoferi</em> was described for the first time in Diagnostic Microbiology and Infectious Disease in 2002 (doi: <a href='https://doi.org/10.1016/s0732-8893(02)00399-1'>10.1016/s0732-8893(02)00399-1</a>
), but it was not before 2007 that a publication in IJSEM followed (doi: <a href='https://doi.org/10.1099/ijs.0.64381-0'>10.1099/ijs.0.64381-0</a>
). Consequently, the AMR package returns 2007 for <code><a href='mo_property.html'>mo_year("S. pettenkoferi")</a></code>.</p><h3 class='hasAnchor' id='arguments'><a class='anchor' href='#arguments'></a>Manual additions</h3>
). Consequently, the <code>AMR</code> package returns 2007 for <code><a href='mo_property.html'>mo_year("S. pettenkoferi")</a></code>.</p><h3 class='hasAnchor' id='arguments'><a class='anchor' href='#arguments'></a>Manual additions</h3>
<p>For convenience, some entries were added manually:</p><ul>

View File

@ -82,7 +82,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="Latest development version">1.6.0.9003</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.6.0.9007</span>
</span>
</div>

View File

@ -82,7 +82,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="Latest development version">1.6.0.9003</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.6.0.9007</span>
</span>
</div>

View File

@ -81,7 +81,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="Latest development version">1.6.0.9006</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.6.0.9007</span>
</span>
</div>

View File

@ -10,6 +10,7 @@ ab_from_text(
collapse = NULL,
translate_ab = FALSE,
thorough_search = NULL,
info = interactive(),
...
)
}
@ -24,6 +25,8 @@ ab_from_text(
\item{thorough_search}{logical to indicate whether the input must be extensively searched for misspelling and other faulty input values. Setting this to \code{TRUE} will take considerably more time than when using \code{FALSE}. At default, it will turn \code{TRUE} when all input elements contain a maximum of three words.}
\item{info}{logical to indicate whether a progress bar should be printed, defaults to \code{TRUE} only in interactive mode}
\item{...}{arguments passed on to \code{\link[=as.ab]{as.ab()}}}
}
\value{

View File

@ -6,7 +6,7 @@
\alias{is.ab}
\title{Transform Input to an Antibiotic ID}
\usage{
as.ab(x, flag_multiple_results = TRUE, info = TRUE, ...)
as.ab(x, flag_multiple_results = TRUE, info = interactive(), ...)
is.ab(x)
}
@ -15,7 +15,7 @@ is.ab(x)
\item{flag_multiple_results}{logical to indicate whether a note should be printed to the console that probably more than one antibiotic code or name can be retrieved from a single input value.}
\item{info}{logical to indicate whether a progress bar should be printed}
\item{info}{a \link{logical} to indicate whether a progress bar should be printed, defaults to \code{TRUE} only in interactive mode}
\item{...}{arguments passed on to internal functions}
}

View File

@ -17,6 +17,7 @@ as.mo(
reference_df = get_mo_source(),
ignore_pattern = getOption("AMR_ignore_pattern"),
language = get_locale(),
info = interactive(),
...
)
@ -47,6 +48,8 @@ This excludes \emph{Enterococci} at default (who are in group D), use \code{Lanc
\item{language}{language to translate text like "no growth", which defaults to the system language (see \code{\link[=get_locale]{get_locale()}})}
\item{info}{a \link{logical} to indicate if a progress bar should be printed if more than 25 items are to be coerced, defaults to \code{TRUE} only in interactive mode}
\item{...}{other arguments passed on to functions}
}
\value{

View File

@ -2,30 +2,102 @@
% Please edit documentation in R/custom_eucast_rules.R
\name{custom_eucast_rules}
\alias{custom_eucast_rules}
\title{Create Custom EUCAST Rules}
\title{Define Custom EUCAST Rules}
\usage{
custom_eucast_rules(...)
}
\arguments{
\item{...}{rules in formula notation, see \emph{Examples}}
}
\value{
A \link{list} containing the custom rules
}
\description{
Create Custom EUCAST Rules
Define custom EUCAST rules for your organisation or specific analysis and use the output of this function in \code{\link[=eucast_rules]{eucast_rules()}}.
}
\details{
This documentation page will be updated shortly. \strong{This function is experimental.}
Some organisations have their own adoption of EUCAST rules. This function can be used to define custom EUCAST rules to be used in the \code{\link[=eucast_rules]{eucast_rules()}} function.
}
\section{How it works}{
..
\subsection{Basics}{
It is also possible to define antibiotic groups instead of single antibiotics. The following groups are allowed (case-insensitive): \code{aminoglycosides}, \code{aminopenicillins}, \code{betalactams}, \code{carbapenems}, \code{cephalosporins}, \code{cephalosporins_1st}, \code{cephalosporins_2nd}, \code{cephalosporins_3rd}, \code{cephalosporins_except_caz}, \code{fluoroquinolones}, \code{glycopeptides}, \code{glycopeptides_except_lipo}, \code{lincosamides}, \code{lipoglycopeptides}, \code{macrolides}, \code{oxazolidinones}, \code{penicillins}, \code{polymyxins}, \code{streptogramins}, \code{tetracyclines}, \code{tetracyclines_except_tgc} and \code{ureidopenicillins}.
If you are familiar with the \code{\link[dplyr:case_when]{case_when()}} function of the \code{dplyr} package, you will recognise the input method to set your own rules. Rules must be set using what \R considers to be the 'formula notation'. The rule itself is written \emph{before} the tilde (\code{~}) and the consequence of the rule is written \emph{after} the tilde:\preformatted{x <- custom_eucast_rules(TZP == "S" ~ aminopenicillins == "S",
TZP == "R" ~ aminopenicillins == "R")
}
\section{Experimental Lifecycle}{
These are two custom EUCAST rules: if TZP (piperacillin/tazobactam) is "S", all aminopenicillins (ampicillin and amoxicillin) must be made "S", and if TZP is "R", aminopenicillins must be made "R". These rules can also be printed to the console, so it is immediately clear how they work:\preformatted{x
#> A set of custom EUCAST rules:
#>
#> 1. If TZP is S then set to S:
#> amoxicillin (AMX), ampicillin (AMP)
#>
#> 2. If TZP is R then set to R:
#> amoxicillin (AMX), ampicillin (AMP)
}
\if{html}{\figure{lifecycle_experimental.svg}{options: style=margin-bottom:5px} \cr}
The \link[=lifecycle]{lifecycle} of this function is \strong{experimental}. An experimental function is in early stages of development. The unlying code might be changing frequently. Experimental functions might be removed without deprecation, so you are generally best off waiting until a function is more mature before you use it in production code. Experimental functions are only available in development versions of this \code{AMR} package and will thus not be included in releases that are submitted to CRAN, since such functions have not yet matured enough.
The rules (the part \emph{before} the tilde, in above example \code{TZP == "S"} and \code{TZP == "R"}) must be evaluable in your data set: it should be able to run as a filter in your data set without errors. This means for the above example that the column \code{TZP} must exist. We will create a sample data set and test the rules set:\preformatted{df <- data.frame(mo = c("E. coli", "K. pneumoniae"),
TZP = "R",
amox = "",
AMP = "")
df
#> mo TZP amox AMP
#> 1 E. coli R
#> 2 K. pneumoniae R
eucast_rules(df, rules = "custom", custom_rules = x)
#> mo TZP amox AMP
#> 1 E. coli R R R
#> 2 K. pneumoniae R R R
}
}
\subsection{Using taxonomic properties in rules}{
There is one exception in variables used for the rules: all column names of the \link{microorganisms} data set can also be used, but do not have to exist in the data set. These column names are: \code{mo}, \code{fullname}, \code{kingdom}, \code{phylum}, \code{class}, \code{order}, \code{family}, \code{genus}, \code{species}, \code{subspecies}, \code{rank}, \code{ref}, \code{species_id}, \code{source}, \code{prevalence} and \code{snomed}. Thus, this next example will work as well, despite the fact that the \code{df} data set does not contain a column \code{genus}:\preformatted{y <- custom_eucast_rules(TZP == "S" & genus == "Klebsiella" ~ aminopenicillins == "S",
TZP == "R" & genus == "Klebsiella" ~ aminopenicillins == "R")
eucast_rules(df, rules = "custom", custom_rules = y)
#> mo TZP amox AMP
#> 1 E. coli R
#> 2 K. pneumoniae R R R
}
}
\subsection{Usage of antibiotic group names}{
It is possible to define antibiotic groups instead of single antibiotics for the rule consequence, the part \emph{after} the tilde. In above examples, the antibiotic group \code{aminopenicillins} is used to include ampicillin and amoxicillin. The following groups are allowed (case-insensitive). Within parentheses are the antibiotic agents that will be matched when running the rule.
\itemize{
\item \code{aminoglycosides}\cr(amikacin, amikacin/fosfomycin, amphotericin B-high, apramycin, arbekacin, astromicin, bekanamycin, dibekacin, framycetin, gentamicin, gentamicin-high, habekacin, hygromycin, isepamicin, kanamycin, kanamycin-high, kanamycin/cephalexin, micronomicin, neomycin, netilmicin, pentisomicin, plazomicin, propikacin, ribostamycin, sisomicin, streptoduocin, streptomycin, streptomycin-high, tobramycin, tobramycin-high)
\item \code{aminopenicillins}\cr(amoxicillin, ampicillin)
\item \code{betalactams}\cr(amoxicillin, amoxicillin/clavulanic acid, amoxicillin/sulbactam, ampicillin, ampicillin/sulbactam, apalcillin, aspoxicillin, avibactam, azidocillin, azlocillin, aztreonam, aztreonam/avibactam, bacampicillin, benzathine benzylpenicillin, benzathine phenoxymethylpenicillin, benzylpenicillin, biapenem, cadazolid, carbenicillin, carindacillin, cefacetrile, cefaclor, cefadroxil, cefaloridine, cefamandole, cefatrizine, cefazedone, cefazolin, cefcapene, cefcapene pivoxil, cefdinir, cefditoren, cefditoren pivoxil, cefepime, cefepime/clavulanic acid, cefepime/tazobactam, cefetamet, cefetamet pivoxil, cefetecol (Cefcatacol), cefetrizole, cefixime, cefmenoxime, cefmetazole, cefodizime, cefonicid, cefoperazone, cefoperazone/sulbactam, ceforanide, cefoselis, cefotaxime, cefotaxime/clavulanic acid, cefotaxime/sulbactam, cefotetan, cefotiam, cefotiam hexetil, cefovecin, cefoxitin, cefoxitin screening, cefozopran, cefpimizole, cefpiramide, cefpirome, cefpodoxime, cefpodoxime proxetil, cefpodoxime/clavulanic acid, cefprozil, cefquinome, cefroxadine, cefsulodin, cefsumide, ceftaroline, ceftaroline/avibactam, ceftazidime, ceftazidime/avibactam, ceftazidime/clavulanic acid, cefteram, cefteram pivoxil, ceftezole, ceftibuten, ceftiofur, ceftizoxime, ceftizoxime alapivoxil, ceftobiprole, ceftobiprole medocaril, ceftolozane/enzyme inhibitor, ceftolozane/tazobactam, ceftriaxone, cefuroxime, cefuroxime axetil, cephalexin, cephalothin, cephapirin, cephradine, ciclacillin, clometocillin, cloxacillin, dicloxacillin, doripenem, epicillin, ertapenem, flucloxacillin, hetacillin, imipenem, imipenem/EDTA, imipenem/relebactam, latamoxef, lenampicillin, loracarbef, mecillinam (Amdinocillin), meropenem, meropenem/nacubactam, meropenem/vaborbactam, metampicillin, methicillin, mezlocillin, mezlocillin/sulbactam, nacubactam, nafcillin, oxacillin, panipenem, penamecillin, penicillin/novobiocin, penicillin/sulbactam, phenethicillin, phenoxymethylpenicillin, piperacillin, piperacillin/sulbactam, piperacillin/tazobactam, piridicillin, pivampicillin, pivmecillinam, procaine benzylpenicillin, propicillin, razupenem, ritipenem, ritipenem acoxil, sarmoxicillin, sulbactam, sulbenicillin, sultamicillin, talampicillin, tazobactam, tebipenem, temocillin, ticarcillin, ticarcillin/clavulanic acid)
\item \code{carbapenems}\cr(biapenem, doripenem, ertapenem, imipenem, imipenem/EDTA, imipenem/relebactam, meropenem, meropenem/nacubactam, meropenem/vaborbactam, panipenem, razupenem, ritipenem, ritipenem acoxil, tebipenem)
\item \code{cephalosporins}\cr(cadazolid, cefacetrile, cefaclor, cefadroxil, cefaloridine, cefamandole, cefatrizine, cefazedone, cefazolin, cefcapene, cefcapene pivoxil, cefdinir, cefditoren, cefditoren pivoxil, cefepime, cefepime/clavulanic acid, cefepime/tazobactam, cefetamet, cefetamet pivoxil, cefetecol (Cefcatacol), cefetrizole, cefixime, cefmenoxime, cefmetazole, cefodizime, cefonicid, cefoperazone, cefoperazone/sulbactam, ceforanide, cefoselis, cefotaxime, cefotaxime/clavulanic acid, cefotaxime/sulbactam, cefotetan, cefotiam, cefotiam hexetil, cefovecin, cefoxitin, cefoxitin screening, cefozopran, cefpimizole, cefpiramide, cefpirome, cefpodoxime, cefpodoxime proxetil, cefpodoxime/clavulanic acid, cefprozil, cefquinome, cefroxadine, cefsulodin, cefsumide, ceftaroline, ceftaroline/avibactam, ceftazidime, ceftazidime/avibactam, ceftazidime/clavulanic acid, cefteram, cefteram pivoxil, ceftezole, ceftibuten, ceftiofur, ceftizoxime, ceftizoxime alapivoxil, ceftobiprole, ceftobiprole medocaril, ceftolozane/enzyme inhibitor, ceftolozane/tazobactam, ceftriaxone, cefuroxime, cefuroxime axetil, cephalexin, cephalothin, cephapirin, cephradine, latamoxef, loracarbef)
\item \code{cephalosporins_1st}\cr(cefacetrile, cefadroxil, cefaloridine, cefatrizine, cefazedone, cefazolin, cefroxadine, ceftezole, cephalexin, cephalothin, cephapirin, cephradine)
\item \code{cephalosporins_2nd}\cr(cefaclor, cefamandole, cefmetazole, cefonicid, ceforanide, cefotetan, cefotiam, cefoxitin, cefoxitin screening, cefprozil, cefuroxime, cefuroxime axetil, loracarbef)
\item \code{cephalosporins_3rd}\cr(cadazolid, cefcapene, cefcapene pivoxil, cefdinir, cefditoren, cefditoren pivoxil, cefetamet, cefetamet pivoxil, cefixime, cefmenoxime, cefodizime, cefoperazone, cefoperazone/sulbactam, cefotaxime, cefotaxime/clavulanic acid, cefotaxime/sulbactam, cefotiam hexetil, cefovecin, cefpimizole, cefpiramide, cefpodoxime, cefpodoxime proxetil, cefpodoxime/clavulanic acid, cefsulodin, ceftazidime, ceftazidime/avibactam, ceftazidime/clavulanic acid, cefteram, cefteram pivoxil, ceftibuten, ceftiofur, ceftizoxime, ceftizoxime alapivoxil, ceftriaxone, latamoxef)
\item \code{cephalosporins_except_caz}\cr(cadazolid, cefacetrile, cefaclor, cefadroxil, cefaloridine, cefamandole, cefatrizine, cefazedone, cefazolin, cefcapene, cefcapene pivoxil, cefdinir, cefditoren, cefditoren pivoxil, cefepime, cefepime/clavulanic acid, cefepime/tazobactam, cefetamet, cefetamet pivoxil, cefetecol (Cefcatacol), cefetrizole, cefixime, cefmenoxime, cefmetazole, cefodizime, cefonicid, cefoperazone, cefoperazone/sulbactam, ceforanide, cefoselis, cefotaxime, cefotaxime/clavulanic acid, cefotaxime/sulbactam, cefotetan, cefotiam, cefotiam hexetil, cefovecin, cefoxitin, cefoxitin screening, cefozopran, cefpimizole, cefpiramide, cefpirome, cefpodoxime, cefpodoxime proxetil, cefpodoxime/clavulanic acid, cefprozil, cefquinome, cefroxadine, cefsulodin, cefsumide, ceftaroline, ceftaroline/avibactam, ceftazidime/avibactam, ceftazidime/clavulanic acid, cefteram, cefteram pivoxil, ceftezole, ceftibuten, ceftiofur, ceftizoxime, ceftizoxime alapivoxil, ceftobiprole, ceftobiprole medocaril, ceftolozane/enzyme inhibitor, ceftolozane/tazobactam, ceftriaxone, cefuroxime, cefuroxime axetil, cephalexin, cephalothin, cephapirin, cephradine, latamoxef, loracarbef)
\item \code{fluoroquinolones}\cr(ciprofloxacin, enoxacin, fleroxacin, gatifloxacin, gemifloxacin, grepafloxacin, levofloxacin, lomefloxacin, moxifloxacin, norfloxacin, ofloxacin, pazufloxacin, pefloxacin, prulifloxacin, rufloxacin, sparfloxacin, temafloxacin, trovafloxacin)
\item \code{glycopeptides}\cr(avoparcin, dalbavancin, norvancomycin, oritavancin, ramoplanin, teicoplanin, teicoplanin-macromethod, telavancin, vancomycin, vancomycin-macromethod)
\item \code{glycopeptides_except_lipo}\cr(avoparcin, norvancomycin, ramoplanin, teicoplanin, teicoplanin-macromethod, vancomycin, vancomycin-macromethod)
\item \code{lincosamides}\cr(clindamycin, lincomycin, pirlimycin)
\item \code{lipoglycopeptides}\cr(dalbavancin, oritavancin, telavancin)
\item \code{macrolides}\cr(azithromycin, clarithromycin, dirithromycin, erythromycin, flurithromycin, josamycin, midecamycin, miocamycin, oleandomycin, rokitamycin, roxithromycin, spiramycin, telithromycin, troleandomycin)
\item \code{oxazolidinones}\cr(cycloserine, linezolid, tedizolid, thiacetazone)
\item \code{penicillins}\cr(amoxicillin, amoxicillin/clavulanic acid, amoxicillin/sulbactam, ampicillin, ampicillin/sulbactam, apalcillin, aspoxicillin, avibactam, azidocillin, azlocillin, aztreonam, aztreonam/avibactam, bacampicillin, benzathine benzylpenicillin, benzathine phenoxymethylpenicillin, benzylpenicillin, carbenicillin, carindacillin, ciclacillin, clometocillin, cloxacillin, dicloxacillin, epicillin, flucloxacillin, hetacillin, lenampicillin, mecillinam (Amdinocillin), metampicillin, methicillin, mezlocillin, mezlocillin/sulbactam, nacubactam, nafcillin, oxacillin, penamecillin, penicillin/novobiocin, penicillin/sulbactam, phenethicillin, phenoxymethylpenicillin, piperacillin, piperacillin/sulbactam, piperacillin/tazobactam, piridicillin, pivampicillin, pivmecillinam, procaine benzylpenicillin, propicillin, sarmoxicillin, sulbactam, sulbenicillin, sultamicillin, talampicillin, tazobactam, temocillin, ticarcillin, ticarcillin/clavulanic acid)
\item \code{polymyxins}\cr(colistin, polymyxin B, polymyxin B/polysorbate 80)
\item \code{streptogramins}\cr(pristinamycin, quinupristin/dalfopristin)
\item \code{tetracyclines}\cr(chlortetracycline, clomocycline, demeclocycline, doxycycline, eravacycline, lymecycline, metacycline, minocycline, oxytetracycline, penimepicycline, rolitetracycline, tetracycline, tigecycline)
\item \code{tetracyclines_except_tgc}\cr(chlortetracycline, clomocycline, demeclocycline, doxycycline, eravacycline, lymecycline, metacycline, minocycline, oxytetracycline, penimepicycline, rolitetracycline, tetracycline)
\item \code{ureidopenicillins}\cr(azlocillin, mezlocillin, piperacillin, piperacillin/tazobactam)
}
}
}
\section{Maturing Lifecycle}{
\if{html}{\figure{lifecycle_maturing.svg}{options: style=margin-bottom:5px} \cr}
The \link[=lifecycle]{lifecycle} of this function is \strong{maturing}. The unlying code of a maturing function has been roughed out, but finer details might still change. Since this function needs wider usage and more extensive testing, you are very welcome \href{https://github.com/msberends/AMR/issues}{to suggest changes at our repository} or \link[=AMR]{write us an email (see section 'Contact Us')}.
}
\examples{

View File

@ -81,7 +81,7 @@ filter_first_weighted_isolate(
\item{points_threshold}{points until the comparison of key antibiotics will lead to inclusion of an isolate when \code{type = "points"}, see \emph{Details}}
\item{info}{print progress}
\item{info}{a \link{logical} to indicate whether a progress bar should be printed, defaults to \code{TRUE} only in interactive mode}
\item{include_unknown}{logical to indicate whether 'unknown' microorganisms should be included too, i.e. microbial code \code{"UNKNOWN"}, which defaults to \code{FALSE}. For WHONET users, this means that all records with organism code \code{"con"} (\emph{contamination}) will be excluded at default. Isolates with a microbial ID of \code{NA} will always be excluded as first isolate.}

View File

@ -62,7 +62,7 @@ key_antibiotics_equal(
\item{points_threshold}{points until the comparison of key antibiotics will lead to inclusion of an isolate when \code{type = "points"}, see \emph{Details}}
\item{info}{print progress}
\item{info}{a \link{logical} to indicate whether a progress bar should be printed, defaults to \code{TRUE} only in interactive mode}
}
\description{
These function can be used to determine first isolates (see \code{\link[=first_isolate]{first_isolate()}}). Using key antibiotics to determine first isolates is more reliable than without key antibiotics. These selected isolates can then be called first 'weighted' isolates.

View File

@ -29,12 +29,12 @@ A \link{logical} vector
Convenient wrapper around \code{\link[=grepl]{grepl()}} to match a pattern: \code{x \%like\% pattern}. It always returns a \code{\link{logical}} vector and is always case-insensitive (use \code{x \%like_case\% pattern} for case-sensitive matching). Also, \code{pattern} can be as long as \code{x} to compare items of each index in both vectors, or they both can have the same length to iterate over all cases.
}
\details{
This \verb{\%like\%} function:
These \code{\link[=like]{like()}} and \verb{\%like\%} functions:
\itemize{
\item Is case-insensitive (use \verb{\%like_case\%} for case-sensitive matching)
\item Supports multiple patterns
\item Checks if \code{pattern} is a valid regular expression and sets \code{fixed = TRUE} if not, to greatly improve speed (vectorised over \code{pattern})
\item Always uses compatibility with Perl unless \code{fixed = TRUE}, to greatly improve speed
\item Are case-insensitive (use \verb{\%like_case\%} for case-sensitive matching)
\item Support multiple patterns
\item Check if \code{pattern} is a valid regular expression and sets \code{fixed = TRUE} if not, to greatly improve speed (vectorised over \code{pattern})
\item Always use compatibility with Perl unless \code{fixed = TRUE}, to greatly improve speed
}
Using RStudio? The text \verb{\%like\%} can also be directly inserted in your code from the Addins menu and can have its own Keyboard Shortcut like \code{Ctrl+Shift+L} or \code{Cmd+Shift+L} (see \code{Tools} > \verb{Modify Keyboard Shortcuts...}).
@ -53,7 +53,6 @@ On our website \url{https://msberends.github.io/AMR/} you can find \href{https:/
}
\examples{
# simple test
a <- "This is a test"
b <- "TEST"
a \%like\% b
@ -72,13 +71,13 @@ a \%like\% b[1]
#> TRUE FALSE FALSE
# get isolates whose name start with 'Ent' or 'ent'
\donttest{
example_isolates[which(mo_name() \%like\% "^ent"), ]
if (require("dplyr")) {
example_isolates \%>\%
filter(mo_name() \%like\% "^ent")
}
}
}
\seealso{
\code{\link[=grepl]{grepl()}}
}

View File

@ -119,7 +119,7 @@ Please suggest your own (country-specific) guidelines by letting us know: \url{h
Custom guidelines can be set with the \code{\link[=custom_mdro_guideline]{custom_mdro_guideline()}} function. This is of great importance if you have custom rules to determine MDROs in your hospital, e.g., rules that are dependent on ward, state of contact isolation or other variables in your data.
If you are familiar with \code{case_when()} of the \code{dplyr} package, you will recognise the input method to set your own rules. Rules must be set using what \R considers to be the 'formula notation':\preformatted{custom <- custom_mdro_guideline(CIP == "R" & age > 60 ~ "Elderly Type A",
If you are familiar with the \code{\link[dplyr:case_when]{case_when()}} function of the \code{dplyr} package, you will recognise the input method to set your own rules. Rules must be set using what \R considers to be the 'formula notation'. The rule is written \emph{before} the tilde (\code{~}) and the consequence of the rule is written \emph{after} the tilde:\preformatted{custom <- custom_mdro_guideline(CIP == "R" & age > 60 ~ "Elderly Type A",
ERY == "R" & age > 60 ~ "Elderly Type B")
}

View File

@ -46,7 +46,7 @@ A data set containing the microbial taxonomy, last updated in March 2021, of six
\details{
Please note that entries are only based on the Catalogue of Life and the LPSN (see below). Since these sources incorporate entries based on (recent) publications in the International Journal of Systematic and Evolutionary Microbiology (IJSEM), it can happen that the year of publication is sometimes later than one might expect.
For example, \emph{Staphylococcus pettenkoferi} was described for the first time in Diagnostic Microbiology and Infectious Disease in 2002 (\doi{10.1016/s0732-8893(02)00399-1}), but it was not before 2007 that a publication in IJSEM followed (\doi{10.1099/ijs.0.64381-0}). Consequently, the AMR package returns 2007 for \code{mo_year("S. pettenkoferi")}.
For example, \emph{Staphylococcus pettenkoferi} was described for the first time in Diagnostic Microbiology and Infectious Disease in 2002 (\doi{10.1016/s0732-8893(02)00399-1}), but it was not before 2007 that a publication in IJSEM followed (\doi{10.1099/ijs.0.64381-0}). Consequently, the \code{AMR} package returns 2007 for \code{mo_year("S. pettenkoferi")}.
\subsection{Manual additions}{
For convenience, some entries were added manually: