added Becker 2019

This commit is contained in:
dr. M.S. (Matthijs) Berends 2019-03-26 14:24:03 +01:00
parent c6a12266e7
commit 29f444543d
45 changed files with 674 additions and 476 deletions

View File

@ -1,6 +1,6 @@
Package: AMR Package: AMR
Version: 0.5.0.9024 Version: 0.5.0.9025
Date: 2019-03-18 Date: 2019-03-26
Title: Antimicrobial Resistance Analysis Title: Antimicrobial Resistance Analysis
Authors@R: c( Authors@R: c(
person( person(

View File

@ -23,6 +23,7 @@ S3method(plot,mic)
S3method(plot,resistance_predict) S3method(plot,resistance_predict)
S3method(plot,rsi) S3method(plot,rsi)
S3method(print,atc) S3method(print,atc)
S3method(print,catalogue_of_life_version)
S3method(print,frequency_tbl) S3method(print,frequency_tbl)
S3method(print,mic) S3method(print,mic)
S3method(print,mo) S3method(print,mo)
@ -191,6 +192,7 @@ exportMethods(plot.frequency_tbl)
exportMethods(plot.mic) exportMethods(plot.mic)
exportMethods(plot.rsi) exportMethods(plot.rsi)
exportMethods(print.atc) exportMethods(print.atc)
exportMethods(print.catalogue_of_life_version)
exportMethods(print.frequency_tbl) exportMethods(print.frequency_tbl)
exportMethods(print.mic) exportMethods(print.mic)
exportMethods(print.mo) exportMethods(print.mo)
@ -221,6 +223,7 @@ importFrom(crayon,red)
importFrom(crayon,silver) importFrom(crayon,silver)
importFrom(crayon,strip_style) importFrom(crayon,strip_style)
importFrom(crayon,underline) importFrom(crayon,underline)
importFrom(crayon,white)
importFrom(crayon,yellow) importFrom(crayon,yellow)
importFrom(data.table,as.data.table) importFrom(data.table,as.data.table)
importFrom(data.table,data.table) importFrom(data.table,data.table)
@ -292,3 +295,4 @@ importFrom(stats,sd)
importFrom(utils,browseURL) importFrom(utils,browseURL)
importFrom(utils,browseVignettes) importFrom(utils,browseVignettes)
importFrom(utils,installed.packages) importFrom(utils,installed.packages)
importFrom(utils,menu)

View File

@ -81,10 +81,10 @@ NULL
#' #'
#' This function returns information about the included data from the Catalogue of Life. It also shows if the included version is their latest annual release. The Catalogue of Life releases their annual release in March each year. #' This function returns information about the included data from the Catalogue of Life. It also shows if the included version is their latest annual release. The Catalogue of Life releases their annual release in March each year.
#' @seealso \code{\link{microorganisms}} #' @seealso \code{\link{microorganisms}}
#' @details The list item \code{is_latest_annual_release} is based on the system date. #' @details The list item \code{...$catalogue_of_life$is_latest_annual_release} is based on the system date.
#' #'
#' For DSMZ, see \code{?microorganisms}. #' For DSMZ, see \code{?microorganisms}.
#' @return a \code{list}, invisibly #' @return a \code{list}, which prints in pretty format
#' @inheritSection catalogue_of_life Catalogue of Life #' @inheritSection catalogue_of_life Catalogue of Life
#' @inheritSection AMR Read more on our website! #' @inheritSection AMR Read more on our website!
#' @importFrom crayon bold underline #' @importFrom crayon bold underline
@ -99,8 +99,8 @@ catalogue_of_life_version <- function() {
lst <- list(catalogue_of_life = lst <- list(catalogue_of_life =
list(version = gsub("{year}", catalogue_of_life$year, catalogue_of_life$version, fixed = TRUE), list(version = gsub("{year}", catalogue_of_life$year, catalogue_of_life$version, fixed = TRUE),
url = gsub("{year}", catalogue_of_life$year, catalogue_of_life$url_CoL, fixed = TRUE), url = gsub("{year}", catalogue_of_life$year, catalogue_of_life$url_CoL, fixed = TRUE),
# annual release always somewhere in March, so before April is TRUE, FALSE otherwise # annual release always somewhere in May, so before June is TRUE, FALSE otherwise
is_latest_annual_release = Sys.Date() < as.Date(paste0(catalogue_of_life$year + 1, "-04-01")), is_latest_annual_release = Sys.Date() < as.Date(paste0(catalogue_of_life$year + 1, "-06-01")),
n = nrow(filter(AMR::microorganisms, source == "CoL"))), n = nrow(filter(AMR::microorganisms, source == "CoL"))),
deutsche_sammlung_von_mikroorganismen_und_zellkulturen = deutsche_sammlung_von_mikroorganismen_und_zellkulturen =
list(version = "Prokaryotic Nomenclature Up-to-Date from DSMZ", list(version = "Prokaryotic Nomenclature Up-to-Date from DSMZ",
@ -112,7 +112,16 @@ catalogue_of_life_version <- function() {
n_total_species = nrow(AMR::microorganisms), n_total_species = nrow(AMR::microorganisms),
n_total_synonyms = nrow(AMR::microorganisms.old))) n_total_synonyms = nrow(AMR::microorganisms.old)))
cat(paste0(bold("Included in this package are:\n\n"), structure(.Data = lst,
class = c("catalogue_of_life_version", "list"))
}
#' @exportMethod print.catalogue_of_life_version
#' @export
#' @noRd
print.catalogue_of_life_version <- function(x, ...) {
lst <- x
cat(paste0(bold("Included in this AMR package are:\n\n"),
underline(lst$catalogue_of_life$version), "\n", underline(lst$catalogue_of_life$version), "\n",
" Available at: ", lst$catalogue_of_life$url, "\n", " Available at: ", lst$catalogue_of_life$url, "\n",
" Number of included species: ", format(lst$catalogue_of_life$n, big.mark = ","), "\n", " Number of included species: ", format(lst$catalogue_of_life$n, big.mark = ","), "\n",
@ -121,9 +130,7 @@ catalogue_of_life_version <- function() {
lst$deutsche_sammlung_von_mikroorganismen_und_zellkulturen$yearmonth, ")")), "\n", lst$deutsche_sammlung_von_mikroorganismen_und_zellkulturen$yearmonth, ")")), "\n",
" Available at: ", lst$deutsche_sammlung_von_mikroorganismen_und_zellkulturen$url, "\n", " Available at: ", lst$deutsche_sammlung_von_mikroorganismen_und_zellkulturen$url, "\n",
" Number of included species: ", format(lst$deutsche_sammlung_von_mikroorganismen_und_zellkulturen$n, big.mark = ","), "\n\n", " Number of included species: ", format(lst$deutsche_sammlung_von_mikroorganismen_und_zellkulturen$n, big.mark = ","), "\n\n",
"Total number of species included: ", format(lst$total_included$n_total_species, big.mark = ","), "\n", "=> Total number of species included: ", format(lst$total_included$n_total_species, big.mark = ","), "\n",
"Total number of synonyms included: ", format(lst$total_included$n_total_synonyms, big.mark = ","), "\n\n", "=> Total number of synonyms included: ", format(lst$total_included$n_total_synonyms, big.mark = ","), "\n\n",
"See for more info ?microorganisms and ?catalogue_of_life.\n")) "See for more info ?microorganisms and ?catalogue_of_life.\n"))
return(base::invisible(lst))
} }

View File

@ -69,7 +69,7 @@
#' S = count_S(cipr), #' S = count_S(cipr),
#' n1 = count_all(cipr), # the actual total; sum of all three #' n1 = count_all(cipr), # the actual total; sum of all three
#' n2 = n_rsi(cipr), # same - analogous to n_distinct #' n2 = n_rsi(cipr), # same - analogous to n_distinct
#' total = n()) # NOT the amount of tested isolates! #' total = n()) # NOT the number of tested isolates!
#' #'
#' # Count co-resistance between amoxicillin/clav acid and gentamicin, #' # Count co-resistance between amoxicillin/clav acid and gentamicin,
#' # so we can see that combination therapy does a lot more than mono therapy. #' # so we can see that combination therapy does a lot more than mono therapy.

View File

@ -19,11 +19,11 @@
# Visit our website for more info: https://msberends.gitab.io/AMR. # # Visit our website for more info: https://msberends.gitab.io/AMR. #
# ==================================================================== # # ==================================================================== #
#' Filter on antibiotic class #' Filter isolates on result in antibiotic class
#' #'
#' Filter on specific antibiotic variables based on their class (ATC groups). #' Filter isolates on results in specific antibiotic variables based on their class (ATC groups). This makes it easy to get a list of isolates that were tested for e.g. any aminoglycoside.
#' @param tbl a data set #' @param tbl a data set
#' @param ab_class an antimicrobial class, like \code{"carbapenems"} #' @param ab_class an antimicrobial class, like \code{"carbapenems"}. More specifically, this should be a text that can be found in a 4th level ATC group (chemical subgroup) or a 5th level ATC group (chemical substance), please see \href{https://www.whocc.no/atc/structure_and_principles/}{this explanation on the WHOCC website}.
#' @param result an antibiotic result: S, I or R (or a combination of more of them) #' @param result an antibiotic result: S, I or R (or a combination of more of them)
#' @param scope the scope to check which variables to check, can be \code{"any"} (default) or \code{"all"} #' @param scope the scope to check which variables to check, can be \code{"any"} (default) or \code{"all"}
#' @param ... parameters passed on to \code{\link[dplyr]{filter_at}} #' @param ... parameters passed on to \code{\link[dplyr]{filter_at}}
@ -54,8 +54,14 @@
#' # filter on isolates that show resistance to #' # filter on isolates that show resistance to
#' # any aminoglycoside and any fluoroquinolone #' # any aminoglycoside and any fluoroquinolone
#' septic_patients %>% #' septic_patients %>%
#' filter_aminoglycosides("R", "any") %>% #' filter_aminoglycosides("R") %>%
#' filter_fluoroquinolones("R", "any") #' filter_fluoroquinolones("R")
#'
#' # filter on isolates that show resistance to
#' # all aminoglycosides and all fluoroquinolones
#' septic_patients %>%
#' filter_aminoglycosides("R", "all") %>%
#' filter_fluoroquinolones("R", "all")
filter_ab_class <- function(tbl, filter_ab_class <- function(tbl,
ab_class, ab_class,
result = NULL, result = NULL,
@ -65,6 +71,8 @@ filter_ab_class <- function(tbl,
if (is.null(result)) { if (is.null(result)) {
result <- c("S", "I", "R") result <- c("S", "I", "R")
} }
# make result = "IR" work too:
result <- unlist(strsplit(result, ""))
if (!all(result %in% c("S", "I", "R"))) { if (!all(result %in% c("S", "I", "R"))) {
stop("`result` must be one or more of: S, I, R", call. = FALSE) stop("`result` must be one or more of: S, I, R", call. = FALSE)
@ -88,12 +96,20 @@ filter_ab_class <- function(tbl,
} else { } else {
scope_txt <- " and " scope_txt <- " and "
scope_fn <- all_vars scope_fn <- all_vars
if (length(vars_df) > 1) {
operator <- gsub("is", "are", operator)
}
} }
message(blue(paste0("Filtering on ", atc_groups, ": ", scope, " of ", if (length(vars_df) > 1) {
scope <- paste(scope, "of ")
} else {
scope <- ""
}
message(blue(paste0("Filtering on ", atc_groups, ": ", scope,
paste(bold(paste0("`", vars_df, "`")), collapse = scope_txt), operator, toString(result)))) paste(bold(paste0("`", vars_df, "`")), collapse = scope_txt), operator, toString(result))))
tbl %>% tbl %>%
filter_at(.vars = vars(vars_df), filter_at(vars(vars_df),
.vars_predicate = scope_fn(. %in% result), scope_fn(. %in% result),
...) ...)
} else { } else {
warning(paste0("no antibiotics of class ", atc_groups, " found, leaving data unchanged"), call. = FALSE) warning(paste0("no antibiotics of class ", atc_groups, " found, leaving data unchanged"), call. = FALSE)
@ -244,7 +260,7 @@ filter_tetracyclines <- function(tbl,
...) ...)
} }
#' @importFrom dplyr %>% filter_at any_vars select #' @importFrom dplyr %>% filter_at vars any_vars select
ab_class_vars <- function(ab_class) { ab_class_vars <- function(ab_class) {
ab_vars <- AMR::antibiotics %>% ab_vars <- AMR::antibiotics %>%
filter_at(vars(c("atc_group1", "atc_group2")), any_vars(. %like% ab_class)) %>% filter_at(vars(c("atc_group1", "atc_group2")), any_vars(. %like% ab_class)) %>%
@ -260,10 +276,23 @@ ab_class_vars <- function(ab_class) {
#' @importFrom dplyr %>% filter pull #' @importFrom dplyr %>% filter pull
ab_class_atcgroups <- function(ab_class) { ab_class_atcgroups <- function(ab_class) {
AMR::antibiotics %>% ifelse(ab_class %in% c("aminoglycoside",
filter(atc %in% ab_class_vars(ab_class)) %>% "carbapenem",
pull("atc_group2") %>% "cephalosporin",
unique() %>% "first-generation cephalosporin",
tolower() %>% "second-generation cephalosporin",
paste(collapse = "/") "third-generation cephalosporin",
"fourth-generation cephalosporin",
"fluoroquinolone",
"glycopeptide",
"macrolide",
"tetracycline"),
paste0(ab_class, "s"),
AMR::antibiotics %>%
filter(atc %in% ab_class_vars(ab_class)) %>%
pull("atc_group2") %>%
unique() %>%
tolower() %>%
paste(collapse = "/")
)
} }

View File

@ -417,9 +417,9 @@ frequency_tbl <- function(x,
header_list$outliers_unique <- n_distinct(boxplot.stats(x)$out) header_list$outliers_unique <- n_distinct(boxplot.stats(x)$out)
} }
if (NROW(x) > 0 & any(class(x) == "rsi")) { if (any(class(x) == "rsi")) {
header_list$count_S <- sum(x == "S", na.rm = TRUE) header_list$count_S <- max(0, sum(x == "S", na.rm = TRUE), na.rm = TRUE)
header_list$count_IR <- sum(x %in% c("I", "R"), na.rm = TRUE) header_list$count_IR <- max(0, sum(x %in% c("I", "R"), na.rm = TRUE), na.rm = TRUE)
} }
formatdates <- "%e %B %Y" # = d mmmm yyyy formatdates <- "%e %B %Y" # = d mmmm yyyy
@ -564,18 +564,14 @@ format_header <- function(x, markdown = FALSE, decimal.mark = ".", big.mark = ",
# FORMATTING # FORMATTING
# rsi # rsi
if (has_length == TRUE & any(x_class == "rsi")) { if (has_length == TRUE & any(x_class == "rsi")) {
if (header$count_S < header$count_IR) { ab <- tryCatch(atc_name(attributes(x)$opt$vars), error = function(e) NA)
ratio <- paste0(green(1), ":", red(format(header$count_IR / header$count_S, if (!is.na(ab)) {
digits = 1, nsmall = 1, decimal.mark = decimal.mark, big.mark = big.mark))) header$drug <- ab[1L]
} else {
ratio <- paste0(green(format(header$count_S / header$count_IR,
digits = 1, nsmall = 1, decimal.mark = decimal.mark, big.mark = big.mark)),
":", red(1))
} }
header$`%IR` <- paste((header$count_IR / header$length) %>% percent(force_zero = TRUE, round = digits, decimal.mark = decimal.mark), header$`%IR` <- percent(header$count_IR / (header$count_S + header$count_IR),
paste0("(ratio ", ratio, ")")) force_zero = TRUE, round = digits, decimal.mark = decimal.mark)
header <- header[!names(header) %in% c("count_S", "count_IR")]
} }
header <- header[!names(header) %in% c("count_S", "count_IR")]
# dates # dates
if (!is.null(header$date_format)) { if (!is.null(header$date_format)) {
if (header$date_format == "%H:%M:%S") { if (header$date_format == "%H:%M:%S") {

View File

@ -164,9 +164,7 @@ ggplot_rsi <- function(data,
datalabels.colour = "grey15", datalabels.colour = "grey15",
...) { ...) {
if (!"ggplot2" %in% rownames(installed.packages())) { stopifnot_installed_package("ggplot2")
stop('this function requires the ggplot2 package.', call. = FALSE)
}
fun_name <- deparse(substitute(fun)) fun_name <- deparse(substitute(fun))
if (!fun_name %in% c("portion_df", "count_df")) { if (!fun_name %in% c("portion_df", "count_df")) {
@ -235,6 +233,8 @@ geom_rsi <- function(position = NULL,
fun = count_df, fun = count_df,
...) { ...) {
stopifnot_installed_package("ggplot2")
fun_name <- deparse(substitute(fun)) fun_name <- deparse(substitute(fun))
if (!fun_name %in% c("portion_df", "count_df", "fun")) { if (!fun_name %in% c("portion_df", "count_df", "fun")) {
stop("`fun` must be portion_df or count_df") stop("`fun` must be portion_df or count_df")
@ -279,6 +279,8 @@ geom_rsi <- function(position = NULL,
#' @export #' @export
facet_rsi <- function(facet = c("Interpretation", "Antibiotic"), nrow = NULL) { facet_rsi <- function(facet = c("Interpretation", "Antibiotic"), nrow = NULL) {
stopifnot_installed_package("ggplot2")
facet <- facet[1] facet <- facet[1]
# we work with aes_string later on # we work with aes_string later on
@ -302,6 +304,8 @@ facet_rsi <- function(facet = c("Interpretation", "Antibiotic"), nrow = NULL) {
#' @rdname ggplot_rsi #' @rdname ggplot_rsi
#' @export #' @export
scale_y_percent <- function(breaks = seq(0, 1, 0.1), limits = NULL) { scale_y_percent <- function(breaks = seq(0, 1, 0.1), limits = NULL) {
stopifnot_installed_package("ggplot2")
if (all(breaks[breaks != 0] > 1)) { if (all(breaks[breaks != 0] > 1)) {
breaks <- breaks / 100 breaks <- breaks / 100
} }
@ -313,6 +317,7 @@ scale_y_percent <- function(breaks = seq(0, 1, 0.1), limits = NULL) {
#' @rdname ggplot_rsi #' @rdname ggplot_rsi
#' @export #' @export
scale_rsi_colours <- function() { scale_rsi_colours <- function() {
stopifnot_installed_package("ggplot2")
#ggplot2::scale_fill_brewer(palette = "RdYlGn") #ggplot2::scale_fill_brewer(palette = "RdYlGn")
ggplot2::scale_fill_manual(values = c("#b22222", "#ae9c20", "#7cfc00")) ggplot2::scale_fill_manual(values = c("#b22222", "#ae9c20", "#7cfc00"))
} }
@ -320,6 +325,7 @@ scale_rsi_colours <- function() {
#' @rdname ggplot_rsi #' @rdname ggplot_rsi
#' @export #' @export
theme_rsi <- function() { theme_rsi <- function() {
stopifnot_installed_package("ggplot2")
ggplot2::theme_minimal() + ggplot2::theme_minimal() +
ggplot2::theme(panel.grid.major.x = ggplot2::element_blank(), ggplot2::theme(panel.grid.major.x = ggplot2::element_blank(),
panel.grid.minor = ggplot2::element_blank(), panel.grid.minor = ggplot2::element_blank(),
@ -332,6 +338,7 @@ labels_rsi_count <- function(position = NULL,
x = "Antibiotic", x = "Antibiotic",
datalabels.size = 3, datalabels.size = 3,
datalabels.colour = "grey15") { datalabels.colour = "grey15") {
stopifnot_installed_package("ggplot2")
if (is.null(position)) { if (is.null(position)) {
position <- "fill" position <- "fill"
} }
@ -357,3 +364,4 @@ getlbls <- function(data) {
" (n=", Value, ")")) %>% " (n=", Value, ")")) %>%
mutate(lbl = ifelse(lbl == "0.0% (n=0)", "", lbl)) mutate(lbl = ifelse(lbl == "0.0% (n=0)", "", lbl))
} }

View File

@ -92,7 +92,7 @@ globalVariables(c(".",
"Sex", "Sex",
"shortname", "shortname",
"species", "species",
"superprevalent", "species_id",
"trade_name", "trade_name",
"transmute", "transmute",
"tsn", "tsn",

View File

@ -194,3 +194,9 @@ search_type_in_df <- function(tbl, type) {
} }
found found
} }
stopifnot_installed_package <- function(package) {
if (!package %in% base::rownames(utils::installed.packages())) {
stop("this function requires the ", package, " package.", call. = FALSE)
}
}

233
R/mo.R
View File

@ -23,10 +23,10 @@
#' #'
#' Use this function to determine a valid microorganism ID (\code{mo}). Determination is done using intelligent rules and the complete taxonomic kingdoms Bacteria, Chromista, Protozoa, Archaea and most microbial species from the kingdom Fungi (see Source). The input can be almost anything: a full name (like \code{"Staphylococcus aureus"}), an abbreviated name (like \code{"S. aureus"}), an abbreviation known in the field (like \code{"MRSA"}), or just a genus. Please see Examples. #' Use this function to determine a valid microorganism ID (\code{mo}). Determination is done using intelligent rules and the complete taxonomic kingdoms Bacteria, Chromista, Protozoa, Archaea and most microbial species from the kingdom Fungi (see Source). The input can be almost anything: a full name (like \code{"Staphylococcus aureus"}), an abbreviated name (like \code{"S. aureus"}), an abbreviation known in the field (like \code{"MRSA"}), or just a genus. Please see Examples.
#' @param x a character vector or a \code{data.frame} with one or two columns #' @param x a character vector or a \code{data.frame} with one or two columns
#' @param Becker a logical to indicate whether \emph{Staphylococci} should be categorised into Coagulase Negative \emph{Staphylococci} ("CoNS") and Coagulase Positive \emph{Staphylococci} ("CoPS") instead of their own species, according to Karsten Becker \emph{et al.} [1]. Note that this does not include species that were newly named after this publication. #' @param Becker a logical to indicate whether \emph{Staphylococci} should be categorised into coagulase-negative \emph{Staphylococci} ("CoNS") and coagulase-positive \emph{Staphylococci} ("CoPS") instead of their own species, according to Karsten Becker \emph{et al.} [1,2]. Note that this does not include species that were newly named after these publications, like \emph{S. caeli}.
#' #'
#' This excludes \emph{Staphylococcus aureus} at default, use \code{Becker = "all"} to also categorise \emph{S. aureus} as "CoPS". #' This excludes \emph{Staphylococcus aureus} at default, use \code{Becker = "all"} to also categorise \emph{S. aureus} as "CoPS".
#' @param Lancefield a logical to indicate whether beta-haemolytic \emph{Streptococci} should be categorised into Lancefield groups instead of their own species, according to Rebecca C. Lancefield [2]. These \emph{Streptococci} will be categorised in their first group, e.g. \emph{Streptococcus dysgalactiae} will be group C, although officially it was also categorised into groups G and L. #' @param Lancefield a logical to indicate whether beta-haemolytic \emph{Streptococci} should be categorised into Lancefield groups instead of their own species, according to Rebecca C. Lancefield [3]. These \emph{Streptococci} will be categorised in their first group, e.g. \emph{Streptococcus dysgalactiae} will be group C, although officially it was also categorised into groups G and L.
#' #'
#' This excludes \emph{Enterococci} at default (who are in group D), use \code{Lancefield = "all"} to also categorise all \emph{Enterococci} as group D. #' This excludes \emph{Enterococci} at default (who are in group D), use \code{Lancefield = "all"} to also categorise all \emph{Enterococci} as group D.
#' @param allow_uncertain a logical (\code{TRUE} or \code{FALSE}) or a value between 0 and 3 to indicate whether the input should be checked for less possible results, see Details #' @param allow_uncertain a logical (\code{TRUE} or \code{FALSE}) or a value between 0 and 3 to indicate whether the input should be checked for less possible results, see Details
@ -49,18 +49,19 @@
#' | | | ----> subspecies, a 3-4 letter acronym #' | | | ----> subspecies, a 3-4 letter acronym
#' | | ----> species, a 3-4 letter acronym #' | | ----> species, a 3-4 letter acronym
#' | ----> genus, a 5-7 letter acronym, mostly without vowels #' | ----> genus, a 5-7 letter acronym, mostly without vowels
#' ----> taxonomic kingdom: A (Archaea), AN (Animalia), B (Bacteria), C (Chromista), #' ----> taxonomic kingdom: A (Archaea), AN (Animalia), B (Bacteria),
#' F (Fungi), P (Protozoa) or PL (Plantae) #' C (Chromista), F (Fungi), P (Protozoa) or
#' PL (Plantae)
#' } #' }
#' #'
#' Values that cannot be coered will be considered 'unknown' and have an MO code \code{UNKNOWN}. #' Values that cannot be coered will be considered 'unknown' and will get the MO code \code{UNKNOWN}.
#' #'
#' Use the \code{\link{mo_property}_*} functions to get properties based on the returned code, see Examples. #' Use the \code{\link{mo_property}_*} functions to get properties based on the returned code, see Examples.
#' #'
#' The algorithm uses data from the Catalogue of Life (see below) and from one other source (see \code{?microorganisms}). #' The algorithm uses data from the Catalogue of Life (see below) and from one other source (see \code{?microorganisms}).
#' #'
#' \strong{Self-learning algoritm} \cr #' \strong{Self-learning algoritm} \cr
#' The \code{as.mo()} function gains experience from previously determined microbial IDs and learns from it. This drastically improves both speed and reliability. Use \code{clean_mo_history()} to reset the algorithms. Only experience from your current \code{AMR} package version is used. This is done because in the future the taxonomic tree (which is included in this package) may change for any organism and it consequently has to rebuild its knowledge. Usually, any guess after the first try runs 90-95\% faster than the first try. The algorithm saves its previous findings to \code{~/.Rhistory_mo}. #' The \code{as.mo()} function gains experience from previously determined microbial IDs and learns from it. This drastically improves both speed and reliability. Use \code{clean_mo_history()} to reset the algorithms. Only experience from your current \code{AMR} package version is used. This is done because in the future the taxonomic tree (which is included in this package) may change for any organism and it consequently has to rebuild its knowledge. Usually, any guess after the first try runs 80-95\% faster than the first try. The algorithm saves its previous findings to \code{~/.Rhistory_mo}.
#' #'
#' \strong{Intelligent rules} \cr #' \strong{Intelligent rules} \cr
#' This function uses intelligent rules to help getting fast and logical results. It tries to find matches in this order: #' This function uses intelligent rules to help getting fast and logical results. It tries to find matches in this order:
@ -80,7 +81,7 @@
#' This means that looking up human pathogenic microorganisms takes less time than looking up human non-pathogenic microorganisms. #' This means that looking up human pathogenic microorganisms takes less time than looking up human non-pathogenic microorganisms.
#' #'
#' \strong{Uncertain results} \cr #' \strong{Uncertain results} \cr
#' The algorithm can additionally use three different levels of uncertainty to guess valid results. The default is \code{allow_uncertain = TRUE}, which is uqual to uncertainty level 2. Using \code{allow_uncertain = FALSE} will skip all of these additional rules: #' The algorithm can additionally use three different levels of uncertainty to guess valid results. The default is \code{allow_uncertain = TRUE}, which is equal to uncertainty level 2. Using \code{allow_uncertain = FALSE} will skip all of these additional rules:
#' \itemize{ #' \itemize{
#' \item{(uncertainty level 1): It tries to look for only matching genera} #' \item{(uncertainty level 1): It tries to look for only matching genera}
#' \item{(uncertainty level 1): It tries to look for previously accepted (but now invalid) taxonomic names} #' \item{(uncertainty level 1): It tries to look for previously accepted (but now invalid) taxonomic names}
@ -121,11 +122,13 @@
#' @section Source: #' @section Source:
#' [1] Becker K \emph{et al.} \strong{Coagulase-Negative Staphylococci}. 2014. Clin Microbiol Rev. 27(4): 870926. \url{https://dx.doi.org/10.1128/CMR.00109-13} #' [1] Becker K \emph{et al.} \strong{Coagulase-Negative Staphylococci}. 2014. Clin Microbiol Rev. 27(4): 870926. \url{https://dx.doi.org/10.1128/CMR.00109-13}
#' #'
#' [2] Lancefield RC \strong{A serological differentiation of human and other groups of hemolytic streptococci}. 1933. J Exp Med. 57(4): 57195. \url{https://dx.doi.org/10.1084/jem.57.4.571} #' [2] Becker K \emph{et al.} \strong{Implications of identifying the recently defined members of the S. aureus complex, S. argenteus and S. schweitzeri: A position paper of members of the ESCMID Study Group for staphylococci and Staphylococcal Diseases (ESGS).}. 2019. Clin Microbiol Infect. 2019 Mar 11. \url{https://doi.org/10.1016/j.cmi.2019.02.028}
#' #'
#' [3] Catalogue of Life: Annual Checklist (public online taxonomic database), \url{www.catalogueoflife.org} (check included annual version with \code{\link{catalogue_of_life_version}()}). #' [3] Lancefield RC \strong{A serological differentiation of human and other groups of hemolytic streptococci}. 1933. J Exp Med. 57(4): 57195. \url{https://dx.doi.org/10.1084/jem.57.4.571}
#'
#' [4] Catalogue of Life: Annual Checklist (public online taxonomic database), \url{www.catalogueoflife.org} (check included annual version with \code{\link{catalogue_of_life_version}()}).
#' @export #' @export
#' @return Character (vector) with class \code{"mo"}. Unknown values will return \code{NA}. #' @return Character (vector) with class \code{"mo"}
#' @seealso \code{\link{microorganisms}} for the \code{data.frame} that is being used to determine ID's. \cr #' @seealso \code{\link{microorganisms}} for the \code{data.frame} that is being used to determine ID's. \cr
#' The \code{\link{mo_property}} functions (like \code{\link{mo_genus}}, \code{\link{mo_gramstain}}) to get properties based on the returned code. #' The \code{\link{mo_property}} functions (like \code{\link{mo_genus}}, \code{\link{mo_gramstain}}) to get properties based on the returned code.
#' @inheritSection AMR Read more on our website! #' @inheritSection AMR Read more on our website!
@ -188,7 +191,8 @@ as.mo <- function(x, Becker = FALSE, Lancefield = FALSE, allow_uncertain = TRUE,
# check onLoad() in R/zzz.R: data tables are created there. # check onLoad() in R/zzz.R: data tables are created there.
} }
mo_hist <- get_mo_history(x, force = isTRUE(list(...)$force_mo_history)) uncertainty_level <- translate_allow_uncertain(allow_uncertain)
mo_hist <- get_mo_history(x, uncertainty_level, force = isTRUE(list(...)$force_mo_history))
if (mo_source_isvalid(reference_df) if (mo_source_isvalid(reference_df)
& isFALSE(Becker) & isFALSE(Becker)
@ -247,13 +251,13 @@ as.mo <- function(x, Becker = FALSE, Lancefield = FALSE, allow_uncertain = TRUE,
"mo"][[1]] "mo"][[1]]
} }
# save them to history # save them to history
set_mo_history(x, y, force = isTRUE(list(...)$force_mo_history)) set_mo_history(x, y, 0, force = isTRUE(list(...)$force_mo_history))
} else { } else {
# will be checked for mo class in validation and uses exec_as.mo internally if necessary # will be checked for mo class in validation and uses exec_as.mo internally if necessary
y <- mo_validate(x = x, property = "mo", y <- mo_validate(x = x, property = "mo",
Becker = Becker, Lancefield = Lancefield, Becker = Becker, Lancefield = Lancefield,
allow_uncertain = allow_uncertain, reference_df = reference_df, allow_uncertain = uncertainty_level, reference_df = reference_df,
force_mo_history = isTRUE(list(...)$force_mo_history)) force_mo_history = isTRUE(list(...)$force_mo_history))
} }
@ -320,15 +324,8 @@ exec_as.mo <- function(x,
fullname = character(0), fullname = character(0),
mo = character(0)) mo = character(0))
failures <- character(0) failures <- character(0)
if (isTRUE(allow_uncertain)) { uncertainty_level <- translate_allow_uncertain(allow_uncertain)
# default to uncertainty level 2
allow_uncertain <- 2
} else {
allow_uncertain <- as.integer(allow_uncertain)
if (!allow_uncertain %in% c(0:3)) {
stop("`allow_uncertain` must be a number between 0 (none) and 3 (all), or TRUE (= 2) or FALSE (= 0).", call. = FALSE)
}
}
x_input <- x x_input <- x
# already strip leading and trailing spaces # already strip leading and trailing spaces
x <- trimws(x, which = "both") x <- trimws(x, which = "both")
@ -341,7 +338,6 @@ exec_as.mo <- function(x,
& !identical(x, "") & !identical(x, "")
& !identical(x, "xxx") & !identical(x, "xxx")
& !identical(x, "con")] & !identical(x, "con")]
x_input_backup <- x
# conversion of old MO codes from v0.5.0 (ITIS) to later versions (Catalogue of Life) # conversion of old MO codes from v0.5.0 (ITIS) to later versions (Catalogue of Life)
if (any(x %like% "^[BFP]_[A-Z]{3,7}") & !all(x %in% microorganisms$mo)) { if (any(x %like% "^[BFP]_[A-Z]{3,7}") & !all(x %in% microorganisms$mo)) {
@ -406,9 +402,13 @@ exec_as.mo <- function(x,
} }
x <- y x <- y
} else if (all(x %in% read_mo_history(force = force_mo_history)$x)) { } else if (all(x %in% read_mo_history(uncertainty_level,
force = force_mo_history)$x)) {
# previously found code # previously found code
x <- microorganismsDT[data.table(mo = get_mo_history(x, force = force_mo_history)), on = "mo", ..property][[1]] x <- microorganismsDT[data.table(mo = get_mo_history(x,
uncertainty_level,
force = force_mo_history)),
on = "mo", ..property][[1]]
} else if (all(tolower(x) %in% microorganismsDT$fullname_lower)) { } else if (all(tolower(x) %in% microorganismsDT$fullname_lower)) {
# we need special treatment for very prevalent full names, they are likely! # we need special treatment for very prevalent full names, they are likely!
@ -430,7 +430,7 @@ exec_as.mo <- function(x,
# commonly used MO codes # commonly used MO codes
y <- as.data.table(AMR::microorganisms.codes)[data.table(code = toupper(x)), on = "code", ] y <- as.data.table(AMR::microorganisms.codes)[data.table(code = toupper(x)), on = "code", ]
# save them to history # save them to history
set_mo_history(x, y$mo, force = force_mo_history) set_mo_history(x, y$mo, 0, force = force_mo_history)
x <- microorganismsDT[data.table(mo = y[["mo"]]), on = "mo", ..property][[1]] x <- microorganismsDT[data.table(mo = y[["mo"]]), on = "mo", ..property][[1]]
@ -502,11 +502,16 @@ exec_as.mo <- function(x,
progress$tick()$print() progress$tick()$print()
found <- microorganismsDT[mo == get_mo_history(x_backup[i], force = force_mo_history), ..property][[1]] if (initial_search == TRUE) {
# previously found result found <- microorganismsDT[mo == get_mo_history(x_backup[i],
if (length(found) > 0) { uncertainty_level,
x[i] <- found[1L] force = force_mo_history),
next ..property][[1]]
# previously found result
if (length(found) > 0) {
x[i] <- found[1L]
next
}
} }
found <- microorganismsDT[mo == toupper(x_backup[i]), ..property][[1]] found <- microorganismsDT[mo == toupper(x_backup[i]), ..property][[1]]
@ -521,7 +526,7 @@ exec_as.mo <- function(x,
if (length(found) > 0) { if (length(found) > 0) {
x[i] <- found[1L] x[i] <- found[1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -535,7 +540,7 @@ exec_as.mo <- function(x,
# empty and nonsense values, ignore without warning # empty and nonsense values, ignore without warning
x[i] <- microorganismsDT[mo == "UNKNOWN", ..property][[1]] x[i] <- microorganismsDT[mo == "UNKNOWN", ..property][[1]]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -552,7 +557,7 @@ exec_as.mo <- function(x,
if (length(found) > 0) { if (length(found) > 0) {
x[i] <- found[1L] x[i] <- found[1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -562,7 +567,7 @@ exec_as.mo <- function(x,
x[i] <- microorganismsDT[mo == "UNKNOWN", ..property][[1]] x[i] <- microorganismsDT[mo == "UNKNOWN", ..property][[1]]
if (initial_search == TRUE) { if (initial_search == TRUE) {
failures <- c(failures, x_backup[i]) failures <- c(failures, x_backup[i])
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -572,7 +577,7 @@ exec_as.mo <- function(x,
x[i] <- microorganismsDT[mo == "UNKNOWN", ..property][[1]] x[i] <- microorganismsDT[mo == "UNKNOWN", ..property][[1]]
if (initial_search == TRUE) { if (initial_search == TRUE) {
failures <- c(failures, x_backup[i]) failures <- c(failures, x_backup[i])
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -582,14 +587,14 @@ exec_as.mo <- function(x,
if (toupper(x_backup_without_spp[i]) %in% c('MRSA', 'MSSA', 'VISA', 'VRSA')) { if (toupper(x_backup_without_spp[i]) %in% c('MRSA', 'MSSA', 'VISA', 'VRSA')) {
x[i] <- microorganismsDT[mo == 'B_STPHY_AUR', ..property][[1]][1L] x[i] <- microorganismsDT[mo == 'B_STPHY_AUR', ..property][[1]][1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
if (toupper(x_backup_without_spp[i]) %in% c('MRSE', 'MSSE')) { if (toupper(x_backup_without_spp[i]) %in% c('MRSE', 'MSSE')) {
x[i] <- microorganismsDT[mo == 'B_STPHY_EPI', ..property][[1]][1L] x[i] <- microorganismsDT[mo == 'B_STPHY_EPI', ..property][[1]][1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -597,14 +602,14 @@ exec_as.mo <- function(x,
| x_backup_without_spp[i] %like% '(enterococci|enterokok|enterococo)[a-z]*?$') { | x_backup_without_spp[i] %like% '(enterococci|enterokok|enterococo)[a-z]*?$') {
x[i] <- microorganismsDT[mo == 'B_ENTRC', ..property][[1]][1L] x[i] <- microorganismsDT[mo == 'B_ENTRC', ..property][[1]][1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
if (toupper(x_backup_without_spp[i]) %in% c("EHEC", "EPEC", "EIEC", "STEC", "ATEC")) { if (toupper(x_backup_without_spp[i]) %in% c("EHEC", "EPEC", "EIEC", "STEC", "ATEC")) {
x[i] <- microorganismsDT[mo == 'B_ESCHR_COL', ..property][[1]][1L] x[i] <- microorganismsDT[mo == 'B_ESCHR_COL', ..property][[1]][1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -612,7 +617,7 @@ exec_as.mo <- function(x,
# multi resistant P. aeruginosa # multi resistant P. aeruginosa
x[i] <- microorganismsDT[mo == 'B_PSDMN_AER', ..property][[1]][1L] x[i] <- microorganismsDT[mo == 'B_PSDMN_AER', ..property][[1]][1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -621,7 +626,7 @@ exec_as.mo <- function(x,
# co-trim resistant S. maltophilia # co-trim resistant S. maltophilia
x[i] <- microorganismsDT[mo == 'B_STNTR_MAL', ..property][[1]][1L] x[i] <- microorganismsDT[mo == 'B_STNTR_MAL', ..property][[1]][1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -629,7 +634,7 @@ exec_as.mo <- function(x,
# peni I, peni R, vanco I, vanco R: S. pneumoniae # peni I, peni R, vanco I, vanco R: S. pneumoniae
x[i] <- microorganismsDT[mo == 'B_STRPT_PNE', ..property][[1]][1L] x[i] <- microorganismsDT[mo == 'B_STRPT_PNE', ..property][[1]][1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -637,7 +642,7 @@ exec_as.mo <- function(x,
# Streptococci, like GBS = Group B Streptococci (B_STRPT_GRB) # Streptococci, like GBS = Group B Streptococci (B_STRPT_GRB)
x[i] <- microorganismsDT[mo == gsub("G([ABCDFGHK])S", "B_STRPT_GR\\1", x_backup_without_spp[i], ignore.case = TRUE), ..property][[1]][1L] x[i] <- microorganismsDT[mo == gsub("G([ABCDFGHK])S", "B_STRPT_GR\\1", x_backup_without_spp[i], ignore.case = TRUE), ..property][[1]][1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -645,7 +650,7 @@ exec_as.mo <- function(x,
# Streptococci in different languages, like "estreptococos grupo B" # Streptococci in different languages, like "estreptococos grupo B"
x[i] <- microorganismsDT[mo == gsub(".*(streptococ|streptokok|estreptococ).* ([ABCDFGHK])$", "B_STRPT_GR\\2", x_backup_without_spp[i], ignore.case = TRUE), ..property][[1]][1L] x[i] <- microorganismsDT[mo == gsub(".*(streptococ|streptokok|estreptococ).* ([ABCDFGHK])$", "B_STRPT_GR\\2", x_backup_without_spp[i], ignore.case = TRUE), ..property][[1]][1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -653,7 +658,7 @@ exec_as.mo <- function(x,
# Streptococci in different languages, like "Group A Streptococci" # Streptococci in different languages, like "Group A Streptococci"
x[i] <- microorganismsDT[mo == gsub(".*group ([ABCDFGHK]) (streptococ|streptokok|estreptococ).*", "B_STRPT_GR\\1", x_backup_without_spp[i], ignore.case = TRUE), ..property][[1]][1L] x[i] <- microorganismsDT[mo == gsub(".*group ([ABCDFGHK]) (streptococ|streptokok|estreptococ).*", "B_STRPT_GR\\1", x_backup_without_spp[i], ignore.case = TRUE), ..property][[1]][1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -664,7 +669,7 @@ exec_as.mo <- function(x,
# coerce S. coagulase negative # coerce S. coagulase negative
x[i] <- microorganismsDT[mo == 'B_STPHY_CNS', ..property][[1]][1L] x[i] <- microorganismsDT[mo == 'B_STPHY_CNS', ..property][[1]][1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -674,7 +679,7 @@ exec_as.mo <- function(x,
# coerce S. coagulase positive # coerce S. coagulase positive
x[i] <- microorganismsDT[mo == 'B_STPHY_CPS', ..property][[1]][1L] x[i] <- microorganismsDT[mo == 'B_STPHY_CPS', ..property][[1]][1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -684,7 +689,7 @@ exec_as.mo <- function(x,
# coerce Gram negatives # coerce Gram negatives
x[i] <- microorganismsDT[mo == 'B_GRAMN', ..property][[1]][1L] x[i] <- microorganismsDT[mo == 'B_GRAMN', ..property][[1]][1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -694,7 +699,7 @@ exec_as.mo <- function(x,
# coerce Gram positives # coerce Gram positives
x[i] <- microorganismsDT[mo == 'B_GRAMP', ..property][[1]][1L] x[i] <- microorganismsDT[mo == 'B_GRAMP', ..property][[1]][1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -703,7 +708,7 @@ exec_as.mo <- function(x,
# Salmonella Group A to Z, just return S. species for now # Salmonella Group A to Z, just return S. species for now
x[i] <- microorganismsDT[mo == 'B_SLMNL', ..property][[1]][1L] x[i] <- microorganismsDT[mo == 'B_SLMNL', ..property][[1]][1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
options(mo_renamed = c(getOption("mo_renamed"), options(mo_renamed = c(getOption("mo_renamed"),
magenta(paste0("Note: ", magenta(paste0("Note: ",
@ -715,7 +720,7 @@ exec_as.mo <- function(x,
# Salmonella with capital letter species like "Salmonella Goettingen" - they're all S. enterica # Salmonella with capital letter species like "Salmonella Goettingen" - they're all S. enterica
x[i] <- microorganismsDT[mo == 'B_SLMNL_ENT', ..property][[1]][1L] x[i] <- microorganismsDT[mo == 'B_SLMNL_ENT', ..property][[1]][1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
options(mo_renamed = c(getOption("mo_renamed"), options(mo_renamed = c(getOption("mo_renamed"),
magenta(paste0("Note: ", magenta(paste0("Note: ",
@ -735,7 +740,7 @@ exec_as.mo <- function(x,
if (length(found) > 0) { if (length(found) > 0) {
x[i] <- found[1L] x[i] <- found[1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -744,7 +749,7 @@ exec_as.mo <- function(x,
if (length(found) > 0) { if (length(found) > 0) {
x[i] <- found[1L] x[i] <- found[1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -759,7 +764,7 @@ exec_as.mo <- function(x,
if (length(mo_found) > 0) { if (length(mo_found) > 0) {
x[i] <- microorganismsDT[mo == mo_found, ..property][[1]][1L] x[i] <- microorganismsDT[mo == mo_found, ..property][[1]][1L]
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -782,7 +787,7 @@ exec_as.mo <- function(x,
x[i] <- microorganismsDT[mo == "UNKNOWN", ..property][[1]] x[i] <- microorganismsDT[mo == "UNKNOWN", ..property][[1]]
if (initial_search == TRUE) { if (initial_search == TRUE) {
failures <- c(failures, x_backup[i]) failures <- c(failures, x_backup[i])
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -869,7 +874,7 @@ exec_as.mo <- function(x,
g.x_backup_without_spp = x_backup_without_spp[i]) g.x_backup_without_spp = x_backup_without_spp[i])
if (!empty_result(x[i])) { if (!empty_result(x[i])) {
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -884,7 +889,7 @@ exec_as.mo <- function(x,
g.x_backup_without_spp = x_backup_without_spp[i]) g.x_backup_without_spp = x_backup_without_spp[i])
if (!empty_result(x[i])) { if (!empty_result(x[i])) {
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -899,7 +904,7 @@ exec_as.mo <- function(x,
g.x_backup_without_spp = x_backup_without_spp[i]) g.x_backup_without_spp = x_backup_without_spp[i])
if (!empty_result(x[i])) { if (!empty_result(x[i])) {
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -925,7 +930,7 @@ exec_as.mo <- function(x,
ref_new = microorganismsDT[col_id == found[1, col_id_new], ref], ref_new = microorganismsDT[col_id == found[1, col_id_new], ref],
mo = microorganismsDT[col_id == found[1, col_id_new], mo]) mo = microorganismsDT[col_id == found[1, col_id_new], mo])
if (initial_search == TRUE) { if (initial_search == TRUE) {
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
next next
} }
@ -938,12 +943,12 @@ exec_as.mo <- function(x,
f.x_withspaces_end_only, f.x_withspaces_end_only,
g.x_backup_without_spp) { g.x_backup_without_spp) {
if (allow_uncertain == 0) { if (uncertainty_level == 0) {
# do not allow uncertainties # do not allow uncertainties
return(NA_character_) return(NA_character_)
} }
if (allow_uncertain >= 1) { if (uncertainty_level >= 1) {
# (1) look again for old taxonomic names, now for G. species ---- # (1) look again for old taxonomic names, now for G. species ----
found <- microorganisms.oldDT[fullname %like% c.x_withspaces_start_end found <- microorganisms.oldDT[fullname %like% c.x_withspaces_start_end
| fullname %like% d.x_withspaces_start_only] | fullname %like% d.x_withspaces_start_only]
@ -966,11 +971,14 @@ exec_as.mo <- function(x,
input = a.x_backup, input = a.x_backup,
fullname = found[1, fullname], fullname = found[1, fullname],
mo = paste("CoL", found[1, col_id]))) mo = paste("CoL", found[1, col_id])))
if (initial_search == TRUE) {
set_mo_history(a.x_backup, get_mo_code(x, property), 1, force = force_mo_history)
}
return(x) return(x)
} }
} }
if (allow_uncertain >= 2) { if (uncertainty_level >= 2) {
# (3) look for genus only, part of name ---- # (3) look for genus only, part of name ----
if (nchar(g.x_backup_without_spp) > 4 & !b.x_trimmed %like% " ") { if (nchar(g.x_backup_without_spp) > 4 & !b.x_trimmed %like% " ") {
if (!grepl("^[A-Z][a-z]+", b.x_trimmed, ignore.case = FALSE)) { if (!grepl("^[A-Z][a-z]+", b.x_trimmed, ignore.case = FALSE)) {
@ -983,6 +991,9 @@ exec_as.mo <- function(x,
input = a.x_backup, input = a.x_backup,
fullname = microorganismsDT[mo == found[1L], fullname][[1]], fullname = microorganismsDT[mo == found[1L], fullname][[1]],
mo = found[1L])) mo = found[1L]))
if (initial_search == TRUE) {
set_mo_history(a.x_backup, get_mo_code(x, property), 2, force = force_mo_history)
}
return(x) return(x)
} }
} }
@ -1000,6 +1011,9 @@ exec_as.mo <- function(x,
input = a.x_backup, input = a.x_backup,
fullname = microorganismsDT[mo == found_result[1L], fullname][[1]], fullname = microorganismsDT[mo == found_result[1L], fullname][[1]],
mo = found_result[1L])) mo = found_result[1L]))
if (initial_search == TRUE) {
set_mo_history(a.x_backup, get_mo_code(found[1L], property), 2, force = force_mo_history)
}
return(found[1L]) return(found[1L])
} }
@ -1018,6 +1032,33 @@ exec_as.mo <- function(x,
input = a.x_backup, input = a.x_backup,
fullname = microorganismsDT[mo == found_result[1L], fullname][[1]], fullname = microorganismsDT[mo == found_result[1L], fullname][[1]],
mo = found_result[1L])) mo = found_result[1L]))
if (initial_search == TRUE) {
set_mo_history(a.x_backup, get_mo_code(found[1L], property), 2, force = force_mo_history)
}
return(found[1L])
}
}
}
}
# (6) try to strip off one element from start and check the remains (only allow 2-part name outcome) ----
x_strip <- a.x_backup %>% strsplit(" ") %>% unlist()
if (length(x_strip) > 1 & nchar(g.x_backup_without_spp) >= 6) {
for (i in 2:(length(x_strip))) {
x_strip_collapsed <- paste(x_strip[i:length(x_strip)], collapse = " ")
found <- suppressMessages(suppressWarnings(exec_as.mo(x_strip_collapsed, initial_search = FALSE, allow_uncertain = FALSE)))
if (!empty_result(found)) {
found_result <- found
found <- microorganismsDT[mo == found_result[1L], ..property][[1]]
# uncertainty level 2 only if the fullname contains a space (otherwise it will be found with lvl 3)
if (microorganismsDT[mo == found_result[1L], fullname][[1]] %like% " ") {
uncertainties <<- rbind(uncertainties,
data.frame(uncertainty = 2,
input = a.x_backup,
fullname = microorganismsDT[mo == found_result[1L], fullname][[1]],
mo = found_result[1L]))
if (initial_search == TRUE) {
set_mo_history(a.x_backup, get_mo_code(found[1L], property), 2, force = force_mo_history)
}
return(found[1L]) return(found[1L])
} }
} }
@ -1025,8 +1066,8 @@ exec_as.mo <- function(x,
} }
} }
if (allow_uncertain >= 3) { if (uncertainty_level >= 3) {
# (6) try to strip off one element from start and check the remains ---- # (7) try to strip off one element from start and check the remains ----
x_strip <- a.x_backup %>% strsplit(" ") %>% unlist() x_strip <- a.x_backup %>% strsplit(" ") %>% unlist()
if (length(x_strip) > 1 & nchar(g.x_backup_without_spp) >= 6) { if (length(x_strip) > 1 & nchar(g.x_backup_without_spp) >= 6) {
for (i in 2:(length(x_strip))) { for (i in 2:(length(x_strip))) {
@ -1040,12 +1081,15 @@ exec_as.mo <- function(x,
input = a.x_backup, input = a.x_backup,
fullname = microorganismsDT[mo == found_result[1L], fullname][[1]], fullname = microorganismsDT[mo == found_result[1L], fullname][[1]],
mo = found_result[1L])) mo = found_result[1L]))
if (initial_search == TRUE) {
set_mo_history(a.x_backup, get_mo_code(found[1L], property), 3, force = force_mo_history)
}
return(found[1L]) return(found[1L])
} }
} }
} }
# (7) part of a name (very unlikely match) ---- # (8) part of a name (very unlikely match) ----
found <- microorganismsDT[fullname %like% f.x_withspaces_end_only] found <- microorganismsDT[fullname %like% f.x_withspaces_end_only]
if (nrow(found) > 0) { if (nrow(found) > 0) {
found_result <- found[["mo"]] found_result <- found[["mo"]]
@ -1056,6 +1100,9 @@ exec_as.mo <- function(x,
input = a.x_backup, input = a.x_backup,
fullname = microorganismsDT[mo == found_result[1L], fullname][[1]], fullname = microorganismsDT[mo == found_result[1L], fullname][[1]],
mo = found_result[1L])) mo = found_result[1L]))
if (initial_search == TRUE) {
set_mo_history(a.x_backup, get_mo_code(found[1L], property), 3, force = force_mo_history)
}
return(found[1L]) return(found[1L])
} }
} }
@ -1071,7 +1118,7 @@ exec_as.mo <- function(x,
x_withspaces_end_only[i], x_withspaces_end_only[i],
x_backup_without_spp[i]) x_backup_without_spp[i])
if (!empty_result(x[i])) { if (!empty_result(x[i])) {
# no set_mo_history here; these are uncertain # no set_mo_history: is already set in uncertain_fn()
next next
} }
@ -1079,7 +1126,7 @@ exec_as.mo <- function(x,
x[i] <- microorganismsDT[mo == "UNKNOWN", ..property][[1]] x[i] <- microorganismsDT[mo == "UNKNOWN", ..property][[1]]
if (initial_search == TRUE) { if (initial_search == TRUE) {
failures <- c(failures, x_backup[i]) failures <- c(failures, x_backup[i])
set_mo_history(x_backup[i], get_mo_code(x[i], property), force = force_mo_history) set_mo_history(x_backup[i], get_mo_code(x[i], property), 0, force = force_mo_history)
} }
} }
} }
@ -1127,8 +1174,8 @@ exec_as.mo <- function(x,
MOs_staph <- microorganismsDT[genus == "Staphylococcus"] MOs_staph <- microorganismsDT[genus == "Staphylococcus"]
setkey(MOs_staph, species) setkey(MOs_staph, species)
CoNS <- MOs_staph[species %in% c("arlettae", "auricularis", "capitis", CoNS <- MOs_staph[species %in% c("arlettae", "auricularis", "capitis",
"caprae", "carnosus", "cohnii", "condimenti", "caprae", "carnosus", "chromogenes", "cohnii", "condimenti",
"devriesei", "epidermidis", "equorum", "devriesei", "epidermidis", "equorum", "felis",
"fleurettii", "gallinarum", "haemolyticus", "fleurettii", "gallinarum", "haemolyticus",
"hominis", "jettensis", "kloosii", "lentus", "hominis", "jettensis", "kloosii", "lentus",
"lugdunensis", "massiliensis", "microti", "lugdunensis", "massiliensis", "microti",
@ -1136,16 +1183,31 @@ exec_as.mo <- function(x,
"pettenkoferi", "piscifermentans", "rostri", "pettenkoferi", "piscifermentans", "rostri",
"saccharolyticus", "saprophyticus", "sciuri", "saccharolyticus", "saprophyticus", "sciuri",
"stepanovicii", "simulans", "succinus", "stepanovicii", "simulans", "succinus",
"vitulinus", "warneri", "xylosus"), ..property][[1]] "vitulinus", "warneri", "xylosus")
CoPS <- MOs_staph[species %in% c("simiae", "agnetis", "chromogenes", | (species == "schleiferi" & subspecies %in% c("schleiferi", "")), ..property][[1]]
"delphini", "felis", "lutrae", CoPS <- MOs_staph[species %in% c("simiae", "agnetis",
"delphini", "lutrae",
"hyicus", "intermedius", "hyicus", "intermedius",
"pseudintermedius", "pseudointermedius", "pseudintermedius", "pseudointermedius",
"schleiferi"), ..property][[1]] "schweitzeri", "argenteus")
| (species == "schleiferi" & subspecies == "coagulans"), ..property][[1]]
# warn when species found that are not in Becker (2014, PMID 25278577) and Becker (2019, PMID 30872103)
post_Becker <- c("argensis", "caeli", "cornubiensis", "edaphicus")
if (any(x %in% MOs_staph[species %in% post_Becker, ..property][[1]])) {
warning("Becker ", italic("et al."), " (2014) does not contain species named after their publication: ",
italic(paste("S.",
sort(mo_species(unique(x[x %in% MOs_staph[species %in% post_Becker, ..property][[1]]]))),
collapse = ", ")),
call. = FALSE,
immediate. = TRUE)
}
x[x %in% CoNS] <- microorganismsDT[mo == 'B_STPHY_CNS', ..property][[1]][1L] x[x %in% CoNS] <- microorganismsDT[mo == 'B_STPHY_CNS', ..property][[1]][1L]
x[x %in% CoPS] <- microorganismsDT[mo == 'B_STPHY_CPS', ..property][[1]][1L] x[x %in% CoPS] <- microorganismsDT[mo == 'B_STPHY_CPS', ..property][[1]][1L]
if (Becker == "all") { if (Becker == "all") {
x[x == microorganismsDT[mo == 'B_STPHY_AUR', ..property][[1]][1L]] <- microorganismsDT[mo == 'B_STPHY_CPS', ..property][[1]][1L] x[x %in% microorganismsDT[mo %like% '^B_STPHY_AUR', ..property][[1]]] <- microorganismsDT[mo == 'B_STPHY_CPS', ..property][[1]][1L]
} }
} }
@ -1305,7 +1367,7 @@ mo_uncertainties <- function() {
} }
#' @exportMethod print.mo_uncertainties #' @exportMethod print.mo_uncertainties
#' @importFrom crayon green yellow red bgGreen bgYellow bgRed #' @importFrom crayon green yellow red white bgGreen bgYellow bgRed
#' @export #' @export
#' @noRd #' @noRd
print.mo_uncertainties <- function(x, ...) { print.mo_uncertainties <- function(x, ...) {
@ -1321,16 +1383,16 @@ print.mo_uncertainties <- function(x, ...) {
for (i in 1:nrow(x)) { for (i in 1:nrow(x)) {
if (x[i, "uncertainty"] == 1) { if (x[i, "uncertainty"] == 1) {
colour1 <- green colour1 <- green
colour2 <- bgGreen colour2 <- function(...) bgGreen(white(...))
} else if (x[i, "uncertainty"] == 2) { } else if (x[i, "uncertainty"] == 2) {
colour1 <- yellow colour1 <- yellow
colour2 <- bgYellow colour2 <- bgYellow
} else { } else {
colour1 <- red colour1 <- red
colour2 <- bgRed colour2 <- function(...) bgRed(white(...))
} }
msg <- paste(msg, msg <- paste(msg,
paste0("[", colour2(paste0(" ", x[i, "uncertainty"], " ")), '] - "', x[i, "input"], '" -> ', paste0(colour2(paste0(" [", x[i, "uncertainty"], "] ")), ' "', x[i, "input"], '" -> ',
colour1(paste0(italic(x[i, "fullname"]), " (", x[i, "mo"], ")"))), colour1(paste0(italic(x[i, "fullname"]), " (", x[i, "mo"], ")"))),
sep = "\n") sep = "\n")
} }
@ -1373,3 +1435,16 @@ get_mo_code <- function(x, property) {
AMR::microorganisms[base::which(AMR::microorganisms[, property] %in% x),]$mo AMR::microorganisms[base::which(AMR::microorganisms[, property] %in% x),]$mo
} }
} }
translate_allow_uncertain <- function(allow_uncertain) {
if (isTRUE(allow_uncertain)) {
# default to uncertainty level 2
allow_uncertain <- 2
} else {
allow_uncertain <- as.integer(allow_uncertain)
if (!allow_uncertain %in% c(0:3)) {
stop("`allow_uncertain` must be a number between 0 (none) and 3 (all), or TRUE (= 2) or FALSE (= 0).", call. = FALSE)
}
}
allow_uncertain
}

View File

@ -21,10 +21,10 @@
# print successful as.mo coercions to file, not uncertain ones # print successful as.mo coercions to file, not uncertain ones
#' @importFrom dplyr %>% distinct filter #' @importFrom dplyr %>% distinct filter
set_mo_history <- function(x, mo, force = FALSE) { set_mo_history <- function(x, mo, uncertainty_level, force = FALSE) {
file_location <- base::path.expand('~/.Rhistory_mo') file_location <- base::path.expand('~/.Rhistory_mo')
if (base::interactive() | force == TRUE) { if (base::interactive() | force == TRUE) {
mo_hist <- read_mo_history(force = force) mo_hist <- read_mo_history(uncertainty_level = uncertainty_level, force = force)
df <- data.frame(x, mo, stringsAsFactors = FALSE) %>% df <- data.frame(x, mo, stringsAsFactors = FALSE) %>%
distinct(x, .keep_all = TRUE) %>% distinct(x, .keep_all = TRUE) %>%
filter(!is.na(x) & !is.na(mo)) filter(!is.na(x) & !is.na(mo))
@ -35,10 +35,12 @@ set_mo_history <- function(x, mo, force = FALSE) {
mo <- df$mo mo <- df$mo
for (i in 1:length(x)) { for (i in 1:length(x)) {
# save package version too, as both the as.mo() algorithm and the reference data set may change # save package version too, as both the as.mo() algorithm and the reference data set may change
if (NROW(mo_hist[base::which(mo_hist$x == x[i] & mo_hist$package_version == utils::packageVersion("AMR")),]) == 0) { if (NROW(mo_hist[base::which(mo_hist$x == x[i] &
base::write(x = c(x[i], mo[i], base::as.character(utils::packageVersion("AMR"))), mo_hist$uncertainty_level >= uncertainty_level &
mo_hist$package_version == utils::packageVersion("AMR")),]) == 0) {
base::write(x = c(x[i], mo[i], uncertainty_level, base::as.character(utils::packageVersion("AMR"))),
file = file_location, file = file_location,
ncolumns = 3, ncolumns = 4,
append = TRUE, append = TRUE,
sep = "\t") sep = "\t")
} }
@ -47,8 +49,8 @@ set_mo_history <- function(x, mo, force = FALSE) {
return(base::invisible()) return(base::invisible())
} }
get_mo_history <- function(x, force = FALSE) { get_mo_history <- function(x, uncertainty_level, force = FALSE) {
file_read <- read_mo_history(force = force) file_read <- read_mo_history(uncertainty_level = uncertainty_level, force = force)
if (base::is.null(file_read)) { if (base::is.null(file_read)) {
NA NA
} else { } else {
@ -59,30 +61,57 @@ get_mo_history <- function(x, force = FALSE) {
} }
#' @importFrom dplyr %>% filter distinct #' @importFrom dplyr %>% filter distinct
read_mo_history <- function(force = FALSE) { read_mo_history <- function(uncertainty_level = 2, force = FALSE, unfiltered = FALSE) {
file_location <- base::path.expand('~/.Rhistory_mo') file_location <- base::path.expand('~/.Rhistory_mo')
if (!base::file.exists(file_location) | (!base::interactive() & force == FALSE)) { if (!base::file.exists(file_location) | (!base::interactive() & force == FALSE)) {
return(NULL) return(NULL)
} }
uncertainty_level_param <- uncertainty_level
file_read <- utils::read.table(file = file_location, file_read <- utils::read.table(file = file_location,
header = FALSE, header = FALSE,
sep = "\t", sep = "\t",
col.names = c("x", "mo", "package_version"), col.names = c("x", "mo", "uncertainty_level", "package_version"),
stringsAsFactors = FALSE) stringsAsFactors = FALSE)
# Below: filter on current package version. # Below: filter on current package version.
# Even current fullnames may be replaced by new taxonomic names, so new versions of # Even current fullnames may be replaced by new taxonomic names, so new versions of
# the Catalogue of Life must not lead to data corruption. # the Catalogue of Life must not lead to data corruption.
file_read %>%
filter(package_version == utils::packageVersion("AMR")) %>%
distinct(x, mo, .keep_all = TRUE)
}
#' @rdname as.mo if (unfiltered == FALSE) {
#' @export file_read <- file_read %>%
clean_mo_history <- function() { filter(package_version == utils::packageVersion("AMR"),
file_location <- base::path.expand('~/.Rhistory_mo') # only take unknowns if uncertainty_level_param is higher
if (base::file.exists(file_location)) { ((mo == "UNKNOWN" & uncertainty_level_param == uncertainty_level) |
base::unlink(file_location) (mo != "UNKNOWN" & uncertainty_level_param >= uncertainty_level))) %>%
arrange(desc(uncertainty_level)) %>%
distinct(x, mo, .keep_all = TRUE)
}
if (nrow(file_read) == 0) {
NULL
} else {
file_read
}
}
#' @rdname as.mo
#' @importFrom crayon red
#' @importFrom utils menu
#' @export
clean_mo_history <- function(...) {
file_location <- base::path.expand('~/.Rhistory_mo')
if (file.exists(file_location)) {
if (interactive() & !isTRUE(list(...)$force)) {
q <- menu(title = paste("This will remove all",
format(nrow(read_mo_history(999, unfiltered = TRUE)), big.mark = ","),
"previously determined microbial IDs. Are you sure?"),
choices = c("Yes", "No"),
graphics = FALSE)
if (q != 1) {
return(invisible())
}
}
unlink(file_location)
cat(red("File", file_location, "removed."))
} }
} }

View File

@ -446,6 +446,8 @@ mo_translate <- function(x, language) {
# Spanish # Spanish
language == "es" ~ x[x_tobetranslated] %>% language == "es" ~ x[x_tobetranslated] %>%
# not 'negativa'
# https://www.sciencedirect.com/science/article/pii/S0123939215000739
gsub("Coagulase-negative Staphylococcus","Staphylococcus coagulasa negativo", ., fixed = TRUE) %>% gsub("Coagulase-negative Staphylococcus","Staphylococcus coagulasa negativo", ., fixed = TRUE) %>%
gsub("Coagulase-positive Staphylococcus","Staphylococcus coagulasa positivo", ., fixed = TRUE) %>% gsub("Coagulase-positive Staphylococcus","Staphylococcus coagulasa positivo", ., fixed = TRUE) %>%
gsub("Beta-haemolytic Streptococcus", "Streptococcus Beta-hemol\u00edtico", ., fixed = TRUE) %>% gsub("Beta-haemolytic Streptococcus", "Streptococcus Beta-hemol\u00edtico", ., fixed = TRUE) %>%
@ -461,6 +463,8 @@ mo_translate <- function(x, language) {
gsub("unknown species", "especie desconocida", ., fixed = TRUE) %>% gsub("unknown species", "especie desconocida", ., fixed = TRUE) %>%
gsub("unknown subspecies", "subespecie desconocida", ., fixed = TRUE) %>% gsub("unknown subspecies", "subespecie desconocida", ., fixed = TRUE) %>%
gsub("unknown rank", "rango desconocido", ., fixed = TRUE) %>% gsub("unknown rank", "rango desconocido", ., fixed = TRUE) %>%
gsub("(CoNS)", "(SCN)", ., fixed = TRUE) %>%
gsub("(CoPS)", "(SCP)", ., fixed = TRUE) %>%
gsub("Gram negative", "Gram negativo", ., fixed = TRUE) %>% gsub("Gram negative", "Gram negativo", ., fixed = TRUE) %>%
gsub("Gram positive", "Gram positivo", ., fixed = TRUE) %>% gsub("Gram positive", "Gram positivo", ., fixed = TRUE) %>%
gsub("Bacteria", "Bacterias", ., fixed = TRUE) %>% gsub("Bacteria", "Bacterias", ., fixed = TRUE) %>%
@ -579,7 +583,12 @@ mo_validate <- function(x, property, ...) {
# check onLoad() in R/zzz.R: data tables are created there. # check onLoad() in R/zzz.R: data tables are created there.
} }
if (!all(x %in% microorganisms[, property]) # try to catch an error when inputting an invalid parameter
# so the call can be set to FALSE
tryCatch(x[1L] %in% AMR::microorganisms[1, property],
error = function(e) stop(e$message, call. = FALSE))
if (!all(x %in% AMR::microorganisms[, property])
| Becker %in% c(TRUE, "all") | Becker %in% c(TRUE, "all")
| Lancefield %in% c(TRUE, "all")) { | Lancefield %in% c(TRUE, "all")) {
exec_as.mo(x, property = property, ...) exec_as.mo(x, property = property, ...)

View File

@ -21,11 +21,11 @@
#' Calculate resistance of isolates #' Calculate resistance of isolates
#' #'
#' @description These functions can be used to calculate the (co-)resistance of microbial isolates (i.e. percentage S, SI, I, IR or R). All functions support quasiquotation with pipes, can be used in \code{dplyr}s \code{\link[dplyr]{summarise}} and support grouped variables, see \emph{Examples}. #' @description These functions can be used to calculate the (co-)resistance of microbial isolates (i.e. percentage of S, SI, I, IR or R). All functions support quasiquotation with pipes, can be used in \code{dplyr}s \code{\link[dplyr]{summarise}} and support grouped variables, see \emph{Examples}.
#' #'
#' \code{portion_R} and \code{portion_IR} can be used to calculate resistance, \code{portion_S} and \code{portion_SI} can be used to calculate susceptibility.\cr #' \code{portion_R} and \code{portion_IR} can be used to calculate resistance, \code{portion_S} and \code{portion_SI} can be used to calculate susceptibility.\cr
#' @param ... 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. #' @param ... 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.
#' @param minimum the minimal amount of available isolates. Any number lower than \code{minimum} will return \code{NA} with a warning. The default number of \code{30} isolates is advised by the Clinical and Laboratory Standards Institute (CLSI) as best practice, see Source. #' @param minimum the minimum allowed number of available (tested) isolates. Any isolate count lower than \code{minimum} will return \code{NA} with a warning. The default number of \code{30} isolates is advised by the Clinical and Laboratory Standards Institute (CLSI) as best practice, see Source.
#' @param as_percent a logical to indicate whether the output must be returned as a hundred fold with \% sign (a character). A value of \code{0.123456} will then be returned as \code{"12.3\%"}. #' @param as_percent a logical to indicate whether the output must be returned as a hundred fold with \% sign (a character). A value of \code{0.123456} will then be returned as \code{"12.3\%"}.
#' @param also_single_tested a logical to indicate whether (in combination therapies) also observations should be included where not all antibiotics were tested, but at least one of the tested antibiotics contains a target interpretation (e.g. S in case of \code{portion_S} and R in case of \code{portion_R}). \strong{This would lead to selection bias in almost all cases.} #' @param also_single_tested a logical to indicate whether (in combination therapies) also observations should be included where not all antibiotics were tested, but at least one of the tested antibiotics contains a target interpretation (e.g. S in case of \code{portion_S} and R in case of \code{portion_R}). \strong{This would lead to selection bias in almost all cases.}
#' @param data a \code{data.frame} containing columns with class \code{rsi} (see \code{\link{as.rsi}}) #' @param data a \code{data.frame} containing columns with class \code{rsi} (see \code{\link{as.rsi}})
@ -39,19 +39,21 @@
#' #'
#' The old \code{\link{rsi}} function is still available for backwards compatibility but is deprecated. #' The old \code{\link{rsi}} function is still available for backwards compatibility but is deprecated.
#' \if{html}{ #' \if{html}{
# (created with https://www.latex4technics.com/)
#' \cr\cr #' \cr\cr
#' To calculate the probability (\emph{p}) of susceptibility of one antibiotic, we use this formula: #' To calculate the probability (\emph{p}) of susceptibility of one antibiotic, we use this formula:
#' \out{<div style="text-align: center">}\figure{mono_therapy.png}\out{</div>} #' \out{<div style="text-align: center;">}\figure{combi_therapy_2.png}\out{</div>}
#' To calculate the probability (\emph{p}) of susceptibility of more antibiotics (i.e. combination therapy), we need to check whether one of them has a susceptible result (as numerator) and count all cases where all antibiotics were tested (as denominator). \cr #' To calculate the probability (\emph{p}) of susceptibility of more antibiotics (i.e. combination therapy), we need to check whether one of them has a susceptible result (as numerator) and count all cases where all antibiotics were tested (as denominator). \cr
#' \cr #' \cr
#' For two antibiotics: #' For two antibiotics:
#' \out{<div style="text-align: center">}\figure{combi_therapy_2.png}\out{</div>} #' \out{<div style="text-align: center;">}\figure{combi_therapy_2.png}\out{</div>}
#' \cr #' \cr
#' For three antibiotics: #' For three antibiotics:
#' \out{<div style="text-align: center">}\figure{combi_therapy_3.png}\out{</div>} #' \out{<div style="text-align: center;">}\figure{combi_therapy_2.png}\out{</div>}
#' \cr #' \cr
#' And so on. #' And so on.
#' } #' }
#'
#' @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/}. #' @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/}.
#' #'
#' Wickham H. \strong{Tidy Data.} The Journal of Statistical Software, vol. 59, 2014. \url{http://vita.had.co.nz/papers/tidy-data.html} #' Wickham H. \strong{Tidy Data.} The Journal of Statistical Software, vol. 59, 2014. \url{http://vita.had.co.nz/papers/tidy-data.html}
@ -92,8 +94,9 @@
#' summarise(R = portion_R(cipr, as_percent = TRUE), #' summarise(R = portion_R(cipr, as_percent = TRUE),
#' I = portion_I(cipr, as_percent = TRUE), #' I = portion_I(cipr, as_percent = TRUE),
#' S = portion_S(cipr, as_percent = TRUE), #' S = portion_S(cipr, as_percent = TRUE),
#' n = n_rsi(cipr), # works like n_distinct in dplyr #' n1 = count_all(cipr), # the actual total; sum of all three
#' total = n()) # NOT the amount of tested isolates! #' n2 = n_rsi(cipr), # same - analogous to n_distinct
#' total = n()) # NOT the number of tested isolates!
#' #'
#' # Calculate co-resistance between amoxicillin/clav acid and gentamicin, #' # Calculate co-resistance between amoxicillin/clav acid and gentamicin,
#' # so we can see that combination therapy does a lot more than mono therapy: #' # so we can see that combination therapy does a lot more than mono therapy:

Binary file not shown.

View File

@ -78,7 +78,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a> <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.5.0.9024</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.5.0.9025</span>
</span> </span>
</div> </div>

View File

@ -40,7 +40,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <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.5.0.9023</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.5.0.9025</span>
</span> </span>
</div> </div>
@ -192,7 +192,7 @@
<h1>How to conduct AMR analysis</h1> <h1>How to conduct AMR analysis</h1>
<h4 class="author">Matthijs S. Berends</h4> <h4 class="author">Matthijs S. Berends</h4>
<h4 class="date">15 March 2019</h4> <h4 class="date">26 March 2019</h4>
<div class="hidden name"><code>AMR.Rmd</code></div> <div class="hidden name"><code>AMR.Rmd</code></div>
@ -201,7 +201,7 @@
<p><strong>Note:</strong> values on this page will change with every website update since they are based on randomly created values and the page was written in <a href="https://rmarkdown.rstudio.com/">RMarkdown</a>. However, the methodology remains unchanged. This page was generated on 15 March 2019.</p> <p><strong>Note:</strong> values on this page will change with every website update since they are based on randomly created values and the page was written in <a href="https://rmarkdown.rstudio.com/">RMarkdown</a>. However, the methodology remains unchanged. This page was generated on 26 March 2019.</p>
<div id="introduction" class="section level1"> <div id="introduction" class="section level1">
<h1 class="hasAnchor"> <h1 class="hasAnchor">
<a href="#introduction" class="anchor"></a>Introduction</h1> <a href="#introduction" class="anchor"></a>Introduction</h1>
@ -217,21 +217,21 @@
</tr></thead> </tr></thead>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">2019-03-15</td> <td align="center">2019-03-26</td>
<td align="center">abcd</td> <td align="center">abcd</td>
<td align="center">Escherichia coli</td> <td align="center">Escherichia coli</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">2019-03-15</td> <td align="center">2019-03-26</td>
<td align="center">abcd</td> <td align="center">abcd</td>
<td align="center">Escherichia coli</td> <td align="center">Escherichia coli</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td> <td align="center">R</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">2019-03-15</td> <td align="center">2019-03-26</td>
<td align="center">efgh</td> <td align="center">efgh</td>
<td align="center">Escherichia coli</td> <td align="center">Escherichia coli</td>
<td align="center">R</td> <td align="center">R</td>
@ -327,54 +327,32 @@
</tr></thead> </tr></thead>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">2011-03-23</td> <td align="center">2014-08-13</td>
<td align="center">H4</td> <td align="center">C5</td>
<td align="center">Hospital B</td> <td align="center">Hospital C</td>
<td align="center">Escherichia coli</td> <td align="center">Escherichia coli</td>
<td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">M</td> <td align="center">M</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">2016-02-07</td> <td align="center">2017-11-08</td>
<td align="center">A10</td> <td align="center">R4</td>
<td align="center">Hospital B</td> <td align="center">Hospital A</td>
<td align="center">Escherichia coli</td> <td align="center">Escherichia coli</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">I</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">M</td>
</tr>
<tr class="odd">
<td align="center">2017-05-30</td>
<td align="center">Q9</td>
<td align="center">Hospital D</td>
<td align="center">Escherichia coli</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
</tr>
<tr class="even">
<td align="center">2016-09-19</td>
<td align="center">U5</td>
<td align="center">Hospital B</td>
<td align="center">Escherichia coli</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">F</td> <td align="center">F</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">2016-03-20</td> <td align="center">2015-01-27</td>
<td align="center">X10</td> <td align="center">U9</td>
<td align="center">Hospital D</td> <td align="center">Hospital D</td>
<td align="center">Streptococcus pneumoniae</td> <td align="center">Klebsiella pneumoniae</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
@ -382,9 +360,31 @@
<td align="center">F</td> <td align="center">F</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">2012-07-29</td> <td align="center">2010-09-17</td>
<td align="center">D10</td> <td align="center">R7</td>
<td align="center">Hospital D</td> <td align="center">Hospital A</td>
<td align="center">Escherichia coli</td>
<td align="center">R</td>
<td align="center">I</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">F</td>
</tr>
<tr class="odd">
<td align="center">2017-04-07</td>
<td align="center">Z10</td>
<td align="center">Hospital B</td>
<td align="center">Staphylococcus aureus</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">F</td>
</tr>
<tr class="even">
<td align="center">2015-08-27</td>
<td align="center">C7</td>
<td align="center">Hospital A</td>
<td align="center">Escherichia coli</td> <td align="center">Escherichia coli</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
@ -411,8 +411,8 @@
#&gt; #&gt;
#&gt; Item Count Percent Cum. Count Cum. Percent #&gt; Item Count Percent Cum. Count Cum. Percent
#&gt; --- ----- ------- -------- ----------- ------------- #&gt; --- ----- ------- -------- ----------- -------------
#&gt; 1 M 10,422 52.1% 10,422 52.1% #&gt; 1 M 10,435 52.2% 10,435 52.2%
#&gt; 2 F 9,578 47.9% 20,000 100.0%</code></pre> #&gt; 2 F 9,565 47.8% 20,000 100.0%</code></pre>
<p>So, we can draw at least two conclusions immediately. From a data scientist perspective, the data looks clean: only values <code>M</code> and <code>F</code>. From a researcher perspective: there are slightly more men. Nothing we didnt already know.</p> <p>So, we can draw at least two conclusions immediately. From a data scientist perspective, the data looks clean: only values <code>M</code> and <code>F</code>. From a researcher perspective: there are slightly more men. Nothing we didnt already know.</p>
<p>The data is already quite clean, but we still need to transform some variables. The <code>bacteria</code> column now consists of text, and we want to add more variables based on microbial IDs later on. So, we will transform this column to valid IDs. The <code><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate()</a></code> function of the <code>dplyr</code> package makes this really easy:</p> <p>The data is already quite clean, but we still need to transform some variables. The <code>bacteria</code> column now consists of text, and we want to add more variables based on microbial IDs later on. So, we will transform this column to valid IDs. The <code><a href="https://dplyr.tidyverse.org/reference/mutate.html">mutate()</a></code> function of the <code>dplyr</code> package makes this really easy:</p>
<div class="sourceCode" id="cb12"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb12-1" title="1">data &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span></a> <div class="sourceCode" id="cb12"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb12-1" title="1">data &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span></a>
@ -443,10 +443,10 @@
<a class="sourceLine" id="cb14-19" title="19"><span class="co">#&gt; Kingella kingae (no changes)</span></a> <a class="sourceLine" id="cb14-19" title="19"><span class="co">#&gt; Kingella kingae (no changes)</span></a>
<a class="sourceLine" id="cb14-20" title="20"><span class="co">#&gt; </span></a> <a class="sourceLine" id="cb14-20" title="20"><span class="co">#&gt; </span></a>
<a class="sourceLine" id="cb14-21" title="21"><span class="co">#&gt; EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes (v3.1, 2016)</span></a> <a class="sourceLine" id="cb14-21" title="21"><span class="co">#&gt; EUCAST Expert Rules, Intrinsic Resistance and Exceptional Phenotypes (v3.1, 2016)</span></a>
<a class="sourceLine" id="cb14-22" title="22"><span class="co">#&gt; Table 1: Intrinsic resistance in Enterobacteriaceae (1315 changes)</span></a> <a class="sourceLine" id="cb14-22" title="22"><span class="co">#&gt; Table 1: Intrinsic resistance in Enterobacteriaceae (1262 changes)</span></a>
<a class="sourceLine" id="cb14-23" title="23"><span class="co">#&gt; Table 2: Intrinsic resistance in non-fermentative Gram-negative bacteria (no changes)</span></a> <a class="sourceLine" id="cb14-23" title="23"><span class="co">#&gt; Table 2: Intrinsic resistance in non-fermentative Gram-negative bacteria (no changes)</span></a>
<a class="sourceLine" id="cb14-24" title="24"><span class="co">#&gt; Table 3: Intrinsic resistance in other Gram-negative bacteria (no changes)</span></a> <a class="sourceLine" id="cb14-24" title="24"><span class="co">#&gt; Table 3: Intrinsic resistance in other Gram-negative bacteria (no changes)</span></a>
<a class="sourceLine" id="cb14-25" title="25"><span class="co">#&gt; Table 4: Intrinsic resistance in Gram-positive bacteria (2799 changes)</span></a> <a class="sourceLine" id="cb14-25" title="25"><span class="co">#&gt; Table 4: Intrinsic resistance in Gram-positive bacteria (2756 changes)</span></a>
<a class="sourceLine" id="cb14-26" title="26"><span class="co">#&gt; Table 8: Interpretive rules for B-lactam agents and Gram-positive cocci (no changes)</span></a> <a class="sourceLine" id="cb14-26" title="26"><span class="co">#&gt; Table 8: Interpretive rules for B-lactam agents and Gram-positive cocci (no changes)</span></a>
<a class="sourceLine" id="cb14-27" title="27"><span class="co">#&gt; Table 9: Interpretive rules for B-lactam agents and Gram-negative rods (no changes)</span></a> <a class="sourceLine" id="cb14-27" title="27"><span class="co">#&gt; Table 9: Interpretive rules for B-lactam agents and Gram-negative rods (no changes)</span></a>
<a class="sourceLine" id="cb14-28" title="28"><span class="co">#&gt; Table 10: Interpretive rules for B-lactam agents and other Gram-negative bacteria (no changes)</span></a> <a class="sourceLine" id="cb14-28" title="28"><span class="co">#&gt; Table 10: Interpretive rules for B-lactam agents and other Gram-negative bacteria (no changes)</span></a>
@ -462,9 +462,9 @@
<a class="sourceLine" id="cb14-38" title="38"><span class="co">#&gt; Non-EUCAST: piperacillin/tazobactam = S where piperacillin = S (no changes)</span></a> <a class="sourceLine" id="cb14-38" title="38"><span class="co">#&gt; Non-EUCAST: piperacillin/tazobactam = S where piperacillin = S (no changes)</span></a>
<a class="sourceLine" id="cb14-39" title="39"><span class="co">#&gt; Non-EUCAST: trimethoprim/sulfa = S where trimethoprim = S (no changes)</span></a> <a class="sourceLine" id="cb14-39" title="39"><span class="co">#&gt; Non-EUCAST: trimethoprim/sulfa = S where trimethoprim = S (no changes)</span></a>
<a class="sourceLine" id="cb14-40" title="40"><span class="co">#&gt; </span></a> <a class="sourceLine" id="cb14-40" title="40"><span class="co">#&gt; </span></a>
<a class="sourceLine" id="cb14-41" title="41"><span class="co">#&gt; =&gt; EUCAST rules affected 7,488 out of 20,000 rows</span></a> <a class="sourceLine" id="cb14-41" title="41"><span class="co">#&gt; =&gt; EUCAST rules affected 7,403 out of 20,000 rows</span></a>
<a class="sourceLine" id="cb14-42" title="42"><span class="co">#&gt; -&gt; added 0 test results</span></a> <a class="sourceLine" id="cb14-42" title="42"><span class="co">#&gt; -&gt; added 0 test results</span></a>
<a class="sourceLine" id="cb14-43" title="43"><span class="co">#&gt; -&gt; changed 4,114 test results (0 to S; 0 to I; 4,114 to R)</span></a></code></pre></div> <a class="sourceLine" id="cb14-43" title="43"><span class="co">#&gt; -&gt; changed 4,018 test results (0 to S; 0 to I; 4,018 to R)</span></a></code></pre></div>
</div> </div>
<div id="adding-new-variables" class="section level1"> <div id="adding-new-variables" class="section level1">
<h1 class="hasAnchor"> <h1 class="hasAnchor">
@ -489,8 +489,8 @@
<a class="sourceLine" id="cb16-3" title="3"><span class="co">#&gt; </span><span class="al">NOTE</span><span class="co">: Using column `bacteria` as input for `col_mo`.</span></a> <a class="sourceLine" id="cb16-3" title="3"><span class="co">#&gt; </span><span class="al">NOTE</span><span class="co">: Using column `bacteria` as input for `col_mo`.</span></a>
<a class="sourceLine" id="cb16-4" title="4"><span class="co">#&gt; </span><span class="al">NOTE</span><span class="co">: Using column `date` as input for `col_date`.</span></a> <a class="sourceLine" id="cb16-4" title="4"><span class="co">#&gt; </span><span class="al">NOTE</span><span class="co">: Using column `date` as input for `col_date`.</span></a>
<a class="sourceLine" id="cb16-5" title="5"><span class="co">#&gt; </span><span class="al">NOTE</span><span class="co">: Using column `patient_id` as input for `col_patient_id`.</span></a> <a class="sourceLine" id="cb16-5" title="5"><span class="co">#&gt; </span><span class="al">NOTE</span><span class="co">: Using column `patient_id` as input for `col_patient_id`.</span></a>
<a class="sourceLine" id="cb16-6" title="6"><span class="co">#&gt; =&gt; Found 5,688 first isolates (28.4% of total)</span></a></code></pre></div> <a class="sourceLine" id="cb16-6" title="6"><span class="co">#&gt; =&gt; Found 5,648 first isolates (28.2% of total)</span></a></code></pre></div>
<p>So only 28.4% is suitable for resistance analysis! We can now filter on it with the <code><a href="https://dplyr.tidyverse.org/reference/filter.html">filter()</a></code> function, also from the <code>dplyr</code> package:</p> <p>So only 28.2% is suitable for resistance analysis! We can now filter on it with the <code><a href="https://dplyr.tidyverse.org/reference/filter.html">filter()</a></code> function, also from the <code>dplyr</code> package:</p>
<div class="sourceCode" id="cb17"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb17-1" title="1">data_1st &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></a> <div class="sourceCode" id="cb17"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb17-1" title="1">data_1st &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb17-2" title="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/filter.html">filter</a></span>(first <span class="op">==</span><span class="st"> </span><span class="ot">TRUE</span>)</a></code></pre></div> <a class="sourceLine" id="cb17-2" title="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/filter.html">filter</a></span>(first <span class="op">==</span><span class="st"> </span><span class="ot">TRUE</span>)</a></code></pre></div>
<p>For future use, the above two syntaxes can be shortened with the <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code> function:</p> <p>For future use, the above two syntaxes can be shortened with the <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code> function:</p>
@ -516,10 +516,10 @@
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">1</td> <td align="center">1</td>
<td align="center">2010-04-01</td> <td align="center">2010-01-29</td>
<td align="center">K1</td> <td align="center">P7</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">R</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
@ -527,101 +527,101 @@
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">2</td> <td align="center">2</td>
<td align="center">2010-04-30</td> <td align="center">2010-05-18</td>
<td align="center">K1</td> <td align="center">P7</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">3</td> <td align="center">3</td>
<td align="center">2010-10-12</td> <td align="center">2010-06-01</td>
<td align="center">K1</td> <td align="center">P7</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">4</td> <td align="center">4</td>
<td align="center">2010-12-05</td> <td align="center">2010-07-21</td>
<td align="center">K1</td> <td align="center">P7</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">I</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">5</td> <td align="center">5</td>
<td align="center">2011-01-19</td> <td align="center">2010-08-20</td>
<td align="center">K1</td> <td align="center">P7</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">6</td> <td align="center">6</td>
<td align="center">2011-04-07</td> <td align="center">2010-12-14</td>
<td align="center">K1</td> <td align="center">P7</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">I</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td align="center">7</td>
<td align="center">2011-06-16</td>
<td align="center">K1</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
</tr> </tr>
<tr class="even"> <tr class="odd">
<td align="center">8</td> <td align="center">7</td>
<td align="center">2011-07-16</td> <td align="center">2011-03-02</td>
<td align="center">K1</td> <td align="center">P7</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">8</td>
<td align="center">2011-03-14</td>
<td align="center">P7</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">9</td> <td align="center">9</td>
<td align="center">2011-08-25</td> <td align="center">2011-05-28</td>
<td align="center">K1</td> <td align="center">P7</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">I</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">10</td> <td align="center">10</td>
<td align="center">2011-09-11</td> <td align="center">2011-08-09</td>
<td align="center">K1</td> <td align="center">P7</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">R</td> <td align="center">I</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">R</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
</tr> </tr>
</tbody> </tbody>
@ -637,7 +637,7 @@
<a class="sourceLine" id="cb19-7" title="7"><span class="co">#&gt; </span><span class="al">NOTE</span><span class="co">: Using column `patient_id` as input for `col_patient_id`.</span></a> <a class="sourceLine" id="cb19-7" title="7"><span class="co">#&gt; </span><span class="al">NOTE</span><span class="co">: Using column `patient_id` as input for `col_patient_id`.</span></a>
<a class="sourceLine" id="cb19-8" title="8"><span class="co">#&gt; </span><span class="al">NOTE</span><span class="co">: Using column `keyab` as input for `col_keyantibiotics`. Use col_keyantibiotics = FALSE to prevent this.</span></a> <a class="sourceLine" id="cb19-8" title="8"><span class="co">#&gt; </span><span class="al">NOTE</span><span class="co">: Using column `keyab` as input for `col_keyantibiotics`. Use col_keyantibiotics = FALSE to prevent this.</span></a>
<a class="sourceLine" id="cb19-9" title="9"><span class="co">#&gt; [Criterion] Inclusion based on key antibiotics, ignoring I.</span></a> <a class="sourceLine" id="cb19-9" title="9"><span class="co">#&gt; [Criterion] Inclusion based on key antibiotics, ignoring I.</span></a>
<a class="sourceLine" id="cb19-10" title="10"><span class="co">#&gt; =&gt; Found 15,948 first weighted isolates (79.7% of total)</span></a></code></pre></div> <a class="sourceLine" id="cb19-10" title="10"><span class="co">#&gt; =&gt; Found 15,891 first weighted isolates (79.5% of total)</span></a></code></pre></div>
<table class="table"> <table class="table">
<thead><tr class="header"> <thead><tr class="header">
<th align="center">isolate</th> <th align="center">isolate</th>
@ -654,10 +654,10 @@
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">1</td> <td align="center">1</td>
<td align="center">2010-04-01</td> <td align="center">2010-01-29</td>
<td align="center">K1</td> <td align="center">P7</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">R</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
@ -666,95 +666,95 @@
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">2</td> <td align="center">2</td>
<td align="center">2010-04-30</td> <td align="center">2010-05-18</td>
<td align="center">K1</td> <td align="center">P7</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
<td align="center">TRUE</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">3</td> <td align="center">3</td>
<td align="center">2010-10-12</td> <td align="center">2010-06-01</td>
<td align="center">K1</td> <td align="center">P7</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
<td align="center">FALSE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">4</td> <td align="center">4</td>
<td align="center">2010-12-05</td> <td align="center">2010-07-21</td>
<td align="center">K1</td> <td align="center">P7</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">I</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">5</td> <td align="center">5</td>
<td align="center">2011-01-19</td> <td align="center">2010-08-20</td>
<td align="center">K1</td> <td align="center">P7</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">6</td>
<td align="center">2011-04-07</td>
<td align="center">K1</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">TRUE</td>
<td align="center">TRUE</td>
</tr>
<tr class="odd">
<td align="center">7</td>
<td align="center">2011-06-16</td>
<td align="center">K1</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">FALSE</td>
</tr>
<tr class="even">
<td align="center">8</td>
<td align="center">2011-07-16</td>
<td align="center">K1</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
<td align="center">FALSE</td>
</tr>
<tr class="even">
<td align="center">6</td>
<td align="center">2010-12-14</td>
<td align="center">P7</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">I</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">FALSE</td>
</tr>
<tr class="odd">
<td align="center">7</td>
<td align="center">2011-03-02</td>
<td align="center">P7</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">TRUE</td>
<td align="center">TRUE</td>
</tr>
<tr class="even">
<td align="center">8</td>
<td align="center">2011-03-14</td>
<td align="center">P7</td>
<td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">FALSE</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">9</td> <td align="center">9</td>
<td align="center">2011-08-25</td> <td align="center">2011-05-28</td>
<td align="center">K1</td> <td align="center">P7</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">I</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
@ -762,23 +762,23 @@
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">10</td> <td align="center">10</td>
<td align="center">2011-09-11</td> <td align="center">2011-08-09</td>
<td align="center">K1</td> <td align="center">P7</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">R</td> <td align="center">I</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">R</td> <td align="center">S</td>
<td align="center">FALSE</td> <td align="center">FALSE</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
</tbody> </tbody>
</table> </table>
<p>Instead of 2, now 7 isolates are flagged. In total, 79.7% of all isolates are marked first weighted - 51.3% more than when using the CLSI guideline. In real life, this novel algorithm will yield 5-10% more isolates than the classic CLSI guideline.</p> <p>Instead of 2, now 8 isolates are flagged. In total, 79.5% of all isolates are marked first weighted - 51.2% more than when using the CLSI guideline. In real life, this novel algorithm will yield 5-10% more isolates than the classic CLSI guideline.</p>
<p>As with <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code>, theres a shortcut for this new algorithm too:</p> <p>As with <code><a href="../reference/first_isolate.html">filter_first_isolate()</a></code>, theres a shortcut for this new algorithm too:</p>
<div class="sourceCode" id="cb20"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb20-1" title="1">data_1st &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></a> <div class="sourceCode" id="cb20"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb20-1" title="1">data_1st &lt;-<span class="st"> </span>data <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb20-2" title="2"><span class="st"> </span><span class="kw"><a href="../reference/first_isolate.html">filter_first_weighted_isolate</a></span>()</a></code></pre></div> <a class="sourceLine" id="cb20-2" title="2"><span class="st"> </span><span class="kw"><a href="../reference/first_isolate.html">filter_first_weighted_isolate</a></span>()</a></code></pre></div>
<p>So we end up with 15,948 isolates for analysis.</p> <p>So we end up with 15,891 isolates for analysis.</p>
<p>We can remove unneeded columns:</p> <p>We can remove unneeded columns:</p>
<div class="sourceCode" id="cb21"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb21-1" title="1">data_1st &lt;-<span class="st"> </span>data_1st <span class="op">%&gt;%</span><span class="st"> </span></a> <div class="sourceCode" id="cb21"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb21-1" title="1">data_1st &lt;-<span class="st"> </span>data_1st <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb21-2" title="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(<span class="op">-</span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(first, keyab))</a></code></pre></div> <a class="sourceLine" id="cb21-2" title="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/select.html">select</a></span>(<span class="op">-</span><span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/c">c</a></span>(first, keyab))</a></code></pre></div>
@ -804,13 +804,13 @@
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td>1</td> <td>1</td>
<td align="center">2011-03-23</td> <td align="center">2014-08-13</td>
<td align="center">H4</td> <td align="center">C5</td>
<td align="center">Hospital B</td> <td align="center">Hospital C</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">R</td>
<td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">M</td> <td align="center">M</td>
<td align="center">Gram negative</td> <td align="center">Gram negative</td>
@ -819,16 +819,16 @@
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td>2</td> <td>4</td>
<td align="center">2016-02-07</td> <td align="center">2010-09-17</td>
<td align="center">A10</td> <td align="center">R7</td>
<td align="center">Hospital B</td> <td align="center">Hospital A</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">R</td>
<td align="center">I</td>
<td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">F</td>
<td align="center">S</td>
<td align="center">S</td>
<td align="center">M</td>
<td align="center">Gram negative</td> <td align="center">Gram negative</td>
<td align="center">Escherichia</td> <td align="center">Escherichia</td>
<td align="center">coli</td> <td align="center">coli</td>
@ -836,41 +836,41 @@
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td>5</td> <td>5</td>
<td align="center">2016-03-20</td> <td align="center">2017-04-07</td>
<td align="center">X10</td> <td align="center">Z10</td>
<td align="center">Hospital D</td> <td align="center">Hospital B</td>
<td align="center">B_STRPT_PNE</td> <td align="center">B_STPHY_AUR</td>
<td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">R</td>
<td align="center">F</td> <td align="center">F</td>
<td align="center">Gram positive</td> <td align="center">Gram positive</td>
<td align="center">Streptococcus</td> <td align="center">Staphylococcus</td>
<td align="center">pneumoniae</td> <td align="center">aureus</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td>7</td> <td>7</td>
<td align="center">2015-08-01</td> <td align="center">2012-04-03</td>
<td align="center">Q4</td> <td align="center">J2</td>
<td align="center">Hospital A</td> <td align="center">Hospital A</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">S</td>
<td align="center">I</td>
<td align="center">S</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">F</td> <td align="center">R</td>
<td align="center">R</td>
<td align="center">S</td>
<td align="center">M</td>
<td align="center">Gram negative</td> <td align="center">Gram negative</td>
<td align="center">Escherichia</td> <td align="center">Escherichia</td>
<td align="center">coli</td> <td align="center">coli</td>
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td>8</td> <td>9</td>
<td align="center">2012-03-10</td> <td align="center">2017-09-09</td>
<td align="center">Z10</td> <td align="center">U3</td>
<td align="center">Hospital C</td> <td align="center">Hospital A</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">R</td> <td align="center">R</td>
<td align="center">S</td> <td align="center">S</td>
@ -883,10 +883,10 @@
<td align="center">TRUE</td> <td align="center">TRUE</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td>11</td> <td>10</td>
<td align="center">2014-10-21</td> <td align="center">2015-12-21</td>
<td align="center">G8</td> <td align="center">E1</td>
<td align="center">Hospital C</td> <td align="center">Hospital B</td>
<td align="center">B_ESCHR_COL</td> <td align="center">B_ESCHR_COL</td>
<td align="center">S</td> <td align="center">S</td>
<td align="center">S</td> <td align="center">S</td>
@ -915,9 +915,9 @@
<div class="sourceCode" id="cb23"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb23-1" title="1"><span class="kw"><a href="../reference/freq.html">freq</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/paste">paste</a></span>(data_1st<span class="op">$</span>genus, data_1st<span class="op">$</span>species))</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"><span class="kw"><a href="../reference/freq.html">freq</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/base/topics/paste">paste</a></span>(data_1st<span class="op">$</span>genus, data_1st<span class="op">$</span>species))</a></code></pre></div>
<p>Or can be used like the <code>dplyr</code> way, which is easier readable:</p> <p>Or can be used like the <code>dplyr</code> way, which is easier readable:</p>
<div class="sourceCode" id="cb24"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb24-1" title="1">data_1st <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(genus, species)</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">data_1st <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/freq.html">freq</a></span>(genus, species)</a></code></pre></div>
<p><strong>Frequency table of <code>genus</code> and <code>species</code> from a <code>data.frame</code> (15,948 x 13)</strong></p> <p><strong>Frequency table of <code>genus</code> and <code>species</code> from a <code>data.frame</code> (15,891 x 13)</strong></p>
<p>Columns: 2<br> <p>Columns: 2<br>
Length: 15,948 (of which NA: 0 = 0.00%)<br> Length: 15,891 (of which NA: 0 = 0.00%)<br>
Unique: 4</p> Unique: 4</p>
<p>Shortest: 16<br> <p>Shortest: 16<br>
Longest: 24</p> Longest: 24</p>
@ -935,32 +935,32 @@ Longest: 24</p>
<td align="left">1</td> <td align="left">1</td>
<td align="left">Escherichia coli</td> <td align="left">Escherichia coli</td>
<td align="right">7,952</td> <td align="right">7,952</td>
<td align="right">49.9%</td> <td align="right">50.0%</td>
<td align="right">7,952</td> <td align="right">7,952</td>
<td align="right">49.9%</td> <td align="right">50.0%</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="left">2</td> <td align="left">2</td>
<td align="left">Staphylococcus aureus</td> <td align="left">Staphylococcus aureus</td>
<td align="right">3,886</td> <td align="right">3,895</td>
<td align="right">24.4%</td> <td align="right">24.5%</td>
<td align="right">11,838</td> <td align="right">11,847</td>
<td align="right">74.2%</td> <td align="right">74.6%</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="left">3</td> <td align="left">3</td>
<td align="left">Streptococcus pneumoniae</td> <td align="left">Streptococcus pneumoniae</td>
<td align="right">2,509</td> <td align="right">2,502</td>
<td align="right">15.7%</td> <td align="right">15.7%</td>
<td align="right">14,347</td> <td align="right">14,349</td>
<td align="right">90.0%</td> <td align="right">90.3%</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="left">4</td> <td align="left">4</td>
<td align="left">Klebsiella pneumoniae</td> <td align="left">Klebsiella pneumoniae</td>
<td align="right">1,601</td> <td align="right">1,542</td>
<td align="right">10.0%</td> <td align="right">9.7%</td>
<td align="right">15,948</td> <td align="right">15,891</td>
<td align="right">100.0%</td> <td align="right">100.0%</td>
</tr> </tr>
</tbody> </tbody>
@ -969,9 +969,9 @@ Longest: 24</p>
<div id="resistance-percentages" class="section level2"> <div id="resistance-percentages" class="section level2">
<h2 class="hasAnchor"> <h2 class="hasAnchor">
<a href="#resistance-percentages" class="anchor"></a>Resistance percentages</h2> <a href="#resistance-percentages" class="anchor"></a>Resistance percentages</h2>
<p>The functions <code><a href="../reference/portion.html">portion_R()</a></code>, <code>portion_RI()</code>, <code><a href="../reference/portion.html">portion_I()</a></code>, <code>portion_IS()</code> and <code><a href="../reference/portion.html">portion_S()</a></code> can be used to determine the portion of a specific antimicrobial outcome. They can be used on their own:</p> <p>The functions <code><a href="../reference/portion.html">portion_S()</a></code>, <code><a href="../reference/portion.html">portion_SI()</a></code>, <code><a href="../reference/portion.html">portion_I()</a></code>, <code><a href="../reference/portion.html">portion_IR()</a></code> and <code><a href="../reference/portion.html">portion_R()</a></code> can be used to determine the portion of a specific antimicrobial outcome. They can be used on their own:</p>
<div class="sourceCode" id="cb25"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb25-1" title="1">data_1st <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_IR</a></span>(amox)</a> <div class="sourceCode" id="cb25"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb25-1" title="1">data_1st <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_IR</a></span>(amox)</a>
<a class="sourceLine" id="cb25-2" title="2"><span class="co">#&gt; [1] 0.4812516</span></a></code></pre></div> <a class="sourceLine" id="cb25-2" title="2"><span class="co">#&gt; [1] 0.4711472</span></a></code></pre></div>
<p>Or can be used in conjuction with <code><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by()</a></code> and <code><a href="https://dplyr.tidyverse.org/reference/summarise.html">summarise()</a></code>, both from the <code>dplyr</code> package:</p> <p>Or can be used in conjuction with <code><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by()</a></code> and <code><a href="https://dplyr.tidyverse.org/reference/summarise.html">summarise()</a></code>, both from the <code>dplyr</code> package:</p>
<div class="sourceCode" id="cb26"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb26-1" title="1">data_1st <span class="op">%&gt;%</span><span class="st"> </span></a> <div class="sourceCode" id="cb26"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb26-1" title="1">data_1st <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb26-2" title="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(hospital) <span class="op">%&gt;%</span><span class="st"> </span></a> <a class="sourceLine" id="cb26-2" title="2"><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(hospital) <span class="op">%&gt;%</span><span class="st"> </span></a>
@ -984,19 +984,19 @@ Longest: 24</p>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">Hospital A</td> <td align="center">Hospital A</td>
<td align="center">0.4801481</td> <td align="center">0.4674370</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">Hospital B</td> <td align="center">Hospital B</td>
<td align="center">0.4811895</td> <td align="center">0.4698925</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">Hospital C</td> <td align="center">Hospital C</td>
<td align="center">0.4707087</td> <td align="center">0.4813574</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">Hospital D</td> <td align="center">Hospital D</td>
<td align="center">0.4915144</td> <td align="center">0.4712389</td>
</tr> </tr>
</tbody> </tbody>
</table> </table>
@ -1014,23 +1014,23 @@ Longest: 24</p>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">Hospital A</td> <td align="center">Hospital A</td>
<td align="center">0.4801481</td> <td align="center">0.4674370</td>
<td align="center">4861</td> <td align="center">4760</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">Hospital B</td> <td align="center">Hospital B</td>
<td align="center">0.4811895</td> <td align="center">0.4698925</td>
<td align="center">5582</td> <td align="center">5580</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">Hospital C</td> <td align="center">Hospital C</td>
<td align="center">0.4707087</td> <td align="center">0.4813574</td>
<td align="center">2441</td> <td align="center">2387</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">Hospital D</td> <td align="center">Hospital D</td>
<td align="center">0.4915144</td> <td align="center">0.4712389</td>
<td align="center">3064</td> <td align="center">3164</td>
</tr> </tr>
</tbody> </tbody>
</table> </table>
@ -1050,27 +1050,27 @@ Longest: 24</p>
<tbody> <tbody>
<tr class="odd"> <tr class="odd">
<td align="center">Escherichia</td> <td align="center">Escherichia</td>
<td align="center">0.7282445</td> <td align="center">0.7272384</td>
<td align="center">0.9031690</td> <td align="center">0.9034205</td>
<td align="center">0.9756036</td> <td align="center">0.9763581</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">Klebsiella</td> <td align="center">Klebsiella</td>
<td align="center">0.7270456</td> <td align="center">0.7457847</td>
<td align="center">0.9000625</td> <td align="center">0.9014267</td>
<td align="center">0.9787633</td> <td align="center">0.9760052</td>
</tr> </tr>
<tr class="odd"> <tr class="odd">
<td align="center">Staphylococcus</td> <td align="center">Staphylococcus</td>
<td align="center">0.7220793</td> <td align="center">0.7245186</td>
<td align="center">0.9184251</td> <td align="center">0.9181001</td>
<td align="center">0.9796706</td> <td align="center">0.9756098</td>
</tr> </tr>
<tr class="even"> <tr class="even">
<td align="center">Streptococcus</td> <td align="center">Streptococcus</td>
<td align="center">0.7182144</td> <td align="center">0.7234213</td>
<td align="center">0.0000000</td> <td align="center">0.0000000</td>
<td align="center">0.7182144</td> <td align="center">0.7234213</td>
</tr> </tr>
</tbody> </tbody>
</table> </table>
@ -1081,36 +1081,36 @@ Longest: 24</p>
<a class="sourceLine" id="cb29-4" title="4"> <span class="st">"2. Gentamicin"</span> =<span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(gent),</a> <a class="sourceLine" id="cb29-4" title="4"> <span class="st">"2. Gentamicin"</span> =<span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(gent),</a>
<a class="sourceLine" id="cb29-5" title="5"> <span class="st">"3. Amoxi/clav + gent"</span> =<span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl, gent)) <span class="op">%&gt;%</span><span class="st"> </span></a> <a class="sourceLine" id="cb29-5" title="5"> <span class="st">"3. Amoxi/clav + gent"</span> =<span class="st"> </span><span class="kw"><a href="../reference/portion.html">portion_S</a></span>(amcl, gent)) <span class="op">%&gt;%</span><span class="st"> </span></a>
<a class="sourceLine" id="cb29-6" title="6"><span class="st"> </span>tidyr<span class="op">::</span><span class="kw"><a href="https://tidyr.tidyverse.org/reference/gather.html">gather</a></span>(<span class="st">"Antibiotic"</span>, <span class="st">"S"</span>, <span class="op">-</span>genus) <span class="op">%&gt;%</span></a> <a class="sourceLine" id="cb29-6" title="6"><span class="st"> </span>tidyr<span class="op">::</span><span class="kw"><a href="https://tidyr.tidyverse.org/reference/gather.html">gather</a></span>(<span class="st">"Antibiotic"</span>, <span class="st">"S"</span>, <span class="op">-</span>genus) <span class="op">%&gt;%</span></a>
<a class="sourceLine" id="cb29-7" title="7"><span class="st"> </span><span class="kw"><a href="https://ggplot2.tidyverse.org/reference/ggplot.html">ggplot</a></span>(<span class="kw"><a href="https://ggplot2.tidyverse.org/reference/aes.html">aes</a></span>(<span class="dt">x =</span> genus,</a> <a class="sourceLine" id="cb29-7" title="7"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/ggplot2/topics/ggplot">ggplot</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/ggplot2/topics/aes">aes</a></span>(<span class="dt">x =</span> genus,</a>
<a class="sourceLine" id="cb29-8" title="8"> <span class="dt">y =</span> S,</a> <a class="sourceLine" id="cb29-8" title="8"> <span class="dt">y =</span> S,</a>
<a class="sourceLine" id="cb29-9" title="9"> <span class="dt">fill =</span> Antibiotic)) <span class="op">+</span></a> <a class="sourceLine" id="cb29-9" title="9"> <span class="dt">fill =</span> Antibiotic)) <span class="op">+</span></a>
<a class="sourceLine" id="cb29-10" title="10"><span class="st"> </span><span class="kw"><a href="https://ggplot2.tidyverse.org/reference/geom_bar.html">geom_col</a></span>(<span class="dt">position =</span> <span class="st">"dodge2"</span>)</a></code></pre></div> <a class="sourceLine" id="cb29-10" title="10"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/ggplot2/topics/geom_bar">geom_col</a></span>(<span class="dt">position =</span> <span class="st">"dodge2"</span>)</a></code></pre></div>
<p><img src="AMR_files/figure-html/plot%201-1.png" width="720"></p> <p><img src="AMR_files/figure-html/plot%201-1.png" width="720"></p>
</div> </div>
<div id="plots" class="section level2"> <div id="plots" class="section level2">
<h2 class="hasAnchor"> <h2 class="hasAnchor">
<a href="#plots" class="anchor"></a>Plots</h2> <a href="#plots" class="anchor"></a>Plots</h2>
<p>To show results in plots, most R users would nowadays use the <code>ggplot2</code> package. This package lets you create plots in layers. You can read more about it <a href="https://ggplot2.tidyverse.org/">on their website</a>. A quick example would look like these syntaxes:</p> <p>To show results in plots, most R users would nowadays use the <code>ggplot2</code> package. This package lets you create plots in layers. You can read more about it <a href="https://ggplot2.tidyverse.org/">on their website</a>. A quick example would look like these syntaxes:</p>
<div class="sourceCode" id="cb30"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb30-1" title="1"><span class="kw"><a href="https://ggplot2.tidyverse.org/reference/ggplot.html">ggplot</a></span>(<span class="dt">data =</span> a_data_set,</a> <div class="sourceCode" id="cb30"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb30-1" title="1"><span class="kw"><a href="https://www.rdocumentation.org/packages/ggplot2/topics/ggplot">ggplot</a></span>(<span class="dt">data =</span> a_data_set,</a>
<a class="sourceLine" id="cb30-2" title="2"> <span class="dt">mapping =</span> <span class="kw"><a href="https://ggplot2.tidyverse.org/reference/aes.html">aes</a></span>(<span class="dt">x =</span> year,</a> <a class="sourceLine" id="cb30-2" title="2"> <span class="dt">mapping =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/ggplot2/topics/aes">aes</a></span>(<span class="dt">x =</span> year,</a>
<a class="sourceLine" id="cb30-3" title="3"> <span class="dt">y =</span> value)) <span class="op">+</span></a> <a class="sourceLine" id="cb30-3" title="3"> <span class="dt">y =</span> value)) <span class="op">+</span></a>
<a class="sourceLine" id="cb30-4" title="4"><span class="st"> </span><span class="kw"><a href="https://ggplot2.tidyverse.org/reference/geom_bar.html">geom_col</a></span>() <span class="op">+</span></a> <a class="sourceLine" id="cb30-4" title="4"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/ggplot2/topics/geom_bar">geom_col</a></span>() <span class="op">+</span></a>
<a class="sourceLine" id="cb30-5" title="5"><span class="st"> </span><span class="kw"><a href="https://ggplot2.tidyverse.org/reference/labs.html">labs</a></span>(<span class="dt">title =</span> <span class="st">"A title"</span>,</a> <a class="sourceLine" id="cb30-5" title="5"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/ggplot2/topics/labs">labs</a></span>(<span class="dt">title =</span> <span class="st">"A title"</span>,</a>
<a class="sourceLine" id="cb30-6" title="6"> <span class="dt">subtitle =</span> <span class="st">"A subtitle"</span>,</a> <a class="sourceLine" id="cb30-6" title="6"> <span class="dt">subtitle =</span> <span class="st">"A subtitle"</span>,</a>
<a class="sourceLine" id="cb30-7" title="7"> <span class="dt">x =</span> <span class="st">"My X axis"</span>,</a> <a class="sourceLine" id="cb30-7" title="7"> <span class="dt">x =</span> <span class="st">"My X axis"</span>,</a>
<a class="sourceLine" id="cb30-8" title="8"> <span class="dt">y =</span> <span class="st">"My Y axis"</span>)</a> <a class="sourceLine" id="cb30-8" title="8"> <span class="dt">y =</span> <span class="st">"My Y axis"</span>)</a>
<a class="sourceLine" id="cb30-9" title="9"></a> <a class="sourceLine" id="cb30-9" title="9"></a>
<a class="sourceLine" id="cb30-10" title="10"><span class="co"># or as short as:</span></a> <a class="sourceLine" id="cb30-10" title="10"><span class="co"># or as short as:</span></a>
<a class="sourceLine" id="cb30-11" title="11"><span class="kw"><a href="https://ggplot2.tidyverse.org/reference/ggplot.html">ggplot</a></span>(a_data_set) <span class="op">+</span></a> <a class="sourceLine" id="cb30-11" title="11"><span class="kw"><a href="https://www.rdocumentation.org/packages/ggplot2/topics/ggplot">ggplot</a></span>(a_data_set) <span class="op">+</span></a>
<a class="sourceLine" id="cb30-12" title="12"><span class="st"> </span><span class="kw"><a href="https://ggplot2.tidyverse.org/reference/geom_bar.html">geom_bar</a></span>(<span class="kw"><a href="https://ggplot2.tidyverse.org/reference/aes.html">aes</a></span>(year))</a></code></pre></div> <a class="sourceLine" id="cb30-12" title="12"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/ggplot2/topics/geom_bar">geom_bar</a></span>(<span class="kw"><a href="https://www.rdocumentation.org/packages/ggplot2/topics/aes">aes</a></span>(year))</a></code></pre></div>
<p>The <code>AMR</code> package contains functions to extend this <code>ggplot2</code> package, for example <code><a href="../reference/ggplot_rsi.html">geom_rsi()</a></code>. It automatically transforms data with <code><a href="../reference/count.html">count_df()</a></code> or <code><a href="../reference/portion.html">portion_df()</a></code> and show results in stacked bars. Its simplest and shortest example:</p> <p>The <code>AMR</code> package contains functions to extend this <code>ggplot2</code> package, for example <code><a href="../reference/ggplot_rsi.html">geom_rsi()</a></code>. It automatically transforms data with <code><a href="../reference/count.html">count_df()</a></code> or <code><a href="../reference/portion.html">portion_df()</a></code> and show results in stacked bars. Its simplest and shortest example:</p>
<div class="sourceCode" id="cb31"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb31-1" title="1"><span class="kw"><a href="https://ggplot2.tidyverse.org/reference/ggplot.html">ggplot</a></span>(data_1st) <span class="op">+</span></a> <div class="sourceCode" id="cb31"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb31-1" title="1"><span class="kw"><a href="https://www.rdocumentation.org/packages/ggplot2/topics/ggplot">ggplot</a></span>(data_1st) <span class="op">+</span></a>
<a class="sourceLine" id="cb31-2" title="2"><span class="st"> </span><span class="kw"><a href="../reference/ggplot_rsi.html">geom_rsi</a></span>(<span class="dt">translate_ab =</span> <span class="ot">FALSE</span>)</a></code></pre></div> <a class="sourceLine" id="cb31-2" title="2"><span class="st"> </span><span class="kw"><a href="../reference/ggplot_rsi.html">geom_rsi</a></span>(<span class="dt">translate_ab =</span> <span class="ot">FALSE</span>)</a></code></pre></div>
<p><img src="AMR_files/figure-html/plot%203-1.png" width="720"></p> <p><img src="AMR_files/figure-html/plot%203-1.png" width="720"></p>
<p>Omit the <code>translate_ab = FALSE</code> to have the antibiotic codes (amox, amcl, cipr, gent) translated to official WHO names (amoxicillin, amoxicillin and betalactamase inhibitor, ciprofloxacin, gentamicin).</p> <p>Omit the <code>translate_ab = FALSE</code> to have the antibiotic codes (amox, amcl, cipr, gent) translated to official WHO names (amoxicillin, amoxicillin and betalactamase inhibitor, ciprofloxacin, gentamicin).</p>
<p>If we group on e.g. the <code>genus</code> column and add some additional functions from our package, we can create this:</p> <p>If we group on e.g. the <code>genus</code> column and add some additional functions from our package, we can create this:</p>
<div class="sourceCode" id="cb32"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb32-1" title="1"><span class="co"># group the data on `genus`</span></a> <div class="sourceCode" id="cb32"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb32-1" title="1"><span class="co"># group the data on `genus`</span></a>
<a class="sourceLine" id="cb32-2" title="2"><span class="kw"><a href="https://ggplot2.tidyverse.org/reference/ggplot.html">ggplot</a></span>(data_1st <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(genus)) <span class="op">+</span><span class="st"> </span></a> <a class="sourceLine" id="cb32-2" title="2"><span class="kw"><a href="https://www.rdocumentation.org/packages/ggplot2/topics/ggplot">ggplot</a></span>(data_1st <span class="op">%&gt;%</span><span class="st"> </span><span class="kw"><a href="https://dplyr.tidyverse.org/reference/group_by.html">group_by</a></span>(genus)) <span class="op">+</span><span class="st"> </span></a>
<a class="sourceLine" id="cb32-3" title="3"><span class="st"> </span><span class="co"># create bars with genus on x axis</span></a> <a class="sourceLine" id="cb32-3" title="3"><span class="st"> </span><span class="co"># create bars with genus on x axis</span></a>
<a class="sourceLine" id="cb32-4" title="4"><span class="st"> </span><span class="co"># it looks for variables with class `rsi`,</span></a> <a class="sourceLine" id="cb32-4" title="4"><span class="st"> </span><span class="co"># it looks for variables with class `rsi`,</span></a>
<a class="sourceLine" id="cb32-5" title="5"><span class="st"> </span><span class="co"># of which we have 4 (earlier created with `as.rsi`)</span></a> <a class="sourceLine" id="cb32-5" title="5"><span class="st"> </span><span class="co"># of which we have 4 (earlier created with `as.rsi`)</span></a>
@ -1122,13 +1122,13 @@ Longest: 24</p>
<a class="sourceLine" id="cb32-11" title="11"><span class="st"> </span><span class="co"># show percentages on y axis</span></a> <a class="sourceLine" id="cb32-11" title="11"><span class="st"> </span><span class="co"># show percentages on y axis</span></a>
<a class="sourceLine" id="cb32-12" title="12"><span class="st"> </span><span class="kw"><a href="../reference/ggplot_rsi.html">scale_y_percent</a></span>(<span class="dt">breaks =</span> <span class="dv">0</span><span class="op">:</span><span class="dv">4</span> <span class="op">*</span><span class="st"> </span><span class="dv">25</span>) <span class="op">+</span></a> <a class="sourceLine" id="cb32-12" title="12"><span class="st"> </span><span class="kw"><a href="../reference/ggplot_rsi.html">scale_y_percent</a></span>(<span class="dt">breaks =</span> <span class="dv">0</span><span class="op">:</span><span class="dv">4</span> <span class="op">*</span><span class="st"> </span><span class="dv">25</span>) <span class="op">+</span></a>
<a class="sourceLine" id="cb32-13" title="13"><span class="st"> </span><span class="co"># turn 90 degrees, make it bars instead of columns</span></a> <a class="sourceLine" id="cb32-13" title="13"><span class="st"> </span><span class="co"># turn 90 degrees, make it bars instead of columns</span></a>
<a class="sourceLine" id="cb32-14" title="14"><span class="st"> </span><span class="kw"><a href="https://ggplot2.tidyverse.org/reference/coord_flip.html">coord_flip</a></span>() <span class="op">+</span></a> <a class="sourceLine" id="cb32-14" title="14"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/ggplot2/topics/coord_flip">coord_flip</a></span>() <span class="op">+</span></a>
<a class="sourceLine" id="cb32-15" title="15"><span class="st"> </span><span class="co"># add labels</span></a> <a class="sourceLine" id="cb32-15" title="15"><span class="st"> </span><span class="co"># add labels</span></a>
<a class="sourceLine" id="cb32-16" title="16"><span class="st"> </span><span class="kw"><a href="https://ggplot2.tidyverse.org/reference/labs.html">labs</a></span>(<span class="dt">title =</span> <span class="st">"Resistance per genus and antibiotic"</span>, </a> <a class="sourceLine" id="cb32-16" title="16"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/ggplot2/topics/labs">labs</a></span>(<span class="dt">title =</span> <span class="st">"Resistance per genus and antibiotic"</span>, </a>
<a class="sourceLine" id="cb32-17" title="17"> <span class="dt">subtitle =</span> <span class="st">"(this is fake data)"</span>) <span class="op">+</span></a> <a class="sourceLine" id="cb32-17" title="17"> <span class="dt">subtitle =</span> <span class="st">"(this is fake data)"</span>) <span class="op">+</span></a>
<a class="sourceLine" id="cb32-18" title="18"><span class="st"> </span><span class="co"># and print genus in italic to follow our convention</span></a> <a class="sourceLine" id="cb32-18" title="18"><span class="st"> </span><span class="co"># and print genus in italic to follow our convention</span></a>
<a class="sourceLine" id="cb32-19" title="19"><span class="st"> </span><span class="co"># (is now y axis because we turned the plot)</span></a> <a class="sourceLine" id="cb32-19" title="19"><span class="st"> </span><span class="co"># (is now y axis because we turned the plot)</span></a>
<a class="sourceLine" id="cb32-20" title="20"><span class="st"> </span><span class="kw"><a href="https://ggplot2.tidyverse.org/reference/theme.html">theme</a></span>(<span class="dt">axis.text.y =</span> <span class="kw"><a href="https://ggplot2.tidyverse.org/reference/element.html">element_text</a></span>(<span class="dt">face =</span> <span class="st">"italic"</span>))</a></code></pre></div> <a class="sourceLine" id="cb32-20" title="20"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/ggplot2/topics/theme">theme</a></span>(<span class="dt">axis.text.y =</span> <span class="kw"><a href="https://www.rdocumentation.org/packages/ggplot2/topics/element">element_text</a></span>(<span class="dt">face =</span> <span class="st">"italic"</span>))</a></code></pre></div>
<p><img src="AMR_files/figure-html/plot%204-1.png" width="720"></p> <p><img src="AMR_files/figure-html/plot%204-1.png" width="720"></p>
<p>To simplify this, we also created the <code><a href="../reference/ggplot_rsi.html">ggplot_rsi()</a></code> function, which combines almost all above functions:</p> <p>To simplify this, we also created the <code><a href="../reference/ggplot_rsi.html">ggplot_rsi()</a></code> function, which combines almost all above functions:</p>
<div class="sourceCode" id="cb33"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb33-1" title="1">data_1st <span class="op">%&gt;%</span><span class="st"> </span></a> <div class="sourceCode" id="cb33"><pre class="sourceCode r"><code class="sourceCode r"><a class="sourceLine" id="cb33-1" title="1">data_1st <span class="op">%&gt;%</span><span class="st"> </span></a>
@ -1137,7 +1137,7 @@ Longest: 24</p>
<a class="sourceLine" id="cb33-4" title="4"> <span class="dt">facet =</span> <span class="st">"Antibiotic"</span>,</a> <a class="sourceLine" id="cb33-4" title="4"> <span class="dt">facet =</span> <span class="st">"Antibiotic"</span>,</a>
<a class="sourceLine" id="cb33-5" title="5"> <span class="dt">breaks =</span> <span class="dv">0</span><span class="op">:</span><span class="dv">4</span> <span class="op">*</span><span class="st"> </span><span class="dv">25</span>,</a> <a class="sourceLine" id="cb33-5" title="5"> <span class="dt">breaks =</span> <span class="dv">0</span><span class="op">:</span><span class="dv">4</span> <span class="op">*</span><span class="st"> </span><span class="dv">25</span>,</a>
<a class="sourceLine" id="cb33-6" title="6"> <span class="dt">datalabels =</span> <span class="ot">FALSE</span>) <span class="op">+</span></a> <a class="sourceLine" id="cb33-6" title="6"> <span class="dt">datalabels =</span> <span class="ot">FALSE</span>) <span class="op">+</span></a>
<a class="sourceLine" id="cb33-7" title="7"><span class="st"> </span><span class="kw"><a href="https://ggplot2.tidyverse.org/reference/coord_flip.html">coord_flip</a></span>()</a></code></pre></div> <a class="sourceLine" id="cb33-7" title="7"><span class="st"> </span><span class="kw"><a href="https://www.rdocumentation.org/packages/ggplot2/topics/coord_flip">coord_flip</a></span>()</a></code></pre></div>
<p><img src="AMR_files/figure-html/plot%205-1.png" width="720"></p> <p><img src="AMR_files/figure-html/plot%205-1.png" width="720"></p>
</div> </div>
<div id="independence-test" class="section level2"> <div id="independence-test" class="section level2">

Binary file not shown.

Before

Width:  |  Height:  |  Size: 35 KiB

After

Width:  |  Height:  |  Size: 35 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 21 KiB

After

Width:  |  Height:  |  Size: 20 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 68 KiB

After

Width:  |  Height:  |  Size: 69 KiB

Binary file not shown.

Before

Width:  |  Height:  |  Size: 50 KiB

After

Width:  |  Height:  |  Size: 51 KiB

View File

@ -78,7 +78,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <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.5.0.9024</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.5.0.9025</span>
</span> </span>
</div> </div>

View File

@ -78,7 +78,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a> <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.5.0.9024</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.5.0.9025</span>
</span> </span>
</div> </div>

View File

@ -42,7 +42,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="index.html">AMR (for R)</a> <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.5.0.9024</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.5.0.9025</span>
</span> </span>
</div> </div>

View File

@ -78,7 +78,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <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.5.0.9024</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.5.0.9025</span>
</span> </span>
</div> </div>

View File

@ -80,7 +80,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <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.5.0.9024</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.5.0.9025</span>
</span> </span>
</div> </div>
@ -252,7 +252,7 @@
<span class='fu'>mo_renamed</span>() <span class='fu'>mo_renamed</span>()
<span class='fu'>clean_mo_history</span>()</pre> <span class='fu'>clean_mo_history</span>(<span class='no'>...</span>)</pre>
<h2 class="hasAnchor" id="arguments"><a class="anchor" href="#arguments"></a>Arguments</h2> <h2 class="hasAnchor" id="arguments"><a class="anchor" href="#arguments"></a>Arguments</h2>
<table class="ref-arguments"> <table class="ref-arguments">
@ -263,12 +263,12 @@
</tr> </tr>
<tr> <tr>
<th>Becker</th> <th>Becker</th>
<td><p>a logical to indicate whether <em>Staphylococci</em> should be categorised into Coagulase Negative <em>Staphylococci</em> ("CoNS") and Coagulase Positive <em>Staphylococci</em> ("CoPS") instead of their own species, according to Karsten Becker <em>et al.</em> [1]. Note that this does not include species that were newly named after this publication.</p> <td><p>a logical to indicate whether <em>Staphylococci</em> should be categorised into coagulase-negative <em>Staphylococci</em> ("CoNS") and coagulase-positive <em>Staphylococci</em> ("CoPS") instead of their own species, according to Karsten Becker <em>et al.</em> [1,2]. Note that this does not include species that were newly named after these publications, like <em>S. caeli</em>.</p>
<p>This excludes <em>Staphylococcus aureus</em> at default, use <code>Becker = "all"</code> to also categorise <em>S. aureus</em> as "CoPS".</p></td> <p>This excludes <em>Staphylococcus aureus</em> at default, use <code>Becker = "all"</code> to also categorise <em>S. aureus</em> as "CoPS".</p></td>
</tr> </tr>
<tr> <tr>
<th>Lancefield</th> <th>Lancefield</th>
<td><p>a logical to indicate whether beta-haemolytic <em>Streptococci</em> should be categorised into Lancefield groups instead of their own species, according to Rebecca C. Lancefield [2]. These <em>Streptococci</em> will be categorised in their first group, e.g. <em>Streptococcus dysgalactiae</em> will be group C, although officially it was also categorised into groups G and L.</p> <td><p>a logical to indicate whether beta-haemolytic <em>Streptococci</em> should be categorised into Lancefield groups instead of their own species, according to Rebecca C. Lancefield [3]. These <em>Streptococci</em> will be categorised in their first group, e.g. <em>Streptococcus dysgalactiae</em> will be group C, although officially it was also categorised into groups G and L.</p>
<p>This excludes <em>Enterococci</em> at default (who are in group D), use <code>Lancefield = "all"</code> to also categorise all <em>Enterococci</em> as group D.</p></td> <p>This excludes <em>Enterococci</em> at default (who are in group D), use <code>Lancefield = "all"</code> to also categorise all <em>Enterococci</em> as group D.</p></td>
</tr> </tr>
<tr> <tr>
@ -287,7 +287,7 @@
<h2 class="hasAnchor" id="value"><a class="anchor" href="#value"></a>Value</h2> <h2 class="hasAnchor" id="value"><a class="anchor" href="#value"></a>Value</h2>
<p>Character (vector) with class <code>"mo"</code>. Unknown values will return <code>NA</code>.</p> <p>Character (vector) with class <code>"mo"</code></p>
<h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2> <h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2>
@ -303,14 +303,15 @@ A microbial ID from this package (class: <code>mo</code>) typically looks like t
| | | ----&gt; subspecies, a 3-4 letter acronym | | | ----&gt; subspecies, a 3-4 letter acronym
| | ----&gt; species, a 3-4 letter acronym | | ----&gt; species, a 3-4 letter acronym
| ----&gt; genus, a 5-7 letter acronym, mostly without vowels | ----&gt; genus, a 5-7 letter acronym, mostly without vowels
----&gt; taxonomic kingdom: A (Archaea), AN (Animalia), B (Bacteria), C (Chromista), ----&gt; taxonomic kingdom: A (Archaea), AN (Animalia), B (Bacteria),
F (Fungi), P (Protozoa) or PL (Plantae) C (Chromista), F (Fungi), P (Protozoa) or
PL (Plantae)
</pre> </pre>
<p>Values that cannot be coered will be considered 'unknown' and have an MO code <code>UNKNOWN</code>.</p> <p>Values that cannot be coered will be considered 'unknown' and will get the MO code <code>UNKNOWN</code>.</p>
<p>Use the <code><a href='mo_property.html'>mo_property</a>_*</code> functions to get properties based on the returned code, see Examples.</p> <p>Use the <code><a href='mo_property.html'>mo_property</a>_*</code> functions to get properties based on the returned code, see Examples.</p>
<p>The algorithm uses data from the Catalogue of Life (see below) and from one other source (see <code><a href='microorganisms.html'>?microorganisms</a></code>).</p> <p>The algorithm uses data from the Catalogue of Life (see below) and from one other source (see <code><a href='microorganisms.html'>?microorganisms</a></code>).</p>
<p><strong>Self-learning algoritm</strong> <br /> <p><strong>Self-learning algoritm</strong> <br />
The <code>as.mo()</code> function gains experience from previously determined microbial IDs and learns from it. This drastically improves both speed and reliability. Use <code>clean_mo_history()</code> to reset the algorithms. Only experience from your current <code>AMR</code> package version is used. This is done because in the future the taxonomic tree (which is included in this package) may change for any organism and it consequently has to rebuild its knowledge. Usually, any guess after the first try runs 90-95% faster than the first try. The algorithm saves its previous findings to <code>~/.Rhistory_mo</code>.</p> The <code>as.mo()</code> function gains experience from previously determined microbial IDs and learns from it. This drastically improves both speed and reliability. Use <code>clean_mo_history()</code> to reset the algorithms. Only experience from your current <code>AMR</code> package version is used. This is done because in the future the taxonomic tree (which is included in this package) may change for any organism and it consequently has to rebuild its knowledge. Usually, any guess after the first try runs 80-95% faster than the first try. The algorithm saves its previous findings to <code>~/.Rhistory_mo</code>.</p>
<p><strong>Intelligent rules</strong> <br /> <p><strong>Intelligent rules</strong> <br />
This function uses intelligent rules to help getting fast and logical results. It tries to find matches in this order:</p><ul> This function uses intelligent rules to help getting fast and logical results. It tries to find matches in this order:</p><ul>
<li><p>Valid MO codes and full names: it first searches in already valid MO code and known genus/species combinations</p></li> <li><p>Valid MO codes and full names: it first searches in already valid MO code and known genus/species combinations</p></li>
@ -324,7 +325,7 @@ This function uses intelligent rules to help getting fast and logical results. I
<li><p>Something like <code>"stau"</code> or <code>"S aur"</code> will return the ID of <em>Staphylococcus aureus</em> and not <em>Staphylococcus auricularis</em></p></li> <li><p>Something like <code>"stau"</code> or <code>"S aur"</code> will return the ID of <em>Staphylococcus aureus</em> and not <em>Staphylococcus auricularis</em></p></li>
</ul><p>This means that looking up human pathogenic microorganisms takes less time than looking up human non-pathogenic microorganisms.</p> </ul><p>This means that looking up human pathogenic microorganisms takes less time than looking up human non-pathogenic microorganisms.</p>
<p><strong>Uncertain results</strong> <br /> <p><strong>Uncertain results</strong> <br />
The algorithm can additionally use three different levels of uncertainty to guess valid results. The default is <code>allow_uncertain = TRUE</code>, which is uqual to uncertainty level 2. Using <code>allow_uncertain = FALSE</code> will skip all of these additional rules:</p><ul> The algorithm can additionally use three different levels of uncertainty to guess valid results. The default is <code>allow_uncertain = TRUE</code>, which is equal to uncertainty level 2. Using <code>allow_uncertain = FALSE</code> will skip all of these additional rules:</p><ul>
<li><p>(uncertainty level 1): It tries to look for only matching genera</p></li> <li><p>(uncertainty level 1): It tries to look for only matching genera</p></li>
<li><p>(uncertainty level 1): It tries to look for previously accepted (but now invalid) taxonomic names</p></li> <li><p>(uncertainty level 1): It tries to look for previously accepted (but now invalid) taxonomic names</p></li>
<li><p>(uncertainty level 2): It strips off values between brackets and the brackets itself, and re-evaluates the input with all previous rules</p></li> <li><p>(uncertainty level 2): It strips off values between brackets and the brackets itself, and re-evaluates the input with all previous rules</p></li>
@ -354,8 +355,9 @@ The intelligent rules takes into account microbial prevalence of pathogens in hu
<p>[1] Becker K <em>et al.</em> <strong>Coagulase-Negative Staphylococci</strong>. 2014. Clin Microbiol Rev. 27(4): 870926. <a href='https://dx.doi.org/10.1128/CMR.00109-13'>https://dx.doi.org/10.1128/CMR.00109-13</a></p> <p>[1] Becker K <em>et al.</em> <strong>Coagulase-Negative Staphylococci</strong>. 2014. Clin Microbiol Rev. 27(4): 870926. <a href='https://dx.doi.org/10.1128/CMR.00109-13'>https://dx.doi.org/10.1128/CMR.00109-13</a></p>
<p>[2] Lancefield RC <strong>A serological differentiation of human and other groups of hemolytic streptococci</strong>. 1933. J Exp Med. 57(4): 57195. <a href='https://dx.doi.org/10.1084/jem.57.4.571'>https://dx.doi.org/10.1084/jem.57.4.571</a></p> <p>[2] Becker K <em>et al.</em> <strong>Implications of identifying the recently defined members of the S. aureus complex, S. argenteus and S. schweitzeri: A position paper of members of the ESCMID Study Group for staphylococci and Staphylococcal Diseases (ESGS).</strong>. 2019. Clin Microbiol Infect. 2019 Mar 11. <a href='https://doi.org/10.1016/j.cmi.2019.02.028'>https://doi.org/10.1016/j.cmi.2019.02.028</a></p>
<p>[3] Catalogue of Life: Annual Checklist (public online taxonomic database), <a href='www.catalogueoflife.org'>www.catalogueoflife.org</a> (check included annual version with <code><a href='catalogue_of_life_version.html'>catalogue_of_life_version</a>()</code>).</p> <p>[3] Lancefield RC <strong>A serological differentiation of human and other groups of hemolytic streptococci</strong>. 1933. J Exp Med. 57(4): 57195. <a href='https://dx.doi.org/10.1084/jem.57.4.571'>https://dx.doi.org/10.1084/jem.57.4.571</a></p>
<p>[4] Catalogue of Life: Annual Checklist (public online taxonomic database), <a href='www.catalogueoflife.org'>www.catalogueoflife.org</a> (check included annual version with <code><a href='catalogue_of_life_version.html'>catalogue_of_life_version</a>()</code>).</p>
<h2 class="hasAnchor" id="catalogue-of-life"><a class="anchor" href="#catalogue-of-life"></a>Catalogue of Life</h2> <h2 class="hasAnchor" id="catalogue-of-life"><a class="anchor" href="#catalogue-of-life"></a>Catalogue of Life</h2>

View File

@ -80,7 +80,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <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.5.0.9024</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.5.0.9025</span>
</span> </span>
</div> </div>

View File

@ -80,7 +80,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <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.5.0.9024</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.5.0.9025</span>
</span> </span>
</div> </div>
@ -245,11 +245,11 @@
<h2 class="hasAnchor" id="value"><a class="anchor" href="#value"></a>Value</h2> <h2 class="hasAnchor" id="value"><a class="anchor" href="#value"></a>Value</h2>
<p>a <code>list</code>, invisibly</p> <p>a <code>list</code>, which prints in pretty format</p>
<h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2> <h2 class="hasAnchor" id="details"><a class="anchor" href="#details"></a>Details</h2>
<p>The list item <code>is_latest_annual_release</code> is based on the system date.</p> <p>The list item <code>...$catalogue_of_life$is_latest_annual_release</code> is based on the system date.</p>
<p>For DSMZ, see <code><a href='microorganisms.html'>?microorganisms</a></code>.</p> <p>For DSMZ, see <code><a href='microorganisms.html'>?microorganisms</a></code>.</p>
<h2 class="hasAnchor" id="catalogue-of-life"><a class="anchor" href="#catalogue-of-life"></a>Catalogue of Life</h2> <h2 class="hasAnchor" id="catalogue-of-life"><a class="anchor" href="#catalogue-of-life"></a>Catalogue of Life</h2>

View File

@ -81,7 +81,7 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <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.5.0.9023</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.5.0.9025</span>
</span> </span>
</div> </div>
@ -340,7 +340,7 @@ count_R and count_IR can be used to count resistant isolates, count_S and count_
<span class='kw'>S</span> <span class='kw'>=</span> <span class='fu'>count_S</span>(<span class='no'>cipr</span>), <span class='kw'>S</span> <span class='kw'>=</span> <span class='fu'>count_S</span>(<span class='no'>cipr</span>),
<span class='kw'>n1</span> <span class='kw'>=</span> <span class='fu'>count_all</span>(<span class='no'>cipr</span>), <span class='co'># the actual total; sum of all three</span> <span class='kw'>n1</span> <span class='kw'>=</span> <span class='fu'>count_all</span>(<span class='no'>cipr</span>), <span class='co'># the actual total; sum of all three</span>
<span class='kw'>n2</span> <span class='kw'>=</span> <span class='fu'>n_rsi</span>(<span class='no'>cipr</span>), <span class='co'># same - analogous to n_distinct</span> <span class='kw'>n2</span> <span class='kw'>=</span> <span class='fu'>n_rsi</span>(<span class='no'>cipr</span>), <span class='co'># same - analogous to n_distinct</span>
<span class='kw'>total</span> <span class='kw'>=</span> <span class='fu'><a href='https://dplyr.tidyverse.org/reference/n.html'>n</a></span>()) <span class='co'># NOT the amount of tested isolates!</span> <span class='kw'>total</span> <span class='kw'>=</span> <span class='fu'><a href='https://dplyr.tidyverse.org/reference/n.html'>n</a></span>()) <span class='co'># NOT the number of tested isolates!</span>
<span class='co'># Count co-resistance between amoxicillin/clav acid and gentamicin,</span> <span class='co'># Count co-resistance between amoxicillin/clav acid and gentamicin,</span>
<span class='co'># so we can see that combination therapy does a lot more than mono therapy.</span> <span class='co'># so we can see that combination therapy does a lot more than mono therapy.</span>

View File

@ -6,7 +6,7 @@
<meta http-equiv="X-UA-Compatible" content="IE=edge"> <meta http-equiv="X-UA-Compatible" content="IE=edge">
<meta name="viewport" content="width=device-width, initial-scale=1.0"> <meta name="viewport" content="width=device-width, initial-scale=1.0">
<title>Filter on antibiotic class — filter_ab_class • AMR (for R)</title> <title>Filter isolates on result in antibiotic class — filter_ab_class • AMR (for R)</title>
<!-- favicons --> <!-- favicons -->
<link rel="icon" type="image/png" sizes="16x16" href="../favicon-16x16.png"> <link rel="icon" type="image/png" sizes="16x16" href="../favicon-16x16.png">
@ -45,9 +45,9 @@
<link href="../extra.css" rel="stylesheet"> <link href="../extra.css" rel="stylesheet">
<script src="../extra.js"></script> <script src="../extra.js"></script>
<meta property="og:title" content="Filter on antibiotic class — filter_ab_class" /> <meta property="og:title" content="Filter isolates on result in antibiotic class — filter_ab_class" />
<meta property="og:description" content="Filter on specific antibiotic variables based on their class (ATC groups)." /> <meta property="og:description" content="Filter isolates on results in specific antibiotic variables based on their class (ATC groups). This makes it easy to get a list of isolates that were tested for e.g. any aminoglycoside." />
<meta property="og:image" content="https://msberends.gitlab.io/AMR/logo.png" /> <meta property="og:image" content="https://msberends.gitlab.io/AMR/logo.png" />
<meta name="twitter:card" content="summary" /> <meta name="twitter:card" content="summary" />
@ -80,7 +80,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <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.5.0.9023</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.5.0.9025</span>
</span> </span>
</div> </div>
@ -230,14 +230,14 @@
<div class="row"> <div class="row">
<div class="col-md-9 contents"> <div class="col-md-9 contents">
<div class="page-header"> <div class="page-header">
<h1>Filter on antibiotic class</h1> <h1>Filter isolates on result in antibiotic class</h1>
<div class="hidden name"><code>filter_ab_class.Rd</code></div> <div class="hidden name"><code>filter_ab_class.Rd</code></div>
</div> </div>
<div class="ref-description"> <div class="ref-description">
<p>Filter on specific antibiotic variables based on their class (ATC groups).</p> <p>Filter isolates on results in specific antibiotic variables based on their class (ATC groups). This makes it easy to get a list of isolates that were tested for e.g. any aminoglycoside.</p>
</div> </div>
@ -274,7 +274,7 @@
</tr> </tr>
<tr> <tr>
<th>ab_class</th> <th>ab_class</th>
<td><p>an antimicrobial class, like <code>"carbapenems"</code></p></td> <td><p>an antimicrobial class, like <code>"carbapenems"</code>. More specifically, this should be a text that can be found in a 4th level ATC group (chemical subgroup) or a 5th level ATC group (chemical substance), please see <a href='https://www.whocc.no/atc/structure_and_principles/'>this explanation on the WHOCC website</a>.</p></td>
</tr> </tr>
<tr> <tr>
<th>result</th> <th>result</th>
@ -317,8 +317,14 @@
<span class='co'># filter on isolates that show resistance to</span> <span class='co'># filter on isolates that show resistance to</span>
<span class='co'># any aminoglycoside and any fluoroquinolone</span> <span class='co'># any aminoglycoside and any fluoroquinolone</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span> <span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'>filter_aminoglycosides</span>(<span class='st'>"R"</span>, <span class='st'>"any"</span>) <span class='kw'>%&gt;%</span> <span class='fu'>filter_aminoglycosides</span>(<span class='st'>"R"</span>) <span class='kw'>%&gt;%</span>
<span class='fu'>filter_fluoroquinolones</span>(<span class='st'>"R"</span>, <span class='st'>"any"</span>) <span class='fu'>filter_fluoroquinolones</span>(<span class='st'>"R"</span>)
<span class='co'># filter on isolates that show resistance to</span>
<span class='co'># all aminoglycosides and all fluoroquinolones</span>
<span class='no'>septic_patients</span> <span class='kw'>%&gt;%</span>
<span class='fu'>filter_aminoglycosides</span>(<span class='st'>"R"</span>, <span class='st'>"all"</span>) <span class='kw'>%&gt;%</span>
<span class='fu'>filter_fluoroquinolones</span>(<span class='st'>"R"</span>, <span class='st'>"all"</span>)
<span class='co'># }</span></pre> <span class='co'># }</span></pre>
</div> </div>
<div class="col-md-3 hidden-xs hidden-sm" id="sidebar"> <div class="col-md-3 hidden-xs hidden-sm" id="sidebar">

View File

@ -78,7 +78,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <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.5.0.9024</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.5.0.9025</span>
</span> </span>
</div> </div>
@ -431,7 +431,7 @@
<td> <td>
<p><code><a href="filter_ab_class.html">filter_ab_class()</a></code> <code><a href="filter_ab_class.html">filter_aminoglycosides()</a></code> <code><a href="filter_ab_class.html">filter_carbapenems()</a></code> <code><a href="filter_ab_class.html">filter_cephalosporins()</a></code> <code><a href="filter_ab_class.html">filter_1st_cephalosporins()</a></code> <code><a href="filter_ab_class.html">filter_2nd_cephalosporins()</a></code> <code><a href="filter_ab_class.html">filter_3rd_cephalosporins()</a></code> <code><a href="filter_ab_class.html">filter_4th_cephalosporins()</a></code> <code><a href="filter_ab_class.html">filter_fluoroquinolones()</a></code> <code><a href="filter_ab_class.html">filter_glycopeptides()</a></code> <code><a href="filter_ab_class.html">filter_macrolides()</a></code> <code><a href="filter_ab_class.html">filter_tetracyclines()</a></code> </p> <p><code><a href="filter_ab_class.html">filter_ab_class()</a></code> <code><a href="filter_ab_class.html">filter_aminoglycosides()</a></code> <code><a href="filter_ab_class.html">filter_carbapenems()</a></code> <code><a href="filter_ab_class.html">filter_cephalosporins()</a></code> <code><a href="filter_ab_class.html">filter_1st_cephalosporins()</a></code> <code><a href="filter_ab_class.html">filter_2nd_cephalosporins()</a></code> <code><a href="filter_ab_class.html">filter_3rd_cephalosporins()</a></code> <code><a href="filter_ab_class.html">filter_4th_cephalosporins()</a></code> <code><a href="filter_ab_class.html">filter_fluoroquinolones()</a></code> <code><a href="filter_ab_class.html">filter_glycopeptides()</a></code> <code><a href="filter_ab_class.html">filter_macrolides()</a></code> <code><a href="filter_ab_class.html">filter_tetracyclines()</a></code> </p>
</td> </td>
<td><p>Filter on antibiotic class</p></td> <td><p>Filter isolates on result in antibiotic class</p></td>
</tr><tr> </tr><tr>
<td> <td>

View File

@ -80,7 +80,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <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.5.0.9024</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.5.0.9025</span>
</span> </span>
</div> </div>

View File

@ -80,7 +80,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <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.5.0.9024</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.5.0.9025</span>
</span> </span>
</div> </div>

View File

@ -80,7 +80,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <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.5.0.9024</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.5.0.9025</span>
</span> </span>
</div> </div>
@ -341,8 +341,9 @@ This package contains the complete taxonomic tree of almost all microorganisms (
<p>[1] Becker K <em>et al.</em> <strong>Coagulase-Negative Staphylococci</strong>. 2014. Clin Microbiol Rev. 27(4): 870926. <a href='https://dx.doi.org/10.1128/CMR.00109-13'>https://dx.doi.org/10.1128/CMR.00109-13</a></p> <p>[1] Becker K <em>et al.</em> <strong>Coagulase-Negative Staphylococci</strong>. 2014. Clin Microbiol Rev. 27(4): 870926. <a href='https://dx.doi.org/10.1128/CMR.00109-13'>https://dx.doi.org/10.1128/CMR.00109-13</a></p>
<p>[2] Lancefield RC <strong>A serological differentiation of human and other groups of hemolytic streptococci</strong>. 1933. J Exp Med. 57(4): 57195. <a href='https://dx.doi.org/10.1084/jem.57.4.571'>https://dx.doi.org/10.1084/jem.57.4.571</a></p> <p>[2] Becker K <em>et al.</em> <strong>Implications of identifying the recently defined members of the S. aureus complex, S. argenteus and S. schweitzeri: A position paper of members of the ESCMID Study Group for staphylococci and Staphylococcal Diseases (ESGS).</strong>. 2019. Clin Microbiol Infect. 2019 Mar 11. <a href='https://doi.org/10.1016/j.cmi.2019.02.028'>https://doi.org/10.1016/j.cmi.2019.02.028</a></p>
<p>[3] Catalogue of Life: Annual Checklist (public online taxonomic database), <a href='www.catalogueoflife.org'>www.catalogueoflife.org</a> (check included annual version with <code><a href='catalogue_of_life_version.html'>catalogue_of_life_version</a>()</code>).</p> <p>[3] Lancefield RC <strong>A serological differentiation of human and other groups of hemolytic streptococci</strong>. 1933. J Exp Med. 57(4): 57195. <a href='https://dx.doi.org/10.1084/jem.57.4.571'>https://dx.doi.org/10.1084/jem.57.4.571</a></p>
<p>[4] Catalogue of Life: Annual Checklist (public online taxonomic database), <a href='www.catalogueoflife.org'>www.catalogueoflife.org</a> (check included annual version with <code><a href='catalogue_of_life_version.html'>catalogue_of_life_version</a>()</code>).</p>
<h2 class="hasAnchor" id="read-more-on-our-website-"><a class="anchor" href="#read-more-on-our-website-"></a>Read more on our website!</h2> <h2 class="hasAnchor" id="read-more-on-our-website-"><a class="anchor" href="#read-more-on-our-website-"></a>Read more on our website!</h2>

View File

@ -47,7 +47,7 @@
<script src="../extra.js"></script> <script src="../extra.js"></script>
<meta property="og:title" content="Calculate resistance of isolates — portion" /> <meta property="og:title" content="Calculate resistance of isolates — portion" />
<meta property="og:description" content="These functions can be used to calculate the (co-)resistance of microbial isolates (i.e. percentage S, SI, I, IR or R). All functions support quasiquotation with pipes, can be used in dplyrs summarise and support grouped variables, see Examples. <meta property="og:description" content="These functions can be used to calculate the (co-)resistance of microbial isolates (i.e. percentage of S, SI, I, IR or R). All functions support quasiquotation with pipes, can be used in dplyrs summarise and support grouped variables, see Examples.
portion_R and portion_IR can be used to calculate resistance, portion_S and portion_SI can be used to calculate susceptibility." /> portion_R and portion_IR can be used to calculate resistance, portion_S and portion_SI can be used to calculate susceptibility." />
<meta property="og:image" content="https://msberends.gitlab.io/AMR/logo.png" /> <meta property="og:image" content="https://msberends.gitlab.io/AMR/logo.png" />
@ -81,7 +81,7 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <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.5.0.9023</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.5.0.9025</span>
</span> </span>
</div> </div>
@ -238,7 +238,7 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
<div class="ref-description"> <div class="ref-description">
<p>These functions can be used to calculate the (co-)resistance of microbial isolates (i.e. percentage S, SI, I, IR or R). All functions support quasiquotation with pipes, can be used in <code>dplyr</code>s <code><a href='https://dplyr.tidyverse.org/reference/summarise.html'>summarise</a></code> and support grouped variables, see <em>Examples</em>.</p> <p>These functions can be used to calculate the (co-)resistance of microbial isolates (i.e. percentage of S, SI, I, IR or R). All functions support quasiquotation with pipes, can be used in <code>dplyr</code>s <code><a href='https://dplyr.tidyverse.org/reference/summarise.html'>summarise</a></code> and support grouped variables, see <em>Examples</em>.</p>
<p><code>portion_R</code> and <code>portion_IR</code> can be used to calculate resistance, <code>portion_S</code> and <code>portion_SI</code> can be used to calculate susceptibility.<br /></p> <p><code>portion_R</code> and <code>portion_IR</code> can be used to calculate resistance, <code>portion_S</code> and <code>portion_SI</code> can be used to calculate susceptibility.<br /></p>
</div> </div>
@ -270,7 +270,7 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
</tr> </tr>
<tr> <tr>
<th>minimum</th> <th>minimum</th>
<td><p>the minimal amount of available isolates. Any number lower than <code>minimum</code> will return <code>NA</code> with a warning. The default number of <code>30</code> isolates is advised by the Clinical and Laboratory Standards Institute (CLSI) as best practice, see Source.</p></td> <td><p>the minimum allowed number of available (tested) isolates. Any isolate count lower than <code>minimum</code> will return <code>NA</code> with a warning. The default number of <code>30</code> isolates is advised by the Clinical and Laboratory Standards Institute (CLSI) as best practice, see Source.</p></td>
</tr> </tr>
<tr> <tr>
<th>as_percent</th> <th>as_percent</th>
@ -311,14 +311,14 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
<p>The old <code><a href='rsi.html'>rsi</a></code> function is still available for backwards compatibility but is deprecated. <p>The old <code><a href='rsi.html'>rsi</a></code> function is still available for backwards compatibility but is deprecated.
<br /><br /> <br /><br />
To calculate the probability (<em>p</em>) of susceptibility of one antibiotic, we use this formula: To calculate the probability (<em>p</em>) of susceptibility of one antibiotic, we use this formula:
<div style="text-align: center"><img src='figures/mono_therapy.png' alt='' /></div> <div style="text-align: center;"><img src='figures/combi_therapy_2.png' alt='' /></div>
To calculate the probability (<em>p</em>) of susceptibility of more antibiotics (i.e. combination therapy), we need to check whether one of them has a susceptible result (as numerator) and count all cases where all antibiotics were tested (as denominator). <br /> To calculate the probability (<em>p</em>) of susceptibility of more antibiotics (i.e. combination therapy), we need to check whether one of them has a susceptible result (as numerator) and count all cases where all antibiotics were tested (as denominator). <br />
<br /> <br />
For two antibiotics: For two antibiotics:
<div style="text-align: center"><img src='figures/combi_therapy_2.png' alt='' /></div> <div style="text-align: center;"><img src='figures/combi_therapy_2.png' alt='' /></div>
<br /> <br />
For three antibiotics: For three antibiotics:
<div style="text-align: center"><img src='figures/combi_therapy_3.png' alt='' /></div> <div style="text-align: center;"><img src='figures/combi_therapy_2.png' alt='' /></div>
<br /> <br />
And so on.</p> And so on.</p>
@ -362,8 +362,9 @@ portion_R and portion_IR can be used to calculate resistance, portion_S and port
<span class='fu'><a href='https://dplyr.tidyverse.org/reference/summarise.html'>summarise</a></span>(<span class='kw'>R</span> <span class='kw'>=</span> <span class='fu'>portion_R</span>(<span class='no'>cipr</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>), <span class='fu'><a href='https://dplyr.tidyverse.org/reference/summarise.html'>summarise</a></span>(<span class='kw'>R</span> <span class='kw'>=</span> <span class='fu'>portion_R</span>(<span class='no'>cipr</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>),
<span class='kw'>I</span> <span class='kw'>=</span> <span class='fu'>portion_I</span>(<span class='no'>cipr</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>), <span class='kw'>I</span> <span class='kw'>=</span> <span class='fu'>portion_I</span>(<span class='no'>cipr</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>),
<span class='kw'>S</span> <span class='kw'>=</span> <span class='fu'>portion_S</span>(<span class='no'>cipr</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>), <span class='kw'>S</span> <span class='kw'>=</span> <span class='fu'>portion_S</span>(<span class='no'>cipr</span>, <span class='kw'>as_percent</span> <span class='kw'>=</span> <span class='fl'>TRUE</span>),
<span class='kw'>n</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>n_rsi</a></span>(<span class='no'>cipr</span>), <span class='co'># works like n_distinct in dplyr</span> <span class='kw'>n1</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>count_all</a></span>(<span class='no'>cipr</span>), <span class='co'># the actual total; sum of all three</span>
<span class='kw'>total</span> <span class='kw'>=</span> <span class='fu'><a href='https://dplyr.tidyverse.org/reference/n.html'>n</a></span>()) <span class='co'># NOT the amount of tested isolates!</span> <span class='kw'>n2</span> <span class='kw'>=</span> <span class='fu'><a href='count.html'>n_rsi</a></span>(<span class='no'>cipr</span>), <span class='co'># same - analogous to n_distinct</span>
<span class='kw'>total</span> <span class='kw'>=</span> <span class='fu'><a href='https://dplyr.tidyverse.org/reference/n.html'>n</a></span>()) <span class='co'># NOT the number of tested isolates!</span>
<span class='co'># Calculate co-resistance between amoxicillin/clav acid and gentamicin,</span> <span class='co'># Calculate co-resistance between amoxicillin/clav acid and gentamicin,</span>
<span class='co'># so we can see that combination therapy does a lot more than mono therapy:</span> <span class='co'># so we can see that combination therapy does a lot more than mono therapy:</span>

View File

@ -80,7 +80,7 @@
</button> </button>
<span class="navbar-brand"> <span class="navbar-brand">
<a class="navbar-link" href="../index.html">AMR (for R)</a> <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.5.0.9023</span> <span class="version label label-default" data-toggle="tooltip" data-placement="bottom" title="Released version">0.5.0.9025</span>
</span> </span>
</div> </div>
@ -257,7 +257,7 @@
</tr> </tr>
<tr> <tr>
<th>minimum</th> <th>minimum</th>
<td><p>the minimal amount of available isolates. Any number lower than <code>minimum</code> will return <code>NA</code> with a warning. The default number of <code>30</code> isolates is advised by the Clinical and Laboratory Standards Institute (CLSI) as best practice, see Source.</p></td> <td><p>the minimum allowed number of available (tested) isolates. Any isolate count lower than <code>minimum</code> will return <code>NA</code> with a warning. The default number of <code>30</code> isolates is advised by the Clinical and Laboratory Standards Institute (CLSI) as best practice, see Source.</p></td>
</tr> </tr>
<tr> <tr>
<th>as_percent</th> <th>as_percent</th>

View File

@ -21,16 +21,16 @@ mo_uncertainties()
mo_renamed() mo_renamed()
clean_mo_history() clean_mo_history(...)
} }
\arguments{ \arguments{
\item{x}{a character vector or a \code{data.frame} with one or two columns} \item{x}{a character vector or a \code{data.frame} with one or two columns}
\item{Becker}{a logical to indicate whether \emph{Staphylococci} should be categorised into Coagulase Negative \emph{Staphylococci} ("CoNS") and Coagulase Positive \emph{Staphylococci} ("CoPS") instead of their own species, according to Karsten Becker \emph{et al.} [1]. Note that this does not include species that were newly named after this publication. \item{Becker}{a logical to indicate whether \emph{Staphylococci} should be categorised into coagulase-negative \emph{Staphylococci} ("CoNS") and coagulase-positive \emph{Staphylococci} ("CoPS") instead of their own species, according to Karsten Becker \emph{et al.} [1,2]. Note that this does not include species that were newly named after these publications, like \emph{S. caeli}.
This excludes \emph{Staphylococcus aureus} at default, use \code{Becker = "all"} to also categorise \emph{S. aureus} as "CoPS".} This excludes \emph{Staphylococcus aureus} at default, use \code{Becker = "all"} to also categorise \emph{S. aureus} as "CoPS".}
\item{Lancefield}{a logical to indicate whether beta-haemolytic \emph{Streptococci} should be categorised into Lancefield groups instead of their own species, according to Rebecca C. Lancefield [2]. These \emph{Streptococci} will be categorised in their first group, e.g. \emph{Streptococcus dysgalactiae} will be group C, although officially it was also categorised into groups G and L. \item{Lancefield}{a logical to indicate whether beta-haemolytic \emph{Streptococci} should be categorised into Lancefield groups instead of their own species, according to Rebecca C. Lancefield [3]. These \emph{Streptococci} will be categorised in their first group, e.g. \emph{Streptococcus dysgalactiae} will be group C, although officially it was also categorised into groups G and L.
This excludes \emph{Enterococci} at default (who are in group D), use \code{Lancefield = "all"} to also categorise all \emph{Enterococci} as group D.} This excludes \emph{Enterococci} at default (who are in group D), use \code{Lancefield = "all"} to also categorise all \emph{Enterococci} as group D.}
@ -41,7 +41,7 @@ clean_mo_history()
\item{...}{other parameters passed on to functions} \item{...}{other parameters passed on to functions}
} }
\value{ \value{
Character (vector) with class \code{"mo"}. Unknown values will return \code{NA}. Character (vector) with class \code{"mo"}
} }
\description{ \description{
Use this function to determine a valid microorganism ID (\code{mo}). Determination is done using intelligent rules and the complete taxonomic kingdoms Bacteria, Chromista, Protozoa, Archaea and most microbial species from the kingdom Fungi (see Source). The input can be almost anything: a full name (like \code{"Staphylococcus aureus"}), an abbreviated name (like \code{"S. aureus"}), an abbreviation known in the field (like \code{"MRSA"}), or just a genus. Please see Examples. Use this function to determine a valid microorganism ID (\code{mo}). Determination is done using intelligent rules and the complete taxonomic kingdoms Bacteria, Chromista, Protozoa, Archaea and most microbial species from the kingdom Fungi (see Source). The input can be almost anything: a full name (like \code{"Staphylococcus aureus"}), an abbreviated name (like \code{"S. aureus"}), an abbreviation known in the field (like \code{"MRSA"}), or just a genus. Please see Examples.
@ -60,18 +60,19 @@ A microbial ID from this package (class: \code{mo}) typically looks like these e
| | | ----> subspecies, a 3-4 letter acronym | | | ----> subspecies, a 3-4 letter acronym
| | ----> species, a 3-4 letter acronym | | ----> species, a 3-4 letter acronym
| ----> genus, a 5-7 letter acronym, mostly without vowels | ----> genus, a 5-7 letter acronym, mostly without vowels
----> taxonomic kingdom: A (Archaea), AN (Animalia), B (Bacteria), C (Chromista), ----> taxonomic kingdom: A (Archaea), AN (Animalia), B (Bacteria),
F (Fungi), P (Protozoa) or PL (Plantae) C (Chromista), F (Fungi), P (Protozoa) or
PL (Plantae)
} }
Values that cannot be coered will be considered 'unknown' and have an MO code \code{UNKNOWN}. Values that cannot be coered will be considered 'unknown' and will get the MO code \code{UNKNOWN}.
Use the \code{\link{mo_property}_*} functions to get properties based on the returned code, see Examples. Use the \code{\link{mo_property}_*} functions to get properties based on the returned code, see Examples.
The algorithm uses data from the Catalogue of Life (see below) and from one other source (see \code{?microorganisms}). The algorithm uses data from the Catalogue of Life (see below) and from one other source (see \code{?microorganisms}).
\strong{Self-learning algoritm} \cr \strong{Self-learning algoritm} \cr
The \code{as.mo()} function gains experience from previously determined microbial IDs and learns from it. This drastically improves both speed and reliability. Use \code{clean_mo_history()} to reset the algorithms. Only experience from your current \code{AMR} package version is used. This is done because in the future the taxonomic tree (which is included in this package) may change for any organism and it consequently has to rebuild its knowledge. Usually, any guess after the first try runs 90-95\% faster than the first try. The algorithm saves its previous findings to \code{~/.Rhistory_mo}. The \code{as.mo()} function gains experience from previously determined microbial IDs and learns from it. This drastically improves both speed and reliability. Use \code{clean_mo_history()} to reset the algorithms. Only experience from your current \code{AMR} package version is used. This is done because in the future the taxonomic tree (which is included in this package) may change for any organism and it consequently has to rebuild its knowledge. Usually, any guess after the first try runs 80-95\% faster than the first try. The algorithm saves its previous findings to \code{~/.Rhistory_mo}.
\strong{Intelligent rules} \cr \strong{Intelligent rules} \cr
This function uses intelligent rules to help getting fast and logical results. It tries to find matches in this order: This function uses intelligent rules to help getting fast and logical results. It tries to find matches in this order:
@ -91,7 +92,7 @@ A couple of effects because of these rules:
This means that looking up human pathogenic microorganisms takes less time than looking up human non-pathogenic microorganisms. This means that looking up human pathogenic microorganisms takes less time than looking up human non-pathogenic microorganisms.
\strong{Uncertain results} \cr \strong{Uncertain results} \cr
The algorithm can additionally use three different levels of uncertainty to guess valid results. The default is \code{allow_uncertain = TRUE}, which is uqual to uncertainty level 2. Using \code{allow_uncertain = FALSE} will skip all of these additional rules: The algorithm can additionally use three different levels of uncertainty to guess valid results. The default is \code{allow_uncertain = TRUE}, which is equal to uncertainty level 2. Using \code{allow_uncertain = FALSE} will skip all of these additional rules:
\itemize{ \itemize{
\item{(uncertainty level 1): It tries to look for only matching genera} \item{(uncertainty level 1): It tries to look for only matching genera}
\item{(uncertainty level 1): It tries to look for previously accepted (but now invalid) taxonomic names} \item{(uncertainty level 1): It tries to look for previously accepted (but now invalid) taxonomic names}
@ -132,9 +133,11 @@ Group 2 probably contains all other microbial pathogens ever found in humans.
[1] Becker K \emph{et al.} \strong{Coagulase-Negative Staphylococci}. 2014. Clin Microbiol Rev. 27(4): 870926. \url{https://dx.doi.org/10.1128/CMR.00109-13} [1] Becker K \emph{et al.} \strong{Coagulase-Negative Staphylococci}. 2014. Clin Microbiol Rev. 27(4): 870926. \url{https://dx.doi.org/10.1128/CMR.00109-13}
[2] Lancefield RC \strong{A serological differentiation of human and other groups of hemolytic streptococci}. 1933. J Exp Med. 57(4): 57195. \url{https://dx.doi.org/10.1084/jem.57.4.571} [2] Becker K \emph{et al.} \strong{Implications of identifying the recently defined members of the S. aureus complex, S. argenteus and S. schweitzeri: A position paper of members of the ESCMID Study Group for staphylococci and Staphylococcal Diseases (ESGS).}. 2019. Clin Microbiol Infect. 2019 Mar 11. \url{https://doi.org/10.1016/j.cmi.2019.02.028}
[3] Catalogue of Life: Annual Checklist (public online taxonomic database), \url{www.catalogueoflife.org} (check included annual version with \code{\link{catalogue_of_life_version}()}). [3] Lancefield RC \strong{A serological differentiation of human and other groups of hemolytic streptococci}. 1933. J Exp Med. 57(4): 57195. \url{https://dx.doi.org/10.1084/jem.57.4.571}
[4] Catalogue of Life: Annual Checklist (public online taxonomic database), \url{www.catalogueoflife.org} (check included annual version with \code{\link{catalogue_of_life_version}()}).
} }
\section{Catalogue of Life}{ \section{Catalogue of Life}{

View File

@ -7,13 +7,13 @@
catalogue_of_life_version() catalogue_of_life_version()
} }
\value{ \value{
a \code{list}, invisibly a \code{list}, which prints in pretty format
} }
\description{ \description{
This function returns information about the included data from the Catalogue of Life. It also shows if the included version is their latest annual release. The Catalogue of Life releases their annual release in March each year. This function returns information about the included data from the Catalogue of Life. It also shows if the included version is their latest annual release. The Catalogue of Life releases their annual release in March each year.
} }
\details{ \details{
The list item \code{is_latest_annual_release} is based on the system date. The list item \code{...$catalogue_of_life$is_latest_annual_release} is based on the system date.
For DSMZ, see \code{?microorganisms}. For DSMZ, see \code{?microorganisms}.
} }

View File

@ -93,7 +93,7 @@ septic_patients \%>\%
S = count_S(cipr), S = count_S(cipr),
n1 = count_all(cipr), # the actual total; sum of all three n1 = count_all(cipr), # the actual total; sum of all three
n2 = n_rsi(cipr), # same - analogous to n_distinct n2 = n_rsi(cipr), # same - analogous to n_distinct
total = n()) # NOT the amount of tested isolates! total = n()) # NOT the number of tested isolates!
# Count co-resistance between amoxicillin/clav acid and gentamicin, # Count co-resistance between amoxicillin/clav acid and gentamicin,
# so we can see that combination therapy does a lot more than mono therapy. # so we can see that combination therapy does a lot more than mono therapy.

View File

@ -13,7 +13,7 @@
\alias{filter_glycopeptides} \alias{filter_glycopeptides}
\alias{filter_macrolides} \alias{filter_macrolides}
\alias{filter_tetracyclines} \alias{filter_tetracyclines}
\title{Filter on antibiotic class} \title{Filter isolates on result in antibiotic class}
\usage{ \usage{
filter_ab_class(tbl, ab_class, result = NULL, scope = "any", ...) filter_ab_class(tbl, ab_class, result = NULL, scope = "any", ...)
@ -42,7 +42,7 @@ filter_tetracyclines(tbl, result = NULL, scope = "any", ...)
\arguments{ \arguments{
\item{tbl}{a data set} \item{tbl}{a data set}
\item{ab_class}{an antimicrobial class, like \code{"carbapenems"}} \item{ab_class}{an antimicrobial class, like \code{"carbapenems"}. More specifically, this should be a text that can be found in a 4th level ATC group (chemical subgroup) or a 5th level ATC group (chemical substance), please see \href{https://www.whocc.no/atc/structure_and_principles/}{this explanation on the WHOCC website}.}
\item{result}{an antibiotic result: S, I or R (or a combination of more of them)} \item{result}{an antibiotic result: S, I or R (or a combination of more of them)}
@ -51,7 +51,7 @@ filter_tetracyclines(tbl, result = NULL, scope = "any", ...)
\item{...}{parameters passed on to \code{\link[dplyr]{filter_at}}} \item{...}{parameters passed on to \code{\link[dplyr]{filter_at}}}
} }
\description{ \description{
Filter on specific antibiotic variables based on their class (ATC groups). Filter isolates on results in specific antibiotic variables based on their class (ATC groups). This makes it easy to get a list of isolates that were tested for e.g. any aminoglycoside.
} }
\details{ \details{
The \code{\link{antibiotics}} data set will be searched for \code{ab_class} in the columns \code{atc_group1} and \code{atc_group2} (case-insensitive). Next, \code{tbl} will be checked for column names with a value in any abbreviations, codes or official names found in the \code{antibiotics} data set. The \code{\link{antibiotics}} data set will be searched for \code{ab_class} in the columns \code{atc_group1} and \code{atc_group2} (case-insensitive). Next, \code{tbl} will be checked for column names with a value in any abbreviations, codes or official names found in the \code{antibiotics} data set.
@ -77,8 +77,14 @@ septic_patients \%>\% filter_aminoglycosides("R", "all")
# filter on isolates that show resistance to # filter on isolates that show resistance to
# any aminoglycoside and any fluoroquinolone # any aminoglycoside and any fluoroquinolone
septic_patients \%>\% septic_patients \%>\%
filter_aminoglycosides("R", "any") \%>\% filter_aminoglycosides("R") \%>\%
filter_fluoroquinolones("R", "any") filter_fluoroquinolones("R")
# filter on isolates that show resistance to
# all aminoglycosides and all fluoroquinolones
septic_patients \%>\%
filter_aminoglycosides("R", "all") \%>\%
filter_fluoroquinolones("R", "all")
} }
\keyword{fillter_class} \keyword{fillter_class}
\keyword{filter} \keyword{filter}

View File

@ -111,9 +111,11 @@ This package contains the complete taxonomic tree of almost all microorganisms (
[1] Becker K \emph{et al.} \strong{Coagulase-Negative Staphylococci}. 2014. Clin Microbiol Rev. 27(4): 870926. \url{https://dx.doi.org/10.1128/CMR.00109-13} [1] Becker K \emph{et al.} \strong{Coagulase-Negative Staphylococci}. 2014. Clin Microbiol Rev. 27(4): 870926. \url{https://dx.doi.org/10.1128/CMR.00109-13}
[2] Lancefield RC \strong{A serological differentiation of human and other groups of hemolytic streptococci}. 1933. J Exp Med. 57(4): 57195. \url{https://dx.doi.org/10.1084/jem.57.4.571} [2] Becker K \emph{et al.} \strong{Implications of identifying the recently defined members of the S. aureus complex, S. argenteus and S. schweitzeri: A position paper of members of the ESCMID Study Group for staphylococci and Staphylococcal Diseases (ESGS).}. 2019. Clin Microbiol Infect. 2019 Mar 11. \url{https://doi.org/10.1016/j.cmi.2019.02.028}
[3] Catalogue of Life: Annual Checklist (public online taxonomic database), \url{www.catalogueoflife.org} (check included annual version with \code{\link{catalogue_of_life_version}()}). [3] Lancefield RC \strong{A serological differentiation of human and other groups of hemolytic streptococci}. 1933. J Exp Med. 57(4): 57195. \url{https://dx.doi.org/10.1084/jem.57.4.571}
[4] Catalogue of Life: Annual Checklist (public online taxonomic database), \url{www.catalogueoflife.org} (check included annual version with \code{\link{catalogue_of_life_version}()}).
} }
\section{Read more on our website!}{ \section{Read more on our website!}{

View File

@ -36,7 +36,7 @@ portion_df(data, translate_ab = getOption("get_antibiotic_names",
\arguments{ \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.} \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.}
\item{minimum}{the minimal amount of available isolates. Any number lower than \code{minimum} will return \code{NA} with a warning. The default number of \code{30} isolates is advised by the Clinical and Laboratory Standards Institute (CLSI) as best practice, see Source.} \item{minimum}{the minimum allowed number of available (tested) isolates. Any isolate count lower than \code{minimum} will return \code{NA} with a warning. The default number of \code{30} isolates is advised by the Clinical and Laboratory Standards Institute (CLSI) as best practice, see Source.}
\item{as_percent}{a logical to indicate whether the output must be returned as a hundred fold with \% sign (a character). A value of \code{0.123456} will then be returned as \code{"12.3\%"}.} \item{as_percent}{a logical to indicate whether the output must be returned as a hundred fold with \% sign (a character). A value of \code{0.123456} will then be returned as \code{"12.3\%"}.}
@ -52,7 +52,7 @@ portion_df(data, translate_ab = getOption("get_antibiotic_names",
Double or, when \code{as_percent = TRUE}, a character. Double or, when \code{as_percent = TRUE}, a character.
} }
\description{ \description{
These functions can be used to calculate the (co-)resistance of microbial isolates (i.e. percentage S, SI, I, IR or R). All functions support quasiquotation with pipes, can be used in \code{dplyr}s \code{\link[dplyr]{summarise}} and support grouped variables, see \emph{Examples}. These functions can be used to calculate the (co-)resistance of microbial isolates (i.e. percentage of S, SI, I, IR or R). All functions support quasiquotation with pipes, can be used in \code{dplyr}s \code{\link[dplyr]{summarise}} and support grouped variables, see \emph{Examples}.
\code{portion_R} and \code{portion_IR} can be used to calculate resistance, \code{portion_S} and \code{portion_SI} can be used to calculate susceptibility.\cr \code{portion_R} and \code{portion_IR} can be used to calculate resistance, \code{portion_S} and \code{portion_SI} can be used to calculate susceptibility.\cr
} }
@ -67,14 +67,14 @@ The old \code{\link{rsi}} function is still available for backwards compatibilit
\if{html}{ \if{html}{
\cr\cr \cr\cr
To calculate the probability (\emph{p}) of susceptibility of one antibiotic, we use this formula: To calculate the probability (\emph{p}) of susceptibility of one antibiotic, we use this formula:
\out{<div style="text-align: center">}\figure{mono_therapy.png}\out{</div>} \out{<div style="text-align: center;">}\figure{combi_therapy_2.png}\out{</div>}
To calculate the probability (\emph{p}) of susceptibility of more antibiotics (i.e. combination therapy), we need to check whether one of them has a susceptible result (as numerator) and count all cases where all antibiotics were tested (as denominator). \cr To calculate the probability (\emph{p}) of susceptibility of more antibiotics (i.e. combination therapy), we need to check whether one of them has a susceptible result (as numerator) and count all cases where all antibiotics were tested (as denominator). \cr
\cr \cr
For two antibiotics: For two antibiotics:
\out{<div style="text-align: center">}\figure{combi_therapy_2.png}\out{</div>} \out{<div style="text-align: center;">}\figure{combi_therapy_2.png}\out{</div>}
\cr \cr
For three antibiotics: For three antibiotics:
\out{<div style="text-align: center">}\figure{combi_therapy_3.png}\out{</div>} \out{<div style="text-align: center;">}\figure{combi_therapy_2.png}\out{</div>}
\cr \cr
And so on. And so on.
} }
@ -113,8 +113,9 @@ septic_patients \%>\%
summarise(R = portion_R(cipr, as_percent = TRUE), summarise(R = portion_R(cipr, as_percent = TRUE),
I = portion_I(cipr, as_percent = TRUE), I = portion_I(cipr, as_percent = TRUE),
S = portion_S(cipr, as_percent = TRUE), S = portion_S(cipr, as_percent = TRUE),
n = n_rsi(cipr), # works like n_distinct in dplyr n1 = count_all(cipr), # the actual total; sum of all three
total = n()) # NOT the amount of tested isolates! n2 = n_rsi(cipr), # same - analogous to n_distinct
total = n()) # NOT the number of tested isolates!
# Calculate co-resistance between amoxicillin/clav acid and gentamicin, # Calculate co-resistance between amoxicillin/clav acid and gentamicin,
# so we can see that combination therapy does a lot more than mono therapy: # so we can see that combination therapy does a lot more than mono therapy:

View File

@ -12,7 +12,7 @@ rsi(ab1, ab2 = NULL, interpretation = "IR", minimum = 30,
\item{interpretation}{antimicrobial interpretation to check for} \item{interpretation}{antimicrobial interpretation to check for}
\item{minimum}{the minimal amount of available isolates. Any number lower than \code{minimum} will return \code{NA} with a warning. The default number of \code{30} isolates is advised by the Clinical and Laboratory Standards Institute (CLSI) as best practice, see Source.} \item{minimum}{the minimum allowed number of available (tested) isolates. Any isolate count lower than \code{minimum} will return \code{NA} with a warning. The default number of \code{30} isolates is advised by the Clinical and Laboratory Standards Institute (CLSI) as best practice, see Source.}
\item{as_percent}{a logical to indicate whether the output must be returned as a hundred fold with \% sign (a character). A value of \code{0.123456} will then be returned as \code{"12.3\%"}.} \item{as_percent}{a logical to indicate whether the output must be returned as a hundred fold with \% sign (a character). A value of \code{0.123456} will then be returned as \code{"12.3\%"}.}

View File

@ -28,7 +28,7 @@ test_that("get_locale works", {
expect_identical(mo_fullname("CoNS", "en"), "Coagulase-negative Staphylococcus (CoNS)") expect_identical(mo_fullname("CoNS", "en"), "Coagulase-negative Staphylococcus (CoNS)")
expect_identical(mo_fullname("CoNS", "de"), "Koagulase-negative Staphylococcus (KNS)") expect_identical(mo_fullname("CoNS", "de"), "Koagulase-negative Staphylococcus (KNS)")
expect_identical(mo_fullname("CoNS", "nl"), "Coagulase-negatieve Staphylococcus (CNS)") expect_identical(mo_fullname("CoNS", "nl"), "Coagulase-negatieve Staphylococcus (CNS)")
expect_identical(mo_fullname("CoNS", "es"), "Staphylococcus coagulasa negativo (CoNS)") expect_identical(mo_fullname("CoNS", "es"), "Staphylococcus coagulasa negativo (SCN)")
expect_identical(mo_fullname("CoNS", "it"), "Staphylococcus negativo coagulasi (CoNS)") expect_identical(mo_fullname("CoNS", "it"), "Staphylococcus negativo coagulasi (CoNS)")
# expect_identical(mo_fullname("CoNS", "fr"), "Staphylococcus \u00e0 coagulase n\u00e9gative (CoNS)") # expect_identical(mo_fullname("CoNS", "fr"), "Staphylococcus \u00e0 coagulase n\u00e9gative (CoNS)")
expect_identical(mo_fullname("CoNS", "pt"), "Staphylococcus coagulase negativo (CoNS)") expect_identical(mo_fullname("CoNS", "pt"), "Staphylococcus coagulase negativo (CoNS)")

View File

@ -22,13 +22,23 @@
context("mo_history.R") context("mo_history.R")
test_that("mo_history works", { test_that("mo_history works", {
clean_mo_history() clean_mo_history(force = TRUE)
expect_equal(read_mo_history(force = TRUE), expect_equal(read_mo_history(force = TRUE),
NULL) NULL)
set_mo_history("testsubject", "B_ESCHR_COL", force = TRUE) expect_equal(as.character(suppressWarnings(as.mo("testsubject"))), "UNKNOWN")
expect_equal(get_mo_history("testsubject", force = TRUE),
set_mo_history("testsubject", "B_ESCHR_COL",
uncertainty_level = translate_allow_uncertain(TRUE),
force = TRUE)
expect_equal(get_mo_history("testsubject",
uncertainty_level = translate_allow_uncertain(TRUE),
force = TRUE),
"B_ESCHR_COL") "B_ESCHR_COL")
expect_equal(as.character(suppressWarnings(as.mo("testsubject"))), "B_ESCHR_COL")
expect_equal(colnames(read_mo_history(force = TRUE)), expect_equal(colnames(read_mo_history(force = TRUE)),
c("x", "mo", "package_version")) c("x", "mo", "uncertainty_level", "package_version"))
}) })

View File

@ -315,7 +315,7 @@ data_1st %>%
## Resistance percentages ## Resistance percentages
The functions `portion_R()`, `portion_RI()`, `portion_I()`, `portion_IS()` and `portion_S()` can be used to determine the portion of a specific antimicrobial outcome. They can be used on their own: The functions `portion_S()`, `portion_SI()`, `portion_I()`, `portion_IR()` and `portion_R()` can be used to determine the portion of a specific antimicrobial outcome. They can be used on their own:
```{r} ```{r}
data_1st %>% portion_IR(amox) data_1st %>% portion_IR(amox)