(v1.3.0.9016) mo_uncertainties() overhaul

pull/67/head
parent 68e9cb78e9
commit 3ff871afeb

@ -1,6 +1,6 @@
Package: AMR
Version: 1.3.0.9015
Date: 2020-09-03
Version: 1.3.0.9016
Date: 2020-09-12
Title: Antimicrobial Resistance Analysis
Authors@R: c(
person(role = c("aut", "cre"),

@ -1,5 +1,5 @@
# AMR 1.3.0.9015
## <small>Last updated: 3 September 2020</small>
# AMR 1.3.0.9016
## <small>Last updated: 12 September 2020</small>
Note: some changes in this version were suggested by anonymous reviewers from the journal we submitted our manuscipt to. We are those reviewers very grateful for going through our code so thoroughly!
@ -39,6 +39,7 @@ Note: some changes in this version were suggested by anonymous reviewers from th
#> [1] 24 24
```
* Improvements for `as.mo()`:
* Any user input value that could mean more than one taxonomic entry is now considered 'uncertain'. Instead of a warning, a message will be thrown and the accompanying `mo_uncertainties()` has been changed completely; it now prints all possible candidates with their score.
* Big speed improvement for already valid microorganism ID. This also means an significant speed improvement for using `mo_*` functions like `mo_name()` on microoganism IDs.
* Added parameter `ignore_pattern` to `as.mo()` which can also be given to `mo_*` functions like `mo_name()`, to exclude known non-relevant input from analysing. This can also be set with the option `AMR_ignore_pattern`.
* `get_locale()` now uses `Sys.getlocale()` instead of `Sys.getlocale("LC_COLLATE")`
@ -48,6 +49,7 @@ Note: some changes in this version were suggested by anonymous reviewers from th
* BORSA is now recognised as an abbreviation for *Staphylococcus aureus*, meaning that e.g. `mo_genus("BORSA")` will return "Staphylococcus"
* Added a feature from AMR 1.1.0 and earlier again, but now without other package dependencies: `tibble` printing support for classes `<rsi>`, `<mic>`, `<disk>`, `<ab>` and `<mo>`. When using `tibble`s containing antimicrobial columns (class `<rsi>`), "S" will print in green, "I" will print in yellow and "R" will print in red. Microbial IDs (class `<mo>`) will emphasise on the genus and species, not on the kingdom.
* Names of antiviral agents in data set `antivirals` now have a starting capital letter, like it is the case in the `antibiotics` data set
* Updated the documentation of the `WHONET` data set to clarify that all patient names are fictitious
### Other
* Removed unnecessary references to the `base` package

@ -492,7 +492,8 @@ create_pillar_column <- function(x, ...) {
}
}
# copied from vctrs::s3_register by their permission
# copied from vctrs::s3_register by their permission:
# https://github.com/r-lib/vctrs/blob/05968ce8e669f73213e3e894b5f4424af4f46316/R/register-s3.R
s3_register <- function(generic, class, method = NULL) {
stopifnot(is.character(generic), length(generic) == 1)
stopifnot(is.character(class), length(class) == 1)

@ -68,3 +68,16 @@
#' @name AMR
#' @rdname AMR
NULL
#' Plotting for classes `rsi` and `disk`
#'
#' Functions to print classes of the `AMR` package.
#' @inheritSection lifecycle Stable lifecycle
#' @inheritSection AMR Read more on our website!
#' @param ... Parameters passed on to functions
#' @inheritParams base::plot
#' @inheritParams graphics::barplot
#' @name plot
#' @rdname plot
#' @keywords internal
NULL

@ -194,7 +194,7 @@ catalogue_of_life <- list(
#' Data set with `r format(nrow(WHONET), big.mark = ",")` isolates - WHONET example
#'
#' This example data set has the exact same structure as an export file from WHONET. Such files can be used with this package, as this example data set shows. The antibiotic results are based on our [example_isolates] data set. All patient names are created using online surname generators and are only in place for practice purposes.
#' This example data set has the exact same structure as an export file from WHONET. Such files can be used with this package, as this example data set shows. The antibiotic results are from our [example_isolates] data set. All patient names are created using online surname generators and are only in place for practice purposes.
#' @format A [`data.frame`] with `r format(nrow(WHONET), big.mark = ",")` observations and `r ncol(WHONET)` variables:
#' - `Identification number`\cr ID of the sample
#' - `Specimen number`\cr ID of the specimen

@ -210,7 +210,7 @@ summary.mic <- function(object, ...) {
#' @method plot mic
#' @export
#' @importFrom graphics barplot axis par
#' @noRd
#' @rdname plot
plot.mic <- function(x,
main = paste("MIC values of", deparse(substitute(x))),
ylab = "Frequency",
@ -229,7 +229,7 @@ plot.mic <- function(x,
#' @method barplot mic
#' @export
#' @importFrom graphics barplot axis
#' @noRd
#' @rdname plot
barplot.mic <- function(height,
main = paste("MIC values of", deparse(substitute(height))),
ylab = "Frequency",

155
R/mo.R

@ -86,7 +86,7 @@
#' - `"Fluoroquinolone-resistant Neisseria gonorrhoeae"`. The first word will be stripped, after which the function will try to find a match. A warning will be thrown that the result *Neisseria gonorrhoeae* (``r as.mo("Neisseria gonorrhoeae")``) needs review.
#'
#' There are three helper functions that can be run after using the [as.mo()] function:
#' - Use [mo_uncertainties()] to get a [`data.frame`] with all values that were coerced to a valid value, but with uncertainty. The output contains a score, that is calculated as \eqn{(n - 0.5 * L) / n}, where *n* is the number of characters of the full taxonomic name of the microorganism, and *L* is the [Levenshtein distance](https://en.wikipedia.org/wiki/Levenshtein_distance) between that full name and the user input.
#' - Use [mo_uncertainties()] to get a [`data.frame`] that prints in a pretty format with all taxonomic names that were guessed. The output contains a score that is based on the human pathogenic prevalence and the [Levenshtein distance](https://en.wikipedia.org/wiki/Levenshtein_distance) between the full taxonomic name and the user input.
#' - Use [mo_failures()] to get a [`character`] [`vector`] with all values that could not be coerced to a valid value.
#' - Use [mo_renamed()] to get a [`data.frame`] with all values that could be coerced based on old, previously accepted taxonomic names.
#'
@ -178,6 +178,14 @@ as.mo <- function(x,
...) {
check_dataset_integrity()
if (tryCatch(all(x %in% MO_lookup$mo, na.rm = TRUE)
& isFALSE(Becker)
& isFALSE(Lancefield), error = function(e) FALSE)) {
# don't look into valid MO codes, just return them
# is.mo() won't work - codes might change between package versions
return(to_class_mo(x))
}
if (tryCatch(all(tolower(x) %in% MO_lookup$fullname_lower, na.rm = TRUE)
& isFALSE(Becker)
@ -273,36 +281,7 @@ exec_as.mo <- function(x,
reference_data_to_use = MO_lookup) {
check_dataset_integrity()
lookup <- function(needle, column = property, haystack = reference_data_to_use, n = 1, debug_mode = debug) {
# `column` can be NULL for all columns, or a selection
# returns a character (vector) - if `column` > length 1 then with columns as names
if (isTRUE(debug_mode)) {
cat(font_silver("looking up: ", substitute(needle), "\n", collapse = ""))
}
if (length(column) == 1) {
res <- haystack[which(eval(substitute(needle), envir = haystack, enclos = parent.frame())), column, drop = TRUE]
res <- as.character(res)
if (length(res) == 0) {
NA_character_
} else {
res[seq_len(min(n, length(res)))]
}
} else {
if (is.null(column)) {
column <- names(haystack)
}
res <- haystack[which(eval(substitute(needle), envir = haystack, enclos = parent.frame())), , drop = FALSE]
res <- res[seq_len(min(n, nrow(res))), column, drop = TRUE]
if (NROW(res) == 0) {
res <- rep(NA_character_, length(column))
}
res <- as.character(res)
names(res) <- column
res
}
}
# start off with replaced language-specific non-ASCII characters with ASCII characters
x <- parse_and_convert(x)
# replace mo codes used in older package versions
@ -323,14 +302,15 @@ exec_as.mo <- function(x,
}
options(mo_renamed_last_run = NULL)
failures <- character(0)
uncertainty_level <- translate_allow_uncertain(allow_uncertain)
uncertainties <- data.frame(uncertainty = integer(0),
input = character(0),
fullname = character(0),
renamed_to = character(0),
mo = character(0),
mo = character(0),
candidates = character(0),
stringsAsFactors = FALSE)
failures <- character(0)
uncertainty_level <- translate_allow_uncertain(allow_uncertain)
old_mo_warning <- FALSE
x_input <- x
@ -403,6 +383,43 @@ exec_as.mo <- function(x,
} else if (!all(x %in% microorganisms[, property])) {
lookup <- function(needle, column = property, haystack = reference_data_to_use, n = 1, debug_mode = debug, input = "") {
# `column` can be NULL for all columns, or a selection
# returns a character (vector) - if `column` > length 1 then with columns as names
if (isTRUE(debug_mode)) {
cat(font_silver("looking up: ", substitute(needle), "\n", collapse = ""))
}
if (length(column) == 1) {
res_df <- haystack[which(eval(substitute(needle), envir = haystack, enclos = parent.frame())), , drop = FALSE]
res <- as.character(res_df[, column, drop = TRUE])
if (length(res) == 0) {
NA_character_
} else {
if (length(res) > n) {
# save the other possible results as well
uncertainties <<- rbind(uncertainties,
format_uncertainty_as_df(uncertainty_level = 1,
input = x_backup[i],
result_mo = res_df[1, "mo", drop = TRUE],
candidates = as.character(res_df[, "fullname", drop = TRUE])))
}
res[seq_len(min(n, length(res)))]
}
} else {
if (is.null(column)) {
column <- names(haystack)
}
res <- haystack[which(eval(substitute(needle), envir = haystack, enclos = parent.frame())), , drop = FALSE]
res <- res[seq_len(min(n, nrow(res))), column, drop = TRUE]
if (NROW(res) == 0) {
res <- rep(NA_character_, length(column))
}
res <- as.character(res)
names(res) <- column
res
}
}
strip_whitespace <- function(x, dyslexia_mode) {
# all whitespaces (tab, new lines, etc.) should be one space
# and spaces before and after should be omitted
@ -1387,9 +1404,7 @@ exec_as.mo <- function(x,
}
msg <- paste0("Result", plural[1], " of ", nr2char(NROW(uncertainties)), " value", plural[1],
" ", plural[3], " guessed with uncertainty. Use mo_uncertainties() to review ", plural[2], ".")
warning(font_red(paste0("\n", msg)),
call. = FALSE,
immediate. = TRUE) # thus will always be shown, even if >= warnings
message(font_blue(msg))
}
# Becker ----
@ -1514,25 +1529,25 @@ was_renamed <- function(name_old, name_new, ref_old = "", ref_new = "", mo = "")
format_uncertainty_as_df <- function(uncertainty_level,
input,
result_mo) {
result_mo,
candidates = NULL) {
if (!is.null(getOption("mo_renamed_last_run", default = NULL))) {
# was found as a renamed mo
df <- data.frame(uncertainty = uncertainty_level,
input = input,
fullname = getOption("mo_renamed_last_run"),
renamed_to = MO_lookup[which(MO_lookup$mo == result_mo), "fullname"][1],
mo = result_mo,
stringsAsFactors = FALSE)
fullname <- getOption("mo_renamed_last_run")
options(mo_renamed_last_run = NULL)
renamed_to <- MO_lookup[match(result_mo, MO_lookup$mo), "fullname", drop = TRUE][1]
} else {
df <- data.frame(uncertainty = uncertainty_level,
input = input,
fullname = MO_lookup[which(MO_lookup$mo == result_mo), "fullname"][1],
renamed_to = NA_character_,
mo = result_mo,
stringsAsFactors = FALSE)
fullname <- MO_lookup[match(result_mo, MO_lookup$mo), "fullname", drop = TRUE][1]
renamed_to <- NA_character_
}
df
data.frame(uncertainty = uncertainty_level,
input = input,
fullname = fullname,
renamed_to = renamed_to,
mo = result_mo,
# save max 25 entries
candidates = if (length(candidates) > 1) paste(candidates[c(2:min(25, length(candidates)))], collapse = ", ") else "",
stringsAsFactors = FALSE)
}
# will be exported using s3_register() in R/zzz.R
@ -1714,13 +1729,27 @@ print.mo_uncertainties <- function(x, ...) {
colour1 <- font_red
colour2 <- function(...) font_red_bg(font_white(...))
}
if (x[i, "candidates"] != "") {
candidates <- unlist(strsplit(x[i, "candidates"], ", ", fixed = TRUE))
scores <- finding_score(x[i, "input"], candidates)
# sort on descending scores
candidates <- candidates[order(1 - scores)]
candidates <- paste0(font_italic(candidates, collapse = NULL),
" (", trimws(percentage(scores[order(1 - scores)], digits = 1)), ")")
candidates <- paste(candidates, collapse = ", ")
# align with input after arrow
candidates <- paste0("\n", strrep(" ", nchar(x[i, "input"]) + 12), "Other: ", candidates)
} else {
candidates <- ""
}
msg <- paste(msg,
paste0(colour2(paste0(" [", x[i, "uncertainty"], "] ")), ' "', x[i, "input"], '" -> ',
colour1(paste0(font_italic(x[i, "fullname"]),
ifelse(!is.na(x[i, "renamed_to"]), paste(", renamed to", font_italic(x[i, "renamed_to"])), ""),
" (", x[i, "mo"],
", score: ", percentage(levenshtein_fraction(x[i, "input"], x[i, "fullname"]), digits = 1),
")"))),
", score: ", trimws(percentage(finding_score(x[i, "input"], x[i, "fullname"]), digits = 1)),
")")),
candidates),
sep = "\n")
}
cat(msg)
@ -1729,7 +1758,7 @@ print.mo_uncertainties <- function(x, ...) {
#' @rdname as.mo
#' @export
mo_renamed <- function() {
items <- getOption("mo_renamed")
items <- getOption("mo_renamed", default = NULL)
if (is.null(items)) {
items <- data.frame()
} else {
@ -1805,15 +1834,25 @@ load_mo_failures_uncertainties_renamed <- function(metadata) {
options("mo_renamed" = metadata$renamed)
}
levenshtein_fraction <- function(input, output) {
finding_score <- function(input, output) {
# output is always a valid fullname
levenshtein <- double(length = length(input))
if (length(output) == 1) {
output <- rep(output, length(input))
}
if (length(input) == 1) {
input <- rep(input, length(output))
}
for (i in seq_len(length(input))) {
# determine Levenshtein distance, but maximise to nchar of output
levenshtein[i] <- min(as.double(utils::adist(input[i], output[i], ignore.case = TRUE)),
nchar(output[i]))
nchar(output[i]))
}
# self-made score between 0 and 1 (for % certainty, so 0 means huge distance, 1 means no distance)
(nchar(output) - 0.5 * levenshtein) / nchar(output)
dist <- (nchar(output) - 0.5 * levenshtein) / nchar(output)
index_in_MO_lookup <- tryCatch((nrow(MO_lookup) - match(output, MO_lookup$fullname)) / nrow(MO_lookup),
error = function(e) rep(1, length(output)))
dist * index_in_MO_lookup
}
trimws2 <- function(x) {

@ -755,7 +755,7 @@ summary.rsi <- function(object, ...) {
#' @method plot rsi
#' @export
#' @importFrom graphics text axis
#' @noRd
#' @rdname plot
plot.rsi <- function(x,
lwd = 2,
ylim = NULL,
@ -812,7 +812,7 @@ plot.rsi <- function(x,
#' @method barplot rsi
#' @export
#' @importFrom graphics barplot axis par
#' @noRd
#' @rdname plot
barplot.rsi <- function(height,
col = c("chartreuse4", "chartreuse3", "brown3"),
xlab = ifelse(beside, "Antimicrobial Interpretation", ""),

@ -63,13 +63,18 @@
#' mo_name("CoNS", language = "pt")
#' #> "Staphylococcus coagulase negativo (CoNS)"
get_locale <- function() {
# AMR versions prior to 1.3.0 used the environmental variable:
if (!identical("", Sys.getenv("AMR_locale"))) {
options(AMR_locale = Sys.getenv("AMR_locale"))
}
if (!is.null(getOption("AMR_locale", default = NULL))) {
if (!language %in% LANGUAGES_SUPPORTED) {
stop_("unsupported language: '", language, "' - use one of: ",
paste0("'", LANGUAGES_SUPPORTED, "'", collapse = ", "),
call = FALSE)
lang <- getOption("AMR_locale")
if (lang %in% LANGUAGES_SUPPORTED) {
return(lang)
} else {
return(getOption("AMR_locale"))
stop_("unsupported language: '", lang, "' - use one of: ",
paste0("'", LANGUAGES_SUPPORTED, "'", collapse = ", "))
}
}

@ -32,8 +32,9 @@
value = sort(c("en", unique(translations_file$lang))),
envir = asNamespace("AMR"))
# support for tibble headers (type_sum) and tibble columns content (pillar_shaft)
# without the need to depend on other packages
# support for tibble headers (type_sum) and tibble columns content (pillar_shaft) without the need to depend on other packages
# this was suggested by the developers of the vctrs package:
# https://github.com/r-lib/vctrs/blob/05968ce8e669f73213e3e894b5f4424af4f46316/R/register-s3.R
s3_register("pillar::pillar_shaft", "ab")
s3_register("tibble::type_sum", "ab")
s3_register("pillar::pillar_shaft", "mo")

@ -138,6 +138,7 @@ reference:
- "`as.mic`"
- "`as.disk`"
- "`eucast_rules`"
- "`plot`"
- title: "Analysing data: antimicrobial resistance"
desc: >

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

@ -168,7 +168,8 @@ data %>%
left_join(ip_tbl, by = c("ipaddress" = "ip")) %>%
group_by(country = countrycode::countrycode(country,
origin = 'iso2c',
destination = 'country.name')) %>%
destination = 'country.name',
custom_match = c(XK = "Kosovo"))) %>%
summarise(first = min(timestamp_server)) %>%
arrange(desc(first)) %>%
mutate(frame = case_when(first <= as.POSIXct("2019-06-30") ~ "Q1-Q2 2019",

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

@ -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.3.0.9015</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9016</span>
</span>
</div>

@ -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.3.0.9015</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9016</span>
</span>
</div>

@ -39,7 +39,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.3.0.9015</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9016</span>
</span>
</div>
@ -226,22 +226,82 @@
<span class="fu"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"VISA"</span>), <span class="co"># Vancomycin Intermediate S. aureus</span>
<span class="fu"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"VRSA"</span>), <span class="co"># Vancomycin Resistant S. aureus</span>
times = <span class="fl">10</span>)
<span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span>
<span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span>
<span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span>
<span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span>
<span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span>
<span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="fu"><a href="https://rdrr.io/r/base/print.html">print</a></span>(<span class="kw">S.aureus</span>, unit = <span class="st">"ms"</span>, signif = <span class="fl">2</span>)
<span class="co"># Unit: milliseconds</span>
<span class="co"># expr min lq mean median uq max</span>
<span class="co"># as.mo("sau") 12.0 12.0 24.0 15.0 40.0 43.0</span>
<span class="co"># as.mo("stau") 170.0 170.0 190.0 180.0 210.0 250.0</span>
<span class="co"># as.mo("STAU") 160.0 180.0 200.0 190.0 220.0 230.0</span>
<span class="co"># as.mo("staaur") 9.4 11.0 21.0 13.0 40.0 48.0</span>
<span class="co"># as.mo("STAAUR") 9.0 13.0 34.0 14.0 43.0 140.0</span>
<span class="co"># as.mo("S. aureus") 16.0 18.0 20.0 19.0 21.0 25.0</span>
<span class="co"># as.mo("S aureus") 15.0 16.0 20.0 18.0 21.0 39.0</span>
<span class="co"># as.mo("Staphylococcus aureus") 1.1 1.1 1.4 1.6 1.6 1.7</span>
<span class="co"># as.mo("Staphylococcus aureus (MRSA)") 870.0 920.0 950.0 940.0 980.0 1000.0</span>
<span class="co"># as.mo("Sthafilokkockus aaureuz") 390.0 410.0 440.0 440.0 460.0 490.0</span>
<span class="co"># as.mo("MRSA") 11.0 12.0 30.0 13.0 40.0 130.0</span>
<span class="co"># as.mo("VISA") 16.0 18.0 30.0 20.0 46.0 69.0</span>
<span class="co"># as.mo("VRSA") 14.0 19.0 33.0 33.0 47.0 51.0</span>
<span class="co"># expr min lq mean median uq max</span>
<span class="co"># as.mo("sau") 9.9 13.0 24.0 17.0 39.0 45</span>
<span class="co"># as.mo("stau") 200.0 210.0 240.0 240.0 260.0 290</span>
<span class="co"># as.mo("STAU") 190.0 220.0 230.0 220.0 260.0 270</span>
<span class="co"># as.mo("staaur") 9.4 13.0 26.0 15.0 44.0 47</span>
<span class="co"># as.mo("STAAUR") 9.3 11.0 18.0 14.0 15.0 45</span>
<span class="co"># as.mo("S. aureus") 21.0 25.0 30.0 26.0 26.0 50</span>
<span class="co"># as.mo("S aureus") 25.0 47.0 48.0 51.0 56.0 64</span>
<span class="co"># as.mo("Staphylococcus aureus") 1.5 1.9 2.3 2.4 2.5 3</span>
<span class="co"># as.mo("Staphylococcus aureus (MRSA)") 860.0 900.0 930.0 920.0 950.0 1100</span>
<span class="co"># as.mo("Sthafilokkockus aaureuz") 410.0 420.0 430.0 430.0 450.0 460</span>
<span class="co"># as.mo("MRSA") 12.0 13.0 16.0 14.0 15.0 41</span>
<span class="co"># as.mo("VISA") 15.0 21.0 38.0 22.0 47.0 130</span>
<span class="co"># as.mo("VRSA") 18.0 20.0 25.0 22.0 22.0 47</span>
<span class="co"># neval</span>
<span class="co"># 10</span>
<span class="co"># 10</span>
@ -286,9 +346,9 @@
<span class="fu"><a href="https://rdrr.io/r/base/print.html">print</a></span>(<span class="kw">run_it</span>, unit = <span class="st">"ms"</span>, signif = <span class="fl">3</span>)
<span class="co"># Unit: milliseconds</span>
<span class="co"># expr min lq mean median uq max neval</span>
<span class="co"># mo_name(x) 90.3 101 120 102 141 202 10</span>
<span class="co"># mo_name(x) 96.1 123 140 133 144 251 10</span>
</pre></div>
<p>So getting official taxonomic names of 2,000,000 (!!) items consisting of 90 unique values only takes 0.102 seconds. You only lose time on your unique input values.</p>
<p>So getting official taxonomic names of 2,000,000 (!!) items consisting of 90 unique values only takes 0.133 seconds. You only lose time on your unique input values.</p>
</div>
<div id="precalculated-results" class="section level3">
<h3 class="hasAnchor">
@ -299,14 +359,24 @@
B = <span class="fu"><a href="../reference/mo_property.html">mo_name</a></span>(<span class="st">"S. aureus"</span>),
C = <span class="fu"><a href="../reference/mo_property.html">mo_name</a></span>(<span class="st">"Staphylococcus aureus"</span>),
times = <span class="fl">10</span>)
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="co"># Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.</span>
<span class="fu"><a href="https://rdrr.io/r/base/print.html">print</a></span>(<span class="kw">run_it</span>, unit = <span class="st">"ms"</span>, signif = <span class="fl">3</span>)
<span class="co"># Unit: milliseconds</span>
<span class="co"># expr min lq mean median uq max neval</span>
<span class="co"># A 7.08 7.29 8.00 8.25 8.49 9.22 10</span>
<span class="co"># B 12.30 13.50 14.20 14.50 14.70 14.80 10</span>
<span class="co"># C 2.14 2.26 7.35 2.38 2.51 52.30 10</span>
<span class="co"># A 7.83 7.96 8.19 8.22 8.33 8.84 10</span>
<span class="co"># B 18.10 19.50 27.80 20.20 20.70 65.90 10</span>
<span class="co"># C 1.77 2.11 2.34 2.27 2.33 3.22 10</span>
</pre></div>
<p>So going from <code><a href="../reference/mo_property.html">mo_name("Staphylococcus aureus")</a></code> to <code>"Staphylococcus aureus"</code> takes 0.0024 seconds - it doesnt even start calculating <em>if the result would be the same as the expected resulting value</em>. That goes for all helper functions:</p>
<p>So going from <code><a href="../reference/mo_property.html">mo_name("Staphylococcus aureus")</a></code> to <code>"Staphylococcus aureus"</code> takes 0.0023 seconds - it doesnt even start calculating <em>if the result would be the same as the expected resulting value</em>. That goes for all helper functions:</p>
<div class="sourceCode" id="cb5"><pre class="downlit">
<span class="kw">run_it</span> <span class="op">&lt;-</span> <span class="fu">microbenchmark</span>(A = <span class="fu"><a href="../reference/mo_property.html">mo_species</a></span>(<span class="st">"aureus"</span>),
B = <span class="fu"><a href="../reference/mo_property.html">mo_genus</a></span>(<span class="st">"Staphylococcus"</span>),
@ -320,14 +390,14 @@
<span class="fu"><a href="https://rdrr.io/r/base/print.html">print</a></span>(<span class="kw">run_it</span>, unit = <span class="st">"ms"</span>, signif = <span class="fl">3</span>)
<span class="co"># Unit: milliseconds</span>
<span class="co"># expr min lq mean median uq max neval</span>
<span class="co"># A 1.29 1.38 1.64 1.47 1.84 2.28 10</span>
<span class="co"># B 1.27 1.62 1.76 1.69 1.82 2.71 10</span>
<span class="co"># C 1.28 1.32 1.56 1.48 1.77 2.09 10</span>
<span class="co"># D 1.29 1.46 1.68 1.66 1.77 2.24 10</span>
<span class="co"># E 1.26 1.39 5.34 1.64 1.77 39.00 10</span>
<span class="co"># F 1.26 1.33 1.58 1.44 1.80 2.14 10</span>
<span class="co"># G 1.32 1.51 1.65 1.68 1.75 2.05 10</span>
<span class="co"># H 1.31 1.43 1.71 1.68 1.86 2.49 10</span>
<span class="co"># A 1.56 1.62 5.61 1.93 2.26 38.90 10</span>
<span class="co"># B 1.50 1.72 1.88 1.90 2.01 2.34 10</span>
<span class="co"># C 1.52 1.76 1.88 1.89 1.96 2.27 10</span>
<span class="co"># D 1.47 1.62 1.85 1.86 1.89 2.80 10</span>
<span class="co"># E 1.51 1.84 1.98 1.88 2.07 2.56 10</span>
<span class="co"># F 1.44 1.50 1.68 1.57 1.89 2.19 10</span>
<span class="co"># G 1.47 1.48 1.65 1.59 1.84 2.00 10</span>
<span class="co"># H 1.55 1.60 1.75 1.69 1.81 2.34 10</span>
</pre></div>
<p>Of course, when running <code><a href="../reference/mo_property.html">mo_phylum("Firmicutes")</a></code> the function has zero knowledge about the actual microorganism, namely <em>S. aureus</em>. But since the result would be <code>"Firmicutes"</code> anyway, there is no point in calculating the result. And because this package knows all phyla of all known bacteria (according to the Catalogue of Life), it can just return the initial value immediately.</p>
</div>
@ -356,13 +426,13 @@
<span class="fu"><a href="https://rdrr.io/r/base/print.html">print</a></span>(<span class="kw">run_it</span>, unit = <span class="st">"ms"</span>, signif = <span class="fl">4</span>)
<span class="co"># Unit: milliseconds</span>
<span class="co"># expr min lq mean median uq max neval</span>
<span class="co"># en 13.29 13.54 17.53 13.70 14.93 58.25 100</span>
<span class="co"># de 14.25 14.46 19.09 14.69 16.23 58.96 100</span>
<span class="co"># nl 17.89 18.46 24.37 19.05 21.14 70.25 100</span>
<span class="co"># es 14.05 14.41 18.08 14.72 16.11 57.07 100</span>
<span class="co"># it 14.07 14.38 19.18 14.63 16.40 58.14 100</span>
<span class="co"># fr 13.98 14.42 17.30 14.57 15.31 56.81 100</span>
<span class="co"># pt 13.95 14.38 17.78 14.60 16.32 57.53 100</span>
<span class="co"># en 13.84 14.04 20.10 14.54 16.47 59.20 100</span>
<span class="co"># de 14.79 15.10 20.00 15.76 17.64 63.37 100</span>
<span class="co"># nl 18.52 19.35 24.11 21.44 22.93 62.12 100</span>
<span class="co"># es 14.72 15.02 20.10 16.06 17.90 60.60 100</span>
<span class="co"># it 14.61 14.93 18.06 15.45 17.33 52.47 100</span>
<span class="co"># fr 14.73 15.02 21.06 15.62 18.09 69.54 100</span>
<span class="co"># pt 14.74 14.99 21.19 16.17 17.88 64.71 100</span>
</pre></div>
<p>Currently supported are German, Dutch, Spanish, Italian, French and Portuguese.</p>
</div>

Binary file not shown.

Before

Width:  |  Height:  |  Size: 87 KiB

After

Width:  |  Height:  |  Size: 88 KiB

@ -39,7 +39,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.3.0.9015</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9016</span>
</span>
</div>
@ -210,7 +210,7 @@ If you are reading this page from within R, please <a href="https://msberends.gi
<a href="#microorganisms-currently-accepted-names" class="anchor"></a>Microorganisms (currently accepted names)</h2>
<p>A data set with 67,151 rows and 16 columns, containing the following column names:<br><em>mo, fullname, kingdom, phylum, class, order, family, genus, species, subspecies, rank, ref, species_id, source, prevalence, snomed</em>.</p>
<p>This data set is in R available as <code>microorganisms</code>, after you load the <code>AMR</code> package.</p>
<p>It was last updated on 1 September 2020 11:07:11 CEST. Find more info about the structure of this data set <a href="https://msberends.github.io/AMR/reference/microorganisms.html">here</a>.</p>
<p>It was last updated on 3 September 2020 20:59:45 CEST. Find more info about the structure of this data set <a href="https://msberends.github.io/AMR/reference/microorganisms.html">here</a>.</p>
<p><strong>Direct download links:</strong><br><a class="dataset-download-button" href="https://github.com/msberends/AMR/raw/master/data-raw/../data-raw/microorganisms.rds" target="_blank"><img src="download_rds.png" width="50px" title="2.7 MB"></a><a class="dataset-download-button" href="https://github.com/msberends/AMR/raw/master/data-raw/../data-raw/microorganisms.xlsx" target="_blank"><img src="download_xlsx.png" width="50px" title="6.1 MB"></a><a class="dataset-download-button" href="https://github.com/msberends/AMR/raw/master/data-raw/../data-raw/microorganisms.txt" target="_blank"><img src="download_txt.png" width="50px" title="13.3 MB"></a><a class="dataset-download-button" href="https://github.com/msberends/AMR/raw/master/data-raw/../data-raw/microorganisms.sas" target="_blank"><img src="download_sas.png" width="50px" title="26.2 MB"></a><a class="dataset-download-button" href="https://github.com/msberends/AMR/raw/master/data-raw/../data-raw/microorganisms.sav" target="_blank"><img src="download_sav.png" width="50px" title="28.2 MB"></a><a class="dataset-download-button" href="https://github.com/msberends/AMR/raw/master/data-raw/../data-raw/microorganisms.dta" target="_blank"><img src="download_dta.png" width="50px" title="25.2 MB"></a></p>
<div id="source" class="section level3">
<h3 class="hasAnchor">

@ -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.3.0.9015</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9016</span>
</span>
</div>

@ -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.3.0.9015</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9016</span>
</span>
</div>

Binary file not shown.

Before

Width:  |  Height:  |  Size: 60 KiB

After

Width:  |  Height:  |  Size: 60 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 1.4 MiB

After

Width:  |  Height:  |  Size: 1.4 MiB

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

@ -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.3.0.9015</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9016</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-1309015" class="section level1">
<h1 class="page-header" data-toc-text="1.3.0.9015">
<a href="#amr-1309015" class="anchor"></a>AMR 1.3.0.9015<small> Unreleased </small>
<div id="amr-1309016" class="section level1">
<h1 class="page-header" data-toc-text="1.3.0.9016">
<a href="#amr-1309016" class="anchor"></a>AMR 1.3.0.9016<small> Unreleased </small>
</h1>
<div id="last-updated-3-september-2020" class="section level2">
<div id="last-updated-12-september-2020" class="section level2">
<h2 class="hasAnchor">
<a href="#last-updated-3-september-2020" class="anchor"></a><small>Last updated: 3 September 2020</small>
<a href="#last-updated-12-september-2020" class="anchor"></a><small>Last updated: 12 September 2020</small>
</h2>
<p>Note: some changes in this version were suggested by anonymous reviewers from the journal we submitted our manuscipt to. We are those reviewers very grateful for going through our code so thoroughly!</p>
<div id="new" class="section level3">
@ -299,6 +299,7 @@
<li>
<p>Improvements for <code><a href="../reference/as.mo.html">as.mo()</a></code>:</p>
<ul>
<li>Any user input value that could mean more than one taxonomic entry is now considered uncertain. Instead of a warning, a message will be thrown and the accompanying <code><a href="../reference/as.mo.html">mo_uncertainties()</a></code> has been changed completely; it now prints all possible candidates with their score.</li>
<li>Big speed improvement for already valid microorganism ID. This also means an significant speed improvement for using <code>mo_*</code> functions like <code><a href="../reference/mo_property.html">mo_name()</a></code> on microoganism IDs.</li>
<li>Added parameter <code>ignore_pattern</code> to <code><a href="../reference/as.mo.html">as.mo()</a></code> which can also be given to <code>mo_*</code> functions like <code><a href="../reference/mo_property.html">mo_name()</a></code>, to exclude known non-relevant input from analysing. This can also be set with the option <code>AMR_ignore_pattern</code>.</li>
</ul>
@ -310,6 +311,7 @@
<li><p>BORSA is now recognised as an abbreviation for <em>Staphylococcus aureus</em>, meaning that e.g. <code><a href="../reference/mo_property.html">mo_genus("BORSA")</a></code> will return “Staphylococcus”</p></li>
<li><p>Added a feature from AMR 1.1.0 and earlier again, but now without other package dependencies: <code>tibble</code> printing support for classes <code>&lt;rsi&gt;</code>, <code>&lt;mic&gt;</code>, <code>&lt;disk&gt;</code>, <code>&lt;ab&gt;</code> and <code>&lt;mo&gt;</code>. When using <code>tibble</code>s containing antimicrobial columns (class <code>&lt;rsi&gt;</code>), “S” will print in green, “I” will print in yellow and “R” will print in red. Microbial IDs (class <code>&lt;mo&gt;</code>) will emphasise on the genus and species, not on the kingdom.</p></li>
<li><p>Names of antiviral agents in data set <code>antivirals</code> now have a starting capital letter, like it is the case in the <code>antibiotics</code> data set</p></li>
<li><p>Updated the documentation of the <code>WHONET</code> data set to clarify that all patient names are fictitious</p></li>
</ul>
</div>
<div id="other" class="section level3">
@ -961,7 +963,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<li>Fixed bug where not all old taxonomic names would be printed, when using a vector as input for <code><a href="../reference/as.mo.html">as.mo()</a></code>
</li>
<li>Manually added <em>Trichomonas vaginalis</em> from the kingdom of Protozoa, which is missing from the Catalogue of Life</li>
<li>Small improvements to <code><a href="https://rdrr.io/r/graphics/plot.default.html">plot()</a></code> and <code><a href="https://rdrr.io/r/graphics/barplot.html">barplot()</a></code> for MIC and RSI classes</li>
<li>Small improvements to <code><a href="../reference/plot.html">plot()</a></code> and <code><a href="https://rdrr.io/r/graphics/barplot.html">barplot()</a></code> for MIC and RSI classes</li>
<li>Allow Catalogue of Life IDs to be coerced by <code><a href="../reference/as.mo.html">as.mo()</a></code>
</li>
</ul>
@ -1169,10 +1171,10 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<li><p>New function <code><a href="../reference/age.html">age()</a></code> to calculate the (patients) age in years</p></li>
<li><p>New function <code><a href="../reference/age_groups.html">age_groups()</a></code> to split ages into custom or predefined groups (like children or elderly). This allows for easier demographic antimicrobial resistance analysis per age group.</p></li>
<li>
<p>New function <code><a href="../reference/resistance_predict.html">ggplot_rsi_predict()</a></code> as well as the base R <code><a href="https://rdrr.io/r/graphics/plot.default.html">plot()</a></code> function can now be used for resistance prediction calculated with <code><a href="../reference/resistance_predict.html">resistance_predict()</a></code>:</p>
<p>New function <code><a href="../reference/resistance_predict.html">ggplot_rsi_predict()</a></code> as well as the base R <code><a href="../reference/plot.html">plot()</a></code> function can now be used for resistance prediction calculated with <code><a href="../reference/resistance_predict.html">resistance_predict()</a></code>:</p>
<div class="sourceCode" id="cb24"><pre class="downlit">
<span class="kw">x</span> <span class="op">&lt;-</span> <span class="fu"><a href="../reference/resistance_predict.html">resistance_predict</a></span>(<span class="kw">septic_patients</span>, col_ab = <span class="st">"amox"</span>)
<span class="fu"><a href="https://rdrr.io/r/graphics/plot.default.html">plot</a></span>(<span class="kw">x</span>)
<span class="fu"><a href="../reference/plot.html">plot</a></span>(<span class="kw">x</span>)
<span class="fu"><a href="../reference/resistance_predict.html">ggplot_rsi_predict</a></span>(<span class="kw">x</span>)
</pre></div>
</li>

@ -2,7 +2,7 @@ pandoc: 2.7.3
pkgdown: 1.5.1.9000
pkgdown_sha: eae56f08694abebf93cdfc0dd8e9ede06d8c815f
articles: []
last_built: 2020-09-03T18:57Z
last_built: 2020-09-12T06:48Z
urls:
reference: https://msberends.github.io/AMR/reference
article: https://msberends.github.io/AMR/articles

@ -49,7 +49,7 @@
<script src="../extra.js"></script>
<meta property="og:title" content="Data set with 500 isolates - WHONET example — WHONET" />
<meta property="og:description" content="This example data set has the exact same structure as an export file from WHONET. Such files can be used with this package, as this example data set shows. The antibiotic results are based on our example_isolates data set. All patient names are created using online surname generators and are only in place for practice purposes." />
<meta property="og:description" content="This example data set has the exact same structure as an export file from WHONET. Such files can be used with this package, as this example data set shows. The antibiotic results are from our example_isolates data set. All patient names are created using online surname generators and are only in place for practice purposes." />
<meta property="og:image" content="https://msberends.github.io/AMR/logo.svg" />
@ -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.3.0.9015</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9016</span>
</span>
</div>
@ -239,7 +239,7 @@
</div>
<div class="ref-description">
<p>This example data set has the exact same structure as an export file from WHONET. Such files can be used with this package, as this example data set shows. The antibiotic results are based on our <a href='example_isolates.html'>example_isolates</a> data set. All patient names are created using online surname generators and are only in place for practice purposes.</p>
<p>This example data set has the exact same structure as an export file from WHONET. Such files can be used with this package, as this example data set shows. The antibiotic results are from our <a href='example_isolates.html'>example_isolates</a> data set. All patient names are created using online surname generators and are only in place for practice purposes.</p>
</div>
<pre class="usage"><span class='kw'>WHONET</span></pre>

@ -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.3.0.9015</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9016</span>
</span>
</div>
@ -384,7 +384,8 @@ The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>stable</s
<span class='fu'>ab_atc</span>(<span class='st'>"ceftriaxon"</span>)
<span class='fu'>ab_atc</span>(<span class='st'>"cephtriaxone"</span>)
<span class='fu'>ab_atc</span>(<span class='st'>"cephthriaxone"</span>)
<span class='fu'>ab_atc</span>(<span class='st'>"seephthriaaksone"</span>)</pre>
<span class='fu'>ab_atc</span>(<span class='st'>"seephthriaaksone"</span>)
</pre>
</div>
<div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar">
<nav id="toc" data-toggle="toc" class="sticky-top">

@ -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.3.0.9015</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9016</span>
</span>
</div>
@ -344,7 +344,8 @@ This package contains <strong>all ~550 antibiotic, antimycotic and antiviral dru
<span class='co'># use ab_* functions to get a specific properties (see ?ab_property);</span>
<span class='co'># they use as.ab() internally:</span>
<span class='fu'><a href='ab_property.html'>ab_name</a></span>(<span class='st'>"J01FA01"</span>) <span class='co'># "Erythromycin"</span>
<span class='fu'><a href='ab_property.html'>ab_name</a></span>(<span class='st'>"eryt"</span>) <span class='co'># "Erythromycin"</span></pre>
<span class='fu'><a href='ab_property.html'>ab_name</a></span>(<span class='st'>"eryt"</span>) <span class='co'># "Erythromycin"</span>
</pre>
</div>
<div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar">
<nav id="toc" data-toggle="toc" class="sticky-top">

@ -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.3.0.9015</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9016</span>
</span>
</div>
@ -300,7 +300,8 @@ The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>stable</s
guideline = <span class='st'>"EUCAST"</span>)
<span class='fu'><a href='as.rsi.html'>as.rsi</a></span>(<span class='kw'>df</span>)
}</pre>
}
</pre>
</div>
<div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar">
<nav id="toc" data-toggle="toc" class="sticky-top">

@ -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.3.0.9015</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9016</span>
</span>
</div>
@ -298,8 +298,9 @@ The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>stable</s
ab = <span class='st'>"AMX"</span>,
guideline = <span class='st'>"EUCAST"</span>)
<span class='fu'><a href='https://rdrr.io/r/graphics/plot.default.html'>plot</a></span>(<span class='kw'>mic_data</span>)
<span class='fu'><a href='https://rdrr.io/r/graphics/barplot.html'>barplot</a></span>(<span class='kw'>mic_data</span>)</pre>
<span class='fu'><a href='plot.html'>plot</a></span>(<span class='kw'>mic_data</span>)
<span class='fu'><a href='https://rdrr.io/r/graphics/barplot.html'>barplot</a></span>(<span class='kw'>mic_data</span>)
</pre>
</div>
<div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar">
<nav id="toc" data-toggle="toc" class="sticky-top">

@ -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.3.0.9015</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9016</span>
</span>
</div>
@ -347,7 +347,7 @@
</ul>
<p>There are three helper functions that can be run after using the <code>as.mo()</code> function:</p><ul>
<li><p>Use <code>mo_uncertainties()</code> to get a <code><a href='https://rdrr.io/r/base/data.frame.html'>data.frame</a></code> with all values that were coerced to a valid value, but with uncertainty. The output contains a score, that is calculated as \((n - 0.5 * L) / n\), where <em>n</em> is the number of characters of the full taxonomic name of the microorganism, and <em>L</em> is the <a href='https://en.wikipedia.org/wiki/Levenshtein_distance'>Levenshtein distance</a> between that full name and the user input.</p></li>
<li><p>Use <code>mo_uncertainties()</code> to get a <code><a href='https://rdrr.io/r/base/data.frame.html'>data.frame</a></code> that prints in a pretty format with all taxonomic names that were guessed. The output contains a score that is based on the human pathogenic prevalence and the <a href='https://en.wikipedia.org/wiki/Levenshtein_distance'>Levenshtein distance</a> between the full taxonomic name and the user input.</p></li>
<li><p>Use <code>mo_failures()</code> to get a <code><a href='https://rdrr.io/r/base/character.html'>character</a></code> <code><a href='https://rdrr.io/r/base/vector.html'>vector</a></code> with all values that could not be coerced to a valid value.</p></li>
<li><p>Use <code>mo_renamed()</code> to get a <code><a href='https://rdrr.io/r/base/data.frame.html'>data.frame</a></code> with all values that could be coerced based on old, previously accepted taxonomic names.</p></li>
</ul>
@ -456,7 +456,8 @@ This package contains the complete taxonomic tree of almost all microorganisms (
<span class='co'># although this works easier and does the same:</span>
<span class='kw'>df</span> <span class='op'>&lt;-</span> <span class='kw'>df</span> <span class='op'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/mutate.html'>mutate</a></span>(mo = <span class='fu'>as.mo</span>(<span class='fu'><a href='https://rdrr.io/r/base/paste.html'>paste</a></span>(<span class='kw'>genus</span>, <span class='kw'>species</span>)))
}</pre>
}
</pre>
</div>
<div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar">
<nav id="toc" data-toggle="toc" class="sticky-top">

@ -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.3.0.9015</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.3.0.9016</span>
</span>
</div>
@ -340,12 +340,14 @@
<li><p>For <strong>cleaning raw / untransformed data</strong>. The data will be cleaned to only contain values S, I and R and will try its best to determine this with some intelligence. For example, mixed values with R/SI interpretations and MIC values such as <code>"&lt;0.25; S"</code> will be coerced to <code>"S"</code>. Combined interpretations for multiple test methods (as seen in laboratory records) such as <code>"S; S"</code> will be coerced to <code>"S"</code>, but a value like <code>"S; I"</code> will return <code>NA</code> with a warning that the input is unclear.</p></li>
<li><p>For <strong>interpreting minimum inhibitory concentration (MIC) values</strong> according to EUCAST or CLSI. You must clean your MIC values first using <code><a href='as.mic.html'>as.mic()</a></code>, that also gives your columns the new data class <code><a href='as.mic.html'>mic</a></code>. Also, be sure to have a column with microorganism names or codes. It will be found automatically, but can be set manually using the <code>mo</code> parameter.</p><ul>
<li><p>Using <code>dplyr</code>, R/SI interpretation can be done very easily with either:</p><pre><span class='kw'>your_data</span> <span class='op'>%&gt;%</span> <span class='fu'><a href='https://dplyr.tidyverse.org/reference/mutate_all.html'>mutate_if</a></span>(<span class='kw'>is.mic</span>, <span class='kw'>as.rsi</span>) <span class='co'># until dplyr 1.0.0</span>
<span class='kw'>your_data</span> <span class='op'>%&gt;%</span> <span class='fu'><a href='https://dplyr.tidyverse.org/reference/mutate.html'>mutate</a></span>(<span class='fu'><a href='https://dplyr.tidyverse.org/reference/across.html'>across</a></span>(<span class='fu'>where</span>(<span class='kw'>is.mic</span>), <span class='kw'>as.rsi</span>)) <span class='co'># since dplyr 1.0.0</span></pre></li>
<span class='kw'>your_data</span> <span class='op'>%&gt;%</span> <span class='fu'><a href='https://dplyr.tidyverse.org/reference/mutate.html'>mutate</a></span>(<span class='fu'><a href='https://dplyr.tidyverse.org/reference/across.html'>across</a></span>(<span class='fu'>where</span>(<span class='kw'>is.mic</span>), <span class='kw'>as.rsi</span>)) <span class='co'># since dplyr 1.0.0</span>
</pre></li>
<li><p>Operators like "&lt;=" will be stripped before interpretation. When using <code>conserve_capped_values = TRUE</code>, an MIC value of e.g. "&gt;2" will always return "R", even if the breakpoint according to the chosen guideline is "&gt;=4". This is to prevent that capped values from raw laboratory data would not be treated conservatively. The default behaviour (<code>conserve_capped_values = FALSE</code>) considers "&gt;2" to be lower than "&gt;=4" and might in this case return "S" or "I".</p></li>
</ul></li>
<li><p>For <strong>interpreting disk diffusion diameters</strong> according to EUCAST or CLSI. You must clean your disk zones first using <code><a href='as.disk.html'>as.disk()</a></code>, that also gives your columns the new data class <code><a href='as.disk.html'>disk</a></code>. Also, be sure to have a column with microorganism names or codes. It will be found automatically, but can be set manually using the <code>mo</code> parameter.</p><ul>
<li><p>Using <code>dplyr</code>, R/SI interpretation can be done very easily with either:</p><pre><span class='kw'>your_data</span> <span class='op'>%&gt;%</span> <span class='fu'><a href='https://dplyr.tidyverse.org/reference/mutate_all.html'>mutate_if</a></span>(<span class='kw'>is.disk</span>, <span class='kw'>as.rsi</span>) <span class='co'># until dplyr 1.0.0</span>
<span class='kw'>your_data</span> <span class='op'>%&gt;%</span> <span class='fu'><a href='https://dplyr.tidyverse.org/reference/mutate.html'>mutate</a></span>(<span class='fu'><a href='https://dplyr.tidyverse.org/reference/across.html'>across</a></span>(<span class='fu'>where</span>(<span class='kw'>is.disk</span>), <span class='kw'>as.rsi</span>)) <span class='co'># since dplyr 1.0.0</span></pre></li>
<span class='kw'>your_data</span> <span class='op'>%&gt;%</span> <span class='fu'><a href='https://dplyr.tidyverse.org/reference/mutate.html'>mutate</a></span>(<span class='fu'><a href='https://dplyr.tidyverse.org/reference/across.html'>across</a></span>(<span class='fu'>where</span>(<span class='kw'>is.disk</span>), <span class='kw'>as.rsi</span>)) <span class='co'># since dplyr 1.0.0</span>
</pre></li>
</ul></li>
<li><p>For <strong>interpreting a complete data set</strong>, with automatic determination of MIC values, disk diffusion diameters, microorganism names or codes, and antimicrobial test results. This is done very simply by running <code>as.rsi(data)</code>.</p></li>
</ol>