Compare commits

...

2 Commits

59 changed files with 1592 additions and 1252 deletions

View File

@ -22,7 +22,6 @@
^data-raw$
^\.lintr$
^tests/testthat/_snaps$
^vignettes/AMR.Rmd$
^vignettes/benchmarks.Rmd$
^vignettes/EUCAST.Rmd$
^vignettes/PCA.Rmd$

View File

@ -1,6 +1,6 @@
Package: AMR
Version: 1.5.0.9024
Date: 2021-02-22
Version: 1.5.0.9026
Date: 2021-02-25
Title: Antimicrobial Resistance Data Analysis
Authors@R: c(
person(role = c("aut", "cre"),

View File

@ -32,6 +32,7 @@ S3method(as.rsi,data.frame)
S3method(as.rsi,default)
S3method(as.rsi,disk)
S3method(as.rsi,mic)
S3method(barplot,disk)
S3method(barplot,mic)
S3method(barplot,rsi)
S3method(c,ab)
@ -242,7 +243,8 @@ export(theme_rsi)
importFrom(graphics,arrows)
importFrom(graphics,axis)
importFrom(graphics,barplot)
importFrom(graphics,par)
importFrom(graphics,legend)
importFrom(graphics,mtext)
importFrom(graphics,plot)
importFrom(graphics,points)
importFrom(graphics,text)

10
NEWS.md
View File

@ -1,5 +1,5 @@
# AMR 1.5.0.9024
## <small>Last updated: 22 February 2021</small>
# AMR 1.5.0.9026
## <small>Last updated: 25 February 2021</small>
### New
* Support for EUCAST Clinical Breakpoints v11.0 (2021), effective in the `eucast_rules()` function and in `as.rsi()` to interpret MIC and disk diffusion values. This is now the default guideline in this package.
@ -23,6 +23,7 @@
```
* Support for custom MDRO guidelines, using the new `custom_mdro_guideline()` function, please see `mdro()` for additional info
* Function `isolate_identifier()`, which will paste a microorganism code with all antimicrobial results of a data set into one string for each row. This is useful to compare isolates, e.g. between institutions or regions, when there is no genotyping available.
* `ggplot()` generics for classes `<mic>` and `<disk>`
* Function `mo_is_yeast()`, which determines whether a microorganism is a member of the taxonomic class Saccharomycetes or the taxonomic order Saccharomycetales:
```r
mo_kingdom(c("Aspergillus", "Candida"))
@ -54,12 +55,15 @@
* `is.rsi.eligible()` now detects if the column name resembles an antibiotic name or code and now returns `TRUE` immediately if the input contains any of the values "R", "S" or "I". This drastically improves speed, also for a lot of other functions that rely on automatic determination of antibiotic columns.
* Functions `get_episode()` and `is_new_episode()` now support less than a day as value for argument `episode_days` (e.g., to include one patient/test per hour)
* Argument `ampc_cephalosporin_resistance` in `eucast_rules()` now also applies to value "I" (not only "S")
* Updated colours of values R, S and I in tibble printing
* Updated `plot()` functions for classes `<mic>`, `<disk>` and `<rsi>` - the former two now support colouring if you supply the microorganism and antimicrobial agent
* Updated colours to colour-blind friendly version for values R, S and I in tibble printing and for all plot methods (`ggplot_rsi()` and using `plot()` on classes `<mic>`, `<disk>` and `<rsi>`)
* Functions `print()` and `summary()` on a Principal Components Analysis object (`pca()`) now print additional group info if the original data was grouped using `dplyr::group_by()`
* Improved speed and reliability of `guess_ab_col()`. As this also internally improves the reliability of `first_isolate()` and `mdro()`, this might have a slight impact on the results of those functions.
* Fix for `mo_name()` when used in other languages than English
* The `like()` function (and its fast alias `%like%`) now always use Perl compatibility, improving speed for many functions in this package (e.g., `as.mo()` is now up to 4 times faster)
* *Staphylococcus cornubiensis* is now correctly categorised as coagulase-positive
* `random_disk()` and `random_mic()` now have an expanded range in their randomisation
* Support for GISA (glycopeptide-intermediate *S. aureus*), so e.g. `mo_genus("GISA")` will return `"Staphylococcus"`
### Other
* Big documentation updates

View File

@ -879,13 +879,16 @@ font_green_bg <- function(..., collapse = " ") {
try_colour(..., before = "\033[42m", after = "\033[49m", collapse = collapse)
}
font_rsi_R_bg <- function(..., collapse = " ") {
try_colour(..., before = "\033[48;5;210m", after = "\033[49m", collapse = collapse)
#ED553B
try_colour(..., before = "\033[48;5;203m", after = "\033[49m", collapse = collapse)
}
font_rsi_S_bg <- function(..., collapse = " ") {
try_colour(..., before = "\033[48;5;113m", after = "\033[49m", collapse = collapse)
#3CAEA3
try_colour(..., before = "\033[48;5;79m", after = "\033[49m", collapse = collapse)
}
font_rsi_I_bg <- function(..., collapse = " ") {
try_colour(..., before = "\033[48;5;185m", after = "\033[49m", collapse = collapse)
#F6D55C
try_colour(..., before = "\033[48;5;222m", after = "\033[49m", collapse = collapse)
}
font_red_bg <- function(..., collapse = " ") {
try_colour(..., before = "\033[41m", after = "\033[49m", collapse = collapse)

13
R/amr.R
View File

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

View File

@ -145,30 +145,6 @@ print.disk <- function(x, ...) {
print(as.integer(x), quote = FALSE)
}
#' @method plot disk
#' @export
#' @importFrom graphics barplot axis
#' @rdname plot
plot.disk <- function(x,
main = paste("Disk zones values of", deparse(substitute(x))),
ylab = "Frequency",
xlab = "Disk diffusion (mm)",
axes = FALSE,
...) {
meet_criteria(main, allow_class = "character", has_length = 1)
meet_criteria(ylab, allow_class = "character", has_length = 1)
meet_criteria(xlab, allow_class = "character", has_length = 1)
meet_criteria(axes, allow_class = "logical", has_length = 1)
barplot(table(x),
ylab = ylab,
xlab = xlab,
axes = axes,
main = main,
...)
axis(2, seq(0, max(table(x))))
}
#' @method [ disk
#' @export
#' @noRd

View File

@ -36,7 +36,8 @@
#' @param facet variable to split plots by, either `"interpretation"` (default) or `"antibiotic"` or a grouping variable
#' @inheritParams proportion
#' @param nrow (when using `facet`) number of rows
#' @param colours a named vector with colours for the bars. The names must be one or more of: S, SI, I, IR, R or be `FALSE` to use default [ggplot2][ggplot2::ggplot()] colours.
#' @param colours a named vector with colours for the bars. The names must be one or more of: S, SI, I, IR, R or be `FALSE` for standard [ggplot2][ggplot2::ggplot()] colours. The default colours are colour-blind friendly, while maintaining the convention that e.g. 'susceptible' should be green and 'resistant' should be red.
#' @param aesthetics aesthetics to apply the colours to, defaults to "fill" but can also be "colour" or "both"
#' @param datalabels show datalabels using [labels_rsi_count()]
#' @param datalabels.size size of the datalabels
#' @param datalabels.colour colour of the datalabels
@ -118,11 +119,6 @@
#' CIP) %>%
#' ggplot_rsi(x = "age_group")
#'
#' # for colourblind mode, use divergent colours from the viridis package:
#' example_isolates %>%
#' select(AMX, NIT, FOS, TMP, CIP) %>%
#' ggplot_rsi() +
#' scale_fill_viridis_d()
#' # a shorter version which also adjusts data label colours:
#' example_isolates %>%
#' select(AMX, NIT, FOS, TMP, CIP) %>%
@ -154,11 +150,11 @@ ggplot_rsi <- function(data,
minimum = 30,
language = get_locale(),
nrow = NULL,
colours = c(S = "#61a8ff",
SI = "#61a8ff",
I = "#61f7ff",
IR = "#ff6961",
R = "#ff6961"),
colours = c(S = "#3CAEA3",
SI = "#3CAEA3",
I = "#F6D55C",
IR = "#ED553B",
R = "#ED553B"),
datalabels = TRUE,
datalabels.size = 2.5,
datalabels.colour = "grey15",
@ -308,17 +304,19 @@ geom_rsi <- function(position = NULL,
x <- "interpretation"
}
ggplot2::layer(geom = "bar", stat = "identity", position = position,
mapping = ggplot2::aes_string(x = x, y = y, fill = fill),
params = list(...), data = function(x) {
rsi_df(data = x,
translate_ab = translate_ab,
language = language,
minimum = minimum,
combine_SI = combine_SI,
combine_IR = combine_IR)
})
ggplot2::geom_col(
data = function(x) {
rsi_df(data = x,
translate_ab = translate_ab,
language = language,
minimum = minimum,
combine_SI = combine_SI,
combine_IR = combine_IR)
},
mapping = ggplot2::aes_string(x = x, y = y, fill = fill),
position = position,
...
)
}
#' @rdname ggplot_rsi
@ -364,25 +362,27 @@ scale_y_percent <- function(breaks = seq(0, 1, 0.1), limits = NULL) {
#' @rdname ggplot_rsi
#' @export
scale_rsi_colours <- function(colours = c(S = "#61a8ff",
SI = "#61a8ff",
I = "#61f7ff",
IR = "#ff6961",
R = "#ff6961")) {
scale_rsi_colours <- function(colours = c(S = "#3CAEA3",
SI = "#3CAEA3",
I = "#F6D55C",
IR = "#ED553B",
R = "#ED553B"),
aesthetics = "fill") {
stop_ifnot_installed("ggplot2")
meet_criteria(colours, allow_class = c("character", "logical"))
# previous colour: palette = "RdYlGn"
# previous colours: values = c("#b22222", "#ae9c20", "#7cfc00")
meet_criteria(aesthetics, allow_class = c("character"), has_length = c(1, 2), is_in = c("colour", "color", "fill", "both"))
if (!identical(colours, FALSE)) {
original_cols <- c(S = "#61a8ff",
SI = "#61a8ff",
I = "#61f7ff",
IR = "#ff6961",
R = "#ff6961")
if ("both" %in% aesthetics) {
aesthetics <- c("colour", "fill")
}
original_cols <- c(S = "#3CAEA3",
SI = "#3CAEA3",
I = "#F6D55C",
IR = "#ED553B",
R = "#ED553B")
colours <- replace(original_cols, names(colours), colours)
ggplot2::scale_fill_manual(values = colours)
ggplot2::scale_fill_manual(values = colours, aesthetics = aesthetics)
}
}

View File

@ -33,7 +33,10 @@ globalVariables(c(".rowid",
"atc_group1",
"atc_group2",
"code",
"cols",
"count",
"data",
"disk",
"dosage",
"dose",
"dose_times",
@ -52,6 +55,7 @@ globalVariables(c(".rowid",
"language",
"lookup",
"method",
"mic ",
"microorganism",
"microorganisms",
"microorganisms.codes",
@ -67,8 +71,8 @@ globalVariables(c(".rowid",
"reference.rule",
"reference.rule_group",
"reference.version",
"rsi_translation",
"rowid",
"rsi_translation",
"rule_group",
"rule_name",
"se_max",

View File

@ -25,7 +25,7 @@
#' Pattern Matching with Keyboard Shortcut
#'
#' Convenient wrapper around [grep()] to match a pattern: `x %like% pattern`. It always returns a [`logical`] vector and is always case-insensitive (use `x %like_case% pattern` for case-sensitive matching). Also, `pattern` can be as long as `x` to compare items of each index in both vectors, or they both can have the same length to iterate over all cases.
#' Convenient wrapper around [grepl()] to match a pattern: `x %like% pattern`. It always returns a [`logical`] vector and is always case-insensitive (use `x %like_case% pattern` for case-sensitive matching). Also, `pattern` can be as long as `x` to compare items of each index in both vectors, or they both can have the same length to iterate over all cases.
#' @inheritSection lifecycle Stable Lifecycle
#' @param x a character vector where matches are sought, or an object which can be coerced by [as.character()] to a character vector.
#' @param pattern a character string containing a regular expression (or [character] string for `fixed = TRUE`) to be matched in the given character vector. Coerced by [as.character()] to a character string if possible. If a [character] vector of length 2 or more is supplied, the first element is used with a warning.
@ -43,7 +43,7 @@
#'
#' Using RStudio? The text `%like%` can also be directly inserted in your code from the Addins menu and can have its own Keyboard Shortcut like `Ctrl+Shift+L` or `Cmd+Shift+L` (see `Tools` > `Modify Keyboard Shortcuts...`).
#' @source Idea from the [`like` function from the `data.table` package](https://github.com/Rdatatable/data.table/blob/master/R/like.R)
#' @seealso [grep()]
#' @seealso [grepl()]
#' @inheritSection AMR Read more on Our Website!
#' @examples
#' # simple test
@ -53,13 +53,17 @@
#' #> TRUE
#' b %like% a
#' #> FALSE
#'
#' # also supports multiple patterns, length must be equal to x
#'
#' # also supports multiple patterns
#' a <- c("Test case", "Something different", "Yet another thing")
#' b <- c( "case", "diff", "yet")
#' a %like% b
#' #> TRUE TRUE TRUE
#'
#' a[1] %like% b
#' #> TRUE FALSE FALSE
#' a %like% b[1]
#' #> TRUE FALSE FALSE
#'
#' # get isolates whose name start with 'Ent' or 'ent'
#' \donttest{
#' if (require("dplyr")) {
@ -71,7 +75,11 @@ like <- function(x, pattern, ignore.case = TRUE) {
meet_criteria(x, allow_NA = TRUE)
meet_criteria(pattern, allow_NA = FALSE)
meet_criteria(ignore.case, allow_class = "logical", has_length = 1)
if (all(is.na(x))) {
return(rep(FALSE, length(x)))
}
# set to fixed if no regex found
fixed <- !any(is_possibly_regex(pattern))
if (ignore.case == TRUE) {
@ -79,53 +87,26 @@ like <- function(x, pattern, ignore.case = TRUE) {
x <- tolower(x)
pattern <- tolower(pattern)
}
if (length(pattern) > 1 & length(x) == 1) {
x <- rep(x, length(pattern))
}
if (all(is.na(x))) {
return(rep(FALSE, length(x)))
}
if (length(pattern) > 1) {
res <- vector(length = length(pattern))
if (length(x) != length(pattern)) {
if (length(x) == 1) {
x <- rep(x, length(pattern))
}
# return TRUE for every 'x' that matches any 'pattern', FALSE otherwise
for (i in seq_len(length(res))) {
if (is.factor(x[i])) {
res[i] <- as.integer(x[i]) %in% grep(pattern[i], levels(x[i]), ignore.case = FALSE, fixed = fixed)
} else {
res[i] <- grepl(pattern[i], x[i], ignore.case = FALSE, fixed = fixed, perl = !fixed)
}
}
res <- vapply(FUN.VALUE = logical(1), pattern, function(pttrn) grepl(pttrn, x, ignore.case = FALSE, fixed = fixed))
res2 <- as.logical(rowSums(res))
# get only first item of every hit in pattern
res2[duplicated(res)] <- FALSE
res2[rowSums(res) == 0] <- NA
return(res2)
} else {
# x and pattern are of same length, so items with each other
for (i in seq_len(length(res))) {
if (is.factor(x[i])) {
res[i] <- as.integer(x[i]) %in% grep(pattern[i], levels(x[i]), ignore.case = FALSE, fixed = fixed, perl = !fixed)
} else {
res[i] <- grepl(pattern[i], x[i], ignore.case = FALSE, fixed = fixed, perl = !fixed)
}
}
return(res)
}
}
# the regular way how grepl works; just one pattern against one or more x
if (is.factor(x)) {
as.integer(x) %in% grep(pattern, levels(x), ignore.case = FALSE, fixed = fixed, perl = !fixed)
} else {
x <- as.character(x)
}
if (length(pattern) == 1) {
grepl(pattern, x, ignore.case = FALSE, fixed = fixed, perl = !fixed)
} else {
if (length(x) == 1) {
x <- rep(x, length(pattern))
} else if (length(pattern) != length(x)) {
stop_("arguments `x` and `pattern` must be of same length, or either one must be 1")
}
mapply(FUN = grepl,
pattern,
x,
MoreArgs = list(ignore.case = FALSE, fixed = fixed, perl = !fixed),
SIMPLIFY = TRUE,
USE.NAMES = FALSE)
}
}

57
R/mic.R
View File

@ -53,8 +53,9 @@
#' ab = "AMX",
#' guideline = "EUCAST")
#'
#' # plot MIC values, see ?plot
#' plot(mic_data)
#' barplot(mic_data)
#' plot(mic_data, mo = "E. coli", ab = "cipro")
as.mic <- function(x, na.rm = FALSE) {
meet_criteria(x, allow_class = c("mic", "character", "numeric", "integer"), allow_NA = TRUE)
meet_criteria(na.rm, allow_class = "logical", has_length = 1)
@ -175,9 +176,11 @@ as.numeric.mic <- function(x, ...) {
#' @method droplevels mic
#' @export
#' @noRd
droplevels.mic <- function(x, exclude = if (any(is.na(levels(x)))) NULL else NA, ...) {
droplevels.mic <- function(x, exclude = if (any(is.na(levels(x)))) NULL else NA, as.mic = TRUE, ...) {
x <- droplevels.factor(x, exclude = exclude, ...)
class(x) <- c("mic", "ordered", "factor")
if (as.mic == TRUE) {
class(x) <- c("mic", "ordered", "factor")
}
x
}
@ -221,54 +224,6 @@ summary.mic <- function(object, ...) {
value
}
#' @method plot mic
#' @export
#' @importFrom graphics barplot axis
#' @rdname plot
plot.mic <- function(x,
main = paste("MIC values of", deparse(substitute(x))),
ylab = "Frequency",
xlab = "MIC value",
axes = FALSE,
...) {
meet_criteria(main, allow_class = "character", has_length = 1)
meet_criteria(ylab, allow_class = "character", has_length = 1)
meet_criteria(xlab, allow_class = "character", has_length = 1)
meet_criteria(axes, allow_class = "logical", has_length = 1)
barplot(table(as.double(x)),
ylab = ylab,
xlab = xlab,
axes = axes,
main = main,
...)
axis(2, seq(0, max(table(as.double(x)))))
}
#' @method barplot mic
#' @export
#' @importFrom graphics barplot axis
#' @rdname plot
barplot.mic <- function(height,
main = paste("MIC values of", deparse(substitute(height))),
ylab = "Frequency",
xlab = "MIC value",
axes = FALSE,
...) {
meet_criteria(main, allow_class = "character", has_length = 1)
meet_criteria(ylab, allow_class = "character", has_length = 1)
meet_criteria(xlab, allow_class = "character", has_length = 1)
meet_criteria(axes, allow_class = "logical", has_length = 1)
barplot(table(as.double(height)),
ylab = ylab,
xlab = xlab,
axes = axes,
main = main,
...)
axis(2, seq(0, max(table(as.double(height)))))
}
#' @method [ mic
#' @export
#' @noRd

4
R/mo.R
View File

@ -711,8 +711,8 @@ exec_as.mo <- function(x,
}
# translate known trivial abbreviations to genus + species ----
if (toupper(x_backup_without_spp[i]) %in% c("MRSA", "MSSA", "VISA", "VRSA", "BORSA")
| x_backup_without_spp[i] %like_case% "(^| )(mrsa|mssa|visa|vrsa|borsa|la-?mrsa|ca-?mrsa)( |$)") {
if (toupper(x_backup_without_spp[i]) %in% c("MRSA", "MSSA", "VISA", "VRSA", "BORSA", "GISA")
| x_backup_without_spp[i] %like_case% "(^| )(mrsa|mssa|visa|vrsa|borsa|gisa|la-?mrsa|ca-?mrsa)( |$)") {
x[i] <- lookup(fullname == "Staphylococcus aureus", uncertainty = -1)
next
}

569
R/plot.R Normal file
View File

@ -0,0 +1,569 @@
# ==================================================================== #
# TITLE #
# Antimicrobial Resistance (AMR) Data Analysis for R #
# #
# SOURCE #
# https://github.com/msberends/AMR #
# #
# LICENCE #
# (c) 2018-2021 Berends MS, Luz CF et al. #
# Developed at the University of Groningen, the Netherlands, in #
# collaboration with non-profit organisations Certe Medical #
# Diagnostics & Advice, and University Medical Center Groningen. #
# #
# This R package is free software; you can freely use and distribute #
# it for both personal and commercial purposes under the terms of the #
# GNU General Public License version 2.0 (GNU GPL-2), as published by #
# the Free Software Foundation. #
# We created this package for both routine data analysis and academic #
# research and it was publicly released in the hope that it will be #
# useful, but it comes WITHOUT ANY WARRANTY OR LIABILITY. #
# #
# Visit our website for the full manual and a complete tutorial about #
# how to conduct AMR data analysis: https://msberends.github.io/AMR/ #
# ==================================================================== #
#' Plotting for Classes `rsi`, `mic` and `disk`
#'
#' Functions to plot classes `rsi`, `mic` and `disk`, with support for base R and `ggplot2`.
#' @inheritSection lifecycle Stable Lifecycle
#' @inheritSection AMR Read more on Our Website!
#' @param x,data MIC values created with [as.mic()] or disk diffusion values created with [as.disk()]
#' @param mapping aesthetic mappings to use for [`ggplot()`][ggplot2::ggplot()]
#' @param main,title title of the plot
#' @param xlab,ylab axis title
#' @param mo any (vector of) text that can be coerced to a valid microorganism code with [as.mo()]
#' @param ab any (vector of) text that can be coerced to a valid antimicrobial code with [as.ab()]
#' @param guideline interpretation guideline to use, defaults to the latest included EUCAST guideline, see *Details*
#' @param colours_RSI colours to use for filling in the bars, must be a vector of three values (in the order R, S and I). The default colours are colour-blind friendly.
#' @param expand logical to indicate whether the range on the x axis should be expanded between the lowest and highest value. For MIC values, intermediate values will be factors of 2 starting from the highest MIC value. For disk diameters, the whole diameter range will be filled.
#' @details
#' The interpretation of "I" will be named "Increased exposure" for all EUCAST guidelines since 2019, and will be named "Intermediate" in all other cases.
#'
#' For interpreting MIC values as well as disk diffusion diameters, supported guidelines to be used as input for the `guideline` argument are: `r vector_and(AMR::rsi_translation$guideline, quotes = TRUE, reverse = TRUE)`.
#'
#' Simply using `"CLSI"` or `"EUCAST"` as input will automatically select the latest version of that guideline.
#' @name plot
#' @rdname plot
#' @return The `ggplot` functions return a [`ggplot`][ggplot2::ggplot()] model that is extendible with any `ggplot2` function.
#' @param ... arguments passed on to [as.rsi()]
#' @examples
#' some_mic_values <- random_mic(size = 100)
#' some_disk_values <- random_disk(size = 100, mo = "Escherichia coli", ab = "cipro")
#'
#' plot(some_mic_values)
#' plot(some_disk_values)
#'
#' # when providing the microorganism and antibiotic, colours will show interpretations:
#' plot(some_mic_values, mo = "S. aureus", ab = "ampicillin")
#' plot(some_disk_values, mo = "Escherichia coli", ab = "cipro")
#'
#' if (require("ggplot2")) {
#' ggplot(some_mic_values)
#' ggplot(some_disk_values, mo = "Escherichia coli", ab = "cipro")
#' }
NULL
#' @method plot mic
#' @importFrom graphics barplot axis mtext legend
#' @export
#' @rdname plot
plot.mic <- function(x,
main = paste("MIC values of", deparse(substitute(x))),
ylab = "Frequency",
xlab = "Minimum Inhibitory Concentration (mg/L)",
mo = NULL,
ab = NULL,
guideline = "EUCAST",
colours_RSI = c("#ED553B", "#3CAEA3", "#F6D55C"),
expand = TRUE,
...) {
meet_criteria(main, allow_class = "character")
meet_criteria(ylab, allow_class = "character", has_length = 1)
meet_criteria(xlab, allow_class = "character", has_length = 1)
meet_criteria(mo, allow_class = c("mo", "character"), allow_NULL = TRUE)
meet_criteria(ab, allow_class = c("ab", "character"), allow_NULL = TRUE)
meet_criteria(guideline, allow_class = "character", has_length = 1)
meet_criteria(colours_RSI, allow_class = "character", has_length = c(1, 3))
if (length(colours_RSI) == 1) {
colours_RSI <- rep(colours_RSI, 3)
}
main <- gsub(" +", " ", paste0(main, collapse = " "))
x <- plot_prepare_table(x, expand = expand)
cols_sub <- plot_colours_subtitle_guideline(x = x,
mo = mo,
ab = ab,
guideline = guideline,
colours_RSI = colours_RSI,
fn = as.mic,
...)
barplot(x,
col = cols_sub$cols,
main = main,
ylim = c(0, max(x) * ifelse(any(colours_RSI %in% cols_sub$cols), 1.1, 1)),
ylab = ylab,
xlab = xlab,
axes = FALSE)
axis(2, seq(0, max(as.double(x))))
if (!is.null(cols_sub$sub)) {
mtext(side = 3, line = 0.5, adj = 0.5, cex = 0.75, cols_sub$sub)
}
if (any(colours_RSI %in% cols_sub$cols)) {
legend_txt <- character(0)
legend_col <- character(0)
if (colours_RSI[2] %in% cols_sub$cols) {
legend_txt <- "Susceptible"
legend_col <- colours_RSI[2]
}
if (colours_RSI[3] %in% cols_sub$cols) {
legend_txt <- c(legend_txt, plot_name_of_I(cols_sub$guideline))
legend_col <- c(legend_col, colours_RSI[3])
}
if (colours_RSI[1] %in% cols_sub$cols) {
legend_txt <- c(legend_txt, "Resistant")
legend_col <- c(legend_col, colours_RSI[1])
}
legend("top",
x.intersp = 0.5,
legend = legend_txt,
fill = legend_col,
horiz = TRUE,
cex = 0.75,
box.lwd = 0,
bg = "#FFFFFF55")
}
}
#' @method barplot mic
#' @export
#' @noRd
barplot.mic <- function(height,
main = paste("MIC values of", deparse(substitute(height))),
ylab = "Frequency",
xlab = "Minimum Inhibitory Concentration (mg/L)",
mo = NULL,
ab = NULL,
guideline = "EUCAST",
colours_RSI = c("#ED553B", "#3CAEA3", "#F6D55C"),
expand = TRUE,
...) {
meet_criteria(main, allow_class = "character")
meet_criteria(ylab, allow_class = "character", has_length = 1)
meet_criteria(xlab, allow_class = "character", has_length = 1)
meet_criteria(mo, allow_class = c("mo", "character"), allow_NULL = TRUE)
meet_criteria(ab, allow_class = c("ab", "character"), allow_NULL = TRUE)
meet_criteria(guideline, allow_class = "character", has_length = 1)
meet_criteria(colours_RSI, allow_class = "character", has_length = c(1, 3))
main <- gsub(" +", " ", paste0(main, collapse = " "))
plot(x = height,
main = main,
ylab = ylab,
xlab = xlab,
mo = mo,
ab = ab,
guideline = guideline,
colours_RSI = colours_RSI,
...)
}
#' @method ggplot mic
#' @rdname plot
# will be exported using s3_register() in R/zzz.R
ggplot.mic <- function(data,
mapping = NULL,
title = paste("MIC values of", deparse(substitute(data))),
ylab = "Frequency",
xlab = "Minimum Inhibitory Concentration (mg/L)",
mo = NULL,
ab = NULL,
guideline = "EUCAST",
colours_RSI = c("#ED553B", "#3CAEA3", "#F6D55C"),
expand = TRUE,
...) {
stop_ifnot_installed("ggplot2")
meet_criteria(title, allow_class = "character")
meet_criteria(ylab, allow_class = "character", has_length = 1)
meet_criteria(xlab, allow_class = "character", has_length = 1)
meet_criteria(mo, allow_class = c("mo", "character"), allow_NULL = TRUE)
meet_criteria(ab, allow_class = c("ab", "character"), allow_NULL = TRUE)
meet_criteria(guideline, allow_class = "character", has_length = 1)
meet_criteria(colours_RSI, allow_class = "character", has_length = c(1, 3))
title <- gsub(" +", " ", paste0(title, collapse = " "))
x <- plot_prepare_table(data, expand = expand)
cols_sub <- plot_colours_subtitle_guideline(x = x,
mo = mo,
ab = ab,
guideline = guideline,
colours_RSI = colours_RSI,
fn = as.mic,
...)
df <- as.data.frame(x, stringsAsFactors = TRUE)
colnames(df) <- c("mic", "count")
df$cols <- cols_sub$cols
df$cols[df$cols == colours_RSI[1]] <- "Resistant"
df$cols[df$cols == colours_RSI[2]] <- "Susceptible"
df$cols[df$cols == colours_RSI[3]] <- plot_name_of_I(cols_sub$guideline)
df$cols <- factor(df$cols,
levels = c("Susceptible", plot_name_of_I(cols_sub$guideline), "Resistant"),
ordered = TRUE)
if (!is.null(mapping)) {
p <- ggplot2::ggplot(df, mapping = mapping)
} else {
p <- ggplot2::ggplot(df)
}
if (any(colours_RSI %in% cols_sub$cols)) {
p <- p +
ggplot2::geom_col(ggplot2::aes(x = mic, y = count, fill = cols)) +
ggplot2::scale_fill_manual(values = c("Resistant" = colours_RSI[1],
"Susceptible" = colours_RSI[2],
"Incr. exposure" = colours_RSI[3],
"Intermediate" = colours_RSI[3]),
name = NULL)
} else {
p <- p +
ggplot2::geom_col(aes(x = mic, y = count))
}
p +
ggplot2::labs(title = title, x = xlab, y = ylab, subtitle = cols_sub$sub)
}
#' @method plot disk
#' @export
#' @importFrom graphics barplot axis mtext legend
#' @rdname plot
plot.disk <- function(x,
main = paste("Disk zones values of", deparse(substitute(x))),
ylab = "Frequency",
xlab = "Disk diffusion diameter (mm)",
mo = NULL,
ab = NULL,
guideline = "EUCAST",
colours_RSI = c("#ED553B", "#3CAEA3", "#F6D55C"),
expand = TRUE,
...) {
meet_criteria(main, allow_class = "character")
meet_criteria(ylab, allow_class = "character", has_length = 1)
meet_criteria(xlab, allow_class = "character", has_length = 1)
meet_criteria(mo, allow_class = c("mo", "character"), allow_NULL = TRUE)
meet_criteria(ab, allow_class = c("ab", "character"), allow_NULL = TRUE)
meet_criteria(guideline, allow_class = "character", has_length = 1)
meet_criteria(colours_RSI, allow_class = "character", has_length = c(1, 3))
if (length(colours_RSI) == 1) {
colours_RSI <- rep(colours_RSI, 3)
}
main <- gsub(" +", " ", paste0(main, collapse = " "))
x <- plot_prepare_table(x, expand = expand)
cols_sub <- plot_colours_subtitle_guideline(x = x,
mo = mo,
ab = ab,
guideline = guideline,
colours_RSI = colours_RSI,
fn = as.disk,
...)
barplot(x,
col = cols_sub$cols,
main = main,
ylim = c(0, max(x) * ifelse(any(colours_RSI %in% cols_sub$cols), 1.1, 1)),
ylab = ylab,
xlab = xlab,
axes = FALSE)
axis(2, seq(0, max(x)))
if (!is.null(cols_sub$sub)) {
mtext(side = 3, line = 0.5, adj = 0.5, cex = 0.75, cols_sub$sub)
}
if (any(colours_RSI %in% cols_sub$cols)) {
legend_txt <- character(0)
legend_col <- character(0)
if (colours_RSI[1] %in% cols_sub$cols) {
legend_txt <- "Resistant"
legend_col <- colours_RSI[1]
}
if (colours_RSI[3] %in% cols_sub$cols) {
legend_txt <- c(legend_txt, plot_name_of_I(cols_sub$guideline))
legend_col <- c(legend_col, colours_RSI[3])
}
if (colours_RSI[2] %in% cols_sub$cols) {
legend_txt <- c(legend_txt, "Susceptible")
legend_col <- c(legend_col, colours_RSI[2])
}
legend("top",
x.intersp = 0.5,
legend = legend_txt,
fill = legend_col,
horiz = TRUE,
cex = 0.75,
box.lwd = 0,
bg = "#FFFFFF55")
}
}
#' @method barplot disk
#' @export
#' @noRd
barplot.disk <- function(height,
main = paste("Disk zones values of", deparse(substitute(height))),
ylab = "Frequency",
xlab = "Disk diffusion diameter (mm)",
mo = NULL,
ab = NULL,
guideline = "EUCAST",
colours_RSI = c("#ED553B", "#3CAEA3", "#F6D55C"),
expand = TRUE,
...) {
meet_criteria(main, allow_class = "character")
meet_criteria(ylab, allow_class = "character", has_length = 1)
meet_criteria(xlab, allow_class = "character", has_length = 1)
meet_criteria(mo, allow_class = c("mo", "character"), allow_NULL = TRUE)
meet_criteria(ab, allow_class = c("ab", "character"), allow_NULL = TRUE)
meet_criteria(guideline, allow_class = "character", has_length = 1)
meet_criteria(colours_RSI, allow_class = "character", has_length = c(1, 3))
main <- gsub(" +", " ", paste0(main, collapse = " "))
plot(x = height,
main = main,
ylab = ylab,
xlab = xlab,
mo = mo,
ab = ab,
guideline = guideline,
colours_RSI = colours_RSI,
...)
}
#' @method ggplot disk
#' @rdname plot
# will be exported using s3_register() in R/zzz.R
ggplot.disk <- function(data,
mapping = NULL,
title = paste("Disk zones values of", deparse(substitute(data))),
ylab = "Frequency",
xlab = "Disk diffusion diameter (mm)",
mo = NULL,
ab = NULL,
guideline = "EUCAST",
colours_RSI = c("#ED553B", "#3CAEA3", "#F6D55C"),
expand = TRUE,
...) {
stop_ifnot_installed("ggplot2")
meet_criteria(title, allow_class = "character")
meet_criteria(ylab, allow_class = "character", has_length = 1)
meet_criteria(xlab, allow_class = "character", has_length = 1)
meet_criteria(mo, allow_class = c("mo", "character"), allow_NULL = TRUE)
meet_criteria(ab, allow_class = c("ab", "character"), allow_NULL = TRUE)
meet_criteria(guideline, allow_class = "character", has_length = 1)
meet_criteria(colours_RSI, allow_class = "character", has_length = c(1, 3))
title <- gsub(" +", " ", paste0(title, collapse = " "))
x <- plot_prepare_table(data, expand = expand)
cols_sub <- plot_colours_subtitle_guideline(x = x,
mo = mo,
ab = ab,
guideline = guideline,
colours_RSI = colours_RSI,
fn = as.disk,
...)
df <- as.data.frame(x, stringsAsFactors = TRUE)
colnames(df) <- c("disk", "count")
df$cols <- cols_sub$cols
df$cols[df$cols == colours_RSI[1]] <- "Resistant"
df$cols[df$cols == colours_RSI[2]] <- "Susceptible"
df$cols[df$cols == colours_RSI[3]] <- plot_name_of_I(cols_sub$guideline)
df$cols <- factor(df$cols,
levels = c("Resistant", plot_name_of_I(cols_sub$guideline), "Susceptible"),
ordered = TRUE)
if (!is.null(mapping)) {
p <- ggplot2::ggplot(df, mapping = mapping)
} else {
p <- ggplot2::ggplot(df)
}
if (any(colours_RSI %in% cols_sub$cols)) {
p <- p +
ggplot2::geom_col(aes(x = disk, y = count, fill = cols)) +
ggplot2::scale_fill_manual(values = c("Resistant" = colours_RSI[1],
"Susceptible" = colours_RSI[2],
"Incr. exposure" = colours_RSI[3],
"Intermediate" = colours_RSI[3]),
name = NULL)
} else {
p <- p +
ggplot2::geom_col(aes(x = disk, y = count))
}
p +
ggplot2::labs(title = title, x = xlab, y = ylab, subtitle = cols_sub$sub)
}
plot_prepare_table <- function(x, expand) {
if (is.mic(x)) {
if (expand == TRUE) {
# expand range for MIC by adding factors of 2 from lowest to highest so all MICs in between also print
extra_range <- max(as.double(x)) / 2
while (min(extra_range) / 2 > min(as.double(x))) {
extra_range <- c(min(extra_range) / 2, extra_range)
}
nms <- extra_range
extra_range <- rep(0, length(extra_range))
names(extra_range) <- nms
x <- table(droplevels(x, as.mic = FALSE))
extra_range <- extra_range[!names(extra_range) %in% names(x)]
x <- as.table(c(x, extra_range))
} else {
x <- table(droplevels(x, as.mic = FALSE))
}
x <- x[order(as.double(as.mic(names(x))))]
} else if (is.disk(x)) {
if (expand == TRUE) {
# expand range for disks from lowest to highest so all mm's in between also print
extra_range <- rep(0, max(x) - min(x) - 1)
names(extra_range) <- seq(min(x) + 1, max(x) - 1)
x <- table(x)
extra_range <- extra_range[!names(extra_range) %in% names(x)]
x <- as.table(c(x, extra_range))
} else {
x <- table(x)
}
x <- x[order(as.double(names(x)))]
}
as.table(x)
}
plot_name_of_I <- function(guideline) {
if (!guideline %like% "CLSI" && as.double(gsub("[^0-9]+", "", guideline)) >= 2019) {
# interpretation since 2019
"Incr. exposure"
} else {
# interpretation until 2019
"Intermediate"
}
}
plot_colours_subtitle_guideline <- function(x, mo, ab, guideline, colours_RSI, fn, ...) {
guideline <- get_guideline(guideline, AMR::rsi_translation)
if (!is.null(mo) && !is.null(ab)) {
# interpret and give colour based on MIC values
mo <- as.mo(mo)
ab <- as.ab(ab)
rsi <- suppressWarnings(suppressMessages(as.rsi(fn(names(x)), mo = mo, ab = ab, guideline = guideline, ...)))
cols <- character(length = length(rsi))
cols[is.na(rsi)] <- "#BEBEBE"
cols[rsi == "R"] <- colours_RSI[1]
cols[rsi == "S"] <- colours_RSI[2]
cols[rsi == "I"] <- colours_RSI[3]
moname <- mo_name(mo, language = NULL)
abname <- ab_name(ab, language = NULL)
if (all(cols == "#BEBEBE")) {
message_("No ", guideline, " interpretations found for ",
ab_name(ab, language = NULL, tolower = TRUE), " in ", moname)
guideline_txt <- ""
} else {
guideline_txt <- paste0("(following ", guideline, ")")
}
sub <- bquote(.(abname)~"in"~italic(.(moname))~.(guideline_txt))
} else {
cols <- "#BEBEBE"
sub <- NULL
}
list(cols = cols, sub = sub, guideline = guideline)
}
#' @method plot rsi
#' @export
#' @importFrom graphics plot text axis
#' @rdname plot
plot.rsi <- function(x,
ylab = "Percentage",
xlab = "Antimicrobial Interpretation",
main = paste("Resistance Overview of", deparse(substitute(x))),
...) {
meet_criteria(ylab, allow_class = "character", has_length = 1)
meet_criteria(xlab, allow_class = "character", has_length = 1)
meet_criteria(main, allow_class = "character", has_length = 1)
data <- as.data.frame(table(x), stringsAsFactors = FALSE)
colnames(data) <- c("x", "n")
data$s <- round((data$n / sum(data$n)) * 100, 1)
if (!"S" %in% data$x) {
data <- rbind(data, data.frame(x = "S", n = 0, s = 0, stringsAsFactors = FALSE),
stringsAsFactors = FALSE)
}
if (!"I" %in% data$x) {
data <- rbind(data, data.frame(x = "I", n = 0, s = 0, stringsAsFactors = FALSE),
stringsAsFactors = FALSE)
}
if (!"R" %in% data$x) {
data <- rbind(data, data.frame(x = "R", n = 0, s = 0, stringsAsFactors = FALSE),
stringsAsFactors = FALSE)
}
data$x <- factor(data$x, levels = c("R", "S", "I"), ordered = TRUE)
ymax <- pm_if_else(max(data$s) > 95, 105, 100)
plot(x = data$x,
y = data$s,
lwd = 2,
ylim = c(0, ymax),
ylab = ylab,
xlab = xlab,
main = main,
axes = FALSE)
# x axis
axis(side = 1, at = 1:pm_n_distinct(data$x), labels = levels(data$x), lwd = 0)
# y axis, 0-100%
axis(side = 2, at = seq(0, 100, 5))
text(x = data$x,
y = data$s + 4,
labels = paste0(data$s, "% (n = ", data$n, ")"))
}
#' @method barplot rsi
#' @importFrom graphics barplot axis
#' @export
#' @noRd
barplot.rsi <- function(height,
main = paste("Resistance Overview of", deparse(substitute(height))),
xlab = "Antimicrobial Interpretation",
ylab = "Frequency",
colours_RSI = c("#ED553B", "#3CAEA3", "#F6D55C"),
expand = TRUE,
...) {
meet_criteria(xlab, allow_class = "character", has_length = 1)
meet_criteria(main, allow_class = "character", has_length = 1)
meet_criteria(ylab, allow_class = "character", has_length = 1)
meet_criteria(colours_RSI, allow_class = "character", has_length = c(1, 3))
if (length(colours_RSI) == 1) {
colours_RSI <- rep(colours_RSI, 3)
}
main <- gsub(" +", " ", paste0(main, collapse = " "))
x <- table(height)
x <- x[c(3, 1, 2)]
barplot(x,
col = colours_RSI,
xlab = xlab,
main = main,
ylab = ylab,
axes = FALSE)
axis(2, seq(0, max(x)))
}

View File

@ -25,7 +25,7 @@
#' Random MIC Values/Disk Zones/RSI Generation
#'
#' These functions can be used for generating random MIC values and disk diffusion diameters, for AMR data analysis practice.
#' These functions can be used for generating random MIC values and disk diffusion diameters, for AMR data analysis practice. By providing a microorganism and antimicrobial agent, the generated results will reflect reality as much as possible.
#' @inheritSection lifecycle Maturing Lifecycle
#' @param size desired size of the returned vector
#' @param mo any character that can be coerced to a valid microorganism code with [as.mo()]
@ -111,8 +111,8 @@ random_exec <- function(type, size, mo = NULL, ab = NULL) {
if (log(set_range_max, 2) %% 1 == 0) {
# return powers of 2
valid_range <- unique(as.double(valid_range))
# add one higher MIC level to set_range_max
set_range_max <- 2 ^ (log(set_range_max, 2) + 1)
# add 1-3 higher MIC levels to set_range_max
set_range_max <- 2 ^ (log(set_range_max, 2) + sample(c(1:3), 1))
set_range <- as.mic(valid_range[log(valid_range, 2) %% 1 == 0 & valid_range <= set_range_max])
} else {
# no power of 2, return factors of 2 to left and right side
@ -121,8 +121,8 @@ random_exec <- function(type, size, mo = NULL, ab = NULL) {
}
return(as.mic(sample(set_range, size = size, replace = TRUE)))
} else if (type == "DISK") {
set_range <- seq(from = as.integer(min(df$breakpoint_R)),
to = as.integer(max(df$breakpoint_S)),
set_range <- seq(from = as.integer(min(df$breakpoint_R) / 1.25),
to = as.integer(max(df$breakpoint_S) * 1.25),
by = 1)
out <- sample(set_range, size = size, replace = TRUE)
out[out < 6] <- sample(c(6:10), length(out[out < 6]), replace = TRUE)

110
R/rsi.R
View File

@ -252,12 +252,13 @@ is.rsi.eligible <- function(x, threshold = 0.05) {
}
#' @export
# extra param: warn (never throw warning)
as.rsi.default <- function(x, ...) {
if (is.rsi(x)) {
return(x)
}
if (inherits(x, "integer") & all(x %in% c(1:3, NA))) {
if (inherits(x, c("integer", "numeric", "double")) && all(x %in% c(1:3, NA))) {
x[x == 1] <- "S"
x[x == 2] <- "I"
x[x == 3] <- "R"
@ -265,11 +266,11 @@ as.rsi.default <- function(x, ...) {
} else if (!all(is.na(x)) && !identical(levels(x), c("S", "I", "R"))) {
if (!any(x %like% "(R|S|I)", na.rm = TRUE)) {
# check if they are actually MICs or disks now that the antibiotic name is valid
# check if they are actually MICs or disks
if (all_valid_mics(x)) {
warning_("The input seems to be MIC values. Transform them with as.mic() before running as.rsi() to interpret them.")
warning_("The input seems to be MIC values. Transform them with `as.mic()` before running `as.rsi()` to interpret them.")
} else if (all_valid_disks(x)) {
warning_("The input seems to be disk diffusion values. Transform them with as.disk() before running as.rsi() to interpret them.")
warning_("The input seems to be disk diffusion values. Transform them with `as.disk()` before running `as.rsi()` to interpret them.")
}
}
@ -1010,107 +1011,6 @@ summary.rsi <- function(object, ...) {
value
}
#' @method plot rsi
#' @export
#' @importFrom graphics plot text axis
#' @rdname plot
plot.rsi <- function(x,
lwd = 2,
ylim = NULL,
ylab = "Percentage",
xlab = "Antimicrobial Interpretation",
main = paste("Resistance Overview of", deparse(substitute(x))),
axes = FALSE,
...) {
meet_criteria(lwd, allow_class = c("numeric", "integer"), has_length = 1, is_positive = TRUE, is_finite = TRUE)
meet_criteria(ylim, allow_class = c("numeric", "integer"), allow_NULL = TRUE)
meet_criteria(ylab, allow_class = "character", has_length = 1)
meet_criteria(xlab, allow_class = "character", has_length = 1)
meet_criteria(main, allow_class = "character", has_length = 1)
meet_criteria(axes, allow_class = "logical", has_length = 1)
data <- as.data.frame(table(x), stringsAsFactors = FALSE)
colnames(data) <- c("x", "n")
data$s <- round((data$n / sum(data$n)) * 100, 1)
if (!"S" %in% data$x) {
data <- rbind(data, data.frame(x = "S", n = 0, s = 0, stringsAsFactors = FALSE),
stringsAsFactors = FALSE)
}
if (!"I" %in% data$x) {
data <- rbind(data, data.frame(x = "I", n = 0, s = 0, stringsAsFactors = FALSE),
stringsAsFactors = FALSE)
}
if (!"R" %in% data$x) {
data <- rbind(data, data.frame(x = "R", n = 0, s = 0, stringsAsFactors = FALSE),
stringsAsFactors = FALSE)
}
# don't use as.rsi() here, it will confuse plot()
data$x <- factor(data$x, levels = c("S", "I", "R"), ordered = TRUE)
ymax <- pm_if_else(max(data$s) > 95, 105, 100)
plot(x = data$x,
y = data$s,
lwd = lwd,
ylim = c(0, ymax),
ylab = ylab,
xlab = xlab,
main = main,
axes = axes,
...)
# x axis
axis(side = 1, at = 1:pm_n_distinct(data$x), labels = levels(data$x), lwd = 0)
# y axis, 0-100%
axis(side = 2, at = seq(0, 100, 5))
text(x = data$x,
y = data$s + 4,
labels = paste0(data$s, "% (n = ", data$n, ")"))
}
#' @method barplot rsi
#' @export
#' @importFrom graphics barplot axis par
#' @rdname plot
barplot.rsi <- function(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,
...) {
meet_criteria(col, allow_class = "character", has_length = 3)
meet_criteria(xlab, allow_class = "character", has_length = 1)
meet_criteria(main, allow_class = "character", has_length = 1)
meet_criteria(ylab, allow_class = "character", has_length = 1)
meet_criteria(beside, allow_class = "logical", has_length = 1)
meet_criteria(axes, allow_class = "logical", has_length = 1)
if (axes == TRUE) {
par(mar = c(5, 4, 4, 2) + 0.1)
} else {
par(mar = c(2, 4, 4, 2) + 0.1)
}
barplot(as.matrix(table(height)),
col = col,
xlab = xlab,
main = main,
ylab = ylab,
beside = beside,
axes = FALSE,
...)
# y axis, 0-100%
axis(side = 2, at = seq(0, max(table(height)) + max(table(height)) * 1.1, by = 25))
if (axes == TRUE && beside == TRUE) {
axis(side = 1, labels = levels(height), at = c(1, 2, 3) + 0.5, lwd = 0)
}
}
#' @method [<- rsi
#' @export
#' @noRd

View File

@ -50,6 +50,8 @@ pkg_env$mo_failed <- character(0)
s3_register("skimr::get_skimmers", "rsi")
s3_register("skimr::get_skimmers", "mic")
s3_register("skimr::get_skimmers", "disk")
s3_register("ggplot2::ggplot", "mic")
s3_register("ggplot2::ggplot", "disk")
# if mo source exists, fire it up (see mo_source())
try({

Binary file not shown.

View File

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

View File

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

File diff suppressed because it is too large Load Diff

Binary file not shown.

Before

Width:  |  Height:  |  Size: 38 KiB

After

Width:  |  Height:  |  Size: 38 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 26 KiB

After

Width:  |  Height:  |  Size: 26 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 68 KiB

After

Width:  |  Height:  |  Size: 68 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 45 KiB

After

Width:  |  Height:  |  Size: 45 KiB

Binary file not shown.

After

Width:  |  Height:  |  Size: 29 KiB

Binary file not shown.

After

Width:  |  Height:  |  Size: 33 KiB

Binary file not shown.

After

Width:  |  Height:  |  Size: 42 KiB

Binary file not shown.

After

Width:  |  Height:  |  Size: 50 KiB

Binary file not shown.

After

Width:  |  Height:  |  Size: 43 KiB

Binary file not shown.

After

Width:  |  Height:  |  Size: 54 KiB

View File

@ -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.5.0.9024</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.5.0.9025</span>
</span>
</div>
@ -226,19 +226,19 @@
times <span class="op">=</span> <span class="fl">25</span><span class="op">)</span>
<span class="fu"><a href="https://rdrr.io/r/base/print.html">print</a></span><span class="op">(</span><span class="va">S.aureus</span>, unit <span class="op">=</span> <span class="st">"ms"</span>, signif <span class="op">=</span> <span class="fl">2</span><span class="op">)</span>
<span class="co"># Unit: milliseconds</span>
<span class="co"># expr min lq mean median uq max neval</span>
<span class="co"># as.mo("sau") 9.3 10 11.0 10 11.0 13.0 25</span>
<span class="co"># as.mo("stau") 52.0 55 73.0 58 92.0 100.0 25</span>
<span class="co"># as.mo("STAU") 50.0 54 73.0 58 96.0 110.0 25</span>
<span class="co"># as.mo("staaur") 9.7 10 14.0 11 12.0 57.0 25</span>
<span class="co"># as.mo("STAAUR") 8.9 10 14.0 10 11.0 52.0 25</span>
<span class="co"># as.mo("S. aureus") 26.0 28 41.0 29 67.0 76.0 25</span>
<span class="co"># as.mo("S aureus") 27.0 28 41.0 30 65.0 76.0 25</span>
<span class="co"># as.mo("Staphylococcus aureus") 2.6 3 3.2 3 3.3 4.6 25</span>
<span class="co"># as.mo("Staphylococcus aureus (MRSA)") 240.0 260 270.0 260 270.0 380.0 25</span>
<span class="co"># as.mo("Sthafilokkockus aaureuz") 160.0 190 200.0 200 200.0 300.0 25</span>
<span class="co"># as.mo("MRSA") 9.3 10 15.0 10 12.0 49.0 25</span>
<span class="co"># as.mo("VISA") 18.0 19 31.0 21 54.0 67.0 25</span></code></pre></div>
<span class="co"># expr min lq mean median uq max neval</span>
<span class="co"># as.mo("sau") 10 11.0 15 11.0 13.0 47 25</span>
<span class="co"># as.mo("stau") 56 57.0 75 62.0 95.0 100 25</span>
<span class="co"># as.mo("STAU") 54 56.0 67 58.0 66.0 110 25</span>
<span class="co"># as.mo("staaur") 10 11.0 12 11.0 12.0 13 25</span>
<span class="co"># as.mo("STAAUR") 10 11.0 16 11.0 12.0 50 25</span>
<span class="co"># as.mo("S. aureus") 28 31.0 46 33.0 65.0 71 25</span>
<span class="co"># as.mo("S aureus") 29 30.0 42 33.0 64.0 67 25</span>
<span class="co"># as.mo("Staphylococcus aureus") 3 3.2 5 3.3 3.7 40 25</span>
<span class="co"># as.mo("Staphylococcus aureus (MRSA)") 240 260.0 270 270.0 280.0 290 25</span>
<span class="co"># as.mo("Sthafilokkockus aaureuz") 170 200.0 210 200.0 210.0 280 25</span>
<span class="co"># as.mo("MRSA") 10 11.0 17 11.0 13.0 51 25</span>
<span class="co"># as.mo("VISA") 19 20.0 36 21.0 50.0 150 25</span></code></pre></div>
<p><img src="benchmarks_files/figure-html/unnamed-chunk-4-1.png" width="750"></p>
<p>In the table above, all measurements are shown in milliseconds (thousands of seconds). A value of 5 milliseconds means it can determine 200 input values per second. It case of 200 milliseconds, this is only 5 input values per second. It is clear that accepted taxonomic names are extremely fast, but some variations are up to 200 times slower to determine.</p>
<p>To improve performance, we implemented two important algorithms to save unnecessary calculations: <strong>repetitive results</strong> and <strong>already precalculated results</strong>.</p>
@ -260,8 +260,8 @@
<span class="co"># what do these values look like? They are of class &lt;mo&gt;:</span>
<span class="fu"><a href="https://rdrr.io/r/utils/head.html">head</a></span><span class="op">(</span><span class="va">x</span><span class="op">)</span>
<span class="co"># Class &lt;mo&gt;</span>
<span class="co"># [1] B_STPHY_AURS B_STRPT_GRPC B_STPHY_CONS B_STPHY_EPDR B_STRPT_PNMN</span>
<span class="co"># [6] B_PROTS_VLGR</span>
<span class="co"># [1] B_ESCHR_COLI B_PROTS_MRBL B_PROTS_MRBL B_PROTS_MRBL B_STPHY_CONS</span>
<span class="co"># [6] B_ENTRC</span>
<span class="co"># as the example_isolates data set has 2,000 rows, we should have 2 million items</span>
<span class="fu"><a href="https://rdrr.io/r/base/length.html">length</a></span><span class="op">(</span><span class="va">x</span><span class="op">)</span>
@ -277,8 +277,8 @@
<span class="fu"><a href="https://rdrr.io/r/base/print.html">print</a></span><span class="op">(</span><span class="va">run_it</span>, unit <span class="op">=</span> <span class="st">"ms"</span>, signif <span class="op">=</span> <span class="fl">3</span><span class="op">)</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) 157 187 222 206 224 372 10</span></code></pre></div>
<p>So getting official taxonomic names of 2,000,000 (!!) items consisting of 90 unique values only takes 0.206 seconds. That is 2.471 milliseconds per unique item on average. You only lose time on your unique input values.</p>
<span class="co"># mo_name(x) 160 189 224 201 228 356 10</span></code></pre></div>
<p>So getting official taxonomic names of 2,000,000 (!!) items consisting of 90 unique values only takes 0.201 seconds. That is 101 nanoseconds on average. You only lose time on your unique input values.</p>
</div>
<div id="precalculated-results" class="section level3">
<h3 class="hasAnchor">
@ -291,10 +291,10 @@
times <span class="op">=</span> <span class="fl">10</span><span class="op">)</span>
<span class="fu"><a href="https://rdrr.io/r/base/print.html">print</a></span><span class="op">(</span><span class="va">run_it</span>, unit <span class="op">=</span> <span class="st">"ms"</span>, signif <span class="op">=</span> <span class="fl">3</span><span class="op">)</span>
<span class="co"># Unit: milliseconds</span>
<span class="co"># expr min lq mean median uq max neval</span>
<span class="co"># A 6.97 7.10 7.55 7.21 8.18 8.32 10</span>
<span class="co"># B 23.70 24.20 36.30 26.30 29.00 89.70 10</span>
<span class="co"># C 1.53 1.65 1.80 1.76 2.00 2.19 10</span></code></pre></div>
<span class="co"># expr min lq mean median uq max neval</span>
<span class="co"># A 6.80 7.17 7.46 7.54 7.81 8.0 10</span>
<span class="co"># B 24.30 25.80 31.60 26.20 28.80 75.6 10</span>
<span class="co"># C 1.59 1.70 1.89 1.84 2.02 2.5 10</span></code></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.0018 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 sourceCode r">
<code class="sourceCode R"><span class="va">run_it</span> <span class="op">&lt;-</span> <span class="fu"><a href="https://rdrr.io/pkg/microbenchmark/man/microbenchmark.html">microbenchmark</a></span><span class="op">(</span>A <span class="op">=</span> <span class="fu"><a href="../reference/mo_property.html">mo_species</a></span><span class="op">(</span><span class="st">"aureus"</span><span class="op">)</span>,
@ -309,14 +309,14 @@
<span class="fu"><a href="https://rdrr.io/r/base/print.html">print</a></span><span class="op">(</span><span class="va">run_it</span>, unit <span class="op">=</span> <span class="st">"ms"</span>, signif <span class="op">=</span> <span class="fl">3</span><span class="op">)</span>
<span class="co"># Unit: milliseconds</span>
<span class="co"># expr min lq mean median uq max neval</span>
<span class="co"># A 1.44 1.72 1.69 1.74 1.75 1.78 10</span>
<span class="co"># B 1.47 1.55 1.67 1.73 1.74 1.89 10</span>
<span class="co"># C 1.52 1.59 1.73 1.74 1.89 1.91 10</span>
<span class="co"># D 1.46 1.51 1.64 1.64 1.75 1.89 10</span>
<span class="co"># E 1.42 1.47 1.60 1.52 1.71 1.97 10</span>
<span class="co"># F 1.44 1.71 1.69 1.72 1.75 1.88 10</span>
<span class="co"># G 1.42 1.50 1.68 1.61 1.73 2.36 10</span>
<span class="co"># H 1.52 1.54 1.66 1.71 1.73 1.87 10</span></code></pre></div>
<span class="co"># A 1.25 1.28 1.39 1.39 1.50 1.56 10</span>
<span class="co"># B 1.17 1.19 1.41 1.43 1.48 1.92 10</span>
<span class="co"># C 1.20 1.33 1.43 1.46 1.50 1.61 10</span>
<span class="co"># D 1.43 1.45 1.50 1.49 1.53 1.61 10</span>
<span class="co"># E 1.26 1.40 1.45 1.43 1.49 1.81 10</span>
<span class="co"># F 1.15 1.17 1.32 1.26 1.44 1.69 10</span>
<span class="co"># G 1.19 1.25 1.37 1.35 1.47 1.58 10</span>
<span class="co"># H 1.20 1.25 1.46 1.31 1.53 2.33 10</span></code></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 contains all phyla of all known bacteria, it can just return the initial value immediately.</p>
</div>
<div id="results-in-other-languages" class="section level3">
@ -343,14 +343,14 @@
times <span class="op">=</span> <span class="fl">100</span><span class="op">)</span>
<span class="fu"><a href="https://rdrr.io/r/base/print.html">print</a></span><span class="op">(</span><span class="va">run_it</span>, unit <span class="op">=</span> <span class="st">"ms"</span>, signif <span class="op">=</span> <span class="fl">4</span><span class="op">)</span>
<span class="co"># Unit: milliseconds</span>
<span class="co"># expr min lq mean median uq max neval</span>
<span class="co"># en 17.12 17.40 22.65 17.54 18.39 78.39 100</span>
<span class="co"># de 19.93 20.26 22.60 20.48 20.97 81.27 100</span>
<span class="co"># nl 24.87 25.24 30.93 25.50 26.90 87.17 100</span>
<span class="co"># es 20.00 20.26 24.39 20.58 21.13 82.01 100</span>
<span class="co"># it 19.92 20.26 26.54 20.66 21.38 79.15 100</span>
<span class="co"># fr 19.62 19.90 24.74 20.10 21.04 77.20 100</span>
<span class="co"># pt 19.74 20.02 26.76 20.41 22.68 82.61 100</span></code></pre></div>
<span class="co"># expr min lq mean median uq max neval</span>
<span class="co"># en 17.05 17.38 21.26 17.74 18.50 97.23 100</span>
<span class="co"># de 19.90 20.33 24.80 20.67 21.06 93.34 100</span>
<span class="co"># nl 24.86 25.30 31.21 25.65 26.34 102.20 100</span>
<span class="co"># es 19.83 20.22 26.56 20.49 21.20 97.59 100</span>
<span class="co"># it 19.79 20.20 26.82 20.63 21.31 94.85 100</span>
<span class="co"># fr 19.61 19.87 24.26 20.21 20.68 92.42 100</span>
<span class="co"># pt 19.64 20.06 23.78 20.40 21.05 92.91 100</span></code></pre></div>
<p>Currently supported non-English languages are German, Dutch, Spanish, Italian, French and Portuguese.</p>
</div>
</div>

Binary file not shown.

Before

Width:  |  Height:  |  Size: 80 KiB

After

Width:  |  Height:  |  Size: 81 KiB

View File

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

View File

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

View File

@ -187,30 +187,30 @@ div[id^=last-updated] h2 {
}
/* tables, make them look like scientific ones */
table {
.table {
font-size: 90%;
}
table * {
.table * {
vertical-align: middle !important;
}
table td {
.table td {
padding: 4px !important;
}
thead {
.table thead {
border-top: 2px solid black;
border-bottom: 2px solid black;
}
thead ~ tbody {
.table thead ~ tbody {
/* only when it has a header */
border-bottom: 2px solid black;
}
thead th {
.table thead th {
text-align: inherit;
}
table a:not(.btn), .table a:not(.btn) {
.table a:not(.btn) {
text-decoration: inherit;
}
table a:not(.btn):hover, .table a:not(.btn):hover {
.table a:not(.btn):hover {
text-decoration: underline;
}

View File

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

View File

@ -1,88 +1,32 @@
<?xml version="1.0"?> <!DOCTYPE svg PUBLIC "-//W3C//DTD SVG 1.1//EN"
"http://www.w3.org/Graphics/SVG/1.1/DTD/svg11.dtd"> <svg
xmlns="http://www.w3.org/2000/svg" xmlns:xl="http://www.w3.org/1999/xlink"
version="1.1" viewBox="8 48 787 198" width="787pt" height="198pt"><metadata
xmlns:dc="http://purl.org/dc/elements/1.1/"><dc:date>2018-01-05
19:43Z</dc:date><!-- Produced by OmniGraffle Professional 5.4.4
--></metadata><defs><font-face font-family="Helvetica Neue" font-size="16"
panose-1="2 0 5 3 0 0 0 2 0 4" units-per-em="1000" underline-position="-100"
underline-thickness="50" slope="0" x-height="517" cap-height="714"
ascent="951.99585" descent="-212.99744"
font-weight="500"><font-face-src><font-face-name
name="HelveticaNeue"/></font-face-src></font-face><marker orient="auto"
overflow="visible" markerUnits="strokeWidth" id="FilledArrow_Marker" viewBox="-1
-4 10 8" markerWidth="10" markerHeight="8" color="black"><g><path d="M 8 0 L 0
-3 L 0 3 Z" fill="currentColor" stroke="currentColor"
stroke-width="1"/></g></marker></defs><g stroke="none" stroke-opacity="1"
stroke-dasharray="none" fill="none" fill-opacity="1"><title>Canvas
1</title><rect fill="white" width="805.88977"
height="536.27556"/><g><title>Layer 1</title><rect x="201.43709" y="148.91563"
width="88.865815" height="36.026683" stroke="#0080ff" stroke-linecap="round"
stroke-linejoin="round" stroke-width="2"/><text transform="translate(206.43709
157.70498)" fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="7.8649073" y="15"
textLength="63.136">maturing</tspan></text><rect x="10.4153" y="97.854194"
width="123.69161" height="36.026683" stroke="#ff8000" stroke-linecap="round"
stroke-linejoin="round" stroke-width="2"/><text transform="translate(15.4153
106.643536)" fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="10.7658034" y="15"
textLength="92.160004">experimental</tspan></text><rect x="339.64294"
y="207.75286" width="64.848027" height="36.026683" stroke="green"
stroke-linecap="round" stroke-linejoin="round" stroke-width="2"/><text
transform="translate(344.64294 216.5422)" fill="black"><tspan
font-family="Helvetica Neue" font-size="16" font-weight="500" x="5.7920134"
y="15" textLength="43.264">stable</tspan></text><rect x="613.9284" y="118.27877"
width="67.249806" height="36.026683" stroke="#ff8000" stroke-linecap="round"
stroke-linejoin="round" stroke-width="2"/><text transform="translate(618.9284
127.06811)" fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="5.9529028" y="15" textLength="5.328">r</tspan><tspan
font-family="Helvetica Neue" font-size="16" font-weight="500" x="10.992903"
y="15" textLength="22.511999">etir</tspan><tspan font-family="Helvetica Neue"
font-size="16" font-weight="500" x="33.216903" y="15"
textLength="18.08">ed</tspan></text><rect x="325.78587" y="50.19685"
width="85.263146" height="36.026683" stroke="#0080ff" stroke-linecap="round"
stroke-linejoin="round" stroke-width="2"/><text transform="translate(330.78587
58.986193)" fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="7.543573" y="15"
textLength="60.176">dormant</tspan></text><rect x="468.56405" y="142.10744"
width="112.8836" height="36.026683" stroke="#0080ff" stroke-linecap="round"
stroke-linejoin="round" stroke-width="2"/><text transform="translate(473.56405
150.89678)" fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="9.801801" y="15"
textLength="83.28">questioning</tspan></text><line x1="135.106906"
y1="134.351596" x2="190.93937" y2="150.77291"
marker-end="url(#FilledArrow_Marker)" stroke="black" stroke-linecap="round"
stroke-linejoin="round" stroke-width="1"/><line x1="286.65074" y1="185.94232"
x2="329.67024" y2="205.99944" marker-end="url(#FilledArrow_Marker)"
stroke="black" stroke-linecap="round" stroke-linejoin="round"
stroke-width="1"/><path d="M 379.93472 206.75285 C 387.55754 192.63012 401.66897
174.0594 426.21202 163.52488 C 436.33446 159.18006 447.11932 156.67954 457.70464
155.39871" marker-end="url(#FilledArrow_Marker)" stroke="black"
stroke-linecap="round" stroke-linejoin="round" stroke-width="1"/><line
x1="582.44766" y1="148.95154" x2="603.2104" y2="144.91434"
marker-end="url(#FilledArrow_Marker)" stroke="black" stroke-linecap="round"
stroke-linejoin="round" stroke-width="1"/><path d="M 501.44774 179.13413 C
487.32306 189.48841 467.98586 202.01855 446.6366 211.18222 C 435.19097 216.09499
424.5888 219.42992 415.18313 221.6778" marker-end="url(#FilledArrow_Marker)"
stroke="black" stroke-linecap="round" stroke-linejoin="round"
stroke-width="1"/><path d="M 412.04903 66.0841 C 438.72737 66.23414 475.24547
68.794908 514.7185 78.42248 C 552.22946 87.57149 584.04206 101.061534 607.12235
112.71587" marker-end="url(#FilledArrow_Marker)" stroke="black"
stroke-linecap="round" stroke-linejoin="round" stroke-width="1"/><path d="M
135.10692 119.41541 C 165.84715 119.854806 204.35783 118.583695 242.39084
112.46344 C 276.08222 107.04184 303.03701 98.838735 323.23284 90.96218"
marker-end="url(#FilledArrow_Marker)" stroke="black" stroke-linecap="round"
stroke-linejoin="round" stroke-width="1"/><path d="M 324.78586 66.603523 C
301.6689 66.933135 270.15767 68.9068 232.17855 75.018384 C 200.11208 80.178506
169.19774 87.361075 143.238715 94.26646" marker-end="url(#FilledArrow_Marker)"
stroke="black" stroke-linecap="round" stroke-linejoin="round"
stroke-width="1"/><rect x="707.0446" y="118.27877" width="85.263146"
height="36.026683" stroke="red" stroke-linecap="round" stroke-linejoin="round"
stroke-width="2"/><text transform="translate(712.0446 127.06811)"
fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="7.255573" y="15" textLength="13.92">ar</tspan><tspan
font-family="Helvetica Neue" font-size="16" font-weight="500" x="20.887573"
y="15" textLength="47.12">chived</tspan></text><line x1="682.1782"
y1="136.29211" x2="696.1446" y2="136.29211"
marker-end="url(#FilledArrow_Marker)" stroke="black" stroke-linecap="round"
stroke-linejoin="round" stroke-width="1"/></g></g></svg>
<?xml version="1.0" encoding="UTF-8"?>
<svg width="510.24pt" height="184.25pt" version="1.1" viewBox="0 0 510.24 184.25" xmlns="http://www.w3.org/2000/svg">
<style>
text {
fill: white;
font-family: "Helvetica Neue";
}
</style>
<defs>
<marker id="a" color="black" overflow="visible" markerHeight="6" markerWidth="7" orient="auto" viewBox="-1 -3 7 6">
<path d="m4.8 0-4.8-1.8v3.6z" fill="currentColor" stroke="currentColor"/>
</marker>
</defs>
<g fill="none">
<title>Canvas 1</title>
<rect width="510.24" height="184.25" fill="#fff"/>
<g>
<title>Layer 1</title>
<rect x="5.6693" y="5.6693" width="116.22" height="48.189" fill="#fd8008"/>
<text transform="translate(63.7793 29.7638)" dominant-baseline="middle" text-anchor="middle">experimental</text>
<rect x="161.57" y="113.39" width="150.24" height="68.031" fill="#108001"/>
<text transform="translate(236.69 147.4055)" dominant-baseline="middle" text-anchor="middle" font-size="19">stable</text>
<path d="m63.356 53.858c2.0388 19.203 10.427 45.968 38.691 65.197 13.679 9.3061 30.217 15.625 46.951 19.9" marker-end="url(#a)" stroke="#000" stroke-linecap="round" stroke-linejoin="round" stroke-width="2"/>
<path d="m311.81 131.57c18.392-5.7638 38.128-13.509 56.693-23.85 25.216-14.046 43.275-30.1 55.731-43.973" marker-end="url(#a)" stroke="#000" stroke-linecap="round" stroke-linejoin="round" stroke-width="2"/>
<rect x="391.18" y="119.06" width="113.39" height="48.189" fill="#074080"/>
<text transform="translate(447.875 143.1545)" dominant-baseline="middle" text-anchor="middle">superseded</text>
<line x1="311.81" x2="378.29" y1="147.22" y2="145.23" marker-end="url(#a)" stroke="#000" stroke-linecap="round" stroke-linejoin="round" stroke-width="2"/>
<rect x="391.18" y="5.6693" width="113.39" height="48.189" fill="#fd8008"/>
<text transform="translate(447.875 29.7638)" dominant-baseline="middle" text-anchor="middle">deprecated</text>
</g>
</g>
</svg>

Before

Width:  |  Height:  |  Size: 6.0 KiB

After

Width:  |  Height:  |  Size: 1.9 KiB

View File

@ -81,7 +81,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.5.0.9024</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.5.0.9026</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-1509024" class="section level1">
<h1 class="page-header" data-toc-text="1.5.0.9024">
<a href="#amr-1509024" class="anchor"></a>AMR 1.5.0.9024<small> Unreleased </small>
<div id="amr-1509026" class="section level1">
<h1 class="page-header" data-toc-text="1.5.0.9026">
<a href="#amr-1509026" class="anchor"></a>AMR 1.5.0.9026<small> Unreleased </small>
</h1>
<div id="last-updated-22-february-2021" class="section level2">
<div id="last-updated-25-february-2021" class="section level2">
<h2 class="hasAnchor">
<a href="#last-updated-22-february-2021" class="anchor"></a><small>Last updated: 22 February 2021</small>
<a href="#last-updated-25-february-2021" class="anchor"></a><small>Last updated: 25 February 2021</small>
</h2>
<div id="new" class="section level3">
<h3 class="hasAnchor">
@ -280,6 +280,7 @@
</li>
<li><p>Support for custom MDRO guidelines, using the new <code><a href="../reference/mdro.html">custom_mdro_guideline()</a></code> function, please see <code><a href="../reference/mdro.html">mdro()</a></code> for additional info</p></li>
<li><p>Function <code><a href="../reference/isolate_identifier.html">isolate_identifier()</a></code>, which will paste a microorganism code with all antimicrobial results of a data set into one string for each row. This is useful to compare isolates, e.g. between institutions or regions, when there is no genotyping available.</p></li>
<li><p><code><a href="https://ggplot2.tidyverse.org/reference/ggplot.html">ggplot()</a></code> generics for classes <code>&lt;mic&gt;</code> and <code>&lt;disk&gt;</code></p></li>
<li>
<p>Function <code><a href="../reference/mo_property.html">mo_is_yeast()</a></code>, which determines whether a microorganism is a member of the taxonomic class Saccharomycetes or the taxonomic order Saccharomycetales:</p>
<div class="sourceCode" id="cb2"><pre class="downlit sourceCode r">
@ -321,7 +322,8 @@
<code><a href="../reference/as.rsi.html">is.rsi.eligible()</a></code> now detects if the column name resembles an antibiotic name or code and now returns <code>TRUE</code> immediately if the input contains any of the values “R”, “S” or “I”. This drastically improves speed, also for a lot of other functions that rely on automatic determination of antibiotic columns.</li>
<li>Functions <code><a href="../reference/get_episode.html">get_episode()</a></code> and <code><a href="../reference/get_episode.html">is_new_episode()</a></code> now support less than a day as value for argument <code>episode_days</code> (e.g., to include one patient/test per hour)</li>
<li>Argument <code>ampc_cephalosporin_resistance</code> in <code><a href="../reference/eucast_rules.html">eucast_rules()</a></code> now also applies to value “I” (not only “S”)</li>
<li>Updated colours of values R, S and I in tibble printing</li>
<li>Updated <code><a href="../reference/plot.html">plot()</a></code> functions for classes <code>&lt;mic&gt;</code>, <code>&lt;disk&gt;</code> and <code>&lt;rsi&gt;</code> - the former two now support colouring if you supply the microorganism and antimicrobial agent</li>
<li>Updated colours to colour-blind friendly version for values R, S and I in tibble printing and for all plot methods (<code><a href="../reference/ggplot_rsi.html">ggplot_rsi()</a></code> and using <code><a href="../reference/plot.html">plot()</a></code> on classes <code>&lt;mic&gt;</code>, <code>&lt;disk&gt;</code> and <code>&lt;rsi&gt;</code>)</li>
<li>Functions <code><a href="https://rdrr.io/r/base/print.html">print()</a></code> and <code><a href="https://rdrr.io/r/base/summary.html">summary()</a></code> on a Principal Components Analysis object (<code><a href="../reference/pca.html">pca()</a></code>) now print additional group info if the original data was grouped using <code><a href="https://dplyr.tidyverse.org/reference/group_by.html">dplyr::group_by()</a></code>
</li>
<li>Improved speed and reliability of <code><a href="../reference/guess_ab_col.html">guess_ab_col()</a></code>. As this also internally improves the reliability of <code><a href="../reference/first_isolate.html">first_isolate()</a></code> and <code><a href="../reference/mdro.html">mdro()</a></code>, this might have a slight impact on the results of those functions.</li>
@ -329,6 +331,10 @@
<li>The <code><a href="../reference/like.html">like()</a></code> function (and its fast alias <code><a href="../reference/like.html">%like%</a></code>) now always use Perl compatibility, improving speed for many functions in this package (e.g., <code><a href="../reference/as.mo.html">as.mo()</a></code> is now up to 4 times faster)</li>
<li>
<em>Staphylococcus cornubiensis</em> is now correctly categorised as coagulase-positive</li>
<li>
<code><a href="../reference/random.html">random_disk()</a></code> and <code><a href="../reference/random.html">random_mic()</a></code> now have an expanded range in their randomisation</li>
<li>Support for GISA (glycopeptide-intermediate <em>S. aureus</em>), so e.g. <code><a href="../reference/mo_property.html">mo_genus("GISA")</a></code> will return <code>"Staphylococcus"</code>
</li>
</ul>
</div>
<div id="other" class="section level3">
@ -655,7 +661,7 @@
<p>Making this package independent of especially the tidyverse (e.g. packages <code>dplyr</code> and <code>tidyr</code>) tremendously increases sustainability on the long term, since tidyverse functions change quite often. Good for users, but hard for package maintainers. Most of our functions are replaced with versions that only rely on base R, which keeps this package fully functional for many years to come, without requiring a lot of maintenance to keep up with other packages anymore. Another upside it that this package can now be used with all versions of R since R-3.0.0 (April 2013). Our package is being used in settings where the resources are very limited. Fewer dependencies on newer software is helpful for such settings.</p>
<p>Negative effects of this change are:</p>
<ul>
<li>Function <code>freq()</code> that was borrowed from the <code>cleaner</code> package was removed. Use <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">cleaner::freq()</a></code>, or run <code><a href="https://github.com/msberends/cleaner">library("cleaner")</a></code> before you use <code>freq()</code>.</li>
<li>Function <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq()</a></code> that was borrowed from the <code>cleaner</code> package was removed. Use <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">cleaner::freq()</a></code>, or run <code><a href="https://github.com/msberends/cleaner">library("cleaner")</a></code> before you use <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq()</a></code>.</li>
<li><del>Printing values of class <code>mo</code> or <code>rsi</code> in a tibble will no longer be in colour and printing <code>rsi</code> in a tibble will show the class <code>&lt;ord&gt;</code>, not <code>&lt;rsi&gt;</code> anymore. This is purely a visual effect.</del></li>
<li><del>All functions from the <code>mo_*</code> family (like <code><a href="../reference/mo_property.html">mo_name()</a></code> and <code><a href="../reference/mo_property.html">mo_gramstain()</a></code>) are noticeably slower when running on hundreds of thousands of rows.</del></li>
<li>For developers: classes <code>mo</code> and <code>ab</code> now both also inherit class <code>character</code>, to support any data transformation. This change invalidates code that checks for class length == 1.</li>
@ -992,7 +998,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<span class="co">#&gt; invalid microorganism code, NA generated</span></code></pre></div>
<p>This is important, because a value like <code>"testvalue"</code> could never be understood by e.g. <code><a href="../reference/mo_property.html">mo_name()</a></code>, although the class would suggest a valid microbial code.</p>
</li>
<li><p>Function <code>freq()</code> has moved to a new package, <a href="https://github.com/msberends/clean"><code>clean</code></a> (<a href="https://cran.r-project.org/package=clean">CRAN link</a>), since creating frequency tables actually does not fit the scope of this package. The <code>freq()</code> function still works, since it is re-exported from the <code>clean</code> package (which will be installed automatically upon updating this <code>AMR</code> package).</p></li>
<li><p>Function <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq()</a></code> has moved to a new package, <a href="https://github.com/msberends/clean"><code>clean</code></a> (<a href="https://cran.r-project.org/package=clean">CRAN link</a>), since creating frequency tables actually does not fit the scope of this package. The <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq()</a></code> function still works, since it is re-exported from the <code>clean</code> package (which will be installed automatically upon updating this <code>AMR</code> package).</p></li>
<li><p>Renamed data set <code>septic_patients</code> to <code>example_isolates</code></p></li>
</ul>
</div>
@ -1261,7 +1267,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<li>The <code><a href="../reference/age.html">age()</a></code> function gained a new argument <code>exact</code> to determine ages with decimals</li>
<li>Removed deprecated functions <code>guess_mo()</code>, <code>guess_atc()</code>, <code>EUCAST_rules()</code>, <code>interpretive_reading()</code>, <code><a href="../reference/as.rsi.html">rsi()</a></code>
</li>
<li>Frequency tables (<code>freq()</code>):
<li>Frequency tables (<code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq()</a></code>):
<ul>
<li><p>speed improvement for microbial IDs</p></li>
<li><p>fixed factor level names for R Markdown</p></li>
@ -1271,12 +1277,12 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<div class="sourceCode" id="cb26"><pre class="downlit sourceCode r">
<code class="sourceCode R">
<span class="va">septic_patients</span> <span class="op">%&gt;%</span>
<span class="fu">freq</span><span class="op">(</span><span class="va">age</span><span class="op">)</span> <span class="op">%&gt;%</span>
<span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span><span class="op">(</span><span class="va">age</span><span class="op">)</span> <span class="op">%&gt;%</span>
<span class="fu"><a href="https://rdrr.io/r/graphics/boxplot.html">boxplot</a></span><span class="op">(</span><span class="op">)</span>
<span class="co"># grouped boxplots:</span>
<span class="va">septic_patients</span> <span class="op">%&gt;%</span>
<span class="fu"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span><span class="op">(</span><span class="va">hospital_id</span><span class="op">)</span> <span class="op">%&gt;%</span>
<span class="fu">freq</span><span class="op">(</span><span class="va">age</span><span class="op">)</span> <span class="op">%&gt;%</span>
<span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span><span class="op">(</span><span class="va">age</span><span class="op">)</span> <span class="op">%&gt;%</span>
<span class="fu"><a href="https://rdrr.io/r/graphics/boxplot.html">boxplot</a></span><span class="op">(</span><span class="op">)</span></code></pre></div>
</li>
</ul>
@ -1286,7 +1292,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<li>Added ceftazidim intrinsic resistance to <em>Streptococci</em>
</li>
<li>Changed default settings for <code><a href="../reference/age_groups.html">age_groups()</a></code>, to let groups of fives and tens end with 100+ instead of 120+</li>
<li>Fix for <code>freq()</code> for when all values are <code>NA</code>
<li>Fix for <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq()</a></code> for when all values are <code>NA</code>
</li>
<li>Fix for <code><a href="../reference/first_isolate.html">first_isolate()</a></code> for when dates are missing</li>
<li>Improved speed of <code><a href="../reference/guess_ab_col.html">guess_ab_col()</a></code>
@ -1527,7 +1533,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
</li>
</ul>
</li>
<li>Frequency tables (<code>freq()</code> function):
<li>Frequency tables (<code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq()</a></code> function):
<ul>
<li>
<p>Support for tidyverse quasiquotation! Now you can create frequency tables of function outcomes:</p>
@ -1537,15 +1543,15 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<span class="co"># OLD WAY</span>
<span class="va">septic_patients</span> <span class="op">%&gt;%</span>
<span class="fu"><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate</a></span><span class="op">(</span>genus <span class="op">=</span> <span class="fu"><a href="../reference/mo_property.html">mo_genus</a></span><span class="op">(</span><span class="va">mo</span><span class="op">)</span><span class="op">)</span> <span class="op">%&gt;%</span>
<span class="fu">freq</span><span class="op">(</span><span class="va">genus</span><span class="op">)</span>
<span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span><span class="op">(</span><span class="va">genus</span><span class="op">)</span>
<span class="co"># NEW WAY</span>
<span class="va">septic_patients</span> <span class="op">%&gt;%</span>
<span class="fu">freq</span><span class="op">(</span><span class="fu"><a href="../reference/mo_property.html">mo_genus</a></span><span class="op">(</span><span class="va">mo</span><span class="op">)</span><span class="op">)</span>
<span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span><span class="op">(</span><span class="fu"><a href="../reference/mo_property.html">mo_genus</a></span><span class="op">(</span><span class="va">mo</span><span class="op">)</span><span class="op">)</span>
<span class="co"># Even supports grouping variables:</span>
<span class="va">septic_patients</span> <span class="op">%&gt;%</span>
<span class="fu"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span><span class="op">(</span><span class="va">gender</span><span class="op">)</span> <span class="op">%&gt;%</span>
<span class="fu">freq</span><span class="op">(</span><span class="fu"><a href="../reference/mo_property.html">mo_genus</a></span><span class="op">(</span><span class="va">mo</span><span class="op">)</span><span class="op">)</span></code></pre></div>
<span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span><span class="op">(</span><span class="fu"><a href="../reference/mo_property.html">mo_genus</a></span><span class="op">(</span><span class="va">mo</span><span class="op">)</span><span class="op">)</span></code></pre></div>
</li>
<li><p>Header info is now available as a list, with the <code>header</code> function</p></li>
<li><p>The argument <code>header</code> is now set to <code>TRUE</code> at default, even for markdown</p></li>
@ -1628,7 +1634,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<li><p>Using <code>portion_*</code> functions now throws a warning when total available isolate is below argument <code>minimum</code></p></li>
<li><p>Functions <code>as.mo</code>, <code>as.rsi</code>, <code>as.mic</code>, <code>as.atc</code> and <code>freq</code> will not set package name as attribute anymore</p></li>
<li>
<p>Frequency tables - <code>freq()</code>:</p>
<p>Frequency tables - <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq()</a></code>:</p>
<ul>
<li>
<p>Support for grouping variables, test with:</p>
@ -1636,14 +1642,14 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<code class="sourceCode R">
<span class="va">septic_patients</span> <span class="op">%&gt;%</span>
<span class="fu"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span><span class="op">(</span><span class="va">hospital_id</span><span class="op">)</span> <span class="op">%&gt;%</span>
<span class="fu">freq</span><span class="op">(</span><span class="va">gender</span><span class="op">)</span></code></pre></div>
<span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span><span class="op">(</span><span class="va">gender</span><span class="op">)</span></code></pre></div>
</li>
<li>
<p>Support for (un)selecting columns:</p>
<div class="sourceCode" id="cb39"><pre class="downlit sourceCode r">
<code class="sourceCode R">
<span class="va">septic_patients</span> <span class="op">%&gt;%</span>
<span class="fu">freq</span><span class="op">(</span><span class="va">hospital_id</span><span class="op">)</span> <span class="op">%&gt;%</span>
<span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span><span class="op">(</span><span class="va">hospital_id</span><span class="op">)</span> <span class="op">%&gt;%</span>
<span class="fu"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span><span class="op">(</span><span class="op">-</span><span class="va">count</span>, <span class="op">-</span><span class="va">cum_count</span><span class="op">)</span> <span class="co"># only get item, percent, cum_percent</span></code></pre></div>
</li>
<li><p>Check for <code><a href="https://hms.tidyverse.org/reference/Deprecated.html">hms::is.hms</a></code></p></li>
@ -1661,7 +1667,7 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<li><p>Removed diacritics from all authors (columns <code>microorganisms$ref</code> and <code>microorganisms.old$ref</code>) to comply with CRAN policy to only allow ASCII characters</p></li>
<li><p>Fix for <code>mo_property</code> not working properly</p></li>
<li><p>Fix for <code>eucast_rules</code> where some Streptococci would become ceftazidime R in EUCAST rule 4.5</p></li>
<li><p>Support for named vectors of class <code>mo</code>, useful for <code>top_freq()</code></p></li>
<li><p>Support for named vectors of class <code>mo</code>, useful for <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">top_freq()</a></code></p></li>
<li><p><code>ggplot_rsi</code> and <code>scale_y_percent</code> have <code>breaks</code> argument</p></li>
<li>
<p>AI improvements for <code>as.mo</code>:</p>
@ -1829,13 +1835,13 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<div class="sourceCode" id="cb46"><pre class="downlit sourceCode r">
<code class="sourceCode R">
<span class="va">my_matrix</span> <span class="op">=</span> <span class="fu"><a href="https://rdrr.io/r/base/with.html">with</a></span><span class="op">(</span><span class="va">septic_patients</span>, <span class="fu"><a href="https://rdrr.io/r/base/matrix.html">matrix</a></span><span class="op">(</span><span class="fu"><a href="https://rdrr.io/r/base/c.html">c</a></span><span class="op">(</span><span class="va">age</span>, <span class="va">gender</span><span class="op">)</span>, ncol <span class="op">=</span> <span class="fl">2</span><span class="op">)</span><span class="op">)</span>
<span class="fu">freq</span><span class="op">(</span><span class="va">my_matrix</span><span class="op">)</span></code></pre></div>
<span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span><span class="op">(</span><span class="va">my_matrix</span><span class="op">)</span></code></pre></div>
<p>For lists, subsetting is possible:</p>
<div class="sourceCode" id="cb47"><pre class="downlit sourceCode r">
<code class="sourceCode R">
<span class="va">my_list</span> <span class="op">=</span> <span class="fu"><a href="https://rdrr.io/r/base/list.html">list</a></span><span class="op">(</span>age <span class="op">=</span> <span class="va">septic_patients</span><span class="op">$</span><span class="va">age</span>, gender <span class="op">=</span> <span class="va">septic_patients</span><span class="op">$</span><span class="va">gender</span><span class="op">)</span>
<span class="va">my_list</span> <span class="op">%&gt;%</span> <span class="fu">freq</span><span class="op">(</span><span class="va">age</span><span class="op">)</span>
<span class="va">my_list</span> <span class="op">%&gt;%</span> <span class="fu">freq</span><span class="op">(</span><span class="va">gender</span><span class="op">)</span></code></pre></div>
<span class="va">my_list</span> <span class="op">%&gt;%</span> <span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span><span class="op">(</span><span class="va">age</span><span class="op">)</span>
<span class="va">my_list</span> <span class="op">%&gt;%</span> <span class="fu"><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq</a></span><span class="op">(</span><span class="va">gender</span><span class="op">)</span></code></pre></div>
</li>
</ul>
</div>
@ -1909,13 +1915,13 @@ This works for all drug combinations, such as ampicillin/sulbactam, ceftazidime/
<ul>
<li>A vignette to explain its usage</li>
<li>Support for <code>rsi</code> (antimicrobial resistance) to use as input</li>
<li>Support for <code>table</code> to use as input: <code>freq(table(x, y))</code>
<li>Support for <code>table</code> to use as input: <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq(table(x, y))</a></code>
</li>
<li>Support for existing functions <code>hist</code> and <code>plot</code> to use a frequency table as input: <code><a href="https://rdrr.io/r/graphics/hist.html">hist(freq(df$age))</a></code>
</li>
<li>Support for <code>as.vector</code>, <code>as.data.frame</code>, <code>as_tibble</code> and <code>format</code>
</li>
<li>Support for quasiquotation: <code>freq(mydata, mycolumn)</code> is the same as <code>mydata %&gt;% freq(mycolumn)</code>
<li>Support for quasiquotation: <code><a href="https://rdrr.io/pkg/cleaner/man/freq.html">freq(mydata, mycolumn)</a></code> is the same as <code>mydata %&gt;% freq(mycolumn)</code>
</li>
<li>Function <code>top_freq</code> function to return the top/below <em>n</em> items as vector</li>
<li>Header of frequency tables now also show Mean Absolute Deviaton (MAD) and Interquartile Range (IQR)</li>

View File

@ -12,7 +12,7 @@ articles:
datasets: datasets.html
resistance_predict: resistance_predict.html
welcome_to_AMR: welcome_to_AMR.html
last_built: 2021-02-22T19:20Z
last_built: 2021-02-25T11:30Z
urls:
reference: https://msberends.github.io/AMR//reference
article: https://msberends.github.io/AMR//articles

View File

@ -82,7 +82,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.5.0.9016</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.5.0.9025</span>
</span>
</div>
@ -298,8 +298,9 @@ The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>stable</s
ab <span class='op'>=</span> <span class='st'>"AMX"</span>,
guideline <span class='op'>=</span> <span class='st'>"EUCAST"</span><span class='op'>)</span>
<span class='co'># plot MIC values, see ?plot</span>
<span class='fu'><a href='plot.html'>plot</a></span><span class='op'>(</span><span class='va'>mic_data</span><span class='op'>)</span>
<span class='fu'><a href='https://rdrr.io/r/graphics/barplot.html'>barplot</a></span><span class='op'>(</span><span class='va'>mic_data</span><span class='op'>)</span>
<span class='fu'><a href='plot.html'>plot</a></span><span class='op'>(</span><span class='va'>mic_data</span>, mo <span class='op'>=</span> <span class='st'>"E. coli"</span>, ab <span class='op'>=</span> <span class='st'>"cipro"</span><span class='op'>)</span>
</pre>
</div>
<div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar">

View File

@ -1,88 +1,32 @@
<?xml version="1.0"?> <!DOCTYPE svg PUBLIC "-//W3C//DTD SVG 1.1//EN"
"http://www.w3.org/Graphics/SVG/1.1/DTD/svg11.dtd"> <svg
xmlns="http://www.w3.org/2000/svg" xmlns:xl="http://www.w3.org/1999/xlink"
version="1.1" viewBox="8 48 787 198" width="787pt" height="198pt"><metadata
xmlns:dc="http://purl.org/dc/elements/1.1/"><dc:date>2018-01-05
19:43Z</dc:date><!-- Produced by OmniGraffle Professional 5.4.4
--></metadata><defs><font-face font-family="Helvetica Neue" font-size="16"
panose-1="2 0 5 3 0 0 0 2 0 4" units-per-em="1000" underline-position="-100"
underline-thickness="50" slope="0" x-height="517" cap-height="714"
ascent="951.99585" descent="-212.99744"
font-weight="500"><font-face-src><font-face-name
name="HelveticaNeue"/></font-face-src></font-face><marker orient="auto"
overflow="visible" markerUnits="strokeWidth" id="FilledArrow_Marker" viewBox="-1
-4 10 8" markerWidth="10" markerHeight="8" color="black"><g><path d="M 8 0 L 0
-3 L 0 3 Z" fill="currentColor" stroke="currentColor"
stroke-width="1"/></g></marker></defs><g stroke="none" stroke-opacity="1"
stroke-dasharray="none" fill="none" fill-opacity="1"><title>Canvas
1</title><rect fill="white" width="805.88977"
height="536.27556"/><g><title>Layer 1</title><rect x="201.43709" y="148.91563"
width="88.865815" height="36.026683" stroke="#0080ff" stroke-linecap="round"
stroke-linejoin="round" stroke-width="2"/><text transform="translate(206.43709
157.70498)" fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="7.8649073" y="15"
textLength="63.136">maturing</tspan></text><rect x="10.4153" y="97.854194"
width="123.69161" height="36.026683" stroke="#ff8000" stroke-linecap="round"
stroke-linejoin="round" stroke-width="2"/><text transform="translate(15.4153
106.643536)" fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="10.7658034" y="15"
textLength="92.160004">experimental</tspan></text><rect x="339.64294"
y="207.75286" width="64.848027" height="36.026683" stroke="green"
stroke-linecap="round" stroke-linejoin="round" stroke-width="2"/><text
transform="translate(344.64294 216.5422)" fill="black"><tspan
font-family="Helvetica Neue" font-size="16" font-weight="500" x="5.7920134"
y="15" textLength="43.264">stable</tspan></text><rect x="613.9284" y="118.27877"
width="67.249806" height="36.026683" stroke="#ff8000" stroke-linecap="round"
stroke-linejoin="round" stroke-width="2"/><text transform="translate(618.9284
127.06811)" fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="5.9529028" y="15" textLength="5.328">r</tspan><tspan
font-family="Helvetica Neue" font-size="16" font-weight="500" x="10.992903"
y="15" textLength="22.511999">etir</tspan><tspan font-family="Helvetica Neue"
font-size="16" font-weight="500" x="33.216903" y="15"
textLength="18.08">ed</tspan></text><rect x="325.78587" y="50.19685"
width="85.263146" height="36.026683" stroke="#0080ff" stroke-linecap="round"
stroke-linejoin="round" stroke-width="2"/><text transform="translate(330.78587
58.986193)" fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="7.543573" y="15"
textLength="60.176">dormant</tspan></text><rect x="468.56405" y="142.10744"
width="112.8836" height="36.026683" stroke="#0080ff" stroke-linecap="round"
stroke-linejoin="round" stroke-width="2"/><text transform="translate(473.56405
150.89678)" fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="9.801801" y="15"
textLength="83.28">questioning</tspan></text><line x1="135.106906"
y1="134.351596" x2="190.93937" y2="150.77291"
marker-end="url(#FilledArrow_Marker)" stroke="black" stroke-linecap="round"
stroke-linejoin="round" stroke-width="1"/><line x1="286.65074" y1="185.94232"
x2="329.67024" y2="205.99944" marker-end="url(#FilledArrow_Marker)"
stroke="black" stroke-linecap="round" stroke-linejoin="round"
stroke-width="1"/><path d="M 379.93472 206.75285 C 387.55754 192.63012 401.66897
174.0594 426.21202 163.52488 C 436.33446 159.18006 447.11932 156.67954 457.70464
155.39871" marker-end="url(#FilledArrow_Marker)" stroke="black"
stroke-linecap="round" stroke-linejoin="round" stroke-width="1"/><line
x1="582.44766" y1="148.95154" x2="603.2104" y2="144.91434"
marker-end="url(#FilledArrow_Marker)" stroke="black" stroke-linecap="round"
stroke-linejoin="round" stroke-width="1"/><path d="M 501.44774 179.13413 C
487.32306 189.48841 467.98586 202.01855 446.6366 211.18222 C 435.19097 216.09499
424.5888 219.42992 415.18313 221.6778" marker-end="url(#FilledArrow_Marker)"
stroke="black" stroke-linecap="round" stroke-linejoin="round"
stroke-width="1"/><path d="M 412.04903 66.0841 C 438.72737 66.23414 475.24547
68.794908 514.7185 78.42248 C 552.22946 87.57149 584.04206 101.061534 607.12235
112.71587" marker-end="url(#FilledArrow_Marker)" stroke="black"
stroke-linecap="round" stroke-linejoin="round" stroke-width="1"/><path d="M
135.10692 119.41541 C 165.84715 119.854806 204.35783 118.583695 242.39084
112.46344 C 276.08222 107.04184 303.03701 98.838735 323.23284 90.96218"
marker-end="url(#FilledArrow_Marker)" stroke="black" stroke-linecap="round"
stroke-linejoin="round" stroke-width="1"/><path d="M 324.78586 66.603523 C
301.6689 66.933135 270.15767 68.9068 232.17855 75.018384 C 200.11208 80.178506
169.19774 87.361075 143.238715 94.26646" marker-end="url(#FilledArrow_Marker)"
stroke="black" stroke-linecap="round" stroke-linejoin="round"
stroke-width="1"/><rect x="707.0446" y="118.27877" width="85.263146"
height="36.026683" stroke="red" stroke-linecap="round" stroke-linejoin="round"
stroke-width="2"/><text transform="translate(712.0446 127.06811)"
fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="7.255573" y="15" textLength="13.92">ar</tspan><tspan
font-family="Helvetica Neue" font-size="16" font-weight="500" x="20.887573"
y="15" textLength="47.12">chived</tspan></text><line x1="682.1782"
y1="136.29211" x2="696.1446" y2="136.29211"
marker-end="url(#FilledArrow_Marker)" stroke="black" stroke-linecap="round"
stroke-linejoin="round" stroke-width="1"/></g></g></svg>
<?xml version="1.0" encoding="UTF-8"?>
<svg width="510.24pt" height="184.25pt" version="1.1" viewBox="0 0 510.24 184.25" xmlns="http://www.w3.org/2000/svg">
<style>
text {
fill: white;
font-family: "Helvetica Neue";
}
</style>
<defs>
<marker id="a" color="black" overflow="visible" markerHeight="6" markerWidth="7" orient="auto" viewBox="-1 -3 7 6">
<path d="m4.8 0-4.8-1.8v3.6z" fill="currentColor" stroke="currentColor"/>
</marker>
</defs>
<g fill="none">
<title>Canvas 1</title>
<rect width="510.24" height="184.25" fill="#fff"/>
<g>
<title>Layer 1</title>
<rect x="5.6693" y="5.6693" width="116.22" height="48.189" fill="#fd8008"/>
<text transform="translate(63.7793 29.7638)" dominant-baseline="middle" text-anchor="middle">experimental</text>
<rect x="161.57" y="113.39" width="150.24" height="68.031" fill="#108001"/>
<text transform="translate(236.69 147.4055)" dominant-baseline="middle" text-anchor="middle" font-size="19">stable</text>
<path d="m63.356 53.858c2.0388 19.203 10.427 45.968 38.691 65.197 13.679 9.3061 30.217 15.625 46.951 19.9" marker-end="url(#a)" stroke="#000" stroke-linecap="round" stroke-linejoin="round" stroke-width="2"/>
<path d="m311.81 131.57c18.392-5.7638 38.128-13.509 56.693-23.85 25.216-14.046 43.275-30.1 55.731-43.973" marker-end="url(#a)" stroke="#000" stroke-linecap="round" stroke-linejoin="round" stroke-width="2"/>
<rect x="391.18" y="119.06" width="113.39" height="48.189" fill="#074080"/>
<text transform="translate(447.875 143.1545)" dominant-baseline="middle" text-anchor="middle">superseded</text>
<line x1="311.81" x2="378.29" y1="147.22" y2="145.23" marker-end="url(#a)" stroke="#000" stroke-linecap="round" stroke-linejoin="round" stroke-width="2"/>
<rect x="391.18" y="5.6693" width="113.39" height="48.189" fill="#fd8008"/>
<text transform="translate(447.875 29.7638)" dominant-baseline="middle" text-anchor="middle">deprecated</text>
</g>
</g>
</svg>

Before

Width:  |  Height:  |  Size: 6.0 KiB

After

Width:  |  Height:  |  Size: 1.9 KiB

View File

@ -82,7 +82,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.5.0.9016</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.5.0.9026</span>
</span>
</div>
@ -256,8 +256,8 @@
minimum <span class='op'>=</span> <span class='fl'>30</span>,
language <span class='op'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span><span class='op'>(</span><span class='op'>)</span>,
nrow <span class='op'>=</span> <span class='cn'>NULL</span>,
colours <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span>S <span class='op'>=</span> <span class='st'>"#61a8ff"</span>, SI <span class='op'>=</span> <span class='st'>"#61a8ff"</span>, I <span class='op'>=</span> <span class='st'>"#61f7ff"</span>, IR <span class='op'>=</span> <span class='st'>"#ff6961"</span>, R <span class='op'>=</span>
<span class='st'>"#ff6961"</span><span class='op'>)</span>,
colours <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span>S <span class='op'>=</span> <span class='st'>"#3CAEA3"</span>, SI <span class='op'>=</span> <span class='st'>"#3CAEA3"</span>, I <span class='op'>=</span> <span class='st'>"#F6D55C"</span>, IR <span class='op'>=</span> <span class='st'>"#ED553B"</span>, R <span class='op'>=</span>
<span class='st'>"#ED553B"</span><span class='op'>)</span>,
datalabels <span class='op'>=</span> <span class='cn'>TRUE</span>,
datalabels.size <span class='op'>=</span> <span class='fl'>2.5</span>,
datalabels.colour <span class='op'>=</span> <span class='st'>"grey15"</span>,
@ -286,8 +286,9 @@
<span class='fu'>scale_y_percent</span><span class='op'>(</span>breaks <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/seq.html'>seq</a></span><span class='op'>(</span><span class='fl'>0</span>, <span class='fl'>1</span>, <span class='fl'>0.1</span><span class='op'>)</span>, limits <span class='op'>=</span> <span class='cn'>NULL</span><span class='op'>)</span>
<span class='fu'>scale_rsi_colours</span><span class='op'>(</span>
colours <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span>S <span class='op'>=</span> <span class='st'>"#61a8ff"</span>, SI <span class='op'>=</span> <span class='st'>"#61a8ff"</span>, I <span class='op'>=</span> <span class='st'>"#61f7ff"</span>, IR <span class='op'>=</span> <span class='st'>"#ff6961"</span>, R <span class='op'>=</span>
<span class='st'>"#ff6961"</span><span class='op'>)</span>
colours <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span>S <span class='op'>=</span> <span class='st'>"#3CAEA3"</span>, SI <span class='op'>=</span> <span class='st'>"#3CAEA3"</span>, I <span class='op'>=</span> <span class='st'>"#F6D55C"</span>, IR <span class='op'>=</span> <span class='st'>"#ED553B"</span>, R <span class='op'>=</span>
<span class='st'>"#ED553B"</span><span class='op'>)</span>,
aesthetics <span class='op'>=</span> <span class='st'>"fill"</span>
<span class='op'>)</span>
<span class='fu'>theme_rsi</span><span class='op'>(</span><span class='op'>)</span>
@ -361,7 +362,7 @@
</tr>
<tr>
<th>colours</th>
<td><p>a named vector with colours for the bars. The names must be one or more of: S, SI, I, IR, R or be <code>FALSE</code> to use default <a href='https://ggplot2.tidyverse.org/reference/ggplot.html'>ggplot2</a> colours.</p></td>
<td><p>a named vector with colours for the bars. The names must be one or more of: S, SI, I, IR, R or be <code>FALSE</code> for standard <a href='https://ggplot2.tidyverse.org/reference/ggplot.html'>ggplot2</a> colours. The default colours are colour-blind friendly, while maintaining the convention that e.g. 'susceptible' should be green and 'resistant' should be red.</p></td>
</tr>
<tr>
<th>datalabels</th>
@ -399,6 +400,10 @@
<th>...</th>
<td><p>other arguments passed on to <code>geom_rsi()</code></p></td>
</tr>
<tr>
<th>aesthetics</th>
<td><p>aesthetics to apply the colours to, defaults to "fill" but can also be "colour" or "both"</p></td>
</tr>
</table>
<h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2>
@ -479,11 +484,6 @@ The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>maturing<
<span class='va'>CIP</span><span class='op'>)</span> <span class='op'>%&gt;%</span>
<span class='fu'>ggplot_rsi</span><span class='op'>(</span>x <span class='op'>=</span> <span class='st'>"age_group"</span><span class='op'>)</span>
<span class='co'># for colourblind mode, use divergent colours from the viridis package:</span>
<span class='va'>example_isolates</span> <span class='op'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/select.html'>select</a></span><span class='op'>(</span><span class='va'>AMX</span>, <span class='va'>NIT</span>, <span class='va'>FOS</span>, <span class='va'>TMP</span>, <span class='va'>CIP</span><span class='op'>)</span> <span class='op'>%&gt;%</span>
<span class='fu'>ggplot_rsi</span><span class='op'>(</span><span class='op'>)</span> <span class='op'>+</span>
<span class='fu'><a href='https://ggplot2.tidyverse.org/reference/scale_viridis.html'>scale_fill_viridis_d</a></span><span class='op'>(</span><span class='op'>)</span>
<span class='co'># a shorter version which also adjusts data label colours:</span>
<span class='va'>example_isolates</span> <span class='op'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/select.html'>select</a></span><span class='op'>(</span><span class='va'>AMX</span>, <span class='va'>NIT</span>, <span class='va'>FOS</span>, <span class='va'>TMP</span>, <span class='va'>CIP</span><span class='op'>)</span> <span class='op'>%&gt;%</span>

View File

@ -81,7 +81,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.5.0.9024</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.5.0.9026</span>
</span>
</div>
@ -453,7 +453,7 @@
</tr><tr>
<td>
<p><code><a href="plot.html">plot(<i>&lt;disk&gt;</i>)</a></code> <code><a href="plot.html">plot(<i>&lt;mic&gt;</i>)</a></code> <code><a href="plot.html">barplot(<i>&lt;mic&gt;</i>)</a></code> <code><a href="plot.html">plot(<i>&lt;rsi&gt;</i>)</a></code> <code><a href="plot.html">barplot(<i>&lt;rsi&gt;</i>)</a></code> </p>
<p><code><a href="plot.html">plot(<i>&lt;mic&gt;</i>)</a></code> <code><a href="plot.html">ggplot(<i>&lt;mic&gt;</i>)</a></code> <code><a href="plot.html">plot(<i>&lt;disk&gt;</i>)</a></code> <code><a href="plot.html">ggplot(<i>&lt;disk&gt;</i>)</a></code> <code><a href="plot.html">plot(<i>&lt;rsi&gt;</i>)</a></code> </p>
</td>
<td><p>Plotting for Classes <code>rsi</code>, <code>mic</code> and <code>disk</code></p></td>
</tr><tr>

View File

@ -49,7 +49,7 @@
<script src="../extra.js"></script>
<meta property="og:title" content="Pattern Matching with Keyboard Shortcut — like" />
<meta property="og:description" content="Convenient wrapper around grep() to match a pattern: x %like% pattern. It always returns a logical vector and is always case-insensitive (use x %like_case% pattern for case-sensitive matching). Also, pattern can be as long as x to compare items of each index in both vectors, or they both can have the same length to iterate over all cases." />
<meta property="og:description" content="Convenient wrapper around grepl() to match a pattern: x %like% pattern. It always returns a logical vector and is always case-insensitive (use x %like_case% pattern for case-sensitive matching). Also, pattern can be as long as x to compare items of each index in both vectors, or they both can have the same length to iterate over all cases." />
<meta property="og:image" content="https://msberends.github.io/AMR/logo.png" />
@ -82,7 +82,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.5.0.9024</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.5.0.9025</span>
</span>
</div>
@ -239,7 +239,7 @@
</div>
<div class="ref-description">
<p>Convenient wrapper around <code><a href='https://rdrr.io/r/base/grep.html'>grep()</a></code> to match a pattern: <code>x %like% pattern</code>. It always returns a <code><a href='https://rdrr.io/r/base/logical.html'>logical</a></code> vector and is always case-insensitive (use <code>x %like_case% pattern</code> for case-sensitive matching). Also, <code>pattern</code> can be as long as <code>x</code> to compare items of each index in both vectors, or they both can have the same length to iterate over all cases.</p>
<p>Convenient wrapper around <code><a href='https://rdrr.io/r/base/grep.html'>grepl()</a></code> to match a pattern: <code>x %like% pattern</code>. It always returns a <code><a href='https://rdrr.io/r/base/logical.html'>logical</a></code> vector and is always case-insensitive (use <code>x %like_case% pattern</code> for case-sensitive matching). Also, <code>pattern</code> can be as long as <code>x</code> to compare items of each index in both vectors, or they both can have the same length to iterate over all cases.</p>
</div>
<pre class="usage"><span class='fu'>like</span><span class='op'>(</span><span class='va'>x</span>, <span class='va'>pattern</span>, ignore.case <span class='op'>=</span> <span class='cn'>TRUE</span><span class='op'>)</span>
@ -295,7 +295,7 @@ The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>stable</s
<p>On our website <a href='https://msberends.github.io/AMR/'>https://msberends.github.io/AMR/</a> you can find <a href='https://msberends.github.io/AMR/articles/AMR.html'>a comprehensive tutorial</a> about how to conduct AMR data analysis, the <a href='https://msberends.github.io/AMR/reference/'>complete documentation of all functions</a> and <a href='https://msberends.github.io/AMR/articles/WHONET.html'>an example analysis using WHONET data</a>. As we would like to better understand the backgrounds and needs of our users, please <a href='https://msberends.github.io/AMR/survey.html'>participate in our survey</a>!</p>
<h2 class="hasAnchor" id="see-also"><a class="anchor" href="#see-also"></a>See also</h2>
<div class='dont-index'><p><code><a href='https://rdrr.io/r/base/grep.html'>grep()</a></code></p></div>
<div class='dont-index'><p><code><a href='https://rdrr.io/r/base/grep.html'>grepl()</a></code></p></div>
<h2 class="hasAnchor" id="examples"><a class="anchor" href="#examples"></a>Examples</h2>
<pre class="examples"><span class='co'># simple test</span>
@ -306,11 +306,15 @@ The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>stable</s
<span class='va'>b</span> <span class='op'>%like%</span> <span class='va'>a</span>
<span class='co'>#&gt; FALSE</span>
<span class='co'># also supports multiple patterns, length must be equal to x</span>
<span class='co'># also supports multiple patterns</span>
<span class='va'>a</span> <span class='op'>&lt;-</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span><span class='st'>"Test case"</span>, <span class='st'>"Something different"</span>, <span class='st'>"Yet another thing"</span><span class='op'>)</span>
<span class='va'>b</span> <span class='op'>&lt;-</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span> <span class='st'>"case"</span>, <span class='st'>"diff"</span>, <span class='st'>"yet"</span><span class='op'>)</span>
<span class='va'>a</span> <span class='op'>%like%</span> <span class='va'>b</span>
<span class='co'>#&gt; TRUE TRUE TRUE</span>
<span class='va'>a</span><span class='op'>[</span><span class='fl'>1</span><span class='op'>]</span> <span class='op'>%like%</span> <span class='va'>b</span>
<span class='co'>#&gt; TRUE FALSE FALSE</span>
<span class='va'>a</span> <span class='op'>%like%</span> <span class='va'>b</span><span class='op'>[</span><span class='fl'>1</span><span class='op'>]</span>
<span class='co'>#&gt; TRUE FALSE FALSE</span>
<span class='co'># get isolates whose name start with 'Ent' or 'ent'</span>
<span class='co'># \donttest{</span>

View File

@ -49,7 +49,7 @@
<script src="../extra.js"></script>
<meta property="og:title" content="Plotting for Classes rsi, mic and disk — plot" />
<meta property="og:description" content="Functions to print classes of the AMR package." />
<meta property="og:description" content="Functions to plot classes rsi, mic and disk, with support for base R and ggplot2." />
<meta property="og:image" content="https://msberends.github.io/AMR/logo.png" />
@ -82,7 +82,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.5.0.9016</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.5.0.9026</span>
</span>
</div>
@ -234,65 +234,78 @@
<div class="col-md-9 contents">
<div class="page-header">
<h1>Plotting for Classes <code>rsi</code>, <code>mic</code> and <code>disk</code></h1>
<small class="dont-index">Source: <a href='https://github.com/msberends/AMR/blob/master/R/amr.R'><code>R/amr.R</code></a>, <a href='https://github.com/msberends/AMR/blob/master/R/disk.R'><code>R/disk.R</code></a>, <a href='https://github.com/msberends/AMR/blob/master/R/mic.R'><code>R/mic.R</code></a>, and 1 more</small>
<small class="dont-index">Source: <a href='https://github.com/msberends/AMR/blob/master/R/plot.R'><code>R/plot.R</code></a></small>
<div class="hidden name"><code>plot.Rd</code></div>
</div>
<div class="ref-description">
<p>Functions to print classes of the <code>AMR</code> package.</p>
<p>Functions to plot classes <code>rsi</code>, <code>mic</code> and <code>disk</code>, with support for base R and <code>ggplot2</code>.</p>
</div>
<pre class="usage"><span class='co'># S3 method for disk</span>
<span class='fu'>plot</span><span class='op'>(</span>
<span class='va'>x</span>,
main <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/paste.html'>paste</a></span><span class='op'>(</span><span class='st'>"Disk zones values of"</span>, <span class='fu'><a href='https://rdrr.io/r/base/deparse.html'>deparse</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/substitute.html'>substitute</a></span><span class='op'>(</span><span class='va'>x</span><span class='op'>)</span><span class='op'>)</span><span class='op'>)</span>,
ylab <span class='op'>=</span> <span class='st'>"Frequency"</span>,
xlab <span class='op'>=</span> <span class='st'>"Disk diffusion (mm)"</span>,
axes <span class='op'>=</span> <span class='cn'>FALSE</span>,
<span class='va'>...</span>
<span class='op'>)</span>
<span class='co'># S3 method for mic</span>
<pre class="usage"><span class='co'># S3 method for mic</span>
<span class='fu'>plot</span><span class='op'>(</span>
<span class='va'>x</span>,
main <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/paste.html'>paste</a></span><span class='op'>(</span><span class='st'>"MIC values of"</span>, <span class='fu'><a href='https://rdrr.io/r/base/deparse.html'>deparse</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/substitute.html'>substitute</a></span><span class='op'>(</span><span class='va'>x</span><span class='op'>)</span><span class='op'>)</span><span class='op'>)</span>,
ylab <span class='op'>=</span> <span class='st'>"Frequency"</span>,
xlab <span class='op'>=</span> <span class='st'>"MIC value"</span>,
axes <span class='op'>=</span> <span class='cn'>FALSE</span>,
xlab <span class='op'>=</span> <span class='st'>"Minimum Inhibitory Concentration (mg/L)"</span>,
mo <span class='op'>=</span> <span class='cn'>NULL</span>,
ab <span class='op'>=</span> <span class='cn'>NULL</span>,
guideline <span class='op'>=</span> <span class='st'>"EUCAST"</span>,
colours_RSI <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span><span class='st'>"#ED553B"</span>, <span class='st'>"#3CAEA3"</span>, <span class='st'>"#F6D55C"</span><span class='op'>)</span>,
expand <span class='op'>=</span> <span class='cn'>TRUE</span>,
<span class='va'>...</span>
<span class='op'>)</span>
<span class='co'># S3 method for mic</span>
<span class='fu'><a href='https://rdrr.io/r/graphics/barplot.html'>barplot</a></span><span class='op'>(</span>
<span class='va'>height</span>,
main <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/paste.html'>paste</a></span><span class='op'>(</span><span class='st'>"MIC values of"</span>, <span class='fu'><a href='https://rdrr.io/r/base/deparse.html'>deparse</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/substitute.html'>substitute</a></span><span class='op'>(</span><span class='va'>height</span><span class='op'>)</span><span class='op'>)</span><span class='op'>)</span>,
<span class='fu'><a href='https://ggplot2.tidyverse.org/reference/ggplot.html'>ggplot</a></span><span class='op'>(</span>
<span class='va'>data</span>,
mapping <span class='op'>=</span> <span class='cn'>NULL</span>,
title <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/paste.html'>paste</a></span><span class='op'>(</span><span class='st'>"MIC values of"</span>, <span class='fu'><a href='https://rdrr.io/r/base/deparse.html'>deparse</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/substitute.html'>substitute</a></span><span class='op'>(</span><span class='va'>data</span><span class='op'>)</span><span class='op'>)</span><span class='op'>)</span>,
ylab <span class='op'>=</span> <span class='st'>"Frequency"</span>,
xlab <span class='op'>=</span> <span class='st'>"MIC value"</span>,
axes <span class='op'>=</span> <span class='cn'>FALSE</span>,
xlab <span class='op'>=</span> <span class='st'>"Minimum Inhibitory Concentration (mg/L)"</span>,
mo <span class='op'>=</span> <span class='cn'>NULL</span>,
ab <span class='op'>=</span> <span class='cn'>NULL</span>,
guideline <span class='op'>=</span> <span class='st'>"EUCAST"</span>,
colours_RSI <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span><span class='st'>"#ED553B"</span>, <span class='st'>"#3CAEA3"</span>, <span class='st'>"#F6D55C"</span><span class='op'>)</span>,
expand <span class='op'>=</span> <span class='cn'>TRUE</span>,
<span class='va'>...</span>
<span class='op'>)</span>
<span class='co'># S3 method for disk</span>
<span class='fu'>plot</span><span class='op'>(</span>
<span class='va'>x</span>,
main <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/paste.html'>paste</a></span><span class='op'>(</span><span class='st'>"Disk zones values of"</span>, <span class='fu'><a href='https://rdrr.io/r/base/deparse.html'>deparse</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/substitute.html'>substitute</a></span><span class='op'>(</span><span class='va'>x</span><span class='op'>)</span><span class='op'>)</span><span class='op'>)</span>,
ylab <span class='op'>=</span> <span class='st'>"Frequency"</span>,
xlab <span class='op'>=</span> <span class='st'>"Disk diffusion diameter (mm)"</span>,
mo <span class='op'>=</span> <span class='cn'>NULL</span>,
ab <span class='op'>=</span> <span class='cn'>NULL</span>,
guideline <span class='op'>=</span> <span class='st'>"EUCAST"</span>,
colours_RSI <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span><span class='st'>"#ED553B"</span>, <span class='st'>"#3CAEA3"</span>, <span class='st'>"#F6D55C"</span><span class='op'>)</span>,
expand <span class='op'>=</span> <span class='cn'>TRUE</span>,
<span class='va'>...</span>
<span class='op'>)</span>
<span class='co'># S3 method for disk</span>
<span class='fu'><a href='https://ggplot2.tidyverse.org/reference/ggplot.html'>ggplot</a></span><span class='op'>(</span>
<span class='va'>data</span>,
mapping <span class='op'>=</span> <span class='cn'>NULL</span>,
title <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/paste.html'>paste</a></span><span class='op'>(</span><span class='st'>"Disk zones values of"</span>, <span class='fu'><a href='https://rdrr.io/r/base/deparse.html'>deparse</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/substitute.html'>substitute</a></span><span class='op'>(</span><span class='va'>data</span><span class='op'>)</span><span class='op'>)</span><span class='op'>)</span>,
ylab <span class='op'>=</span> <span class='st'>"Frequency"</span>,
xlab <span class='op'>=</span> <span class='st'>"Disk diffusion diameter (mm)"</span>,
mo <span class='op'>=</span> <span class='cn'>NULL</span>,
ab <span class='op'>=</span> <span class='cn'>NULL</span>,
guideline <span class='op'>=</span> <span class='st'>"EUCAST"</span>,
colours_RSI <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span><span class='st'>"#ED553B"</span>, <span class='st'>"#3CAEA3"</span>, <span class='st'>"#F6D55C"</span><span class='op'>)</span>,
expand <span class='op'>=</span> <span class='cn'>TRUE</span>,
<span class='va'>...</span>
<span class='op'>)</span>
<span class='co'># S3 method for rsi</span>
<span class='fu'>plot</span><span class='op'>(</span>
<span class='va'>x</span>,
lwd <span class='op'>=</span> <span class='fl'>2</span>,
ylim <span class='op'>=</span> <span class='cn'>NULL</span>,
ylab <span class='op'>=</span> <span class='st'>"Percentage"</span>,
xlab <span class='op'>=</span> <span class='st'>"Antimicrobial Interpretation"</span>,
main <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/paste.html'>paste</a></span><span class='op'>(</span><span class='st'>"Resistance Overview of"</span>, <span class='fu'><a href='https://rdrr.io/r/base/deparse.html'>deparse</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/substitute.html'>substitute</a></span><span class='op'>(</span><span class='va'>x</span><span class='op'>)</span><span class='op'>)</span><span class='op'>)</span>,
axes <span class='op'>=</span> <span class='cn'>FALSE</span>,
<span class='va'>...</span>
<span class='op'>)</span>
<span class='co'># S3 method for rsi</span>
<span class='fu'><a href='https://rdrr.io/r/graphics/barplot.html'>barplot</a></span><span class='op'>(</span>
<span class='va'>height</span>,
col <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/c.html'>c</a></span><span class='op'>(</span><span class='st'>"chartreuse4"</span>, <span class='st'>"chartreuse3"</span>, <span class='st'>"brown3"</span><span class='op'>)</span>,
xlab <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/ifelse.html'>ifelse</a></span><span class='op'>(</span><span class='va'>beside</span>, <span class='st'>"Antimicrobial Interpretation"</span>, <span class='st'>""</span><span class='op'>)</span>,
main <span class='op'>=</span> <span class='fu'><a href='https://rdrr.io/r/base/paste.html'>paste</a></span><span class='op'>(</span><span class='st'>"Resistance Overview of"</span>, <span class='fu'><a href='https://rdrr.io/r/base/deparse.html'>deparse</a></span><span class='op'>(</span><span class='fu'><a href='https://rdrr.io/r/base/substitute.html'>substitute</a></span><span class='op'>(</span><span class='va'>height</span><span class='op'>)</span><span class='op'>)</span><span class='op'>)</span>,
ylab <span class='op'>=</span> <span class='st'>"Frequency"</span>,
beside <span class='op'>=</span> <span class='cn'>TRUE</span>,
axes <span class='op'>=</span> <span class='va'>beside</span>,
<span class='va'>...</span>
<span class='op'>)</span></pre>
@ -300,63 +313,55 @@
<table class="ref-arguments">
<colgroup><col class="name" /><col class="desc" /></colgroup>
<tr>
<th>x</th>
<td><p>the coordinates of points in the plot. Alternatively, a
single plotting structure, function or <em>any <span style="R">R</span> object with a
<code>plot</code> method</em> can be provided.</p></td>
<th>x, data</th>
<td><p>MIC values created with <code><a href='as.mic.html'>as.mic()</a></code> or disk diffusion values created with <code><a href='as.disk.html'>as.disk()</a></code></p></td>
</tr>
<tr>
<th>main</th>
<td><p>overall and sub title for the plot.</p></td>
<th>main, title</th>
<td><p>title of the plot</p></td>
</tr>
<tr>
<th>ylab</th>
<td><p>a label for the y axis.</p></td>
<th>xlab, ylab</th>
<td><p>axis title</p></td>
</tr>
<tr>
<th>xlab</th>
<td><p>a label for the x axis.</p></td>
<th>mo</th>
<td><p>any (vector of) text that can be coerced to a valid microorganism code with <code><a href='as.mo.html'>as.mo()</a></code></p></td>
</tr>
<tr>
<th>axes</th>
<td><p>logical. If <code>TRUE</code>, a vertical (or horizontal, if
<code>horiz</code> is true) axis is drawn.</p></td>
<th>ab</th>
<td><p>any (vector of) text that can be coerced to a valid antimicrobial code with <code><a href='as.ab.html'>as.ab()</a></code></p></td>
</tr>
<tr>
<th>guideline</th>
<td><p>interpretation guideline to use, defaults to the latest included EUCAST guideline, see <em>Details</em></p></td>
</tr>
<tr>
<th>colours_RSI</th>
<td><p>colours to use for filling in the bars, must be a vector of three values (in the order R, S and I). The default colours are colour-blind friendly.</p></td>
</tr>
<tr>
<th>expand</th>
<td><p>logical to indicate whether the range on the x axis should be expanded between the lowest and highest value. For MIC values, intermediate values will be factors of 2 starting from the highest MIC value. For disk diameters, the whole diameter range will be filled.</p></td>
</tr>
<tr>
<th>...</th>
<td><p>Arguments passed on to functions</p></td>
<td><p>arguments passed on to <code><a href='as.rsi.html'>as.rsi()</a></code></p></td>
</tr>
<tr>
<th>height</th>
<td><p>either a vector or matrix of values describing the
bars which make up the plot. If <code>height</code> is a vector, the
plot consists of a sequence of rectangular bars with heights
given by the values in the vector. If <code>height</code> is a matrix
and <code>beside</code> is <code>FALSE</code> then each bar of the plot
corresponds to a column of <code>height</code>, with the values in the
column giving the heights of stacked sub-bars making up the
bar. If <code>height</code> is a matrix and <code>beside</code> is
<code>TRUE</code>, then the values in each column are juxtaposed
rather than stacked.</p></td>
</tr>
<tr>
<th>ylim</th>
<td><p>limits for the y axis.</p></td>
</tr>
<tr>
<th>col</th>
<td><p>a vector of colors for the bars or bar components.
By default, grey is used if <code>height</code> is a vector, and a
gamma-corrected grey palette if <code>height</code> is a matrix.</p></td>
</tr>
<tr>
<th>beside</th>
<td><p>a logical value. If <code>FALSE</code>, the columns of
<code>height</code> are portrayed as stacked bars, and if <code>TRUE</code>
the columns are portrayed as juxtaposed bars.</p></td>
<th>mapping</th>
<td><p>aesthetic mappings to use for <code><a href='https://ggplot2.tidyverse.org/reference/ggplot.html'>ggplot()</a></code></p></td>
</tr>
</table>
<h2 class="hasAnchor" id="value"><a class="anchor" href="#value"></a>Value</h2>
<p>The <code>ggplot</code> functions return a <code><a href='https://ggplot2.tidyverse.org/reference/ggplot.html'>ggplot</a></code> model that is extendible with any <code>ggplot2</code> function.</p>
<h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2>
<p>The interpretation of "I" will be named "Increased exposure" for all EUCAST guidelines since 2019, and will be named "Intermediate" in all other cases.</p>
<p>For interpreting MIC values as well as disk diffusion diameters, supported guidelines to be used as input for the <code>guideline</code> argument are: "EUCAST 2021", "EUCAST 2020", "EUCAST 2019", "EUCAST 2018", "EUCAST 2017", "EUCAST 2016", "EUCAST 2015", "EUCAST 2014", "EUCAST 2013", "EUCAST 2012", "EUCAST 2011", "CLSI 2019", "CLSI 2018", "CLSI 2017", "CLSI 2016", "CLSI 2015", "CLSI 2014", "CLSI 2013", "CLSI 2012", "CLSI 2011" and "CLSI 2010".</p>
<p>Simply using <code>"CLSI"</code> or <code>"EUCAST"</code> as input will automatically select the latest version of that guideline.</p>
<h2 class="hasAnchor" id="stable-lifecycle"><a class="anchor" href="#stable-lifecycle"></a>Stable Lifecycle</h2>
@ -370,6 +375,22 @@ The <a href='lifecycle.html'>lifecycle</a> of this function is <strong>stable</s
<p>On our website <a href='https://msberends.github.io/AMR/'>https://msberends.github.io/AMR/</a> you can find <a href='https://msberends.github.io/AMR/articles/AMR.html'>a comprehensive tutorial</a> about how to conduct AMR data analysis, the <a href='https://msberends.github.io/AMR/reference/'>complete documentation of all functions</a> and <a href='https://msberends.github.io/AMR/articles/WHONET.html'>an example analysis using WHONET data</a>. As we would like to better understand the backgrounds and needs of our users, please <a href='https://msberends.github.io/AMR/survey.html'>participate in our survey</a>!</p>
<h2 class="hasAnchor" id="examples"><a class="anchor" href="#examples"></a>Examples</h2>
<pre class="examples"><span class='va'>some_mic_values</span> <span class='op'>&lt;-</span> <span class='fu'><a href='random.html'>random_mic</a></span><span class='op'>(</span>size <span class='op'>=</span> <span class='fl'>100</span><span class='op'>)</span>
<span class='va'>some_disk_values</span> <span class='op'>&lt;-</span> <span class='fu'><a href='random.html'>random_disk</a></span><span class='op'>(</span>size <span class='op'>=</span> <span class='fl'>100</span>, mo <span class='op'>=</span> <span class='st'>"Escherichia coli"</span>, ab <span class='op'>=</span> <span class='st'>"cipro"</span><span class='op'>)</span>
<span class='fu'>plot</span><span class='op'>(</span><span class='va'>some_mic_values</span><span class='op'>)</span>
<span class='fu'>plot</span><span class='op'>(</span><span class='va'>some_disk_values</span><span class='op'>)</span>
<span class='co'># when providing the microorganism and antibiotic, colours will show interpretations:</span>
<span class='fu'>plot</span><span class='op'>(</span><span class='va'>some_mic_values</span>, mo <span class='op'>=</span> <span class='st'>"S. aureus"</span>, ab <span class='op'>=</span> <span class='st'>"ampicillin"</span><span class='op'>)</span>
<span class='fu'>plot</span><span class='op'>(</span><span class='va'>some_disk_values</span>, mo <span class='op'>=</span> <span class='st'>"Escherichia coli"</span>, ab <span class='op'>=</span> <span class='st'>"cipro"</span><span class='op'>)</span>
<span class='kw'>if</span> <span class='op'>(</span><span class='kw'><a href='https://rdrr.io/r/base/library.html'>require</a></span><span class='op'>(</span><span class='st'><a href='http://ggplot2.tidyverse.org'>"ggplot2"</a></span><span class='op'>)</span><span class='op'>)</span> <span class='op'>{</span>
<span class='fu'><a href='https://ggplot2.tidyverse.org/reference/ggplot.html'>ggplot</a></span><span class='op'>(</span><span class='va'>some_mic_values</span><span class='op'>)</span>
<span class='fu'><a href='https://ggplot2.tidyverse.org/reference/ggplot.html'>ggplot</a></span><span class='op'>(</span><span class='va'>some_disk_values</span>, mo <span class='op'>=</span> <span class='st'>"Escherichia coli"</span>, ab <span class='op'>=</span> <span class='st'>"cipro"</span><span class='op'>)</span>
<span class='op'>}</span>
</pre>
</div>
<div class="col-md-3 hidden-xs hidden-sm" id="pkgdown-sidebar">
<nav id="toc" data-toggle="toc" class="sticky-top">

View File

@ -49,7 +49,7 @@
<script src="../extra.js"></script>
<meta property="og:title" content="Random MIC Values/Disk Zones/RSI Generation — random" />
<meta property="og:description" content="These functions can be used for generating random MIC values and disk diffusion diameters, for AMR data analysis practice." />
<meta property="og:description" content="These functions can be used for generating random MIC values and disk diffusion diameters, for AMR data analysis practice. By providing a microorganism and antimicrobial agent, the generated results will reflect reality as much as possible." />
<meta property="og:image" content="https://msberends.github.io/AMR/logo.png" />
@ -82,7 +82,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.5.0.9016</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">1.5.0.9025</span>
</span>
</div>
@ -239,7 +239,7 @@
</div>
<div class="ref-description">
<p>These functions can be used for generating random MIC values and disk diffusion diameters, for AMR data analysis practice.</p>
<p>These functions can be used for generating random MIC values and disk diffusion diameters, for AMR data analysis practice. By providing a microorganism and antimicrobial agent, the generated results will reflect reality as much as possible.</p>
</div>
<pre class="usage"><span class='fu'>random_mic</span><span class='op'>(</span><span class='va'>size</span>, mo <span class='op'>=</span> <span class='cn'>NULL</span>, ab <span class='op'>=</span> <span class='cn'>NULL</span>, <span class='va'>...</span><span class='op'>)</span>

View File

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

View File

@ -54,8 +54,9 @@ as.rsi(x = as.mic(4),
ab = "AMX",
guideline = "EUCAST")
# plot MIC values, see ?plot
plot(mic_data)
barplot(mic_data)
plot(mic_data, mo = "E. coli", ab = "cipro")
}
\seealso{
\code{\link[=as.rsi]{as.rsi()}}

View File

@ -1,88 +1,32 @@
<?xml version="1.0"?> <!DOCTYPE svg PUBLIC "-//W3C//DTD SVG 1.1//EN"
"http://www.w3.org/Graphics/SVG/1.1/DTD/svg11.dtd"> <svg
xmlns="http://www.w3.org/2000/svg" xmlns:xl="http://www.w3.org/1999/xlink"
version="1.1" viewBox="8 48 787 198" width="787pt" height="198pt"><metadata
xmlns:dc="http://purl.org/dc/elements/1.1/"><dc:date>2018-01-05
19:43Z</dc:date><!-- Produced by OmniGraffle Professional 5.4.4
--></metadata><defs><font-face font-family="Helvetica Neue" font-size="16"
panose-1="2 0 5 3 0 0 0 2 0 4" units-per-em="1000" underline-position="-100"
underline-thickness="50" slope="0" x-height="517" cap-height="714"
ascent="951.99585" descent="-212.99744"
font-weight="500"><font-face-src><font-face-name
name="HelveticaNeue"/></font-face-src></font-face><marker orient="auto"
overflow="visible" markerUnits="strokeWidth" id="FilledArrow_Marker" viewBox="-1
-4 10 8" markerWidth="10" markerHeight="8" color="black"><g><path d="M 8 0 L 0
-3 L 0 3 Z" fill="currentColor" stroke="currentColor"
stroke-width="1"/></g></marker></defs><g stroke="none" stroke-opacity="1"
stroke-dasharray="none" fill="none" fill-opacity="1"><title>Canvas
1</title><rect fill="white" width="805.88977"
height="536.27556"/><g><title>Layer 1</title><rect x="201.43709" y="148.91563"
width="88.865815" height="36.026683" stroke="#0080ff" stroke-linecap="round"
stroke-linejoin="round" stroke-width="2"/><text transform="translate(206.43709
157.70498)" fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="7.8649073" y="15"
textLength="63.136">maturing</tspan></text><rect x="10.4153" y="97.854194"
width="123.69161" height="36.026683" stroke="#ff8000" stroke-linecap="round"
stroke-linejoin="round" stroke-width="2"/><text transform="translate(15.4153
106.643536)" fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="10.7658034" y="15"
textLength="92.160004">experimental</tspan></text><rect x="339.64294"
y="207.75286" width="64.848027" height="36.026683" stroke="green"
stroke-linecap="round" stroke-linejoin="round" stroke-width="2"/><text
transform="translate(344.64294 216.5422)" fill="black"><tspan
font-family="Helvetica Neue" font-size="16" font-weight="500" x="5.7920134"
y="15" textLength="43.264">stable</tspan></text><rect x="613.9284" y="118.27877"
width="67.249806" height="36.026683" stroke="#ff8000" stroke-linecap="round"
stroke-linejoin="round" stroke-width="2"/><text transform="translate(618.9284
127.06811)" fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="5.9529028" y="15" textLength="5.328">r</tspan><tspan
font-family="Helvetica Neue" font-size="16" font-weight="500" x="10.992903"
y="15" textLength="22.511999">etir</tspan><tspan font-family="Helvetica Neue"
font-size="16" font-weight="500" x="33.216903" y="15"
textLength="18.08">ed</tspan></text><rect x="325.78587" y="50.19685"
width="85.263146" height="36.026683" stroke="#0080ff" stroke-linecap="round"
stroke-linejoin="round" stroke-width="2"/><text transform="translate(330.78587
58.986193)" fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="7.543573" y="15"
textLength="60.176">dormant</tspan></text><rect x="468.56405" y="142.10744"
width="112.8836" height="36.026683" stroke="#0080ff" stroke-linecap="round"
stroke-linejoin="round" stroke-width="2"/><text transform="translate(473.56405
150.89678)" fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="9.801801" y="15"
textLength="83.28">questioning</tspan></text><line x1="135.106906"
y1="134.351596" x2="190.93937" y2="150.77291"
marker-end="url(#FilledArrow_Marker)" stroke="black" stroke-linecap="round"
stroke-linejoin="round" stroke-width="1"/><line x1="286.65074" y1="185.94232"
x2="329.67024" y2="205.99944" marker-end="url(#FilledArrow_Marker)"
stroke="black" stroke-linecap="round" stroke-linejoin="round"
stroke-width="1"/><path d="M 379.93472 206.75285 C 387.55754 192.63012 401.66897
174.0594 426.21202 163.52488 C 436.33446 159.18006 447.11932 156.67954 457.70464
155.39871" marker-end="url(#FilledArrow_Marker)" stroke="black"
stroke-linecap="round" stroke-linejoin="round" stroke-width="1"/><line
x1="582.44766" y1="148.95154" x2="603.2104" y2="144.91434"
marker-end="url(#FilledArrow_Marker)" stroke="black" stroke-linecap="round"
stroke-linejoin="round" stroke-width="1"/><path d="M 501.44774 179.13413 C
487.32306 189.48841 467.98586 202.01855 446.6366 211.18222 C 435.19097 216.09499
424.5888 219.42992 415.18313 221.6778" marker-end="url(#FilledArrow_Marker)"
stroke="black" stroke-linecap="round" stroke-linejoin="round"
stroke-width="1"/><path d="M 412.04903 66.0841 C 438.72737 66.23414 475.24547
68.794908 514.7185 78.42248 C 552.22946 87.57149 584.04206 101.061534 607.12235
112.71587" marker-end="url(#FilledArrow_Marker)" stroke="black"
stroke-linecap="round" stroke-linejoin="round" stroke-width="1"/><path d="M
135.10692 119.41541 C 165.84715 119.854806 204.35783 118.583695 242.39084
112.46344 C 276.08222 107.04184 303.03701 98.838735 323.23284 90.96218"
marker-end="url(#FilledArrow_Marker)" stroke="black" stroke-linecap="round"
stroke-linejoin="round" stroke-width="1"/><path d="M 324.78586 66.603523 C
301.6689 66.933135 270.15767 68.9068 232.17855 75.018384 C 200.11208 80.178506
169.19774 87.361075 143.238715 94.26646" marker-end="url(#FilledArrow_Marker)"
stroke="black" stroke-linecap="round" stroke-linejoin="round"
stroke-width="1"/><rect x="707.0446" y="118.27877" width="85.263146"
height="36.026683" stroke="red" stroke-linecap="round" stroke-linejoin="round"
stroke-width="2"/><text transform="translate(712.0446 127.06811)"
fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="7.255573" y="15" textLength="13.92">ar</tspan><tspan
font-family="Helvetica Neue" font-size="16" font-weight="500" x="20.887573"
y="15" textLength="47.12">chived</tspan></text><line x1="682.1782"
y1="136.29211" x2="696.1446" y2="136.29211"
marker-end="url(#FilledArrow_Marker)" stroke="black" stroke-linecap="round"
stroke-linejoin="round" stroke-width="1"/></g></g></svg>
<?xml version="1.0" encoding="UTF-8"?>
<svg width="510.24pt" height="184.25pt" version="1.1" viewBox="0 0 510.24 184.25" xmlns="http://www.w3.org/2000/svg">
<style>
text {
fill: white;
font-family: "Helvetica Neue";
}
</style>
<defs>
<marker id="a" color="black" overflow="visible" markerHeight="6" markerWidth="7" orient="auto" viewBox="-1 -3 7 6">
<path d="m4.8 0-4.8-1.8v3.6z" fill="currentColor" stroke="currentColor"/>
</marker>
</defs>
<g fill="none">
<title>Canvas 1</title>
<rect width="510.24" height="184.25" fill="#fff"/>
<g>
<title>Layer 1</title>
<rect x="5.6693" y="5.6693" width="116.22" height="48.189" fill="#fd8008"/>
<text transform="translate(63.7793 29.7638)" dominant-baseline="middle" text-anchor="middle">experimental</text>
<rect x="161.57" y="113.39" width="150.24" height="68.031" fill="#108001"/>
<text transform="translate(236.69 147.4055)" dominant-baseline="middle" text-anchor="middle" font-size="19">stable</text>
<path d="m63.356 53.858c2.0388 19.203 10.427 45.968 38.691 65.197 13.679 9.3061 30.217 15.625 46.951 19.9" marker-end="url(#a)" stroke="#000" stroke-linecap="round" stroke-linejoin="round" stroke-width="2"/>
<path d="m311.81 131.57c18.392-5.7638 38.128-13.509 56.693-23.85 25.216-14.046 43.275-30.1 55.731-43.973" marker-end="url(#a)" stroke="#000" stroke-linecap="round" stroke-linejoin="round" stroke-width="2"/>
<rect x="391.18" y="119.06" width="113.39" height="48.189" fill="#074080"/>
<text transform="translate(447.875 143.1545)" dominant-baseline="middle" text-anchor="middle">superseded</text>
<line x1="311.81" x2="378.29" y1="147.22" y2="145.23" marker-end="url(#a)" stroke="#000" stroke-linecap="round" stroke-linejoin="round" stroke-width="2"/>
<rect x="391.18" y="5.6693" width="113.39" height="48.189" fill="#fd8008"/>
<text transform="translate(447.875 29.7638)" dominant-baseline="middle" text-anchor="middle">deprecated</text>
</g>
</g>
</svg>

Before

Width:  |  Height:  |  Size: 6.0 KiB

After

Width:  |  Height:  |  Size: 1.9 KiB

View File

@ -24,8 +24,8 @@ ggplot_rsi(
minimum = 30,
language = get_locale(),
nrow = NULL,
colours = c(S = "#61a8ff", SI = "#61a8ff", I = "#61f7ff", IR = "#ff6961", R =
"#ff6961"),
colours = c(S = "#3CAEA3", SI = "#3CAEA3", I = "#F6D55C", IR = "#ED553B", R =
"#ED553B"),
datalabels = TRUE,
datalabels.size = 2.5,
datalabels.colour = "grey15",
@ -54,8 +54,9 @@ facet_rsi(facet = c("interpretation", "antibiotic"), nrow = NULL)
scale_y_percent(breaks = seq(0, 1, 0.1), limits = NULL)
scale_rsi_colours(
colours = c(S = "#61a8ff", SI = "#61a8ff", I = "#61f7ff", IR = "#ff6961", R =
"#ff6961")
colours = c(S = "#3CAEA3", SI = "#3CAEA3", I = "#F6D55C", IR = "#ED553B", R =
"#ED553B"),
aesthetics = "fill"
)
theme_rsi()
@ -99,7 +100,7 @@ labels_rsi_count(
\item{nrow}{(when using \code{facet}) number of rows}
\item{colours}{a named vector with colours for the bars. The names must be one or more of: S, SI, I, IR, R or be \code{FALSE} to use default \link[ggplot2:ggplot]{ggplot2} colours.}
\item{colours}{a named vector with colours for the bars. The names must be one or more of: S, SI, I, IR, R or be \code{FALSE} for standard \link[ggplot2:ggplot]{ggplot2} colours. The default colours are colour-blind friendly, while maintaining the convention that e.g. 'susceptible' should be green and 'resistant' should be red.}
\item{datalabels}{show datalabels using \code{\link[=labels_rsi_count]{labels_rsi_count()}}}
@ -118,6 +119,8 @@ labels_rsi_count(
\item{y.title}{text to show as y axis description}
\item{...}{other arguments passed on to \code{\link[=geom_rsi]{geom_rsi()}}}
\item{aesthetics}{aesthetics to apply the colours to, defaults to "fill" but can also be "colour" or "both"}
}
\description{
Use these functions to create bar plots for AMR data analysis. All functions rely on \link[ggplot2:ggplot]{ggplot2} functions.
@ -205,11 +208,6 @@ example_isolates \%>\%
CIP) \%>\%
ggplot_rsi(x = "age_group")
# for colourblind mode, use divergent colours from the viridis package:
example_isolates \%>\%
select(AMX, NIT, FOS, TMP, CIP) \%>\%
ggplot_rsi() +
scale_fill_viridis_d()
# a shorter version which also adjusts data label colours:
example_isolates \%>\%
select(AMX, NIT, FOS, TMP, CIP) \%>\%

View File

@ -26,7 +26,7 @@ x \%like_case\% pattern
A \code{\link{logical}} vector
}
\description{
Convenient wrapper around \code{\link[=grep]{grep()}} to match a pattern: \code{x \%like\% pattern}. It always returns a \code{\link{logical}} vector and is always case-insensitive (use \code{x \%like_case\% pattern} for case-sensitive matching). Also, \code{pattern} can be as long as \code{x} to compare items of each index in both vectors, or they both can have the same length to iterate over all cases.
Convenient wrapper around \code{\link[=grepl]{grepl()}} to match a pattern: \code{x \%like\% pattern}. It always returns a \code{\link{logical}} vector and is always case-insensitive (use \code{x \%like_case\% pattern} for case-sensitive matching). Also, \code{pattern} can be as long as \code{x} to compare items of each index in both vectors, or they both can have the same length to iterate over all cases.
}
\details{
The \verb{\%like\%} function:
@ -61,11 +61,15 @@ a \%like\% b
b \%like\% a
#> FALSE
# also supports multiple patterns, length must be equal to x
# also supports multiple patterns
a <- c("Test case", "Something different", "Yet another thing")
b <- c( "case", "diff", "yet")
a \%like\% b
#> TRUE TRUE TRUE
a[1] \%like\% b
#> TRUE FALSE FALSE
a \%like\% b[1]
#> TRUE FALSE FALSE
# get isolates whose name start with 'Ent' or 'ent'
\donttest{
@ -76,5 +80,5 @@ if (require("dplyr")) {
}
}
\seealso{
\code{\link[=grep]{grep()}}
\code{\link[=grepl]{grepl()}}
}

View File

@ -1,102 +1,109 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/amr.R, R/disk.R, R/mic.R, R/rsi.R
% Please edit documentation in R/plot.R
\name{plot}
\alias{plot}
\alias{plot.disk}
\alias{plot.mic}
\alias{barplot.mic}
\alias{ggplot.mic}
\alias{plot.disk}
\alias{ggplot.disk}
\alias{plot.rsi}
\alias{barplot.rsi}
\title{Plotting for Classes \code{rsi}, \code{mic} and \code{disk}}
\usage{
\method{plot}{disk}(
x,
main = paste("Disk zones values of", deparse(substitute(x))),
ylab = "Frequency",
xlab = "Disk diffusion (mm)",
axes = FALSE,
...
)
\method{plot}{mic}(
x,
main = paste("MIC values of", deparse(substitute(x))),
ylab = "Frequency",
xlab = "MIC value",
axes = FALSE,
xlab = "Minimum Inhibitory Concentration (mg/L)",
mo = NULL,
ab = NULL,
guideline = "EUCAST",
colours_RSI = c("#ED553B", "#3CAEA3", "#F6D55C"),
expand = TRUE,
...
)
\method{barplot}{mic}(
height,
main = paste("MIC values of", deparse(substitute(height))),
\method{ggplot}{mic}(
data,
mapping = NULL,
title = paste("MIC values of", deparse(substitute(data))),
ylab = "Frequency",
xlab = "MIC value",
axes = FALSE,
xlab = "Minimum Inhibitory Concentration (mg/L)",
mo = NULL,
ab = NULL,
guideline = "EUCAST",
colours_RSI = c("#ED553B", "#3CAEA3", "#F6D55C"),
expand = TRUE,
...
)
\method{plot}{disk}(
x,
main = paste("Disk zones values of", deparse(substitute(x))),
ylab = "Frequency",
xlab = "Disk diffusion diameter (mm)",
mo = NULL,
ab = NULL,
guideline = "EUCAST",
colours_RSI = c("#ED553B", "#3CAEA3", "#F6D55C"),
expand = TRUE,
...
)
\method{ggplot}{disk}(
data,
mapping = NULL,
title = paste("Disk zones values of", deparse(substitute(data))),
ylab = "Frequency",
xlab = "Disk diffusion diameter (mm)",
mo = NULL,
ab = NULL,
guideline = "EUCAST",
colours_RSI = c("#ED553B", "#3CAEA3", "#F6D55C"),
expand = TRUE,
...
)
\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{x, data}{MIC values created with \code{\link[=as.mic]{as.mic()}} or disk diffusion values created with \code{\link[=as.disk]{as.disk()}}}
\item{main}{overall and sub title for the plot.}
\item{main, title}{title of the plot}
\item{ylab}{a label for the y axis.}
\item{xlab, ylab}{axis title}
\item{xlab}{a label for the x axis.}
\item{mo}{any (vector of) text that can be coerced to a valid microorganism code with \code{\link[=as.mo]{as.mo()}}}
\item{axes}{logical. If \code{TRUE}, a vertical (or horizontal, if
\code{horiz} is true) axis is drawn.}
\item{ab}{any (vector of) text that can be coerced to a valid antimicrobial code with \code{\link[=as.ab]{as.ab()}}}
\item{...}{Arguments passed on to functions}
\item{guideline}{interpretation guideline to use, defaults to the latest included EUCAST guideline, see \emph{Details}}
\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{colours_RSI}{colours to use for filling in the bars, must be a vector of three values (in the order R, S and I). The default colours are colour-blind friendly.}
\item{ylim}{limits for the y axis.}
\item{expand}{logical to indicate whether the range on the x axis should be expanded between the lowest and highest value. For MIC values, intermediate values will be factors of 2 starting from the highest MIC value. For disk diameters, the whole diameter range will be filled.}
\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{...}{arguments passed on to \code{\link[=as.rsi]{as.rsi()}}}
\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.}
\item{mapping}{aesthetic mappings to use for \code{\link[ggplot2:ggplot]{ggplot()}}}
}
\value{
The \code{ggplot} functions return a \code{\link[ggplot2:ggplot]{ggplot}} model that is extendible with any \code{ggplot2} function.
}
\description{
Functions to print classes of the \code{AMR} package.
Functions to plot classes \code{rsi}, \code{mic} and \code{disk}, with support for base R and \code{ggplot2}.
}
\details{
The interpretation of "I" will be named "Increased exposure" for all EUCAST guidelines since 2019, and will be named "Intermediate" in all other cases.
For interpreting MIC values as well as disk diffusion diameters, supported guidelines to be used as input for the \code{guideline} argument are: "EUCAST 2021", "EUCAST 2020", "EUCAST 2019", "EUCAST 2018", "EUCAST 2017", "EUCAST 2016", "EUCAST 2015", "EUCAST 2014", "EUCAST 2013", "EUCAST 2012", "EUCAST 2011", "CLSI 2019", "CLSI 2018", "CLSI 2017", "CLSI 2016", "CLSI 2015", "CLSI 2014", "CLSI 2013", "CLSI 2012", "CLSI 2011" and "CLSI 2010".
Simply using \code{"CLSI"} or \code{"EUCAST"} as input will automatically select the latest version of that guideline.
}
\section{Stable Lifecycle}{
@ -111,4 +118,19 @@ If the unlying code needs breaking changes, they will occur gradually. For examp
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 data analysis, the \href{https://msberends.github.io/AMR/reference/}{complete documentation of all functions} 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}
\examples{
some_mic_values <- random_mic(size = 100)
some_disk_values <- random_disk(size = 100, mo = "Escherichia coli", ab = "cipro")
plot(some_mic_values)
plot(some_disk_values)
# when providing the microorganism and antibiotic, colours will show interpretations:
plot(some_mic_values, mo = "S. aureus", ab = "ampicillin")
plot(some_disk_values, mo = "Escherichia coli", ab = "cipro")
if (require("ggplot2")) {
ggplot(some_mic_values)
ggplot(some_disk_values, mo = "Escherichia coli", ab = "cipro")
}
}

View File

@ -28,7 +28,7 @@ random_rsi(size, prob_RSI = c(0.33, 0.33, 0.33), ...)
class \verb{<mic>} for \code{\link[=random_mic]{random_mic()}} (see \code{\link[=as.mic]{as.mic()}}) and class \verb{<disk>} for \code{\link[=random_disk]{random_disk()}} (see \code{\link[=as.disk]{as.disk()}})
}
\description{
These functions can be used for generating random MIC values and disk diffusion diameters, for AMR data analysis practice.
These functions can be used for generating random MIC values and disk diffusion diameters, for AMR data analysis practice. By providing a microorganism and antimicrobial agent, the generated results will reflect reality as much as possible.
}
\details{
The base R function \code{\link[=sample]{sample()}} is used for generating values.

View File

@ -187,30 +187,30 @@ div[id^=last-updated] h2 {
}
/* tables, make them look like scientific ones */
table {
.table {
font-size: 90%;
}
table * {
.table * {
vertical-align: middle !important;
}
table td {
.table td {
padding: 4px !important;
}
thead {
.table thead {
border-top: 2px solid black;
border-bottom: 2px solid black;
}
thead ~ tbody {
.table thead ~ tbody {
/* only when it has a header */
border-bottom: 2px solid black;
}
thead th {
.table thead th {
text-align: inherit;
}
table a:not(.btn), .table a:not(.btn) {
.table a:not(.btn) {
text-decoration: inherit;
}
table a:not(.btn):hover, .table a:not(.btn):hover {
.table a:not(.btn):hover {
text-decoration: underline;
}

View File

@ -1,88 +1,32 @@
<?xml version="1.0"?> <!DOCTYPE svg PUBLIC "-//W3C//DTD SVG 1.1//EN"
"http://www.w3.org/Graphics/SVG/1.1/DTD/svg11.dtd"> <svg
xmlns="http://www.w3.org/2000/svg" xmlns:xl="http://www.w3.org/1999/xlink"
version="1.1" viewBox="8 48 787 198" width="787pt" height="198pt"><metadata
xmlns:dc="http://purl.org/dc/elements/1.1/"><dc:date>2018-01-05
19:43Z</dc:date><!-- Produced by OmniGraffle Professional 5.4.4
--></metadata><defs><font-face font-family="Helvetica Neue" font-size="16"
panose-1="2 0 5 3 0 0 0 2 0 4" units-per-em="1000" underline-position="-100"
underline-thickness="50" slope="0" x-height="517" cap-height="714"
ascent="951.99585" descent="-212.99744"
font-weight="500"><font-face-src><font-face-name
name="HelveticaNeue"/></font-face-src></font-face><marker orient="auto"
overflow="visible" markerUnits="strokeWidth" id="FilledArrow_Marker" viewBox="-1
-4 10 8" markerWidth="10" markerHeight="8" color="black"><g><path d="M 8 0 L 0
-3 L 0 3 Z" fill="currentColor" stroke="currentColor"
stroke-width="1"/></g></marker></defs><g stroke="none" stroke-opacity="1"
stroke-dasharray="none" fill="none" fill-opacity="1"><title>Canvas
1</title><rect fill="white" width="805.88977"
height="536.27556"/><g><title>Layer 1</title><rect x="201.43709" y="148.91563"
width="88.865815" height="36.026683" stroke="#0080ff" stroke-linecap="round"
stroke-linejoin="round" stroke-width="2"/><text transform="translate(206.43709
157.70498)" fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="7.8649073" y="15"
textLength="63.136">maturing</tspan></text><rect x="10.4153" y="97.854194"
width="123.69161" height="36.026683" stroke="#ff8000" stroke-linecap="round"
stroke-linejoin="round" stroke-width="2"/><text transform="translate(15.4153
106.643536)" fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="10.7658034" y="15"
textLength="92.160004">experimental</tspan></text><rect x="339.64294"
y="207.75286" width="64.848027" height="36.026683" stroke="green"
stroke-linecap="round" stroke-linejoin="round" stroke-width="2"/><text
transform="translate(344.64294 216.5422)" fill="black"><tspan
font-family="Helvetica Neue" font-size="16" font-weight="500" x="5.7920134"
y="15" textLength="43.264">stable</tspan></text><rect x="613.9284" y="118.27877"
width="67.249806" height="36.026683" stroke="#ff8000" stroke-linecap="round"
stroke-linejoin="round" stroke-width="2"/><text transform="translate(618.9284
127.06811)" fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="5.9529028" y="15" textLength="5.328">r</tspan><tspan
font-family="Helvetica Neue" font-size="16" font-weight="500" x="10.992903"
y="15" textLength="22.511999">etir</tspan><tspan font-family="Helvetica Neue"
font-size="16" font-weight="500" x="33.216903" y="15"
textLength="18.08">ed</tspan></text><rect x="325.78587" y="50.19685"
width="85.263146" height="36.026683" stroke="#0080ff" stroke-linecap="round"
stroke-linejoin="round" stroke-width="2"/><text transform="translate(330.78587
58.986193)" fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="7.543573" y="15"
textLength="60.176">dormant</tspan></text><rect x="468.56405" y="142.10744"
width="112.8836" height="36.026683" stroke="#0080ff" stroke-linecap="round"
stroke-linejoin="round" stroke-width="2"/><text transform="translate(473.56405
150.89678)" fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="9.801801" y="15"
textLength="83.28">questioning</tspan></text><line x1="135.106906"
y1="134.351596" x2="190.93937" y2="150.77291"
marker-end="url(#FilledArrow_Marker)" stroke="black" stroke-linecap="round"
stroke-linejoin="round" stroke-width="1"/><line x1="286.65074" y1="185.94232"
x2="329.67024" y2="205.99944" marker-end="url(#FilledArrow_Marker)"
stroke="black" stroke-linecap="round" stroke-linejoin="round"
stroke-width="1"/><path d="M 379.93472 206.75285 C 387.55754 192.63012 401.66897
174.0594 426.21202 163.52488 C 436.33446 159.18006 447.11932 156.67954 457.70464
155.39871" marker-end="url(#FilledArrow_Marker)" stroke="black"
stroke-linecap="round" stroke-linejoin="round" stroke-width="1"/><line
x1="582.44766" y1="148.95154" x2="603.2104" y2="144.91434"
marker-end="url(#FilledArrow_Marker)" stroke="black" stroke-linecap="round"
stroke-linejoin="round" stroke-width="1"/><path d="M 501.44774 179.13413 C
487.32306 189.48841 467.98586 202.01855 446.6366 211.18222 C 435.19097 216.09499
424.5888 219.42992 415.18313 221.6778" marker-end="url(#FilledArrow_Marker)"
stroke="black" stroke-linecap="round" stroke-linejoin="round"
stroke-width="1"/><path d="M 412.04903 66.0841 C 438.72737 66.23414 475.24547
68.794908 514.7185 78.42248 C 552.22946 87.57149 584.04206 101.061534 607.12235
112.71587" marker-end="url(#FilledArrow_Marker)" stroke="black"
stroke-linecap="round" stroke-linejoin="round" stroke-width="1"/><path d="M
135.10692 119.41541 C 165.84715 119.854806 204.35783 118.583695 242.39084
112.46344 C 276.08222 107.04184 303.03701 98.838735 323.23284 90.96218"
marker-end="url(#FilledArrow_Marker)" stroke="black" stroke-linecap="round"
stroke-linejoin="round" stroke-width="1"/><path d="M 324.78586 66.603523 C
301.6689 66.933135 270.15767 68.9068 232.17855 75.018384 C 200.11208 80.178506
169.19774 87.361075 143.238715 94.26646" marker-end="url(#FilledArrow_Marker)"
stroke="black" stroke-linecap="round" stroke-linejoin="round"
stroke-width="1"/><rect x="707.0446" y="118.27877" width="85.263146"
height="36.026683" stroke="red" stroke-linecap="round" stroke-linejoin="round"
stroke-width="2"/><text transform="translate(712.0446 127.06811)"
fill="black"><tspan font-family="Helvetica Neue" font-size="16"
font-weight="500" x="7.255573" y="15" textLength="13.92">ar</tspan><tspan
font-family="Helvetica Neue" font-size="16" font-weight="500" x="20.887573"
y="15" textLength="47.12">chived</tspan></text><line x1="682.1782"
y1="136.29211" x2="696.1446" y2="136.29211"
marker-end="url(#FilledArrow_Marker)" stroke="black" stroke-linecap="round"
stroke-linejoin="round" stroke-width="1"/></g></g></svg>
<?xml version="1.0" encoding="UTF-8"?>
<svg width="510.24pt" height="184.25pt" version="1.1" viewBox="0 0 510.24 184.25" xmlns="http://www.w3.org/2000/svg">
<style>
text {
fill: white;
font-family: "Helvetica Neue";
}
</style>
<defs>
<marker id="a" color="black" overflow="visible" markerHeight="6" markerWidth="7" orient="auto" viewBox="-1 -3 7 6">
<path d="m4.8 0-4.8-1.8v3.6z" fill="currentColor" stroke="currentColor"/>
</marker>
</defs>
<g fill="none">
<title>Canvas 1</title>
<rect width="510.24" height="184.25" fill="#fff"/>
<g>
<title>Layer 1</title>
<rect x="5.6693" y="5.6693" width="116.22" height="48.189" fill="#fd8008"/>
<text transform="translate(63.7793 29.7638)" dominant-baseline="middle" text-anchor="middle">experimental</text>
<rect x="161.57" y="113.39" width="150.24" height="68.031" fill="#108001"/>
<text transform="translate(236.69 147.4055)" dominant-baseline="middle" text-anchor="middle" font-size="19">stable</text>
<path d="m63.356 53.858c2.0388 19.203 10.427 45.968 38.691 65.197 13.679 9.3061 30.217 15.625 46.951 19.9" marker-end="url(#a)" stroke="#000" stroke-linecap="round" stroke-linejoin="round" stroke-width="2"/>
<path d="m311.81 131.57c18.392-5.7638 38.128-13.509 56.693-23.85 25.216-14.046 43.275-30.1 55.731-43.973" marker-end="url(#a)" stroke="#000" stroke-linecap="round" stroke-linejoin="round" stroke-width="2"/>
<rect x="391.18" y="119.06" width="113.39" height="48.189" fill="#074080"/>
<text transform="translate(447.875 143.1545)" dominant-baseline="middle" text-anchor="middle">superseded</text>
<line x1="311.81" x2="378.29" y1="147.22" y2="145.23" marker-end="url(#a)" stroke="#000" stroke-linecap="round" stroke-linejoin="round" stroke-width="2"/>
<rect x="391.18" y="5.6693" width="113.39" height="48.189" fill="#fd8008"/>
<text transform="translate(447.875 29.7638)" dominant-baseline="middle" text-anchor="middle">deprecated</text>
</g>
</g>
</svg>

Before

Width:  |  Height:  |  Size: 6.0 KiB

After

Width:  |  Height:  |  Size: 1.9 KiB

View File

@ -43,9 +43,17 @@ test_that("disk works", {
expect_s3_class(x, "disk")
pdf(NULL) # prevent Rplots.pdf being created
expect_silent(barplot(as.disk(c(10, 20, 40))))
expect_silent(plot(as.disk(c(10, 20, 40))))
expect_silent(plot(as.disk(c(10, 20, 40)), expand = FALSE))
expect_silent(plot(as.disk(c(10, 20, 40)), mo = "esco", ab = "cipr"))
if (require("ggplot2")) {
expect_s3_class(ggplot(as.disk(c(10, 20, 40))), "gg")
expect_s3_class(ggplot(as.disk(c(10, 20, 40)), expand = FALSE), "gg")
expect_s3_class(ggplot(as.disk(c(10, 20, 40)), mo = "esco", ab = "cipr"), "gg")
}
expect_output(print(as.disk(12)))
library(dplyr, warn.conflicts = FALSE)
expect_output(print(tibble(d = as.disk(12))))

View File

@ -51,6 +51,13 @@ test_that("mic works", {
pdf(NULL) # prevent Rplots.pdf being created
expect_silent(barplot(as.mic(c(1, 2, 4, 8))))
expect_silent(plot(as.mic(c(1, 2, 4, 8))))
expect_silent(plot(as.mic(c(1, 2, 4, 8)), expand = FALSE))
expect_silent(plot(as.mic(c(1, 2, 4, 8)), mo = "esco", ab = "cipr"))
if (require("ggplot2")) {
expect_s3_class(ggplot(as.mic(c(1, 2, 4, 8))), "gg")
expect_s3_class(ggplot(as.mic(c(1, 2, 4, 8)), expand = FALSE), "gg")
expect_s3_class(ggplot(as.mic(c(1, 2, 4, 8, 32)), mo = "esco", ab = "cipr"), "gg")
}
expect_output(print(as.mic(c(1, 2, 4, 8))))
expect_equal(summary(as.mic(c(2, 8))),

View File

@ -111,34 +111,26 @@ bacteria <- c("Escherichia coli", "Staphylococcus aureus",
"Streptococcus pneumoniae", "Klebsiella pneumoniae")
```
## Other variables
For completeness, we can also add the hospital where the patients was admitted and we need to define valid antibmicrobial results for our randomisation:
```{r create other}
hospitals <- c("Hospital A", "Hospital B", "Hospital C", "Hospital D")
ab_interpretations <- c("S", "I", "R")
```
## Put everything together
Using the `sample()` function, we can randomly select items from all objects we defined earlier. To let our fake data reflect reality a bit, we will also approximately define the probabilities of bacteria and the antibiotic results with the `prob` parameter.
Using the `sample()` function, we can randomly select items from all objects we defined earlier. To let our fake data reflect reality a bit, we will also approximately define the probabilities of bacteria and the antibiotic results, using the `random_rsi()` function.
```{r merge data}
sample_size <- 20000
data <- data.frame(date = sample(dates, size = sample_size, replace = TRUE),
patient_id = sample(patients, size = sample_size, replace = TRUE),
hospital = sample(hospitals, size = sample_size, replace = TRUE,
hospital = sample(c("Hospital A",
"Hospital B",
"Hospital C",
"Hospital D"),
size = sample_size, replace = TRUE,
prob = c(0.30, 0.35, 0.15, 0.20)),
bacteria = sample(bacteria, size = sample_size, replace = TRUE,
prob = c(0.50, 0.25, 0.15, 0.10)),
AMX = sample(ab_interpretations, size = sample_size, replace = TRUE,
prob = c(0.60, 0.05, 0.35)),
AMC = sample(ab_interpretations, size = sample_size, replace = TRUE,
prob = c(0.75, 0.10, 0.15)),
CIP = sample(ab_interpretations, size = sample_size, replace = TRUE,
prob = c(0.80, 0.00, 0.20)),
GEN = sample(ab_interpretations, size = sample_size, replace = TRUE,
prob = c(0.92, 0.00, 0.08)))
AMX = random_rsi(sample_size, prob_RSI = c(0.35, 0.60, 0.05)),
AMC = random_rsi(sample_size, prob_RSI = c(0.15, 0.75, 0.10)),
CIP = random_rsi(sample_size, prob_RSI = c(0.20, 0.80, 0.00)),
GEN = random_rsi(sample_size, prob_RSI = c(0.08, 0.92, 0.00)))
```
Using the `left_join()` function from the `dplyr` package, we can 'map' the gender to the patient ID using the `patients_table` object we created earlier:
@ -443,6 +435,7 @@ data_1st %>%
```
## Plots
To show results in plots, most R users would nowadays use the `ggplot2` package. This package lets you create plots in layers. You can read more about it [on their website](https://ggplot2.tidyverse.org/). A quick example would look like these syntaxes:
```{r plot 2, eval = FALSE}
@ -480,7 +473,7 @@ ggplot(data_1st %>% group_by(genus)) +
geom_rsi(x = "genus") +
# split plots on antibiotic
facet_rsi(facet = "antibiotic") +
# set colours to the R/SI interpretations
# set colours to the R/SI interpretations (colour-blind friendly)
scale_rsi_colours() +
# show percentages on y axis
scale_y_percent(breaks = 0:4 * 25) +
@ -506,6 +499,65 @@ data_1st %>%
coord_flip()
```
### Plotting MIC and disk diffusion values
The AMR package also extends the `plot()` and `ggplot()` functions for plotting minimum inhibitory concentrations (MIC, created with `as.mic()`) and disk diffusion diameters (created with `as.disk()`).
With the `random_mic()` and `random_disk()` functions, we can generate sampled values for the new data types (S3 classes) `<mic>` and `<disk>`:
```{r, results='markup'}
mic_values <- random_mic(size = 100)
mic_values
```
```{r}
# base R:
plot(mic_values)
# ggplot2:
ggplot(mic_values)
```
But we could also be more specific, by generating MICs that are likely to be found in *E. coli* for ciprofloxacin:
```{r, results = 'markup', message = FALSE, warning = FALSE}
# this will generate MICs that are likely to be found in E. coli for ciprofloxacin:
mic_values_specific <- random_mic(size = 100, mo = "E. coli", ab = "cipro")
```
For the `plot()` and `ggplot()` function, we can define the microorganism and an antimicrobial agent the same way. This will add the interpretation of those values according to a chosen guidelines (defaults to the latest EUCAST guideline).
Default colours are colour-blind friendly, while maintaining the convention that e.g. 'susceptible' should be green and 'resistant' should be red:
```{r, message = FALSE, warning = FALSE}
# base R:
plot(mic_values_specific, mo = "E. coli", ab = "cipro")
# ggplot2:
ggplot(mic_values_specific, mo = "E. coli", ab = "cipro")
```
For disk diffusion values, there is not much of a difference in plotting:
```{r, results = 'markup'}
# this will generate disks that are likely to be found in E. coli for ciprofloxacin:
disk_values_specific <- random_disk(size = 100, mo = "E. coli", ab = "cipro")
disk_values_specific
```
```{r, message = FALSE, warning = FALSE}
# base R:
plot(disk_values_specific, mo = "E. coli", ab = "cipro")
```
And when using the `ggplot2` package, but now choosing the latest implemented CLSI guideline (notice that the EUCAST-specific term "Incr. exposure" has changed to "Intermediate"):
```{r, message = FALSE, warning = FALSE}
# and ggplot2, but now choosing an old CLSI guideline:
ggplot(disk_values_specific,
mo = "E. coli",
ab = "cipro",
guideline = "CLSI")
```
## Independence test
The next example uses the `example_isolates` data set. This is a data set included with this package and contains 2,000 microbial isolates with their full antibiograms. It reflects reality and can be used to practice AMR data analysis.

View File

@ -117,7 +117,7 @@ run_it <- microbenchmark(mo_name(x),
print(run_it, unit = "ms", signif = 3)
```
So getting official taxonomic names of `r format(length(x), big.mark = ",")` (!!) items consisting of `r n_distinct(x)` unique values only takes `r round(median(run_it$time, na.rm = TRUE) / 1e9, 3)` seconds. That is `r round(mean(run_it$time, na.rm = TRUE) / 1e6 / n_distinct(x), 3)` milliseconds per unique item on average. You only lose time on your unique input values.
So getting official taxonomic names of `r format(length(x), big.mark = ",")` (!!) items consisting of `r n_distinct(x)` unique values only takes `r round(median(run_it$time, na.rm = TRUE) / 1e9, 3)` seconds. That is `r round(median(run_it$time, na.rm = TRUE) / length(x), 0)` nanoseconds on average. You only lose time on your unique input values.
### Precalculated results