`) 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
diff --git a/R/aa_helper_functions.R b/R/aa_helper_functions.R
index 94449983..27124309 100755
--- a/R/aa_helper_functions.R
+++ b/R/aa_helper_functions.R
@@ -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)
diff --git a/R/amr.R b/R/amr.R
index aa0ff9df..6836fa5e 100644
--- a/R/amr.R
+++ b/R/amr.R
@@ -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
diff --git a/R/data.R b/R/data.R
index 4e3cb375..ba40b439 100755
--- a/R/data.R
+++ b/R/data.R
@@ -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
diff --git a/R/mic.R b/R/mic.R
index 79e571b4..1cb55136 100755
--- a/R/mic.R
+++ b/R/mic.R
@@ -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",
diff --git a/R/mo.R b/R/mo.R
index 747a7f04..b0700fda 100755
--- a/R/mo.R
+++ b/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) {
diff --git a/R/rsi.R b/R/rsi.R
index 549fad89..245d6d5e 100755
--- a/R/rsi.R
+++ b/R/rsi.R
@@ -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", ""),
diff --git a/R/translate.R b/R/translate.R
index ca1d255d..daf9410f 100755
--- a/R/translate.R
+++ b/R/translate.R
@@ -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 = ", "))
}
}
diff --git a/R/zzz.R b/R/zzz.R
index d298ee5d..c51a4c58 100755
--- a/R/zzz.R
+++ b/R/zzz.R
@@ -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")
diff --git a/_pkgdown.yml b/_pkgdown.yml
index e1219603..125002b9 100644
--- a/_pkgdown.yml
+++ b/_pkgdown.yml
@@ -138,6 +138,7 @@ reference:
- "`as.mic`"
- "`as.disk`"
- "`eucast_rules`"
+ - "`plot`"
- title: "Analysing data: antimicrobial resistance"
desc: >
diff --git a/data-raw/antibiotics.dta b/data-raw/antibiotics.dta
index e67a7a99..776d4ea9 100644
Binary files a/data-raw/antibiotics.dta and b/data-raw/antibiotics.dta differ
diff --git a/data-raw/antibiotics.sas b/data-raw/antibiotics.sas
index 5f4aeb0a..c1900173 100644
Binary files a/data-raw/antibiotics.sas and b/data-raw/antibiotics.sas differ
diff --git a/data-raw/antibiotics.sav b/data-raw/antibiotics.sav
index d797056f..3c580d16 100644
Binary files a/data-raw/antibiotics.sav and b/data-raw/antibiotics.sav differ
diff --git a/data-raw/antibiotics.xlsx b/data-raw/antibiotics.xlsx
index ea96de58..529a4caf 100644
Binary files a/data-raw/antibiotics.xlsx and b/data-raw/antibiotics.xlsx differ
diff --git a/data-raw/antivirals.dta b/data-raw/antivirals.dta
index 5a850d13..221d01ce 100644
Binary files a/data-raw/antivirals.dta and b/data-raw/antivirals.dta differ
diff --git a/data-raw/antivirals.sas b/data-raw/antivirals.sas
index 436a75ad..faa7fe33 100644
Binary files a/data-raw/antivirals.sas and b/data-raw/antivirals.sas differ
diff --git a/data-raw/antivirals.sav b/data-raw/antivirals.sav
index 6a57eba7..24ba37ab 100644
Binary files a/data-raw/antivirals.sav and b/data-raw/antivirals.sav differ
diff --git a/data-raw/antivirals.xlsx b/data-raw/antivirals.xlsx
index 19478cf3..06c1c5a8 100644
Binary files a/data-raw/antivirals.xlsx and b/data-raw/antivirals.xlsx differ
diff --git a/data-raw/country_analysis.R b/data-raw/country_analysis.R
index f25f8ea4..d4a0cdc8 100644
--- a/data-raw/country_analysis.R
+++ b/data-raw/country_analysis.R
@@ -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",
diff --git a/data-raw/intrinsic_resistant.dta b/data-raw/intrinsic_resistant.dta
index 2d9cec0a..33908d00 100644
Binary files a/data-raw/intrinsic_resistant.dta and b/data-raw/intrinsic_resistant.dta differ
diff --git a/data-raw/intrinsic_resistant.sas b/data-raw/intrinsic_resistant.sas
index b652469d..158bd444 100644
Binary files a/data-raw/intrinsic_resistant.sas and b/data-raw/intrinsic_resistant.sas differ
diff --git a/data-raw/intrinsic_resistant.sav b/data-raw/intrinsic_resistant.sav
index 75b9e9d0..1e3109fb 100644
Binary files a/data-raw/intrinsic_resistant.sav and b/data-raw/intrinsic_resistant.sav differ
diff --git a/data-raw/intrinsic_resistant.xlsx b/data-raw/intrinsic_resistant.xlsx
index 39aba4d8..910424fc 100644
Binary files a/data-raw/intrinsic_resistant.xlsx and b/data-raw/intrinsic_resistant.xlsx differ
diff --git a/data-raw/microorganisms.dta b/data-raw/microorganisms.dta
index 72619ea9..68f139dc 100644
Binary files a/data-raw/microorganisms.dta and b/data-raw/microorganisms.dta differ
diff --git a/data-raw/microorganisms.old.dta b/data-raw/microorganisms.old.dta
index 519118cb..ad04a5e4 100644
Binary files a/data-raw/microorganisms.old.dta and b/data-raw/microorganisms.old.dta differ
diff --git a/data-raw/microorganisms.old.sas b/data-raw/microorganisms.old.sas
index 12d3927f..b16aa247 100644
Binary files a/data-raw/microorganisms.old.sas and b/data-raw/microorganisms.old.sas differ
diff --git a/data-raw/microorganisms.old.sav b/data-raw/microorganisms.old.sav
index 8c66c83b..03f45ada 100644
Binary files a/data-raw/microorganisms.old.sav and b/data-raw/microorganisms.old.sav differ
diff --git a/data-raw/microorganisms.old.xlsx b/data-raw/microorganisms.old.xlsx
index 32065953..4f7bc5dc 100644
Binary files a/data-raw/microorganisms.old.xlsx and b/data-raw/microorganisms.old.xlsx differ
diff --git a/data-raw/microorganisms.sas b/data-raw/microorganisms.sas
index 8877096e..991e1fa5 100644
Binary files a/data-raw/microorganisms.sas and b/data-raw/microorganisms.sas differ
diff --git a/data-raw/microorganisms.sav b/data-raw/microorganisms.sav
index f7055613..90b895ba 100644
Binary files a/data-raw/microorganisms.sav and b/data-raw/microorganisms.sav differ
diff --git a/data-raw/microorganisms.xlsx b/data-raw/microorganisms.xlsx
index 0ce89ed2..afe20d7d 100644
Binary files a/data-raw/microorganisms.xlsx and b/data-raw/microorganisms.xlsx differ
diff --git a/data-raw/rsi_translation.dta b/data-raw/rsi_translation.dta
index bb374afd..2b01fec7 100644
Binary files a/data-raw/rsi_translation.dta and b/data-raw/rsi_translation.dta differ
diff --git a/data-raw/rsi_translation.sas b/data-raw/rsi_translation.sas
index e8f3f3d2..56f71cc9 100644
Binary files a/data-raw/rsi_translation.sas and b/data-raw/rsi_translation.sas differ
diff --git a/data-raw/rsi_translation.sav b/data-raw/rsi_translation.sav
index d4c4224d..f7808452 100644
Binary files a/data-raw/rsi_translation.sav and b/data-raw/rsi_translation.sav differ
diff --git a/data-raw/rsi_translation.xlsx b/data-raw/rsi_translation.xlsx
index 1d502a81..5f1a0549 100644
Binary files a/data-raw/rsi_translation.xlsx and b/data-raw/rsi_translation.xlsx differ
diff --git a/docs/404.html b/docs/404.html
index afc17ed6..1287c7c6 100644
--- a/docs/404.html
+++ b/docs/404.html
@@ -81,7 +81,7 @@
AMR (for R)
- 1.3.0.9015
+ 1.3.0.9016
diff --git a/docs/LICENSE-text.html b/docs/LICENSE-text.html
index 0bac0325..e167677e 100644
--- a/docs/LICENSE-text.html
+++ b/docs/LICENSE-text.html
@@ -81,7 +81,7 @@
AMR (for R)
- 1.3.0.9015
+ 1.3.0.9016
diff --git a/docs/articles/benchmarks.html b/docs/articles/benchmarks.html
index 3322982a..fd384788 100644
--- a/docs/articles/benchmarks.html
+++ b/docs/articles/benchmarks.html
@@ -39,7 +39,7 @@
AMR (for R)
- 1.3.0.9015
+ 1.3.0.9016
@@ -226,22 +226,82 @@
as.mo("VISA"), # Vancomycin Intermediate S. aureus
as.mo("VRSA"), # Vancomycin Resistant S. aureus
times = 10)
+# Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.
+# Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.
+# Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.
+# Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.
+# Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.
+# Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Results of three values were guessed with uncertainty. Use mo_uncertainties() to review them.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
print(S.aureus, unit = "ms", signif = 2)
# Unit: milliseconds
-# expr min lq mean median uq max
-# as.mo("sau") 12.0 12.0 24.0 15.0 40.0 43.0
-# as.mo("stau") 170.0 170.0 190.0 180.0 210.0 250.0
-# as.mo("STAU") 160.0 180.0 200.0 190.0 220.0 230.0
-# as.mo("staaur") 9.4 11.0 21.0 13.0 40.0 48.0
-# as.mo("STAAUR") 9.0 13.0 34.0 14.0 43.0 140.0
-# as.mo("S. aureus") 16.0 18.0 20.0 19.0 21.0 25.0
-# as.mo("S aureus") 15.0 16.0 20.0 18.0 21.0 39.0
-# as.mo("Staphylococcus aureus") 1.1 1.1 1.4 1.6 1.6 1.7
-# as.mo("Staphylococcus aureus (MRSA)") 870.0 920.0 950.0 940.0 980.0 1000.0
-# as.mo("Sthafilokkockus aaureuz") 390.0 410.0 440.0 440.0 460.0 490.0
-# as.mo("MRSA") 11.0 12.0 30.0 13.0 40.0 130.0
-# as.mo("VISA") 16.0 18.0 30.0 20.0 46.0 69.0
-# as.mo("VRSA") 14.0 19.0 33.0 33.0 47.0 51.0
+# expr min lq mean median uq max
+# as.mo("sau") 9.9 13.0 24.0 17.0 39.0 45
+# as.mo("stau") 200.0 210.0 240.0 240.0 260.0 290
+# as.mo("STAU") 190.0 220.0 230.0 220.0 260.0 270
+# as.mo("staaur") 9.4 13.0 26.0 15.0 44.0 47
+# as.mo("STAAUR") 9.3 11.0 18.0 14.0 15.0 45
+# as.mo("S. aureus") 21.0 25.0 30.0 26.0 26.0 50
+# as.mo("S aureus") 25.0 47.0 48.0 51.0 56.0 64
+# as.mo("Staphylococcus aureus") 1.5 1.9 2.3 2.4 2.5 3
+# as.mo("Staphylococcus aureus (MRSA)") 860.0 900.0 930.0 920.0 950.0 1100
+# as.mo("Sthafilokkockus aaureuz") 410.0 420.0 430.0 430.0 450.0 460
+# as.mo("MRSA") 12.0 13.0 16.0 14.0 15.0 41
+# as.mo("VISA") 15.0 21.0 38.0 22.0 47.0 130
+# as.mo("VRSA") 18.0 20.0 25.0 22.0 22.0 47
# neval
# 10
# 10
@@ -286,9 +346,9 @@
print(run_it, unit = "ms", signif = 3)
# Unit: milliseconds
# expr min lq mean median uq max neval
-# mo_name(x) 90.3 101 120 102 141 202 10
+# mo_name(x) 96.1 123 140 133 144 251 10
-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.
+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.
@@ -299,14 +359,24 @@
B = mo_name("S. aureus"),
C = mo_name("Staphylococcus aureus"),
times = 10)
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
+# Result of one value was guessed with uncertainty. Use mo_uncertainties() to review it.
print(run_it, unit = "ms", signif = 3)
# Unit: milliseconds
# expr min lq mean median uq max neval
-# A 7.08 7.29 8.00 8.25 8.49 9.22 10
-# B 12.30 13.50 14.20 14.50 14.70 14.80 10
-# C 2.14 2.26 7.35 2.38 2.51 52.30 10
+# A 7.83 7.96 8.19 8.22 8.33 8.84 10
+# B 18.10 19.50 27.80 20.20 20.70 65.90 10
+# C 1.77 2.11 2.34 2.27 2.33 3.22 10
-So going from mo_name("Staphylococcus aureus")
to "Staphylococcus aureus"
takes 0.0024 seconds - it doesn’t even start calculating if the result would be the same as the expected resulting value. That goes for all helper functions:
+So going from mo_name("Staphylococcus aureus")
to "Staphylococcus aureus"
takes 0.0023 seconds - it doesn’t even start calculating if the result would be the same as the expected resulting value. That goes for all helper functions:
run_it <- microbenchmark(A = mo_species("aureus"),
B = mo_genus("Staphylococcus"),
@@ -320,14 +390,14 @@
print(run_it, unit = "ms", signif = 3)
# Unit: milliseconds
# expr min lq mean median uq max neval
-# A 1.29 1.38 1.64 1.47 1.84 2.28 10
-# B 1.27 1.62 1.76 1.69 1.82 2.71 10
-# C 1.28 1.32 1.56 1.48 1.77 2.09 10
-# D 1.29 1.46 1.68 1.66 1.77 2.24 10
-# E 1.26 1.39 5.34 1.64 1.77 39.00 10
-# F 1.26 1.33 1.58 1.44 1.80 2.14 10
-# G 1.32 1.51 1.65 1.68 1.75 2.05 10
-# H 1.31 1.43 1.71 1.68 1.86 2.49 10
+# A 1.56 1.62 5.61 1.93 2.26 38.90 10
+# B 1.50 1.72 1.88 1.90 2.01 2.34 10
+# C 1.52 1.76 1.88 1.89 1.96 2.27 10
+# D 1.47 1.62 1.85 1.86 1.89 2.80 10
+# E 1.51 1.84 1.98 1.88 2.07 2.56 10
+# F 1.44 1.50 1.68 1.57 1.89 2.19 10
+# G 1.47 1.48 1.65 1.59 1.84 2.00 10
+# H 1.55 1.60 1.75 1.69 1.81 2.34 10
Of course, when running mo_phylum("Firmicutes")
the function has zero knowledge about the actual microorganism, namely S. aureus. But since the result would be "Firmicutes"
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.
@@ -356,13 +426,13 @@
print(run_it, unit = "ms", signif = 4)
# Unit: milliseconds
# expr min lq mean median uq max neval
-# en 13.29 13.54 17.53 13.70 14.93 58.25 100
-# de 14.25 14.46 19.09 14.69 16.23 58.96 100
-# nl 17.89 18.46 24.37 19.05 21.14 70.25 100
-# es 14.05 14.41 18.08 14.72 16.11 57.07 100
-# it 14.07 14.38 19.18 14.63 16.40 58.14 100
-# fr 13.98 14.42 17.30 14.57 15.31 56.81 100
-# pt 13.95 14.38 17.78 14.60 16.32 57.53 100
+# en 13.84 14.04 20.10 14.54 16.47 59.20 100
+# de 14.79 15.10 20.00 15.76 17.64 63.37 100
+# nl 18.52 19.35 24.11 21.44 22.93 62.12 100
+# es 14.72 15.02 20.10 16.06 17.90 60.60 100
+# it 14.61 14.93 18.06 15.45 17.33 52.47 100
+# fr 14.73 15.02 21.06 15.62 18.09 69.54 100
+# pt 14.74 14.99 21.19 16.17 17.88 64.71 100
Currently supported are German, Dutch, Spanish, Italian, French and Portuguese.
diff --git a/docs/articles/benchmarks_files/figure-html/unnamed-chunk-4-1.png b/docs/articles/benchmarks_files/figure-html/unnamed-chunk-4-1.png
index e7d07072..a4b97b1a 100644
Binary files a/docs/articles/benchmarks_files/figure-html/unnamed-chunk-4-1.png and b/docs/articles/benchmarks_files/figure-html/unnamed-chunk-4-1.png differ
diff --git a/docs/articles/datasets.html b/docs/articles/datasets.html
index 523cffbd..71c5bdc7 100644
--- a/docs/articles/datasets.html
+++ b/docs/articles/datasets.html
@@ -39,7 +39,7 @@
AMR (for R)
- 1.3.0.9015
+ 1.3.0.9016
@@ -210,7 +210,7 @@ If you are reading this page from within R, please Microorganisms (currently accepted names)
A data set with 67,151 rows and 16 columns, containing the following column names:
‘mo’, ‘fullname’, ‘kingdom’, ‘phylum’, ‘class’, ‘order’, ‘family’, ‘genus’, ‘species’, ‘subspecies’, ‘rank’, ‘ref’, ‘species_id’, ‘source’, ‘prevalence’, ‘snomed’.
This data set is in R available as microorganisms
, after you load the AMR
package.
-It was last updated on 1 September 2020 11:07:11 CEST. Find more info about the structure of this data set here.
+It was last updated on 3 September 2020 20:59:45 CEST. Find more info about the structure of this data set here.
Direct download links:
diff --git a/docs/articles/index.html b/docs/articles/index.html
index 73a7e909..8ded3898 100644
--- a/docs/articles/index.html
+++ b/docs/articles/index.html
@@ -81,7 +81,7 @@
AMR (for R)
- 1.3.0.9015
+ 1.3.0.9016
diff --git a/docs/authors.html b/docs/authors.html
index baeb0492..e5db534d 100644
--- a/docs/authors.html
+++ b/docs/authors.html
@@ -81,7 +81,7 @@
AMR (for R)
- 1.3.0.9015
+ 1.3.0.9016
diff --git a/docs/countries.png b/docs/countries.png
index 12d05988..c65919ce 100644
Binary files a/docs/countries.png and b/docs/countries.png differ
diff --git a/docs/countries_large.png b/docs/countries_large.png
index 3ddd6ed3..b3e95cf1 100644
Binary files a/docs/countries_large.png and b/docs/countries_large.png differ
diff --git a/docs/index.html b/docs/index.html
index edca0938..85eef5eb 100644
--- a/docs/index.html
+++ b/docs/index.html
@@ -43,7 +43,7 @@
AMR (for R)
- 1.3.0.9015
+ 1.3.0.9016
diff --git a/docs/news/index.html b/docs/news/index.html
index 8c06acb1..f1acb44a 100644
--- a/docs/news/index.html
+++ b/docs/news/index.html
@@ -81,7 +81,7 @@
AMR (for R)
- 1.3.0.9015
+ 1.3.0.9016
@@ -236,13 +236,13 @@
Source: NEWS.md
-
-
@@ -300,7 +300,8 @@ The lifecycle of this function is stable"EUCAST")
as.rsi(df)
-}
+}
+
@@ -298,8 +298,9 @@ The lifecycle of this function is stable"AMX",
guideline = "EUCAST")
-plot(mic_data)
-barplot(mic_data)
+plot(mic_data)
+barplot(mic_data)
+
@@ -347,7 +347,7 @@
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 \((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 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 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.
@@ -456,7 +456,8 @@ This package contains the complete taxonomic tree of almost all microorganisms (
# although this works easier and does the same:
df <- df %>%
mutate(mo = as.mo(paste(genus, species)))
-}
+}
+
@@ -340,12 +340,14 @@
For cleaning raw / untransformed data. 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 "<0.25; S"
will be coerced to "S"
. Combined interpretations for multiple test methods (as seen in laboratory records) such as "S; S"
will be coerced to "S"
, but a value like "S; I"
will return NA
with a warning that the input is unclear.
For interpreting minimum inhibitory concentration (MIC) values according to EUCAST or CLSI. You must clean your MIC values first using as.mic()
, that also gives your columns the new data class mic
. Also, be sure to have a column with microorganism names or codes. It will be found automatically, but can be set manually using the mo
parameter.
Using dplyr
, R/SI interpretation can be done very easily with either:
your_data %>% mutate_if(is.mic, as.rsi) # until dplyr 1.0.0
-your_data %>% mutate(across(where(is.mic), as.rsi)) # since dplyr 1.0.0
+your_data %>% mutate(across(where(is.mic), as.rsi)) # since dplyr 1.0.0
+
Operators like "<=" will be stripped before interpretation. When using conserve_capped_values = TRUE
, an MIC value of e.g. ">2" will always return "R", even if the breakpoint according to the chosen guideline is ">=4". This is to prevent that capped values from raw laboratory data would not be treated conservatively. The default behaviour (conserve_capped_values = FALSE
) considers ">2" to be lower than ">=4" and might in this case return "S" or "I".
For interpreting disk diffusion diameters according to EUCAST or CLSI. You must clean your disk zones first using as.disk()
, that also gives your columns the new data class disk
. Also, be sure to have a column with microorganism names or codes. It will be found automatically, but can be set manually using the mo
parameter.
Using dplyr
, R/SI interpretation can be done very easily with either:
your_data %>% mutate_if(is.disk, as.rsi) # until dplyr 1.0.0
-your_data %>% mutate(across(where(is.disk), as.rsi)) # since dplyr 1.0.0
+your_data %>% mutate(across(where(is.disk), as.rsi)) # since dplyr 1.0.0
+
For interpreting a complete data set, with automatic determination of MIC values, disk diffusion diameters, microorganism names or codes, and antimicrobial test results. This is done very simply by running as.rsi(data)
.
@@ -468,7 +470,7 @@ The lifecycle of this function is stablersi_data <- as.rsi(c(rep("S", 474), rep("I", 36), rep("R", 370)))
is.rsi(rsi_data)
-plot(rsi_data) # for percentages
+plot(rsi_data) # for percentages
barplot(rsi_data) # for frequencies
if (FALSE) {
@@ -487,7 +489,8 @@ The lifecycle of this function is stable# default threshold of `is.rsi.eligible` is 5%.
is.rsi.eligible(WHONET$`First name`) # fails, >80% is invalid
is.rsi.eligible(WHONET$`First name`, threshold = 0.99) # succeeds
-}
+}
+
@@ -333,7 +333,8 @@ The lifecycle of this function is stable# [2] "ANTIBACTERIALS FOR SYSTEMIC USE"
# [3] "BETA-LACTAM ANTIBACTERIALS, PENICILLINS"
# [4] "Penicillins with extended spectrum"
-}
+}
+
@@ -355,7 +355,8 @@ The lifecycle of this function is stablefunction(x) ifelse(x == as.mo("E. coli"),
"E. coli",
"Others"))
-# }
+# }
+
@@ -444,6 +444,12 @@
eucast_rules()
Apply EUCAST rules |
+
+
+
+ plot(<mic>) barplot(<mic>) plot(<rsi>) barplot(<rsi>)
+ |
+ Plotting for classes rsi and disk |
diff --git a/docs/reference/like.html b/docs/reference/like.html
index c9fb0aac..e7122de8 100644
--- a/docs/reference/like.html
+++ b/docs/reference/like.html
@@ -82,7 +82,7 @@
AMR (for R)
- 1.3.0.9015
+ 1.3.0.9016
@@ -317,7 +317,8 @@ The lifecycle of this function is stablelibrary(dplyr)
example_isolates %>%
filter(mo_name(mo) %like% "^ent")
-}
+}
+
diff --git a/docs/reference/mo_property.html b/docs/reference/mo_property.html
index 6aa53b02..94e59775 100644
--- a/docs/reference/mo_property.html
+++ b/docs/reference/mo_property.html
@@ -82,7 +82,7 @@
AMR (for R)
- 1.3.0.9015
+ 1.3.0.9016
@@ -461,7 +461,8 @@ This package contains the complete taxonomic tree of almost all microorganisms (
mo_taxonomy("E. coli")
# get a list with the taxonomy, the authors, Gram-stain and URL to the online database
mo_info("E. coli")
-# }
+# }
+
@@ -291,7 +291,8 @@ The lifecycle of this function is stable# Portuguese
mo_name("CoNS", language = "pt")
-#> "Staphylococcus coagulase negativo (CoNS)"
+#> "Staphylococcus coagulase negativo (CoNS)"
+
diff --git a/man/WHONET.Rd b/man/WHONET.Rd
index ebd34b80..ce4104d8 100644
--- a/man/WHONET.Rd
+++ b/man/WHONET.Rd
@@ -39,7 +39,7 @@ A \code{\link{data.frame}} with 500 observations and 53 variables:
WHONET
}
\description{
-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 \link{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 \link{example_isolates} data set. All patient names are created using online surname generators and are only in place for practice purposes.
}
\section{Reference data publicly available}{
diff --git a/man/as.mo.Rd b/man/as.mo.Rd
index 9571edbc..5090f54b 100644
--- a/man/as.mo.Rd
+++ b/man/as.mo.Rd
@@ -106,7 +106,7 @@ With the default setting (\code{allow_uncertain = TRUE}, level 2), below example
There are three helper functions that can be run after using the \code{\link[=as.mo]{as.mo()}} function:
\itemize{
-\item Use \code{\link[=mo_uncertainties]{mo_uncertainties()}} to get a \code{\link{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 \emph{n} is the number of characters of the full taxonomic name of the microorganism, and \emph{L} is the \href{https://en.wikipedia.org/wiki/Levenshtein_distance}{Levenshtein distance} between that full name and the user input.
+\item Use \code{\link[=mo_uncertainties]{mo_uncertainties()}} to get a \code{\link{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 \href{https://en.wikipedia.org/wiki/Levenshtein_distance}{Levenshtein distance} between the full taxonomic name and the user input.
\item Use \code{\link[=mo_failures]{mo_failures()}} to get a \code{\link{character}} \code{\link{vector}} with all values that could not be coerced to a valid value.
\item Use \code{\link[=mo_renamed]{mo_renamed()}} to get a \code{\link{data.frame}} with all values that could be coerced based on old, previously accepted taxonomic names.
}
diff --git a/man/plot.Rd b/man/plot.Rd
new file mode 100644
index 00000000..e5ca5816
--- /dev/null
+++ b/man/plot.Rd
@@ -0,0 +1,104 @@
+% Generated by roxygen2: do not edit by hand
+% Please edit documentation in R/amr.R, R/mic.R, R/rsi.R
+\name{plot}
+\alias{plot}
+\alias{plot.mic}
+\alias{barplot.mic}
+\alias{plot.rsi}
+\alias{barplot.rsi}
+\title{Plotting for classes \code{rsi} and \code{disk}}
+\usage{
+\method{plot}{mic}(
+ x,
+ main = paste("MIC values of", deparse(substitute(x))),
+ ylab = "Frequency",
+ xlab = "MIC value",
+ axes = FALSE,
+ ...
+)
+
+\method{barplot}{mic}(
+ height,
+ main = paste("MIC values of", deparse(substitute(height))),
+ ylab = "Frequency",
+ xlab = "MIC value",
+ axes = FALSE,
+ ...
+)
+
+\method{plot}{rsi}(
+ x,
+ lwd = 2,
+ ylim = NULL,
+ ylab = "Percentage",
+ xlab = "Antimicrobial Interpretation",
+ main = paste("Resistance Overview of", deparse(substitute(x))),
+ axes = FALSE,
+ ...
+)
+
+\method{barplot}{rsi}(
+ height,
+ col = c("chartreuse4", "chartreuse3", "brown3"),
+ xlab = ifelse(beside, "Antimicrobial Interpretation", ""),
+ main = paste("Resistance Overview of", deparse(substitute(height))),
+ ylab = "Frequency",
+ beside = TRUE,
+ axes = beside,
+ ...
+)
+}
+\arguments{
+\item{x}{the coordinates of points in the plot. Alternatively, a
+ single plotting structure, function or \emph{any \R object with a
+ \code{plot} method} can be provided.}
+
+\item{main}{overall and sub title for the plot.}
+
+\item{ylab}{a label for the y axis.}
+
+\item{xlab}{a label for the x axis.}
+
+\item{axes}{logical. If \code{TRUE}, a vertical (or horizontal, if
+ \code{horiz} is true) axis is drawn.}
+
+\item{...}{Parameters passed on to functions}
+
+\item{height}{either a vector or matrix of values describing the
+ bars which make up the plot. If \code{height} is a vector, the
+ plot consists of a sequence of rectangular bars with heights
+ given by the values in the vector. If \code{height} is a matrix
+ and \code{beside} is \code{FALSE} then each bar of the plot
+ corresponds to a column of \code{height}, with the values in the
+ column giving the heights of stacked sub-bars making up the
+ bar. If \code{height} is a matrix and \code{beside} is
+ \code{TRUE}, then the values in each column are juxtaposed
+ rather than stacked.}
+
+\item{ylim}{limits for the y axis.}
+
+\item{col}{a vector of colors for the bars or bar components.
+ By default, grey is used if \code{height} is a vector, and a
+ gamma-corrected grey palette if \code{height} is a matrix.}
+
+\item{beside}{a logical value. If \code{FALSE}, the columns of
+ \code{height} are portrayed as stacked bars, and if \code{TRUE}
+ the columns are portrayed as juxtaposed bars.}
+}
+\description{
+Functions to print classes of the \code{AMR} package.
+}
+\section{Stable lifecycle}{
+
+\if{html}{\figure{lifecycle_stable.svg}{options: style=margin-bottom:5px} \cr}
+The \link[=lifecycle]{lifecycle} of this function is \strong{stable}. In a stable function, major changes are unlikely. This means that the unlying code will generally evolve by adding new arguments; removing arguments or changing the meaning of existing arguments will be avoided.
+
+If the unlying code needs breaking changes, they will occur gradually. For example, a parameter will be deprecated and first continue to work, but will emit an message informing you of the change. Next, typically after at least one newly released version on CRAN, the message will be transformed to an error.
+}
+
+\section{Read more on our website!}{
+
+On our website \url{https://msberends.github.io/AMR} you can find \href{https://msberends.github.io/AMR/articles/AMR.html}{a comprehensive tutorial} about how to conduct AMR analysis, the \href{https://msberends.github.io/AMR/reference}{complete documentation of all functions} (which reads a lot easier than here in R) and \href{https://msberends.github.io/AMR/articles/WHONET.html}{an example analysis using WHONET data}. As we would like to better understand the backgrounds and needs of our users, please \href{https://msberends.github.io/AMR/survey.html}{participate in our survey}!
+}
+
+\keyword{internal}
diff --git a/pkgdown/logos/countries.png b/pkgdown/logos/countries.png
index 12d05988..c65919ce 100644
Binary files a/pkgdown/logos/countries.png and b/pkgdown/logos/countries.png differ
diff --git a/pkgdown/logos/countries_large.png b/pkgdown/logos/countries_large.png
index 3ddd6ed3..b3e95cf1 100644
Binary files a/pkgdown/logos/countries_large.png and b/pkgdown/logos/countries_large.png differ
diff --git a/tests/testthat/test-mo.R b/tests/testthat/test-mo.R
index 61790de7..f5542a5b 100644
--- a/tests/testthat/test-mo.R
+++ b/tests/testthat/test-mo.R
@@ -201,12 +201,12 @@ test_that("as.mo works", {
print(mo_renamed())
# check uncertain names
- expect_equal(suppressWarnings(as.character(as.mo("staaur extratest", allow_uncertain = TRUE))), "B_STPHY_AURS")
+ expect_equal(suppressMessages(as.character(as.mo("staaur extratest", allow_uncertain = TRUE))), "B_STPHY_AURS")
expect_equal(suppressWarnings(as.character(as.mo("staaur extratest", allow_uncertain = FALSE))), "UNKNOWN")
- expect_warning(as.mo("esco extra_text", allow_uncertain = TRUE))
- expect_equal(suppressWarnings(as.character(as.mo("unexisting aureus", allow_uncertain = 3))), "B_STPHY_AURS")
- expect_equal(suppressWarnings(as.character(as.mo("unexisting staphy", allow_uncertain = 3))), "B_STPHY")
- expect_equal(suppressWarnings(as.character(as.mo("Staphylococcus aureus unexisting", allow_uncertain = 3))), "B_STPHY_AURS")
+ expect_message(as.mo("e coli extra_text", allow_uncertain = TRUE))
+ expect_equal(suppressMessages(as.character(as.mo("unexisting aureus", allow_uncertain = 3))), "B_STPHY_AURS")
+ expect_equal(suppressMessages(as.character(as.mo("unexisting staphy", allow_uncertain = 3))), "B_STPHY")
+ expect_equal(suppressMessages(as.character(as.mo("Staphylococcus aureus unexisting", allow_uncertain = 3))), "B_STPHY_AURS")
# predefined reference_df
expect_equal(as.character(as.mo("TestingOwnID",