(v0.7.0.9008) T. vaginalis, rsi_df

This commit is contained in:
dr. M.S. (Matthijs) Berends 2019-06-13 14:28:46 +02:00
parent 699e87ab4a
commit 254745061c
32 changed files with 382 additions and 259 deletions

View File

@ -1,6 +1,6 @@
Package: AMR
Version: 0.7.0.9007
Date: 2019-06-12
Version: 0.7.0.9008
Date: 2019-06-13
Title: Antimicrobial Resistance Analysis
Authors@R: c(
person(

View File

@ -172,6 +172,7 @@ export(ratio)
export(read.4D)
export(resistance_predict)
export(right_join_microorganisms)
export(rsi_df)
export(rsi_predict)
export(scale_rsi_colours)
export(scale_type.ab)

15
NEWS.md
View File

@ -1,6 +1,17 @@
# AMR 0.7.0.9007
# AMR 0.7.0.9008
#### New
* Function `rsi_df()` to transform a `data.frame` to a data set containing only the microbial interpretation (S, I, R), the antibiotic, the percentage of S/I/R and the number of available isolates. This is a convenient combinations of existing functions `count_df()` and `portion_df()` to immediately show resistance percentages and number of available isolates:
```r
septic_patients %>%
select(AMX, CIP) %>%
rsi_df()
# antibiotic interpretation value isolates
# 1 Amoxicillin SI 0.4442636 546
# 2 Amoxicillin R 0.5557364 683
# 3 Ciprofloxacin SI 0.8381831 1181
# 4 Ciprofloxacin R 0.1618169 228
```
* Support for all scientifically published pathotypes of *E. coli* to date. Supported are: AIEC (Adherent-Invasive *E. coli*), ATEC (Atypical Entero-pathogenic *E. coli*), DAEC (Diffusely Adhering *E. coli*), EAEC (Entero-Aggresive *E. coli*), EHEC (Entero-Haemorrhagic *E. coli*), EIEC (Entero-Invasive *E. coli*), EPEC (Entero-Pathogenic *E. coli*), ETEC (Entero-Toxigenic *E. coli*), NMEC (Neonatal Meningitiscausing *E. coli*), STEC (Shiga-toxin producing *E. coli*) and UPEC (Uropathogenic *E. coli*). All these lead to the microbial ID of *E. coli*:
```r
as.mo("UPEC")
@ -11,6 +22,7 @@
* Function `mo_info()` as an analogy to `ab_info()`. The `mo_info()` prints a list with the full taxonomy, authors, and the URL to the online database of a microorganism
#### Changed
* Column names of output `count_df()` and `portion_df()` are now lowercase
* Fixed bug in translation of microorganism names
* Fixed bug in determining taxonomic kingdoms
* Algorithm improvements for `as.ab()` and `as.mo()` to understand even more severely misspelled input
@ -23,6 +35,7 @@
* Removed `latest_annual_release` from the `catalogue_of_life_version()` function
* Removed antibiotic code `PVM1` from the `antibiotics` data set as this was a duplicate of `PME`
* Fixed bug where not all old taxonomic named would not be printed when using a vector as input for `as.mo()`
* Manually added *Trichomonas vaginalis* from the kingdom of Protozoa, which is missing from the Catalogue of Life
#### Other
* Fixed a note thrown by CRAN tests

1
R/ab.R
View File

@ -203,7 +203,6 @@ as.ab <- function(x) {
# try by removing all spaces
if (x[i] %like% " ") {
found <- suppressWarnings(as.ab(gsub(" +", "", x[i])))
print(found)
if (length(found) > 0 & !is.na(found)) {
x_new[i] <- found[1L]
next

View File

@ -136,6 +136,9 @@ age <- function(x, reference = Sys.Date(), exact = FALSE) {
#' select(age_group, CIP) %>%
#' ggplot_rsi(x = "age_group")
age_groups <- function(x, split_at = c(12, 25, 55, 75)) {
if (!is.numeric(x)) {
stop("`x` and must be numeric, not a ", paste0(class(x), collapse = "/"), ".")
}
if (is.character(split_at)) {
split_at <- split_at[1L]
if (split_at %like% "^(child|kid|junior)") {
@ -148,11 +151,7 @@ age_groups <- function(x, split_at = c(12, 25, 55, 75)) {
split_at <- 1:10 * 10
}
}
split_at <- as.integer(split_at)
if (!is.numeric(x) | !is.numeric(split_at)) {
stop("`x` and `split_at` must both be numeric.")
}
split_at <- sort(unique(split_at))
split_at <- sort(unique(as.integer(split_at)))
if (!split_at[1] == 0) {
# add base number 0
split_at <- c(0, split_at)

View File

@ -29,9 +29,11 @@
#' @inheritSection as.rsi Interpretation of S, I and R
#' @details These functions are meant to count isolates. Use the \code{\link{portion}_*} functions to calculate microbial resistance.
#'
#' \code{n_rsi} is an alias of \code{count_all}. They can be used to count all available isolates, i.e. where all input antibiotics have an available result (S, I or R). Their use is equal to \code{\link{n_distinct}}. Their function is equal to \code{count_S(...) + count_IR(...)}.
#' The function \code{n_rsi} is an alias of \code{count_all}. They can be used to count all available isolates, i.e. where all input antibiotics have an available result (S, I or R). Their use is equal to \code{\link{n_distinct}}. Their function is equal to \code{count_S(...) + count_IR(...)}.
#'
#' \code{count_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and counts the amounts of R, I and S. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each variable with class \code{"rsi"}.
#' The function \code{count_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and counts the amounts of S, I and R. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each variable with class \code{"rsi"}.
#'
#' The function \code{rsi_df} works exactly like \code{count_df}, but add the percentage of S, I and R.
#' @source Wickham H. \strong{Tidy Data.} The Journal of Statistical Software, vol. 59, 2014. \url{http://vita.had.co.nz/papers/tidy-data.html}
#' @seealso \code{\link{portion}_*} to calculate microbial resistance and susceptibility.
#' @keywords resistance susceptibility rsi antibiotics isolate isolates

View File

@ -55,7 +55,7 @@
#'
#' A data set containing the microbial taxonomy of six kingdoms from the Catalogue of Life. MO codes can be looked up using \code{\link{as.mo}}.
#' @inheritSection catalogue_of_life Catalogue of Life
#' @format A \code{\link{data.frame}} with 67,903 observations and 16 variables:
#' @format A \code{\link{data.frame}} with 67,906 observations and 16 variables:
#' \describe{
#' \item{\code{mo}}{ID of microorganism as used by this package}
#' \item{\code{col_id}}{Catalogue of Life ID}
@ -69,9 +69,10 @@
#' }
#' @details Manually added were:
#' \itemize{
#' \item{9 species of \emph{Streptococcus} (beta haemolytic groups A, B, C, D, F, G, H, K and unspecified)}
#' \item{2 species of \emph{Staphylococcus} (coagulase-negative [CoNS] and coagulase-positive [CoPS])}
#' \item{3 other undefined (unknown, unknown Gram negatives and unknown Gram positives)}
#' \item{9 entries of \emph{Streptococcus} (beta haemolytic groups A, B, C, D, F, G, H, K and unspecified)}
#' \item{2 entries of \emph{Staphylococcus} (coagulase-negative [CoNS] and coagulase-positive [CoPS])}
#' \item{3 entries of Trichomonas (Trichomonas vaginalis, and its family and genus)}
#' \item{3 other 'undefined' entries (unknown, unknown Gram negatives and unknown Gram positives)}
#' \item{8,830 species from the DSMZ (Deutsche Sammlung von Mikroorganismen und Zellkulturen) that are not in the Catalogue of Life}
#' }
#' @section About the records from DSMZ (see source):

View File

@ -24,11 +24,11 @@
#' Use these functions to create bar plots for antimicrobial resistance analysis. All functions rely on internal \code{\link[ggplot2]{ggplot}2} functions.
#' @param data a \code{data.frame} with column(s) of class \code{"rsi"} (see \code{\link{as.rsi}})
#' @param position position adjustment of bars, either \code{"fill"} (default when \code{fun} is \code{\link{count_df}}), \code{"stack"} (default when \code{fun} is \code{\link{portion_df}}) or \code{"dodge"}
#' @param x variable to show on x axis, either \code{"Antibiotic"} (default) or \code{"Interpretation"} or a grouping variable
#' @param fill variable to categorise using the plots legend, either \code{"Antibiotic"} (default) or \code{"Interpretation"} or a grouping variable
#' @param x variable to show on x axis, either \code{"antibiotic"} (default) or \code{"interpretation"} or a grouping variable
#' @param fill variable to categorise using the plots legend, either \code{"antibiotic"} (default) or \code{"interpretation"} or a grouping variable
#' @param breaks numeric vector of positions
#' @param limits numeric vector of length two providing limits of the scale, use \code{NA} to refer to the existing minimum or maximum
#' @param facet variable to split plots by, either \code{"Interpretation"} (default) or \code{"Antibiotic"} or a grouping variable
#' @param facet variable to split plots by, either \code{"interpretation"} (default) or \code{"antibiotic"} or a grouping variable
#' @param fun function to transform \code{data}, either \code{\link{count_df}} (default) or \code{\link{portion_df}}
#' @inheritParams portion
#' @param nrow (when using \code{facet}) number of rows
@ -129,7 +129,7 @@
#' select(hospital_id, AMX, NIT, FOS, TMP, CIP) %>%
#' group_by(hospital_id) %>%
#' ggplot_rsi(x = "hospital_id",
#' facet = "Antibiotic",
#' facet = "antibiotic",
#' nrow = 1,
#' title = "AMR of Anti-UTI Drugs Per Hospital",
#' x.title = "Hospital",
@ -150,7 +150,7 @@
#' # group by MO
#' group_by(bug) %>%
#' # plot the thing, putting MOs on the facet
#' ggplot_rsi(x = "Antibiotic",
#' ggplot_rsi(x = "antibiotic",
#' facet = "bug",
#' translate_ab = FALSE,
#' nrow = 1,
@ -161,8 +161,8 @@
#' }
ggplot_rsi <- function(data,
position = NULL,
x = "Antibiotic",
fill = "Interpretation",
x = "antibiotic",
fill = "interpretation",
# params = list(),
facet = NULL,
breaks = seq(0, 1, 0.1),
@ -226,7 +226,7 @@ ggplot_rsi <- function(data,
fun = fun, combine_SI = combine_SI, combine_IR = combine_IR, ...) +
theme_rsi()
if (fill == "Interpretation") {
if (fill == "interpretation") {
# set RSI colours
if (isFALSE(colours) & missing(datalabels.colour)) {
# set datalabel colour to middle gray
@ -267,8 +267,8 @@ ggplot_rsi <- function(data,
#' @rdname ggplot_rsi
#' @export
geom_rsi <- function(position = NULL,
x = c("Antibiotic", "Interpretation"),
fill = "Interpretation",
x = c("antibiotic", "interpretation"),
fill = "interpretation",
translate_ab = "name",
language = get_locale(),
combine_SI = TRUE,
@ -286,7 +286,7 @@ geom_rsi <- function(position = NULL,
if (!fun_name %in% c("portion_df", "count_df", "fun")) {
stop("`fun` must be portion_df or count_df")
}
y <- "Value"
y <- "value"
if (identical(fun, count_df)) {
if (missing(position) | is.null(position)) {
position <- "fill"
@ -312,10 +312,10 @@ geom_rsi <- function(position = NULL,
x <- substr(x, 2, nchar(x) - 1)
}
if (tolower(x) %in% tolower(c('ab', 'antibiotic', 'abx', 'antibiotics'))) {
x <- "Antibiotic"
} else if (tolower(x) %in% tolower(c('SIR', 'RSI', 'interpretation', 'interpretations', 'result'))) {
x <- "Interpretation"
if (tolower(x) %in% tolower(c('ab', 'abx', 'antibiotics'))) {
x <- "antibiotic"
} else if (tolower(x) %in% tolower(c('SIR', 'RSI', 'interpretations', 'result'))) {
x <- "interpretation"
}
ggplot2::layer(geom = "bar", stat = "identity", position = position,
@ -332,7 +332,7 @@ geom_rsi <- function(position = NULL,
#' @rdname ggplot_rsi
#' @export
facet_rsi <- function(facet = c("Interpretation", "Antibiotic"), nrow = NULL) {
facet_rsi <- function(facet = c("interpretation", "antibiotic"), nrow = NULL) {
stopifnot_installed_package("ggplot2")
@ -347,10 +347,10 @@ facet_rsi <- function(facet = c("Interpretation", "Antibiotic"), nrow = NULL) {
facet <- substr(facet, 2, nchar(facet) - 1)
}
if (tolower(facet) %in% tolower(c('SIR', 'RSI', 'interpretation', 'interpretations', 'result'))) {
facet <- "Interpretation"
} else if (tolower(facet) %in% tolower(c('ab', 'antibiotic', 'abx', 'antibiotics'))) {
facet <- "Antibiotic"
if (tolower(facet) %in% tolower(c('SIR', 'RSI', 'interpretations', 'result'))) {
facet <- "interpretation"
} else if (tolower(facet) %in% tolower(c('ab', 'abx', 'antibiotics'))) {
facet <- "antibiotic"
}
ggplot2::facet_wrap(facets = facet, scales = "free_x", nrow = nrow)
@ -408,7 +408,7 @@ theme_rsi <- function() {
#' @importFrom dplyr mutate %>% group_by_at
#' @export
labels_rsi_count <- function(position = NULL,
x = "Antibiotic",
x = "antibiotic",
translate_ab = "name",
combine_SI = TRUE,
combine_IR = FALSE,
@ -424,7 +424,7 @@ labels_rsi_count <- function(position = NULL,
x_name <- x
ggplot2::geom_text(mapping = ggplot2::aes_string(label = "lbl",
x = x,
y = "Value"),
y = "value"),
position = position,
inherit.aes = FALSE,
size = datalabels.size,
@ -438,7 +438,7 @@ labels_rsi_count <- function(position = NULL,
combine_SI = combine_SI,
combine_IR = combine_IR) %>%
group_by_at(x_name) %>%
mutate(lbl = paste0(percent(Value / sum(Value, na.rm = TRUE), force_zero = TRUE),
"\n(n=", Value, ")"))
mutate(lbl = paste0(percent(value / sum(value, na.rm = TRUE), force_zero = TRUE),
"\n(n=", value, ")"))
})
}

View File

@ -38,7 +38,9 @@
#'
#' These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the \code{\link[AMR]{count}} functions to count isolates. \emph{Low counts can infuence the outcome - these \code{portion} functions may camouflage this, since they only return the portion albeit being dependent on the \code{minimum} parameter.}
#'
#' \code{portion_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and calculates the portions R, I and S. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each variable with class \code{"rsi"}.
#' The function \code{portion_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and calculates the portions R, I and S. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each group and each variable with class \code{"rsi"}.
#'
#' The function \code{rsi_df} works exactly like \code{portion_df}, but add the number of isolates.
#' \if{html}{
# (created with https://www.latex4technics.com/)
#' \cr\cr

View File

@ -151,6 +151,7 @@ rsi_calc <- function(...,
}
}
#' @importFrom dplyr %>% summarise_if mutate select everything bind_rows
rsi_calc_df <- function(type, # "portion" or "count"
data,
translate_ab = "name",
@ -196,8 +197,8 @@ rsi_calc_df <- function(type, # "portion" or "count"
.funs = int_fn)
}
summ %>%
mutate(Interpretation = int) %>%
select(Interpretation, everything())
mutate(interpretation = int) %>%
select(interpretation, everything())
}
resS <- get_summaryfunction("S")
@ -209,28 +210,29 @@ rsi_calc_df <- function(type, # "portion" or "count"
if (isFALSE(combine_SI) & isFALSE(combine_IR)) {
res <- bind_rows(resS, resI, resR) %>%
mutate(Interpretation = factor(Interpretation,
mutate(interpretation = factor(interpretation,
levels = c("S", "I", "R"),
ordered = TRUE))
} else if (isTRUE(combine_IR)) {
res <- bind_rows(resS, resIR) %>%
mutate(Interpretation = factor(Interpretation,
mutate(interpretation = factor(interpretation,
levels = c("S", "IR"),
ordered = TRUE))
} else if (isTRUE(combine_SI)) {
res <- bind_rows(resSI, resR) %>%
mutate(Interpretation = factor(Interpretation,
mutate(interpretation = factor(interpretation,
levels = c("SI", "R"),
ordered = TRUE))
}
res <- res %>%
tidyr::gather(Antibiotic, Value, -Interpretation, -data.groups)
tidyr::gather(antibiotic, value, -interpretation, -data.groups) %>%
select(antibiotic, everything())
if (!translate_ab == FALSE) {
res <- res %>% mutate(Antibiotic = ab_property(Antibiotic, property = translate_ab, language = language))
res <- res %>% mutate(antibiotic = ab_property(antibiotic, property = translate_ab, language = language))
}
res

58
R/rsi_df.R Normal file
View File

@ -0,0 +1,58 @@
# ==================================================================== #
# TITLE #
# Antimicrobial Resistance (AMR) Analysis #
# #
# SOURCE #
# https://gitlab.com/msberends/AMR #
# #
# LICENCE #
# (c) 2019 Berends MS (m.s.berends@umcg.nl), Luz CF (c.f.luz@umcg.nl) #
# #
# 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. #
# #
# This R package was created for academic research and was publicly #
# released in the hope that it will be useful, but it comes WITHOUT #
# ANY WARRANTY OR LIABILITY. #
# Visit our website for more info: https://msberends.gitlab.io/AMR. #
# ==================================================================== #
#' @rdname portion
#' @rdname count
#' @importFrom dplyr %>% select_if bind_rows summarise_if mutate group_vars select everything
#' @export
rsi_df <- function(data,
translate_ab = "name",
language = get_locale(),
minimum = 30,
as_percent = FALSE,
combine_SI = TRUE,
combine_IR = FALSE) {
portions <- rsi_calc_df(type = "portion",
data = data,
translate_ab = translate_ab,
language = language,
minimum = minimum,
as_percent = as_percent,
combine_SI = combine_SI,
combine_IR = combine_IR,
combine_SI_missing = missing(combine_SI))
counts <- rsi_calc_df(type = "count",
data = data,
translate_ab = FALSE,
language = "en",
minimum = minimum,
as_percent = as_percent,
combine_SI = combine_SI,
combine_IR = combine_IR,
combine_SI_missing = missing(combine_SI))
data.frame(portions,
isolates = counts$value,
stringsAsFactors = FALSE)
}

Binary file not shown.

View File

@ -444,7 +444,43 @@ MOs <- MOs %>%
fullname = "Beta-haemolytic Streptococcus",
ref = NA_character_,
species_id = "",
source = "manually added")
source = "manually added"),
# Trichomonas vaginalis is missing, same order as Dientamoeba
MOs %>%
filter(fullname == "Dientamoeba") %>%
mutate(mo = gsub("DNTMB", "THMNS", mo),
col_id = NA,
fullname = "Trichomonas",
family = "Trichomonadidae",
genus = "Trichomonas",
source = "manually added",
ref = "Donne, 1836",
species_id = ""),
MOs %>%
filter(fullname == "Dientamoeba fragilis") %>%
mutate(mo = gsub("DNTMB", "THMNS", mo),
mo = gsub("FRA", "VAG", mo),
col_id = NA,
fullname = "Trichomonas vaginalis",
family = "Trichomonadidae",
genus = "Trichomonas",
species = "vaginalis",
source = "manually added",
ref = "Donne, 1836",
species_id = ""),
MOs %>% # add family as such too
filter(fullname == "Monocercomonadidae") %>%
mutate(mo = gsub("MNCRCMND", "TRCHMNDD", mo),
col_id = NA,
fullname = "Trichomonadidae",
family = "Trichomonadidae",
rank = "family",
genus = "",
species = "",
source = "manually added",
ref = "",
species_id = ""),
)
@ -485,8 +521,12 @@ MOs <- MOs %>%
TRUE ~ 3
))
# arrange
MOs <- MOs %>% arrange(fullname)
MOs.old <- MOs.old %>% arrange(fullname)
# save it
MOs <- as.data.frame(MOs %>% arrange(fullname), stringsAsFactors = FALSE)
MOs <- as.data.frame(MOs, stringsAsFactors = FALSE)
MOs.old <- as.data.frame(MOs.old, stringsAsFactors = FALSE)
class(MOs$mo) <- "mo"

View File

@ -154,6 +154,8 @@ pt vegetative vegetativo FALSE FALSE
pt ([([ ]*?)group \\1grupo FALSE FALSE
pt ([([ ]*?)Group \\1Grupo FALSE FALSE
de clavulanic acid Clavulansäure FALSE TRUE
nl 4-aminosalicylic acid 4-aminosalicylzuur
nl Adefovir dipivoxil Adefovir
nl Aldesulfone sodium Aldesulfon
@ -348,8 +350,10 @@ nl Thiamphenicol Thiamfenicol
nl Thioacetazone/isoniazid Thioacetazon/isoniazide
nl Ticarcillin Ticarcilline
nl Ticarcillin/beta-lactamase inhibitor Ticarcilline/enzymremmer
nl Ticarcillin/clavulanic acid Ticarcilline/clavulaanzuur
nl Tinidazole Tinidazol
nl Tobramycin Tobramycine
nl Trimethoprim/sulfamethoxazole Trimethoprim/sulfamethoxazol
nl Troleandomycin Troleandomycine
nl Trovafloxacin Trovafloxacine
nl Vancomycin Vancomycine

Can't render this file because it has a wrong number of fields in line 157.

Binary file not shown.

Binary file not shown.

View File

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

View File

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

View File

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

View File

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

View File

@ -78,7 +78,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">0.7.0.9007</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.0.9008</span>
</span>
</div>
@ -232,20 +232,31 @@
</div>
<div id="amr-0709007" class="section level1">
<div id="amr-0709008" class="section level1">
<h1 class="page-header">
<a href="#amr-0709007" class="anchor"></a>AMR 0.7.0.9007<small> Unreleased </small>
<a href="#amr-0709008" class="anchor"></a>AMR 0.7.0.9008<small> Unreleased </small>
</h1>
<div id="new" class="section level4">
<h4 class="hasAnchor">
<a href="#new" class="anchor"></a>New</h4>
<ul>
<li>
<p>Function <code><a href="../reference/portion.html">rsi_df()</a></code> to transform a <code>data.frame</code> to a data set containing only the microbial interpretation (S, I, R), the antibiotic, the percentage of S/I/R and the number of available isolates. This is a convenient combinations of existing functions <code><a href="../reference/count.html">count_df()</a></code> and <code><a href="../reference/portion.html">portion_df()</a></code> to immediately show resistance percentages and number of available isolates:</p>
<div class="sourceCode" id="cb1"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb1-1" title="1">septic_patients <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb1-2" title="2"><span class="st"> </span><span class="kw">select</span>(AMX, CIP) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb1-3" title="3"><span class="st"> </span><span class="kw"><a href="../reference/portion.html">rsi_df</a></span>()</a>
<a class="sourceLine" id="cb1-4" title="4"><span class="co"># antibiotic interpretation value isolates</span></a>
<a class="sourceLine" id="cb1-5" title="5"><span class="co"># 1 Amoxicillin SI 0.4442636 546</span></a>
<a class="sourceLine" id="cb1-6" title="6"><span class="co"># 2 Amoxicillin R 0.5557364 683</span></a>
<a class="sourceLine" id="cb1-7" title="7"><span class="co"># 3 Ciprofloxacin SI 0.8381831 1181</span></a>
<a class="sourceLine" id="cb1-8" title="8"><span class="co"># 4 Ciprofloxacin R 0.1618169 228</span></a></code></pre></div>
</li>
<li>
<p>Support for all scientifically published pathotypes of <em>E. coli</em> to date. Supported are: AIEC (Adherent-Invasive <em>E. coli</em>), ATEC (Atypical Entero-pathogenic <em>E. coli</em>), DAEC (Diffusely Adhering <em>E. coli</em>), EAEC (Entero-Aggresive <em>E. coli</em>), EHEC (Entero-Haemorrhagic <em>E. coli</em>), EIEC (Entero-Invasive <em>E. coli</em>), EPEC (Entero-Pathogenic <em>E. coli</em>), ETEC (Entero-Toxigenic <em>E. coli</em>), NMEC (Neonatal Meningitiscausing <em>E. coli</em>), STEC (Shiga-toxin producing <em>E. coli</em>) and UPEC (Uropathogenic <em>E. coli</em>). All these lead to the microbial ID of <em>E. coli</em>:</p>
<div class="sourceCode" id="cb1"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb1-1" title="1"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"UPEC"</span>)</a>
<a class="sourceLine" id="cb1-2" title="2"><span class="co"># B_ESCHR_COL</span></a>
<a class="sourceLine" id="cb1-3" title="3"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"UPEC"</span>)</a>
<a class="sourceLine" id="cb1-4" title="4"><span class="co"># "Escherichia coli"</span></a></code></pre></div>
<div class="sourceCode" id="cb2"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb2-1" title="1"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"UPEC"</span>)</a>
<a class="sourceLine" id="cb2-2" title="2"><span class="co"># B_ESCHR_COL</span></a>
<a class="sourceLine" id="cb2-3" title="3"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"UPEC"</span>)</a>
<a class="sourceLine" id="cb2-4" title="4"><span class="co"># "Escherichia coli"</span></a></code></pre></div>
</li>
<li><p>Function <code><a href="../reference/mo_property.html">mo_info()</a></code> as an analogy to <code><a href="../reference/ab_property.html">ab_info()</a></code>. The <code><a href="../reference/mo_property.html">mo_info()</a></code> prints a list with the full taxonomy, authors, and the URL to the online database of a microorganism</p></li>
</ul>
@ -254,6 +265,7 @@
<h4 class="hasAnchor">
<a href="#changed" class="anchor"></a>Changed</h4>
<ul>
<li>Column names of output <code><a href="../reference/count.html">count_df()</a></code> and <code><a href="../reference/portion.html">portion_df()</a></code> are now lowercase</li>
<li>Fixed bug in translation of microorganism names</li>
<li>Fixed bug in determining taxonomic kingdoms</li>
<li>Algorithm improvements for <code><a href="../reference/as.ab.html">as.ab()</a></code> and <code><a href="../reference/as.mo.html">as.mo()</a></code> to understand even more severely misspelled input</li>
@ -270,6 +282,7 @@
</li>
<li>Fixed bug where not all old taxonomic named would not be printed when using a vector as input for <code><a href="../reference/as.mo.html">as.mo()</a></code>
</li>
<li>Manually added <em>Trichomonas vaginalis</em> from the kingdom of Protozoa, which is missing from the Catalogue of Life</li>
</ul>
</div>
<div id="other" class="section level4">
@ -338,14 +351,14 @@ Please <a href="https://gitlab.com/msberends/AMR/issues/new?issue%5Btitle%5D=Tra
<li>when all values are unique it now shows a message instead of a warning</li>
<li>
<p>support for boxplots:</p>
<div class="sourceCode" id="cb2"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb2-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb2-2" title="2"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(age) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb2-3" title="3"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/graphics/topics/boxplot">boxplot</a></span>()</a>
<a class="sourceLine" id="cb2-4" title="4"><span class="co"># grouped boxplots:</span></a>
<a class="sourceLine" id="cb2-5" title="5">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb2-6" title="6"><span class="st"> </span><span class="kw">group_by</span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb2-7" title="7"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(age) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb2-8" title="8"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/graphics/topics/boxplot">boxplot</a></span>()</a></code></pre></div>
<div class="sourceCode" id="cb3"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb3-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb3-2" title="2"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(age) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb3-3" title="3"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/graphics/topics/boxplot">boxplot</a></span>()</a>
<a class="sourceLine" id="cb3-4" title="4"><span class="co"># grouped boxplots:</span></a>
<a class="sourceLine" id="cb3-5" title="5">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb3-6" title="6"><span class="st"> </span><span class="kw">group_by</span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb3-7" title="7"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(age) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb3-8" title="8"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/graphics/topics/boxplot">boxplot</a></span>()</a></code></pre></div>
</li>
</ul>
</li>
@ -430,32 +443,32 @@ This data is updated annually - check the included version with the new function
</li>
<li>
<p>New filters for antimicrobial classes. Use these functions to filter isolates on results in one of more antibiotics from a specific class:</p>
<div class="sourceCode" id="cb3"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb3-1" title="1"><span class="kw"><a href="../reference/filter_ab_class.html">filter_aminoglycosides</a></span>()</a>
<a class="sourceLine" id="cb3-2" title="2"><span class="kw"><a href="../reference/filter_ab_class.html">filter_carbapenems</a></span>()</a>
<a class="sourceLine" id="cb3-3" title="3"><span class="kw"><a href="../reference/filter_ab_class.html">filter_cephalosporins</a></span>()</a>
<a class="sourceLine" id="cb3-4" title="4"><span class="kw"><a href="../reference/filter_ab_class.html">filter_1st_cephalosporins</a></span>()</a>
<a class="sourceLine" id="cb3-5" title="5"><span class="kw"><a href="../reference/filter_ab_class.html">filter_2nd_cephalosporins</a></span>()</a>
<a class="sourceLine" id="cb3-6" title="6"><span class="kw"><a href="../reference/filter_ab_class.html">filter_3rd_cephalosporins</a></span>()</a>
<a class="sourceLine" id="cb3-7" title="7"><span class="kw"><a href="../reference/filter_ab_class.html">filter_4th_cephalosporins</a></span>()</a>
<a class="sourceLine" id="cb3-8" title="8"><span class="kw"><a href="../reference/filter_ab_class.html">filter_fluoroquinolones</a></span>()</a>
<a class="sourceLine" id="cb3-9" title="9"><span class="kw"><a href="../reference/filter_ab_class.html">filter_glycopeptides</a></span>()</a>
<a class="sourceLine" id="cb3-10" title="10"><span class="kw"><a href="../reference/filter_ab_class.html">filter_macrolides</a></span>()</a>
<a class="sourceLine" id="cb3-11" title="11"><span class="kw"><a href="../reference/filter_ab_class.html">filter_tetracyclines</a></span>()</a></code></pre></div>
<div class="sourceCode" id="cb4"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb4-1" title="1"><span class="kw"><a href="../reference/filter_ab_class.html">filter_aminoglycosides</a></span>()</a>
<a class="sourceLine" id="cb4-2" title="2"><span class="kw"><a href="../reference/filter_ab_class.html">filter_carbapenems</a></span>()</a>
<a class="sourceLine" id="cb4-3" title="3"><span class="kw"><a href="../reference/filter_ab_class.html">filter_cephalosporins</a></span>()</a>
<a class="sourceLine" id="cb4-4" title="4"><span class="kw"><a href="../reference/filter_ab_class.html">filter_1st_cephalosporins</a></span>()</a>
<a class="sourceLine" id="cb4-5" title="5"><span class="kw"><a href="../reference/filter_ab_class.html">filter_2nd_cephalosporins</a></span>()</a>
<a class="sourceLine" id="cb4-6" title="6"><span class="kw"><a href="../reference/filter_ab_class.html">filter_3rd_cephalosporins</a></span>()</a>
<a class="sourceLine" id="cb4-7" title="7"><span class="kw"><a href="../reference/filter_ab_class.html">filter_4th_cephalosporins</a></span>()</a>
<a class="sourceLine" id="cb4-8" title="8"><span class="kw"><a href="../reference/filter_ab_class.html">filter_fluoroquinolones</a></span>()</a>
<a class="sourceLine" id="cb4-9" title="9"><span class="kw"><a href="../reference/filter_ab_class.html">filter_glycopeptides</a></span>()</a>
<a class="sourceLine" id="cb4-10" title="10"><span class="kw"><a href="../reference/filter_ab_class.html">filter_macrolides</a></span>()</a>
<a class="sourceLine" id="cb4-11" title="11"><span class="kw"><a href="../reference/filter_ab_class.html">filter_tetracyclines</a></span>()</a></code></pre></div>
<p>The <code>antibiotics</code> data set will be searched, after which the input data will be checked for column names with a value in any abbreviations, codes or official names found in the <code>antibiotics</code> data set. For example:</p>
<div class="sourceCode" id="cb4"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb4-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/filter_ab_class.html">filter_glycopeptides</a></span>(<span class="dt">result =</span> <span class="st">"R"</span>)</a>
<a class="sourceLine" id="cb4-2" title="2"><span class="co"># Filtering on glycopeptide antibacterials: any of `vanc` or `teic` is R</span></a>
<a class="sourceLine" id="cb4-3" title="3">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/filter_ab_class.html">filter_glycopeptides</a></span>(<span class="dt">result =</span> <span class="st">"R"</span>, <span class="dt">scope =</span> <span class="st">"all"</span>)</a>
<a class="sourceLine" id="cb4-4" title="4"><span class="co"># Filtering on glycopeptide antibacterials: all of `vanc` and `teic` is R</span></a></code></pre></div>
<div class="sourceCode" id="cb5"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb5-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/filter_ab_class.html">filter_glycopeptides</a></span>(<span class="dt">result =</span> <span class="st">"R"</span>)</a>
<a class="sourceLine" id="cb5-2" title="2"><span class="co"># Filtering on glycopeptide antibacterials: any of `vanc` or `teic` is R</span></a>
<a class="sourceLine" id="cb5-3" title="3">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/filter_ab_class.html">filter_glycopeptides</a></span>(<span class="dt">result =</span> <span class="st">"R"</span>, <span class="dt">scope =</span> <span class="st">"all"</span>)</a>
<a class="sourceLine" id="cb5-4" title="4"><span class="co"># Filtering on glycopeptide antibacterials: all of `vanc` and `teic` is R</span></a></code></pre></div>
</li>
<li>
<p>All <code>ab_*</code> functions are deprecated and replaced by <code>atc_*</code> functions:</p>
<div class="sourceCode" id="cb5"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb5-1" title="1">ab_property -&gt;<span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">atc_property</a></span>()</a>
<a class="sourceLine" id="cb5-2" title="2">ab_name -&gt;<span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">atc_name</a></span>()</a>
<a class="sourceLine" id="cb5-3" title="3">ab_official -&gt;<span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">atc_official</a></span>()</a>
<a class="sourceLine" id="cb5-4" title="4">ab_trivial_nl -&gt;<span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">atc_trivial_nl</a></span>()</a>
<a class="sourceLine" id="cb5-5" title="5">ab_certe -&gt;<span class="st"> </span><span class="kw">atc_certe</span>()</a>
<a class="sourceLine" id="cb5-6" title="6">ab_umcg -&gt;<span class="st"> </span><span class="kw">atc_umcg</span>()</a>
<a class="sourceLine" id="cb5-7" title="7">ab_tradenames -&gt;<span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">atc_tradenames</a></span>()</a></code></pre></div>
<div class="sourceCode" id="cb6"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb6-1" title="1">ab_property -&gt;<span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">atc_property</a></span>()</a>
<a class="sourceLine" id="cb6-2" title="2">ab_name -&gt;<span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">atc_name</a></span>()</a>
<a class="sourceLine" id="cb6-3" title="3">ab_official -&gt;<span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">atc_official</a></span>()</a>
<a class="sourceLine" id="cb6-4" title="4">ab_trivial_nl -&gt;<span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">atc_trivial_nl</a></span>()</a>
<a class="sourceLine" id="cb6-5" title="5">ab_certe -&gt;<span class="st"> </span><span class="kw">atc_certe</span>()</a>
<a class="sourceLine" id="cb6-6" title="6">ab_umcg -&gt;<span class="st"> </span><span class="kw">atc_umcg</span>()</a>
<a class="sourceLine" id="cb6-7" title="7">ab_tradenames -&gt;<span class="st"> </span><span class="kw"><a href="../reference/AMR-deprecated.html">atc_tradenames</a></span>()</a></code></pre></div>
These functions use <code><a href="../reference/as.atc.html">as.atc()</a></code> internally. The old <code>atc_property</code> has been renamed <code><a href="../reference/atc_online.html">atc_online_property()</a></code>. This is done for two reasons: firstly, not all ATC codes are of antibiotics (ab) but can also be of antivirals or antifungals. Secondly, the input must have class <code>atc</code> or must be coerable to this class. Properties of these classes should start with the same class name, analogous to <code><a href="../reference/as.mo.html">as.mo()</a></code> and e.g. <code>mo_genus</code>.</li>
<li>New functions <code><a href="../reference/mo_source.html">set_mo_source()</a></code> and <code><a href="../reference/mo_source.html">get_mo_source()</a></code> to use your own predefined MO codes as input for <code><a href="../reference/as.mo.html">as.mo()</a></code> and consequently all <code>mo_*</code> functions</li>
<li>Support for the upcoming <a href="https://dplyr.tidyverse.org"><code>dplyr</code></a> version 0.8.0</li>
@ -467,20 +480,20 @@ These functions use <code><a href="../reference/as.atc.html">as.atc()</a></code>
<li>New function <code><a href="../reference/age_groups.html">age_groups()</a></code> to split ages into custom or predefined groups (like children or elderly). This allows for easier demographic antimicrobial resistance analysis per age group.</li>
<li>
<p>New function <code><a href="../reference/resistance_predict.html">ggplot_rsi_predict()</a></code> as well as the base R <code><a href="https://www.rdocumentation.org/packages/graphics/topics/plot">plot()</a></code> function can now be used for resistance prediction calculated with <code><a href="../reference/resistance_predict.html">resistance_predict()</a></code>:</p>
<div class="sourceCode" id="cb6"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb6-1" title="1">x &lt;-<span class="st"> </span><span class="kw"><a href="../reference/resistance_predict.html">resistance_predict</a></span>(septic_patients, <span class="dt">col_ab =</span> <span class="st">"amox"</span>)</a>
<a class="sourceLine" id="cb6-2" title="2"><span class="kw"><a href="https://www.rdocumentation.org/packages/graphics/topics/plot">plot</a></span>(x)</a>
<a class="sourceLine" id="cb6-3" title="3"><span class="kw"><a href="../reference/resistance_predict.html">ggplot_rsi_predict</a></span>(x)</a></code></pre></div>
<div class="sourceCode" id="cb7"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb7-1" title="1">x &lt;-<span class="st"> </span><span class="kw"><a href="../reference/resistance_predict.html">resistance_predict</a></span>(septic_patients, <span class="dt">col_ab =</span> <span class="st">"amox"</span>)</a>
<a class="sourceLine" id="cb7-2" title="2"><span class="kw"><a href="https://www.rdocumentation.org/packages/graphics/topics/plot">plot</a></span>(x)</a>
<a class="sourceLine" id="cb7-3" title="3"><span class="kw"><a href="../reference/resistance_predict.html">ggplot_rsi_predict</a></span>(x)</a></code></pre></div>
</li>
<li>
<p>Functions <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code> and <code><a href="../reference/first_isolate.html">filter_first_weighted_isolate()</a></code> to shorten and fasten filtering on data sets with antimicrobial results, e.g.:</p>
<div class="sourceCode" id="cb7"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb7-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/first_isolate.html">filter_first_isolate</a></span>(...)</a>
<a class="sourceLine" id="cb7-2" title="2"><span class="co"># or</span></a>
<a class="sourceLine" id="cb7-3" title="3"><span class="kw"><a href="../reference/first_isolate.html">filter_first_isolate</a></span>(septic_patients, ...)</a></code></pre></div>
<div class="sourceCode" id="cb8"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb8-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/first_isolate.html">filter_first_isolate</a></span>(...)</a>
<a class="sourceLine" id="cb8-2" title="2"><span class="co"># or</span></a>
<a class="sourceLine" id="cb8-3" title="3"><span class="kw"><a href="../reference/first_isolate.html">filter_first_isolate</a></span>(septic_patients, ...)</a></code></pre></div>
<p>is equal to:</p>
<div class="sourceCode" id="cb8"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb8-1" title="1">septic_patients <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb8-2" title="2"><span class="st"> </span><span class="kw">mutate</span>(<span class="dt">only_firsts =</span> <span class="kw"><a href="../reference/first_isolate.html">first_isolate</a></span>(septic_patients, ...)) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb8-3" title="3"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/stats/topics/filter">filter</a></span>(only_firsts <span class="op">==</span><span class="st"> </span><span class="ot">TRUE</span>) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb8-4" title="4"><span class="st"> </span><span class="kw">select</span>(<span class="op">-</span>only_firsts)</a></code></pre></div>
<div class="sourceCode" id="cb9"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb9-1" title="1">septic_patients <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb9-2" title="2"><span class="st"> </span><span class="kw">mutate</span>(<span class="dt">only_firsts =</span> <span class="kw"><a href="../reference/first_isolate.html">first_isolate</a></span>(septic_patients, ...)) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb9-3" title="3"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/stats/topics/filter">filter</a></span>(only_firsts <span class="op">==</span><span class="st"> </span><span class="ot">TRUE</span>) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb9-4" title="4"><span class="st"> </span><span class="kw">select</span>(<span class="op">-</span>only_firsts)</a></code></pre></div>
</li>
<li>New function <code><a href="../reference/availability.html">availability()</a></code> to check the number of available (non-empty) results in a <code>data.frame</code>
</li>
@ -509,33 +522,33 @@ These functions use <code><a href="../reference/as.atc.html">as.atc()</a></code>
<ul>
<li>
<p>Now handles incorrect spelling, like <code>i</code> instead of <code>y</code> and <code>f</code> instead of <code>ph</code>:</p>
<div class="sourceCode" id="cb9"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb9-1" title="1"><span class="co"># mo_fullname() uses as.mo() internally</span></a>
<a class="sourceLine" id="cb9-2" title="2"></a>
<a class="sourceLine" id="cb9-3" title="3"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"Sthafilokockus aaureuz"</span>)</a>
<a class="sourceLine" id="cb9-4" title="4"><span class="co">#&gt; [1] "Staphylococcus aureus"</span></a>
<a class="sourceLine" id="cb9-5" title="5"></a>
<a class="sourceLine" id="cb9-6" title="6"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. klossi"</span>)</a>
<a class="sourceLine" id="cb9-7" title="7"><span class="co">#&gt; [1] "Staphylococcus kloosii"</span></a></code></pre></div>
<div class="sourceCode" id="cb10"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb10-1" title="1"><span class="co"># mo_fullname() uses as.mo() internally</span></a>
<a class="sourceLine" id="cb10-2" title="2"></a>
<a class="sourceLine" id="cb10-3" title="3"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"Sthafilokockus aaureuz"</span>)</a>
<a class="sourceLine" id="cb10-4" title="4"><span class="co">#&gt; [1] "Staphylococcus aureus"</span></a>
<a class="sourceLine" id="cb10-5" title="5"></a>
<a class="sourceLine" id="cb10-6" title="6"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. klossi"</span>)</a>
<a class="sourceLine" id="cb10-7" title="7"><span class="co">#&gt; [1] "Staphylococcus kloosii"</span></a></code></pre></div>
</li>
<li>
<p>Uncertainty of the algorithm is now divided into four levels, 0 to 3, where the default <code>allow_uncertain = TRUE</code> is equal to uncertainty level 2. Run <code><a href="../reference/as.mo.html">?as.mo</a></code> for more info about these levels.</p>
<div class="sourceCode" id="cb10"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb10-1" title="1"><span class="co"># equal:</span></a>
<a class="sourceLine" id="cb10-2" title="2"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="ot">TRUE</span>)</a>
<a class="sourceLine" id="cb10-3" title="3"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="dv">2</span>)</a>
<a class="sourceLine" id="cb10-4" title="4"></a>
<a class="sourceLine" id="cb10-5" title="5"><span class="co"># also equal:</span></a>
<a class="sourceLine" id="cb10-6" title="6"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="ot">FALSE</span>)</a>
<a class="sourceLine" id="cb10-7" title="7"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="dv">0</span>)</a></code></pre></div>
<div class="sourceCode" id="cb11"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb11-1" title="1"><span class="co"># equal:</span></a>
<a class="sourceLine" id="cb11-2" title="2"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="ot">TRUE</span>)</a>
<a class="sourceLine" id="cb11-3" title="3"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="dv">2</span>)</a>
<a class="sourceLine" id="cb11-4" title="4"></a>
<a class="sourceLine" id="cb11-5" title="5"><span class="co"># also equal:</span></a>
<a class="sourceLine" id="cb11-6" title="6"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="ot">FALSE</span>)</a>
<a class="sourceLine" id="cb11-7" title="7"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(..., <span class="dt">allow_uncertain =</span> <span class="dv">0</span>)</a></code></pre></div>
Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a></code> could lead to very unreliable results.</li>
<li>Implemented the latest publication of Becker <em>et al.</em> (2019), for categorising coagulase-negative <em>Staphylococci</em>
</li>
<li>All microbial IDs that found are now saved to a local file <code>~/.Rhistory_mo</code>. Use the new function <code>clean_mo_history()</code> to delete this file, which resets the algorithms.</li>
<li>
<p>Incoercible results will now be considered unknown, MO code <code>UNKNOWN</code>. On foreign systems, properties of these will be translated to all languages already previously supported: German, Dutch, French, Italian, Spanish and Portuguese:</p>
<div class="sourceCode" id="cb11"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb11-1" title="1"><span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(<span class="st">"qwerty"</span>, <span class="dt">language =</span> <span class="st">"es"</span>)</a>
<a class="sourceLine" id="cb11-2" title="2"><span class="co"># Warning: </span></a>
<a class="sourceLine" id="cb11-3" title="3"><span class="co"># one unique value (^= 100.0%) could not be coerced and is considered 'unknown': "qwerty". Use mo_failures() to review it.</span></a>
<a class="sourceLine" id="cb11-4" title="4"><span class="co">#&gt; [1] "(género desconocido)"</span></a></code></pre></div>
<div class="sourceCode" id="cb12"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb12-1" title="1"><span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(<span class="st">"qwerty"</span>, <span class="dt">language =</span> <span class="st">"es"</span>)</a>
<a class="sourceLine" id="cb12-2" title="2"><span class="co"># Warning: </span></a>
<a class="sourceLine" id="cb12-3" title="3"><span class="co"># one unique value (^= 100.0%) could not be coerced and is considered 'unknown': "qwerty". Use mo_failures() to review it.</span></a>
<a class="sourceLine" id="cb12-4" title="4"><span class="co">#&gt; [1] "(género desconocido)"</span></a></code></pre></div>
</li>
<li>Fix for vector containing only empty values</li>
<li>Finds better results when input is in other languages</li>
@ -581,19 +594,19 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<ul>
<li>
<p>Support for tidyverse quasiquotation! Now you can create frequency tables of function outcomes:</p>
<div class="sourceCode" id="cb12"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb12-1" title="1"><span class="co"># Determine genus of microorganisms (mo) in `septic_patients` data set:</span></a>
<a class="sourceLine" id="cb12-2" title="2"><span class="co"># OLD WAY</span></a>
<a class="sourceLine" id="cb12-3" title="3">septic_patients <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb12-4" title="4"><span class="st"> </span><span class="kw">mutate</span>(<span class="dt">genus =</span> <span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(mo)) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb12-5" title="5"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(genus)</a>
<a class="sourceLine" id="cb12-6" title="6"><span class="co"># NEW WAY</span></a>
<a class="sourceLine" id="cb12-7" title="7">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb12-8" title="8"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(<span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(mo))</a>
<a class="sourceLine" id="cb12-9" title="9"></a>
<a class="sourceLine" id="cb12-10" title="10"><span class="co"># Even supports grouping variables:</span></a>
<a class="sourceLine" id="cb12-11" title="11">septic_patients <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb12-12" title="12"><span class="st"> </span><span class="kw">group_by</span>(gender) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb12-13" title="13"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(<span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(mo))</a></code></pre></div>
<div class="sourceCode" id="cb13"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb13-1" title="1"><span class="co"># Determine genus of microorganisms (mo) in `septic_patients` data set:</span></a>
<a class="sourceLine" id="cb13-2" title="2"><span class="co"># OLD WAY</span></a>
<a class="sourceLine" id="cb13-3" title="3">septic_patients <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb13-4" title="4"><span class="st"> </span><span class="kw">mutate</span>(<span class="dt">genus =</span> <span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(mo)) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb13-5" title="5"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(genus)</a>
<a class="sourceLine" id="cb13-6" title="6"><span class="co"># NEW WAY</span></a>
<a class="sourceLine" id="cb13-7" title="7">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb13-8" title="8"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(<span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(mo))</a>
<a class="sourceLine" id="cb13-9" title="9"></a>
<a class="sourceLine" id="cb13-10" title="10"><span class="co"># Even supports grouping variables:</span></a>
<a class="sourceLine" id="cb13-11" title="11">septic_patients <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb13-12" title="12"><span class="st"> </span><span class="kw">group_by</span>(gender) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb13-13" title="13"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(<span class="kw"><a href="../reference/mo_property.html">mo_genus</a></span>(mo))</a></code></pre></div>
</li>
<li>Header info is now available as a list, with the <code>header</code> function</li>
<li>The parameter <code>header</code> is now set to <code>TRUE</code> at default, even for markdown</li>
@ -668,10 +681,10 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<li>Fewer than 3 characters as input for <code>as.mo</code> will return NA</li>
<li>
<p>Function <code>as.mo</code> (and all <code>mo_*</code> wrappers) now supports genus abbreviations with “species” attached</p>
<div class="sourceCode" id="cb13"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb13-1" title="1"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"E. species"</span>) <span class="co"># B_ESCHR</span></a>
<a class="sourceLine" id="cb13-2" title="2"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"E. spp."</span>) <span class="co"># "Escherichia species"</span></a>
<a class="sourceLine" id="cb13-3" title="3"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"S. spp"</span>) <span class="co"># B_STPHY</span></a>
<a class="sourceLine" id="cb13-4" title="4"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. species"</span>) <span class="co"># "Staphylococcus species"</span></a></code></pre></div>
<div class="sourceCode" id="cb14"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb14-1" title="1"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"E. species"</span>) <span class="co"># B_ESCHR</span></a>
<a class="sourceLine" id="cb14-2" title="2"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"E. spp."</span>) <span class="co"># "Escherichia species"</span></a>
<a class="sourceLine" id="cb14-3" title="3"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"S. spp"</span>) <span class="co"># B_STPHY</span></a>
<a class="sourceLine" id="cb14-4" title="4"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. species"</span>) <span class="co"># "Staphylococcus species"</span></a></code></pre></div>
</li>
<li>Added parameter <code>combine_IR</code> (TRUE/FALSE) to functions <code>portion_df</code> and <code>count_df</code>, to indicate that all values of I and R must be merged into one, so the output only consists of S vs. IR (susceptible vs. non-susceptible)</li>
<li>Fix for <code>portion_*(..., as_percent = TRUE)</code> when minimal number of isolates would not be met</li>
@ -684,15 +697,15 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<ul>
<li>
<p>Support for grouping variables, test with:</p>
<div class="sourceCode" id="cb14"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb14-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb14-2" title="2"><span class="st"> </span><span class="kw">group_by</span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb14-3" title="3"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(gender)</a></code></pre></div>
<div class="sourceCode" id="cb15"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb15-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb15-2" title="2"><span class="st"> </span><span class="kw">group_by</span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb15-3" title="3"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(gender)</a></code></pre></div>
</li>
<li>
<p>Support for (un)selecting columns:</p>
<div class="sourceCode" id="cb15"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb15-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb15-2" title="2"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb15-3" title="3"><span class="st"> </span><span class="kw">select</span>(<span class="op">-</span>count, <span class="op">-</span>cum_count) <span class="co"># only get item, percent, cum_percent</span></a></code></pre></div>
<div class="sourceCode" id="cb16"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb16-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb16-2" title="2"><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(hospital_id) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb16-3" title="3"><span class="st"> </span><span class="kw">select</span>(<span class="op">-</span>count, <span class="op">-</span>cum_count) <span class="co"># only get item, percent, cum_percent</span></a></code></pre></div>
</li>
<li>Check for <code><a href="https://www.rdocumentation.org/packages/hms/topics/hms">hms::is.hms</a></code>
</li>
@ -772,18 +785,18 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
</li>
</ul>
<p>They also come with support for German, Dutch, French, Italian, Spanish and Portuguese:</p>
<div class="sourceCode" id="cb16"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb16-1" title="1"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>)</a>
<a class="sourceLine" id="cb16-2" title="2"><span class="co"># [1] "Gram negative"</span></a>
<a class="sourceLine" id="cb16-3" title="3"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>, <span class="dt">language =</span> <span class="st">"de"</span>) <span class="co"># German</span></a>
<a class="sourceLine" id="cb16-4" title="4"><span class="co"># [1] "Gramnegativ"</span></a>
<a class="sourceLine" id="cb16-5" title="5"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>, <span class="dt">language =</span> <span class="st">"es"</span>) <span class="co"># Spanish</span></a>
<a class="sourceLine" id="cb16-6" title="6"><span class="co"># [1] "Gram negativo"</span></a>
<a class="sourceLine" id="cb16-7" title="7"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. group A"</span>, <span class="dt">language =</span> <span class="st">"pt"</span>) <span class="co"># Portuguese</span></a>
<a class="sourceLine" id="cb16-8" title="8"><span class="co"># [1] "Streptococcus grupo A"</span></a></code></pre></div>
<div class="sourceCode" id="cb17"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb17-1" title="1"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>)</a>
<a class="sourceLine" id="cb17-2" title="2"><span class="co"># [1] "Gram negative"</span></a>
<a class="sourceLine" id="cb17-3" title="3"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>, <span class="dt">language =</span> <span class="st">"de"</span>) <span class="co"># German</span></a>
<a class="sourceLine" id="cb17-4" title="4"><span class="co"># [1] "Gramnegativ"</span></a>
<a class="sourceLine" id="cb17-5" title="5"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"E. coli"</span>, <span class="dt">language =</span> <span class="st">"es"</span>) <span class="co"># Spanish</span></a>
<a class="sourceLine" id="cb17-6" title="6"><span class="co"># [1] "Gram negativo"</span></a>
<a class="sourceLine" id="cb17-7" title="7"><span class="kw"><a href="../reference/mo_property.html">mo_fullname</a></span>(<span class="st">"S. group A"</span>, <span class="dt">language =</span> <span class="st">"pt"</span>) <span class="co"># Portuguese</span></a>
<a class="sourceLine" id="cb17-8" title="8"><span class="co"># [1] "Streptococcus grupo A"</span></a></code></pre></div>
<p>Furthermore, former taxonomic names will give a note about the current taxonomic name:</p>
<div class="sourceCode" id="cb17"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb17-1" title="1"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"Esc blattae"</span>)</a>
<a class="sourceLine" id="cb17-2" title="2"><span class="co"># Note: 'Escherichia blattae' (Burgess et al., 1973) was renamed 'Shimwellia blattae' (Priest and Barker, 2010)</span></a>
<a class="sourceLine" id="cb17-3" title="3"><span class="co"># [1] "Gram negative"</span></a></code></pre></div>
<div class="sourceCode" id="cb18"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb18-1" title="1"><span class="kw"><a href="../reference/mo_property.html">mo_gramstain</a></span>(<span class="st">"Esc blattae"</span>)</a>
<a class="sourceLine" id="cb18-2" title="2"><span class="co"># Note: 'Escherichia blattae' (Burgess et al., 1973) was renamed 'Shimwellia blattae' (Priest and Barker, 2010)</span></a>
<a class="sourceLine" id="cb18-3" title="3"><span class="co"># [1] "Gram negative"</span></a></code></pre></div>
</li>
<li>Functions <code>count_R</code>, <code>count_IR</code>, <code>count_I</code>, <code>count_SI</code> and <code>count_S</code> to selectively count resistant or susceptible isolates
<ul>
@ -794,18 +807,18 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
</li>
<li>
<p>Functions <code>as.mo</code> and <code>is.mo</code> as replacements for <code>as.bactid</code> and <code>is.bactid</code> (since the <code>microoganisms</code> data set not only contains bacteria). These last two functions are deprecated and will be removed in a future release. The <code>as.mo</code> function determines microbial IDs using intelligent rules:</p>
<div class="sourceCode" id="cb18"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb18-1" title="1"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"E. coli"</span>)</a>
<a class="sourceLine" id="cb18-2" title="2"><span class="co"># [1] B_ESCHR_COL</span></a>
<a class="sourceLine" id="cb18-3" title="3"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"MRSA"</span>)</a>
<a class="sourceLine" id="cb18-4" title="4"><span class="co"># [1] B_STPHY_AUR</span></a>
<a class="sourceLine" id="cb18-5" title="5"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"S group A"</span>)</a>
<a class="sourceLine" id="cb18-6" title="6"><span class="co"># [1] B_STRPTC_GRA</span></a></code></pre></div>
<div class="sourceCode" id="cb19"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb19-1" title="1"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"E. coli"</span>)</a>
<a class="sourceLine" id="cb19-2" title="2"><span class="co"># [1] B_ESCHR_COL</span></a>
<a class="sourceLine" id="cb19-3" title="3"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"MRSA"</span>)</a>
<a class="sourceLine" id="cb19-4" title="4"><span class="co"># [1] B_STPHY_AUR</span></a>
<a class="sourceLine" id="cb19-5" title="5"><span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(<span class="st">"S group A"</span>)</a>
<a class="sourceLine" id="cb19-6" title="6"><span class="co"># [1] B_STRPTC_GRA</span></a></code></pre></div>
<p>And with great speed too - on a quite regular Linux server from 2007 it takes us less than 0.02 seconds to transform 25,000 items:</p>
<div class="sourceCode" id="cb19"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb19-1" title="1">thousands_of_E_colis &lt;-<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/rep">rep</a></span>(<span class="st">"E. coli"</span>, <span class="dv">25000</span>)</a>
<a class="sourceLine" id="cb19-2" title="2">microbenchmark<span class="op">::</span><span class="kw"><a href="https://www.rdocumentation.org/packages/microbenchmark/topics/microbenchmark">microbenchmark</a></span>(<span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(thousands_of_E_colis), <span class="dt">unit =</span> <span class="st">"s"</span>)</a>
<a class="sourceLine" id="cb19-3" title="3"><span class="co"># Unit: seconds</span></a>
<a class="sourceLine" id="cb19-4" title="4"><span class="co"># min median max neval</span></a>
<a class="sourceLine" id="cb19-5" title="5"><span class="co"># 0.01817717 0.01843957 0.03878077 100</span></a></code></pre></div>
<div class="sourceCode" id="cb20"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb20-1" title="1">thousands_of_E_colis &lt;-<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/rep">rep</a></span>(<span class="st">"E. coli"</span>, <span class="dv">25000</span>)</a>
<a class="sourceLine" id="cb20-2" title="2">microbenchmark<span class="op">::</span><span class="kw"><a href="https://www.rdocumentation.org/packages/microbenchmark/topics/microbenchmark">microbenchmark</a></span>(<span class="kw"><a href="../reference/as.mo.html">as.mo</a></span>(thousands_of_E_colis), <span class="dt">unit =</span> <span class="st">"s"</span>)</a>
<a class="sourceLine" id="cb20-3" title="3"><span class="co"># Unit: seconds</span></a>
<a class="sourceLine" id="cb20-4" title="4"><span class="co"># min median max neval</span></a>
<a class="sourceLine" id="cb20-5" title="5"><span class="co"># 0.01817717 0.01843957 0.03878077 100</span></a></code></pre></div>
</li>
<li>Added parameter <code>reference_df</code> for <code>as.mo</code>, so users can supply their own microbial IDs, name or codes as a reference table</li>
<li>Renamed all previous references to <code>bactid</code> to <code>mo</code>, like:
@ -833,12 +846,12 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<li>Added three antimicrobial agents to the <code>antibiotics</code> data set: Terbinafine (D01BA02), Rifaximin (A07AA11) and Isoconazole (D01AC05)</li>
<li>
<p>Added 163 trade names to the <code>antibiotics</code> data set, it now contains 298 different trade names in total, e.g.:</p>
<div class="sourceCode" id="cb20"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb20-1" title="1"><span class="kw"><a href="../reference/AMR-deprecated.html">ab_official</a></span>(<span class="st">"Bactroban"</span>)</a>
<a class="sourceLine" id="cb20-2" title="2"><span class="co"># [1] "Mupirocin"</span></a>
<a class="sourceLine" id="cb20-3" title="3"><span class="kw"><a href="../reference/ab_property.html">ab_name</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="st">"Bactroban"</span>, <span class="st">"Amoxil"</span>, <span class="st">"Zithromax"</span>, <span class="st">"Floxapen"</span>))</a>
<a class="sourceLine" id="cb20-4" title="4"><span class="co"># [1] "Mupirocin" "Amoxicillin" "Azithromycin" "Flucloxacillin"</span></a>
<a class="sourceLine" id="cb20-5" title="5"><span class="kw"><a href="../reference/ab_property.html">ab_atc</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="st">"Bactroban"</span>, <span class="st">"Amoxil"</span>, <span class="st">"Zithromax"</span>, <span class="st">"Floxapen"</span>))</a>
<a class="sourceLine" id="cb20-6" title="6"><span class="co"># [1] "R01AX06" "J01CA04" "J01FA10" "J01CF05"</span></a></code></pre></div>
<div class="sourceCode" id="cb21"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb21-1" title="1"><span class="kw"><a href="../reference/AMR-deprecated.html">ab_official</a></span>(<span class="st">"Bactroban"</span>)</a>
<a class="sourceLine" id="cb21-2" title="2"><span class="co"># [1] "Mupirocin"</span></a>
<a class="sourceLine" id="cb21-3" title="3"><span class="kw"><a href="../reference/ab_property.html">ab_name</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="st">"Bactroban"</span>, <span class="st">"Amoxil"</span>, <span class="st">"Zithromax"</span>, <span class="st">"Floxapen"</span>))</a>
<a class="sourceLine" id="cb21-4" title="4"><span class="co"># [1] "Mupirocin" "Amoxicillin" "Azithromycin" "Flucloxacillin"</span></a>
<a class="sourceLine" id="cb21-5" title="5"><span class="kw"><a href="../reference/ab_property.html">ab_atc</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(<span class="st">"Bactroban"</span>, <span class="st">"Amoxil"</span>, <span class="st">"Zithromax"</span>, <span class="st">"Floxapen"</span>))</a>
<a class="sourceLine" id="cb21-6" title="6"><span class="co"># [1] "R01AX06" "J01CA04" "J01FA10" "J01CF05"</span></a></code></pre></div>
</li>
<li>For <code>first_isolate</code>, rows will be ignored when theres no species available</li>
<li>Function <code>ratio</code> is now deprecated and will be removed in a future release, as it is not really the scope of this package</li>
@ -849,13 +862,13 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
</li>
<li>
<p>Support for quasiquotation in the functions series <code>count_*</code> and <code>portions_*</code>, and <code>n_rsi</code>. This allows to check for more than 2 vectors or columns.</p>
<div class="sourceCode" id="cb21"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb21-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw">select</span>(amox, cipr) <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/count.html">count_IR</a></span>()</a>
<a class="sourceLine" id="cb21-2" title="2"><span class="co"># which is the same as:</span></a>
<a class="sourceLine" id="cb21-3" title="3">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/count.html">count_IR</a></span>(amox, cipr)</a>
<a class="sourceLine" id="cb21-4" title="4"></a>
<a class="sourceLine" id="cb21-5" title="5">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl)</a>
<a class="sourceLine" id="cb21-6" title="6">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl, gent)</a>
<a class="sourceLine" id="cb21-7" title="7">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl, gent, pita)</a></code></pre></div>
<div class="sourceCode" id="cb22"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb22-1" title="1">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw">select</span>(amox, cipr) <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/count.html">count_IR</a></span>()</a>
<a class="sourceLine" id="cb22-2" title="2"><span class="co"># which is the same as:</span></a>
<a class="sourceLine" id="cb22-3" title="3">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/count.html">count_IR</a></span>(amox, cipr)</a>
<a class="sourceLine" id="cb22-4" title="4"></a>
<a class="sourceLine" id="cb22-5" title="5">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl)</a>
<a class="sourceLine" id="cb22-6" title="6">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl, gent)</a>
<a class="sourceLine" id="cb22-7" title="7">septic_patients <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl, gent, pita)</a></code></pre></div>
</li>
<li>Edited <code>ggplot_rsi</code> and <code>geom_rsi</code> so they can cope with <code>count_df</code>. The new <code>fun</code> parameter has value <code>portion_df</code> at default, but can be set to <code>count_df</code>.</li>
<li>Fix for <code>ggplot_rsi</code> when the <code>ggplot2</code> package was not loaded</li>
@ -869,12 +882,12 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
</li>
<li>
<p>Support for types (classes) list and matrix for <code>freq</code></p>
<div class="sourceCode" id="cb22"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb22-1" title="1">my_matrix =<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/with">with</a></span>(septic_patients, <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/matrix">matrix</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(age, gender), <span class="dt">ncol =</span> <span class="dv">2</span>))</a>
<a class="sourceLine" id="cb22-2" title="2"><span class="kw"><a href="../reference/freq.html">freq</a></span>(my_matrix)</a></code></pre></div>
<div class="sourceCode" id="cb23"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb23-1" title="1">my_matrix =<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/with">with</a></span>(septic_patients, <span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/matrix">matrix</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(age, gender), <span class="dt">ncol =</span> <span class="dv">2</span>))</a>
<a class="sourceLine" id="cb23-2" title="2"><span class="kw"><a href="../reference/freq.html">freq</a></span>(my_matrix)</a></code></pre></div>
<p>For lists, subsetting is possible:</p>
<div class="sourceCode" id="cb23"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb23-1" title="1">my_list =<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/list">list</a></span>(<span class="dt">age =</span> septic_patients<span class="op">$</span>age, <span class="dt">gender =</span> septic_patients<span class="op">$</span>gender)</a>
<a class="sourceLine" id="cb23-2" title="2">my_list <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(age)</a>
<a class="sourceLine" id="cb23-3" title="3">my_list <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(gender)</a></code></pre></div>
<div class="sourceCode" id="cb24"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb24-1" title="1">my_list =<span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/list">list</a></span>(<span class="dt">age =</span> septic_patients<span class="op">$</span>age, <span class="dt">gender =</span> septic_patients<span class="op">$</span>gender)</a>
<a class="sourceLine" id="cb24-2" title="2">my_list <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(age)</a>
<a class="sourceLine" id="cb24-3" title="3">my_list <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(gender)</a></code></pre></div>
</li>
</ul>
</div>
@ -1108,7 +1121,7 @@ Using <code><a href="../reference/as.mo.html">as.mo(..., allow_uncertain = 3)</a
<div id="tocnav">
<h2>Contents</h2>
<ul class="nav nav-pills nav-stacked">
<li><a href="#amr-0709007">0.7.0.9007</a></li>
<li><a href="#amr-0709008">0.7.0.9008</a></li>
<li><a href="#amr-070">0.7.0</a></li>
<li><a href="#amr-061">0.6.1</a></li>
<li><a href="#amr-060">0.6.0</a></li>

View File

@ -81,7 +81,7 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.7.0.9000</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.0.9008</span>
</span>
</div>
@ -166,13 +166,6 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
Create frequency tables
</a>
</li>
<li>
<a href="../reference/g.test.html">
<span class="fa fa-clipboard-check"></span>
Use the G-test
</a>
</li>
<li>
<a href="../articles/benchmarks.html">
<span class="fa fa-shipping-fast"></span>
@ -311,8 +304,9 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
<h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2>
<p>These functions are meant to count isolates. Use the <code><a href='portion.html'>portion</a>_*</code> functions to calculate microbial resistance.</p>
<p><code>n_rsi</code> is an alias of <code>count_all</code>. They can be used to count all available isolates, i.e. where all input antibiotics have an available result (S, I or R). Their use is equal to <code><a href='https://dplyr.tidyverse.org/reference/n_distinct.html'>n_distinct</a></code>. Their function is equal to <code>count_S(...) + count_IR(...)</code>.</p>
<p><code>count_df</code> takes any variable from <code>data</code> that has an <code>"rsi"</code> class (created with <code><a href='as.rsi.html'>as.rsi</a></code>) and counts the amounts of R, I and S. The resulting <em>tidy data</em> (see Source) <code>data.frame</code> will have three rows (S/I/R) and a column for each variable with class <code>"rsi"</code>.</p>
<p>The function <code>n_rsi</code> is an alias of <code>count_all</code>. They can be used to count all available isolates, i.e. where all input antibiotics have an available result (S, I or R). Their use is equal to <code><a href='https://dplyr.tidyverse.org/reference/n_distinct.html'>n_distinct</a></code>. Their function is equal to <code>count_S(...) + count_IR(...)</code>.</p>
<p>The function <code>count_df</code> takes any variable from <code>data</code> that has an <code>"rsi"</code> class (created with <code><a href='as.rsi.html'>as.rsi</a></code>) and counts the amounts of S, I and R. The resulting <em>tidy data</em> (see Source) <code>data.frame</code> will have three rows (S/I/R) and a column for each variable with class <code>"rsi"</code>.</p>
<p>The function <code>rsi_df</code> works exactly like <code>count_df</code>, but add the percentage of S, I and R.</p>
<h2 class="hasAnchor" id="interpretation-of-s-i-and-r"><a class="anchor" href="#interpretation-of-s-i-and-r"></a>Interpretation of S, I and R</h2>

View File

@ -80,7 +80,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.7.0.9000</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.0.9008</span>
</span>
</div>
@ -165,13 +165,6 @@
Create frequency tables
</a>
</li>
<li>
<a href="../reference/g.test.html">
<span class="fa fa-clipboard-check"></span>
Use the G-test
</a>
</li>
<li>
<a href="../articles/benchmarks.html">
<span class="fa fa-shipping-fast"></span>
@ -248,8 +241,8 @@
</div>
<pre class="usage"><span class='fu'>ggplot_rsi</span>(<span class='no'>data</span>, <span class='kw'>position</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>x</span> <span class='kw'>=</span> <span class='st'>"Antibiotic"</span>,
<span class='kw'>fill</span> <span class='kw'>=</span> <span class='st'>"Interpretation"</span>, <span class='kw'>facet</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>breaks</span> <span class='kw'>=</span> <span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/seq'>seq</a></span>(<span class='fl'>0</span>, <span class='fl'>1</span>, <span class='fl'>0.1</span>),
<pre class="usage"><span class='fu'>ggplot_rsi</span>(<span class='no'>data</span>, <span class='kw'>position</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>x</span> <span class='kw'>=</span> <span class='st'>"antibiotic"</span>,
<span class='kw'>fill</span> <span class='kw'>=</span> <span class='st'>"interpretation"</span>, <span class='kw'>facet</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>breaks</span> <span class='kw'>=</span> <span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/seq'>seq</a></span>(<span class='fl'>0</span>, <span class='fl'>1</span>, <span class='fl'>0.1</span>),
<span class='kw'>limits</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>translate_ab</span> <span class='kw'>=</span> <span class='st'>"name"</span>, <span class='kw'>combine_SI</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>,
<span class='kw'>combine_IR</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(), <span class='kw'>fun</span> <span class='kw'>=</span> <span class='no'>count_df</span>,
<span class='kw'>nrow</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>colours</span> <span class='kw'>=</span> <span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/c'>c</a></span>(<span class='kw'>S</span> <span class='kw'>=</span> <span class='st'>"#61a8ff"</span>, <span class='kw'>SI</span> <span class='kw'>=</span> <span class='st'>"#61a8ff"</span>, <span class='kw'>I</span> <span class='kw'>=</span>
@ -258,12 +251,12 @@
<span class='kw'>subtitle</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>caption</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>x.title</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>y.title</span> <span class='kw'>=</span> <span class='kw'>NULL</span>,
<span class='no'>...</span>)
<span class='fu'>geom_rsi</span>(<span class='kw'>position</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>x</span> <span class='kw'>=</span> <span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/c'>c</a></span>(<span class='st'>"Antibiotic"</span>, <span class='st'>"Interpretation"</span>),
<span class='kw'>fill</span> <span class='kw'>=</span> <span class='st'>"Interpretation"</span>, <span class='kw'>translate_ab</span> <span class='kw'>=</span> <span class='st'>"name"</span>,
<span class='fu'>geom_rsi</span>(<span class='kw'>position</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>x</span> <span class='kw'>=</span> <span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/c'>c</a></span>(<span class='st'>"antibiotic"</span>, <span class='st'>"interpretation"</span>),
<span class='kw'>fill</span> <span class='kw'>=</span> <span class='st'>"interpretation"</span>, <span class='kw'>translate_ab</span> <span class='kw'>=</span> <span class='st'>"name"</span>,
<span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(), <span class='kw'>combine_SI</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>, <span class='kw'>combine_IR</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>,
<span class='kw'>fun</span> <span class='kw'>=</span> <span class='no'>count_df</span>, <span class='no'>...</span>)
<span class='fu'>facet_rsi</span>(<span class='kw'>facet</span> <span class='kw'>=</span> <span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/c'>c</a></span>(<span class='st'>"Interpretation"</span>, <span class='st'>"Antibiotic"</span>), <span class='kw'>nrow</span> <span class='kw'>=</span> <span class='kw'>NULL</span>)
<span class='fu'>facet_rsi</span>(<span class='kw'>facet</span> <span class='kw'>=</span> <span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/c'>c</a></span>(<span class='st'>"interpretation"</span>, <span class='st'>"antibiotic"</span>), <span class='kw'>nrow</span> <span class='kw'>=</span> <span class='kw'>NULL</span>)
<span class='fu'>scale_y_percent</span>(<span class='kw'>breaks</span> <span class='kw'>=</span> <span class='fu'><a href='https://www.rdocumentation.org/packages/base/topics/seq'>seq</a></span>(<span class='fl'>0</span>, <span class='fl'>1</span>, <span class='fl'>0.1</span>), <span class='kw'>limits</span> <span class='kw'>=</span> <span class='kw'>NULL</span>)
@ -272,7 +265,7 @@
<span class='fu'>theme_rsi</span>()
<span class='fu'>labels_rsi_count</span>(<span class='kw'>position</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>x</span> <span class='kw'>=</span> <span class='st'>"Antibiotic"</span>,
<span class='fu'>labels_rsi_count</span>(<span class='kw'>position</span> <span class='kw'>=</span> <span class='kw'>NULL</span>, <span class='kw'>x</span> <span class='kw'>=</span> <span class='st'>"antibiotic"</span>,
<span class='kw'>translate_ab</span> <span class='kw'>=</span> <span class='st'>"name"</span>, <span class='kw'>combine_SI</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>, <span class='kw'>combine_IR</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>,
<span class='kw'>datalabels.size</span> <span class='kw'>=</span> <span class='fl'>3</span>, <span class='kw'>datalabels.colour</span> <span class='kw'>=</span> <span class='st'>"gray15"</span>)</pre>
@ -289,15 +282,15 @@
</tr>
<tr>
<th>x</th>
<td><p>variable to show on x axis, either <code>"Antibiotic"</code> (default) or <code>"Interpretation"</code> or a grouping variable</p></td>
<td><p>variable to show on x axis, either <code>"antibiotic"</code> (default) or <code>"interpretation"</code> or a grouping variable</p></td>
</tr>
<tr>
<th>fill</th>
<td><p>variable to categorise using the plots legend, either <code>"Antibiotic"</code> (default) or <code>"Interpretation"</code> or a grouping variable</p></td>
<td><p>variable to categorise using the plots legend, either <code>"antibiotic"</code> (default) or <code>"interpretation"</code> or a grouping variable</p></td>
</tr>
<tr>
<th>facet</th>
<td><p>variable to split plots by, either <code>"Interpretation"</code> (default) or <code>"Antibiotic"</code> or a grouping variable</p></td>
<td><p>variable to split plots by, either <code>"interpretation"</code> (default) or <code>"antibiotic"</code> or a grouping variable</p></td>
</tr>
<tr>
<th>breaks</th>
@ -458,7 +451,7 @@
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/select.html'>select</a></span>(<span class='no'>hospital_id</span>, <span class='no'>AMX</span>, <span class='no'>NIT</span>, <span class='no'>FOS</span>, <span class='no'>TMP</span>, <span class='no'>CIP</span>) <span class='kw'>%&gt;%</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/group_by.html'>group_by</a></span>(<span class='no'>hospital_id</span>) <span class='kw'>%&gt;%</span>
<span class='fu'>ggplot_rsi</span>(<span class='kw'>x</span> <span class='kw'>=</span> <span class='st'>"hospital_id"</span>,
<span class='kw'>facet</span> <span class='kw'>=</span> <span class='st'>"Antibiotic"</span>,
<span class='kw'>facet</span> <span class='kw'>=</span> <span class='st'>"antibiotic"</span>,
<span class='kw'>nrow</span> <span class='kw'>=</span> <span class='fl'>1</span>,
<span class='kw'>title</span> <span class='kw'>=</span> <span class='st'>"AMR of Anti-UTI Drugs Per Hospital"</span>,
<span class='kw'>x.title</span> <span class='kw'>=</span> <span class='st'>"Hospital"</span>,
@ -479,7 +472,7 @@
<span class='co'># group by MO</span>
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/group_by.html'>group_by</a></span>(<span class='no'>bug</span>) <span class='kw'>%&gt;%</span>
<span class='co'># plot the thing, putting MOs on the facet</span>
<span class='fu'>ggplot_rsi</span>(<span class='kw'>x</span> <span class='kw'>=</span> <span class='st'>"Antibiotic"</span>,
<span class='fu'>ggplot_rsi</span>(<span class='kw'>x</span> <span class='kw'>=</span> <span class='st'>"antibiotic"</span>,
<span class='kw'>facet</span> <span class='kw'>=</span> <span class='st'>"bug"</span>,
<span class='kw'>translate_ab</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>,
<span class='kw'>nrow</span> <span class='kw'>=</span> <span class='fl'>1</span>,

View File

@ -78,7 +78,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">0.7.0.9007</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.0.9008</span>
</span>
</div>
@ -435,7 +435,7 @@
</tr><tr>
<td>
<p><code><a href="portion.html">portion_R()</a></code> <code><a href="portion.html">portion_IR()</a></code> <code><a href="portion.html">portion_I()</a></code> <code><a href="portion.html">portion_SI()</a></code> <code><a href="portion.html">portion_S()</a></code> <code><a href="portion.html">portion_df()</a></code> </p>
<p><code><a href="portion.html">portion_R()</a></code> <code><a href="portion.html">portion_IR()</a></code> <code><a href="portion.html">portion_I()</a></code> <code><a href="portion.html">portion_SI()</a></code> <code><a href="portion.html">portion_S()</a></code> <code><a href="portion.html">portion_df()</a></code> <code><a href="portion.html">rsi_df()</a></code> </p>
</td>
<td><p>Calculate resistance of isolates</p></td>
</tr><tr>

View File

@ -80,7 +80,7 @@
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.7.0.9000</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.0.9008</span>
</span>
</div>
@ -165,13 +165,6 @@
Create frequency tables
</a>
</li>
<li>
<a href="../reference/g.test.html">
<span class="fa fa-clipboard-check"></span>
Use the G-test
</a>
</li>
<li>
<a href="../articles/benchmarks.html">
<span class="fa fa-shipping-fast"></span>
@ -252,7 +245,7 @@
<h2 class="hasAnchor" id="format"><a class="anchor" href="#format"></a>Format</h2>
<p>A <code><a href='https://www.rdocumentation.org/packages/base/topics/data.frame'>data.frame</a></code> with 67,903 observations and 16 variables:</p><dl class='dl-horizontal'>
<p>A <code><a href='https://www.rdocumentation.org/packages/base/topics/data.frame'>data.frame</a></code> with 67,906 observations and 16 variables:</p><dl class='dl-horizontal'>
<dt><code>mo</code></dt><dd><p>ID of microorganism as used by this package</p></dd>
<dt><code>col_id</code></dt><dd><p>Catalogue of Life ID</p></dd>
<dt><code>fullname</code></dt><dd><p>Full name, like <code>"Escherichia coli"</code></p></dd>
@ -272,9 +265,10 @@
<h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2>
<p>Manually added were:</p><ul>
<li><p>9 species of <em>Streptococcus</em> (beta haemolytic groups A, B, C, D, F, G, H, K and unspecified)</p></li>
<li><p>2 species of <em>Staphylococcus</em> (coagulase-negative [CoNS] and coagulase-positive [CoPS])</p></li>
<li><p>3 other undefined (unknown, unknown Gram negatives and unknown Gram positives)</p></li>
<li><p>9 entries of <em>Streptococcus</em> (beta haemolytic groups A, B, C, D, F, G, H, K and unspecified)</p></li>
<li><p>2 entries of <em>Staphylococcus</em> (coagulase-negative [CoNS] and coagulase-positive [CoPS])</p></li>
<li><p>3 entries of Trichomonas (Trichomonas vaginalis, and its family and genus)</p></li>
<li><p>3 other 'undefined' entries (unknown, unknown Gram negatives and unknown Gram positives)</p></li>
<li><p>8,830 species from the DSMZ (Deutsche Sammlung von Mikroorganismen und Zellkulturen) that are not in the Catalogue of Life</p></li>
</ul>

View File

@ -81,7 +81,7 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
</button>
<span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.7.0.9000</span>
<span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Latest development version">0.7.0.9008</span>
</span>
</div>
@ -166,13 +166,6 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
Create frequency tables
</a>
</li>
<li>
<a href="../reference/g.test.html">
<span class="fa fa-clipboard-check"></span>
Use the G-test
</a>
</li>
<li>
<a href="../articles/benchmarks.html">
<span class="fa fa-shipping-fast"></span>
@ -266,6 +259,10 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
<span class='kw'>also_single_tested</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='fu'>portion_df</span>(<span class='no'>data</span>, <span class='kw'>translate_ab</span> <span class='kw'>=</span> <span class='st'>"name"</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(),
<span class='kw'>minimum</span> <span class='kw'>=</span> <span class='fl'>30</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>, <span class='kw'>combine_SI</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>,
<span class='kw'>combine_IR</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)
<span class='fu'>rsi_df</span>(<span class='no'>data</span>, <span class='kw'>translate_ab</span> <span class='kw'>=</span> <span class='st'>"name"</span>, <span class='kw'>language</span> <span class='kw'>=</span> <span class='fu'><a href='translate.html'>get_locale</a></span>(),
<span class='kw'>minimum</span> <span class='kw'>=</span> <span class='fl'>30</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>, <span class='kw'>combine_SI</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>,
<span class='kw'>combine_IR</span> <span class='kw'>=</span> <span class='fl'>FALSE</span>)</pre>
@ -323,7 +320,8 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
<p><strong>Remember that you should filter your table to let it contain only first isolates!</strong> Use <code><a href='first_isolate.html'>first_isolate</a></code> to determine them in your data set.</p>
<p>These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the <code><a href='count.html'>count</a></code> functions to count isolates. <em>Low counts can infuence the outcome - these <code>portion</code> functions may camouflage this, since they only return the portion albeit being dependent on the <code>minimum</code> parameter.</em></p>
<p><code>portion_df</code> takes any variable from <code>data</code> that has an <code>"rsi"</code> class (created with <code><a href='as.rsi.html'>as.rsi</a></code>) and calculates the portions R, I and S. The resulting <em>tidy data</em> (see Source) <code>data.frame</code> will have three rows (S/I/R) and a column for each variable with class <code>"rsi"</code>.
<p>The function <code>portion_df</code> takes any variable from <code>data</code> that has an <code>"rsi"</code> class (created with <code><a href='as.rsi.html'>as.rsi</a></code>) and calculates the portions R, I and S. The resulting <em>tidy data</em> (see Source) <code>data.frame</code> will have three rows (S/I/R) and a column for each group and each variable with class <code>"rsi"</code>.</p>
<p>The function <code>rsi_df</code> works exactly like <code>portion_df</code>, but add the number of isolates.
<br /><br />
To calculate the probability (<em>p</em>) of susceptibility of one antibiotic, we use this formula:
<div style="text-align: center;"><img src='figures/combi_therapy_2.png' alt='' /></div>

View File

@ -58,9 +58,11 @@ These functions can be used to count resistant/susceptible microbial isolates. A
\details{
These functions are meant to count isolates. Use the \code{\link{portion}_*} functions to calculate microbial resistance.
\code{n_rsi} is an alias of \code{count_all}. They can be used to count all available isolates, i.e. where all input antibiotics have an available result (S, I or R). Their use is equal to \code{\link{n_distinct}}. Their function is equal to \code{count_S(...) + count_IR(...)}.
The function \code{n_rsi} is an alias of \code{count_all}. They can be used to count all available isolates, i.e. where all input antibiotics have an available result (S, I or R). Their use is equal to \code{\link{n_distinct}}. Their function is equal to \code{count_S(...) + count_IR(...)}.
\code{count_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and counts the amounts of R, I and S. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each variable with class \code{"rsi"}.
The function \code{count_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and counts the amounts of S, I and R. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each variable with class \code{"rsi"}.
The function \code{rsi_df} works exactly like \code{count_df}, but add the percentage of S, I and R.
}
\section{Interpretation of S, I and R}{

View File

@ -10,8 +10,8 @@
\alias{labels_rsi_count}
\title{AMR plots with \code{ggplot2}}
\usage{
ggplot_rsi(data, position = NULL, x = "Antibiotic",
fill = "Interpretation", facet = NULL, breaks = seq(0, 1, 0.1),
ggplot_rsi(data, position = NULL, x = "antibiotic",
fill = "interpretation", facet = NULL, breaks = seq(0, 1, 0.1),
limits = NULL, translate_ab = "name", combine_SI = TRUE,
combine_IR = FALSE, language = get_locale(), fun = count_df,
nrow = NULL, colours = c(S = "#61a8ff", SI = "#61a8ff", I =
@ -20,12 +20,12 @@ ggplot_rsi(data, position = NULL, x = "Antibiotic",
subtitle = NULL, caption = NULL, x.title = NULL, y.title = NULL,
...)
geom_rsi(position = NULL, x = c("Antibiotic", "Interpretation"),
fill = "Interpretation", translate_ab = "name",
geom_rsi(position = NULL, x = c("antibiotic", "interpretation"),
fill = "interpretation", translate_ab = "name",
language = get_locale(), combine_SI = TRUE, combine_IR = FALSE,
fun = count_df, ...)
facet_rsi(facet = c("Interpretation", "Antibiotic"), nrow = NULL)
facet_rsi(facet = c("interpretation", "antibiotic"), nrow = NULL)
scale_y_percent(breaks = seq(0, 1, 0.1), limits = NULL)
@ -34,7 +34,7 @@ scale_rsi_colours(colours = c(S = "#61a8ff", SI = "#61a8ff", I =
theme_rsi()
labels_rsi_count(position = NULL, x = "Antibiotic",
labels_rsi_count(position = NULL, x = "antibiotic",
translate_ab = "name", combine_SI = TRUE, combine_IR = FALSE,
datalabels.size = 3, datalabels.colour = "gray15")
}
@ -43,11 +43,11 @@ labels_rsi_count(position = NULL, x = "Antibiotic",
\item{position}{position adjustment of bars, either \code{"fill"} (default when \code{fun} is \code{\link{count_df}}), \code{"stack"} (default when \code{fun} is \code{\link{portion_df}}) or \code{"dodge"}}
\item{x}{variable to show on x axis, either \code{"Antibiotic"} (default) or \code{"Interpretation"} or a grouping variable}
\item{x}{variable to show on x axis, either \code{"antibiotic"} (default) or \code{"interpretation"} or a grouping variable}
\item{fill}{variable to categorise using the plots legend, either \code{"Antibiotic"} (default) or \code{"Interpretation"} or a grouping variable}
\item{fill}{variable to categorise using the plots legend, either \code{"antibiotic"} (default) or \code{"interpretation"} or a grouping variable}
\item{facet}{variable to split plots by, either \code{"Interpretation"} (default) or \code{"Antibiotic"} or a grouping variable}
\item{facet}{variable to split plots by, either \code{"interpretation"} (default) or \code{"antibiotic"} or a grouping variable}
\item{breaks}{numeric vector of positions}
@ -178,7 +178,7 @@ septic_patients \%>\%
select(hospital_id, AMX, NIT, FOS, TMP, CIP) \%>\%
group_by(hospital_id) \%>\%
ggplot_rsi(x = "hospital_id",
facet = "Antibiotic",
facet = "antibiotic",
nrow = 1,
title = "AMR of Anti-UTI Drugs Per Hospital",
x.title = "Hospital",
@ -199,7 +199,7 @@ septic_patients \%>\%
# group by MO
group_by(bug) \%>\%
# plot the thing, putting MOs on the facet
ggplot_rsi(x = "Antibiotic",
ggplot_rsi(x = "antibiotic",
facet = "bug",
translate_ab = FALSE,
nrow = 1,

View File

@ -4,7 +4,7 @@
\name{microorganisms}
\alias{microorganisms}
\title{Data set with ~65,000 microorganisms}
\format{A \code{\link{data.frame}} with 67,903 observations and 16 variables:
\format{A \code{\link{data.frame}} with 67,906 observations and 16 variables:
\describe{
\item{\code{mo}}{ID of microorganism as used by this package}
\item{\code{col_id}}{Catalogue of Life ID}
@ -30,9 +30,10 @@ A data set containing the microbial taxonomy of six kingdoms from the Catalogue
\details{
Manually added were:
\itemize{
\item{9 species of \emph{Streptococcus} (beta haemolytic groups A, B, C, D, F, G, H, K and unspecified)}
\item{2 species of \emph{Staphylococcus} (coagulase-negative [CoNS] and coagulase-positive [CoPS])}
\item{3 other undefined (unknown, unknown Gram negatives and unknown Gram positives)}
\item{9 entries of \emph{Streptococcus} (beta haemolytic groups A, B, C, D, F, G, H, K and unspecified)}
\item{2 entries of \emph{Staphylococcus} (coagulase-negative [CoNS] and coagulase-positive [CoPS])}
\item{3 entries of Trichomonas (Trichomonas vaginalis, and its family and genus)}
\item{3 other 'undefined' entries (unknown, unknown Gram negatives and unknown Gram positives)}
\item{8,830 species from the DSMZ (Deutsche Sammlung von Mikroorganismen und Zellkulturen) that are not in the Catalogue of Life}
}
}

View File

@ -1,5 +1,5 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/portion.R
% Please edit documentation in R/portion.R, R/rsi_df.R
\name{portion}
\alias{portion}
\alias{portion_R}
@ -8,6 +8,7 @@
\alias{portion_SI}
\alias{portion_S}
\alias{portion_df}
\alias{rsi_df}
\title{Calculate resistance of isolates}
\source{
\strong{M39 Analysis and Presentation of Cumulative Antimicrobial Susceptibility Test Data, 4th Edition}, 2014, \emph{Clinical and Laboratory Standards Institute (CLSI)}. \url{https://clsi.org/standards/products/microbiology/documents/m39/}.
@ -33,6 +34,10 @@ portion_S(..., minimum = 30, as_percent = FALSE,
portion_df(data, translate_ab = "name", language = get_locale(),
minimum = 30, as_percent = FALSE, combine_SI = TRUE,
combine_IR = FALSE)
rsi_df(data, translate_ab = "name", language = get_locale(),
minimum = 30, as_percent = FALSE, combine_SI = TRUE,
combine_IR = FALSE)
}
\arguments{
\item{...}{one or more vectors (or columns) with antibiotic interpretations. They will be transformed internally with \code{\link{as.rsi}} if needed. Use multiple columns to calculate (the lack of) co-resistance: the probability where one of two drugs have a resistant or susceptible result. See Examples.}
@ -66,7 +71,9 @@ These functions can be used to calculate the (co-)resistance of microbial isolat
These functions are not meant to count isolates, but to calculate the portion of resistance/susceptibility. Use the \code{\link[AMR]{count}} functions to count isolates. \emph{Low counts can infuence the outcome - these \code{portion} functions may camouflage this, since they only return the portion albeit being dependent on the \code{minimum} parameter.}
\code{portion_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and calculates the portions R, I and S. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each variable with class \code{"rsi"}.
The function \code{portion_df} takes any variable from \code{data} that has an \code{"rsi"} class (created with \code{\link{as.rsi}}) and calculates the portions R, I and S. The resulting \emph{tidy data} (see Source) \code{data.frame} will have three rows (S/I/R) and a column for each group and each variable with class \code{"rsi"}.
The function \code{rsi_df} works exactly like \code{portion_df}, but add the number of isolates.
\if{html}{
\cr\cr
To calculate the probability (\emph{p}) of susceptibility of one antibiotic, we use this formula:

View File

@ -50,17 +50,17 @@ test_that("counts work", {
# count_df
expect_equal(
septic_patients %>% select(AMX) %>% count_df() %>% pull(Value),
septic_patients %>% select(AMX) %>% count_df() %>% pull(value),
c(septic_patients$AMX %>% count_SI(),
septic_patients$AMX %>% count_R())
)
expect_equal(
septic_patients %>% select(AMX) %>% count_df(combine_IR = TRUE) %>% pull(Value),
septic_patients %>% select(AMX) %>% count_df(combine_IR = TRUE) %>% pull(value),
c(septic_patients$AMX %>% count_S(),
septic_patients$AMX %>% count_IR())
)
expect_equal(
septic_patients %>% select(AMX) %>% count_df(combine_SI = FALSE) %>% pull(Value),
septic_patients %>% select(AMX) %>% count_df(combine_SI = FALSE) %>% pull(value),
c(septic_patients$AMX %>% count_S(),
septic_patients$AMX %>% count_I(),
septic_patients$AMX %>% count_R())

View File

@ -100,17 +100,17 @@ test_that("portions works", {
# portion_df
expect_equal(
septic_patients %>% select(AMX) %>% portion_df() %>% pull(Value),
septic_patients %>% select(AMX) %>% portion_df() %>% pull(value),
c(septic_patients$AMX %>% portion_SI(),
septic_patients$AMX %>% portion_R())
)
expect_equal(
septic_patients %>% select(AMX) %>% portion_df(combine_IR = TRUE) %>% pull(Value),
septic_patients %>% select(AMX) %>% portion_df(combine_IR = TRUE) %>% pull(value),
c(septic_patients$AMX %>% portion_S(),
septic_patients$AMX %>% portion_IR())
)
expect_equal(
septic_patients %>% select(AMX) %>% portion_df(combine_SI = FALSE) %>% pull(Value),
septic_patients %>% select(AMX) %>% portion_df(combine_SI = FALSE) %>% pull(value),
c(septic_patients$AMX %>% portion_S(),
septic_patients$AMX %>% portion_I(),
septic_patients$AMX %>% portion_R())